149 SUBROUTINE sdrvsy_aa( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR,
150 $ NMAX, A, AFAC, AINV, B, X, XACT, WORK,
151 $ RWORK, IWORK, NOUT )
159 INTEGER NMAX, NN, NOUT, NRHS
164 INTEGER IWORK( * ), NVAL( * )
165 REAL A( * ), AFAC( * ), AINV( * ), B( * ),
166 $ rwork( * ), work( * ), x( * ), xact( * )
173 PARAMETER ( ONE = 1.0e+0, zero = 0.0e+0 )
174 INTEGER NTYPES, NTESTS
175 parameter( ntypes = 10, ntests = 3 )
177 parameter( nfact = 2 )
181 CHARACTER DIST, FACT,
TYPE, UPLO, XTYPE
182 CHARACTER*3 MATPATH, PATH
183 INTEGER I, I1, I2, IFACT, IMAT, IN, INFO, IOFF, IUPLO,
184 $ izero, j, k, kl, ku, lda, lwork, mode, n,
185 $ nb, nbmin, nerrs, nfail, nimat, nrun, nt
189 CHARACTER FACTS( NFACT ), UPLOS( 2 )
190 INTEGER ISEED( 4 ), ISEEDY( 4 )
191 REAL RESULT( NTESTS )
195 EXTERNAL DGET06, SLANSY
208 COMMON / infoc / infot, nunit, ok, lerr
209 COMMON / srnamc / srnamt
215 DATA iseedy / 1988, 1989, 1990, 1991 /
216 DATA uplos /
'U',
'L' / , facts /
'F',
'N' /
224 path( 1: 1 ) =
'Single precision'
229 matpath( 1: 1 ) =
'Single precision'
230 matpath( 2: 3 ) =
'SY'
236 iseed( i ) = iseedy( i )
242 $
CALL serrvx( path, nout )
256 lwork = max( 3*n-2, n*(1+nb) )
257 lwork = max( lwork, 1 )
264 DO 170 imat = 1, nimat
268 IF( .NOT.dotype( imat ) )
273 zerot = imat.GE.3 .AND. imat.LE.6
274 IF( zerot .AND. n.LT.imat-2 )
280 uplo = uplos( iuplo )
285 CALL slatb4( matpath, imat, n, n,
TYPE, kl, ku, anorm,
286 $ mode, cndnum, dist )
289 CALL slatms( n, n, dist, iseed,
TYPE, rwork, mode,
290 $ cndnum, anorm, kl, ku, uplo, a, lda, work,
296 CALL alaerh( path,
'SLATMS', info, 0, uplo, n, n, -1,
297 $ -1, -1, imat, nfail, nerrs, nout )
307 ELSE IF( imat.EQ.4 )
THEN
317 IF( iuplo.EQ.1 )
THEN
318 ioff = ( izero-1 )*lda
319 DO 20 i = 1, izero - 1
329 DO 40 i = 1, izero - 1
340 IF( iuplo.EQ.1 )
THEN
369 DO 150 ifact = 1, nfact
373 fact = facts( ifact )
378 CALL slarhs( matpath, xtype, uplo,
' ', n, n, kl, ku,
379 $ nrhs, a, lda, xact, lda, b, lda, iseed,
385 IF( ifact.EQ.2 )
THEN
386 CALL slacpy( uplo, n, n, a, lda, afac, lda )
387 CALL slacpy(
'Full', n, nrhs, b, lda, x, lda )
392 CALL ssysv_aa( uplo, n, nrhs, afac, lda, iwork,
393 $ x, lda, work, lwork, info )
398 IF( izero.GT.0 )
THEN
404 ELSE IF( iwork( j ).EQ.k )
THEN
418 CALL alaerh( path,
'SSYSV_AA ', info, k,
419 $ uplo, n, n, -1, -1, nrhs,
420 $ imat, nfail, nerrs, nout )
422 ELSE IF( info.NE.0 )
THEN
429 CALL ssyt01_aa( uplo, n, a, lda, afac, lda,
430 $ iwork, ainv, lda, rwork,
435 CALL slacpy(
'Full', n, nrhs, b, lda, work, lda )
436 CALL spot02( uplo, n, nrhs, a, lda, x, lda, work,
437 $ lda, rwork, result( 2 ) )
444 IF( result( k ).GE.thresh )
THEN
445 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
446 $
CALL aladhd( nout, path )
447 WRITE( nout, fmt = 9999 )
'SSYSV_AA ',
448 $ uplo, n, imat, k, result( k )
464 CALL alasvm( path, nout, nfail, nrun, nerrs )
466 9999
FORMAT( 1x, a,
', UPLO=''', a1,
''', N =', i5,
', type ', i2,
467 $
', test ', i2,
', ratio =', g12.5 )
subroutine alasvm(type, nout, nfail, nrun, nerrs)
ALASVM
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 aladhd(iounit, path)
ALADHD
subroutine alaerh(path, subnam, info, infoe, opts, m, n, kl, ku, n5, imat, nfail, nerrs, nout)
ALAERH
subroutine ssysv_aa(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)
SSYSV_AA computes the solution to system of linear equations A * X = B for SY matrices
subroutine ssytrf_aa(uplo, n, a, lda, ipiv, work, lwork, info)
SSYTRF_AA
subroutine slacpy(uplo, m, n, a, lda, b, ldb)
SLACPY copies all or part of one two-dimensional array to another.
subroutine slaset(uplo, m, n, alpha, beta, a, lda)
SLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.
subroutine sdrvsy_aa(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
SDRVSY_AA
subroutine serrvx(path, nunit)
SERRVX
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 ssyt01_aa(uplo, n, a, lda, afac, ldafac, ipiv, c, ldc, rwork, resid)
SSYT01_AA