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