LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
zdrvge.f
Go to the documentation of this file.
1 *> \brief \b ZDRVGE
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 * Definition:
9 * ===========
10 *
11 * SUBROUTINE ZDRVGE( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX,
12 * A, AFAC, ASAV, B, BSAV, X, XACT, S, WORK,
13 * RWORK, IWORK, NOUT )
14 *
15 * .. Scalar Arguments ..
16 * LOGICAL TSTERR
17 * INTEGER NMAX, NN, NOUT, NRHS
18 * DOUBLE PRECISION THRESH
19 * ..
20 * .. Array Arguments ..
21 * LOGICAL DOTYPE( * )
22 * INTEGER IWORK( * ), NVAL( * )
23 * DOUBLE PRECISION RWORK( * ), S( * )
24 * COMPLEX*16 A( * ), AFAC( * ), ASAV( * ), B( * ),
25 * $ BSAV( * ), WORK( * ), X( * ), XACT( * )
26 * ..
27 *
28 *
29 *> \par Purpose:
30 * =============
31 *>
32 *> \verbatim
33 *>
34 *> ZDRVGE tests the driver routines ZGESV and -SVX.
35 *> \endverbatim
36 *
37 * Arguments:
38 * ==========
39 *
40 *> \param[in] DOTYPE
41 *> \verbatim
42 *> DOTYPE is LOGICAL array, dimension (NTYPES)
43 *> The matrix types to be used for testing. Matrices of type j
44 *> (for 1 <= j <= NTYPES) are used for testing if DOTYPE(j) =
45 *> .TRUE.; if DOTYPE(j) = .FALSE., then type j is not used.
46 *> \endverbatim
47 *>
48 *> \param[in] NN
49 *> \verbatim
50 *> NN is INTEGER
51 *> The number of values of N contained in the vector NVAL.
52 *> \endverbatim
53 *>
54 *> \param[in] NVAL
55 *> \verbatim
56 *> NVAL is INTEGER array, dimension (NN)
57 *> The values of the matrix column dimension N.
58 *> \endverbatim
59 *>
60 *> \param[in] NRHS
61 *> \verbatim
62 *> NRHS is INTEGER
63 *> The number of right hand side vectors to be generated for
64 *> each linear system.
65 *> \endverbatim
66 *>
67 *> \param[in] THRESH
68 *> \verbatim
69 *> THRESH is DOUBLE PRECISION
70 *> The threshold value for the test ratios. A result is
71 *> included in the output file if RESULT >= THRESH. To have
72 *> every test ratio printed, use THRESH = 0.
73 *> \endverbatim
74 *>
75 *> \param[in] TSTERR
76 *> \verbatim
77 *> TSTERR is LOGICAL
78 *> Flag that indicates whether error exits are to be tested.
79 *> \endverbatim
80 *>
81 *> \param[in] NMAX
82 *> \verbatim
83 *> NMAX is INTEGER
84 *> The maximum value permitted for N, used in dimensioning the
85 *> work arrays.
86 *> \endverbatim
87 *>
88 *> \param[out] A
89 *> \verbatim
90 *> A is COMPLEX*16 array, dimension (NMAX*NMAX)
91 *> \endverbatim
92 *>
93 *> \param[out] AFAC
94 *> \verbatim
95 *> AFAC is COMPLEX*16 array, dimension (NMAX*NMAX)
96 *> \endverbatim
97 *>
98 *> \param[out] ASAV
99 *> \verbatim
100 *> ASAV is COMPLEX*16 array, dimension (NMAX*NMAX)
101 *> \endverbatim
102 *>
103 *> \param[out] B
104 *> \verbatim
105 *> B is COMPLEX*16 array, dimension (NMAX*NRHS)
106 *> \endverbatim
107 *>
108 *> \param[out] BSAV
109 *> \verbatim
110 *> BSAV is COMPLEX*16 array, dimension (NMAX*NRHS)
111 *> \endverbatim
112 *>
113 *> \param[out] X
114 *> \verbatim
115 *> X is COMPLEX*16 array, dimension (NMAX*NRHS)
116 *> \endverbatim
117 *>
118 *> \param[out] XACT
119 *> \verbatim
120 *> XACT is COMPLEX*16 array, dimension (NMAX*NRHS)
121 *> \endverbatim
122 *>
123 *> \param[out] S
124 *> \verbatim
125 *> S is DOUBLE PRECISION array, dimension (2*NMAX)
126 *> \endverbatim
127 *>
128 *> \param[out] WORK
129 *> \verbatim
130 *> WORK is COMPLEX*16 array, dimension
131 *> (NMAX*max(3,NRHS))
132 *> \endverbatim
133 *>
134 *> \param[out] RWORK
135 *> \verbatim
136 *> RWORK is DOUBLE PRECISION array, dimension (2*NRHS+NMAX)
137 *> \endverbatim
138 *>
139 *> \param[out] IWORK
140 *> \verbatim
141 *> IWORK is INTEGER array, dimension (NMAX)
142 *> \endverbatim
143 *>
144 *> \param[in] NOUT
145 *> \verbatim
146 *> NOUT is INTEGER
147 *> The unit number for output.
148 *> \endverbatim
149 *
150 * Authors:
151 * ========
152 *
153 *> \author Univ. of Tennessee
154 *> \author Univ. of California Berkeley
155 *> \author Univ. of Colorado Denver
156 *> \author NAG Ltd.
157 *
158 *> \date November 2011
159 *
160 *> \ingroup complex16_lin
161 *
162 * =====================================================================
163  SUBROUTINE zdrvge( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX,
164  $ a, afac, asav, b, bsav, x, xact, s, work,
165  $ rwork, iwork, nout )
166 *
167 * -- LAPACK test routine (version 3.4.0) --
168 * -- LAPACK is a software package provided by Univ. of Tennessee, --
169 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
170 * November 2011
171 *
172 * .. Scalar Arguments ..
173  LOGICAL tsterr
174  INTEGER nmax, nn, nout, nrhs
175  DOUBLE PRECISION thresh
176 * ..
177 * .. Array Arguments ..
178  LOGICAL dotype( * )
179  INTEGER iwork( * ), nval( * )
180  DOUBLE PRECISION rwork( * ), s( * )
181  COMPLEX*16 a( * ), afac( * ), asav( * ), b( * ),
182  $ bsav( * ), work( * ), x( * ), xact( * )
183 * ..
184 *
185 * =====================================================================
186 *
187 * .. Parameters ..
188  DOUBLE PRECISION one, zero
189  parameter( one = 1.0d+0, zero = 0.0d+0 )
190  INTEGER ntypes
191  parameter( ntypes = 11 )
192  INTEGER ntests
193  parameter( ntests = 7 )
194  INTEGER ntran
195  parameter( ntran = 3 )
196 * ..
197 * .. Local Scalars ..
198  LOGICAL equil, nofact, prefac, trfcon, zerot
199  CHARACTER dist, equed, fact, trans, type, xtype
200  CHARACTER*3 path
201  INTEGER i, iequed, ifact, imat, in, info, ioff, itran,
202  $ izero, k, k1, kl, ku, lda, lwork, mode, n, nb,
203  $ nbmin, nerrs, nfact, nfail, nimat, nrun, nt
204  DOUBLE PRECISION ainvnm, amax, anorm, anormi, anormo, cndnum,
205  $ colcnd, rcond, rcondc, rcondi, rcondo, roldc,
206  $ roldi, roldo, rowcnd, rpvgrw
207 * ..
208 * .. Local Arrays ..
209  CHARACTER equeds( 4 ), facts( 3 ), transs( ntran )
210  INTEGER iseed( 4 ), iseedy( 4 )
211  DOUBLE PRECISION rdum( 1 ), result( ntests )
212 * ..
213 * .. External Functions ..
214  LOGICAL lsame
215  DOUBLE PRECISION dget06, dlamch, zlange, zlantr
216  EXTERNAL lsame, dget06, dlamch, zlange, zlantr
217 * ..
218 * .. External Subroutines ..
219  EXTERNAL aladhd, alaerh, alasvm, xlaenv, zerrvx, zgeequ,
222  $ zlatb4, zlatms
223 * ..
224 * .. Intrinsic Functions ..
225  INTRINSIC abs, dcmplx, max
226 * ..
227 * .. Scalars in Common ..
228  LOGICAL lerr, ok
229  CHARACTER*32 srnamt
230  INTEGER infot, nunit
231 * ..
232 * .. Common blocks ..
233  common / infoc / infot, nunit, ok, lerr
234  common / srnamc / srnamt
235 * ..
236 * .. Data statements ..
237  DATA iseedy / 1988, 1989, 1990, 1991 /
238  DATA transs / 'N', 'T', 'C' /
239  DATA facts / 'F', 'N', 'E' /
240  DATA equeds / 'N', 'R', 'C', 'B' /
241 * ..
242 * .. Executable Statements ..
243 *
244 * Initialize constants and the random number seed.
245 *
246  path( 1: 1 ) = 'Zomplex precision'
247  path( 2: 3 ) = 'GE'
248  nrun = 0
249  nfail = 0
250  nerrs = 0
251  DO 10 i = 1, 4
252  iseed( i ) = iseedy( i )
253  10 continue
254 *
255 * Test the error exits
256 *
257  IF( tsterr )
258  $ CALL zerrvx( path, nout )
259  infot = 0
260 *
261 * Set the block size and minimum block size for testing.
262 *
263  nb = 1
264  nbmin = 2
265  CALL xlaenv( 1, nb )
266  CALL xlaenv( 2, nbmin )
267 *
268 * Do for each value of N in NVAL
269 *
270  DO 90 in = 1, nn
271  n = nval( in )
272  lda = max( n, 1 )
273  xtype = 'N'
274  nimat = ntypes
275  IF( n.LE.0 )
276  $ nimat = 1
277 *
278  DO 80 imat = 1, nimat
279 *
280 * Do the tests only if DOTYPE( IMAT ) is true.
281 *
282  IF( .NOT.dotype( imat ) )
283  $ go to 80
284 *
285 * Skip types 5, 6, or 7 if the matrix size is too small.
286 *
287  zerot = imat.GE.5 .AND. imat.LE.7
288  IF( zerot .AND. n.LT.imat-4 )
289  $ go to 80
290 *
291 * Set up parameters with ZLATB4 and generate a test matrix
292 * with ZLATMS.
293 *
294  CALL zlatb4( path, imat, n, n, type, kl, ku, anorm, mode,
295  $ cndnum, dist )
296  rcondc = one / cndnum
297 *
298  srnamt = 'ZLATMS'
299  CALL zlatms( n, n, dist, iseed, type, rwork, mode, cndnum,
300  $ anorm, kl, ku, 'No packing', a, lda, work,
301  $ info )
302 *
303 * Check error code from ZLATMS.
304 *
305  IF( info.NE.0 ) THEN
306  CALL alaerh( path, 'ZLATMS', info, 0, ' ', n, n, -1, -1,
307  $ -1, imat, nfail, nerrs, nout )
308  go to 80
309  END IF
310 *
311 * For types 5-7, zero one or more columns of the matrix to
312 * test that INFO is returned correctly.
313 *
314  IF( zerot ) THEN
315  IF( imat.EQ.5 ) THEN
316  izero = 1
317  ELSE IF( imat.EQ.6 ) THEN
318  izero = n
319  ELSE
320  izero = n / 2 + 1
321  END IF
322  ioff = ( izero-1 )*lda
323  IF( imat.LT.7 ) THEN
324  DO 20 i = 1, n
325  a( ioff+i ) = zero
326  20 continue
327  ELSE
328  CALL zlaset( 'Full', n, n-izero+1, dcmplx( zero ),
329  $ dcmplx( zero ), a( ioff+1 ), lda )
330  END IF
331  ELSE
332  izero = 0
333  END IF
334 *
335 * Save a copy of the matrix A in ASAV.
336 *
337  CALL zlacpy( 'Full', n, n, a, lda, asav, lda )
338 *
339  DO 70 iequed = 1, 4
340  equed = equeds( iequed )
341  IF( iequed.EQ.1 ) THEN
342  nfact = 3
343  ELSE
344  nfact = 1
345  END IF
346 *
347  DO 60 ifact = 1, nfact
348  fact = facts( ifact )
349  prefac = lsame( fact, 'F' )
350  nofact = lsame( fact, 'N' )
351  equil = lsame( fact, 'E' )
352 *
353  IF( zerot ) THEN
354  IF( prefac )
355  $ go to 60
356  rcondo = zero
357  rcondi = zero
358 *
359  ELSE IF( .NOT.nofact ) THEN
360 *
361 * Compute the condition number for comparison with
362 * the value returned by ZGESVX (FACT = 'N' reuses
363 * the condition number from the previous iteration
364 * with FACT = 'F').
365 *
366  CALL zlacpy( 'Full', n, n, asav, lda, afac, lda )
367  IF( equil .OR. iequed.GT.1 ) THEN
368 *
369 * Compute row and column scale factors to
370 * equilibrate the matrix A.
371 *
372  CALL zgeequ( n, n, afac, lda, s, s( n+1 ),
373  $ rowcnd, colcnd, amax, info )
374  IF( info.EQ.0 .AND. n.GT.0 ) THEN
375  IF( lsame( equed, 'R' ) ) THEN
376  rowcnd = zero
377  colcnd = one
378  ELSE IF( lsame( equed, 'C' ) ) THEN
379  rowcnd = one
380  colcnd = zero
381  ELSE IF( lsame( equed, 'B' ) ) THEN
382  rowcnd = zero
383  colcnd = zero
384  END IF
385 *
386 * Equilibrate the matrix.
387 *
388  CALL zlaqge( n, n, afac, lda, s, s( n+1 ),
389  $ rowcnd, colcnd, amax, equed )
390  END IF
391  END IF
392 *
393 * Save the condition number of the non-equilibrated
394 * system for use in ZGET04.
395 *
396  IF( equil ) THEN
397  roldo = rcondo
398  roldi = rcondi
399  END IF
400 *
401 * Compute the 1-norm and infinity-norm of A.
402 *
403  anormo = zlange( '1', n, n, afac, lda, rwork )
404  anormi = zlange( 'I', n, n, afac, lda, rwork )
405 *
406 * Factor the matrix A.
407 *
408  srnamt = 'ZGETRF'
409  CALL zgetrf( n, n, afac, lda, iwork, info )
410 *
411 * Form the inverse of A.
412 *
413  CALL zlacpy( 'Full', n, n, afac, lda, a, lda )
414  lwork = nmax*max( 3, nrhs )
415  srnamt = 'ZGETRI'
416  CALL zgetri( n, a, lda, iwork, work, lwork, info )
417 *
418 * Compute the 1-norm condition number of A.
419 *
420  ainvnm = zlange( '1', n, n, a, lda, rwork )
421  IF( anormo.LE.zero .OR. ainvnm.LE.zero ) THEN
422  rcondo = one
423  ELSE
424  rcondo = ( one / anormo ) / ainvnm
425  END IF
426 *
427 * Compute the infinity-norm condition number of A.
428 *
429  ainvnm = zlange( 'I', n, n, a, lda, rwork )
430  IF( anormi.LE.zero .OR. ainvnm.LE.zero ) THEN
431  rcondi = one
432  ELSE
433  rcondi = ( one / anormi ) / ainvnm
434  END IF
435  END IF
436 *
437  DO 50 itran = 1, ntran
438 *
439 * Do for each value of TRANS.
440 *
441  trans = transs( itran )
442  IF( itran.EQ.1 ) THEN
443  rcondc = rcondo
444  ELSE
445  rcondc = rcondi
446  END IF
447 *
448 * Restore the matrix A.
449 *
450  CALL zlacpy( 'Full', n, n, asav, lda, a, lda )
451 *
452 * Form an exact solution and set the right hand side.
453 *
454  srnamt = 'ZLARHS'
455  CALL zlarhs( path, xtype, 'Full', trans, n, n, kl,
456  $ ku, nrhs, a, lda, xact, lda, b, lda,
457  $ iseed, info )
458  xtype = 'C'
459  CALL zlacpy( 'Full', n, nrhs, b, lda, bsav, lda )
460 *
461  IF( nofact .AND. itran.EQ.1 ) THEN
462 *
463 * --- Test ZGESV ---
464 *
465 * Compute the LU factorization of the matrix and
466 * solve the system.
467 *
468  CALL zlacpy( 'Full', n, n, a, lda, afac, lda )
469  CALL zlacpy( 'Full', n, nrhs, b, lda, x, lda )
470 *
471  srnamt = 'ZGESV '
472  CALL zgesv( n, nrhs, afac, lda, iwork, x, lda,
473  $ info )
474 *
475 * Check error code from ZGESV .
476 *
477  IF( info.NE.izero )
478  $ CALL alaerh( path, 'ZGESV ', info, izero,
479  $ ' ', n, n, -1, -1, nrhs, imat,
480  $ nfail, nerrs, nout )
481 *
482 * Reconstruct matrix from factors and compute
483 * residual.
484 *
485  CALL zget01( n, n, a, lda, afac, lda, iwork,
486  $ rwork, result( 1 ) )
487  nt = 1
488  IF( izero.EQ.0 ) THEN
489 *
490 * Compute residual of the computed solution.
491 *
492  CALL zlacpy( 'Full', n, nrhs, b, lda, work,
493  $ lda )
494  CALL zget02( 'No transpose', n, n, nrhs, a,
495  $ lda, x, lda, work, lda, rwork,
496  $ result( 2 ) )
497 *
498 * Check solution from generated exact solution.
499 *
500  CALL zget04( n, nrhs, x, lda, xact, lda,
501  $ rcondc, result( 3 ) )
502  nt = 3
503  END IF
504 *
505 * Print information about the tests that did not
506 * pass the threshold.
507 *
508  DO 30 k = 1, nt
509  IF( result( k ).GE.thresh ) THEN
510  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
511  $ CALL aladhd( nout, path )
512  WRITE( nout, fmt = 9999 )'ZGESV ', n,
513  $ imat, k, result( k )
514  nfail = nfail + 1
515  END IF
516  30 continue
517  nrun = nrun + nt
518  END IF
519 *
520 * --- Test ZGESVX ---
521 *
522  IF( .NOT.prefac )
523  $ CALL zlaset( 'Full', n, n, dcmplx( zero ),
524  $ dcmplx( zero ), afac, lda )
525  CALL zlaset( 'Full', n, nrhs, dcmplx( zero ),
526  $ dcmplx( zero ), x, lda )
527  IF( iequed.GT.1 .AND. n.GT.0 ) THEN
528 *
529 * Equilibrate the matrix if FACT = 'F' and
530 * EQUED = 'R', 'C', or 'B'.
531 *
532  CALL zlaqge( n, n, a, lda, s, s( n+1 ), rowcnd,
533  $ colcnd, amax, equed )
534  END IF
535 *
536 * Solve the system and compute the condition number
537 * and error bounds using ZGESVX.
538 *
539  srnamt = 'ZGESVX'
540  CALL zgesvx( fact, trans, n, nrhs, a, lda, afac,
541  $ lda, iwork, equed, s, s( n+1 ), b,
542  $ lda, x, lda, rcond, rwork,
543  $ rwork( nrhs+1 ), work,
544  $ rwork( 2*nrhs+1 ), info )
545 *
546 * Check the error code from ZGESVX.
547 *
548  IF( info.NE.izero )
549  $ CALL alaerh( path, 'ZGESVX', info, izero,
550  $ fact // trans, n, n, -1, -1, nrhs,
551  $ imat, nfail, nerrs, nout )
552 *
553 * Compare RWORK(2*NRHS+1) from ZGESVX with the
554 * computed reciprocal pivot growth factor RPVGRW
555 *
556  IF( info.NE.0 .AND. info.LE.n) THEN
557  rpvgrw = zlantr( 'M', 'U', 'N', info, info,
558  $ afac, lda, rdum )
559  IF( rpvgrw.EQ.zero ) THEN
560  rpvgrw = one
561  ELSE
562  rpvgrw = zlange( 'M', n, info, a, lda,
563  $ rdum ) / rpvgrw
564  END IF
565  ELSE
566  rpvgrw = zlantr( 'M', 'U', 'N', n, n, afac, lda,
567  $ rdum )
568  IF( rpvgrw.EQ.zero ) THEN
569  rpvgrw = one
570  ELSE
571  rpvgrw = zlange( 'M', n, n, a, lda, rdum ) /
572  $ rpvgrw
573  END IF
574  END IF
575  result( 7 ) = abs( rpvgrw-rwork( 2*nrhs+1 ) ) /
576  $ max( rwork( 2*nrhs+1 ), rpvgrw ) /
577  $ dlamch( 'E' )
578 *
579  IF( .NOT.prefac ) THEN
580 *
581 * Reconstruct matrix from factors and compute
582 * residual.
583 *
584  CALL zget01( n, n, a, lda, afac, lda, iwork,
585  $ rwork( 2*nrhs+1 ), result( 1 ) )
586  k1 = 1
587  ELSE
588  k1 = 2
589  END IF
590 *
591  IF( info.EQ.0 ) THEN
592  trfcon = .false.
593 *
594 * Compute residual of the computed solution.
595 *
596  CALL zlacpy( 'Full', n, nrhs, bsav, lda, work,
597  $ lda )
598  CALL zget02( trans, n, n, nrhs, asav, lda, x,
599  $ lda, work, lda, rwork( 2*nrhs+1 ),
600  $ result( 2 ) )
601 *
602 * Check solution from generated exact solution.
603 *
604  IF( nofact .OR. ( prefac .AND. lsame( equed,
605  $ 'N' ) ) ) THEN
606  CALL zget04( n, nrhs, x, lda, xact, lda,
607  $ rcondc, result( 3 ) )
608  ELSE
609  IF( itran.EQ.1 ) THEN
610  roldc = roldo
611  ELSE
612  roldc = roldi
613  END IF
614  CALL zget04( n, nrhs, x, lda, xact, lda,
615  $ roldc, result( 3 ) )
616  END IF
617 *
618 * Check the error bounds from iterative
619 * refinement.
620 *
621  CALL zget07( trans, n, nrhs, asav, lda, b, lda,
622  $ x, lda, xact, lda, rwork, .true.,
623  $ rwork( nrhs+1 ), result( 4 ) )
624  ELSE
625  trfcon = .true.
626  END IF
627 *
628 * Compare RCOND from ZGESVX with the computed value
629 * in RCONDC.
630 *
631  result( 6 ) = dget06( rcond, rcondc )
632 *
633 * Print information about the tests that did not pass
634 * the threshold.
635 *
636  IF( .NOT.trfcon ) THEN
637  DO 40 k = k1, ntests
638  IF( result( k ).GE.thresh ) THEN
639  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
640  $ CALL aladhd( nout, path )
641  IF( prefac ) THEN
642  WRITE( nout, fmt = 9997 )'ZGESVX',
643  $ fact, trans, n, equed, imat, k,
644  $ result( k )
645  ELSE
646  WRITE( nout, fmt = 9998 )'ZGESVX',
647  $ fact, trans, n, imat, k, result( k )
648  END IF
649  nfail = nfail + 1
650  END IF
651  40 continue
652  nrun = nrun + 7 - k1
653  ELSE
654  IF( result( 1 ).GE.thresh .AND. .NOT.prefac )
655  $ THEN
656  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
657  $ CALL aladhd( nout, path )
658  IF( prefac ) THEN
659  WRITE( nout, fmt = 9997 )'ZGESVX', fact,
660  $ trans, n, equed, imat, 1, result( 1 )
661  ELSE
662  WRITE( nout, fmt = 9998 )'ZGESVX', fact,
663  $ trans, n, imat, 1, result( 1 )
664  END IF
665  nfail = nfail + 1
666  nrun = nrun + 1
667  END IF
668  IF( result( 6 ).GE.thresh ) THEN
669  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
670  $ CALL aladhd( nout, path )
671  IF( prefac ) THEN
672  WRITE( nout, fmt = 9997 )'ZGESVX', fact,
673  $ trans, n, equed, imat, 6, result( 6 )
674  ELSE
675  WRITE( nout, fmt = 9998 )'ZGESVX', fact,
676  $ trans, n, imat, 6, result( 6 )
677  END IF
678  nfail = nfail + 1
679  nrun = nrun + 1
680  END IF
681  IF( result( 7 ).GE.thresh ) THEN
682  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
683  $ CALL aladhd( nout, path )
684  IF( prefac ) THEN
685  WRITE( nout, fmt = 9997 )'ZGESVX', fact,
686  $ trans, n, equed, imat, 7, result( 7 )
687  ELSE
688  WRITE( nout, fmt = 9998 )'ZGESVX', fact,
689  $ trans, n, imat, 7, result( 7 )
690  END IF
691  nfail = nfail + 1
692  nrun = nrun + 1
693  END IF
694 *
695  END IF
696 *
697  50 continue
698  60 continue
699  70 continue
700  80 continue
701  90 continue
702 *
703 * Print a summary of the results.
704 *
705  CALL alasvm( path, nout, nfail, nrun, nerrs )
706 *
707  9999 format( 1x, a, ', N =', i5, ', type ', i2, ', test(', i2, ') =',
708  $ g12.5 )
709  9998 format( 1x, a, ', FACT=''', a1, ''', TRANS=''', a1, ''', N=', i5,
710  $ ', type ', i2, ', test(', i1, ')=', g12.5 )
711  9997 format( 1x, a, ', FACT=''', a1, ''', TRANS=''', a1, ''', N=', i5,
712  $ ', EQUED=''', a1, ''', type ', i2, ', test(', i1, ')=',
713  $ g12.5 )
714  return
715 *
716 * End of ZDRVGE
717 *
718  END