LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine dchksy ( logical, dimension( * )  DOTYPE,
integer  NN,
integer, dimension( * )  NVAL,
integer  NNB,
integer, dimension( * )  NBVAL,
integer  NNS,
integer, dimension( * )  NSVAL,
double precision  THRESH,
logical  TSTERR,
integer  NMAX,
double precision, dimension( * )  A,
double precision, dimension( * )  AFAC,
double precision, dimension( * )  AINV,
double precision, dimension( * )  B,
double precision, dimension( * )  X,
double precision, dimension( * )  XACT,
double precision, dimension( * )  WORK,
double precision, dimension( * )  RWORK,
integer, dimension( * )  IWORK,
integer  NOUT 
)

DCHKSY

Purpose:
 DCHKSY tests DSYTRF, -TRI2, -TRS, -TRS2, -RFS, and -CON.
Parameters
[in]DOTYPE
          DOTYPE is LOGICAL array, dimension (NTYPES)
          The matrix types to be used for testing.  Matrices of type j
          (for 1 <= j <= NTYPES) are used for testing if DOTYPE(j) =
          .TRUE.; if DOTYPE(j) = .FALSE., then type j is not used.
[in]NN
          NN is INTEGER
          The number of values of N contained in the vector NVAL.
[in]NVAL
          NVAL is INTEGER array, dimension (NN)
          The values of the matrix dimension N.
[in]NNB
          NNB is INTEGER
          The number of values of NB contained in the vector NBVAL.
[in]NBVAL
          NBVAL is INTEGER array, dimension (NBVAL)
          The values of the blocksize NB.
[in]NNS
          NNS is INTEGER
          The number of values of NRHS contained in the vector NSVAL.
[in]NSVAL
          NSVAL is INTEGER array, dimension (NNS)
          The values of the number of right hand sides NRHS.
[in]THRESH
          THRESH is DOUBLE PRECISION
          The threshold value for the test ratios.  A result is
          included in the output file if RESULT >= THRESH.  To have
          every test ratio printed, use THRESH = 0.
[in]TSTERR
          TSTERR is LOGICAL
          Flag that indicates whether error exits are to be tested.
[in]NMAX
          NMAX is INTEGER
          The maximum value permitted for N, used in dimensioning the
          work arrays.
[out]A
          A is DOUBLE PRECISION array, dimension (NMAX*NMAX)
[out]AFAC
          AFAC is DOUBLE PRECISION array, dimension (NMAX*NMAX)
[out]AINV
          AINV is DOUBLE PRECISION array, dimension (NMAX*NMAX)
[out]B
          B is DOUBLE PRECISION array, dimension (NMAX*NSMAX)
          where NSMAX is the largest entry in NSVAL.
[out]X
          X is DOUBLE PRECISION array, dimension (NMAX*NSMAX)
[out]XACT
          XACT is DOUBLE PRECISION array, dimension (NMAX*NSMAX)
[out]WORK
          WORK is DOUBLE PRECISION array, dimension (NMAX*max(3,NSMAX))
[out]RWORK
          RWORK is DOUBLE PRECISION array, dimension (max(NMAX,2*NSMAX))
[out]IWORK
          IWORK is INTEGER array, dimension (2*NMAX)
[in]NOUT
          NOUT is INTEGER
          The unit number for output.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2013

Definition at line 172 of file dchksy.f.

