153 SUBROUTINE sdrvsy_rk( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR,
154 $ NMAX, A, AFAC, E, AINV, B, X, XACT, WORK,
155 $ RWORK, IWORK, NOUT )
163 INTEGER NMAX, NN, NOUT, NRHS
168 INTEGER IWORK( * ), NVAL( * )
169 REAL A( * ), AFAC( * ), AINV( * ), B( * ), E( * ),
170 $ rwork( * ), work( * ), x( * ), xact( * )
177 PARAMETER ( ONE = 1.0e+0, zero = 0.0e+0 )
178 INTEGER NTYPES, NTESTS
179 parameter( ntypes = 10, ntests = 3 )
181 parameter( nfact = 2 )
185 CHARACTER DIST, FACT,
TYPE, UPLO, XTYPE
186 CHARACTER*3 PATH, MATPATH
187 INTEGER I, I1, I2, IFACT, IMAT, IN, INFO, IOFF, IUPLO,
188 $ izero, j, k, kl, ku, lda, lwork, mode, n,
189 $ nb, nbmin, nerrs, nfail, nimat, nrun, nt
190 REAL AINVNM, ANORM, CNDNUM, RCONDC
193 CHARACTER FACTS( NFACT ), UPLOS( 2 )
194 INTEGER ISEED( 4 ), ISEEDY( 4 )
195 REAL RESULT( NTESTS )
212 COMMON / infoc / infot, nunit, ok, lerr
213 COMMON / srnamc / srnamt
219 DATA iseedy / 1988, 1989, 1990, 1991 /
220 DATA uplos /
'U',
'L' / , facts /
'F',
'N' /
228 path( 1: 1 ) =
'Single precision'
233 matpath( 1: 1 ) =
'Single precision'
234 matpath( 2: 3 ) =
'SY'
240 iseed( i ) = iseedy( i )
242 lwork = max( 2*nmax, nmax*nrhs )
247 $
CALL serrvx( path, nout )
268 DO 170 imat = 1, nimat
272 IF( .NOT.dotype( imat ) )
277 zerot = imat.GE.3 .AND. imat.LE.6
278 IF( zerot .AND. n.LT.imat-2 )
284 uplo = uplos( iuplo )
291 CALL slatb4( matpath, imat, n, n,
TYPE, kl, ku, anorm,
292 $ mode, cndnum, dist )
297 CALL slatms( n, n, dist, iseed,
TYPE, rwork, mode,
298 $ cndnum, anorm, kl, ku, uplo, a, lda, work,
304 CALL alaerh( path,
'SLATMS', info, 0, uplo, n, n, -1,
305 $ -1, -1, imat, nfail, nerrs, nout )
318 ELSE IF( imat.EQ.4 )
THEN
328 IF( iuplo.EQ.1 )
THEN
329 ioff = ( izero-1 )*lda
330 DO 20 i = 1, izero - 1
340 DO 40 i = 1, izero - 1
351 IF( iuplo.EQ.1 )
THEN
381 DO 150 ifact = 1, nfact
385 fact = facts( ifact )
394 ELSE IF( ifact.EQ.1 )
THEN
398 anorm = slansy(
'1', uplo, n, a, lda, rwork )
402 CALL slacpy( uplo, n, n, a, lda, afac, lda )
403 CALL ssytrf_rk( uplo, n, afac, lda, e, iwork, work,
408 CALL slacpy( uplo, n, n, afac, lda, ainv, lda )
409 lwork = (n+nb+1)*(nb+3)
414 CALL ssytri_3( uplo, n, ainv, lda, e, iwork,
415 $ work, lwork, info )
416 ainvnm = slansy(
'1', uplo, n, ainv, lda, rwork )
420 IF( anorm.LE.zero .OR. ainvnm.LE.zero )
THEN
423 rcondc = ( one / anorm ) / ainvnm
430 CALL slarhs( matpath, xtype, uplo,
' ', n, n, kl, ku,
431 $ nrhs, a, lda, xact, lda, b, lda, iseed,
437 IF( ifact.EQ.2 )
THEN
438 CALL slacpy( uplo, n, n, a, lda, afac, lda )
439 CALL slacpy(
'Full', n, nrhs, b, lda, x, lda )
445 CALL ssysv_rk( uplo, n, nrhs, afac, lda, e, iwork,
446 $ x, lda, work, lwork, info )
454 IF( iwork( k ).LT.0 )
THEN
455 IF( iwork( k ).NE.-k )
THEN
459 ELSE IF( iwork( k ).NE.k )
THEN
468 CALL alaerh( path,
'SSYSV_RK', info, k, uplo,
469 $ n, n, -1, -1, nrhs, imat, nfail,
472 ELSE IF( info.NE.0 )
THEN
479 CALL ssyt01_3( uplo, n, a, lda, afac, lda, e,
480 $ iwork, ainv, lda, rwork,
485 CALL slacpy(
'Full', n, nrhs, b, lda, work, lda )
486 CALL spot02( uplo, n, nrhs, a, lda, x, lda, work,
487 $ lda, rwork, result( 2 ) )
492 CALL sget04( n, nrhs, x, lda, xact, lda, rcondc,
500 IF( result( k ).GE.thresh )
THEN
501 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
502 $
CALL aladhd( nout, path )
503 WRITE( nout, fmt = 9999 )
'SSYSV_RK', uplo,
504 $ n, imat, k, result( k )
520 CALL alasvm( path, nout, nfail, nrun, nerrs )
522 9999
FORMAT( 1x, a,
', UPLO=''', a1,
''', N =', i5,
', type ', i2,
523 $
', test ', i2,
', ratio =', g12.5 )
subroutine alasvm(type, nout, nfail, nrun, nerrs)
ALASVM
subroutine slarhs(path, xtype, uplo, trans, m, n, kl, ku, nrhs, a, lda, x, ldx, b, ldb, iseed, info)
SLARHS
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 ssysv_rk(uplo, n, nrhs, a, lda, e, ipiv, b, ldb, work, lwork, info)
SSYSV_RK computes the solution to system of linear equations A * X = B for SY matrices
subroutine ssytrf_rk(uplo, n, a, lda, e, ipiv, work, lwork, info)
SSYTRF_RK computes the factorization of a real symmetric indefinite matrix using the bounded Bunch-Ka...
subroutine ssytri_3(uplo, n, a, lda, e, ipiv, work, lwork, info)
SSYTRI_3
subroutine slacpy(uplo, m, n, a, lda, b, ldb)
SLACPY copies all or part of one two-dimensional array to another.
subroutine sdrvsy_rk(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, e, ainv, b, x, xact, work, rwork, iwork, nout)
SDRVSY_RK
subroutine serrvx(path, nunit)
SERRVX
subroutine sget04(n, nrhs, x, ldx, xact, ldxact, rcond, resid)
SGET04
subroutine slatb4(path, imat, m, n, type, kl, ku, anorm, mode, cndnum, dist)
SLATB4
subroutine slatms(m, n, dist, iseed, sym, d, mode, cond, dmax, kl, ku, pack, a, lda, work, info)
SLATMS
subroutine spot02(uplo, n, nrhs, a, lda, x, ldx, b, ldb, rwork, resid)
SPOT02
subroutine ssyt01_3(uplo, n, a, lda, afac, ldafac, e, ipiv, c, ldc, rwork, resid)
SSYT01_3