150 SUBROUTINE cdrvsy_aa( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR,
151 $ NMAX, A, AFAC, AINV, B, X, XACT, WORK,
152 $ RWORK, IWORK, NOUT )
160 INTEGER NMAX, NN, NOUT, NRHS
165 INTEGER IWORK( * ), NVAL( * )
167 COMPLEX A( * ), AFAC( * ), AINV( * ), B( * ),
168 $ work( * ), x( * ), xact( * )
175 PARAMETER ( ZERO = 0.0d+0 )
177 parameter( czero = 0.0e+0 )
178 INTEGER NTYPES, NTESTS
179 parameter( ntypes = 10, ntests = 3 )
181 parameter( nfact = 2 )
185 CHARACTER DIST, FACT,
TYPE, UPLO, XTYPE
186 CHARACTER*3 MATPATH, PATH
187 INTEGER I, I1, I2, IFACT, IMAT, IN, INFO, IOFF, IUPLO,
188 $ izero, j, k, kl, ku, lda, lwork, mode, n,
189 $ nb, nbmin, nerrs, nfail, nimat, nrun, nt
193 CHARACTER FACTS( NFACT ), UPLOS( 2 )
194 INTEGER ISEED( 4 ), ISEEDY( 4 )
195 REAL RESULT( NTESTS )
199 EXTERNAL DGET06, CLANSY
212 COMMON / infoc / infot, nunit, ok, lerr
213 COMMON / srnamc / srnamt
219 DATA iseedy / 1988, 1989, 1990, 1991 /
220 DATA uplos /
'U',
'L' / , facts /
'F',
'N' /
228 path( 1: 1 ) =
'Complex precision'
233 matpath( 1: 1 ) =
'Complex precision'
234 matpath( 2: 3 ) =
'SY'
240 iseed( i ) = iseedy( i )
246 $
CALL cerrvx( path, nout )
260 lwork = max( 3*n-2, n*(1+nb) )
261 lwork = max( lwork, 1 )
268 DO 170 imat = 1, nimat
272 IF( .NOT.dotype( imat ) )
277 zerot = imat.GE.3 .AND. imat.LE.6
278 IF( zerot .AND. n.LT.imat-2 )
284 uplo = uplos( iuplo )
289 CALL clatb4( matpath, imat, n, n,
TYPE, kl, ku, anorm,
290 $ mode, cndnum, dist )
293 CALL clatms( n, n, dist, iseed,
TYPE, rwork, mode,
294 $ cndnum, anorm, kl, ku, uplo, a, lda, work,
300 CALL alaerh( path,
'CLATMS', info, 0, uplo, n, n, -1,
301 $ -1, -1, imat, nfail, nerrs, nout )
311 ELSE IF( imat.EQ.4 )
THEN
321 IF( iuplo.EQ.1 )
THEN
322 ioff = ( izero-1 )*lda
323 DO 20 i = 1, izero - 1
333 DO 40 i = 1, izero - 1
344 IF( iuplo.EQ.1 )
THEN
373 DO 150 ifact = 1, nfact
377 fact = facts( ifact )
382 CALL clarhs( matpath, xtype, uplo,
' ', n, n, kl, ku,
383 $ nrhs, a, lda, xact, lda, b, lda, iseed,
389 IF( ifact.EQ.2 )
THEN
390 CALL clacpy( uplo, n, n, a, lda, afac, lda )
391 CALL clacpy(
'Full', n, nrhs, b, lda, x, lda )
396 CALL csysv_aa( uplo, n, nrhs, afac, lda, iwork,
397 $ x, lda, work, lwork, info )
402 IF( izero.GT.0 )
THEN
408 ELSE IF( iwork( j ).EQ.k )
THEN
422 CALL alaerh( path,
'CSYSV_AA ', info, k,
423 $ uplo, n, n, -1, -1, nrhs,
424 $ imat, nfail, nerrs, nout )
426 ELSE IF( info.NE.0 )
THEN
433 CALL csyt01_aa( uplo, n, a, lda, afac, lda,
434 $ iwork, ainv, lda, rwork,
439 CALL clacpy(
'Full', n, nrhs, b, lda, work, lda )
440 CALL csyt02( uplo, n, nrhs, a, lda, x, lda, work,
441 $ lda, rwork, result( 2 ) )
448 IF( result( k ).GE.thresh )
THEN
449 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
450 $
CALL aladhd( nout, path )
451 WRITE( nout, fmt = 9999 )
'CSYSV_AA ',
452 $ uplo, n, imat, k, result( k )
468 CALL alasvm( path, nout, nfail, nrun, nerrs )
470 9999
FORMAT( 1x, a,
', UPLO=''', a1,
''', N =', i5,
', type ', i2,
471 $
', test ', i2,
', ratio =', g12.5 )
subroutine alasvm(type, nout, nfail, nrun, nerrs)
ALASVM
subroutine clarhs(path, xtype, uplo, trans, m, n, kl, ku, nrhs, a, lda, x, ldx, b, ldb, iseed, info)
CLARHS
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 cdrvsy_aa(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
CDRVSY_AA
subroutine cerrvx(path, nunit)
CERRVX
subroutine cget04(n, nrhs, x, ldx, xact, ldxact, rcond, resid)
CGET04
subroutine clatb4(path, imat, m, n, type, kl, ku, anorm, mode, cndnum, dist)
CLATB4
subroutine clatms(m, n, dist, iseed, sym, d, mode, cond, dmax, kl, ku, pack, a, lda, work, info)
CLATMS
subroutine csyt01_aa(uplo, n, a, lda, afac, ldafac, ipiv, c, ldc, rwork, resid)
CSYT01
subroutine csyt02(uplo, n, nrhs, a, lda, x, ldx, b, ldb, rwork, resid)
CSYT02
subroutine csysv_aa(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)
CSYSV_AA computes the solution to system of linear equations A * X = B for SY matrices
subroutine csytrf_aa(uplo, n, a, lda, ipiv, work, lwork, info)
CSYTRF_AA
subroutine clacpy(uplo, m, n, a, lda, b, ldb)
CLACPY copies all or part of one two-dimensional array to another.
subroutine claset(uplo, m, n, alpha, beta, a, lda)
CLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.