161 SUBROUTINE zchksp( DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR,
162 $ NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK,
171 INTEGER NMAX, NN, NNS, NOUT
172 DOUBLE PRECISION THRESH
176 INTEGER IWORK( * ), NSVAL( * ), NVAL( * )
177 DOUBLE PRECISION RWORK( * )
178 COMPLEX*16 A( * ), AFAC( * ), AINV( * ), B( * ),
179 $ work( * ), x( * ), xact( * )
185 DOUBLE PRECISION ZERO
186 PARAMETER ( ZERO = 0.0d+0 )
188 parameter( ntypes = 11 )
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 DOUBLE PRECISION ANORM, CNDNUM, RCOND, RCONDC
203 INTEGER ISEED( 4 ), ISEEDY( 4 )
204 DOUBLE PRECISION RESULT( NTESTS )
208 DOUBLE PRECISION DGET06, ZLANSP
209 EXTERNAL lsame, dget06, zlansp
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 ) =
'Zomplex precision'
243 iseed( i ) = iseedy( i )
249 $
CALL zerrsy( path, nout )
262 DO 160 imat = 1, nimat
266 IF( .NOT.dotype( imat ) )
271 zerot = imat.GE.3 .AND. imat.LE.6
272 IF( zerot .AND. n.LT.imat-2 )
278 uplo = uplos( iuplo )
279 IF( lsame( uplo,
'U' ) )
THEN
285 IF( imat.NE.ntypes )
THEN
290 CALL zlatb4( path, imat, n, n,
TYPE, kl, ku, anorm,
291 $ mode, cndnum, dist )
294 CALL zlatms( n, n, dist, iseed,
TYPE, rwork, mode,
295 $ cndnum, anorm, kl, ku, packit, a, lda,
301 CALL alaerh( path,
'ZLATMS', info, 0, uplo, n, n,
302 $ -1, -1, -1, imat, nfail, nerrs, nout )
312 ELSE IF( imat.EQ.4 )
THEN
322 IF( iuplo.EQ.1 )
THEN
323 ioff = ( izero-1 )*izero / 2
324 DO 20 i = 1, izero - 1
334 DO 40 i = 1, izero - 1
344 IF( iuplo.EQ.1 )
THEN
378 CALL zlatsp( uplo, n, a, iseed )
384 CALL zcopy( npp, a, 1, afac, 1 )
386 CALL zsptrf( uplo, n, afac, iwork, info )
394 IF( iwork( k ).LT.0 )
THEN
395 IF( iwork( k ).NE.-k )
THEN
399 ELSE IF( iwork( k ).NE.k )
THEN
408 $
CALL alaerh( path,
'ZSPTRF', info, k, uplo, n, n, -1,
409 $ -1, -1, imat, nfail, nerrs, nout )
419 CALL zspt01( uplo, n, a, afac, iwork, ainv, lda, rwork,
426 IF( .NOT.trfcon )
THEN
427 CALL zcopy( npp, afac, 1, ainv, 1 )
429 CALL zsptri( uplo, n, ainv, iwork, work, info )
434 $
CALL alaerh( path,
'ZSPTRI', info, 0, uplo, n, n,
435 $ -1, -1, -1, imat, nfail, nerrs, nout )
437 CALL zspt03( uplo, n, a, ainv, work, lda, rwork,
438 $ rcondc, result( 2 ) )
446 IF( result( k ).GE.thresh )
THEN
447 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
448 $
CALL alahd( nout, path )
449 WRITE( nout, fmt = 9999 )uplo, n, imat, k,
470 CALL zlarhs( path, xtype, uplo,
' ', n, n, kl, ku,
471 $ nrhs, a, lda, xact, lda, b, lda, iseed,
473 CALL zlacpy(
'Full', n, nrhs, b, lda, x, lda )
476 CALL zsptrs( uplo, n, nrhs, afac, iwork, x, lda,
482 $
CALL alaerh( path,
'ZSPTRS', info, 0, uplo, n, n,
483 $ -1, -1, nrhs, imat, nfail, nerrs,
486 CALL zlacpy(
'Full', n, nrhs, b, lda, work, lda )
487 CALL zspt02( uplo, n, nrhs, a, x, lda, work, lda,
488 $ rwork, result( 3 ) )
493 CALL zget04( n, nrhs, x, lda, xact, lda, rcondc,
500 CALL zsprfs( 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,
'ZSPRFS', info, 0, uplo, n, n,
508 $ -1, -1, nrhs, imat, nfail, nerrs,
511 CALL zget04( n, nrhs, x, lda, xact, lda, rcondc,
513 CALL zppt05( 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 = zlansp(
'1', uplo, n, a, rwork )
538 CALL zspcon( uplo, n, afac, iwork, anorm, rcond, work,
544 $
CALL alaerh( path,
'ZSPCON', info, 0, uplo, n, n, -1,
545 $ -1, -1, imat, nfail, nerrs, nout )
547 result( 8 ) = dget06( 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 zlarhs(path, xtype, uplo, trans, m, n, kl, ku, nrhs, a, lda, x, ldx, b, ldb, iseed, info)
ZLARHS
subroutine alaerh(path, subnam, info, infoe, opts, m, n, kl, ku, n5, imat, nfail, nerrs, nout)
ALAERH
subroutine alahd(iounit, path)
ALAHD
subroutine zcopy(n, zx, incx, zy, incy)
ZCOPY
subroutine zspcon(uplo, n, ap, ipiv, anorm, rcond, work, info)
ZSPCON
subroutine zsprfs(uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx, ferr, berr, work, rwork, info)
ZSPRFS
subroutine zsptrf(uplo, n, ap, ipiv, info)
ZSPTRF
subroutine zsptri(uplo, n, ap, ipiv, work, info)
ZSPTRI
subroutine zsptrs(uplo, n, nrhs, ap, ipiv, b, ldb, info)
ZSPTRS
subroutine zlacpy(uplo, m, n, a, lda, b, ldb)
ZLACPY copies all or part of one two-dimensional array to another.
subroutine zchksp(dotype, nn, nval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
ZCHKSP
subroutine zerrsy(path, nunit)
ZERRSY
subroutine zget04(n, nrhs, x, ldx, xact, ldxact, rcond, resid)
ZGET04
subroutine zlatb4(path, imat, m, n, type, kl, ku, anorm, mode, cndnum, dist)
ZLATB4
subroutine zlatms(m, n, dist, iseed, sym, d, mode, cond, dmax, kl, ku, pack, a, lda, work, info)
ZLATMS
subroutine zlatsp(uplo, n, x, iseed)
ZLATSP
subroutine zppt05(uplo, n, nrhs, ap, b, ldb, x, ldx, xact, ldxact, ferr, berr, reslts)
ZPPT05
subroutine zspt01(uplo, n, a, afac, ipiv, c, ldc, rwork, resid)
ZSPT01
subroutine zspt02(uplo, n, nrhs, a, x, ldx, b, ldb, rwork, resid)
ZSPT02
subroutine zspt03(uplo, n, a, ainv, work, ldw, rwork, rcond, resid)
ZSPT03