155 SUBROUTINE cdrvhe_rk( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR,
156 $ NMAX, A, AFAC, E, AINV, B, X, XACT, WORK,
157 $ RWORK, IWORK, NOUT )
165 INTEGER NMAX, NN, NOUT, NRHS
170 INTEGER IWORK( * ), NVAL( * )
172 COMPLEX A( * ), AFAC( * ), AINV( * ), B( * ), E( * ),
173 $ work( * ), x( * ), xact( * )
180 PARAMETER ( ONE = 1.0e+0, zero = 0.0e+0 )
181 INTEGER NTYPES, NTESTS
182 parameter( ntypes = 10, ntests = 3 )
184 parameter( nfact = 2 )
188 CHARACTER DIST, FACT,
TYPE, UPLO, XTYPE
189 CHARACTER*3 MATPATH, PATH
190 INTEGER I, I1, I2, IFACT, IMAT, IN, INFO, IOFF, IUPLO,
191 $ izero, j, k, kl, ku, lda, lwork, mode, n,
192 $ nb, nbmin, nerrs, nfail, nimat, nrun, nt
193 REAL AINVNM, ANORM, CNDNUM, RCONDC
196 CHARACTER FACTS( NFACT ), UPLOS( 2 )
197 INTEGER ISEED( 4 ), ISEEDY( 4 )
198 REAL RESULT( NTESTS )
216 COMMON / infoc / infot, nunit, ok, lerr
217 COMMON / srnamc / srnamt
223 DATA iseedy / 1988, 1989, 1990, 1991 /
224 DATA uplos /
'U',
'L' / , facts /
'F',
'N' /
232 path( 1: 1 ) =
'Complex precision'
237 matpath( 1: 1 ) =
'Complex precision'
238 matpath( 2: 3 ) =
'HE'
244 iseed( i ) = iseedy( i )
246 lwork = max( 2*nmax, nmax*nrhs )
251 $
CALL cerrvx( path, nout )
272 DO 170 imat = 1, nimat
276 IF( .NOT.dotype( imat ) )
281 zerot = imat.GE.3 .AND. imat.LE.6
282 IF( zerot .AND. n.LT.imat-2 )
288 uplo = uplos( iuplo )
295 CALL clatb4( matpath, imat, n, n,
TYPE, kl, ku, anorm,
296 $ mode, cndnum, dist )
301 CALL clatms( n, n, dist, iseed,
TYPE, rwork, mode,
302 $ cndnum, anorm, kl, ku, uplo, a, lda,
308 CALL alaerh( path,
'CLATMS', info, 0, uplo, n, n,
309 $ -1, -1, -1, imat, nfail, nerrs, nout )
319 ELSE IF( imat.EQ.4 )
THEN
329 IF( iuplo.EQ.1 )
THEN
330 ioff = ( izero-1 )*lda
331 DO 20 i = 1, izero - 1
341 DO 40 i = 1, izero - 1
351 IF( iuplo.EQ.1 )
THEN
384 DO 150 ifact = 1, nfact
388 fact = facts( ifact )
397 ELSE IF( ifact.EQ.1 )
THEN
401 anorm = clanhe(
'1', uplo, n, a, lda, rwork )
405 CALL clacpy( uplo, n, n, a, lda, afac, lda )
406 CALL chetrf_rk( uplo, n, afac, lda, e, iwork, work,
411 CALL clacpy( uplo, n, n, afac, lda, ainv, lda )
412 lwork = (n+nb+1)*(nb+3)
417 CALL csytri_3( uplo, n, ainv, lda, e, iwork,
418 $ work, lwork, info )
419 ainvnm = clanhe(
'1', uplo, n, ainv, lda, rwork )
423 IF( anorm.LE.zero .OR. ainvnm.LE.zero )
THEN
426 rcondc = ( one / anorm ) / ainvnm
433 CALL clarhs( matpath, xtype, uplo,
' ', n, n, kl, ku,
434 $ nrhs, a, lda, xact, lda, b, lda, iseed,
440 IF( ifact.EQ.2 )
THEN
441 CALL clacpy( uplo, n, n, a, lda, afac, lda )
442 CALL clacpy(
'Full', n, nrhs, b, lda, x, lda )
448 CALL chesv_rk( uplo, n, nrhs, afac, lda, e, iwork,
449 $ x, lda, work, lwork, info )
457 IF( iwork( k ).LT.0 )
THEN
458 IF( iwork( k ).NE.-k )
THEN
462 ELSE IF( iwork( k ).NE.k )
THEN
471 CALL alaerh( path,
'CHESV_RK', info, k, uplo,
472 $ n, n, -1, -1, nrhs, imat, nfail,
475 ELSE IF( info.NE.0 )
THEN
482 CALL chet01_3( uplo, n, a, lda, afac, lda, e,
483 $ iwork, ainv, lda, rwork,
488 CALL clacpy(
'Full', n, nrhs, b, lda, work, lda )
489 CALL cpot02( uplo, n, nrhs, a, lda, x, lda, work,
490 $ lda, rwork, result( 2 ) )
495 CALL cget04( n, nrhs, x, lda, xact, lda, rcondc,
503 IF( result( k ).GE.thresh )
THEN
504 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
505 $
CALL aladhd( nout, path )
506 WRITE( nout, fmt = 9999 )
'CHESV_RK', uplo,
507 $ n, imat, k, result( k )
523 CALL alasvm( path, nout, nfail, nrun, nerrs )
525 9999
FORMAT( 1x, a,
', UPLO=''', a1,
''', N =', i5,
', type ', i2,
526 $
', 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_rk(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, e, ainv, b, x, xact, work, rwork, iwork, nout)
CDRVHE_RK
subroutine cerrvx(path, nunit)
CERRVX
subroutine cget04(n, nrhs, x, ldx, xact, ldxact, rcond, resid)
CGET04
subroutine chet01_3(uplo, n, a, lda, afac, ldafac, e, ipiv, c, ldc, rwork, resid)
CHET01_3
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_rk(uplo, n, nrhs, a, lda, e, ipiv, b, ldb, work, lwork, info)
CHESV_RK computes the solution to system of linear equations A * X = B for SY matrices
subroutine chetrf_rk(uplo, n, a, lda, e, ipiv, work, lwork, info)
CHETRF_RK computes the factorization of a complex Hermitian indefinite matrix using the bounded Bunch...
subroutine csytri_3(uplo, n, a, lda, e, ipiv, work, lwork, info)
CSYTRI_3
subroutine chetri_3(uplo, n, a, lda, e, ipiv, work, lwork, info)
CHETRI_3
subroutine clacpy(uplo, m, n, a, lda, b, ldb)
CLACPY copies all or part of one two-dimensional array to another.