174 SUBROUTINE cchkhe_rk( DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL,
175 $ THRESH, TSTERR, NMAX, A, AFAC, E, AINV, B,
176 $ X, XACT, WORK, RWORK, IWORK, NOUT )
184 INTEGER NMAX, NN, NNB, NNS, NOUT
189 INTEGER IWORK( * ), NBVAL( * ), NSVAL( * ), NVAL( * )
191 COMPLEX A( * ), AFAC( * ), AINV( * ), B( * ), E( * ),
192 $ work( * ), x( * ), xact( * )
199 PARAMETER ( ZERO = 0.0e+0, one = 1.0e+0 )
201 parameter( onehalf = 0.5e+0 )
203 parameter( eight = 8.0e+0, sevten = 17.0e+0 )
205 parameter( czero = ( 0.0e+0, 0.0e+0 ) )
207 parameter( ntypes = 10 )
209 parameter( ntests = 7 )
212 LOGICAL TRFCON, ZEROT
213 CHARACTER DIST,
TYPE, UPLO, XTYPE
214 CHARACTER*3 PATH, MATPATH
215 INTEGER I, I1, I2, IMAT, IN, INB, INFO, IOFF, IRHS,
216 $ itemp, itemp2, iuplo, izero, j, k, kl, ku, lda,
217 $ lwork, mode, n, nb, nerrs, nfail, nimat, nrhs,
219 REAL ALPHA, ANORM, CNDNUM, CONST, SING_MAX,
220 $ SING_MIN, RCOND, RCONDC, STEMP
224 INTEGER ISEED( 4 ), ISEEDY( 4 ), IDUMMY( 1 )
225 REAL RESULT( NTESTS )
226 COMPLEX BLOCK( 2, 2 ), CDUMMY( 1 )
229 REAL CLANGE, CLANHE, SGET06
230 EXTERNAL CLANGE, CLANHE, SGET06
239 INTRINSIC conjg, max, min, sqrt
247 COMMON / infoc / infot, nunit, ok, lerr
248 COMMON / srnamc / srnamt
251 DATA iseedy / 1988, 1989, 1990, 1991 /
252 DATA uplos /
'U',
'L' /
258 alpha = ( one+sqrt( sevten ) ) / eight
262 path( 1: 1 ) =
'Complex precision'
267 matpath( 1: 1 ) =
'Complex precision'
268 matpath( 2: 3 ) =
'HE'
274 iseed( i ) = iseedy( i )
280 $
CALL cerrhe( path, nout )
302 DO 260 imat = 1, nimat
306 IF( .NOT.dotype( imat ) )
311 zerot = imat.GE.3 .AND. imat.LE.6
312 IF( zerot .AND. n.LT.imat-2 )
318 uplo = uplos( iuplo )
325 CALL clatb4( matpath, imat, n, n,
TYPE, kl, ku, anorm,
326 $ mode, cndnum, dist )
331 CALL clatms( n, n, dist, iseed,
TYPE, rwork, mode,
332 $ cndnum, anorm, kl, ku, uplo, a, lda,
338 CALL alaerh( path,
'CLATMS', info, 0, uplo, n, n,
339 $ -1, -1, -1, imat, nfail, nerrs, nout )
353 ELSE IF( imat.EQ.4 )
THEN
363 IF( iuplo.EQ.1 )
THEN
364 ioff = ( izero-1 )*lda
365 DO 20 i = 1, izero - 1
375 DO 40 i = 1, izero - 1
385 IF( iuplo.EQ.1 )
THEN
432 CALL clacpy( uplo, n, n, a, lda, afac, lda )
439 lwork = max( 2, nb )*lda
441 CALL chetrf_rk( uplo, n, afac, lda, e, iwork, ainv,
450 IF( iwork( k ).LT.0 )
THEN
451 IF( iwork( k ).NE.-k )
THEN
455 ELSE IF( iwork( k ).NE.k )
THEN
464 $
CALL alaerh( path,
'CHETRF_RK', info, k,
465 $ uplo, n, n, -1, -1, nb, imat,
466 $ nfail, nerrs, nout )
479 CALL chet01_3( uplo, n, a, lda, afac, lda, e, iwork,
480 $ ainv, lda, rwork, result( 1 ) )
489 IF( inb.EQ.1 .AND. .NOT.trfcon )
THEN
490 CALL clacpy( uplo, n, n, afac, lda, ainv, lda )
497 lwork = (n+nb+1)*(nb+3)
498 CALL chetri_3( uplo, n, ainv, lda, e, iwork, work,
504 $
CALL alaerh( path,
'CHETRI_3', info, -1,
505 $ uplo, n, n, -1, -1, -1, imat,
506 $ nfail, nerrs, nout )
511 CALL cpot03( uplo, n, a, lda, ainv, lda, work, lda,
512 $ rwork, rcondc, result( 2 ) )
520 IF( result( k ).GE.thresh )
THEN
521 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
522 $
CALL alahd( nout, path )
523 WRITE( nout, fmt = 9999 )uplo, n, nb, imat, k,
536 const = ( ( alpha**2-one ) / ( alpha**2-onehalf ) ) /
539 IF( iuplo.EQ.1 )
THEN
548 IF( iwork( k ).GT.zero )
THEN
553 stemp = clange(
'M', k-1, 1,
554 $ afac( ( k-1 )*lda+1 ), lda, rwork )
560 stemp = clange(
'M', k-2, 2,
561 $ afac( ( k-2 )*lda+1 ), lda, rwork )
568 stemp = stemp - const + thresh
569 IF( stemp.GT.result( 3 ) )
570 $ result( 3 ) = stemp
586 IF( iwork( k ).GT.zero )
THEN
591 stemp = clange(
'M', n-k, 1,
592 $ afac( ( k-1 )*lda+k+1 ), lda, rwork )
598 stemp = clange(
'M', n-k-1, 2,
599 $ afac( ( k-1 )*lda+k+2 ), lda, rwork )
606 stemp = stemp - const + thresh
607 IF( stemp.GT.result( 3 ) )
608 $ result( 3 ) = stemp
624 const = ( ( alpha**2-one ) / ( alpha**2-onehalf ) )*
625 $ ( ( one + alpha ) / ( one - alpha ) )
626 CALL clacpy( uplo, n, n, afac, lda, ainv, lda )
628 IF( iuplo.EQ.1 )
THEN
637 IF( iwork( k ).LT.zero )
THEN
643 block( 1, 1 ) = afac( ( k-2 )*lda+k-1 )
644 block( 1, 2 ) = e( k )
645 block( 2, 1 ) = conjg( block( 1, 2 ) )
646 block( 2, 2 ) = afac( (k-1)*lda+k )
648 CALL cgesvd(
'N',
'N', 2, 2, block, 2, rwork,
649 $ cdummy, 1, cdummy, 1,
650 $ work, 6, rwork( 3 ), info )
653 sing_max = rwork( 1 )
654 sing_min = rwork( 2 )
656 stemp = sing_max / sing_min
660 stemp = stemp - const + thresh
661 IF( stemp.GT.result( 4 ) )
662 $ result( 4 ) = stemp
681 IF( iwork( k ).LT.zero )
THEN
687 block( 1, 1 ) = afac( ( k-1 )*lda+k )
688 block( 2, 1 ) = e( k )
689 block( 1, 2 ) = conjg( block( 2, 1 ) )
690 block( 2, 2 ) = afac( k*lda+k+1 )
692 CALL cgesvd(
'N',
'N', 2, 2, block, 2, rwork,
693 $ cdummy, 1, cdummy, 1,
694 $ work, 6, rwork(3), info )
696 sing_max = rwork( 1 )
697 sing_min = rwork( 2 )
699 stemp = sing_max / sing_min
703 stemp = stemp - const + thresh
704 IF( stemp.GT.result( 4 ) )
705 $ result( 4 ) = stemp
720 IF( result( k ).GE.thresh )
THEN
721 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
722 $
CALL alahd( nout, path )
723 WRITE( nout, fmt = 9999 )uplo, n, nb, imat, k,
758 CALL clarhs( matpath, xtype, uplo,
' ', n, n,
759 $ kl, ku, nrhs, a, lda, xact, lda,
760 $ b, lda, iseed, info )
761 CALL clacpy(
'Full', n, nrhs, b, lda, x, lda )
764 CALL chetrs_3( uplo, n, nrhs, afac, lda, e, iwork,
770 $
CALL alaerh( path,
'CHETRS_3', info, 0,
771 $ uplo, n, n, -1, -1, nrhs, imat,
772 $ nfail, nerrs, nout )
774 CALL clacpy(
'Full', n, nrhs, b, lda, work, lda )
778 CALL cpot02( uplo, n, nrhs, a, lda, x, lda, work,
779 $ lda, rwork, result( 5 ) )
784 CALL cget04( n, nrhs, x, lda, xact, lda, rcondc,
791 IF( result( k ).GE.thresh )
THEN
792 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
793 $
CALL alahd( nout, path )
794 WRITE( nout, fmt = 9998 )uplo, n, nrhs,
795 $ imat, k, result( k )
809 anorm = clanhe(
'1', uplo, n, a, lda, rwork )
811 CALL checon_3( uplo, n, afac, lda, e, iwork, anorm,
812 $ rcond, work, info )
817 $
CALL alaerh( path,
'CHECON_3', info, 0,
818 $ uplo, n, n, -1, -1, -1, imat,
819 $ nfail, nerrs, nout )
823 result( 7 ) = sget06( rcond, rcondc )
828 IF( result( 7 ).GE.thresh )
THEN
829 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
830 $
CALL alahd( nout, path )
831 WRITE( nout, fmt = 9997 )uplo, n, imat, 7,
844 CALL alasum( path, nout, nfail, nrun, nerrs )
846 9999
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
', NB =', i4,
', type ',
847 $ i2,
', test ', i2,
', ratio =', g12.5 )
848 9998
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
', NRHS=', i3,
', type ',
849 $ i2,
', test ', i2,
', ratio =', g12.5 )
850 9997
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
',', 10x,
' type ', i2,
851 $
', test ', i2,
', ratio =', 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_rk(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, e, ainv, b, x, xact, work, rwork, iwork, nout)
CCHKHE_RK
subroutine cerrhe(path, nunit)
CERRHE
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 cpot03(uplo, n, a, lda, ainv, ldainv, work, ldwork, rwork, rcond, resid)
CPOT03
subroutine cgesvd(jobu, jobvt, m, n, a, lda, s, u, ldu, vt, ldvt, work, lwork, rwork, info)
CGESVD computes the singular value decomposition (SVD) for GE matrices
subroutine checon_3(uplo, n, a, lda, e, ipiv, anorm, rcond, work, info)
CHECON_3
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 chetri_3(uplo, n, a, lda, e, ipiv, work, lwork, info)
CHETRI_3
subroutine chetrs_3(uplo, n, nrhs, a, lda, e, ipiv, b, ldb, info)
CHETRS_3
subroutine clacpy(uplo, m, n, a, lda, b, ldb)
CLACPY copies all or part of one two-dimensional array to another.