168 SUBROUTINE cchksy( 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 = 11 )
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 SGET06, CLANSY
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 cerrsy( 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 )
299 IF( imat.NE.ntypes )
THEN
304 CALL clatb4( path, imat, n, n,
TYPE, kl, ku, anorm,
305 $ mode, cndnum, dist )
310 CALL clatms( n, n, dist, iseed,
TYPE, rwork, mode,
311 $ cndnum, anorm, kl, ku,
'N', a, lda, work,
317 CALL alaerh( path,
'CLATMS', info, 0, uplo, n, n,
318 $ -1, -1, -1, imat, nfail, nerrs, nout )
332 ELSE IF( imat.EQ.4 )
THEN
342 IF( iuplo.EQ.1 )
THEN
343 ioff = ( izero-1 )*lda
344 DO 20 i = 1, izero - 1
354 DO 40 i = 1, izero - 1
364 IF( iuplo.EQ.1 )
THEN
400 CALL clatsy( uplo, n, a, lda, iseed )
421 CALL clacpy( uplo, n, n, a, lda, afac, lda )
428 lwork = max( 2, nb )*lda
430 CALL csytrf( uplo, n, afac, lda, iwork, ainv, lwork,
439 IF( iwork( k ).LT.0 )
THEN
440 IF( iwork( k ).NE.-k )
THEN
444 ELSE IF( iwork( k ).NE.k )
THEN
453 $
CALL alaerh( path,
'CSYTRF', info, k, uplo, n, n,
454 $ -1, -1, nb, imat, nfail, nerrs, nout )
467 CALL csyt01( uplo, n, a, lda, afac, lda, iwork, ainv,
468 $ lda, rwork, result( 1 ) )
477 IF( inb.EQ.1 .AND. .NOT.trfcon )
THEN
478 CALL clacpy( uplo, n, n, afac, lda, ainv, lda )
480 lwork = (n+nb+1)*(nb+3)
481 CALL csytri2( uplo, n, ainv, lda, iwork, work,
487 $
CALL alaerh( path,
'CSYTRI2', info, 0, uplo, n,
488 $ n, -1, -1, -1, imat, nfail, nerrs,
494 CALL csyt03( uplo, n, a, lda, ainv, lda, work, lda,
495 $ rwork, rcondc, result( 2 ) )
503 IF( result( k ).GE.thresh )
THEN
504 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
505 $
CALL alahd( nout, path )
506 WRITE( nout, fmt = 9999 )uplo, n, nb, imat, k,
538 CALL clarhs( path, xtype, uplo,
' ', n, n, kl, ku,
539 $ nrhs, a, lda, xact, lda, b, lda,
541 CALL clacpy(
'Full', n, nrhs, b, lda, x, lda )
544 CALL csytrs( uplo, n, nrhs, afac, lda, iwork, x,
550 $
CALL alaerh( path,
'CSYTRS', info, 0, uplo, n,
551 $ n, -1, -1, nrhs, imat, nfail,
554 CALL clacpy(
'Full', n, nrhs, b, lda, work, lda )
558 CALL csyt02( uplo, n, nrhs, a, lda, x, lda, work,
559 $ lda, rwork, result( 3 ) )
568 CALL clarhs( path, xtype, uplo,
' ', n, n, kl, ku,
569 $ nrhs, a, lda, xact, lda, b, lda,
571 CALL clacpy(
'Full', n, nrhs, b, lda, x, lda )
574 CALL csytrs2( uplo, n, nrhs, afac, lda, iwork, x,
580 $
CALL alaerh( path,
'CSYTRS2', info, 0, uplo, n,
581 $ n, -1, -1, nrhs, imat, nfail,
584 CALL clacpy(
'Full', n, nrhs, b, lda, work, lda )
588 CALL csyt02( uplo, n, nrhs, a, lda, x, lda, work,
589 $ lda, rwork, result( 4 ) )
594 CALL cget04( n, nrhs, x, lda, xact, lda, rcondc,
601 CALL csyrfs( uplo, n, nrhs, a, lda, afac, lda,
602 $ iwork, b, lda, x, lda, rwork,
603 $ rwork( nrhs+1 ), work,
604 $ rwork( 2*nrhs+1 ), info )
609 $
CALL alaerh( path,
'CSYRFS', info, 0, uplo, n,
610 $ n, -1, -1, nrhs, imat, nfail,
613 CALL cget04( n, nrhs, x, lda, xact, lda, rcondc,
615 CALL cpot05( uplo, n, nrhs, a, lda, b, lda, x, lda,
616 $ xact, lda, rwork, rwork( nrhs+1 ),
623 IF( result( k ).GE.thresh )
THEN
624 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
625 $
CALL alahd( nout, path )
626 WRITE( nout, fmt = 9998 )uplo, n, nrhs,
627 $ imat, k, result( k )
641 anorm = clansy(
'1', uplo, n, a, lda, rwork )
643 CALL csycon( uplo, n, afac, lda, iwork, anorm, rcond,
649 $
CALL alaerh( path,
'CSYCON', info, 0, uplo, n, n,
650 $ -1, -1, -1, imat, nfail, nerrs, nout )
654 result( 9 ) = sget06( rcond, rcondc )
659 IF( result( 9 ).GE.thresh )
THEN
660 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
661 $
CALL alahd( nout, path )
662 WRITE( nout, fmt = 9997 )uplo, n, imat, 9,
674 CALL alasum( path, nout, nfail, nrun, nerrs )
676 9999
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
', NB =', i4,
', type ',
677 $ i2,
', test ', i2,
', ratio =', g12.5 )
678 9998
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
', NRHS=', i3,
', type ',
679 $ i2,
', test(', i2,
') =', g12.5 )
680 9997
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
',', 10x,
' type ', i2,
681 $
', 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 cchksy(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
CCHKSY
subroutine cerrsy(path, nunit)
CERRSY
subroutine cget04(n, nrhs, x, ldx, xact, ldxact, rcond, resid)
CGET04
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 clatsy(uplo, n, x, ldx, iseed)
CLATSY
subroutine cpot05(uplo, n, nrhs, a, lda, b, ldb, x, ldx, xact, ldxact, ferr, berr, reslts)
CPOT05
subroutine csyt01(uplo, n, a, lda, afac, ldafac, ipiv, c, ldc, rwork, resid)
CSYT01
subroutine csyt02(uplo, n, nrhs, a, lda, x, ldx, b, ldb, rwork, resid)
CSYT02
subroutine csyt03(uplo, n, a, lda, ainv, ldainv, work, ldwork, rwork, rcond, resid)
CSYT03
subroutine csycon(uplo, n, a, lda, ipiv, anorm, rcond, work, info)
CSYCON
subroutine csyrfs(uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x, ldx, ferr, berr, work, rwork, info)
CSYRFS
subroutine csytrf(uplo, n, a, lda, ipiv, work, lwork, info)
CSYTRF
subroutine csytri2(uplo, n, a, lda, ipiv, work, lwork, info)
CSYTRI2
subroutine csytrs2(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, info)
CSYTRS2
subroutine csytrs(uplo, n, nrhs, a, lda, ipiv, b, ldb, info)
CSYTRS
subroutine clacpy(uplo, m, n, a, lda, b, ldb)
CLACPY copies all or part of one two-dimensional array to another.