169 $ THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X,
170 $ XACT, WORK, RWORK, IWORK, NOUT )
178 INTEGER NMAX, NN, NNB, NNS, NOUT
183 INTEGER IWORK( * ), NBVAL( * ), NSVAL( * ), NVAL( * )
184 REAL A( * ), AFAC( * ), AINV( * ), B( * ),
185 $ rwork( * ), work( * ), x( * ), xact( * )
192 PARAMETER ( ZERO = 0.0d+0, one = 1.0d+0 )
194 parameter( eight = 8.0d+0, sevten = 17.0d+0 )
196 parameter( ntypes = 10 )
198 parameter( ntests = 7 )
201 LOGICAL TRFCON, ZEROT
202 CHARACTER DIST,
TYPE, UPLO, XTYPE
203 CHARACTER*3 PATH, MATPATH
204 INTEGER I, I1, I2, IMAT, IN, INB, INFO, IOFF, IRHS,
205 $ iuplo, izero, j, k, kl, ku, lda, lwork, mode,
206 $ n, nb, nerrs, nfail, nimat, nrhs, nrun, nt
207 REAL ALPHA, ANORM, CNDNUM, CONST, SING_MAX,
208 $ SING_MIN, RCOND, RCONDC, STEMP
212 INTEGER ISEED( 4 ), ISEEDY( 4 )
213 REAL BLOCK( 2, 2 ), RESULT( NTESTS ), SDUMMY( 1 )
216 REAL SGET06, SLANGE, SLANSY
217 EXTERNAL SGET06, SLANGE, SLANSY
226 INTRINSIC max, min, sqrt
234 COMMON / infoc / infot, nunit, ok, lerr
235 COMMON / srnamc / srnamt
238 DATA iseedy / 1988, 1989, 1990, 1991 /
239 DATA uplos /
'U',
'L' /
245 alpha = ( one+sqrt( sevten ) ) / eight
249 path( 1: 1 ) =
'Single precision'
254 matpath( 1: 1 ) =
'Single precision'
255 matpath( 2: 3 ) =
'SY'
261 iseed( i ) = iseedy( i )
267 $
CALL serrsy( path, nout )
289 DO 260 imat = 1, nimat
293 IF( .NOT.dotype( imat ) )
298 zerot = imat.GE.3 .AND. imat.LE.6
299 IF( zerot .AND. n.LT.imat-2 )
305 uplo = uplos( iuplo )
312 CALL slatb4( matpath, imat, n, n,
TYPE, kl, ku, anorm,
313 $ mode, cndnum, dist )
318 CALL slatms( n, n, dist, iseed,
TYPE, rwork, mode,
319 $ cndnum, anorm, kl, ku, uplo, a, lda, work,
325 CALL alaerh( path,
'SLATMS', info, 0, uplo, n, n, -1,
326 $ -1, -1, imat, nfail, nerrs, nout )
340 ELSE IF( imat.EQ.4 )
THEN
350 IF( iuplo.EQ.1 )
THEN
351 ioff = ( izero-1 )*lda
352 DO 20 i = 1, izero - 1
362 DO 40 i = 1, izero - 1
372 IF( iuplo.EQ.1 )
THEN
419 CALL slacpy( uplo, n, n, a, lda, afac, lda )
426 lwork = max( 2, nb )*lda
427 srnamt =
'SSYTRF_ROOK'
437 IF( iwork( k ).LT.0 )
THEN
438 IF( iwork( k ).NE.-k )
THEN
442 ELSE IF( iwork( k ).NE.k )
THEN
451 $
CALL alaerh( path,
'SSYTRF_ROOK', info, k,
452 $ uplo, n, n, -1, -1, nb, imat,
453 $ nfail, nerrs, nout )
466 CALL ssyt01_rook( uplo, n, a, lda, afac, lda, iwork,
467 $ ainv, lda, rwork, result( 1 ) )
476 IF( inb.EQ.1 .AND. .NOT.trfcon )
THEN
477 CALL slacpy( uplo, n, n, afac, lda, ainv, lda )
478 srnamt =
'SSYTRI_ROOK'
485 $
CALL alaerh( path,
'SSYTRI_ROOK', info, -1,
486 $ uplo, n, n, -1, -1, -1, imat,
487 $ nfail, nerrs, nout )
492 CALL spot03( uplo, n, a, lda, ainv, lda, work, lda,
493 $ rwork, rcondc, result( 2 ) )
501 IF( result( k ).GE.thresh )
THEN
502 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
503 $
CALL alahd( nout, path )
504 WRITE( nout, fmt = 9999 )uplo, n, nb, imat, k,
517 const = one / ( one-alpha )
519 IF( iuplo.EQ.1 )
THEN
528 IF( iwork( k ).GT.zero )
THEN
533 stemp = slange(
'M', k-1, 1,
534 $ afac( ( k-1 )*lda+1 ), lda, rwork )
540 stemp = slange(
'M', k-2, 2,
541 $ afac( ( k-2 )*lda+1 ), lda, rwork )
548 stemp = stemp - const + thresh
549 IF( stemp.GT.result( 3 ) )
550 $ result( 3 ) = stemp
566 IF( iwork( k ).GT.zero )
THEN
571 stemp = slange(
'M', n-k, 1,
572 $ afac( ( k-1 )*lda+k+1 ), lda, rwork )
578 stemp = slange(
'M', n-k-1, 2,
579 $ afac( ( k-1 )*lda+k+2 ), lda, rwork )
586 stemp = stemp - const + thresh
587 IF( stemp.GT.result( 3 ) )
588 $ result( 3 ) = stemp
604 const = ( one+alpha ) / ( one-alpha )
605 CALL slacpy( uplo, n, n, afac, lda, ainv, lda )
607 IF( iuplo.EQ.1 )
THEN
616 IF( iwork( k ).LT.zero )
THEN
622 block( 1, 1 ) = afac( ( k-2 )*lda+k-1 )
623 block( 1, 2 ) = afac( (k-1)*lda+k-1 )
624 block( 2, 1 ) = block( 1, 2 )
625 block( 2, 2 ) = afac( (k-1)*lda+k )
627 CALL sgesvd(
'N',
'N', 2, 2, block, 2, rwork,
628 $ sdummy, 1, sdummy, 1,
632 sing_max = rwork( 1 )
633 sing_min = rwork( 2 )
635 stemp = sing_max / sing_min
639 stemp = stemp - const + thresh
640 IF( stemp.GT.result( 4 ) )
641 $ result( 4 ) = stemp
660 IF( iwork( k ).LT.zero )
THEN
666 block( 1, 1 ) = afac( ( k-1 )*lda+k )
667 block( 2, 1 ) = afac( ( k-1 )*lda+k+1 )
668 block( 1, 2 ) = block( 2, 1 )
669 block( 2, 2 ) = afac( k*lda+k+1 )
671 CALL sgesvd(
'N',
'N', 2, 2, block, 2, rwork,
672 $ sdummy, 1, sdummy, 1,
676 sing_max = rwork( 1 )
677 sing_min = rwork( 2 )
679 stemp = sing_max / sing_min
683 stemp = stemp - const + thresh
684 IF( stemp.GT.result( 4 ) )
685 $ result( 4 ) = stemp
700 IF( result( k ).GE.thresh )
THEN
701 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
702 $
CALL alahd( nout, path )
703 WRITE( nout, fmt = 9999 )uplo, n, nb, imat, k,
735 CALL slarhs( matpath, xtype, uplo,
' ', n, n,
736 $ kl, ku, nrhs, a, lda, xact, lda,
737 $ b, lda, iseed, info )
738 CALL slacpy(
'Full', n, nrhs, b, lda, x, lda )
740 srnamt =
'SSYTRS_ROOK'
747 $
CALL alaerh( path,
'SSYTRS_ROOK', info, 0,
748 $ uplo, n, n, -1, -1, nrhs, imat,
749 $ nfail, nerrs, nout )
751 CALL slacpy(
'Full', n, nrhs, b, lda, work, lda )
755 CALL spot02( uplo, n, nrhs, a, lda, x, lda, work,
756 $ lda, rwork, result( 5 ) )
761 CALL sget04( n, nrhs, x, lda, xact, lda, rcondc,
768 IF( result( k ).GE.thresh )
THEN
769 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
770 $
CALL alahd( nout, path )
771 WRITE( nout, fmt = 9998 )uplo, n, nrhs,
772 $ imat, k, result( k )
786 anorm = slansy(
'1', uplo, n, a, lda, rwork )
787 srnamt =
'SSYCON_ROOK'
788 CALL ssycon_rook( uplo, n, afac, lda, iwork, anorm,
789 $ rcond, work, iwork( n+1 ), info )
794 $
CALL alaerh( path,
'SSYCON_ROOK', info, 0,
795 $ uplo, n, n, -1, -1, -1, imat,
796 $ nfail, nerrs, nout )
800 result( 7 ) = sget06( rcond, rcondc )
805 IF( result( 7 ).GE.thresh )
THEN
806 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
807 $
CALL alahd( nout, path )
808 WRITE( nout, fmt = 9997 )uplo, n, imat, 7,
821 CALL alasum( path, nout, nfail, nrun, nerrs )
823 9999
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
', NB =', i4,
', type ',
824 $ i2,
', test ', i2,
', ratio =', g12.5 )
825 9998
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
', NRHS=', i3,
', type ',
826 $ i2,
', test(', i2,
') =', g12.5 )
827 9997
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
',', 10x,
' type ', i2,
828 $
', 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 sgesvd(jobu, jobvt, m, n, a, lda, s, u, ldu, vt, ldvt, work, lwork, info)
SGESVD computes the singular value decomposition (SVD) for GE matrices
subroutine ssycon_rook(uplo, n, a, lda, ipiv, anorm, rcond, work, iwork, info)
SSYCON_ROOK
subroutine ssytrf_rook(uplo, n, a, lda, ipiv, work, lwork, info)
SSYTRF_ROOK
subroutine ssytri_rook(uplo, n, a, lda, ipiv, work, info)
SSYTRI_ROOK
subroutine ssytrs_rook(uplo, n, nrhs, a, lda, ipiv, b, ldb, info)
SSYTRS_ROOK
subroutine slacpy(uplo, m, n, a, lda, b, ldb)
SLACPY copies all or part of one two-dimensional array to another.
subroutine schksy_rook(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
SCHKSY_ROOK
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 ssyt01_rook(uplo, n, a, lda, afac, ldafac, ipiv, c, ldc, rwork, resid)
SSYT01_ROOK