169 SUBROUTINE schkpo( 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
184 INTEGER IWORK( * ), NBVAL( * ), NSVAL( * ), NVAL( * )
185 REAL A( * ), AFAC( * ), AINV( * ), B( * ),
186 $ rwork( * ), work( * ), x( * ), xact( * )
193 PARAMETER ( ZERO = 0.0e+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 REAL ANORM, CNDNUM, RCOND, RCONDC
210 INTEGER ISEED( 4 ), ISEEDY( 4 )
211 REAL RESULT( NTESTS )
215 EXTERNAL SGET06, SLANSY
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 ) =
'Single precision'
249 iseed( i ) = iseedy( i )
255 $
CALL serrpo( 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 slatb4( path, imat, n, n,
TYPE, kl, ku, anorm, mode,
295 CALL slatms( n, n, dist, iseed,
TYPE, rwork, mode,
296 $ cndnum, anorm, kl, ku, uplo, a, lda, work,
302 CALL alaerh( path,
'SLATMS', 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 slacpy( uplo, n, n, a, lda, afac, lda )
356 CALL spotrf( uplo, n, afac, lda, info )
360 IF( info.NE.izero )
THEN
361 CALL alaerh( path,
'SPOTRF', info, izero, uplo, n,
362 $ n, -1, -1, nb, imat, nfail, nerrs,
375 CALL slacpy( uplo, n, n, afac, lda, ainv, lda )
376 CALL spot01( uplo, n, a, lda, ainv, lda, rwork,
382 CALL slacpy( uplo, n, n, afac, lda, ainv, lda )
384 CALL spotri( uplo, n, ainv, lda, info )
389 $
CALL alaerh( path,
'SPOTRI', info, 0, uplo, n, n,
390 $ -1, -1, -1, imat, nfail, nerrs, nout )
392 CALL spot03( 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 slarhs( path, xtype, uplo,
' ', n, n, kl, ku,
423 $ nrhs, a, lda, xact, lda, b, lda,
425 CALL slacpy(
'Full', n, nrhs, b, lda, x, lda )
428 CALL spotrs( uplo, n, nrhs, afac, lda, x, lda,
434 $
CALL alaerh( path,
'SPOTRS', info, 0, uplo, n,
435 $ n, -1, -1, nrhs, imat, nfail,
438 CALL slacpy(
'Full', n, nrhs, b, lda, work, lda )
439 CALL spot02( uplo, n, nrhs, a, lda, x, lda, work,
440 $ lda, rwork, result( 3 ) )
445 CALL sget04( n, nrhs, x, lda, xact, lda, rcondc,
452 CALL sporfs( uplo, n, nrhs, a, lda, afac, lda, b,
453 $ lda, x, lda, rwork, rwork( nrhs+1 ),
454 $ work, iwork, info )
459 $
CALL alaerh( path,
'SPORFS', info, 0, uplo, n,
460 $ n, -1, -1, nrhs, imat, nfail,
463 CALL sget04( n, nrhs, x, lda, xact, lda, rcondc,
465 CALL spot05( 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 = slansy(
'1', uplo, n, a, lda, rwork )
489 CALL spocon( uplo, n, afac, lda, anorm, rcond, work,
495 $
CALL alaerh( path,
'SPOCON', info, 0, uplo, n, n,
496 $ -1, -1, -1, imat, nfail, nerrs, nout )
498 result( 8 ) = sget06( 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 slarhs(path, xtype, uplo, trans, m, n, kl, ku, nrhs, a, lda, x, ldx, b, ldb, iseed, info)
SLARHS
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 slacpy(uplo, m, n, a, lda, b, ldb)
SLACPY copies all or part of one two-dimensional array to another.
subroutine spocon(uplo, n, a, lda, anorm, rcond, work, iwork, info)
SPOCON
subroutine sporfs(uplo, n, nrhs, a, lda, af, ldaf, b, ldb, x, ldx, ferr, berr, work, iwork, info)
SPORFS
subroutine spotrf(uplo, n, a, lda, info)
SPOTRF
subroutine spotri(uplo, n, a, lda, info)
SPOTRI
subroutine spotrs(uplo, n, nrhs, a, lda, b, ldb, info)
SPOTRS
subroutine schkpo(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
SCHKPO
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 spot01(uplo, n, a, lda, afac, ldafac, rwork, resid)
SPOT01
subroutine spot02(uplo, n, nrhs, a, lda, x, ldx, b, ldb, rwork, resid)
SPOT02
subroutine spot03(uplo, n, a, lda, ainv, ldainv, work, ldwork, rwork, rcond, resid)
SPOT03
subroutine spot05(uplo, n, nrhs, a, lda, b, ldb, x, ldx, xact, ldxact, ferr, berr, reslts)
SPOT05