55 SUBROUTINE schkbl( NIN, NOUT )
70 parameter ( lda = 20 )
72 parameter ( zero = 0.0e+0 )
75 INTEGER I, IHI, IHIIN, ILO, ILOIN, INFO, J, KNT, N,
77 REAL ANORM, MEPS, RMAX, SFMIN, TEMP, VMAX
81 REAL A( lda, lda ), AIN( lda, lda ), DUMMY( 1 ),
82 $ scale( lda ), scalin( lda )
86 EXTERNAL slamch, slange
103 sfmin = slamch(
'S' )
108 READ( nin, fmt = * )n
112 READ( nin, fmt = * )( a( i, j ), j = 1, n )
115 READ( nin, fmt = * )iloin, ihiin
117 READ( nin, fmt = * )( ain( i, j ), j = 1, n )
119 READ( nin, fmt = * )( scalin( i ), i = 1, n )
121 anorm = slange(
'M', n, n, a, lda, dummy )
124 CALL sgebal(
'B', n, a, lda, ilo, ihi, scale, info )
131 IF( ilo.NE.iloin .OR. ihi.NE.ihiin )
THEN
138 temp = max( a( i, j ), ain( i, j ) )
139 temp = max( temp, sfmin )
140 vmax = max( vmax, abs( a( i, j )-ain( i, j ) ) / temp )
145 temp = max( scale( i ), scalin( i ) )
146 temp = max( temp, sfmin )
147 vmax = max( vmax, abs( scale( i )-scalin( i ) ) / temp )
151 IF( vmax.GT.rmax )
THEN
160 WRITE( nout, fmt = 9999 )
161 9999
FORMAT( 1x,
'.. test output of SGEBAL .. ' )
163 WRITE( nout, fmt = 9998 )rmax
164 9998
FORMAT( 1x,
'value of largest test error = ', e12.3 )
165 WRITE( nout, fmt = 9997 )lmax( 1 )
166 9997
FORMAT( 1x,
'example number where info is not zero = ', i4 )
167 WRITE( nout, fmt = 9996 )lmax( 2 )
168 9996
FORMAT( 1x,
'example number where ILO or IHI wrong = ', i4 )
169 WRITE( nout, fmt = 9995 )lmax( 3 )
170 9995
FORMAT( 1x,
'example number having largest error = ', i4 )
171 WRITE( nout, fmt = 9994 )ninfo
172 9994
FORMAT( 1x,
'number of examples where info is not 0 = ', i4 )
173 WRITE( nout, fmt = 9993 )knt
174 9993
FORMAT( 1x,
'total number of examples tested = ', i4 )
subroutine sgebal(JOB, N, A, LDA, ILO, IHI, SCALE, INFO)
SGEBAL
subroutine schkbl(NIN, NOUT)
SCHKBL