154 SUBROUTINE cdrvsp( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX,
155 $ A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK,
164 INTEGER NMAX, NN, NOUT, NRHS
169 INTEGER IWORK( * ), NVAL( * )
171 COMPLEX A( * ), AFAC( * ), AINV( * ), B( * ),
172 $ work( * ), x( * ), xact( * )
179 PARAMETER ( ONE = 1.0e+0, zero = 0.0e+0 )
180 INTEGER NTYPES, NTESTS
181 parameter( ntypes = 11, ntests = 6 )
183 parameter( nfact = 2 )
187 CHARACTER DIST, FACT, PACKIT,
TYPE, UPLO, XTYPE
189 INTEGER I, I1, I2, IFACT, IMAT, IN, INFO, IOFF, IUPLO,
190 $ izero, j, k, k1, kl, ku, lda, mode, n, nb,
191 $ nbmin, nerrs, nfail, nimat, npp, nrun, nt
192 REAL AINVNM, ANORM, CNDNUM, RCOND, RCONDC
195 CHARACTER FACTS( NFACT )
196 INTEGER ISEED( 4 ), ISEEDY( 4 )
197 REAL RESULT( NTESTS )
201 EXTERNAL CLANSP, SGET06
215 COMMON / infoc / infot, nunit, ok, lerr
216 COMMON / srnamc / srnamt
219 INTRINSIC cmplx, max, min
222 DATA iseedy / 1988, 1989, 1990, 1991 /
223 DATA facts /
'F',
'N' /
229 path( 1: 1 ) =
'Complex precision'
235 iseed( i ) = iseedy( i )
241 $
CALL cerrvx( path, nout )
262 DO 170 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 IF( iuplo.EQ.1 )
THEN
286 IF( imat.NE.ntypes )
THEN
291 CALL clatb4( path, imat, n, n,
TYPE, kl, ku, anorm,
292 $ mode, cndnum, dist )
295 CALL clatms( n, n, dist, iseed,
TYPE, rwork, mode,
296 $ cndnum, anorm, kl, ku, packit, a, lda,
302 CALL alaerh( path,
'CLATMS', info, 0, uplo, n, n,
303 $ -1, -1, -1, imat, nfail, nerrs, nout )
313 ELSE IF( imat.EQ.4 )
THEN
323 IF( iuplo.EQ.1 )
THEN
324 ioff = ( izero-1 )*izero / 2
325 DO 20 i = 1, izero - 1
335 DO 40 i = 1, izero - 1
345 IF( iuplo.EQ.1 )
THEN
379 CALL clatsp( uplo, n, a, iseed )
382 DO 150 ifact = 1, nfact
386 fact = facts( ifact )
396 ELSE IF( ifact.EQ.1 )
THEN
400 anorm = clansp(
'1', uplo, n, a, rwork )
404 CALL ccopy( npp, a, 1, afac, 1 )
405 CALL csptrf( uplo, n, afac, iwork, info )
409 CALL ccopy( npp, afac, 1, ainv, 1 )
410 CALL csptri( uplo, n, ainv, iwork, work, info )
411 ainvnm = clansp(
'1', uplo, n, ainv, rwork )
415 IF( anorm.LE.zero .OR. ainvnm.LE.zero )
THEN
418 rcondc = ( one / anorm ) / ainvnm
425 CALL clarhs( path, xtype, uplo,
' ', n, n, kl, ku,
426 $ nrhs, a, lda, xact, lda, b, lda, iseed,
432 IF( ifact.EQ.2 )
THEN
433 CALL ccopy( npp, a, 1, afac, 1 )
434 CALL clacpy(
'Full', n, nrhs, b, lda, x, lda )
439 CALL cspsv( uplo, n, nrhs, afac, iwork, x, lda,
448 IF( iwork( k ).LT.0 )
THEN
449 IF( iwork( k ).NE.-k )
THEN
453 ELSE IF( iwork( k ).NE.k )
THEN
462 CALL alaerh( path,
'CSPSV ', info, k, uplo, n,
463 $ n, -1, -1, nrhs, imat, nfail,
466 ELSE IF( info.NE.0 )
THEN
473 CALL cspt01( uplo, n, a, afac, iwork, ainv, lda,
474 $ rwork, result( 1 ) )
478 CALL clacpy(
'Full', n, nrhs, b, lda, work, lda )
479 CALL cspt02( uplo, n, nrhs, a, x, lda, work, lda,
480 $ rwork, result( 2 ) )
484 CALL cget04( n, nrhs, x, lda, xact, lda, rcondc,
492 IF( result( k ).GE.thresh )
THEN
493 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
494 $
CALL aladhd( nout, path )
495 WRITE( nout, fmt = 9999 )
'CSPSV ', uplo, n,
496 $ imat, k, result( k )
506 IF( ifact.EQ.2 .AND. npp.GT.0 )
507 $
CALL claset(
'Full', npp, 1, cmplx( zero ),
508 $ cmplx( zero ), afac, npp )
509 CALL claset(
'Full', n, nrhs, cmplx( zero ),
510 $ cmplx( zero ), x, lda )
516 CALL cspsvx( fact, uplo, n, nrhs, a, afac, iwork, b,
517 $ lda, x, lda, rcond, rwork,
518 $ rwork( nrhs+1 ), work, rwork( 2*nrhs+1 ),
527 IF( iwork( k ).LT.0 )
THEN
528 IF( iwork( k ).NE.-k )
THEN
532 ELSE IF( iwork( k ).NE.k )
THEN
541 CALL alaerh( path,
'CSPSVX', info, k, fact // uplo,
542 $ n, n, -1, -1, nrhs, imat, nfail,
548 IF( ifact.GE.2 )
THEN
553 CALL cspt01( uplo, n, a, afac, iwork, ainv, lda,
554 $ rwork( 2*nrhs+1 ), result( 1 ) )
562 CALL clacpy(
'Full', n, nrhs, b, lda, work, lda )
563 CALL cspt02( uplo, n, nrhs, a, x, lda, work, lda,
564 $ rwork( 2*nrhs+1 ), result( 2 ) )
568 CALL cget04( n, nrhs, x, lda, xact, lda, rcondc,
573 CALL cppt05( uplo, n, nrhs, a, b, lda, x, lda,
574 $ xact, lda, rwork, rwork( nrhs+1 ),
583 result( 6 ) = sget06( rcond, rcondc )
589 IF( result( k ).GE.thresh )
THEN
590 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
591 $
CALL aladhd( nout, path )
592 WRITE( nout, fmt = 9998 )
'CSPSVX', fact, uplo,
593 $ n, imat, k, result( k )
607 CALL alasvm( path, nout, nfail, nrun, nerrs )
609 9999
FORMAT( 1x, a,
', UPLO=''', a1,
''', N =', i5,
', type ', i2,
610 $
', test ', i2,
', ratio =', g12.5 )
611 9998
FORMAT( 1x, a,
', FACT=''', a1,
''', UPLO=''', a1,
''', N =', i5,
612 $
', type ', i2,
', test ', i2,
', ratio =', g12.5 )
subroutine alasvm(type, nout, nfail, nrun, nerrs)
ALASVM
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 aladhd(iounit, path)
ALADHD
subroutine alaerh(path, subnam, info, infoe, opts, m, n, kl, ku, n5, imat, nfail, nerrs, nout)
ALAERH
subroutine cdrvsp(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
CDRVSP
subroutine cerrvx(path, nunit)
CERRVX
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 clatsp(uplo, n, x, iseed)
CLATSP
subroutine cppt05(uplo, n, nrhs, ap, b, ldb, x, ldx, xact, ldxact, ferr, berr, reslts)
CPPT05
subroutine cspt01(uplo, n, a, afac, ipiv, c, ldc, rwork, resid)
CSPT01
subroutine cspt02(uplo, n, nrhs, a, x, ldx, b, ldb, rwork, resid)
CSPT02
subroutine ccopy(n, cx, incx, cy, incy)
CCOPY
subroutine cspsv(uplo, n, nrhs, ap, ipiv, b, ldb, info)
CSPSV computes the solution to system of linear equations A * X = B for OTHER matrices
subroutine cspsvx(fact, uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)
CSPSVX computes the solution to system of linear equations A * X = B for OTHER matrices
subroutine csptrf(uplo, n, ap, ipiv, info)
CSPTRF
subroutine csptri(uplo, n, ap, ipiv, work, info)
CSPTRI
subroutine clacpy(uplo, m, n, a, lda, b, ldb)
CLACPY copies all or part of one two-dimensional array to another.
subroutine claset(uplo, m, n, alpha, beta, a, lda)
CLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.