160 SUBROUTINE schkpp( DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR,
161 $ NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK,
170 INTEGER NMAX, NN, NNS, NOUT
175 INTEGER IWORK( * ), NSVAL( * ), NVAL( * )
176 REAL A( * ), AFAC( * ), AINV( * ), B( * ),
177 $ rwork( * ), work( * ), x( * ), xact( * )
184 PARAMETER ( ZERO = 0.0e+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 REAL ANORM, CNDNUM, RCOND, RCONDC
200 CHARACTER PACKS( 2 ), UPLOS( 2 )
201 INTEGER ISEED( 4 ), ISEEDY( 4 )
202 REAL RESULT( NTESTS )
206 EXTERNAL SGET06, SLANSP
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 ) =
'Single precision'
240 iseed( i ) = iseedy( i )
246 $
CALL serrpo( 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 slatb4( path, imat, n, n,
TYPE, kl, ku, anorm, mode,
285 CALL slatms( n, n, dist, iseed,
TYPE, rwork, mode,
286 $ cndnum, anorm, kl, ku, packit, a, lda, work,
292 CALL alaerh( path,
'SLATMS', 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 scopy( npp, a, 1, afac, 1 )
341 CALL spptrf( uplo, n, afac, info )
345 IF( info.NE.izero )
THEN
346 CALL alaerh( path,
'SPPTRF', info, izero, uplo, n, n,
347 $ -1, -1, -1, imat, nfail, nerrs, nout )
359 CALL scopy( npp, afac, 1, ainv, 1 )
360 CALL sppt01( uplo, n, a, ainv, rwork, result( 1 ) )
365 CALL scopy( npp, afac, 1, ainv, 1 )
367 CALL spptri( uplo, n, ainv, info )
372 $
CALL alaerh( path,
'SPPTRI', info, 0, uplo, n, n, -1,
373 $ -1, -1, imat, nfail, nerrs, nout )
375 CALL sppt03( 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 slarhs( path, xtype, uplo,
' ', n, n, kl, ku,
400 $ nrhs, a, lda, xact, lda, b, lda, iseed,
402 CALL slacpy(
'Full', n, nrhs, b, lda, x, lda )
405 CALL spptrs( uplo, n, nrhs, afac, x, lda, info )
410 $
CALL alaerh( path,
'SPPTRS', info, 0, uplo, n, n,
411 $ -1, -1, nrhs, imat, nfail, nerrs,
414 CALL slacpy(
'Full', n, nrhs, b, lda, work, lda )
415 CALL sppt02( uplo, n, nrhs, a, x, lda, work, lda,
416 $ rwork, result( 3 ) )
421 CALL sget04( n, nrhs, x, lda, xact, lda, rcondc,
428 CALL spprfs( uplo, n, nrhs, a, afac, b, lda, x, lda,
429 $ rwork, rwork( nrhs+1 ), work, iwork,
435 $
CALL alaerh( path,
'SPPRFS', info, 0, uplo, n, n,
436 $ -1, -1, nrhs, imat, nfail, nerrs,
439 CALL sget04( n, nrhs, x, lda, xact, lda, rcondc,
441 CALL sppt05( 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 = slansp(
'1', uplo, n, a, rwork )
465 CALL sppcon( uplo, n, afac, anorm, rcond, work, iwork,
471 $
CALL alaerh( path,
'SPPCON', info, 0, uplo, n, n, -1,
472 $ -1, -1, imat, nfail, nerrs, nout )
474 result( 8 ) = sget06( 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 slarhs(path, xtype, uplo, trans, m, n, kl, ku, nrhs, a, lda, x, ldx, b, ldb, iseed, info)
SLARHS
subroutine alaerh(path, subnam, info, infoe, opts, m, n, kl, ku, n5, imat, nfail, nerrs, nout)
ALAERH
subroutine alahd(iounit, path)
ALAHD
subroutine scopy(n, sx, incx, sy, incy)
SCOPY
subroutine slacpy(uplo, m, n, a, lda, b, ldb)
SLACPY copies all or part of one two-dimensional array to another.
subroutine sppcon(uplo, n, ap, anorm, rcond, work, iwork, info)
SPPCON
subroutine spprfs(uplo, n, nrhs, ap, afp, b, ldb, x, ldx, ferr, berr, work, iwork, info)
SPPRFS
subroutine spptrf(uplo, n, ap, info)
SPPTRF
subroutine spptri(uplo, n, ap, info)
SPPTRI
subroutine spptrs(uplo, n, nrhs, ap, b, ldb, info)
SPPTRS
subroutine schkpp(dotype, nn, nval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
SCHKPP
subroutine serrpo(path, nunit)
SERRPO
subroutine sget04(n, nrhs, x, ldx, xact, ldxact, rcond, resid)
SGET04
subroutine slatb4(path, imat, m, n, type, kl, ku, anorm, mode, cndnum, dist)
SLATB4
subroutine slatms(m, n, dist, iseed, sym, d, mode, cond, dmax, kl, ku, pack, a, lda, work, info)
SLATMS
subroutine sppt01(uplo, n, a, afac, rwork, resid)
SPPT01
subroutine sppt02(uplo, n, nrhs, a, x, ldx, b, ldb, rwork, resid)
SPPT02
subroutine sppt03(uplo, n, a, ainv, work, ldwork, rwork, rcond, resid)
SPPT03
subroutine sppt05(uplo, n, nrhs, ap, b, ldb, x, ldx, xact, ldxact, ferr, berr, reslts)
SPPT05