150 SUBROUTINE cdrvhe_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 ( ONE = 1.0e+0, zero = 0.0e+0 )
176 INTEGER NTYPES, NTESTS
177 parameter( ntypes = 10, ntests = 3 )
179 parameter( nfact = 2 )
183 CHARACTER DIST, FACT,
TYPE, UPLO, XTYPE
184 CHARACTER*3 MATPATH, PATH
185 INTEGER I, I1, I2, IFACT, IMAT, IN, INFO, IOFF, IUPLO,
186 $ izero, j, k, kl, ku, lda, lwork, mode, n,
187 $ nb, nbmin, nerrs, nfail, nimat, nrun, nt
191 CHARACTER FACTS( NFACT ), UPLOS( 2 )
192 INTEGER ISEED( 4 ), ISEEDY( 4 )
193 REAL RESULT( NTESTS )
197 EXTERNAL CLANHE, SGET06
211 COMMON / infoc / infot, nunit, ok, lerr
212 COMMON / srnamc / srnamt
215 INTRINSIC cmplx, max, min
218 DATA iseedy / 1988, 1989, 1990, 1991 /
219 DATA uplos /
'U',
'L' / , facts /
'F',
'N' /
227 path( 1: 1 ) =
'Complex precision'
232 matpath( 1: 1 ) =
'Complex precision'
233 matpath( 2: 3 ) =
'HE'
239 iseed( i ) = iseedy( i )
245 $
CALL cerrvx( path, nout )
259 lwork = max( 3*n-2, n*(1+nb) )
260 lwork = max( lwork, 1 )
267 DO 170 imat = 1, nimat
271 IF( .NOT.dotype( imat ) )
276 zerot = imat.GE.3 .AND. imat.LE.6
277 IF( zerot .AND. n.LT.imat-2 )
283 uplo = uplos( iuplo )
290 CALL clatb4( matpath, imat, n, n,
TYPE, kl, ku, anorm,
291 $ mode, cndnum, dist )
296 CALL clatms( n, n, dist, iseed,
TYPE, rwork, mode,
297 $ cndnum, anorm, kl, ku, uplo, a, lda,
303 CALL alaerh( path,
'CLATMS', info, 0, uplo, n, n,
304 $ -1, -1, -1, imat, nfail, nerrs, nout )
314 ELSE IF( imat.EQ.4 )
THEN
324 IF( iuplo.EQ.1 )
THEN
325 ioff = ( izero-1 )*lda
326 DO 20 i = 1, izero - 1
336 DO 40 i = 1, izero - 1
347 IF( iuplo.EQ.1 )
THEN
380 DO 150 ifact = 1, nfact
384 fact = facts( ifact )
389 CALL clarhs( matpath, xtype, uplo,
' ', n, n, kl, ku,
390 $ nrhs, a, lda, xact, lda, b, lda, iseed,
396 IF( ifact.EQ.2 )
THEN
397 CALL clacpy( uplo, n, n, a, lda, afac, lda )
398 CALL clacpy(
'Full', n, nrhs, b, lda, x, lda )
403 CALL chesv_aa( uplo, n, nrhs, afac, lda, iwork,
404 $ x, lda, work, lwork, info )
409 IF( izero.GT.0 )
THEN
415 ELSE IF( iwork( j ).EQ.k )
THEN
429 CALL alaerh( path,
'CHESV_AA', info, k,
430 $ uplo, n, n, -1, -1, nrhs,
431 $ imat, nfail, nerrs, nout )
433 ELSE IF( info.NE.0 )
THEN
440 CALL chet01_aa( uplo, n, a, lda, afac, lda,
441 $ iwork, ainv, lda, rwork,
446 CALL clacpy(
'Full', n, nrhs, b, lda, work, lda )
447 CALL cpot02( uplo, n, nrhs, a, lda, x, lda, work,
448 $ lda, rwork, result( 2 ) )
455 IF( result( k ).GE.thresh )
THEN
456 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
457 $
CALL aladhd( nout, path )
458 WRITE( nout, fmt = 9999 )
'CHESV_AA ',
459 $ uplo, n, imat, k, result( k )
475 CALL alasvm( path, nout, nfail, nrun, nerrs )
477 9999
FORMAT( 1x, a,
', UPLO=''', a1,
''', N =', i5,
', type ', i2,
478 $
', 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 cdrvhe_aa(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
CDRVHE_AA
subroutine cerrvx(path, nunit)
CERRVX
subroutine cget04(n, nrhs, x, ldx, xact, ldxact, rcond, resid)
CGET04
subroutine chet01_aa(uplo, n, a, lda, afac, ldafac, ipiv, c, ldc, rwork, resid)
CHET01_AA
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 cpot02(uplo, n, nrhs, a, lda, x, ldx, b, ldb, rwork, resid)
CPOT02
subroutine chesv_aa(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)
CHESV_AA computes the solution to system of linear equations A * X = B for HE matrices
subroutine chetrf_aa(uplo, n, a, lda, ipiv, work, lwork, info)
CHETRF_AA
subroutine clacpy(uplo, m, n, a, lda, b, ldb)
CLACPY copies all or part of one two-dimensional array to another.