160 SUBROUTINE dchksp( DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR,
161 $ NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK,
170 INTEGER NMAX, NN, NNS, NOUT
171 DOUBLE PRECISION THRESH
175 INTEGER IWORK( * ), NSVAL( * ), NVAL( * )
176 DOUBLE PRECISION A( * ), AFAC( * ), AINV( * ), B( * ),
177 $ rwork( * ), work( * ), x( * ), xact( * )
183 DOUBLE PRECISION ZERO
184 PARAMETER ( ZERO = 0.0d+0 )
186 parameter( ntypes = 10 )
188 parameter( ntests = 8 )
191 LOGICAL TRFCON, ZEROT
192 CHARACTER DIST, PACKIT,
TYPE, UPLO, XTYPE
194 INTEGER I, I1, I2, IMAT, IN, INFO, IOFF, IRHS, IUPLO,
195 $ izero, j, k, kl, ku, lda, mode, n, nerrs,
196 $ nfail, nimat, npp, nrhs, nrun, nt
197 DOUBLE PRECISION ANORM, CNDNUM, RCOND, RCONDC
201 INTEGER ISEED( 4 ), ISEEDY( 4 )
202 DOUBLE PRECISION RESULT( NTESTS )
206 DOUBLE PRECISION DGET06, DLANSP
207 EXTERNAL lsame, dget06, dlansp
224 COMMON / infoc / infot, nunit, ok, lerr
225 COMMON / srnamc / srnamt
228 DATA iseedy / 1988, 1989, 1990, 1991 /
229 DATA uplos /
'U',
'L' /
235 path( 1: 1 ) =
'Double precision'
241 iseed( i ) = iseedy( i )
247 $
CALL derrsy( path, nout )
261 DO 160 imat = 1, nimat
265 IF( .NOT.dotype( imat ) )
270 zerot = imat.GE.3 .AND. imat.LE.6
271 IF( zerot .AND. n.LT.imat-2 )
277 uplo = uplos( iuplo )
278 IF( lsame( uplo,
'U' ) )
THEN
287 CALL dlatb4( path, imat, n, n,
TYPE, kl, ku, anorm, mode,
291 CALL dlatms( n, n, dist, iseed,
TYPE, rwork, mode,
292 $ cndnum, anorm, kl, ku, packit, a, lda, work,
298 CALL alaerh( path,
'DLATMS', info, 0, uplo, n, n, -1,
299 $ -1, -1, imat, nfail, nerrs, nout )
309 ELSE IF( imat.EQ.4 )
THEN
319 IF( iuplo.EQ.1 )
THEN
320 ioff = ( izero-1 )*izero / 2
321 DO 20 i = 1, izero - 1
331 DO 40 i = 1, izero - 1
342 IF( iuplo.EQ.1 )
THEN
373 CALL dcopy( npp, a, 1, afac, 1 )
375 CALL dsptrf( uplo, n, afac, iwork, info )
383 IF( iwork( k ).LT.0 )
THEN
384 IF( iwork( k ).NE.-k )
THEN
388 ELSE IF( iwork( k ).NE.k )
THEN
397 $
CALL alaerh( path,
'DSPTRF', info, k, uplo, n, n, -1,
398 $ -1, -1, imat, nfail, nerrs, nout )
408 CALL dspt01( uplo, n, a, afac, iwork, ainv, lda, rwork,
415 IF( .NOT.trfcon )
THEN
416 CALL dcopy( npp, afac, 1, ainv, 1 )
418 CALL dsptri( uplo, n, ainv, iwork, work, info )
423 $
CALL alaerh( path,
'DSPTRI', info, 0, uplo, n, n,
424 $ -1, -1, -1, imat, nfail, nerrs, nout )
426 CALL dppt03( uplo, n, a, ainv, work, lda, rwork,
427 $ rcondc, result( 2 ) )
435 IF( result( k ).GE.thresh )
THEN
436 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
437 $
CALL alahd( nout, path )
438 WRITE( nout, fmt = 9999 )uplo, n, imat, k,
459 CALL dlarhs( path, xtype, uplo,
' ', n, n, kl, ku,
460 $ nrhs, a, lda, xact, lda, b, lda, iseed,
462 CALL dlacpy(
'Full', n, nrhs, b, lda, x, lda )
465 CALL dsptrs( uplo, n, nrhs, afac, iwork, x, lda,
471 $
CALL alaerh( path,
'DSPTRS', info, 0, uplo, n, n,
472 $ -1, -1, nrhs, imat, nfail, nerrs,
475 CALL dlacpy(
'Full', n, nrhs, b, lda, work, lda )
476 CALL dppt02( uplo, n, nrhs, a, x, lda, work, lda,
477 $ rwork, result( 3 ) )
482 CALL dget04( n, nrhs, x, lda, xact, lda, rcondc,
489 CALL dsprfs( uplo, n, nrhs, a, afac, iwork, b, lda, x,
490 $ lda, rwork, rwork( nrhs+1 ), work,
491 $ iwork( n+1 ), info )
496 $
CALL alaerh( path,
'DSPRFS', info, 0, uplo, n, n,
497 $ -1, -1, nrhs, imat, nfail, nerrs,
500 CALL dget04( n, nrhs, x, lda, xact, lda, rcondc,
502 CALL dppt05( uplo, n, nrhs, a, b, lda, x, lda, xact,
503 $ lda, rwork, rwork( nrhs+1 ),
510 IF( result( k ).GE.thresh )
THEN
511 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
512 $
CALL alahd( nout, path )
513 WRITE( nout, fmt = 9998 )uplo, n, nrhs, imat,
525 anorm = dlansp(
'1', uplo, n, a, rwork )
527 CALL dspcon( uplo, n, afac, iwork, anorm, rcond, work,
528 $ iwork( n+1 ), info )
533 $
CALL alaerh( path,
'DSPCON', info, 0, uplo, n, n, -1,
534 $ -1, -1, imat, nfail, nerrs, nout )
536 result( 8 ) = dget06( rcond, rcondc )
540 IF( result( 8 ).GE.thresh )
THEN
541 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
542 $
CALL alahd( nout, path )
543 WRITE( nout, fmt = 9999 )uplo, n, imat, 8,
554 CALL alasum( path, nout, nfail, nrun, nerrs )
556 9999
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
', type ', i2,
', test ',
557 $ i2,
', ratio =', g12.5 )
558 9998
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
', NRHS=', i3,
', type ',
559 $ i2,
', 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 alaerh(path, subnam, info, infoe, opts, m, n, kl, ku, n5, imat, nfail, nerrs, nout)
ALAERH
subroutine alahd(iounit, path)
ALAHD
subroutine dchksp(dotype, nn, nval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
DCHKSP
subroutine derrsy(path, nunit)
DERRSY
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 dppt02(uplo, n, nrhs, a, x, ldx, b, ldb, rwork, resid)
DPPT02
subroutine dppt03(uplo, n, a, ainv, work, ldwork, rwork, rcond, resid)
DPPT03
subroutine dppt05(uplo, n, nrhs, ap, b, ldb, x, ldx, xact, ldxact, ferr, berr, reslts)
DPPT05
subroutine dspt01(uplo, n, a, afac, ipiv, c, ldc, rwork, resid)
DSPT01
subroutine dcopy(n, dx, incx, dy, incy)
DCOPY
subroutine dspcon(uplo, n, ap, ipiv, anorm, rcond, work, iwork, info)
DSPCON
subroutine dsprfs(uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx, ferr, berr, work, iwork, info)
DSPRFS
subroutine dsptrf(uplo, n, ap, ipiv, info)
DSPTRF
subroutine dsptri(uplo, n, ap, ipiv, work, info)
DSPTRI
subroutine dsptrs(uplo, n, nrhs, ap, ipiv, b, ldb, info)
DSPTRS
subroutine dlacpy(uplo, m, n, a, lda, b, ldb)
DLACPY copies all or part of one two-dimensional array to another.