161 SUBROUTINE cchkhp( DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR,
162 $ NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK,
171 INTEGER NMAX, NN, NNS, NOUT
176 INTEGER IWORK( * ), NSVAL( * ), NVAL( * )
178 COMPLEX A( * ), AFAC( * ), AINV( * ), B( * ),
179 $ work( * ), x( * ), xact( * )
186 PARAMETER ( ZERO = 0.0e+0 )
188 parameter( ntypes = 10 )
190 parameter( ntests = 8 )
193 LOGICAL TRFCON, ZEROT
194 CHARACTER DIST, PACKIT,
TYPE, UPLO, XTYPE
196 INTEGER I, I1, I2, IMAT, IN, INFO, IOFF, IRHS, IUPLO,
197 $ izero, j, k, kl, ku, lda, mode, n, nerrs,
198 $ nfail, nimat, npp, nrhs, nrun, nt
199 REAL ANORM, CNDNUM, RCOND, RCONDC
203 INTEGER ISEED( 4 ), ISEEDY( 4 )
204 REAL RESULT( NTESTS )
209 EXTERNAL lsame, clanhp, sget06
226 COMMON / infoc / infot, nunit, ok, lerr
227 COMMON / srnamc / srnamt
230 DATA iseedy / 1988, 1989, 1990, 1991 /
231 DATA uplos /
'U',
'L' /
237 path( 1: 1 ) =
'Complex precision'
243 iseed( i ) = iseedy( i )
249 $
CALL cerrsy( path, nout )
263 DO 160 imat = 1, nimat
267 IF( .NOT.dotype( imat ) )
272 zerot = imat.GE.3 .AND. imat.LE.6
273 IF( zerot .AND. n.LT.imat-2 )
279 uplo = uplos( iuplo )
280 IF( lsame( uplo,
'U' ) )
THEN
289 CALL clatb4( path, imat, n, n,
TYPE, kl, ku, anorm, mode,
293 CALL clatms( n, n, dist, iseed,
TYPE, rwork, mode,
294 $ cndnum, anorm, kl, ku, packit, 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 )*izero / 2
323 DO 20 i = 1, izero - 1
333 DO 40 i = 1, izero - 1
344 IF( iuplo.EQ.1 )
THEN
374 IF( iuplo.EQ.1 )
THEN
377 CALL claipd( n, a, n, -1 )
383 CALL ccopy( npp, a, 1, afac, 1 )
385 CALL chptrf( uplo, n, afac, iwork, info )
393 IF( iwork( k ).LT.0 )
THEN
394 IF( iwork( k ).NE.-k )
THEN
398 ELSE IF( iwork( k ).NE.k )
THEN
407 $
CALL alaerh( path,
'CHPTRF', info, k, uplo, n, n, -1,
408 $ -1, -1, imat, nfail, nerrs, nout )
418 CALL chpt01( uplo, n, a, afac, iwork, ainv, lda, rwork,
425 IF( .NOT.trfcon )
THEN
426 CALL ccopy( npp, afac, 1, ainv, 1 )
428 CALL chptri( uplo, n, ainv, iwork, work, info )
433 $
CALL alaerh( path,
'CHPTRI', info, 0, uplo, n, n,
434 $ -1, -1, -1, imat, nfail, nerrs, nout )
436 CALL cppt03( uplo, n, a, ainv, work, lda, rwork,
437 $ rcondc, result( 2 ) )
445 IF( result( k ).GE.thresh )
THEN
446 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
447 $
CALL alahd( nout, path )
448 WRITE( nout, fmt = 9999 )uplo, n, imat, k,
469 CALL clarhs( path, xtype, uplo,
' ', n, n, kl, ku,
470 $ nrhs, a, lda, xact, lda, b, lda, iseed,
473 CALL clacpy(
'Full', n, nrhs, b, lda, x, lda )
476 CALL chptrs( uplo, n, nrhs, afac, iwork, x, lda,
482 $
CALL alaerh( path,
'CHPTRS', info, 0, uplo, n, n,
483 $ -1, -1, nrhs, imat, nfail, nerrs,
486 CALL clacpy(
'Full', n, nrhs, b, lda, work, lda )
487 CALL cppt02( uplo, n, nrhs, a, x, lda, work, lda,
488 $ rwork, result( 3 ) )
493 CALL cget04( n, nrhs, x, lda, xact, lda, rcondc,
500 CALL chprfs( uplo, n, nrhs, a, afac, iwork, b, lda, x,
501 $ lda, rwork, rwork( nrhs+1 ), work,
502 $ rwork( 2*nrhs+1 ), info )
507 $
CALL alaerh( path,
'CHPRFS', info, 0, uplo, n, n,
508 $ -1, -1, nrhs, imat, nfail, nerrs,
511 CALL cget04( n, nrhs, x, lda, xact, lda, rcondc,
513 CALL cppt05( uplo, n, nrhs, a, b, lda, x, lda, xact,
514 $ lda, rwork, rwork( nrhs+1 ),
521 IF( result( k ).GE.thresh )
THEN
522 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
523 $
CALL alahd( nout, path )
524 WRITE( nout, fmt = 9998 )uplo, n, nrhs, imat,
536 anorm = clanhp(
'1', uplo, n, a, rwork )
538 CALL chpcon( uplo, n, afac, iwork, anorm, rcond, work,
544 $
CALL alaerh( path,
'CHPCON', info, 0, uplo, n, n, -1,
545 $ -1, -1, imat, nfail, nerrs, nout )
547 result( 8 ) = sget06( rcond, rcondc )
551 IF( result( 8 ).GE.thresh )
THEN
552 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
553 $
CALL alahd( nout, path )
554 WRITE( nout, fmt = 9999 )uplo, n, imat, 8,
565 CALL alasum( path, nout, nfail, nrun, nerrs )
567 9999
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
', type ', i2,
', test ',
568 $ i2,
', ratio =', g12.5 )
569 9998
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
', NRHS=', i3,
', type ',
570 $ i2,
', 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 alaerh(path, subnam, info, infoe, opts, m, n, kl, ku, n5, imat, nfail, nerrs, nout)
ALAERH
subroutine alahd(iounit, path)
ALAHD
subroutine cchkhp(dotype, nn, nval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
CCHKHP
subroutine cerrsy(path, nunit)
CERRSY
subroutine cget04(n, nrhs, x, ldx, xact, ldxact, rcond, resid)
CGET04
subroutine chpt01(uplo, n, a, afac, ipiv, c, ldc, rwork, resid)
CHPT01
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 cppt02(uplo, n, nrhs, a, x, ldx, b, ldb, rwork, resid)
CPPT02
subroutine cppt03(uplo, n, a, ainv, work, ldwork, rwork, rcond, resid)
CPPT03
subroutine cppt05(uplo, n, nrhs, ap, b, ldb, x, ldx, xact, ldxact, ferr, berr, reslts)
CPPT05
subroutine ccopy(n, cx, incx, cy, incy)
CCOPY
subroutine chpcon(uplo, n, ap, ipiv, anorm, rcond, work, info)
CHPCON
subroutine chprfs(uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx, ferr, berr, work, rwork, info)
CHPRFS
subroutine chptrf(uplo, n, ap, ipiv, info)
CHPTRF
subroutine chptri(uplo, n, ap, ipiv, work, info)
CHPTRI
subroutine chptrs(uplo, n, nrhs, ap, ipiv, b, ldb, info)
CHPTRS
subroutine clacpy(uplo, m, n, a, lda, b, ldb)
CLACPY copies all or part of one two-dimensional array to another.