167 SUBROUTINE schksy( DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL,
168 $ THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X,
169 $ XACT, WORK, RWORK, IWORK, NOUT )
177 INTEGER NMAX, NN, NNB, NNS, NOUT
182 INTEGER IWORK( * ), NBVAL( * ), NSVAL( * ), NVAL( * )
183 REAL A( * ), AFAC( * ), AINV( * ), B( * ),
184 $ rwork( * ), work( * ), x( * ), xact( * )
191 PARAMETER ( ZERO = 0.0e+0 )
193 parameter( ntypes = 10 )
195 parameter( ntests = 9 )
198 LOGICAL TRFCON, ZEROT
199 CHARACTER DIST,
TYPE, UPLO, XTYPE
201 INTEGER I, I1, I2, IMAT, IN, INB, INFO, IOFF, IRHS,
202 $ iuplo, izero, j, k, kl, ku, lda, lwork, mode,
203 $ n, nb, nerrs, nfail, nimat, nrhs, nrun, nt
204 REAL ANORM, CNDNUM, RCOND, RCONDC
208 INTEGER ISEED( 4 ), ISEEDY( 4 )
209 REAL RESULT( NTESTS )
213 EXTERNAL SGET06, SLANSY
230 COMMON / infoc / infot, nunit, ok, lerr
231 COMMON / srnamc / srnamt
234 DATA iseedy / 1988, 1989, 1990, 1991 /
235 DATA uplos /
'U',
'L' /
241 path( 1: 1 ) =
'Single precision'
247 iseed( i ) = iseedy( i )
253 $
CALL serrsy( path, nout )
275 DO 170 imat = 1, nimat
279 IF( .NOT.dotype( imat ) )
284 zerot = imat.GE.3 .AND. imat.LE.6
285 IF( zerot .AND. n.LT.imat-2 )
291 uplo = uplos( iuplo )
298 CALL slatb4( path, imat, n, n,
TYPE, kl, ku, anorm, mode,
304 CALL slatms( n, n, dist, iseed,
TYPE, rwork, mode,
305 $ cndnum, anorm, kl, ku, uplo, a, lda, work,
311 CALL alaerh( path,
'SLATMS', info, 0, uplo, n, n, -1,
312 $ -1, -1, imat, nfail, nerrs, nout )
326 ELSE IF( imat.EQ.4 )
THEN
336 IF( iuplo.EQ.1 )
THEN
337 ioff = ( izero-1 )*lda
338 DO 20 i = 1, izero - 1
348 DO 40 i = 1, izero - 1
358 IF( iuplo.EQ.1 )
THEN
405 CALL slacpy( uplo, n, n, a, lda, afac, lda )
412 lwork = max( 2, nb )*lda
414 CALL ssytrf( uplo, n, afac, lda, iwork, ainv, lwork,
423 IF( iwork( k ).LT.0 )
THEN
424 IF( iwork( k ).NE.-k )
THEN
428 ELSE IF( iwork( k ).NE.k )
THEN
437 $
CALL alaerh( path,
'SSYTRF', info, k, uplo, n, n,
438 $ -1, -1, nb, imat, nfail, nerrs, nout )
451 CALL ssyt01( uplo, n, a, lda, afac, lda, iwork, ainv,
452 $ lda, rwork, result( 1 ) )
461 IF( inb.EQ.1 .AND. .NOT.trfcon )
THEN
462 CALL slacpy( uplo, n, n, afac, lda, ainv, lda )
464 lwork = (n+nb+1)*(nb+3)
465 CALL ssytri2( uplo, n, ainv, lda, iwork, work,
471 $
CALL alaerh( path,
'SSYTRI2', info, -1, uplo, n,
472 $ n, -1, -1, -1, imat, nfail, nerrs,
478 CALL spot03( uplo, n, a, lda, ainv, lda, work, lda,
479 $ rwork, rcondc, result( 2 ) )
487 IF( result( k ).GE.thresh )
THEN
488 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
489 $
CALL alahd( nout, path )
490 WRITE( nout, fmt = 9999 )uplo, n, nb, imat, k,
522 CALL slarhs( path, xtype, uplo,
' ', n, n, kl, ku,
523 $ nrhs, a, lda, xact, lda, b, lda,
525 CALL slacpy(
'Full', n, nrhs, b, lda, x, lda )
528 CALL ssytrs( uplo, n, nrhs, afac, lda, iwork, x,
534 $
CALL alaerh( path,
'SSYTRS', info, 0, uplo, n,
535 $ n, -1, -1, nrhs, imat, nfail,
538 CALL slacpy(
'Full', n, nrhs, b, lda, work, lda )
542 CALL spot02( uplo, n, nrhs, a, lda, x, lda, work,
543 $ lda, rwork, result( 3 ) )
552 CALL slarhs( path, xtype, uplo,
' ', n, n, kl, ku,
553 $ nrhs, a, lda, xact, lda, b, lda,
555 CALL slacpy(
'Full', n, nrhs, b, lda, x, lda )
558 CALL ssytrs2( uplo, n, nrhs, afac, lda, iwork, x,
564 $
CALL alaerh( path,
'SSYTRS2', info, 0, uplo, n,
565 $ n, -1, -1, nrhs, imat, nfail,
568 CALL slacpy(
'Full', n, nrhs, b, lda, work, lda )
572 CALL spot02( uplo, n, nrhs, a, lda, x, lda, work,
573 $ lda, rwork, result( 4 ) )
578 CALL sget04( n, nrhs, x, lda, xact, lda, rcondc,
585 CALL ssyrfs( uplo, n, nrhs, a, lda, afac, lda,
586 $ iwork, b, lda, x, lda, rwork,
587 $ rwork( nrhs+1 ), work, iwork( n+1 ),
593 $
CALL alaerh( path,
'SSYRFS', info, 0, uplo, n,
594 $ n, -1, -1, nrhs, imat, nfail,
597 CALL sget04( n, nrhs, x, lda, xact, lda, rcondc,
599 CALL spot05( uplo, n, nrhs, a, lda, b, lda, x, lda,
600 $ xact, lda, rwork, rwork( nrhs+1 ),
607 IF( result( k ).GE.thresh )
THEN
608 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
609 $
CALL alahd( nout, path )
610 WRITE( nout, fmt = 9998 )uplo, n, nrhs,
611 $ imat, k, result( k )
625 anorm = slansy(
'1', uplo, n, a, lda, rwork )
627 CALL ssycon( uplo, n, afac, lda, iwork, anorm, rcond,
628 $ work, iwork( n+1 ), info )
633 $
CALL alaerh( path,
'SSYCON', info, 0, uplo, n, n,
634 $ -1, -1, -1, imat, nfail, nerrs, nout )
638 result( 9 ) = sget06( rcond, rcondc )
643 IF( result( 9 ).GE.thresh )
THEN
644 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
645 $
CALL alahd( nout, path )
646 WRITE( nout, fmt = 9997 )uplo, n, imat, 9,
659 CALL alasum( path, nout, nfail, nrun, nerrs )
661 9999
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
', NB =', i4,
', type ',
662 $ i2,
', test ', i2,
', ratio =', g12.5 )
663 9998
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
', NRHS=', i3,
', type ',
664 $ i2,
', test(', i2,
') =', g12.5 )
665 9997
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
',', 10x,
' type ', i2,
666 $
', 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 ssycon(uplo, n, a, lda, ipiv, anorm, rcond, work, iwork, info)
SSYCON
subroutine ssyrfs(uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x, ldx, ferr, berr, work, iwork, info)
SSYRFS
subroutine ssytrf(uplo, n, a, lda, ipiv, work, lwork, info)
SSYTRF
subroutine ssytri2(uplo, n, a, lda, ipiv, work, lwork, info)
SSYTRI2
subroutine ssytrs2(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, info)
SSYTRS2
subroutine ssytrs(uplo, n, nrhs, a, lda, ipiv, b, ldb, info)
SSYTRS
subroutine slacpy(uplo, m, n, a, lda, b, ldb)
SLACPY copies all or part of one two-dimensional array to another.
subroutine ssyconv(uplo, way, n, a, lda, ipiv, e, info)
SSYCONV
subroutine schksy(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
SCHKSY
subroutine serrsy(path, nunit)
SERRSY
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 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
subroutine ssyt01(uplo, n, a, lda, afac, ldafac, ipiv, c, ldc, rwork, resid)
SSYT01