149 SUBROUTINE ddrvsy_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
160 DOUBLE PRECISION THRESH
164 INTEGER IWORK( * ), NVAL( * )
165 DOUBLE PRECISION A( * ), AFAC( * ), AINV( * ), B( * ),
166 $ rwork( * ), work( * ), x( * ), xact( * )
172 DOUBLE PRECISION ONE, ZERO
173 PARAMETER ( ONE = 1.0d+0, zero = 0.0d+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
186 DOUBLE PRECISION ANORM, CNDNUM
189 CHARACTER FACTS( NFACT ), UPLOS( 2 )
190 INTEGER ISEED( 4 ), ISEEDY( 4 )
191 DOUBLE PRECISION RESULT( NTESTS )
194 DOUBLE PRECISION DGET06, DLANSY
195 EXTERNAL DGET06, DLANSY
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 ) =
'Double precision'
229 matpath( 1: 1 ) =
'Double precision'
230 matpath( 2: 3 ) =
'SY'
236 iseed( i ) = iseedy( i )
242 $
CALL derrvx( 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 dlatb4( matpath, imat, n, n,
TYPE, kl, ku, anorm,
286 $ mode, cndnum, dist )
289 CALL dlatms( n, n, dist, iseed,
TYPE, rwork, mode,
290 $ cndnum, anorm, kl, ku, uplo, a, lda, work,
296 CALL alaerh( path,
'DLATMS', 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 dlarhs( matpath, xtype, uplo,
' ', n, n, kl, ku,
379 $ nrhs, a, lda, xact, lda, b, lda, iseed,
385 IF( ifact.EQ.2 )
THEN
386 CALL dlacpy( uplo, n, n, a, lda, afac, lda )
387 CALL dlacpy(
'Full', n, nrhs, b, lda, x, lda )
392 CALL dsysv_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,
'DSYSV_AA ', info, k,
419 $ uplo, n, n, -1, -1, nrhs,
420 $ imat, nfail, nerrs, nout )
422 ELSE IF( info.NE.0 )
THEN
429 CALL dsyt01_aa( uplo, n, a, lda, afac, lda,
430 $ iwork, ainv, lda, rwork,
435 CALL dlacpy(
'Full', n, nrhs, b, lda, work, lda )
436 CALL dpot02( 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 )
'DSYSV_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 dlarhs(path, xtype, uplo, trans, m, n, kl, ku, nrhs, a, lda, x, ldx, b, ldb, iseed, info)
DLARHS
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 ddrvsy_aa(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
DDRVSY_AA
subroutine derrvx(path, nunit)
DERRVX
subroutine dget04(n, nrhs, x, ldx, xact, ldxact, rcond, resid)
DGET04
subroutine dlatb4(path, imat, m, n, type, kl, ku, anorm, mode, cndnum, dist)
DLATB4
subroutine dlatms(m, n, dist, iseed, sym, d, mode, cond, dmax, kl, ku, pack, a, lda, work, info)
DLATMS
subroutine dpot02(uplo, n, nrhs, a, lda, x, ldx, b, ldb, rwork, resid)
DPOT02
subroutine dsyt01_aa(uplo, n, a, lda, afac, ldafac, ipiv, c, ldc, rwork, resid)
DSYT01
subroutine dsysv_aa(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)
DSYSV_AA computes the solution to system of linear equations A * X = B for SY matrices
subroutine dsytrf_aa(uplo, n, a, lda, ipiv, work, lwork, info)
DSYTRF_AA
subroutine dlacpy(uplo, m, n, a, lda, b, ldb)
DLACPY copies all or part of one two-dimensional array to another.
subroutine dlaset(uplo, m, n, alpha, beta, a, lda)
DLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.