171 SUBROUTINE dchksy( DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL,
172 $ thresh, tsterr, nmax, a, afac, ainv, b, x,
173 $ xact, work, rwork, iwork, nout )
182 INTEGER nmax, nn, nnb, nns, nout
183 DOUBLE PRECISION thresh
187 INTEGER iwork( * ), nbval( * ), nsval( * ), nval( * )
188 DOUBLE PRECISION a( * ), afac( * ), ainv( * ), b( * ),
189 $ rwork( * ), work( * ), x( * ), xact( * )
195 DOUBLE PRECISION zero
196 parameter( zero = 0.0d+0 )
198 parameter( ntypes = 10 )
200 parameter( ntests = 9 )
203 LOGICAL trfcon, zerot
204 CHARACTER dist, type, uplo, xtype
206 INTEGER i, i1, i2, imat, in, inb, info, ioff, irhs,
207 $ iuplo, izero, j, k, kl, ku, lda, lwork, mode,
208 $ n, nb, nerrs, nfail, nimat, nrhs, nrun, nt
209 DOUBLE PRECISION anorm, cndnum, rcond, rcondc
213 INTEGER iseed( 4 ), iseedy( 4 )
214 DOUBLE PRECISION result( ntests )
235 common / infoc / infot, nunit, ok, lerr
236 common / srnamc / srnamt
239 DATA iseedy / 1988, 1989, 1990, 1991 /
240 DATA uplos /
'U',
'L' /
246 path( 1: 1 ) =
'Double precision'
252 iseed( i ) = iseedy( i )
258 $ CALL
derrsy( path, nout )
280 DO 170 imat = 1, nimat
284 IF( .NOT.dotype( imat ) )
289 zerot = imat.GE.3 .AND. imat.LE.6
290 IF( zerot .AND. n.LT.imat-2 )
296 uplo = uplos( iuplo )
303 CALL
dlatb4( path, imat, n, n, type, kl, ku, anorm, mode,
309 CALL
dlatms( n, n, dist, iseed, type, rwork, mode,
310 $ cndnum, anorm, kl, ku, uplo, a, lda, work,
316 CALL
alaerh( path,
'DLATMS', info, 0, uplo, n, n, -1,
317 $ -1, -1, imat, nfail, nerrs, nout )
328 ELSE IF( imat.EQ.4 )
THEN
338 IF( iuplo.EQ.1 )
THEN
339 ioff = ( izero-1 )*lda
340 DO 20 i = 1, izero - 1
350 DO 40 i = 1, izero - 1
361 IF( iuplo.EQ.1 )
THEN
405 CALL
dlacpy( uplo, n, n, a, lda, afac, lda )
412 lwork = max( 2, nb )*lda
414 CALL
dsytrf( uplo, n, afac, lda, iwork, ainv, lwork,
423 IF( iwork( k ).LT.0 )
THEN
424 IF( iwork( k ).NE.-k )
THEN
428 ELSE IF( iwork( k ).NE.k )
THEN
437 $ CALL
alaerh( path,
'DSYTRF', info, k, uplo, n, n,
438 $ -1, -1, nb, imat, nfail, nerrs, nout )
451 CALL
dsyt01( uplo, n, a, lda, afac, lda, iwork, ainv,
452 $ lda, rwork, result( 1 ) )
461 IF( inb.EQ.1 .AND. .NOT.trfcon )
THEN
462 CALL
dlacpy( uplo, n, n, afac, lda, ainv, lda )
464 lwork = (n+nb+1)*(nb+3)
465 CALL
dsytri2( uplo, n, ainv, lda, iwork, work,
471 $ CALL
alaerh( path,
'DSYTRI2', info, -1, uplo, n,
472 $ n, -1, -1, -1, imat, nfail, nerrs,
478 CALL
dpot03( uplo, n, a, lda, ainv, lda, work, lda,
479 $ rwork, rcondc, result( 2 ) )
487 IF( result( k ).GE.thresh )
THEN
488 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
489 $ CALL
alahd( nout, path )
490 WRITE( nout, fmt = 9999 )uplo, n, nb, imat, k,
520 CALL
dlarhs( path, xtype, uplo,
' ', n, n, kl, ku,
521 $ nrhs, a, lda, xact, lda, b, lda,
523 CALL
dlacpy(
'Full', n, nrhs, b, lda, x, lda )
526 CALL
dsytrs( uplo, n, nrhs, afac, lda, iwork, x,
532 $ CALL
alaerh( path,
'DSYTRS', info, 0, uplo, n,
533 $ n, -1, -1, nrhs, imat, nfail,
536 CALL
dlacpy(
'Full', n, nrhs, b, lda, work, lda )
540 CALL
dpot02( uplo, n, nrhs, a, lda, x, lda, work,
541 $ lda, rwork, result( 3 ) )
551 CALL
dlarhs( path, xtype, uplo,
' ', n, n, kl, ku,
552 $ nrhs, a, lda, xact, lda, b, lda,
554 CALL
dlacpy(
'Full', n, nrhs, b, lda, x, lda )
557 CALL
dsytrs2( uplo, n, nrhs, afac, lda, iwork, x,
563 $ CALL
alaerh( path,
'DSYTRS2', info, 0, uplo, n,
564 $ n, -1, -1, nrhs, imat, nfail,
567 CALL
dlacpy(
'Full', n, nrhs, b, lda, work, lda )
571 CALL
dpot02( uplo, n, nrhs, a, lda, x, lda, work,
572 $ lda, rwork, result( 4 ) )
577 CALL
dget04( n, nrhs, x, lda, xact, lda, rcondc,
584 CALL
dsyrfs( uplo, n, nrhs, a, lda, afac, lda,
585 $ iwork, b, lda, x, lda, rwork,
586 $ rwork( nrhs+1 ), work, iwork( n+1 ),
592 $ CALL
alaerh( path,
'DSYRFS', info, 0, uplo, n,
593 $ n, -1, -1, nrhs, imat, nfail,
596 CALL
dget04( n, nrhs, x, lda, xact, lda, rcondc,
598 CALL
dpot05( uplo, n, nrhs, a, lda, b, lda, x, lda,
599 $ xact, lda, rwork, rwork( nrhs+1 ),
606 IF( result( k ).GE.thresh )
THEN
607 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
608 $ CALL
alahd( nout, path )
609 WRITE( nout, fmt = 9998 )uplo, n, nrhs,
610 $ imat, k, result( k )
621 anorm =
dlansy(
'1', uplo, n, a, lda, rwork )
623 CALL
dsycon( uplo, n, afac, lda, iwork, anorm, rcond,
624 $ work, iwork( n+1 ), info )
629 $ CALL
alaerh( path,
'DSYCON', info, 0, uplo, n, n,
630 $ -1, -1, -1, imat, nfail, nerrs, nout )
634 result( 9 ) =
dget06( rcond, rcondc )
639 IF( result( 9 ).GE.thresh )
THEN
640 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
641 $ CALL
alahd( nout, path )
642 WRITE( nout, fmt = 9997 )uplo, n, imat, 9,
655 CALL
alasum( path, nout, nfail, nrun, nerrs )
657 9999 format(
' UPLO = ''', a1,
''', N =', i5,
', NB =', i4,
', type ',
658 $ i2,
', test ', i2,
', ratio =', g12.5 )
659 9998 format(
' UPLO = ''', a1,
''', N =', i5,
', NRHS=', i3,
', type ',
660 $ i2,
', test(', i2,
') =', g12.5 )
661 9997 format(
' UPLO = ''', a1,
''', N =', i5,
',', 10x,
' type ', i2,
662 $
', test(', i2,
') =', g12.5 )