156 SUBROUTINE cdrvpp( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX,
157 $ A, AFAC, ASAV, B, BSAV, X, XACT, S, WORK,
166 INTEGER NMAX, NN, NOUT, NRHS
172 REAL RWORK( * ), S( * )
173 COMPLEX A( * ), AFAC( * ), ASAV( * ), B( * ),
174 $ bsav( * ), work( * ), x( * ), xact( * )
181 PARAMETER ( ONE = 1.0e+0, zero = 0.0e+0 )
183 parameter( ntypes = 9 )
185 parameter( ntests = 6 )
188 LOGICAL EQUIL, NOFACT, PREFAC, ZEROT
189 CHARACTER DIST, EQUED, FACT, PACKIT,
TYPE, UPLO, XTYPE
191 INTEGER I, IEQUED, IFACT, IMAT, IN, INFO, IOFF, IUPLO,
192 $ izero, k, k1, kl, ku, lda, mode, n, nerrs,
193 $ nfact, nfail, nimat, npp, nrun, nt
194 REAL AINVNM, AMAX, ANORM, CNDNUM, RCOND, RCONDC,
198 CHARACTER EQUEDS( 2 ), FACTS( 3 ), PACKS( 2 ), UPLOS( 2 )
199 INTEGER ISEED( 4 ), ISEEDY( 4 )
200 REAL RESULT( NTESTS )
205 EXTERNAL lsame, clanhp, sget06
219 COMMON / infoc / infot, nunit, ok, lerr
220 COMMON / srnamc / srnamt
226 DATA iseedy / 1988, 1989, 1990, 1991 /
227 DATA uplos /
'U',
'L' / , facts /
'F',
'N',
'E' / ,
228 $ packs /
'C',
'R' / , equeds /
'N',
'Y' /
234 path( 1: 1 ) =
'Complex precision'
240 iseed( i ) = iseedy( i )
246 $
CALL cerrvx( path, nout )
260 DO 130 imat = 1, nimat
264 IF( .NOT.dotype( imat ) )
269 zerot = imat.GE.3 .AND. imat.LE.5
270 IF( zerot .AND. n.LT.imat-2 )
276 uplo = uplos( iuplo )
277 packit = packs( iuplo )
282 CALL clatb4( path, imat, n, n,
TYPE, kl, ku, anorm, mode,
284 rcondc = one / cndnum
287 CALL clatms( n, n, dist, iseed,
TYPE, rwork, mode,
288 $ cndnum, anorm, kl, ku, packit, a, lda, work,
294 CALL alaerh( path,
'CLATMS', info, 0, uplo, n, n, -1,
295 $ -1, -1, imat, nfail, nerrs, nout )
305 ELSE IF( imat.EQ.4 )
THEN
313 IF( iuplo.EQ.1 )
THEN
314 ioff = ( izero-1 )*izero / 2
315 DO 20 i = 1, izero - 1
325 DO 40 i = 1, izero - 1
340 IF( iuplo.EQ.1 )
THEN
343 CALL claipd( n, a, n, -1 )
348 CALL ccopy( npp, a, 1, asav, 1 )
351 equed = equeds( iequed )
352 IF( iequed.EQ.1 )
THEN
358 DO 100 ifact = 1, nfact
359 fact = facts( ifact )
360 prefac = lsame( fact,
'F' )
361 nofact = lsame( fact,
'N' )
362 equil = lsame( fact,
'E' )
369 ELSE IF( .NOT.lsame( fact,
'N' ) )
THEN
376 CALL ccopy( npp, asav, 1, afac, 1 )
377 IF( equil .OR. iequed.GT.1 )
THEN
382 CALL cppequ( uplo, n, afac, s, scond, amax,
384 IF( info.EQ.0 .AND. n.GT.0 )
THEN
390 CALL claqhp( uplo, n, afac, s, scond,
403 anorm = clanhp(
'1', uplo, n, afac, rwork )
407 CALL cpptrf( uplo, n, afac, info )
411 CALL ccopy( npp, afac, 1, a, 1 )
412 CALL cpptri( uplo, n, a, info )
416 ainvnm = clanhp(
'1', uplo, n, a, rwork )
417 IF( anorm.LE.zero .OR. ainvnm.LE.zero )
THEN
420 rcondc = ( one / anorm ) / ainvnm
426 CALL ccopy( npp, asav, 1, a, 1 )
431 CALL clarhs( path, xtype, uplo,
' ', n, n, kl, ku,
432 $ nrhs, a, lda, xact, lda, b, lda,
435 CALL clacpy(
'Full', n, nrhs, b, lda, bsav, lda )
444 CALL ccopy( npp, a, 1, afac, 1 )
445 CALL clacpy(
'Full', n, nrhs, b, lda, x, lda )
448 CALL cppsv( uplo, n, nrhs, afac, x, lda, info )
452 IF( info.NE.izero )
THEN
453 CALL alaerh( path,
'CPPSV ', info, izero,
454 $ uplo, n, n, -1, -1, nrhs, imat,
455 $ nfail, nerrs, nout )
457 ELSE IF( info.NE.0 )
THEN
464 CALL cppt01( uplo, n, a, afac, rwork,
469 CALL clacpy(
'Full', n, nrhs, b, lda, work,
471 CALL cppt02( uplo, n, nrhs, a, x, lda, work,
472 $ lda, rwork, result( 2 ) )
476 CALL cget04( n, nrhs, x, lda, xact, lda, rcondc,
484 IF( result( k ).GE.thresh )
THEN
485 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
486 $
CALL aladhd( nout, path )
487 WRITE( nout, fmt = 9999 )
'CPPSV ', uplo,
488 $ n, imat, k, result( k )
498 IF( .NOT.prefac .AND. npp.GT.0 )
499 $
CALL claset(
'Full', npp, 1, cmplx( zero ),
500 $ cmplx( zero ), afac, npp )
501 CALL claset(
'Full', n, nrhs, cmplx( zero ),
502 $ cmplx( zero ), x, lda )
503 IF( iequed.GT.1 .AND. n.GT.0 )
THEN
508 CALL claqhp( uplo, n, a, s, scond, amax, equed )
515 CALL cppsvx( fact, uplo, n, nrhs, a, afac, equed,
516 $ s, b, lda, x, lda, rcond, rwork,
517 $ rwork( nrhs+1 ), work,
518 $ rwork( 2*nrhs+1 ), info )
522 IF( info.NE.izero )
THEN
523 CALL alaerh( path,
'CPPSVX', info, izero,
524 $ fact // uplo, n, n, -1, -1, nrhs,
525 $ imat, nfail, nerrs, nout )
530 IF( .NOT.prefac )
THEN
535 CALL cppt01( uplo, n, a, afac,
536 $ rwork( 2*nrhs+1 ), result( 1 ) )
544 CALL clacpy(
'Full', n, nrhs, bsav, lda, work,
546 CALL cppt02( uplo, n, nrhs, asav, x, lda, work,
547 $ lda, rwork( 2*nrhs+1 ),
552 IF( nofact .OR. ( prefac .AND. lsame( equed,
554 CALL cget04( n, nrhs, x, lda, xact, lda,
555 $ rcondc, result( 3 ) )
557 CALL cget04( n, nrhs, x, lda, xact, lda,
558 $ roldc, result( 3 ) )
564 CALL cppt05( uplo, n, nrhs, asav, b, lda, x,
565 $ lda, xact, lda, rwork,
566 $ rwork( nrhs+1 ), result( 4 ) )
574 result( 6 ) = sget06( rcond, rcondc )
580 IF( result( k ).GE.thresh )
THEN
581 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
582 $
CALL aladhd( nout, path )
584 WRITE( nout, fmt = 9997 )
'CPPSVX', fact,
585 $ uplo, n, equed, imat, k, result( k )
587 WRITE( nout, fmt = 9998 )
'CPPSVX', fact,
588 $ uplo, n, imat, k, result( k )
603 CALL alasvm( path, nout, nfail, nrun, nerrs )
605 9999
FORMAT( 1x, a,
', UPLO=''', a1,
''', N =', i5,
', type ', i1,
606 $
', test(', i1,
')=', g12.5 )
607 9998
FORMAT( 1x, a,
', FACT=''', a1,
''', UPLO=''', a1,
''', N=', i5,
608 $
', type ', i1,
', test(', i1,
')=', g12.5 )
609 9997
FORMAT( 1x, a,
', FACT=''', a1,
''', UPLO=''', a1,
''', N=', i5,
610 $
', EQUED=''', a1,
''', type ', i1,
', test(', i1,
')=',
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 aladhd(iounit, path)
ALADHD
subroutine alaerh(path, subnam, info, infoe, opts, m, n, kl, ku, n5, imat, nfail, nerrs, nout)
ALAERH
subroutine cdrvpp(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, asav, b, bsav, x, xact, s, work, rwork, nout)
CDRVPP
subroutine cerrvx(path, nunit)
CERRVX
subroutine cget04(n, nrhs, x, ldx, xact, ldxact, rcond, resid)
CGET04
subroutine claipd(n, a, inda, vinda)
CLAIPD
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 cppt01(uplo, n, a, afac, rwork, resid)
CPPT01
subroutine cppt02(uplo, n, nrhs, a, x, ldx, b, ldb, rwork, resid)
CPPT02
subroutine cppt05(uplo, n, nrhs, ap, b, ldb, x, ldx, xact, ldxact, ferr, berr, reslts)
CPPT05
subroutine ccopy(n, cx, incx, cy, incy)
CCOPY
subroutine clacpy(uplo, m, n, a, lda, b, ldb)
CLACPY copies all or part of one two-dimensional array to another.
subroutine claqhp(uplo, n, ap, s, scond, amax, equed)
CLAQHP scales a Hermitian matrix stored in packed form.
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.
subroutine cppequ(uplo, n, ap, s, scond, amax, info)
CPPEQU
subroutine cppsv(uplo, n, nrhs, ap, b, ldb, info)
CPPSV computes the solution to system of linear equations A * X = B for OTHER matrices
subroutine cppsvx(fact, uplo, n, nrhs, ap, afp, equed, s, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)
CPPSVX computes the solution to system of linear equations A * X = B for OTHER matrices
subroutine cpptrf(uplo, n, ap, info)
CPPTRF
subroutine cpptri(uplo, n, ap, info)
CPPTRI