172 *
173 * -- LAPACK test routine (version 3.5.0) --
174 * -- LAPACK is a software package provided by Univ. of Tennessee, --
175 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
176 * November 2013
177 *
178 * .. Scalar Arguments ..
179  LOGICAL tsterr
180  INTEGER nmax, nn, nnb, nns, nout
181  DOUBLE PRECISION thresh
182 * ..
183 * .. Array Arguments ..
184  LOGICAL dotype( * )
185  INTEGER iwork( * ), nbval( * ), nsval( * ), nval( * )
186  DOUBLE PRECISION a( * ), afac( * ), ainv( * ), b( * ),
187  $ rwork( * ), work( * ), x( * ), xact( * )
188 * ..
189 *
190 * =====================================================================
191 *
192 * .. Parameters ..
193  DOUBLE PRECISION zero
194  parameter ( zero = 0.0d+0 )
195  INTEGER ntypes
196  parameter ( ntypes = 10 )
197  INTEGER ntests
198  parameter ( ntests = 9 )
199 * ..
200 * .. Local Scalars ..
201  LOGICAL trfcon, zerot
202  CHARACTER dist, TYPE, uplo, xtype
203  CHARACTER*3 path
204  INTEGER i, i1, i2, imat, in, inb, info, ioff, irhs,
205  $ iuplo, izero, j, k, kl, ku, lda, lwork, mode,
206  $ n, nb, nerrs, nfail, nimat, nrhs, nrun, nt
207  DOUBLE PRECISION anorm, cndnum, rcond, rcondc
208 * ..
209 * .. Local Arrays ..
210  CHARACTER uplos( 2 )
211  INTEGER iseed( 4 ), iseedy( 4 )
212  DOUBLE PRECISION result( ntests )
213 * ..
214 * .. External Functions ..
215  DOUBLE PRECISION dget06, dlansy
216  EXTERNAL dget06, dlansy
217 * ..
218 * .. External Subroutines ..
219  EXTERNAL alaerh, alahd, alasum, derrsy, dget04, dlacpy,
221  $ dsycon, dsyrfs, dsyt01, dsytrf,
223 * ..
224 * .. Intrinsic Functions ..
225  INTRINSIC max, min
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 uplos / 'U', 'L' /
239 * ..
240 * .. Executable Statements ..
241 *
242 * Initialize constants and the random number seed.
243 *
244  path( 1: 1 ) = 'Double precision'
245  path( 2: 3 ) = 'SY'
246  nrun = 0
247  nfail = 0
248  nerrs = 0
249  DO 10 i = 1, 4
250  iseed( i ) = iseedy( i )
251  10 CONTINUE
252 *
253 * Test the error exits
254 *
255  IF( tsterr )
256  $ CALL derrsy( path, nout )
257  infot = 0
258 *
259 * Set the minimum block size for which the block routine should
260 * be used, which will be later returned by ILAENV
261 *
262  CALL xlaenv( 2, 2 )
263 *
264 * Do for each value of N in NVAL
265 *
266  DO 180 in = 1, nn
267  n = nval( in )
268  lda = max( n, 1 )
269  xtype = 'N'
270  nimat = ntypes
271  IF( n.LE.0 )
272  $ nimat = 1
273 *
274  izero = 0
275 *
276 * Do for each value of matrix type IMAT
277 *
278  DO 170 imat = 1, nimat
279 *
280 * Do the tests only if DOTYPE( IMAT ) is true.
281 *
282  IF( .NOT.dotype( imat ) )
283  $ GO TO 170
284 *
285 * Skip types 3, 4, 5, or 6 if the matrix size is too small.
286 *
287  zerot = imat.GE.3 .AND. imat.LE.6
288  IF( zerot .AND. n.LT.imat-2 )
289  $ GO TO 170
290 *
291 * Do first for UPLO = 'U', then for UPLO = 'L'
292 *
293  DO 160 iuplo = 1, 2
294  uplo = uplos( iuplo )
295 *
296 * Begin generate the test matrix A.
297 *
298 *
299 * Set up parameters with DLATB4 for the matrix generator
300 * based on the type of matrix to be generated.
301 *
302  CALL dlatb4( path, imat, n, n, TYPE, kl, ku, anorm, mode,
303  $ cndnum, dist )
304 *
305 * Generate a matrix with DLATMS.
306 *
307  srnamt = 'DLATMS'
308  CALL dlatms( n, n, dist, iseed, TYPE, rwork, mode,
309  $ cndnum, anorm, kl, ku, uplo, a, lda, work,
310  $ info )
311 *
312 * Check error code from DLATMS and handle error.
313 *
314  IF( info.NE.0 ) THEN
315  CALL alaerh( path, 'DLATMS', info, 0, uplo, n, n, -1,
316  $ -1, -1, imat, nfail, nerrs, nout )
317 *
318 * Skip all tests for this generated matrix
319 *
320  GO TO 160
321  END IF
322 *
323 * For matrix types 3-6, zero one or more rows and
324 * columns of the matrix to test that INFO is returned
325 * correctly.
326 *
327  IF( zerot ) THEN
328  IF( imat.EQ.3 ) THEN
329  izero = 1
330  ELSE IF( imat.EQ.4 ) THEN
331  izero = n
332  ELSE
333  izero = n / 2 + 1
334  END IF
335 *
336  IF( imat.LT.6 ) THEN
337 *
338 * Set row and column IZERO to zero.
339 *
340  IF( iuplo.EQ.1 ) THEN
341  ioff = ( izero-1 )*lda
342  DO 20 i = 1, izero - 1
343  a( ioff+i ) = zero
344  20 CONTINUE
345  ioff = ioff + izero
346  DO 30 i = izero, n
347  a( ioff ) = zero
348  ioff = ioff + lda
349  30 CONTINUE
350  ELSE
351  ioff = izero
352  DO 40 i = 1, izero - 1
353  a( ioff ) = zero
354  ioff = ioff + lda
355  40 CONTINUE
356  ioff = ioff - izero
357  DO 50 i = izero, n
358  a( ioff+i ) = zero
359  50 CONTINUE
360  END IF
361  ELSE
362  IF( iuplo.EQ.1 ) THEN
363 *
364 * Set the first IZERO rows and columns to zero.
365 *
366  ioff = 0
367  DO 70 j = 1, n
368  i2 = min( j, izero )
369  DO 60 i = 1, i2
370  a( ioff+i ) = zero
371  60 CONTINUE
372  ioff = ioff + lda
373  70 CONTINUE
374  ELSE
375 *
376 * Set the last IZERO rows and columns to zero.
377 *
378  ioff = 0
379  DO 90 j = 1, n
380  i1 = max( j, izero )
381  DO 80 i = i1, n
382  a( ioff+i ) = zero
383  80 CONTINUE
384  ioff = ioff + lda
385  90 CONTINUE
386  END IF
387  END IF
388  ELSE
389  izero = 0
390  END IF
391 *
392 * End generate the test matrix A.
393 *
394 * Do for each value of NB in NBVAL
395 *
396  DO 150 inb = 1, nnb
397 *
398 * Set the optimal blocksize, which will be later
399 * returned by ILAENV.
400 *
401  nb = nbval( inb )
402  CALL xlaenv( 1, nb )
403 *
404 * Copy the test matrix A into matrix AFAC which
405 * will be factorized in place. This is needed to
406 * preserve the test matrix A for subsequent tests.
407 *
408  CALL dlacpy( uplo, n, n, a, lda, afac, lda )
409 *
410 * Compute the L*D*L**T or U*D*U**T factorization of the
411 * matrix. IWORK stores details of the interchanges and
412 * the block structure of D. AINV is a work array for
413 * block factorization, LWORK is the length of AINV.
414 *
415  lwork = max( 2, nb )*lda
416  srnamt = 'DSYTRF'
417  CALL dsytrf( uplo, n, afac, lda, iwork, ainv, lwork,
418  $ info )
419 *
420 * Adjust the expected value of INFO to account for
421 * pivoting.
422 *
423  k = izero
424  IF( k.GT.0 ) THEN
425  100 CONTINUE
426  IF( iwork( k ).LT.0 ) THEN
427  IF( iwork( k ).NE.-k ) THEN
428  k = -iwork( k )
429  GO TO 100
430  END IF
431  ELSE IF( iwork( k ).NE.k ) THEN
432  k = iwork( k )
433  GO TO 100
434  END IF
435  END IF
436 *
437 * Check error code from DSYTRF and handle error.
438 *
439  IF( info.NE.k )
440  $ CALL alaerh( path, 'DSYTRF', info, k, uplo, n, n,
441  $ -1, -1, nb, imat, nfail, nerrs, nout )
442 *
443 * Set the condition estimate flag if the INFO is not 0.
444 *
445  IF( info.NE.0 ) THEN
446  trfcon = .true.
447  ELSE
448  trfcon = .false.
449  END IF
450 *
451 *+ TEST 1
452 * Reconstruct matrix from factors and compute residual.
453 *
454  CALL dsyt01( uplo, n, a, lda, afac, lda, iwork, ainv,
455  $ lda, rwork, result( 1 ) )
456  nt = 1
457 *
458 *+ TEST 2
459 * Form the inverse and compute the residual,
460 * if the factorization was competed without INFO > 0
461 * (i.e. there is no zero rows and columns).
462 * Do it only for the first block size.
463 *
464  IF( inb.EQ.1 .AND. .NOT.trfcon ) THEN
465  CALL dlacpy( uplo, n, n, afac, lda, ainv, lda )
466  srnamt = 'DSYTRI2'
467  lwork = (n+nb+1)*(nb+3)
468  CALL dsytri2( uplo, n, ainv, lda, iwork, work,
469  $ lwork, info )
470 *
471 * Check error code from DSYTRI2 and handle error.
472 *
473  IF( info.NE.0 )
474  $ CALL alaerh( path, 'DSYTRI2', info, -1, uplo, n,
475  $ n, -1, -1, -1, imat, nfail, nerrs,
476  $ nout )
477 *
478 * Compute the residual for a symmetric matrix times
479 * its inverse.
480 *
481  CALL dpot03( uplo, n, a, lda, ainv, lda, work, lda,
482  $ rwork, rcondc, result( 2 ) )
483  nt = 2
484  END IF
485 *
486 * Print information about the tests that did not pass
487 * the threshold.
488 *
489  DO 110 k = 1, nt
490  IF( result( k ).GE.thresh ) THEN
491  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
492  $ CALL alahd( nout, path )
493  WRITE( nout, fmt = 9999 )uplo, n, nb, imat, k,
494  $ result( k )
495  nfail = nfail + 1
496  END IF
497  110 CONTINUE
498  nrun = nrun + nt
499 *
500 * Skip the other tests if this is not the first block
501 * size.
502 *
503  IF( inb.GT.1 )
504  $ GO TO 150
505 *
506 * Do only the condition estimate if INFO is not 0.
507 *
508  IF( trfcon ) THEN
509  rcondc = zero
510  GO TO 140
511  END IF
512 *
513 * Do for each value of NRHS in NSVAL.
514 *
515  DO 130 irhs = 1, nns
516  nrhs = nsval( irhs )
517 *
518 *+ TEST 3 ( Using TRS)
519 * Solve and compute residual for A * X = B.
520 *
521 * Choose a set of NRHS random solution vectors
522 * stored in XACT and set up the right hand side B
523 *
524  srnamt = 'DLARHS'
525  CALL dlarhs( path, xtype, uplo, ' ', n, n, kl, ku,
526  $ nrhs, a, lda, xact, lda, b, lda,
527  $ iseed, info )
528  CALL dlacpy( 'Full', n, nrhs, b, lda, x, lda )
529 *
530  srnamt = 'DSYTRS'
531  CALL dsytrs( uplo, n, nrhs, afac, lda, iwork, x,
532  $ lda, info )
533 *
534 * Check error code from DSYTRS and handle error.
535 *
536  IF( info.NE.0 )
537  $ CALL alaerh( path, 'DSYTRS', info, 0, uplo, n,
538  $ n, -1, -1, nrhs, imat, nfail,
539  $ nerrs, nout )
540 *
541  CALL dlacpy( 'Full', n, nrhs, b, lda, work, lda )
542 *
543 * Compute the residual for the solution
544 *
545  CALL dpot02( uplo, n, nrhs, a, lda, x, lda, work,
546  $ lda, rwork, result( 3 ) )
547 *
548 *+ TEST 4 (Using TRS2)
549 *
550 * Solve and compute residual for A * X = B.
551 *
552 * Choose a set of NRHS random solution vectors
553 * stored in XACT and set up the right hand side B
554 *
555  srnamt = 'DLARHS'
556  CALL dlarhs( path, xtype, uplo, ' ', n, n, kl, ku,
557  $ nrhs, a, lda, xact, lda, b, lda,
558  $ iseed, info )
559  CALL dlacpy( 'Full', n, nrhs, b, lda, x, lda )
560 *
561  srnamt = 'DSYTRS2'
562  CALL dsytrs2( uplo, n, nrhs, afac, lda, iwork, x,
563  $ lda, work, info )
564 *
565 * Check error code from DSYTRS2 and handle error.
566 *
567  IF( info.NE.0 )
568  $ CALL alaerh( path, 'DSYTRS2', info, 0, uplo, n,
569  $ n, -1, -1, nrhs, imat, nfail,
570  $ nerrs, nout )
571 *
572  CALL dlacpy( 'Full', n, nrhs, b, lda, work, lda )
573 *
574 * Compute the residual for the solution
575 *
576  CALL dpot02( uplo, n, nrhs, a, lda, x, lda, work,
577  $ lda, rwork, result( 4 ) )
578 *
579 *+ TEST 5
580 * Check solution from generated exact solution.
581 *
582  CALL dget04( n, nrhs, x, lda, xact, lda, rcondc,
583  $ result( 5 ) )
584 *
585 *+ TESTS 6, 7, and 8
586 * Use iterative refinement to improve the solution.
587 *
588  srnamt = 'DSYRFS'
589  CALL dsyrfs( uplo, n, nrhs, a, lda, afac, lda,
590  $ iwork, b, lda, x, lda, rwork,
591  $ rwork( nrhs+1 ), work, iwork( n+1 ),
592  $ info )
593 *
594 * Check error code from DSYRFS and handle error.
595 *
596  IF( info.NE.0 )
597  $ CALL alaerh( path, 'DSYRFS', info, 0, uplo, n,
598  $ n, -1, -1, nrhs, imat, nfail,
599  $ nerrs, nout )
600 *
601  CALL dget04( n, nrhs, x, lda, xact, lda, rcondc,
602  $ result( 6 ) )
603  CALL dpot05( uplo, n, nrhs, a, lda, b, lda, x, lda,
604  $ xact, lda, rwork, rwork( nrhs+1 ),
605  $ result( 7 ) )
606 *
607 * Print information about the tests that did not pass
608 * the threshold.
609 *
610  DO 120 k = 3, 8
611  IF( result( k ).GE.thresh ) THEN
612  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
613  $ CALL alahd( nout, path )
614  WRITE( nout, fmt = 9998 )uplo, n, nrhs,
615  $ imat, k, result( k )
616  nfail = nfail + 1
617  END IF
618  120 CONTINUE
619  nrun = nrun + 6
620 *
621 * End do for each value of NRHS in NSVAL.
622 *
623  130 CONTINUE
624 *
625 *+ TEST 9
626 * Get an estimate of RCOND = 1/CNDNUM.
627 *
628  140 CONTINUE
629  anorm = dlansy( '1', uplo, n, a, lda, rwork )
630  srnamt = 'DSYCON'
631  CALL dsycon( uplo, n, afac, lda, iwork, anorm, rcond,
632  $ work, iwork( n+1 ), info )
633 *
634 * Check error code from DSYCON and handle error.
635 *
636  IF( info.NE.0 )
637  $ CALL alaerh( path, 'DSYCON', info, 0, uplo, n, n,
638  $ -1, -1, -1, imat, nfail, nerrs, nout )
639 *
640 * Compute the test ratio to compare values of RCOND
641 *
642  result( 9 ) = dget06( rcond, rcondc )
643 *
644 * Print information about the tests that did not pass
645 * the threshold.
646 *
647  IF( result( 9 ).GE.thresh ) THEN
648  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
649  $ CALL alahd( nout, path )
650  WRITE( nout, fmt = 9997 )uplo, n, imat, 9,
651  $ result( 9 )
652  nfail = nfail + 1
653  END IF
654  nrun = nrun + 1
655  150 CONTINUE
656 *
657  160 CONTINUE
658  170 CONTINUE
659  180 CONTINUE
660 *
661 * Print a summary of the results.
662 *
663  CALL alasum( path, nout, nfail, nrun, nerrs )
664 *
665  9999 FORMAT( ' UPLO = ''', a1, ''', N =', i5, ', NB =', i4, ', type ',
666  $ i2, ', test ', i2, ', ratio =', g12.5 )
667  9998 FORMAT( ' UPLO = ''', a1, ''', N =', i5, ', NRHS=', i3, ', type ',
668  $ i2, ', test(', i2, ') =', g12.5 )
669  9997 FORMAT( ' UPLO = ''', a1, ''', N =', i5, ',', 10x, ' type ', i2,
670  $ ', test(', i2, ') =', g12.5 )
671  RETURN
672 *
673 * End of DCHKSY
674 *
subroutine alahd(IOUNIT, PATH)
ALAHD
Definition: alahd.f:95
double precision function dlansy(NORM, UPLO, N, A, LDA, WORK)
DLANSY returns the value of the 1-norm, or the Frobenius norm, or the infinity norm, or the element of largest absolute value of a real symmetric matrix.
Definition: dlansy.f:124
subroutine alaerh(PATH, SUBNAM, INFO, INFOE, OPTS, M, N, KL, KU, N5, IMAT, NFAIL, NERRS, NOUT)
ALAERH
Definition: alaerh.f:149
subroutine dlarhs(PATH, XTYPE, UPLO, TRANS, M, N, KL, KU, NRHS, A, LDA, X, LDX, B, LDB, ISEED, INFO)
DLARHS
Definition: dlarhs.f:206
subroutine dsyrfs(UPLO, N, NRHS, A, LDA, AF, LDAF, IPIV, B, LDB, X, LDX, FERR, BERR, WORK, IWORK, INFO)
DSYRFS
Definition: dsyrfs.f:193
subroutine dsytri2(UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
DSYTRI2
Definition: dsytri2.f:129
subroutine dlacpy(UPLO, M, N, A, LDA, B, LDB)
DLACPY copies all or part of one two-dimensional array to another.
Definition: dlacpy.f:105
subroutine dsycon(UPLO, N, A, LDA, IPIV, ANORM, RCOND, WORK, IWORK, INFO)
DSYCON
Definition: dsycon.f:132
subroutine xlaenv(ISPEC, NVALUE)
XLAENV
Definition: xlaenv.f:83
subroutine dpot03(UPLO, N, A, LDA, AINV, LDAINV, WORK, LDWORK, RWORK, RCOND, RESID)
DPOT03
Definition: dpot03.f:127
subroutine dsyt01(UPLO, N, A, LDA, AFAC, LDAFAC, IPIV, C, LDC, RWORK, RESID)
DSYT01
Definition: dsyt01.f:126
subroutine dlatb4(PATH, IMAT, M, N, TYPE, KL, KU, ANORM, MODE, CNDNUM, DIST)
DLATB4
Definition: dlatb4.f:122
subroutine dget04(N, NRHS, X, LDX, XACT, LDXACT, RCOND, RESID)
DGET04
Definition: dget04.f:104
subroutine dsytrs(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO)
DSYTRS
Definition: dsytrs.f:122
subroutine dsytrf(UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
DSYTRF
Definition: dsytrf.f:184
subroutine derrsy(PATH, NUNIT)
DERRSY
Definition: derrsy.f:57
double precision function dget06(RCOND, RCONDC)
DGET06
Definition: dget06.f:57
subroutine dsytrs2(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, INFO)
DSYTRS2
Definition: dsytrs2.f:134
subroutine dpot05(UPLO, N, NRHS, A, LDA, B, LDB, X, LDX, XACT, LDXACT, FERR, BERR, RESLTS)
DPOT05
Definition: dpot05.f:166
subroutine dlatms(M, N, DIST, ISEED, SYM, D, MODE, COND, DMAX, KL, KU, PACK, A, LDA, WORK, INFO)
DLATMS
Definition: dlatms.f:323
subroutine dpot02(UPLO, N, NRHS, A, LDA, X, LDX, B, LDB, RWORK, RESID)
DPOT02
Definition: dpot02.f:129
subroutine alasum(TYPE, NOUT, NFAIL, NRUN, NERRS)
ALASUM
Definition: alasum.f:75

Here is the call graph for this function:

Here is the caller graph for this function: