169 SUBROUTINE dchkpo( DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL,
170 $ THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X,
171 $ XACT, WORK, RWORK, IWORK, NOUT )
179 INTEGER NMAX, NN, NNB, NNS, NOUT
180 DOUBLE PRECISION THRESH
184 INTEGER IWORK( * ), NBVAL( * ), NSVAL( * ), NVAL( * )
185 DOUBLE PRECISION A( * ), AFAC( * ), AINV( * ), B( * ),
186 $ rwork( * ), work( * ), x( * ), xact( * )
192 DOUBLE PRECISION ZERO
193 PARAMETER ( ZERO = 0.0d+0 )
195 parameter( ntypes = 9 )
197 parameter( ntests = 8 )
201 CHARACTER DIST,
TYPE, UPLO, XTYPE
203 INTEGER I, IMAT, IN, INB, INFO, IOFF, IRHS, IUPLO,
204 $ izero, k, kl, ku, lda, mode, n, nb, nerrs,
205 $ nfail, nimat, nrhs, nrun
206 DOUBLE PRECISION ANORM, CNDNUM, RCOND, RCONDC
210 INTEGER ISEED( 4 ), ISEEDY( 4 )
211 DOUBLE PRECISION RESULT( NTESTS )
214 DOUBLE PRECISION DGET06, DLANSY
215 EXTERNAL DGET06, DLANSY
229 COMMON / infoc / infot, nunit, ok, lerr
230 COMMON / srnamc / srnamt
236 DATA iseedy / 1988, 1989, 1990, 1991 /
237 DATA uplos /
'U',
'L' /
243 path( 1: 1 ) =
'Double precision'
249 iseed( i ) = iseedy( i )
255 $
CALL derrpo( path, nout )
270 DO 110 imat = 1, nimat
274 IF( .NOT.dotype( imat ) )
279 zerot = imat.GE.3 .AND. imat.LE.5
280 IF( zerot .AND. n.LT.imat-2 )
286 uplo = uplos( iuplo )
291 CALL dlatb4( path, imat, n, n,
TYPE, kl, ku, anorm, mode,
295 CALL dlatms( n, n, dist, iseed,
TYPE, rwork, mode,
296 $ cndnum, anorm, kl, ku, uplo, a, lda, work,
302 CALL alaerh( path,
'DLATMS', info, 0, uplo, n, n, -1,
303 $ -1, -1, imat, nfail, nerrs, nout )
313 ELSE IF( imat.EQ.4 )
THEN
318 ioff = ( izero-1 )*lda
322 IF( iuplo.EQ.1 )
THEN
323 DO 20 i = 1, izero - 1
333 DO 40 i = 1, izero - 1
354 CALL dlacpy( uplo, n, n, a, lda, afac, lda )
356 CALL dpotrf( uplo, n, afac, lda, info )
360 IF( info.NE.izero )
THEN
361 CALL alaerh( path,
'DPOTRF', info, izero, uplo, n,
362 $ n, -1, -1, nb, imat, nfail, nerrs,
375 CALL dlacpy( uplo, n, n, afac, lda, ainv, lda )
376 CALL dpot01( uplo, n, a, lda, ainv, lda, rwork,
382 CALL dlacpy( uplo, n, n, afac, lda, ainv, lda )
384 CALL dpotri( uplo, n, ainv, lda, info )
389 $
CALL alaerh( path,
'DPOTRI', info, 0, uplo, n, n,
390 $ -1, -1, -1, imat, nfail, nerrs, nout )
392 CALL dpot03( uplo, n, a, lda, ainv, lda, work, lda,
393 $ rwork, rcondc, result( 2 ) )
399 IF( result( k ).GE.thresh )
THEN
400 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
401 $
CALL alahd( nout, path )
402 WRITE( nout, fmt = 9999 )uplo, n, nb, imat, k,
422 CALL dlarhs( path, xtype, uplo,
' ', n, n, kl, ku,
423 $ nrhs, a, lda, xact, lda, b, lda,
425 CALL dlacpy(
'Full', n, nrhs, b, lda, x, lda )
428 CALL dpotrs( uplo, n, nrhs, afac, lda, x, lda,
434 $
CALL alaerh( path,
'DPOTRS', info, 0, uplo, n,
435 $ n, -1, -1, nrhs, imat, nfail,
438 CALL dlacpy(
'Full', n, nrhs, b, lda, work, lda )
439 CALL dpot02( uplo, n, nrhs, a, lda, x, lda, work,
440 $ lda, rwork, result( 3 ) )
445 CALL dget04( n, nrhs, x, lda, xact, lda, rcondc,
452 CALL dporfs( uplo, n, nrhs, a, lda, afac, lda, b,
453 $ lda, x, lda, rwork, rwork( nrhs+1 ),
454 $ work, iwork, info )
459 $
CALL alaerh( path,
'DPORFS', info, 0, uplo, n,
460 $ n, -1, -1, nrhs, imat, nfail,
463 CALL dget04( n, nrhs, x, lda, xact, lda, rcondc,
465 CALL dpot05( uplo, n, nrhs, a, lda, b, lda, x, lda,
466 $ xact, lda, rwork, rwork( nrhs+1 ),
473 IF( result( k ).GE.thresh )
THEN
474 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
475 $
CALL alahd( nout, path )
476 WRITE( nout, fmt = 9998 )uplo, n, nrhs,
477 $ imat, k, result( k )
487 anorm = dlansy(
'1', uplo, n, a, lda, rwork )
489 CALL dpocon( uplo, n, afac, lda, anorm, rcond, work,
495 $
CALL alaerh( path,
'DPOCON', info, 0, uplo, n, n,
496 $ -1, -1, -1, imat, nfail, nerrs, nout )
498 result( 8 ) = dget06( rcond, rcondc )
502 IF( result( 8 ).GE.thresh )
THEN
503 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
504 $
CALL alahd( nout, path )
505 WRITE( nout, fmt = 9997 )uplo, n, imat, 8,
517 CALL alasum( path, nout, nfail, nrun, nerrs )
519 9999
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
', NB =', i4,
', type ',
520 $ i2,
', test ', i2,
', ratio =', g12.5 )
521 9998
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
', NRHS=', i3,
', type ',
522 $ i2,
', test(', i2,
') =', g12.5 )
523 9997
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
',', 10x,
' type ', i2,
524 $
', test(', i2,
') =', g12.5 )
subroutine alasum(type, nout, nfail, nrun, nerrs)
ALASUM
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 dchkpo(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
DCHKPO
subroutine derrpo(path, nunit)
DERRPO
subroutine dget04(n, nrhs, x, ldx, xact, ldxact, rcond, resid)
DGET04
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 dpot01(uplo, n, a, lda, afac, ldafac, rwork, resid)
DPOT01
subroutine dpot02(uplo, n, nrhs, a, lda, x, ldx, b, ldb, rwork, resid)
DPOT02
subroutine dpot03(uplo, n, a, lda, ainv, ldainv, work, ldwork, rwork, rcond, resid)
DPOT03
subroutine dpot05(uplo, n, nrhs, a, lda, b, ldb, x, ldx, xact, ldxact, ferr, berr, reslts)
DPOT05
subroutine dlacpy(uplo, m, n, a, lda, b, ldb)
DLACPY copies all or part of one two-dimensional array to another.
subroutine dpocon(uplo, n, a, lda, anorm, rcond, work, iwork, info)
DPOCON
subroutine dporfs(uplo, n, nrhs, a, lda, af, ldaf, b, ldb, x, ldx, ferr, berr, work, iwork, info)
DPORFS
subroutine dpotrf(uplo, n, a, lda, info)
DPOTRF
subroutine dpotri(uplo, n, a, lda, info)
DPOTRI
subroutine dpotrs(uplo, n, nrhs, a, lda, b, ldb, info)
DPOTRS