154 SUBROUTINE dchktp( DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR,
155 $ NMAX, AP, AINVP, B, X, XACT, WORK, RWORK,
164 INTEGER NMAX, NN, NNS, NOUT
165 DOUBLE PRECISION THRESH
169 INTEGER IWORK( * ), NSVAL( * ), NVAL( * )
170 DOUBLE PRECISION AINVP( * ), AP( * ), B( * ), RWORK( * ),
171 $ work( * ), x( * ), xact( * )
177 INTEGER NTYPE1, NTYPES
178 PARAMETER ( NTYPE1 = 10, ntypes = 18 )
180 parameter( ntests = 9 )
182 parameter( ntran = 3 )
183 DOUBLE PRECISION ONE, ZERO
184 parameter( one = 1.0d+0, zero = 0.0d+0 )
187 CHARACTER DIAG, NORM, TRANS, UPLO, XTYPE
189 INTEGER I, IDIAG, IMAT, IN, INFO, IRHS, ITRAN, IUPLO,
190 $ k, lap, lda, n, nerrs, nfail, nrhs, nrun
191 DOUBLE PRECISION AINVNM, ANORM, RCOND, RCONDC, RCONDI, RCONDO,
195 CHARACTER TRANSS( NTRAN ), UPLOS( 2 )
196 INTEGER ISEED( 4 ), ISEEDY( 4 )
197 DOUBLE PRECISION RESULT( NTESTS )
201 DOUBLE PRECISION DLANTP
202 EXTERNAL lsame, dlantp
213 INTEGER INFOT, IOUNIT
216 COMMON / infoc / infot, iounit, ok, lerr
217 COMMON / srnamc / srnamt
223 DATA iseedy / 1988, 1989, 1990, 1991 /
224 DATA uplos /
'U',
'L' / , transs /
'N',
'T',
'C' /
230 path( 1: 1 ) =
'Double precision'
236 iseed( i ) = iseedy( i )
242 $
CALL derrtr( path, nout )
251 lap = lda*( lda+1 ) / 2
254 DO 70 imat = 1, ntype1
258 IF( .NOT.dotype( imat ) )
265 uplo = uplos( iuplo )
270 CALL dlattp( imat, uplo,
'No transpose', diag, iseed, n,
271 $ ap, x, work, info )
275 IF( lsame( diag,
'N' ) )
THEN
285 $
CALL dcopy( lap, ap, 1, ainvp, 1 )
287 CALL dtptri( uplo, diag, n, ainvp, info )
292 $
CALL alaerh( path,
'DTPTRI', info, 0, uplo // diag, n,
293 $ n, -1, -1, -1, imat, nfail, nerrs, nout )
297 anorm = dlantp(
'I', uplo, diag, n, ap, rwork )
298 ainvnm = dlantp(
'I', uplo, diag, n, ainvp, rwork )
299 IF( anorm.LE.zero .OR. ainvnm.LE.zero )
THEN
302 rcondi = ( one / anorm ) / ainvnm
308 CALL dtpt01( uplo, diag, n, ap, ainvp, rcondo, rwork,
313 IF( result( 1 ).GE.thresh )
THEN
314 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
315 $
CALL alahd( nout, path )
316 WRITE( nout, fmt = 9999 )uplo, diag, n, imat, 1,
326 DO 30 itran = 1, ntran
330 trans = transs( itran )
331 IF( itran.EQ.1 )
THEN
343 CALL dlarhs( path, xtype, uplo, trans, n, n, 0,
344 $ idiag, nrhs, ap, lap, xact, lda, b,
347 CALL dlacpy(
'Full', n, nrhs, b, lda, x, lda )
350 CALL dtptrs( uplo, trans, diag, n, nrhs, ap, x,
356 $
CALL alaerh( path,
'DTPTRS', info, 0,
357 $ uplo // trans // diag, n, n, -1,
358 $ -1, -1, imat, nfail, nerrs, nout )
360 CALL dtpt02( uplo, trans, diag, n, nrhs, ap, x,
361 $ lda, b, lda, work, result( 2 ) )
366 CALL dget04( n, nrhs, x, lda, xact, lda, rcondc,
374 CALL dtprfs( uplo, trans, diag, n, nrhs, ap, b,
375 $ lda, x, lda, rwork, rwork( nrhs+1 ),
376 $ work, iwork, info )
381 $
CALL alaerh( path,
'DTPRFS', info, 0,
382 $ uplo // trans // diag, n, n, -1,
383 $ -1, nrhs, imat, nfail, nerrs,
386 CALL dget04( n, nrhs, x, lda, xact, lda, rcondc,
388 CALL dtpt05( uplo, trans, diag, n, nrhs, ap, b,
389 $ lda, x, lda, xact, lda, rwork,
390 $ rwork( nrhs+1 ), result( 5 ) )
396 IF( result( k ).GE.thresh )
THEN
397 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
398 $
CALL alahd( nout, path )
399 WRITE( nout, fmt = 9998 )uplo, trans, diag,
400 $ n, nrhs, imat, k, result( k )
412 IF( itran.EQ.1 )
THEN
421 CALL dtpcon( norm, uplo, diag, n, ap, rcond, work,
427 $
CALL alaerh( path,
'DTPCON', info, 0,
428 $ norm // uplo // diag, n, n, -1, -1,
429 $ -1, imat, nfail, nerrs, nout )
431 CALL dtpt06( rcond, rcondc, uplo, diag, n, ap, rwork,
436 IF( result( 7 ).GE.thresh )
THEN
437 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
438 $
CALL alahd( nout, path )
439 WRITE( nout, fmt = 9997 )
'DTPCON', norm, uplo,
440 $ diag, n, imat, 7, result( 7 )
450 DO 100 imat = ntype1 + 1, ntypes
454 IF( .NOT.dotype( imat ) )
461 uplo = uplos( iuplo )
462 DO 80 itran = 1, ntran
466 trans = transs( itran )
471 CALL dlattp( imat, uplo, trans, diag, iseed, n, ap, x,
478 CALL dcopy( n, x, 1, b, 1 )
479 CALL dlatps( uplo, trans, diag,
'N', n, ap, b, scale,
485 $
CALL alaerh( path,
'DLATPS', info, 0,
486 $ uplo // trans // diag //
'N', n, n,
487 $ -1, -1, -1, imat, nfail, nerrs, nout )
489 CALL dtpt03( uplo, trans, diag, n, 1, ap, scale,
490 $ rwork, one, b, lda, x, lda, work,
496 CALL dcopy( n, x, 1, b( n+1 ), 1 )
497 CALL dlatps( uplo, trans, diag,
'Y', n, ap, b( n+1 ),
498 $ scale, rwork, info )
503 $
CALL alaerh( path,
'DLATPS', info, 0,
504 $ uplo // trans // diag //
'Y', n, n,
505 $ -1, -1, -1, imat, nfail, nerrs, nout )
507 CALL dtpt03( uplo, trans, diag, n, 1, ap, scale,
508 $ rwork, one, b( n+1 ), lda, x, lda, work,
514 IF( result( 8 ).GE.thresh )
THEN
515 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
516 $
CALL alahd( nout, path )
517 WRITE( nout, fmt = 9996 )
'DLATPS', uplo, trans,
518 $ diag,
'N', n, imat, 8, result( 8 )
521 IF( result( 9 ).GE.thresh )
THEN
522 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
523 $
CALL alahd( nout, path )
524 WRITE( nout, fmt = 9996 )
'DLATPS', uplo, trans,
525 $ diag,
'Y', n, imat, 9, result( 9 )
536 CALL alasum( path, nout, nfail, nrun, nerrs )
538 9999
FORMAT(
' UPLO=''', a1,
''', DIAG=''', a1,
''', N=', i5,
539 $
', type ', i2,
', test(', i2,
')= ', g12.5 )
540 9998
FORMAT(
' UPLO=''', a1,
''', TRANS=''', a1,
''', DIAG=''', a1,
541 $
''', N=', i5,
''', NRHS=', i5,
', type ', i2,
', test(',
543 9997
FORMAT( 1x, a,
'( ''', a1,
''', ''', a1,
''', ''', a1,
''',',
544 $ i5,
', ... ), type ', i2,
', test(', i2,
')=', g12.5 )
545 9996
FORMAT( 1x, a,
'( ''', a1,
''', ''', a1,
''', ''', a1,
''', ''',
546 $ a1,
''',', i5,
', ... ), type ', i2,
', test(', i2,
')=',
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 dchktp(dotype, nn, nval, nns, nsval, thresh, tsterr, nmax, ap, ainvp, b, x, xact, work, rwork, iwork, nout)
DCHKTP
subroutine derrtr(path, nunit)
DERRTR
subroutine dget04(n, nrhs, x, ldx, xact, ldxact, rcond, resid)
DGET04
subroutine dlattp(imat, uplo, trans, diag, iseed, n, a, b, work, info)
DLATTP
subroutine dtpt01(uplo, diag, n, ap, ainvp, rcond, work, resid)
DTPT01
subroutine dtpt02(uplo, trans, diag, n, nrhs, ap, x, ldx, b, ldb, work, resid)
DTPT02
subroutine dtpt03(uplo, trans, diag, n, nrhs, ap, scale, cnorm, tscal, x, ldx, b, ldb, work, resid)
DTPT03
subroutine dtpt05(uplo, trans, diag, n, nrhs, ap, b, ldb, x, ldx, xact, ldxact, ferr, berr, reslts)
DTPT05
subroutine dtpt06(rcond, rcondc, uplo, diag, n, ap, work, rat)
DTPT06
subroutine dcopy(n, dx, incx, dy, incy)
DCOPY
subroutine dlacpy(uplo, m, n, a, lda, b, ldb)
DLACPY copies all or part of one two-dimensional array to another.
subroutine dlatps(uplo, trans, diag, normin, n, ap, x, scale, cnorm, info)
DLATPS solves a triangular system of equations with the matrix held in packed storage.
subroutine dtpcon(norm, uplo, diag, n, ap, rcond, work, iwork, info)
DTPCON
subroutine dtprfs(uplo, trans, diag, n, nrhs, ap, b, ldb, x, ldx, ferr, berr, work, iwork, info)
DTPRFS
subroutine dtptri(uplo, diag, n, ap, info)
DTPTRI
subroutine dtptrs(uplo, trans, diag, n, nrhs, ap, b, ldb, info)
DTPTRS