143 SUBROUTINE ddrvac( DOTYPE, NM, MVAL, NNS, NSVAL, THRESH, NMAX,
144 $ a, afac, b, x, work,
145 $ rwork, swork, nout )
153 INTEGER nmax, nm, nns, nout
154 DOUBLE PRECISION thresh
158 INTEGER mval( * ), nsval( * )
160 DOUBLE PRECISION a( * ), afac( * ), b( * ),
161 $ rwork( * ), work( * ), x( * )
167 DOUBLE PRECISION zero
168 parameter( zero = 0.0d+0 )
170 parameter( ntypes = 9 )
172 parameter( ntests = 1 )
176 CHARACTER dist, type, uplo, xtype
178 INTEGER i, im, imat, info, ioff, irhs, iuplo,
179 $ izero, kl, ku, lda, mode, n,
180 $ nerrs, nfail, nimat, nrhs, nrun
181 DOUBLE PRECISION anorm, cndnum
185 INTEGER iseed( 4 ), iseedy( 4 )
186 DOUBLE PRECISION result( ntests )
201 INTRINSIC dble, max, sqrt
209 common / infoc / infot, nunit, ok, lerr
210 common / srnamc / srnamt
213 DATA iseedy / 1988, 1989, 1990, 1991 /
214 DATA uplos /
'U',
'L' /
221 path( 1: 1 ) =
'Double precision'
227 iseed( i ) = iseedy( i )
241 DO 110 imat = 1, nimat
245 IF( .NOT.dotype( imat ) )
250 zerot = imat.GE.3 .AND. imat.LE.5
251 IF( zerot .AND. n.LT.imat-2 )
257 uplo = uplos( iuplo )
262 CALL
dlatb4( path, imat, n, n, type, kl, ku, anorm, mode,
266 CALL
dlatms( n, n, dist, iseed, type, rwork, mode,
267 $ cndnum, anorm, kl, ku, uplo, a, lda, work,
273 CALL
alaerh( path,
'DLATMS', info, 0, uplo, n, n, -1,
274 $ -1, -1, imat, nfail, nerrs, nout )
284 ELSE IF( imat.EQ.4 )
THEN
289 ioff = ( izero-1 )*lda
293 IF( iuplo.EQ.1 )
THEN
294 DO 20 i = 1, izero - 1
304 DO 40 i = 1, izero - 1
324 CALL
dlarhs( path, xtype, uplo,
' ', n, n, kl, ku,
325 $ nrhs, a, lda, x, lda, b, lda,
334 CALL
dlacpy(
'All', n, n, a, lda, afac, lda)
336 CALL
dsposv( uplo, n, nrhs, afac, lda, b, lda, x, lda,
337 $ work, swork, iter, info )
340 CALL
dlacpy(
'All', n, n, a, lda, afac, lda )
345 IF( info.NE.izero )
THEN
347 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
348 $ CALL
alahd( nout, path )
351 IF( info.NE.izero .AND. izero.NE.0 )
THEN
352 WRITE( nout, fmt = 9988 )
'DSPOSV',info,izero,n,
355 WRITE( nout, fmt = 9975 )
'DSPOSV',info,n,imat
366 CALL
dlacpy(
'All', n, nrhs, b, lda, work, lda )
368 CALL
dpot06( uplo, n, nrhs, a, lda, x, lda, work,
369 $ lda, rwork, result( 1 ) )
383 IF ((thresh.LE.0.0e+00)
384 $ .OR.((iter.GE.0).AND.(n.GT.0)
385 $ .AND.(result(1).GE.sqrt(dble(n))))
386 $ .OR.((iter.LT.0).AND.(result(1).GE.thresh)))
THEN
388 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
THEN
389 WRITE( nout, fmt = 8999 )
'DPO'
390 WRITE( nout, fmt =
'( '' Matrix types:'' )' )
391 WRITE( nout, fmt = 8979 )
392 WRITE( nout, fmt =
'( '' Test ratios:'' )' )
393 WRITE( nout, fmt = 8960 )1
394 WRITE( nout, fmt =
'( '' Messages:'' )' )
397 WRITE( nout, fmt = 9998 )uplo, n, nrhs, imat, 1,
413 IF( nfail.GT.0 )
THEN
414 WRITE( nout, fmt = 9996 )
'DSPOSV', nfail, nrun
416 WRITE( nout, fmt = 9995 )
'DSPOSV', nrun
418 IF( nerrs.GT.0 )
THEN
419 WRITE( nout, fmt = 9994 )nerrs
422 9998 format(
' UPLO=''', a1,
''', N =', i5,
', NRHS=', i3,
', type ',
423 $ i2,
', test(', i2,
') =', g12.5 )
424 9996 format( 1x, a6,
': ', i6,
' out of ', i6,
425 $
' tests failed to pass the threshold' )
426 9995 format( /1x,
'All tests for ', a6,
427 $
' routines passed the threshold ( ', i6,
' tests run)' )
428 9994 format( 6x, i6,
' error messages recorded' )
432 9988 format(
' *** ', a6,
' returned with INFO =', i5,
' instead of ',
433 $ i5, /
' ==> N =', i5,
', type ',
438 9975 format(
' *** Error code from ', a6,
'=', i5,
' for M=', i5,
440 8999 format( / 1x, a3,
': positive definite dense matrices' )
441 8979 format( 4x,
'1. Diagonal', 24x,
'7. Last n/2 columns zero', / 4x,
442 $
'2. Upper triangular', 16x,
443 $
'8. Random, CNDNUM = sqrt(0.1/EPS)', / 4x,
444 $
'3. Lower triangular', 16x,
'9. Random, CNDNUM = 0.1/EPS',
445 $ / 4x,
'4. Random, CNDNUM = 2', 13x,
446 $
'10. Scaled near underflow', / 4x,
'5. First column zero',
447 $ 14x,
'11. Scaled near overflow', / 4x,
448 $
'6. Last column zero' )
449 8960 format( 3x, i2,
': norm_1( B - A * X ) / ',
450 $
'( norm_1(A) * norm_1(X) * EPS * SQRT(N) ) > 1 if ITERREF',
451 $ / 4x,
'or norm_1( B - A * X ) / ',
452 $
'( norm_1(A) * norm_1(X) * EPS ) > THRES if DPOTRF' )