168 SUBROUTINE cchkhe( 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
183 INTEGER IWORK( * ), NBVAL( * ), NSVAL( * ), NVAL( * )
185 COMPLEX A( * ), AFAC( * ), AINV( * ), B( * ),
186 $ work( * ), x( * ), xact( * )
193 PARAMETER ( ZERO = 0.0e+0 )
195 parameter( czero = ( 0.0e+0, 0.0e+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 REAL ANORM, CNDNUM, RCOND, RCONDC
212 INTEGER ISEED( 4 ), ISEEDY( 4 )
213 REAL RESULT( NTESTS )
217 EXTERNAL CLANHE, SGET06
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 ) =
'Complex precision'
251 iseed( i ) = iseedy( i )
257 $
CALL cerrhe( path, nout )
279 DO 170 imat = 1, nimat
283 IF( .NOT.dotype( imat ) )
288 zerot = imat.GE.3 .AND. imat.LE.6
289 IF( zerot .AND. n.LT.imat-2 )
295 uplo = uplos( iuplo )
303 CALL clatb4( path, imat, n, n,
TYPE, kl, ku, anorm, mode,
309 CALL clatms( n, n, dist, iseed,
TYPE, rwork, mode,
310 $ cndnum, anorm, kl, ku, uplo, a, lda, work,
316 CALL alaerh( path,
'CLATMS', info, 0, uplo, n, n, -1,
317 $ -1, -1, imat, nfail, nerrs, nout )
331 ELSE IF( imat.EQ.4 )
THEN
341 IF( iuplo.EQ.1 )
THEN
342 ioff = ( izero-1 )*lda
343 DO 20 i = 1, izero - 1
353 DO 40 i = 1, izero - 1
363 IF( iuplo.EQ.1 )
THEN
395 CALL claipd( n, a, lda+1, 0 )
414 CALL clacpy( uplo, n, n, a, lda, afac, lda )
421 lwork = max( 2, nb )*lda
423 CALL chetrf( uplo, n, afac, lda, iwork, ainv, lwork,
432 IF( iwork( k ).LT.0 )
THEN
433 IF( iwork( k ).NE.-k )
THEN
437 ELSE IF( iwork( k ).NE.k )
THEN
446 $
CALL alaerh( path,
'CHETRF', info, k, uplo, n, n,
447 $ -1, -1, nb, imat, nfail, nerrs, nout )
460 CALL chet01( uplo, n, a, lda, afac, lda, iwork, ainv,
461 $ lda, rwork, result( 1 ) )
470 IF( inb.EQ.1 .AND. .NOT.trfcon )
THEN
471 CALL clacpy( uplo, n, n, afac, lda, ainv, lda )
473 lwork = (n+nb+1)*(nb+3)
474 CALL chetri2( uplo, n, ainv, lda, iwork, work,
480 $
CALL alaerh( path,
'CHETRI2', info, -1, uplo, n,
481 $ n, -1, -1, -1, imat, nfail, nerrs,
487 CALL cpot03( uplo, n, a, lda, ainv, lda, work, lda,
488 $ rwork, rcondc, result( 2 ) )
496 IF( result( k ).GE.thresh )
THEN
497 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
498 $
CALL alahd( nout, path )
499 WRITE( nout, fmt = 9999 )uplo, n, nb, imat, k,
531 CALL clarhs( path, xtype, uplo,
' ', n, n, kl, ku,
532 $ nrhs, a, lda, xact, lda, b, lda,
534 CALL clacpy(
'Full', n, nrhs, b, lda, x, lda )
537 CALL chetrs( uplo, n, nrhs, afac, lda, iwork, x,
543 $
CALL alaerh( path,
'CHETRS', info, 0, uplo, n,
544 $ n, -1, -1, nrhs, imat, nfail,
547 CALL clacpy(
'Full', n, nrhs, b, lda, work, lda )
551 CALL cpot02( uplo, n, nrhs, a, lda, x, lda, work,
552 $ lda, rwork, result( 3 ) )
561 CALL clarhs( path, xtype, uplo,
' ', n, n, kl, ku,
562 $ nrhs, a, lda, xact, lda, b, lda,
564 CALL clacpy(
'Full', n, nrhs, b, lda, x, lda )
567 CALL chetrs2( uplo, n, nrhs, afac, lda, iwork, x,
573 $
CALL alaerh( path,
'CHETRS2', info, 0, uplo, n,
574 $ n, -1, -1, nrhs, imat, nfail,
577 CALL clacpy(
'Full', n, nrhs, b, lda, work, lda )
581 CALL cpot02( uplo, n, nrhs, a, lda, x, lda, work,
582 $ lda, rwork, result( 4 ) )
587 CALL cget04( n, nrhs, x, lda, xact, lda, rcondc,
594 CALL cherfs( uplo, n, nrhs, a, lda, afac, lda,
595 $ iwork, b, lda, x, lda, rwork,
596 $ rwork( nrhs+1 ), work,
597 $ rwork( 2*nrhs+1 ), info )
602 $
CALL alaerh( path,
'CHERFS', info, 0, uplo, n,
603 $ n, -1, -1, nrhs, imat, nfail,
606 CALL cget04( n, nrhs, x, lda, xact, lda, rcondc,
608 CALL cpot05( uplo, n, nrhs, a, lda, b, lda, x, lda,
609 $ xact, lda, rwork, rwork( nrhs+1 ),
616 IF( result( k ).GE.thresh )
THEN
617 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
618 $
CALL alahd( nout, path )
619 WRITE( nout, fmt = 9998 )uplo, n, nrhs,
620 $ imat, k, result( k )
634 anorm = clanhe(
'1', uplo, n, a, lda, rwork )
636 CALL checon( uplo, n, afac, lda, iwork, anorm, rcond,
642 $
CALL alaerh( path,
'CHECON', info, 0, uplo, n, n,
643 $ -1, -1, -1, imat, nfail, nerrs, nout )
647 result( 9 ) = sget06( rcond, rcondc )
652 IF( result( 9 ).GE.thresh )
THEN
653 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
654 $
CALL alahd( nout, path )
655 WRITE( nout, fmt = 9997 )uplo, n, imat, 8,
667 CALL alasum( path, nout, nfail, nrun, nerrs )
669 9999
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
', NB =', i4,
', type ',
670 $ i2,
', test ', i2,
', ratio =', g12.5 )
671 9998
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
', NRHS=', i3,
', type ',
672 $ i2,
', test(', i2,
') =', g12.5 )
673 9997
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
',', 10x,
' type ', i2,
674 $
', test(', i2,
') =', g12.5 )
subroutine alasum(type, nout, nfail, nrun, nerrs)
ALASUM
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 alaerh(path, subnam, info, infoe, opts, m, n, kl, ku, n5, imat, nfail, nerrs, nout)
ALAERH
subroutine alahd(iounit, path)
ALAHD
subroutine cchkhe(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
CCHKHE
subroutine cerrhe(path, nunit)
CERRHE
subroutine cget04(n, nrhs, x, ldx, xact, ldxact, rcond, resid)
CGET04
subroutine chet01(uplo, n, a, lda, afac, ldafac, ipiv, c, ldc, rwork, resid)
CHET01
subroutine claipd(n, a, inda, vinda)
CLAIPD
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 cpot03(uplo, n, a, lda, ainv, ldainv, work, ldwork, rwork, rcond, resid)
CPOT03
subroutine cpot05(uplo, n, nrhs, a, lda, b, ldb, x, ldx, xact, ldxact, ferr, berr, reslts)
CPOT05
subroutine checon(uplo, n, a, lda, ipiv, anorm, rcond, work, info)
CHECON
subroutine cherfs(uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x, ldx, ferr, berr, work, rwork, info)
CHERFS
subroutine chetrf(uplo, n, a, lda, ipiv, work, lwork, info)
CHETRF
subroutine chetri2(uplo, n, a, lda, ipiv, work, lwork, info)
CHETRI2
subroutine chetrs2(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, info)
CHETRS2
subroutine chetrs(uplo, n, nrhs, a, lda, ipiv, b, ldb, info)
CHETRS
subroutine clacpy(uplo, m, n, a, lda, b, ldb)
CLACPY copies all or part of one two-dimensional array to another.