151 SUBROUTINE zdrvab( DOTYPE, NM, MVAL, NNS,
152 $ nsval, thresh, nmax, a, afac, b,
153 $ x, work, rwork, swork, iwork, nout )
161 INTEGER nm, nmax, nns, nout
162 DOUBLE PRECISION thresh
166 INTEGER mval( * ), nsval( * ), iwork( * )
167 DOUBLE PRECISION rwork( * )
169 COMPLEX*16 a( * ), afac( * ), b( * ),
176 DOUBLE PRECISION zero
177 parameter( zero = 0.0d+0 )
179 parameter( ntypes = 11 )
181 parameter( ntests = 1 )
185 CHARACTER dist, trans, type, xtype
187 INTEGER i, im, imat, info, ioff, irhs,
188 $ izero, kl, ku, lda, m, mode, n,
189 $ nerrs, nfail, nimat, nrhs, nrun
190 DOUBLE PRECISION anorm, cndnum
193 INTEGER iseed( 4 ), iseedy( 4 )
194 DOUBLE PRECISION result( ntests )
204 INTRINSIC dcmplx, dble, max, min, sqrt
212 common / infoc / infot, nunit, ok, lerr
213 common / srnamc / srnamt
216 DATA iseedy / 2006, 2007, 2008, 2009 /
223 path( 1: 1 ) =
'Zomplex precision'
229 iseed( i ) = iseedy( i )
242 IF( m.LE.0 .OR. n.LE.0 )
245 DO 100 imat = 1, nimat
249 IF( .NOT.dotype( imat ) )
254 zerot = imat.GE.5 .AND. imat.LE.7
255 IF( zerot .AND. n.LT.imat-4 )
261 CALL
zlatb4( path, imat, m, n, type, kl, ku, anorm, mode,
265 CALL
zlatms( m, n, dist, iseed, type, rwork, mode,
266 $ cndnum, anorm, kl, ku,
'No packing', a, lda,
272 CALL
alaerh( path,
'ZLATMS', info, 0,
' ', m, n, -1,
273 $ -1, -1, imat, nfail, nerrs, nout )
283 ELSE IF( imat.EQ.6 )
THEN
286 izero = min( m, n ) / 2 + 1
288 ioff = ( izero-1 )*lda
294 CALL
zlaset(
'Full', m, n-izero+1, dcmplx(zero),
295 $ dcmplx(zero), a( ioff+1 ), lda )
307 CALL
zlarhs( path, xtype,
' ', trans, n, n, kl,
308 $ ku, nrhs, a, lda, x, lda, b,
315 CALL
zlacpy(
'Full', m, n, a, lda, afac, lda )
317 CALL
zcgesv( n, nrhs, a, lda, iwork, b, lda, x, lda,
318 $ work, swork, rwork, iter, info)
321 CALL
zlacpy(
'Full', m, n, afac, lda, a, lda )
327 IF( info.NE.izero )
THEN
329 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
330 $ CALL
alahd( nout, path )
333 IF( info.NE.izero .AND. izero.NE.0 )
THEN
334 WRITE( nout, fmt = 9988 )
'ZCGESV',info,
337 WRITE( nout, fmt = 9975 )
'ZCGESV',info,
349 CALL
zlacpy(
'Full', n, nrhs, b, lda, work, lda )
351 CALL
zget08( trans, n, n, nrhs, a, lda, x, lda, work,
352 $ lda, rwork, result( 1 ) )
366 IF ((thresh.LE.0.0e+00)
367 $ .OR.((iter.GE.0).AND.(n.GT.0)
368 $ .AND.(result(1).GE.sqrt(dble(n))))
369 $ .OR.((iter.LT.0).AND.(result(1).GE.thresh)))
THEN
371 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
THEN
372 WRITE( nout, fmt = 8999 )
'DGE'
373 WRITE( nout, fmt =
'( '' Matrix types:'' )' )
374 WRITE( nout, fmt = 8979 )
375 WRITE( nout, fmt =
'( '' Test ratios:'' )' )
376 WRITE( nout, fmt = 8960 )1
377 WRITE( nout, fmt =
'( '' Messages:'' )' )
380 WRITE( nout, fmt = 9998 )trans, n, nrhs,
381 $ imat, 1, result( 1 )
391 IF( nfail.GT.0 )
THEN
392 WRITE( nout, fmt = 9996 )
'ZCGESV', nfail, nrun
394 WRITE( nout, fmt = 9995 )
'ZCGESV', nrun
396 IF( nerrs.GT.0 )
THEN
397 WRITE( nout, fmt = 9994 )nerrs
400 9998 format(
' TRANS=''', a1,
''', N =', i5,
', NRHS=', i3,
', type ',
401 $ i2,
', test(', i2,
') =', g12.5 )
402 9996 format( 1x, a6,
': ', i6,
' out of ', i6,
403 $
' tests failed to pass the threshold' )
404 9995 format( /1x,
'All tests for ', a6,
405 $
' routines passed the threshold ( ', i6,
' tests run)' )
406 9994 format( 6x, i6,
' error messages recorded' )
410 9988 format(
' *** ', a6,
' returned with INFO =', i5,
' instead of ',
411 $ i5, /
' ==> M =', i5,
', type ',
416 9975 format(
' *** Error code from ', a6,
'=', i5,
' for M=', i5,
418 8999 format( / 1x, a3,
': General dense matrices' )
419 8979 format( 4x,
'1. Diagonal', 24x,
'7. Last n/2 columns zero', / 4x,
420 $
'2. Upper triangular', 16x,
421 $
'8. Random, CNDNUM = sqrt(0.1/EPS)', / 4x,
422 $
'3. Lower triangular', 16x,
'9. Random, CNDNUM = 0.1/EPS',
423 $ / 4x,
'4. Random, CNDNUM = 2', 13x,
424 $
'10. Scaled near underflow', / 4x,
'5. First column zero',
425 $ 14x,
'11. Scaled near overflow', / 4x,
426 $
'6. Last column zero' )
427 8960 format( 3x, i2,
': norm_1( B - A * X ) / ',
428 $
'( norm_1(A) * norm_1(X) * EPS * SQRT(N) ) > 1 if ITERREF',
429 $ / 4x,
'or norm_1( B - A * X ) / ',
430 $
'( norm_1(A) * norm_1(X) * EPS ) > THRES if DGETRF' )