54 SUBROUTINE schkgl( NIN, NOUT )
68 INTEGER LDA, LDB, LWORK
69 parameter ( lda = 20, ldb = 20, lwork = 6*lda )
71 parameter ( zero = 0.0e+0 )
74 INTEGER I, IHI, IHIIN, ILO, ILOIN, INFO, J, KNT, N,
76 REAL ANORM, BNORM, EPS, RMAX, VMAX
80 REAL A( lda, lda ), AIN( lda, lda ), B( ldb, ldb ),
81 $ bin( ldb, ldb ), lscale( lda ), lsclin( lda ),
82 $ rscale( lda ), rsclin( lda ), work( lwork )
86 EXTERNAL slamch, slange
103 eps = slamch(
'Precision' )
107 READ( nin, fmt = * )n
111 READ( nin, fmt = * )( a( i, j ), j = 1, n )
115 READ( nin, fmt = * )( b( i, j ), j = 1, n )
118 READ( nin, fmt = * )iloin, ihiin
120 READ( nin, fmt = * )( ain( i, j ), j = 1, n )
123 READ( nin, fmt = * )( bin( i, j ), j = 1, n )
126 READ( nin, fmt = * )( lsclin( i ), i = 1, n )
127 READ( nin, fmt = * )( rsclin( i ), i = 1, n )
129 anorm = slange(
'M', n, n, a, lda, work )
130 bnorm = slange(
'M', n, n, b, ldb, work )
134 CALL sggbal(
'B', n, a, lda, b, ldb, ilo, ihi, lscale, rscale,
142 IF( ilo.NE.iloin .OR. ihi.NE.ihiin )
THEN
150 vmax = max( vmax, abs( a( i, j )-ain( i, j ) ) )
151 vmax = max( vmax, abs( b( i, j )-bin( i, j ) ) )
156 vmax = max( vmax, abs( lscale( i )-lsclin( i ) ) )
157 vmax = max( vmax, abs( rscale( i )-rsclin( i ) ) )
160 vmax = vmax / ( eps*max( anorm, bnorm ) )
162 IF( vmax.GT.rmax )
THEN
171 WRITE( nout, fmt = 9999 )
172 9999
FORMAT( 1x,
'.. test output of SGGBAL .. ' )
174 WRITE( nout, fmt = 9998 )rmax
175 9998
FORMAT( 1x,
'value of largest test error = ', e12.3 )
176 WRITE( nout, fmt = 9997 )lmax( 1 )
177 9997
FORMAT( 1x,
'example number where info is not zero = ', i4 )
178 WRITE( nout, fmt = 9996 )lmax( 2 )
179 9996
FORMAT( 1x,
'example number where ILO or IHI wrong = ', i4 )
180 WRITE( nout, fmt = 9995 )lmax( 3 )
181 9995
FORMAT( 1x,
'example number having largest error = ', i4 )
182 WRITE( nout, fmt = 9994 )ninfo
183 9994
FORMAT( 1x,
'number of examples where info is not 0 = ', i4 )
184 WRITE( nout, fmt = 9993 )knt
185 9993
FORMAT( 1x,
'total number of examples tested = ', i4 )
subroutine sggbal(JOB, N, A, LDA, B, LDB, ILO, IHI, LSCALE, RSCALE, WORK, INFO)
SGGBAL
subroutine schkgl(NIN, NOUT)
SCHKGL