160 SUBROUTINE dchkpp( 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 = 9 )
188 parameter( ntests = 8 )
192 CHARACTER DIST, PACKIT,
TYPE, UPLO, XTYPE
194 INTEGER I, IMAT, IN, INFO, IOFF, IRHS, IUPLO, IZERO, K,
195 $ kl, ku, lda, mode, n, nerrs, nfail, nimat, npp,
197 DOUBLE PRECISION ANORM, CNDNUM, RCOND, RCONDC
200 CHARACTER PACKS( 2 ), UPLOS( 2 )
201 INTEGER ISEED( 4 ), ISEEDY( 4 )
202 DOUBLE PRECISION RESULT( NTESTS )
205 DOUBLE PRECISION DGET06, DLANSP
206 EXTERNAL DGET06, DLANSP
220 COMMON / infoc / infot, nunit, ok, lerr
221 COMMON / srnamc / srnamt
227 DATA iseedy / 1988, 1989, 1990, 1991 /
228 DATA uplos /
'U',
'L' / , packs /
'C',
'R' /
234 path( 1: 1 ) =
'Double precision'
240 iseed( i ) = iseedy( i )
246 $
CALL derrpo( path, nout )
259 DO 100 imat = 1, nimat
263 IF( .NOT.dotype( imat ) )
268 zerot = imat.GE.3 .AND. imat.LE.5
269 IF( zerot .AND. n.LT.imat-2 )
275 uplo = uplos( iuplo )
276 packit = packs( iuplo )
281 CALL dlatb4( path, imat, n, n,
TYPE, kl, ku, anorm, mode,
285 CALL dlatms( n, n, dist, iseed,
TYPE, rwork, mode,
286 $ cndnum, anorm, kl, ku, packit, a, lda, work,
292 CALL alaerh( path,
'DLATMS', info, 0, uplo, n, n, -1,
293 $ -1, -1, imat, nfail, nerrs, nout )
303 ELSE IF( imat.EQ.4 )
THEN
311 IF( iuplo.EQ.1 )
THEN
312 ioff = ( izero-1 )*izero / 2
313 DO 20 i = 1, izero - 1
323 DO 40 i = 1, izero - 1
339 CALL dcopy( npp, a, 1, afac, 1 )
341 CALL dpptrf( uplo, n, afac, info )
345 IF( info.NE.izero )
THEN
346 CALL alaerh( path,
'DPPTRF', info, izero, uplo, n, n,
347 $ -1, -1, -1, imat, nfail, nerrs, nout )
359 CALL dcopy( npp, afac, 1, ainv, 1 )
360 CALL dppt01( uplo, n, a, ainv, rwork, result( 1 ) )
365 CALL dcopy( npp, afac, 1, ainv, 1 )
367 CALL dpptri( uplo, n, ainv, info )
372 $
CALL alaerh( path,
'DPPTRI', info, 0, uplo, n, n, -1,
373 $ -1, -1, imat, nfail, nerrs, nout )
375 CALL dppt03( uplo, n, a, ainv, work, lda, rwork, rcondc,
382 IF( result( k ).GE.thresh )
THEN
383 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
384 $
CALL alahd( nout, path )
385 WRITE( nout, fmt = 9999 )uplo, n, imat, k,
399 CALL dlarhs( path, xtype, uplo,
' ', n, n, kl, ku,
400 $ nrhs, a, lda, xact, lda, b, lda, iseed,
402 CALL dlacpy(
'Full', n, nrhs, b, lda, x, lda )
405 CALL dpptrs( uplo, n, nrhs, afac, x, lda, info )
410 $
CALL alaerh( path,
'DPPTRS', info, 0, uplo, n, n,
411 $ -1, -1, nrhs, imat, nfail, nerrs,
414 CALL dlacpy(
'Full', n, nrhs, b, lda, work, lda )
415 CALL dppt02( uplo, n, nrhs, a, x, lda, work, lda,
416 $ rwork, result( 3 ) )
421 CALL dget04( n, nrhs, x, lda, xact, lda, rcondc,
428 CALL dpprfs( uplo, n, nrhs, a, afac, b, lda, x, lda,
429 $ rwork, rwork( nrhs+1 ), work, iwork,
435 $
CALL alaerh( path,
'DPPRFS', info, 0, uplo, n, n,
436 $ -1, -1, nrhs, imat, nfail, nerrs,
439 CALL dget04( n, nrhs, x, lda, xact, lda, rcondc,
441 CALL dppt05( uplo, n, nrhs, a, b, lda, x, lda, xact,
442 $ lda, rwork, rwork( nrhs+1 ),
449 IF( result( k ).GE.thresh )
THEN
450 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
451 $
CALL alahd( nout, path )
452 WRITE( nout, fmt = 9998 )uplo, n, nrhs, imat,
463 anorm = dlansp(
'1', uplo, n, a, rwork )
465 CALL dppcon( uplo, n, afac, anorm, rcond, work, iwork,
471 $
CALL alaerh( path,
'DPPCON', info, 0, uplo, n, n, -1,
472 $ -1, -1, imat, nfail, nerrs, nout )
474 result( 8 ) = dget06( rcond, rcondc )
478 IF( result( 8 ).GE.thresh )
THEN
479 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
480 $
CALL alahd( nout, path )
481 WRITE( nout, fmt = 9999 )uplo, n, imat, 8,
492 CALL alasum( path, nout, nfail, nrun, nerrs )
494 9999
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
', type ', i2,
', test ',
495 $ i2,
', ratio =', g12.5 )
496 9998
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
', NRHS=', i3,
', type ',
497 $ 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 dchkpp(dotype, nn, nval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
DCHKPP
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 dppt01(uplo, n, a, afac, rwork, resid)
DPPT01
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 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 dppcon(uplo, n, ap, anorm, rcond, work, iwork, info)
DPPCON
subroutine dpprfs(uplo, n, nrhs, ap, afp, b, ldb, x, ldx, ferr, berr, work, iwork, info)
DPPRFS
subroutine dpptrf(uplo, n, ap, info)
DPPTRF
subroutine dpptri(uplo, n, ap, info)
DPPTRI
subroutine dpptrs(uplo, n, nrhs, ap, b, ldb, info)
DPPTRS