168 SUBROUTINE zchkhe( DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL,
169 $ THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X,
170 $ XACT, WORK, RWORK, IWORK, NOUT )
178 INTEGER NMAX, NN, NNB, NNS, NOUT
179 DOUBLE PRECISION THRESH
183 INTEGER IWORK( * ), NBVAL( * ), NSVAL( * ), NVAL( * )
184 DOUBLE PRECISION RWORK( * )
185 COMPLEX*16 A( * ), AFAC( * ), AINV( * ), B( * ),
186 $ work( * ), x( * ), xact( * )
192 DOUBLE PRECISION ZERO
193 PARAMETER ( ZERO = 0.0d+0 )
195 parameter( czero = ( 0.0d+0, 0.0d+0 ) )
197 parameter( ntypes = 10 )
199 parameter( ntests = 9 )
202 LOGICAL TRFCON, ZEROT
203 CHARACTER DIST,
TYPE, UPLO, XTYPE
205 INTEGER I, I1, I2, IMAT, IN, INB, INFO, IOFF, IRHS,
206 $ iuplo, izero, j, k, kl, ku, lda, lwork, mode,
207 $ n, nb, nerrs, nfail, nimat, nrhs, nrun, nt
208 DOUBLE PRECISION ANORM, CNDNUM, RCOND, RCONDC
212 INTEGER ISEED( 4 ), ISEEDY( 4 )
213 DOUBLE PRECISION RESULT( NTESTS )
216 DOUBLE PRECISION DGET06, ZLANHE
217 EXTERNAL DGET06, ZLANHE
234 COMMON / infoc / infot, nunit, ok, lerr
235 COMMON / srnamc / srnamt
238 DATA iseedy / 1988, 1989, 1990, 1991 /
239 DATA uplos /
'U',
'L' /
245 path( 1: 1 ) =
'Zomplex precision'
251 iseed( i ) = iseedy( i )
257 $
CALL zerrhe( path, nout )
276 DO 170 imat = 1, nimat
280 IF( .NOT.dotype( imat ) )
285 zerot = imat.GE.3 .AND. imat.LE.6
286 IF( zerot .AND. n.LT.imat-2 )
292 uplo = uplos( iuplo )
297 CALL zlatb4( path, imat, n, n,
TYPE, kl, ku, anorm, mode,
303 CALL zlatms( n, n, dist, iseed,
TYPE, rwork, mode,
304 $ cndnum, anorm, kl, ku, uplo, a, lda, work,
310 CALL alaerh( path,
'ZLATMS', info, 0, uplo, n, n, -1,
311 $ -1, -1, imat, nfail, nerrs, nout )
324 ELSE IF( imat.EQ.4 )
THEN
334 IF( iuplo.EQ.1 )
THEN
335 ioff = ( izero-1 )*lda
336 DO 20 i = 1, izero - 1
346 DO 40 i = 1, izero - 1
356 IF( iuplo.EQ.1 )
THEN
391 CALL zlaipd( n, a, lda+1, 0 )
407 CALL zlacpy( uplo, n, n, a, lda, afac, lda )
414 lwork = max( 2, nb )*lda
416 CALL zhetrf( uplo, n, afac, lda, iwork, ainv, lwork,
425 IF( iwork( k ).LT.0 )
THEN
426 IF( iwork( k ).NE.-k )
THEN
430 ELSE IF( iwork( k ).NE.k )
THEN
439 $
CALL alaerh( path,
'ZHETRF', info, k, uplo, n, n,
440 $ -1, -1, nb, imat, nfail, nerrs, nout )
453 CALL zhet01( uplo, n, a, lda, afac, lda, iwork, ainv,
454 $ lda, rwork, result( 1 ) )
460 IF( inb.EQ.1 .AND. .NOT.trfcon )
THEN
461 CALL zlacpy( uplo, n, n, afac, lda, ainv, lda )
463 lwork = (n+nb+1)*(nb+3)
464 CALL zhetri2( uplo, n, ainv, lda, iwork, work,
470 $
CALL alaerh( path,
'ZHETRI', info, -1, uplo, n,
471 $ n, -1, -1, -1, imat, nfail, nerrs,
477 CALL zpot03( uplo, n, a, lda, ainv, lda, work, lda,
478 $ rwork, rcondc, result( 2 ) )
486 IF( result( k ).GE.thresh )
THEN
487 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
488 $
CALL alahd( nout, path )
489 WRITE( nout, fmt = 9999 )uplo, n, nb, imat, k,
521 CALL zlarhs( path, xtype, uplo,
' ', n, n, kl, ku,
522 $ nrhs, a, lda, xact, lda, b, lda,
524 CALL zlacpy(
'Full', n, nrhs, b, lda, x, lda )
527 CALL zhetrs( uplo, n, nrhs, afac, lda, iwork, x,
533 $
CALL alaerh( path,
'ZHETRS', info, 0, uplo, n,
534 $ n, -1, -1, nrhs, imat, nfail,
537 CALL zlacpy(
'Full', n, nrhs, b, lda, work, lda )
541 CALL zpot02( uplo, n, nrhs, a, lda, x, lda, work,
542 $ lda, rwork, result( 3 ) )
551 CALL zlarhs( path, xtype, uplo,
' ', n, n, kl, ku,
552 $ nrhs, a, lda, xact, lda, b, lda,
554 CALL zlacpy(
'Full', n, nrhs, b, lda, x, lda )
557 CALL zhetrs2( uplo, n, nrhs, afac, lda, iwork, x,
563 $
CALL alaerh( path,
'ZHETRS2', info, 0, uplo, n,
564 $ n, -1, -1, nrhs, imat, nfail,
567 CALL zlacpy(
'Full', n, nrhs, b, lda, work, lda )
571 CALL zpot02( uplo, n, nrhs, a, lda, x, lda, work,
572 $ lda, rwork, result( 4 ) )
577 CALL zget04( n, nrhs, x, lda, xact, lda, rcondc,
584 CALL zherfs( uplo, n, nrhs, a, lda, afac, lda,
585 $ iwork, b, lda, x, lda, rwork,
586 $ rwork( nrhs+1 ), work,
587 $ rwork( 2*nrhs+1 ), info )
592 $
CALL alaerh( path,
'ZHERFS', info, 0, uplo, n,
593 $ n, -1, -1, nrhs, imat, nfail,
596 CALL zget04( n, nrhs, x, lda, xact, lda, rcondc,
598 CALL zpot05( uplo, n, nrhs, a, lda, b, lda, x, lda,
599 $ xact, lda, rwork, rwork( nrhs+1 ),
606 IF( result( k ).GE.thresh )
THEN
607 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
608 $
CALL alahd( nout, path )
609 WRITE( nout, fmt = 9998 )uplo, n, nrhs,
610 $ imat, k, result( k )
624 anorm = zlanhe(
'1', uplo, n, a, lda, rwork )
626 CALL zhecon( uplo, n, afac, lda, iwork, anorm, rcond,
632 $
CALL alaerh( path,
'ZHECON', info, 0, uplo, n, n,
633 $ -1, -1, -1, imat, nfail, nerrs, nout )
635 result( 9 ) = dget06( rcond, rcondc )
640 IF( result( 9 ).GE.thresh )
THEN
641 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
642 $
CALL alahd( nout, path )
643 WRITE( nout, fmt = 9997 )uplo, n, imat, 9,
655 CALL alasum( path, nout, nfail, nrun, nerrs )
657 9999
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
', NB =', i4,
', type ',
658 $ i2,
', test ', i2,
', ratio =', g12.5 )
659 9998
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
', NRHS=', i3,
', type ',
660 $ i2,
', test(', i2,
') =', g12.5 )
661 9997
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
',', 10x,
' type ', i2,
662 $
', test(', i2,
') =', g12.5 )
subroutine alasum(type, nout, nfail, nrun, nerrs)
ALASUM
subroutine xlaenv(ispec, nvalue)
XLAENV
subroutine zlarhs(path, xtype, uplo, trans, m, n, kl, ku, nrhs, a, lda, x, ldx, b, ldb, iseed, info)
ZLARHS
subroutine alaerh(path, subnam, info, infoe, opts, m, n, kl, ku, n5, imat, nfail, nerrs, nout)
ALAERH
subroutine alahd(iounit, path)
ALAHD
subroutine zhecon(uplo, n, a, lda, ipiv, anorm, rcond, work, info)
ZHECON
subroutine zherfs(uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x, ldx, ferr, berr, work, rwork, info)
ZHERFS
subroutine zhetrf(uplo, n, a, lda, ipiv, work, lwork, info)
ZHETRF
subroutine zhetri2(uplo, n, a, lda, ipiv, work, lwork, info)
ZHETRI2
subroutine zhetrs2(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, info)
ZHETRS2
subroutine zhetrs(uplo, n, nrhs, a, lda, ipiv, b, ldb, info)
ZHETRS
subroutine zlacpy(uplo, m, n, a, lda, b, ldb)
ZLACPY copies all or part of one two-dimensional array to another.
subroutine zchkhe(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
ZCHKHE
subroutine zerrhe(path, nunit)
ZERRHE
subroutine zget04(n, nrhs, x, ldx, xact, ldxact, rcond, resid)
ZGET04
subroutine zhet01(uplo, n, a, lda, afac, ldafac, ipiv, c, ldc, rwork, resid)
ZHET01
subroutine zlaipd(n, a, inda, vinda)
ZLAIPD
subroutine zlatb4(path, imat, m, n, type, kl, ku, anorm, mode, cndnum, dist)
ZLATB4
subroutine zlatms(m, n, dist, iseed, sym, d, mode, cond, dmax, kl, ku, pack, a, lda, work, info)
ZLATMS
subroutine zpot02(uplo, n, nrhs, a, lda, x, ldx, b, ldb, rwork, resid)
ZPOT02
subroutine zpot03(uplo, n, a, lda, ainv, ldainv, work, ldwork, rwork, rcond, resid)
ZPOT03
subroutine zpot05(uplo, n, nrhs, a, lda, b, ldb, x, ldx, xact, ldxact, ferr, berr, reslts)
ZPOT05