164 SUBROUTINE sdrvpo( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX,
165 $ A, AFAC, ASAV, B, BSAV, X, XACT, S, WORK,
166 $ RWORK, IWORK, NOUT )
174 INTEGER NMAX, NN, NOUT, NRHS
179 INTEGER IWORK( * ), NVAL( * )
180 REAL A( * ), AFAC( * ), ASAV( * ), B( * ),
181 $ bsav( * ), rwork( * ), s( * ), work( * ),
189 PARAMETER ( ONE = 1.0e+0, zero = 0.0e+0 )
191 parameter( ntypes = 9 )
193 parameter( ntests = 6 )
196 LOGICAL EQUIL, NOFACT, PREFAC, ZEROT
197 CHARACTER DIST, EQUED, FACT,
TYPE, UPLO, XTYPE
199 INTEGER I, IEQUED, IFACT, IMAT, IN, INFO, IOFF, IUPLO,
200 $ izero, k, k1, kl, ku, lda, mode, n, nb, nbmin,
201 $ nerrs, nfact, nfail, nimat, nrun, nt,
203 REAL AINVNM, AMAX, ANORM, CNDNUM, RCOND, RCONDC,
204 $ ROLDC, SCOND, RPVGRW_SVXX
207 CHARACTER EQUEDS( 2 ), FACTS( 3 ), UPLOS( 2 )
208 INTEGER ISEED( 4 ), ISEEDY( 4 )
209 REAL RESULT( NTESTS ), BERR( NRHS ),
210 $ errbnds_n( nrhs, 3 ), errbnds_c( nrhs, 3 )
215 EXTERNAL lsame, sget06, slansy
232 COMMON / infoc / infot, nunit, ok, lerr
233 COMMON / srnamc / srnamt
236 DATA iseedy / 1988, 1989, 1990, 1991 /
237 DATA uplos /
'U',
'L' /
238 DATA facts /
'F',
'N',
'E' /
239 DATA equeds /
'N',
'Y' /
245 path( 1: 1 ) =
'Single precision'
251 iseed( i ) = iseedy( i )
257 $
CALL serrvx( path, nout )
277 DO 120 imat = 1, nimat
281 IF( .NOT.dotype( imat ) )
286 zerot = imat.GE.3 .AND. imat.LE.5
287 IF( zerot .AND. n.LT.imat-2 )
293 uplo = uplos( iuplo )
298 CALL slatb4( path, imat, n, n,
TYPE, kl, ku, anorm, mode,
302 CALL slatms( n, n, dist, iseed,
TYPE, rwork, mode,
303 $ cndnum, anorm, kl, ku, uplo, a, lda, work,
309 CALL alaerh( path,
'SLATMS', info, 0, uplo, n, n, -1,
310 $ -1, -1, imat, nfail, nerrs, nout )
320 ELSE IF( imat.EQ.4 )
THEN
325 ioff = ( izero-1 )*lda
329 IF( iuplo.EQ.1 )
THEN
330 DO 20 i = 1, izero - 1
340 DO 40 i = 1, izero - 1
355 CALL slacpy( uplo, n, n, a, lda, asav, lda )
358 equed = equeds( iequed )
359 IF( iequed.EQ.1 )
THEN
365 DO 90 ifact = 1, nfact
366 fact = facts( ifact )
367 prefac = lsame( fact,
'F' )
368 nofact = lsame( fact,
'N' )
369 equil = lsame( fact,
'E' )
376 ELSE IF( .NOT.lsame( fact,
'N' ) )
THEN
383 CALL slacpy( uplo, n, n, asav, lda, afac, lda )
384 IF( equil .OR. iequed.GT.1 )
THEN
389 CALL spoequ( n, afac, lda, s, scond, amax,
391 IF( info.EQ.0 .AND. n.GT.0 )
THEN
397 CALL slaqsy( uplo, n, afac, lda, s, scond,
410 anorm = slansy(
'1', uplo, n, afac, lda, rwork )
414 CALL spotrf( uplo, n, afac, lda, info )
418 CALL slacpy( uplo, n, n, afac, lda, a, lda )
419 CALL spotri( uplo, n, a, lda, info )
423 ainvnm = slansy(
'1', uplo, n, a, lda, rwork )
424 IF( anorm.LE.zero .OR. ainvnm.LE.zero )
THEN
427 rcondc = ( one / anorm ) / ainvnm
433 CALL slacpy( uplo, n, n, asav, lda, a, lda )
438 CALL slarhs( path, xtype, uplo,
' ', n, n, kl, ku,
439 $ nrhs, a, lda, xact, lda, b, lda,
442 CALL slacpy(
'Full', n, nrhs, b, lda, bsav, lda )
451 CALL slacpy( uplo, n, n, a, lda, afac, lda )
452 CALL slacpy(
'Full', n, nrhs, b, lda, x, lda )
455 CALL sposv( uplo, n, nrhs, afac, lda, x, lda,
460 IF( info.NE.izero )
THEN
461 CALL alaerh( path,
'SPOSV ', info, izero,
462 $ uplo, n, n, -1, -1, nrhs, imat,
463 $ nfail, nerrs, nout )
465 ELSE IF( info.NE.0 )
THEN
472 CALL spot01( uplo, n, a, lda, afac, lda, rwork,
477 CALL slacpy(
'Full', n, nrhs, b, lda, work,
479 CALL spot02( uplo, n, nrhs, a, lda, x, lda,
480 $ work, lda, rwork, result( 2 ) )
484 CALL sget04( 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 )
'SPOSV ', uplo,
496 $ n, imat, k, result( k )
507 $
CALL slaset( uplo, n, n, zero, zero, afac, lda )
508 CALL slaset(
'Full', n, nrhs, zero, zero, x, lda )
509 IF( iequed.GT.1 .AND. n.GT.0 )
THEN
514 CALL slaqsy( uplo, n, a, lda, s, scond, amax,
522 CALL sposvx( fact, uplo, n, nrhs, a, lda, afac,
523 $ lda, equed, s, b, lda, x, lda, rcond,
524 $ rwork, rwork( nrhs+1 ), work, iwork,
529 IF( info.NE.izero )
THEN
530 CALL alaerh( path,
'SPOSVX', info, izero,
531 $ fact // uplo, n, n, -1, -1, nrhs,
532 $ imat, nfail, nerrs, nout )
537 IF( .NOT.prefac )
THEN
542 CALL spot01( uplo, n, a, lda, afac, lda,
543 $ rwork( 2*nrhs+1 ), result( 1 ) )
551 CALL slacpy(
'Full', n, nrhs, bsav, lda, work,
553 CALL spot02( uplo, n, nrhs, asav, lda, x, lda,
554 $ work, lda, rwork( 2*nrhs+1 ),
559 IF( nofact .OR. ( prefac .AND. lsame( equed,
561 CALL sget04( n, nrhs, x, lda, xact, lda,
562 $ rcondc, result( 3 ) )
564 CALL sget04( n, nrhs, x, lda, xact, lda,
565 $ roldc, result( 3 ) )
571 CALL spot05( uplo, n, nrhs, asav, lda, b, lda,
572 $ x, lda, xact, lda, rwork,
573 $ rwork( nrhs+1 ), result( 4 ) )
581 result( 6 ) = sget06( rcond, rcondc )
587 IF( result( k ).GE.thresh )
THEN
588 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
589 $
CALL aladhd( nout, path )
591 WRITE( nout, fmt = 9997 )
'SPOSVX', fact,
592 $ uplo, n, equed, imat, k, result( k )
594 WRITE( nout, fmt = 9998 )
'SPOSVX', fact,
595 $ uplo, n, imat, k, result( k )
606 CALL slacpy(
'Full', n, n, asav, lda, a, lda )
607 CALL slacpy(
'Full', n, nrhs, bsav, lda, b, lda )
610 $
CALL slaset( uplo, n, n, zero, zero, afac, lda )
611 CALL slaset(
'Full', n, nrhs, zero, zero, x, lda )
612 IF( iequed.GT.1 .AND. n.GT.0 )
THEN
617 CALL slaqsy( uplo, n, a, lda, s, scond, amax,
626 CALL sposvxx( fact, uplo, n, nrhs, a, lda, afac,
627 $ lda, equed, s, b, lda, x,
628 $ lda, rcond, rpvgrw_svxx, berr, n_err_bnds,
629 $ errbnds_n, errbnds_c, 0, zero, work,
634 IF( info.EQ.n+1 )
GOTO 90
635 IF( info.NE.izero )
THEN
636 CALL alaerh( path,
'SPOSVXX', info, izero,
637 $ fact // uplo, n, n, -1, -1, nrhs,
638 $ imat, nfail, nerrs, nout )
643 IF( .NOT.prefac )
THEN
648 CALL spot01( uplo, n, a, lda, afac, lda,
649 $ rwork( 2*nrhs+1 ), result( 1 ) )
657 CALL slacpy(
'Full', n, nrhs, bsav, lda, work,
659 CALL spot02( uplo, n, nrhs, asav, lda, x, lda,
660 $ work, lda, rwork( 2*nrhs+1 ),
665 IF( nofact .OR. ( prefac .AND. lsame( equed,
667 CALL sget04( n, nrhs, x, lda, xact, lda,
668 $ rcondc, result( 3 ) )
670 CALL sget04( n, nrhs, x, lda, xact, lda,
671 $ roldc, result( 3 ) )
677 CALL spot05( uplo, n, nrhs, asav, lda, b, lda,
678 $ x, lda, xact, lda, rwork,
679 $ rwork( nrhs+1 ), result( 4 ) )
687 result( 6 ) = sget06( rcond, rcondc )
693 IF( result( k ).GE.thresh )
THEN
694 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
695 $
CALL aladhd( nout, path )
697 WRITE( nout, fmt = 9997 )
'SPOSVXX', fact,
698 $ uplo, n, equed, imat, k, result( k )
700 WRITE( nout, fmt = 9998 )
'SPOSVXX', fact,
701 $ uplo, n, imat, k, result( k )
715 CALL alasvm( path, nout, nfail, nrun, nerrs )
722 9999
FORMAT( 1x, a,
', UPLO=''', a1,
''', N =', i5,
', type ', i1,
723 $
', test(', i1,
')=', g12.5 )
724 9998
FORMAT( 1x, a,
', FACT=''', a1,
''', UPLO=''', a1,
''', N=', i5,
725 $
', type ', i1,
', test(', i1,
')=', g12.5 )
726 9997
FORMAT( 1x, a,
', FACT=''', a1,
''', UPLO=''', a1,
''', N=', i5,
727 $
', EQUED=''', a1,
''', type ', i1,
', test(', i1,
') =',
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 slacpy(uplo, m, n, a, lda, b, ldb)
SLACPY copies all or part of one two-dimensional array to another.
subroutine slaqsy(uplo, n, a, lda, s, scond, amax, equed)
SLAQSY scales a symmetric/Hermitian matrix, using scaling factors computed by spoequ.
subroutine slaset(uplo, m, n, alpha, beta, a, lda)
SLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.
subroutine spoequ(n, a, lda, s, scond, amax, info)
SPOEQU
subroutine sposv(uplo, n, nrhs, a, lda, b, ldb, info)
SPOSV computes the solution to system of linear equations A * X = B for PO matrices
subroutine sposvx(fact, uplo, n, nrhs, a, lda, af, ldaf, equed, s, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)
SPOSVX computes the solution to system of linear equations A * X = B for PO matrices
subroutine sposvxx(fact, uplo, n, nrhs, a, lda, af, ldaf, equed, s, b, ldb, x, ldx, rcond, rpvgrw, berr, n_err_bnds, err_bnds_norm, err_bnds_comp, nparams, params, work, iwork, info)
SPOSVXX computes the solution to system of linear equations A * X = B for PO matrices
subroutine spotrf(uplo, n, a, lda, info)
SPOTRF
subroutine spotri(uplo, n, a, lda, info)
SPOTRI
subroutine sdrvpo(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, asav, b, bsav, x, xact, s, work, rwork, iwork, nout)
SDRVPO
subroutine sebchvxx(thresh, path)
SEBCHVXX
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 spot01(uplo, n, a, lda, afac, ldafac, rwork, resid)
SPOT01
subroutine spot02(uplo, n, nrhs, a, lda, x, ldx, b, ldb, rwork, resid)
SPOT02
subroutine spot05(uplo, n, nrhs, a, lda, b, ldb, x, ldx, xact, ldxact, ferr, berr, reslts)
SPOT05