154 SUBROUTINE cdrvsy_rk( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR,
155 $ NMAX, A, AFAC, E, AINV, B, X, XACT, WORK,
156 $ RWORK, IWORK, NOUT )
164 INTEGER NMAX, NN, NOUT, NRHS
169 INTEGER IWORK( * ), NVAL( * )
171 COMPLEX A( * ), AFAC( * ), AINV( * ), B( * ), E( * ),
172 $ work( * ), x( * ), xact( * )
179 PARAMETER ( ONE = 1.0e+0, zero = 0.0e+0 )
180 INTEGER NTYPES, NTESTS
181 parameter( ntypes = 11, ntests = 3 )
183 parameter( nfact = 2 )
187 CHARACTER DIST, FACT,
TYPE, UPLO, XTYPE
188 CHARACTER*3 MATPATH, PATH
189 INTEGER I, I1, I2, IFACT, IMAT, IN, INFO, IOFF, IUPLO,
190 $ izero, j, k, kl, ku, lda, lwork, mode, n,
191 $ nb, nbmin, nerrs, nfail, nimat, nrun, nt
192 REAL AINVNM, ANORM, CNDNUM, RCONDC
195 CHARACTER FACTS( NFACT ), UPLOS( 2 )
196 INTEGER ISEED( 4 ), ISEEDY( 4 )
197 REAL RESULT( NTESTS )
215 COMMON / infoc / infot, nunit, ok, lerr
216 COMMON / srnamc / srnamt
222 DATA iseedy / 1988, 1989, 1990, 1991 /
223 DATA uplos /
'U',
'L' / , facts /
'F',
'N' /
231 path( 1: 1 ) =
'Complex precision'
236 matpath( 1: 1 ) =
'Complex precision'
237 matpath( 2: 3 ) =
'SY'
243 iseed( i ) = iseedy( i )
245 lwork = max( 2*nmax, nmax*nrhs )
250 $
CALL cerrvx( path, nout )
271 DO 170 imat = 1, nimat
275 IF( .NOT.dotype( imat ) )
280 zerot = imat.GE.3 .AND. imat.LE.6
281 IF( zerot .AND. n.LT.imat-2 )
287 uplo = uplos( iuplo )
289 IF( imat.NE.ntypes )
THEN
296 CALL clatb4( matpath, imat, n, n,
TYPE, kl, ku, anorm,
297 $ mode, cndnum, dist )
302 CALL clatms( n, n, dist, iseed,
TYPE, rwork, mode,
303 $ cndnum, anorm, kl, ku, uplo, a, lda,
309 CALL alaerh( path,
'CLATMS', info, 0, uplo, n, n,
310 $ -1, -1, -1, imat, nfail, nerrs, nout )
320 ELSE IF( imat.EQ.4 )
THEN
330 IF( iuplo.EQ.1 )
THEN
331 ioff = ( izero-1 )*lda
332 DO 20 i = 1, izero - 1
342 DO 40 i = 1, izero - 1
352 IF( iuplo.EQ.1 )
THEN
389 CALL clatsy( uplo, n, a, lda, iseed )
392 DO 150 ifact = 1, nfact
396 fact = facts( ifact )
405 ELSE IF( ifact.EQ.1 )
THEN
409 anorm = clansy(
'1', uplo, n, a, lda, rwork )
414 CALL clacpy( uplo, n, n, a, lda, afac, lda )
415 CALL csytrf_rk( uplo, n, afac, lda, e, iwork, work,
420 CALL clacpy( uplo, n, n, afac, lda, ainv, lda )
421 lwork = (n+nb+1)*(nb+3)
426 CALL csytri_3( uplo, n, ainv, lda, e, iwork,
427 $ work, lwork, info )
428 ainvnm = clansy(
'1', uplo, n, ainv, lda, rwork )
432 IF( anorm.LE.zero .OR. ainvnm.LE.zero )
THEN
435 rcondc = ( one / anorm ) / ainvnm
442 CALL clarhs( matpath, xtype, uplo,
' ', n, n, kl, ku,
443 $ nrhs, a, lda, xact, lda, b, lda, iseed,
449 IF( ifact.EQ.2 )
THEN
450 CALL clacpy( uplo, n, n, a, lda, afac, lda )
451 CALL clacpy(
'Full', n, nrhs, b, lda, x, lda )
457 CALL csysv_rk( uplo, n, nrhs, afac, lda, e, iwork,
458 $ x, lda, work, lwork, info )
466 IF( iwork( k ).LT.0 )
THEN
467 IF( iwork( k ).NE.-k )
THEN
471 ELSE IF( iwork( k ).NE.k )
THEN
480 CALL alaerh( path,
'CSYSV_RK', info, k, uplo,
481 $ n, n, -1, -1, nrhs, imat, nfail,
484 ELSE IF( info.NE.0 )
THEN
491 CALL csyt01_3( uplo, n, a, lda, afac, lda, e,
492 $ iwork, ainv, lda, rwork,
497 CALL clacpy(
'Full', n, nrhs, b, lda, work, lda )
498 CALL csyt02( uplo, n, nrhs, a, lda, x, lda, work,
499 $ lda, rwork, result( 2 ) )
504 CALL cget04( n, nrhs, x, lda, xact, lda, rcondc,
512 IF( result( k ).GE.thresh )
THEN
513 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
514 $
CALL aladhd( nout, path )
515 WRITE( nout, fmt = 9999 )
'CSYSV_RK', uplo,
516 $ n, imat, k, result( k )
532 CALL alasvm( path, nout, nfail, nrun, nerrs )
534 9999
FORMAT( 1x, a,
', UPLO=''', a1,
''', N =', i5,
', type ', i2,
535 $
', 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 cdrvsy_rk(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, e, ainv, b, x, xact, work, rwork, iwork, nout)
CDRVSY_RK
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 clatsy(uplo, n, x, ldx, iseed)
CLATSY
subroutine csyt01_3(uplo, n, a, lda, afac, ldafac, e, ipiv, c, ldc, rwork, resid)
CSYT01_3
subroutine csyt02(uplo, n, nrhs, a, lda, x, ldx, b, ldb, rwork, resid)
CSYT02
subroutine csysv_rk(uplo, n, nrhs, a, lda, e, ipiv, b, ldb, work, lwork, info)
CSYSV_RK computes the solution to system of linear equations A * X = B for SY matrices
subroutine csytrf_rk(uplo, n, a, lda, e, ipiv, work, lwork, info)
CSYTRF_RK computes the factorization of a complex symmetric indefinite matrix using the bounded Bunch...
subroutine csytri_3(uplo, n, a, lda, e, ipiv, work, lwork, info)
CSYTRI_3
subroutine clacpy(uplo, m, n, a, lda, b, ldb)
CLACPY copies all or part of one two-dimensional array to another.