172 SUBROUTINE cchksy( DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL,
173 $ thresh, tsterr, nmax, a, afac, ainv, b, x,
174 $ xact, work, rwork, iwork, nout )
183 INTEGER nmax, nn, nnb, nns, nout
188 INTEGER iwork( * ), nbval( * ), nsval( * ), nval( * )
190 COMPLEX a( * ), afac( * ), ainv( * ), b( * ),
191 $ work( * ), x( * ), xact( * )
198 parameter( zero = 0.0e+0 )
200 parameter( czero = ( 0.0e+0, 0.0e+0 ) )
202 parameter( ntypes = 11 )
204 parameter( ntests = 9 )
207 LOGICAL trfcon, zerot
208 CHARACTER dist, type, uplo, xtype
210 INTEGER i, i1, i2, imat, in, inb, info, ioff, irhs,
211 $ iuplo, izero, j, k, kl, ku, lda, lwork, mode,
212 $ n, nb, nerrs, nfail, nimat, nrhs, nrun, nt
213 REAL anorm, cndnum, rcond, rcondc
217 INTEGER iseed( 4 ), iseedy( 4 )
218 REAL result( ntests )
239 common / infoc / infot, nunit, ok, lerr
240 common / srnamc / srnamt
243 DATA iseedy / 1988, 1989, 1990, 1991 /
244 DATA uplos /
'U',
'L' /
250 path( 1: 1 ) =
'Complex precision'
256 iseed( i ) = iseedy( i )
262 $ CALL
cerrsy( path, nout )
284 DO 170 imat = 1, nimat
288 IF( .NOT.dotype( imat ) )
293 zerot = imat.GE.3 .AND. imat.LE.6
294 IF( zerot .AND. n.LT.imat-2 )
300 uplo = uplos( iuplo )
302 IF( imat.NE.ntypes )
THEN
309 CALL
clatb4( path, imat, n, n, type, kl, ku, anorm,
310 $ mode, cndnum, dist )
315 CALL
clatms( n, n, dist, iseed, type, rwork, mode,
316 $ cndnum, anorm, kl, ku,
'N', a, lda, work,
322 CALL
alaerh( path,
'CLATMS', info, 0, uplo, n, n,
323 $ -1, -1, -1, imat, nfail, nerrs, nout )
334 ELSE IF( imat.EQ.4 )
THEN
344 IF( iuplo.EQ.1 )
THEN
345 ioff = ( izero-1 )*lda
346 DO 20 i = 1, izero - 1
356 DO 40 i = 1, izero - 1
366 IF( iuplo.EQ.1 )
THEN
403 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,
536 CALL
clarhs( path, xtype, uplo,
' ', n, n, kl, ku,
537 $ nrhs, a, lda, xact, lda, b, lda,
539 CALL
clacpy(
'Full', n, nrhs, b, lda, x, lda )
542 CALL
csytrs( uplo, n, nrhs, afac, lda, iwork, x,
548 $ CALL
alaerh( path,
'CSYTRS', info, 0, uplo, n,
549 $ n, -1, -1, nrhs, imat, nfail,
552 CALL
clacpy(
'Full', n, nrhs, b, lda, work, lda )
556 CALL
csyt02( uplo, n, nrhs, a, lda, x, lda, work,
557 $ lda, rwork, result( 3 ) )
566 CALL
clarhs( path, xtype, uplo,
' ', n, n, kl, ku,
567 $ nrhs, a, lda, xact, lda, b, lda,
569 CALL
clacpy(
'Full', n, nrhs, b, lda, x, lda )
572 CALL
csytrs2( uplo, n, nrhs, afac, lda, iwork, x,
578 $ CALL
alaerh( path,
'CSYTRS2', info, 0, uplo, n,
579 $ n, -1, -1, nrhs, imat, nfail,
582 CALL
clacpy(
'Full', n, nrhs, b, lda, work, lda )
586 CALL
csyt02( uplo, n, nrhs, a, lda, x, lda, work,
587 $ lda, rwork, result( 4 ) )
592 CALL
cget04( n, nrhs, x, lda, xact, lda, rcondc,
599 CALL
csyrfs( uplo, n, nrhs, a, lda, afac, lda,
600 $ iwork, b, lda, x, lda, rwork,
601 $ rwork( nrhs+1 ), work,
602 $ rwork( 2*nrhs+1 ), info )
607 $ CALL
alaerh( path,
'CSYRFS', info, 0, uplo, n,
608 $ n, -1, -1, nrhs, imat, nfail,
611 CALL
cget04( n, nrhs, x, lda, xact, lda, rcondc,
613 CALL
cpot05( uplo, n, nrhs, a, lda, b, lda, x, lda,
614 $ xact, lda, rwork, rwork( nrhs+1 ),
621 IF( result( k ).GE.thresh )
THEN
622 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
623 $ CALL
alahd( nout, path )
624 WRITE( nout, fmt = 9998 )uplo, n, nrhs,
625 $ imat, k, result( k )
636 anorm =
clansy(
'1', uplo, n, a, lda, rwork )
638 CALL
csycon( uplo, n, afac, lda, iwork, anorm, rcond,
644 $ CALL
alaerh( path,
'CSYCON', info, 0, uplo, n, n,
645 $ -1, -1, -1, imat, nfail, nerrs, nout )
649 result( 9 ) =
sget06( rcond, rcondc )
654 IF( result( 9 ).GE.thresh )
THEN
655 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
656 $ CALL
alahd( nout, path )
657 WRITE( nout, fmt = 9997 )uplo, n, imat, 9,
669 CALL
alasum( path, nout, nfail, nrun, nerrs )
671 9999 format(
' UPLO = ''', a1,
''', N =', i5,
', NB =', i4,
', type ',
672 $ i2,
', test ', i2,
', ratio =', g12.5 )
673 9998 format(
' UPLO = ''', a1,
''', N =', i5,
', NRHS=', i3,
', type ',
674 $ i2,
', test(', i2,
') =', g12.5 )
675 9997 format(
' UPLO = ''', a1,
''', N =', i5,
',', 10x,
' type ', i2,
676 $
', test(', i2,
') =', g12.5 )