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