161 SUBROUTINE zdrvge( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX,
162 $ A, AFAC, ASAV, B, BSAV, X, XACT, S, WORK,
163 $ RWORK, IWORK, NOUT )
171 INTEGER NMAX, NN, NOUT, NRHS
172 DOUBLE PRECISION THRESH
176 INTEGER IWORK( * ), NVAL( * )
177 DOUBLE PRECISION RWORK( * ), S( * )
178 COMPLEX*16 A( * ), AFAC( * ), ASAV( * ), B( * ),
179 $ bsav( * ), work( * ), x( * ), xact( * )
185 DOUBLE PRECISION ONE, ZERO
186 PARAMETER ( ONE = 1.0d+0, zero = 0.0d+0 )
188 parameter( ntypes = 11 )
190 parameter( ntests = 7 )
192 parameter( ntran = 3 )
195 LOGICAL EQUIL, NOFACT, PREFAC, TRFCON, ZEROT
196 CHARACTER DIST, EQUED, FACT, TRANS,
TYPE, XTYPE
198 INTEGER I, IEQUED, IFACT, IMAT, IN, INFO, IOFF, ITRAN,
199 $ izero, k, k1, kl, ku, lda, lwork, mode, n, nb,
200 $ nbmin, nerrs, nfact, nfail, nimat, nrun, nt
201 DOUBLE PRECISION AINVNM, AMAX, ANORM, ANORMI, ANORMO, CNDNUM,
202 $ COLCND, RCOND, RCONDC, RCONDI, RCONDO, ROLDC,
203 $ roldi, roldo, rowcnd, rpvgrw
206 CHARACTER EQUEDS( 4 ), FACTS( 3 ), TRANSS( NTRAN )
207 INTEGER ISEED( 4 ), ISEEDY( 4 )
208 DOUBLE PRECISION RDUM( 1 ), RESULT( NTESTS )
212 DOUBLE PRECISION DGET06, DLAMCH, ZLANGE, ZLANTR
213 EXTERNAL lsame, dget06, dlamch, zlange, zlantr
222 INTRINSIC abs, dcmplx, max
230 COMMON / infoc / infot, nunit, ok, lerr
231 COMMON / srnamc / srnamt
234 DATA iseedy / 1988, 1989, 1990, 1991 /
235 DATA transs /
'N',
'T',
'C' /
236 DATA facts /
'F',
'N',
'E' /
237 DATA equeds /
'N',
'R',
'C',
'B' /
243 path( 1: 1 ) =
'Zomplex precision'
249 iseed( i ) = iseedy( i )
255 $
CALL zerrvx( path, nout )
275 DO 80 imat = 1, nimat
279 IF( .NOT.dotype( imat ) )
284 zerot = imat.GE.5 .AND. imat.LE.7
285 IF( zerot .AND. n.LT.imat-4 )
291 CALL zlatb4( path, imat, n, n,
TYPE, kl, ku, anorm, mode,
293 rcondc = one / cndnum
296 CALL zlatms( n, n, dist, iseed,
TYPE, rwork, mode, cndnum,
297 $ anorm, kl, ku,
'No packing', a, lda, work,
303 CALL alaerh( path,
'ZLATMS', info, 0,
' ', n, n, -1, -1,
304 $ -1, imat, nfail, nerrs, nout )
314 ELSE IF( imat.EQ.6 )
THEN
319 ioff = ( izero-1 )*lda
325 CALL zlaset(
'Full', n, n-izero+1, dcmplx( zero ),
326 $ dcmplx( zero ), a( ioff+1 ), lda )
334 CALL zlacpy(
'Full', n, n, a, lda, asav, lda )
337 equed = equeds( iequed )
338 IF( iequed.EQ.1 )
THEN
344 DO 60 ifact = 1, nfact
345 fact = facts( ifact )
346 prefac = lsame( fact,
'F' )
347 nofact = lsame( fact,
'N' )
348 equil = lsame( fact,
'E' )
356 ELSE IF( .NOT.nofact )
THEN
363 CALL zlacpy(
'Full', n, n, asav, lda, afac, lda )
364 IF( equil .OR. iequed.GT.1 )
THEN
369 CALL zgeequ( n, n, afac, lda, s, s( n+1 ),
370 $ rowcnd, colcnd, amax, info )
371 IF( info.EQ.0 .AND. n.GT.0 )
THEN
372 IF( lsame( equed,
'R' ) )
THEN
375 ELSE IF( lsame( equed,
'C' ) )
THEN
378 ELSE IF( lsame( equed,
'B' ) )
THEN
385 CALL zlaqge( n, n, afac, lda, s, s( n+1 ),
386 $ rowcnd, colcnd, amax, equed )
400 anormo = zlange(
'1', n, n, afac, lda, rwork )
401 anormi = zlange(
'I', n, n, afac, lda, rwork )
406 CALL zgetrf( n, n, afac, lda, iwork, info )
410 CALL zlacpy(
'Full', n, n, afac, lda, a, lda )
411 lwork = nmax*max( 3, nrhs )
413 CALL zgetri( n, a, lda, iwork, work, lwork, info )
417 ainvnm = zlange(
'1', n, n, a, lda, rwork )
418 IF( anormo.LE.zero .OR. ainvnm.LE.zero )
THEN
421 rcondo = ( one / anormo ) / ainvnm
426 ainvnm = zlange(
'I', n, n, a, lda, rwork )
427 IF( anormi.LE.zero .OR. ainvnm.LE.zero )
THEN
430 rcondi = ( one / anormi ) / ainvnm
434 DO 50 itran = 1, ntran
438 trans = transs( itran )
439 IF( itran.EQ.1 )
THEN
447 CALL zlacpy(
'Full', n, n, asav, lda, a, lda )
452 CALL zlarhs( path, xtype,
'Full', trans, n, n, kl,
453 $ ku, nrhs, a, lda, xact, lda, b, lda,
456 CALL zlacpy(
'Full', n, nrhs, b, lda, bsav, lda )
458 IF( nofact .AND. itran.EQ.1 )
THEN
465 CALL zlacpy(
'Full', n, n, a, lda, afac, lda )
466 CALL zlacpy(
'Full', n, nrhs, b, lda, x, lda )
469 CALL zgesv( n, nrhs, afac, lda, iwork, x, lda,
475 $
CALL alaerh( path,
'ZGESV ', info, izero,
476 $
' ', n, n, -1, -1, nrhs, imat,
477 $ nfail, nerrs, nout )
482 CALL zget01( n, n, a, lda, afac, lda, iwork,
483 $ rwork, result( 1 ) )
485 IF( izero.EQ.0 )
THEN
489 CALL zlacpy(
'Full', n, nrhs, b, lda, work,
491 CALL zget02(
'No transpose', n, n, nrhs, a,
492 $ lda, x, lda, work, lda, rwork,
497 CALL zget04( n, nrhs, x, lda, xact, lda,
498 $ rcondc, result( 3 ) )
506 IF( result( k ).GE.thresh )
THEN
507 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
508 $
CALL aladhd( nout, path )
509 WRITE( nout, fmt = 9999 )
'ZGESV ', n,
510 $ imat, k, result( k )
520 $
CALL zlaset(
'Full', n, n, dcmplx( zero ),
521 $ dcmplx( zero ), afac, lda )
522 CALL zlaset(
'Full', n, nrhs, dcmplx( zero ),
523 $ dcmplx( zero ), x, lda )
524 IF( iequed.GT.1 .AND. n.GT.0 )
THEN
529 CALL zlaqge( n, n, a, lda, s, s( n+1 ), rowcnd,
530 $ colcnd, amax, equed )
537 CALL zgesvx( fact, trans, n, nrhs, a, lda, afac,
538 $ lda, iwork, equed, s, s( n+1 ), b,
539 $ lda, x, lda, rcond, rwork,
540 $ rwork( nrhs+1 ), work,
541 $ rwork( 2*nrhs+1 ), info )
546 $
CALL alaerh( path,
'ZGESVX', info, izero,
547 $ fact // trans, n, n, -1, -1, nrhs,
548 $ imat, nfail, nerrs, nout )
553 IF( info.NE.0 .AND. info.LE.n)
THEN
554 rpvgrw = zlantr(
'M',
'U',
'N', info, info,
556 IF( rpvgrw.EQ.zero )
THEN
559 rpvgrw = zlange(
'M', n, info, a, lda,
563 rpvgrw = zlantr(
'M',
'U',
'N', n, n, afac, lda,
565 IF( rpvgrw.EQ.zero )
THEN
568 rpvgrw = zlange(
'M', n, n, a, lda, rdum ) /
572 result( 7 ) = abs( rpvgrw-rwork( 2*nrhs+1 ) ) /
573 $ max( rwork( 2*nrhs+1 ), rpvgrw ) /
576 IF( .NOT.prefac )
THEN
581 CALL zget01( n, n, a, lda, afac, lda, iwork,
582 $ rwork( 2*nrhs+1 ), result( 1 ) )
593 CALL zlacpy(
'Full', n, nrhs, bsav, lda, work,
595 CALL zget02( trans, n, n, nrhs, asav, lda, x,
596 $ lda, work, lda, rwork( 2*nrhs+1 ),
601 IF( nofact .OR. ( prefac .AND. lsame( equed,
603 CALL zget04( n, nrhs, x, lda, xact, lda,
604 $ rcondc, result( 3 ) )
606 IF( itran.EQ.1 )
THEN
611 CALL zget04( n, nrhs, x, lda, xact, lda,
612 $ roldc, result( 3 ) )
618 CALL zget07( trans, n, nrhs, asav, lda, b, lda,
619 $ x, lda, xact, lda, rwork, .true.,
620 $ rwork( nrhs+1 ), result( 4 ) )
628 result( 6 ) = dget06( rcond, rcondc )
633 IF( .NOT.trfcon )
THEN
635 IF( result( k ).GE.thresh )
THEN
636 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
637 $
CALL aladhd( nout, path )
639 WRITE( nout, fmt = 9997 )
'ZGESVX',
640 $ fact, trans, n, equed, imat, k,
643 WRITE( nout, fmt = 9998 )
'ZGESVX',
644 $ fact, trans, n, imat, k, result( k )
649 nrun = nrun + ntests - k1 + 1
651 IF( result( 1 ).GE.thresh .AND. .NOT.prefac )
653 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
654 $
CALL aladhd( nout, path )
656 WRITE( nout, fmt = 9997 )
'ZGESVX', fact,
657 $ trans, n, equed, imat, 1, result( 1 )
659 WRITE( nout, fmt = 9998 )
'ZGESVX', fact,
660 $ trans, n, imat, 1, result( 1 )
665 IF( result( 6 ).GE.thresh )
THEN
666 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
667 $
CALL aladhd( nout, path )
669 WRITE( nout, fmt = 9997 )
'ZGESVX', fact,
670 $ trans, n, equed, imat, 6, result( 6 )
672 WRITE( nout, fmt = 9998 )
'ZGESVX', fact,
673 $ trans, n, imat, 6, result( 6 )
678 IF( result( 7 ).GE.thresh )
THEN
679 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
680 $
CALL aladhd( nout, path )
682 WRITE( nout, fmt = 9997 )
'ZGESVX', fact,
683 $ trans, n, equed, imat, 7, result( 7 )
685 WRITE( nout, fmt = 9998 )
'ZGESVX', fact,
686 $ trans, n, imat, 7, result( 7 )
702 CALL alasvm( path, nout, nfail, nrun, nerrs )
704 9999
FORMAT( 1x, a,
', N =', i5,
', type ', i2,
', test(', i2,
') =',
706 9998
FORMAT( 1x, a,
', FACT=''', a1,
''', TRANS=''', a1,
''', N=', i5,
707 $
', type ', i2,
', test(', i1,
')=', g12.5 )
708 9997
FORMAT( 1x, a,
', FACT=''', a1,
''', TRANS=''', a1,
''', N=', i5,
709 $
', EQUED=''', a1,
''', type ', i2,
', test(', i1,
')=',
subroutine alasvm(type, nout, nfail, nrun, nerrs)
ALASVM
subroutine xlaenv(ispec, nvalue)
XLAENV
subroutine zget02(trans, m, n, nrhs, a, lda, x, ldx, b, ldb, rwork, resid)
ZGET02
subroutine zlarhs(path, xtype, uplo, trans, m, n, kl, ku, nrhs, a, lda, x, ldx, b, ldb, iseed, info)
ZLARHS
subroutine aladhd(iounit, path)
ALADHD
subroutine alaerh(path, subnam, info, infoe, opts, m, n, kl, ku, n5, imat, nfail, nerrs, nout)
ALAERH
subroutine zgeequ(m, n, a, lda, r, c, rowcnd, colcnd, amax, info)
ZGEEQU
subroutine zgesv(n, nrhs, a, lda, ipiv, b, ldb, info)
Download ZGESV + dependencies <a href="http://www.netlib.org/cgi-bin/netlibfiles....
subroutine zgesvx(fact, trans, n, nrhs, a, lda, af, ldaf, ipiv, equed, r, c, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)
ZGESVX computes the solution to system of linear equations A * X = B for GE matrices
subroutine zgetrf(m, n, a, lda, ipiv, info)
ZGETRF
subroutine zgetri(n, a, lda, ipiv, work, lwork, info)
ZGETRI
subroutine zlacpy(uplo, m, n, a, lda, b, ldb)
ZLACPY copies all or part of one two-dimensional array to another.
subroutine zlaqge(m, n, a, lda, r, c, rowcnd, colcnd, amax, equed)
ZLAQGE scales a general rectangular matrix, using row and column scaling factors computed by sgeequ.
subroutine zlaset(uplo, m, n, alpha, beta, a, lda)
ZLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.
subroutine zdrvge(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, asav, b, bsav, x, xact, s, work, rwork, iwork, nout)
ZDRVGE
subroutine zerrvx(path, nunit)
ZERRVX
subroutine zget01(m, n, a, lda, afac, ldafac, ipiv, rwork, resid)
ZGET01
subroutine zget04(n, nrhs, x, ldx, xact, ldxact, rcond, resid)
ZGET04
subroutine zget07(trans, n, nrhs, a, lda, b, ldb, x, ldx, xact, ldxact, ferr, chkferr, berr, reslts)
ZGET07
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