182 SUBROUTINE dchkge( DOTYPE, NM, MVAL, NN, NVAL, NNB, NBVAL, NNS,
183 $ NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B,
184 $ X, XACT, WORK, RWORK, IWORK, NOUT )
192 INTEGER NM, NMAX, NN, NNB, NNS, NOUT
193 DOUBLE PRECISION THRESH
197 INTEGER IWORK( * ), MVAL( * ), NBVAL( * ), NSVAL( * ),
199 DOUBLE PRECISION A( * ), AFAC( * ), AINV( * ), B( * ),
200 $ RWORK( * ), WORK( * ), X( * ), XACT( * )
206 DOUBLE PRECISION ONE, ZERO
207 PARAMETER ( ONE = 1.0d+0, zero = 0.0d+0 )
209 parameter( ntypes = 11 )
211 parameter( ntests = 8 )
213 parameter( ntran = 3 )
216 LOGICAL TRFCON, ZEROT
217 CHARACTER DIST, NORM, TRANS,
TYPE, XTYPE
219 INTEGER I, IM, IMAT, IN, INB, INFO, IOFF, IRHS, ITRAN,
220 $ izero, k, kl, ku, lda, lwork, m, mode, n, nb,
221 $ nerrs, nfail, nimat, nrhs, nrun, nt
222 DOUBLE PRECISION AINVNM, ANORM, ANORMI, ANORMO, CNDNUM, DUMMY,
223 $ RCOND, RCONDC, RCONDI, RCONDO
226 CHARACTER TRANSS( NTRAN )
227 INTEGER ISEED( 4 ), ISEEDY( 4 )
228 DOUBLE PRECISION RESULT( NTESTS )
231 DOUBLE PRECISION DGET06, DLANGE
232 EXTERNAL DGET06, DLANGE
249 COMMON / infoc / infot, nunit, ok, lerr
250 COMMON / srnamc / srnamt
253 DATA iseedy / 1988, 1989, 1990, 1991 / ,
254 $ transs /
'N',
'T',
'C' /
260 path( 1: 1 ) =
'Double precision'
266 iseed( i ) = iseedy( i )
273 $
CALL derrge( path, nout )
289 IF( m.LE.0 .OR. n.LE.0 )
292 DO 100 imat = 1, nimat
296 IF( .NOT.dotype( imat ) )
301 zerot = imat.GE.5 .AND. imat.LE.7
302 IF( zerot .AND. n.LT.imat-4 )
308 CALL dlatb4( path, imat, m, n,
TYPE, kl, ku, anorm, mode,
312 CALL dlatms( m, n, dist, iseed,
TYPE, rwork, mode,
313 $ cndnum, anorm, kl, ku,
'No packing', a, lda,
319 CALL alaerh( path,
'DLATMS', info, 0,
' ', m, n, -1,
320 $ -1, -1, imat, nfail, nerrs, nout )
330 ELSE IF( imat.EQ.6 )
THEN
333 izero = min( m, n ) / 2 + 1
335 ioff = ( izero-1 )*lda
341 CALL dlaset(
'Full', m, n-izero+1, zero, zero,
362 CALL dlacpy(
'Full', m, n, a, lda, afac, lda )
364 CALL dgetrf( m, n, afac, lda, iwork, info )
369 $
CALL alaerh( path,
'DGETRF', info, izero,
' ', m,
370 $ n, -1, -1, nb, imat, nfail, nerrs,
377 CALL dlacpy(
'Full', m, n, afac, lda, ainv, lda )
378 CALL dget01( m, n, a, lda, ainv, lda, iwork, rwork,
386 IF( m.EQ.n .AND. info.EQ.0 )
THEN
387 CALL dlacpy(
'Full', n, n, afac, lda, ainv, lda )
390 lwork = nmax*max( 3, nrhs )
391 CALL dgetri( n, ainv, lda, iwork, work, lwork,
397 $
CALL alaerh( path,
'DGETRI', info, 0,
' ', n, n,
398 $ -1, -1, nb, imat, nfail, nerrs,
405 CALL dget03( n, a, lda, ainv, lda, work, lda,
406 $ rwork, rcondo, result( 2 ) )
407 anormo = dlange(
'O', m, n, a, lda, rwork )
411 anormi = dlange(
'I', m, n, a, lda, rwork )
412 ainvnm = dlange(
'I', n, n, ainv, lda, rwork )
413 IF( anormi.LE.zero .OR. ainvnm.LE.zero )
THEN
416 rcondi = ( one / anormi ) / ainvnm
424 anormo = dlange(
'O', m, n, a, lda, rwork )
425 anormi = dlange(
'I', m, n, a, lda, rwork )
434 IF( result( k ).GE.thresh )
THEN
435 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
436 $
CALL alahd( nout, path )
437 WRITE( nout, fmt = 9999 )m, n, nb, imat, k,
448 IF( inb.GT.1 .OR. m.NE.n )
457 DO 50 itran = 1, ntran
458 trans = transs( itran )
459 IF( itran.EQ.1 )
THEN
469 CALL dlarhs( path, xtype,
' ', trans, n, n, kl,
470 $ ku, nrhs, a, lda, xact, lda, b,
474 CALL dlacpy(
'Full', n, nrhs, b, lda, x, lda )
476 CALL dgetrs( trans, n, nrhs, afac, lda, iwork,
482 $
CALL alaerh( path,
'DGETRS', info, 0, trans,
483 $ n, n, -1, -1, nrhs, imat, nfail,
486 CALL dlacpy(
'Full', n, nrhs, b, lda, work,
488 CALL dget02( trans, n, n, nrhs, a, lda, x, lda,
489 $ work, lda, rwork, result( 3 ) )
494 CALL dget04( n, nrhs, x, lda, xact, lda, rcondc,
502 CALL dgerfs( trans, n, nrhs, a, lda, afac, lda,
503 $ iwork, b, lda, x, lda, rwork,
504 $ rwork( nrhs+1 ), work,
505 $ iwork( n+1 ), info )
510 $
CALL alaerh( path,
'DGERFS', info, 0, trans,
511 $ n, n, -1, -1, nrhs, imat, nfail,
514 CALL dget04( n, nrhs, x, lda, xact, lda, rcondc,
516 CALL dget07( trans, n, nrhs, a, lda, b, lda, x,
517 $ lda, xact, lda, rwork, .true.,
518 $ rwork( nrhs+1 ), result( 6 ) )
524 IF( result( k ).GE.thresh )
THEN
525 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
526 $
CALL alahd( nout, path )
527 WRITE( nout, fmt = 9998 )trans, n, nrhs,
528 $ imat, k, result( k )
541 IF( itran.EQ.1 )
THEN
551 CALL dgecon( norm, n, afac, lda, anorm, rcond,
552 $ work, iwork( n+1 ), info )
557 $
CALL alaerh( path,
'DGECON', info, 0, norm, n,
558 $ n, -1, -1, -1, imat, nfail, nerrs,
565 result( 8 ) = dget06( rcond, rcondc )
570 IF( result( 8 ).GE.thresh )
THEN
571 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
572 $
CALL alahd( nout, path )
573 WRITE( nout, fmt = 9997 )norm, n, imat, 8,
586 CALL alasum( path, nout, nfail, nrun, nerrs )
588 9999
FORMAT(
' M = ', i5,
', N =', i5,
', NB =', i4,
', type ', i2,
589 $
', test(', i2,
') =', g12.5 )
590 9998
FORMAT(
' TRANS=''', a1,
''', N =', i5,
', NRHS=', i3,
', type ',
591 $ i2,
', test(', i2,
') =', g12.5 )
592 9997
FORMAT(
' NORM =''', a1,
''', N =', i5,
',', 10x,
' type ', i2,
593 $
', test(', i2,
') =', g12.5 )
subroutine alasum(type, nout, nfail, nrun, nerrs)
ALASUM
subroutine dget02(trans, m, n, nrhs, a, lda, x, ldx, b, ldb, rwork, resid)
DGET02
subroutine dlarhs(path, xtype, uplo, trans, m, n, kl, ku, nrhs, a, lda, x, ldx, b, ldb, iseed, info)
DLARHS
subroutine xlaenv(ispec, nvalue)
XLAENV
subroutine alaerh(path, subnam, info, infoe, opts, m, n, kl, ku, n5, imat, nfail, nerrs, nout)
ALAERH
subroutine alahd(iounit, path)
ALAHD
subroutine dchkge(dotype, nm, mval, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
DCHKGE
subroutine derrge(path, nunit)
DERRGE
subroutine dget01(m, n, a, lda, afac, ldafac, ipiv, rwork, resid)
DGET01
subroutine dget03(n, a, lda, ainv, ldainv, work, ldwork, rwork, rcond, resid)
DGET03
subroutine dget04(n, nrhs, x, ldx, xact, ldxact, rcond, resid)
DGET04
subroutine dget07(trans, n, nrhs, a, lda, b, ldb, x, ldx, xact, ldxact, ferr, chkferr, berr, reslts)
DGET07
subroutine dlatb4(path, imat, m, n, type, kl, ku, anorm, mode, cndnum, dist)
DLATB4
subroutine dlatms(m, n, dist, iseed, sym, d, mode, cond, dmax, kl, ku, pack, a, lda, work, info)
DLATMS
subroutine dgecon(norm, n, a, lda, anorm, rcond, work, iwork, info)
DGECON
subroutine dgerfs(trans, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x, ldx, ferr, berr, work, iwork, info)
DGERFS
subroutine dgetrf(m, n, a, lda, ipiv, info)
DGETRF
subroutine dgetri(n, a, lda, ipiv, work, lwork, info)
DGETRI
subroutine dgetrs(trans, n, nrhs, a, lda, ipiv, b, ldb, info)
DGETRS
subroutine dlacpy(uplo, m, n, a, lda, b, ldb)
DLACPY copies all or part of one two-dimensional array to another.
subroutine dlaset(uplo, m, n, alpha, beta, a, lda)
DLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.