LAPACK 3.3.0

cdrvsyx.f

Go to the documentation of this file.
00001       SUBROUTINE CDRVSY( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX,
00002      $                   A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK,
00003      $                   NOUT )
00004 *
00005 *  -- LAPACK test routine (version 3.2) --
00006 *     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
00007 *     November 2006
00008 *
00009 *     .. Scalar Arguments ..
00010       LOGICAL            TSTERR
00011       INTEGER            NMAX, NN, NOUT, NRHS
00012       REAL               THRESH
00013 *     ..
00014 *     .. Array Arguments ..
00015       LOGICAL            DOTYPE( * )
00016       INTEGER            IWORK( * ), NVAL( * )
00017       REAL               RWORK( * )
00018       COMPLEX            A( * ), AFAC( * ), AINV( * ), B( * ),
00019      $                   WORK( * ), X( * ), XACT( * )
00020 *     ..
00021 *
00022 *  Purpose
00023 *  =======
00024 *
00025 *  CDRVSY tests the driver routines CSYSV, -SVX, and -SVXX.
00026 *
00027 *  Note that this file is used only when the XBLAS are available,
00028 *  otherwise cdrvsy.f defines this subroutine.
00029 *
00030 *  Arguments
00031 *  =========
00032 *
00033 *  DOTYPE  (input) LOGICAL array, dimension (NTYPES)
00034 *          The matrix types to be used for testing.  Matrices of type j
00035 *          (for 1 <= j <= NTYPES) are used for testing if DOTYPE(j) =
00036 *          .TRUE.; if DOTYPE(j) = .FALSE., then type j is not used.
00037 *
00038 *  NN      (input) INTEGER
00039 *          The number of values of N contained in the vector NVAL.
00040 *
00041 *  NVAL    (input) INTEGER array, dimension (NN)
00042 *          The values of the matrix dimension N.
00043 *
00044 *  NRHS    (input) INTEGER
00045 *          The number of right hand side vectors to be generated for
00046 *          each linear system.
00047 *
00048 *  THRESH  (input) REAL
00049 *          The threshold value for the test ratios.  A result is
00050 *          included in the output file if RESULT >= THRESH.  To have
00051 *          every test ratio printed, use THRESH = 0.
00052 *
00053 *  TSTERR  (input) LOGICAL
00054 *          Flag that indicates whether error exits are to be tested.
00055 *
00056 *  NMAX    (input) INTEGER
00057 *          The maximum value permitted for N, used in dimensioning the
00058 *          work arrays.
00059 *
00060 *  A       (workspace) COMPLEX array, dimension (NMAX*NMAX)
00061 *
00062 *  AFAC    (workspace) COMPLEX array, dimension (NMAX*NMAX)
00063 *
00064 *  AINV    (workspace) COMPLEX array, dimension (NMAX*NMAX)
00065 *
00066 *  B       (workspace) COMPLEX array, dimension (NMAX*NRHS)
00067 *
00068 *  X       (workspace) COMPLEX array, dimension (NMAX*NRHS)
00069 *
00070 *  XACT    (workspace) COMPLEX array, dimension (NMAX*NRHS)
00071 *
00072 *  WORK    (workspace) COMPLEX array, dimension
00073 *                      (NMAX*max(2,NRHS))
00074 *
00075 *  RWORK   (workspace) REAL array, dimension (NMAX+2*NRHS)
00076 *
00077 *  IWORK   (workspace) INTEGER array, dimension (NMAX)
00078 *
00079 *  NOUT    (input) INTEGER
00080 *          The unit number for output.
00081 *
00082 *  =====================================================================
00083 *
00084 *     .. Parameters ..
00085       REAL               ONE, ZERO
00086       PARAMETER          ( ONE = 1.0E+0, ZERO = 0.0E+0 )
00087       INTEGER            NTYPES, NTESTS
00088       PARAMETER          ( NTYPES = 11, NTESTS = 6 )
00089       INTEGER            NFACT
00090       PARAMETER          ( NFACT = 2 )
00091 *     ..
00092 *     .. Local Scalars ..
00093       LOGICAL            ZEROT
00094       CHARACTER          DIST, EQUED, FACT, TYPE, UPLO, XTYPE
00095       CHARACTER*3        PATH
00096       INTEGER            I, I1, I2, IFACT, IMAT, IN, INFO, IOFF, IUPLO,
00097      $                   IZERO, J, K, K1, KL, KU, LDA, LWORK, MODE, N,
00098      $                   NB, NBMIN, NERRS, NFAIL, NIMAT, NRUN, NT,
00099      $                   N_ERR_BNDS
00100       REAL               AINVNM, ANORM, CNDNUM, RCOND, RCONDC,
00101      $                   RPVGRW_SVXX
00102 *     ..
00103 *     .. Local Arrays ..
00104       CHARACTER          FACTS( NFACT ), UPLOS( 2 )
00105       INTEGER            ISEED( 4 ), ISEEDY( 4 )
00106       REAL               RESULT( NTESTS ), BERR( NRHS ),
00107      $                   ERRBNDS_N( NRHS, 3 ), ERRBNDS_C( NRHS, 3 )
00108 *     ..
00109 *     .. External Functions ..
00110       REAL               CLANSY, SGET06
00111       EXTERNAL           CLANSY, SGET06
00112 *     ..
00113 *     .. External Subroutines ..
00114       EXTERNAL           ALADHD, ALAERH, ALASVM, CERRVX, CGET04, CLACPY,
00115      $                   CLARHS, CLASET, CLATB4, CLATMS, CLATSY, CPOT05,
00116      $                   CSYSV, CSYSVX, CSYT01, CSYT02, CSYTRF, CSYTRI2,
00117      $                   XLAENV, CSYSVXX
00118 *     ..
00119 *     .. Scalars in Common ..
00120       LOGICAL            LERR, OK
00121       CHARACTER*32       SRNAMT
00122       INTEGER            INFOT, NUNIT
00123 *     ..
00124 *     .. Common blocks ..
00125       COMMON             / INFOC / INFOT, NUNIT, OK, LERR
00126       COMMON             / SRNAMC / SRNAMT
00127 *     ..
00128 *     .. Intrinsic Functions ..
00129       INTRINSIC          CMPLX, MAX, MIN
00130 *     ..
00131 *     .. Data statements ..
00132       DATA               ISEEDY / 1988, 1989, 1990, 1991 /
00133       DATA               UPLOS / 'U', 'L' / , FACTS / 'F', 'N' /
00134 *     ..
00135 *     .. Executable Statements ..
00136 *
00137 *     Initialize constants and the random number seed.
00138 *
00139       PATH( 1: 1 ) = 'Complex precision'
00140       PATH( 2: 3 ) = 'SY'
00141       NRUN = 0
00142       NFAIL = 0
00143       NERRS = 0
00144       DO 10 I = 1, 4
00145          ISEED( I ) = ISEEDY( I )
00146    10 CONTINUE
00147       LWORK = MAX( 2*NMAX, NMAX*NRHS )
00148 *
00149 *     Test the error exits
00150 *
00151       IF( TSTERR )
00152      $   CALL CERRVX( PATH, NOUT )
00153       INFOT = 0
00154 *
00155 *     Set the block size and minimum block size for testing.
00156 *
00157       NB = 1
00158       NBMIN = 2
00159       CALL XLAENV( 1, NB )
00160       CALL XLAENV( 2, NBMIN )
00161 *
00162 *     Do for each value of N in NVAL
00163 *
00164       DO 180 IN = 1, NN
00165          N = NVAL( IN )
00166          LDA = MAX( N, 1 )
00167          XTYPE = 'N'
00168          NIMAT = NTYPES
00169          IF( N.LE.0 )
00170      $      NIMAT = 1
00171 *
00172          DO 170 IMAT = 1, NIMAT
00173 *
00174 *           Do the tests only if DOTYPE( IMAT ) is true.
00175 *
00176             IF( .NOT.DOTYPE( IMAT ) )
00177      $         GO TO 170
00178 *
00179 *           Skip types 3, 4, 5, or 6 if the matrix size is too small.
00180 *
00181             ZEROT = IMAT.GE.3 .AND. IMAT.LE.6
00182             IF( ZEROT .AND. N.LT.IMAT-2 )
00183      $         GO TO 170
00184 *
00185 *           Do first for UPLO = 'U', then for UPLO = 'L'
00186 *
00187             DO 160 IUPLO = 1, 2
00188                UPLO = UPLOS( IUPLO )
00189 *
00190                IF( IMAT.NE.NTYPES ) THEN
00191 *
00192 *                 Set up parameters with CLATB4 and generate a test
00193 *                 matrix with CLATMS.
00194 *
00195                   CALL CLATB4( PATH, IMAT, N, N, TYPE, KL, KU, ANORM,
00196      $                         MODE, CNDNUM, DIST )
00197 *
00198                   SRNAMT = 'CLATMS'
00199                   CALL CLATMS( N, N, DIST, ISEED, TYPE, RWORK, MODE,
00200      $                         CNDNUM, ANORM, KL, KU, UPLO, A, LDA,
00201      $                         WORK, INFO )
00202 *
00203 *                 Check error code from CLATMS.
00204 *
00205                   IF( INFO.NE.0 ) THEN
00206                      CALL ALAERH( PATH, 'CLATMS', INFO, 0, UPLO, N, N,
00207      $                            -1, -1, -1, IMAT, NFAIL, NERRS, NOUT )
00208                      GO TO 160
00209                   END IF
00210 *
00211 *                 For types 3-6, zero one or more rows and columns of
00212 *                 the matrix to test that INFO is returned correctly.
00213 *
00214                   IF( ZEROT ) THEN
00215                      IF( IMAT.EQ.3 ) THEN
00216                         IZERO = 1
00217                      ELSE IF( IMAT.EQ.4 ) THEN
00218                         IZERO = N
00219                      ELSE
00220                         IZERO = N / 2 + 1
00221                      END IF
00222 *
00223                      IF( IMAT.LT.6 ) THEN
00224 *
00225 *                       Set row and column IZERO to zero.
00226 *
00227                         IF( IUPLO.EQ.1 ) THEN
00228                            IOFF = ( IZERO-1 )*LDA
00229                            DO 20 I = 1, IZERO - 1
00230                               A( IOFF+I ) = ZERO
00231    20                      CONTINUE
00232                            IOFF = IOFF + IZERO
00233                            DO 30 I = IZERO, N
00234                               A( IOFF ) = ZERO
00235                               IOFF = IOFF + LDA
00236    30                      CONTINUE
00237                         ELSE
00238                            IOFF = IZERO
00239                            DO 40 I = 1, IZERO - 1
00240                               A( IOFF ) = ZERO
00241                               IOFF = IOFF + LDA
00242    40                      CONTINUE
00243                            IOFF = IOFF - IZERO
00244                            DO 50 I = IZERO, N
00245                               A( IOFF+I ) = ZERO
00246    50                      CONTINUE
00247                         END IF
00248                      ELSE
00249                         IF( IUPLO.EQ.1 ) THEN
00250 *
00251 *                          Set the first IZERO rows to zero.
00252 *
00253                            IOFF = 0
00254                            DO 70 J = 1, N
00255                               I2 = MIN( J, IZERO )
00256                               DO 60 I = 1, I2
00257                                  A( IOFF+I ) = ZERO
00258    60                         CONTINUE
00259                               IOFF = IOFF + LDA
00260    70                      CONTINUE
00261                         ELSE
00262 *
00263 *                          Set the last IZERO rows to zero.
00264 *
00265                            IOFF = 0
00266                            DO 90 J = 1, N
00267                               I1 = MAX( J, IZERO )
00268                               DO 80 I = I1, N
00269                                  A( IOFF+I ) = ZERO
00270    80                         CONTINUE
00271                               IOFF = IOFF + LDA
00272    90                      CONTINUE
00273                         END IF
00274                      END IF
00275                   ELSE
00276                      IZERO = 0
00277                   END IF
00278                ELSE
00279 *
00280 *                 IMAT = NTYPES:  Use a special block diagonal matrix to
00281 *                 test alternate code for the 2-by-2 blocks.
00282 *
00283                   CALL CLATSY( UPLO, N, A, LDA, ISEED )
00284                END IF
00285 *
00286                DO 150 IFACT = 1, NFACT
00287 *
00288 *                 Do first for FACT = 'F', then for other values.
00289 *
00290                   FACT = FACTS( IFACT )
00291 *
00292 *                 Compute the condition number for comparison with
00293 *                 the value returned by CSYSVX.
00294 *
00295                   IF( ZEROT ) THEN
00296                      IF( IFACT.EQ.1 )
00297      $                  GO TO 150
00298                      RCONDC = ZERO
00299 *
00300                   ELSE IF( IFACT.EQ.1 ) THEN
00301 *
00302 *                    Compute the 1-norm of A.
00303 *
00304                      ANORM = CLANSY( '1', UPLO, N, A, LDA, RWORK )
00305 *
00306 *                    Factor the matrix A.
00307 *
00308                      CALL CLACPY( UPLO, N, N, A, LDA, AFAC, LDA )
00309                      CALL CSYTRF( UPLO, N, AFAC, LDA, IWORK, WORK,
00310      $                            LWORK, INFO )
00311 *
00312 *                    Compute inv(A) and take its norm.
00313 *
00314                      CALL CLACPY( UPLO, N, N, AFAC, LDA, AINV, LDA )
00315                      LWORK = (N+NB+1)*(NB+3)
00316                      CALL CSYTRI2( UPLO, N, AINV, LDA, IWORK, WORK,
00317      $                            LWORK, INFO )
00318                      AINVNM = CLANSY( '1', UPLO, N, AINV, LDA, RWORK )
00319 *
00320 *                    Compute the 1-norm condition number of A.
00321 *
00322                      IF( ANORM.LE.ZERO .OR. AINVNM.LE.ZERO ) THEN
00323                         RCONDC = ONE
00324                      ELSE
00325                         RCONDC = ( ONE / ANORM ) / AINVNM
00326                      END IF
00327                   END IF
00328 *
00329 *                 Form an exact solution and set the right hand side.
00330 *
00331                   SRNAMT = 'CLARHS'
00332                   CALL CLARHS( PATH, XTYPE, UPLO, ' ', N, N, KL, KU,
00333      $                         NRHS, A, LDA, XACT, LDA, B, LDA, ISEED,
00334      $                         INFO )
00335                   XTYPE = 'C'
00336 *
00337 *                 --- Test CSYSV  ---
00338 *
00339                   IF( IFACT.EQ.2 ) THEN
00340                      CALL CLACPY( UPLO, N, N, A, LDA, AFAC, LDA )
00341                      CALL CLACPY( 'Full', N, NRHS, B, LDA, X, LDA )
00342 *
00343 *                    Factor the matrix and solve the system using CSYSV.
00344 *
00345                      SRNAMT = 'CSYSV '
00346                      CALL CSYSV( UPLO, N, NRHS, AFAC, LDA, IWORK, X,
00347      $                           LDA, WORK, LWORK, INFO )
00348 *
00349 *                    Adjust the expected value of INFO to account for
00350 *                    pivoting.
00351 *
00352                      K = IZERO
00353                      IF( K.GT.0 ) THEN
00354   100                   CONTINUE
00355                         IF( IWORK( K ).LT.0 ) THEN
00356                            IF( IWORK( K ).NE.-K ) THEN
00357                               K = -IWORK( K )
00358                               GO TO 100
00359                            END IF
00360                         ELSE IF( IWORK( K ).NE.K ) THEN
00361                            K = IWORK( K )
00362                            GO TO 100
00363                         END IF
00364                      END IF
00365 *
00366 *                    Check error code from CSYSV .
00367 *
00368                      IF( INFO.NE.K ) THEN
00369                         CALL ALAERH( PATH, 'CSYSV ', INFO, K, UPLO, N,
00370      $                               N, -1, -1, NRHS, IMAT, NFAIL,
00371      $                               NERRS, NOUT )
00372                         GO TO 120
00373                      ELSE IF( INFO.NE.0 ) THEN
00374                         GO TO 120
00375                      END IF
00376 *
00377 *                    Reconstruct matrix from factors and compute
00378 *                    residual.
00379 *
00380                      CALL CSYT01( UPLO, N, A, LDA, AFAC, LDA, IWORK,
00381      $                            AINV, LDA, RWORK, RESULT( 1 ) )
00382 *
00383 *                    Compute residual of the computed solution.
00384 *
00385                      CALL CLACPY( 'Full', N, NRHS, B, LDA, WORK, LDA )
00386                      CALL CSYT02( UPLO, N, NRHS, A, LDA, X, LDA, WORK,
00387      $                            LDA, RWORK, RESULT( 2 ) )
00388 *
00389 *                    Check solution from generated exact solution.
00390 *
00391                      CALL CGET04( N, NRHS, X, LDA, XACT, LDA, RCONDC,
00392      $                            RESULT( 3 ) )
00393                      NT = 3
00394 *
00395 *                    Print information about the tests that did not pass
00396 *                    the threshold.
00397 *
00398                      DO 110 K = 1, NT
00399                         IF( RESULT( K ).GE.THRESH ) THEN
00400                            IF( NFAIL.EQ.0 .AND. NERRS.EQ.0 )
00401      $                        CALL ALADHD( NOUT, PATH )
00402                            WRITE( NOUT, FMT = 9999 )'CSYSV ', UPLO, N,
00403      $                        IMAT, K, RESULT( K )
00404                            NFAIL = NFAIL + 1
00405                         END IF
00406   110                CONTINUE
00407                      NRUN = NRUN + NT
00408   120                CONTINUE
00409                   END IF
00410 *
00411 *                 --- Test CSYSVX ---
00412 *
00413                   IF( IFACT.EQ.2 )
00414      $               CALL CLASET( UPLO, N, N, CMPLX( ZERO ),
00415      $                            CMPLX( ZERO ), AFAC, LDA )
00416                   CALL CLASET( 'Full', N, NRHS, CMPLX( ZERO ),
00417      $                         CMPLX( ZERO ), X, LDA )
00418 *
00419 *                 Solve the system and compute the condition number and
00420 *                 error bounds using CSYSVX.
00421 *
00422                   SRNAMT = 'CSYSVX'
00423                   CALL CSYSVX( FACT, UPLO, N, NRHS, A, LDA, AFAC, LDA,
00424      $                         IWORK, B, LDA, X, LDA, RCOND, RWORK,
00425      $                         RWORK( NRHS+1 ), WORK, LWORK,
00426      $                         RWORK( 2*NRHS+1 ), INFO )
00427 *
00428 *                 Adjust the expected value of INFO to account for
00429 *                 pivoting.
00430 *
00431                   K = IZERO
00432                   IF( K.GT.0 ) THEN
00433   130                CONTINUE
00434                      IF( IWORK( K ).LT.0 ) THEN
00435                         IF( IWORK( K ).NE.-K ) THEN
00436                            K = -IWORK( K )
00437                            GO TO 130
00438                         END IF
00439                      ELSE IF( IWORK( K ).NE.K ) THEN
00440                         K = IWORK( K )
00441                         GO TO 130
00442                      END IF
00443                   END IF
00444 *
00445 *                 Check the error code from CSYSVX.
00446 *
00447                   IF( INFO.NE.K ) THEN
00448                      CALL ALAERH( PATH, 'CSYSVX', INFO, K, FACT // UPLO,
00449      $                            N, N, -1, -1, NRHS, IMAT, NFAIL,
00450      $                            NERRS, NOUT )
00451                      GO TO 150
00452                   END IF
00453 *
00454                   IF( INFO.EQ.0 ) THEN
00455                      IF( IFACT.GE.2 ) THEN
00456 *
00457 *                       Reconstruct matrix from factors and compute
00458 *                       residual.
00459 *
00460                         CALL CSYT01( UPLO, N, A, LDA, AFAC, LDA, IWORK,
00461      $                               AINV, LDA, RWORK( 2*NRHS+1 ),
00462      $                               RESULT( 1 ) )
00463                         K1 = 1
00464                      ELSE
00465                         K1 = 2
00466                      END IF
00467 *
00468 *                    Compute residual of the computed solution.
00469 *
00470                      CALL CLACPY( 'Full', N, NRHS, B, LDA, WORK, LDA )
00471                      CALL CSYT02( UPLO, N, NRHS, A, LDA, X, LDA, WORK,
00472      $                            LDA, RWORK( 2*NRHS+1 ), RESULT( 2 ) )
00473 *
00474 *                    Check solution from generated exact solution.
00475 *
00476                      CALL CGET04( N, NRHS, X, LDA, XACT, LDA, RCONDC,
00477      $                            RESULT( 3 ) )
00478 *
00479 *                    Check the error bounds from iterative refinement.
00480 *
00481                      CALL CPOT05( UPLO, N, NRHS, A, LDA, B, LDA, X, LDA,
00482      $                            XACT, LDA, RWORK, RWORK( NRHS+1 ),
00483      $                            RESULT( 4 ) )
00484                   ELSE
00485                      K1 = 6
00486                   END IF
00487 *
00488 *                 Compare RCOND from CSYSVX with the computed value
00489 *                 in RCONDC.
00490 *
00491                   RESULT( 6 ) = SGET06( RCOND, RCONDC )
00492 *
00493 *                 Print information about the tests that did not pass
00494 *                 the threshold.
00495 *
00496                   DO 140 K = K1, 6
00497                      IF( RESULT( K ).GE.THRESH ) THEN
00498                         IF( NFAIL.EQ.0 .AND. NERRS.EQ.0 )
00499      $                     CALL ALADHD( NOUT, PATH )
00500                         WRITE( NOUT, FMT = 9998 )'CSYSVX', FACT, UPLO,
00501      $                     N, IMAT, K, RESULT( K )
00502                         NFAIL = NFAIL + 1
00503                      END IF
00504   140             CONTINUE
00505                   NRUN = NRUN + 7 - K1
00506 *
00507 *                 --- Test CSYSVXX ---
00508 *
00509 *                 Restore the matrices A and B.
00510 *
00511                   IF( IFACT.EQ.2 )
00512      $               CALL CLASET( UPLO, N, N, CMPLX( ZERO ),
00513      $                 CMPLX( ZERO ), AFAC, LDA )
00514                   CALL CLASET( 'Full', N, NRHS, CMPLX( ZERO ),
00515      $                 CMPLX( ZERO ), X, LDA )
00516 *
00517 *                 Solve the system and compute the condition number
00518 *                 and error bounds using CSYSVXX.
00519 *
00520                   SRNAMT = 'CSYSVXX'
00521                   N_ERR_BNDS = 3
00522                   EQUED = 'N'
00523                   CALL CSYSVXX( FACT, UPLO, N, NRHS, A, LDA, AFAC,
00524      $                 LDA, IWORK, EQUED, WORK( N+1 ), B, LDA, X,
00525      $                 LDA, RCOND, RPVGRW_SVXX, BERR, N_ERR_BNDS,
00526      $                 ERRBNDS_N, ERRBNDS_C, 0, ZERO, WORK,
00527      $                 IWORK( N+1 ), INFO )
00528 *
00529 *                 Adjust the expected value of INFO to account for
00530 *                 pivoting.
00531 *
00532                   K = IZERO
00533                   IF( K.GT.0 ) THEN
00534  135                 CONTINUE
00535                      IF( IWORK( K ).LT.0 ) THEN
00536                         IF( IWORK( K ).NE.-K ) THEN
00537                            K = -IWORK( K )
00538                            GO TO 135
00539                         END IF
00540                      ELSE IF( IWORK( K ).NE.K ) THEN
00541                         K = IWORK( K )
00542                         GO TO 135
00543                      END IF
00544                   END IF
00545 *
00546 *                 Check the error code from CSYSVXX.
00547 *
00548                   IF( INFO.NE.K ) THEN
00549                      CALL ALAERH( PATH, 'CSYSVXX', INFO, K,
00550      $                    FACT // UPLO, N, N, -1, -1, NRHS, IMAT, NFAIL,
00551      $                    NERRS, NOUT )
00552                      GO TO 150
00553                   END IF
00554 *
00555                   IF( INFO.EQ.0 ) THEN
00556                      IF( IFACT.GE.2 ) THEN
00557 *
00558 *                 Reconstruct matrix from factors and compute
00559 *                 residual.
00560 *
00561                         CALL CSYT01( UPLO, N, A, LDA, AFAC, LDA, IWORK,
00562      $                       AINV, LDA, RWORK(2*NRHS+1),
00563      $                       RESULT( 1 ) )
00564                         K1 = 1
00565                      ELSE
00566                         K1 = 2
00567                      END IF
00568 *
00569 *                 Compute residual of the computed solution.
00570 *
00571                      CALL CLACPY( 'Full', N, NRHS, B, LDA, WORK, LDA )
00572                      CALL CSYT02( UPLO, N, NRHS, A, LDA, X, LDA, WORK,
00573      $                    LDA, RWORK( 2*NRHS+1 ), RESULT( 2 ) )
00574                      RESULT( 2 ) = 0.0
00575 *
00576 *                 Check solution from generated exact solution.
00577 *
00578                      CALL CGET04( N, NRHS, X, LDA, XACT, LDA, RCONDC,
00579      $                    RESULT( 3 ) )
00580 *
00581 *                 Check the error bounds from iterative refinement.
00582 *
00583                      CALL CPOT05( UPLO, N, NRHS, A, LDA, B, LDA, X, LDA,
00584      $                    XACT, LDA, RWORK, RWORK( NRHS+1 ),
00585      $                    RESULT( 4 ) )
00586                   ELSE
00587                      K1 = 6
00588                   END IF
00589 *
00590 *                 Compare RCOND from CSYSVXX with the computed value
00591 *                 in RCONDC.
00592 *
00593                   RESULT( 6 ) = SGET06( RCOND, RCONDC )
00594 *
00595 *                 Print information about the tests that did not pass
00596 *                 the threshold.
00597 *
00598                   DO 85 K = K1, 6
00599                      IF( RESULT( K ).GE.THRESH ) THEN
00600                         IF( NFAIL.EQ.0 .AND. NERRS.EQ.0 )
00601      $                       CALL ALADHD( NOUT, PATH )
00602                         WRITE( NOUT, FMT = 9998 )'CSYSVXX',
00603      $                       FACT, UPLO, N, IMAT, K,
00604      $                       RESULT( K )
00605                         NFAIL = NFAIL + 1
00606                      END IF
00607  85               CONTINUE
00608                   NRUN = NRUN + 7 - K1
00609 *
00610   150          CONTINUE
00611 *
00612   160       CONTINUE
00613   170    CONTINUE
00614   180 CONTINUE
00615 *
00616 *     Print a summary of the results.
00617 *
00618       CALL ALASVM( PATH, NOUT, NFAIL, NRUN, NERRS )
00619 *
00620 
00621 *     Test Error Bounds from CSYSVXX
00622 
00623       CALL CEBCHVXX(THRESH, PATH)
00624 
00625  9999 FORMAT( 1X, A, ', UPLO=''', A1, ''', N =', I5, ', type ', I2,
00626      $      ', test ', I2, ', ratio =', G12.5 )
00627  9998 FORMAT( 1X, A, ', FACT=''', A1, ''', UPLO=''', A1, ''', N =', I5,
00628      $      ', type ', I2, ', test ', I2, ', ratio =', G12.5 )
00629       RETURN
00630 *
00631 *     End of CDRVSY
00632 *
00633       END
 All Files Functions