161 SUBROUTINE cdrvge( 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
176 INTEGER IWORK( * ), NVAL( * )
177 REAL RWORK( * ), S( * )
178 COMPLEX A( * ), AFAC( * ), ASAV( * ), B( * ),
179 $ bsav( * ), work( * ), x( * ), xact( * )
186 PARAMETER ( ONE = 1.0e+0, zero = 0.0e+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 REAL 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 REAL RDUM( 1 ), RESULT( NTESTS )
212 REAL CLANGE, CLANTR, SGET06, SLAMCH
213 EXTERNAL lsame, clange, clantr, sget06, slamch
222 INTRINSIC abs, cmplx, 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 ) =
'Complex precision'
249 iseed( i ) = iseedy( i )
255 $
CALL cerrvx( 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 clatb4( path, imat, n, n,
TYPE, kl, ku, anorm, mode,
293 rcondc = one / cndnum
296 CALL clatms( n, n, dist, iseed,
TYPE, rwork, mode, cndnum,
297 $ anorm, kl, ku,
'No packing', a, lda, work,
303 CALL alaerh( path,
'CLATMS', 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 claset(
'Full', n, n-izero+1, cmplx( zero ),
326 $ cmplx( zero ), a( ioff+1 ), lda )
334 CALL clacpy(
'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 clacpy(
'Full', n, n, asav, lda, afac, lda )
364 IF( equil .OR. iequed.GT.1 )
THEN
369 CALL cgeequ( 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 claqge( n, n, afac, lda, s, s( n+1 ),
386 $ rowcnd, colcnd, amax, equed )
400 anormo = clange(
'1', n, n, afac, lda, rwork )
401 anormi = clange(
'I', n, n, afac, lda, rwork )
406 CALL cgetrf( n, n, afac, lda, iwork, info )
410 CALL clacpy(
'Full', n, n, afac, lda, a, lda )
411 lwork = nmax*max( 3, nrhs )
413 CALL cgetri( n, a, lda, iwork, work, lwork, info )
417 ainvnm = clange(
'1', n, n, a, lda, rwork )
418 IF( anormo.LE.zero .OR. ainvnm.LE.zero )
THEN
421 rcondo = ( one / anormo ) / ainvnm
426 ainvnm = clange(
'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 clacpy(
'Full', n, n, asav, lda, a, lda )
452 CALL clarhs( path, xtype,
'Full', trans, n, n, kl,
453 $ ku, nrhs, a, lda, xact, lda, b, lda,
456 CALL clacpy(
'Full', n, nrhs, b, lda, bsav, lda )
458 IF( nofact .AND. itran.EQ.1 )
THEN
465 CALL clacpy(
'Full', n, n, a, lda, afac, lda )
466 CALL clacpy(
'Full', n, nrhs, b, lda, x, lda )
469 CALL cgesv( n, nrhs, afac, lda, iwork, x, lda,
475 $
CALL alaerh( path,
'CGESV ', info, izero,
476 $
' ', n, n, -1, -1, nrhs, imat,
477 $ nfail, nerrs, nout )
482 CALL cget01( n, n, a, lda, afac, lda, iwork,
483 $ rwork, result( 1 ) )
485 IF( izero.EQ.0 )
THEN
489 CALL clacpy(
'Full', n, nrhs, b, lda, work,
491 CALL cget02(
'No transpose', n, n, nrhs, a,
492 $ lda, x, lda, work, lda, rwork,
497 CALL cget04( 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 )
'CGESV ', n,
510 $ imat, k, result( k )
520 $
CALL claset(
'Full', n, n, cmplx( zero ),
521 $ cmplx( zero ), afac, lda )
522 CALL claset(
'Full', n, nrhs, cmplx( zero ),
523 $ cmplx( zero ), x, lda )
524 IF( iequed.GT.1 .AND. n.GT.0 )
THEN
529 CALL claqge( n, n, a, lda, s, s( n+1 ), rowcnd,
530 $ colcnd, amax, equed )
537 CALL cgesvx( 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,
'CGESVX', 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 = clantr(
'M',
'U',
'N', info, info,
556 IF( rpvgrw.EQ.zero )
THEN
559 rpvgrw = clange(
'M', n, info, a, lda,
563 rpvgrw = clantr(
'M',
'U',
'N', n, n, afac, lda,
565 IF( rpvgrw.EQ.zero )
THEN
568 rpvgrw = clange(
'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 cget01( n, n, a, lda, afac, lda, iwork,
582 $ rwork( 2*nrhs+1 ), result( 1 ) )
593 CALL clacpy(
'Full', n, nrhs, bsav, lda, work,
595 CALL cget02( 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 cget04( n, nrhs, x, lda, xact, lda,
604 $ rcondc, result( 3 ) )
606 IF( itran.EQ.1 )
THEN
611 CALL cget04( n, nrhs, x, lda, xact, lda,
612 $ roldc, result( 3 ) )
618 CALL cget07( trans, n, nrhs, asav, lda, b, lda,
619 $ x, lda, xact, lda, rwork, .true.,
620 $ rwork( nrhs+1 ), result( 4 ) )
628 result( 6 ) = sget06( 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 )
'CGESVX',
640 $ fact, trans, n, equed, imat, k,
643 WRITE( nout, fmt = 9998 )
'CGESVX',
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 )
'CGESVX', fact,
657 $ trans, n, equed, imat, 1, result( 1 )
659 WRITE( nout, fmt = 9998 )
'CGESVX', 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 )
'CGESVX', fact,
670 $ trans, n, equed, imat, 6, result( 6 )
672 WRITE( nout, fmt = 9998 )
'CGESVX', 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 )
'CGESVX', fact,
683 $ trans, n, equed, imat, 7, result( 7 )
685 WRITE( nout, fmt = 9998 )
'CGESVX', 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 cget02(trans, m, n, nrhs, a, lda, x, ldx, b, ldb, rwork, resid)
CGET02
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 cdrvge(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, asav, b, bsav, x, xact, s, work, rwork, iwork, nout)
CDRVGE
subroutine cerrvx(path, nunit)
CERRVX
subroutine cget01(m, n, a, lda, afac, ldafac, ipiv, rwork, resid)
CGET01
subroutine cget04(n, nrhs, x, ldx, xact, ldxact, rcond, resid)
CGET04
subroutine cget07(trans, n, nrhs, a, lda, b, ldb, x, ldx, xact, ldxact, ferr, chkferr, berr, reslts)
CGET07
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 cgeequ(m, n, a, lda, r, c, rowcnd, colcnd, amax, info)
CGEEQU
subroutine cgesv(n, nrhs, a, lda, ipiv, b, ldb, info)
Download CGESV + dependencies <a href="http://www.netlib.org/cgi-bin/netlibfiles....
subroutine cgesvx(fact, trans, n, nrhs, a, lda, af, ldaf, ipiv, equed, r, c, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)
CGESVX computes the solution to system of linear equations A * X = B for GE matrices
subroutine cgetrf(m, n, a, lda, ipiv, info)
CGETRF
subroutine cgetri(n, a, lda, ipiv, work, lwork, info)
CGETRI
subroutine clacpy(uplo, m, n, a, lda, b, ldb)
CLACPY copies all or part of one two-dimensional array to another.
subroutine claqge(m, n, a, lda, r, c, rowcnd, colcnd, amax, equed)
CLAQGE scales a general rectangular matrix, using row and column scaling factors computed by sgeequ.
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.