📄 zdrvev.f
字号:
SUBROUTINE ZDRVEV( NSIZES, NN, NTYPES, DOTYPE, ISEED, THRESH,
$ NOUNIT, A, LDA, H, W, W1, VL, LDVL, VR, LDVR,
$ LRE, LDLRE, RESULT, WORK, NWORK, RWORK, IWORK,
$ INFO )
*
* -- LAPACK test routine (version 3.1) --
* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
* November 2006
*
* .. Scalar Arguments ..
INTEGER INFO, LDA, LDLRE, LDVL, LDVR, NOUNIT, NSIZES,
$ NTYPES, NWORK
DOUBLE PRECISION THRESH
* ..
* .. Array Arguments ..
LOGICAL DOTYPE( * )
INTEGER ISEED( 4 ), IWORK( * ), NN( * )
DOUBLE PRECISION RESULT( 7 ), RWORK( * )
COMPLEX*16 A( LDA, * ), H( LDA, * ), LRE( LDLRE, * ),
$ VL( LDVL, * ), VR( LDVR, * ), W( * ), W1( * ),
$ WORK( * )
* ..
*
* Purpose
* =======
*
* ZDRVEV checks the nonsymmetric eigenvalue problem driver ZGEEV.
*
* When ZDRVEV is called, a number of matrix "sizes" ("n's") and a
* number of matrix "types" are specified. For each size ("n")
* and each type of matrix, one matrix will be generated and used
* to test the nonsymmetric eigenroutines. For each matrix, 7
* tests will be performed:
*
* (1) | A * VR - VR * W | / ( n |A| ulp )
*
* Here VR is the matrix of unit right eigenvectors.
* W is a diagonal matrix with diagonal entries W(j).
*
* (2) | A**H * VL - VL * W**H | / ( n |A| ulp )
*
* Here VL is the matrix of unit left eigenvectors, A**H is the
* conjugate-transpose of A, and W is as above.
*
* (3) | |VR(i)| - 1 | / ulp and whether largest component real
*
* VR(i) denotes the i-th column of VR.
*
* (4) | |VL(i)| - 1 | / ulp and whether largest component real
*
* VL(i) denotes the i-th column of VL.
*
* (5) W(full) = W(partial)
*
* W(full) denotes the eigenvalues computed when both VR and VL
* are also computed, and W(partial) denotes the eigenvalues
* computed when only W, only W and VR, or only W and VL are
* computed.
*
* (6) VR(full) = VR(partial)
*
* VR(full) denotes the right eigenvectors computed when both VR
* and VL are computed, and VR(partial) denotes the result
* when only VR is computed.
*
* (7) VL(full) = VL(partial)
*
* VL(full) denotes the left eigenvectors computed when both VR
* and VL are also computed, and VL(partial) denotes the result
* when only VL is computed.
*
* The "sizes" are specified by an array NN(1:NSIZES); the value of
* each element NN(j) specifies one size.
* The "types" are specified by a logical array DOTYPE( 1:NTYPES );
* if DOTYPE(j) is .TRUE., then matrix type "j" will be generated.
* Currently, the list of possible types is:
*
* (1) The zero matrix.
* (2) The identity matrix.
* (3) A (transposed) Jordan block, with 1's on the diagonal.
*
* (4) A diagonal matrix with evenly spaced entries
* 1, ..., ULP and random complex angles.
* (ULP = (first number larger than 1) - 1 )
* (5) A diagonal matrix with geometrically spaced entries
* 1, ..., ULP and random complex angles.
* (6) A diagonal matrix with "clustered" entries 1, ULP, ..., ULP
* and random complex angles.
*
* (7) Same as (4), but multiplied by a constant near
* the overflow threshold
* (8) Same as (4), but multiplied by a constant near
* the underflow threshold
*
* (9) A matrix of the form U' T U, where U is unitary and
* T has evenly spaced entries 1, ..., ULP with random complex
* angles on the diagonal and random O(1) entries in the upper
* triangle.
*
* (10) A matrix of the form U' T U, where U is unitary and
* T has geometrically spaced entries 1, ..., ULP with random
* complex angles on the diagonal and random O(1) entries in
* the upper triangle.
*
* (11) A matrix of the form U' T U, where U is unitary and
* T has "clustered" entries 1, ULP,..., ULP with random
* complex angles on the diagonal and random O(1) entries in
* the upper triangle.
*
* (12) A matrix of the form U' T U, where U is unitary and
* T has complex eigenvalues randomly chosen from
* ULP < |z| < 1 and random O(1) entries in the upper
* triangle.
*
* (13) A matrix of the form X' T X, where X has condition
* SQRT( ULP ) and T has evenly spaced entries 1, ..., ULP
* with random complex angles on the diagonal and random O(1)
* entries in the upper triangle.
*
* (14) A matrix of the form X' T X, where X has condition
* SQRT( ULP ) and T has geometrically spaced entries
* 1, ..., ULP with random complex angles on the diagonal
* and random O(1) entries in the upper triangle.
*
* (15) A matrix of the form X' T X, where X has condition
* SQRT( ULP ) and T has "clustered" entries 1, ULP,..., ULP
* with random complex angles on the diagonal and random O(1)
* entries in the upper triangle.
*
* (16) A matrix of the form X' T X, where X has condition
* SQRT( ULP ) and T has complex eigenvalues randomly chosen
* from ULP < |z| < 1 and random O(1) entries in the upper
* triangle.
*
* (17) Same as (16), but multiplied by a constant
* near the overflow threshold
* (18) Same as (16), but multiplied by a constant
* near the underflow threshold
*
* (19) Nonsymmetric matrix with random entries chosen from |z| < 1
* If N is at least 4, all entries in first two rows and last
* row, and first column and last two columns are zero.
* (20) Same as (19), but multiplied by a constant
* near the overflow threshold
* (21) Same as (19), but multiplied by a constant
* near the underflow threshold
*
* Arguments
* ==========
*
* NSIZES (input) INTEGER
* The number of sizes of matrices to use. If it is zero,
* ZDRVEV does nothing. It must be at least zero.
*
* NN (input) INTEGER array, dimension (NSIZES)
* An array containing the sizes to be used for the matrices.
* Zero values will be skipped. The values must be at least
* zero.
*
* NTYPES (input) INTEGER
* The number of elements in DOTYPE. If it is zero, ZDRVEV
* does nothing. It must be at least zero. If it is MAXTYP+1
* and NSIZES is 1, then an additional type, MAXTYP+1 is
* defined, which is to use whatever matrix is in A. This
* is only useful if DOTYPE(1:MAXTYP) is .FALSE. and
* DOTYPE(MAXTYP+1) is .TRUE. .
*
* DOTYPE (input) LOGICAL array, dimension (NTYPES)
* If DOTYPE(j) is .TRUE., then for each size in NN a
* matrix of that size and of type j will be generated.
* If NTYPES is smaller than the maximum number of types
* defined (PARAMETER MAXTYP), then types NTYPES+1 through
* MAXTYP will not be generated. If NTYPES is larger
* than MAXTYP, DOTYPE(MAXTYP+1) through DOTYPE(NTYPES)
* will be ignored.
*
* ISEED (input/output) INTEGER array, dimension (4)
* On entry ISEED specifies the seed of the random number
* generator. The array elements should be between 0 and 4095;
* if not they will be reduced mod 4096. Also, ISEED(4) must
* be odd. The random number generator uses a linear
* congruential sequence limited to small integers, and so
* should produce machine independent random numbers. The
* values of ISEED are changed on exit, and can be used in the
* next call to ZDRVEV to continue the same random number
* sequence.
*
* THRESH (input) DOUBLE PRECISION
* A test will count as "failed" if the "error", computed as
* described above, exceeds THRESH. Note that the error
* is scaled to be O(1), so THRESH should be a reasonably
* small multiple of 1, e.g., 10 or 100. In particular,
* it should not depend on the precision (single vs. double)
* or the size of the matrix. It must be at least zero.
*
* NOUNIT (input) INTEGER
* The FORTRAN unit number for printing out error messages
* (e.g., if a routine returns INFO not equal to 0.)
*
* A (workspace) COMPLEX*16 array, dimension (LDA, max(NN))
* Used to hold the matrix whose eigenvalues are to be
* computed. On exit, A contains the last matrix actually used.
*
* LDA (input) INTEGER
* The leading dimension of A, and H. LDA must be at
* least 1 and at least max(NN).
*
* H (workspace) COMPLEX*16 array, dimension (LDA, max(NN))
* Another copy of the test matrix A, modified by ZGEEV.
*
* W (workspace) COMPLEX*16 array, dimension (max(NN))
* The eigenvalues of A. On exit, W are the eigenvalues of
* the matrix in A.
*
* W1 (workspace) COMPLEX*16 array, dimension (max(NN))
* Like W, this array contains the eigenvalues of A,
* but those computed when ZGEEV only computes a partial
* eigendecomposition, i.e. not the eigenvalues and left
* and right eigenvectors.
*
* VL (workspace) COMPLEX*16 array, dimension (LDVL, max(NN))
* VL holds the computed left eigenvectors.
*
* LDVL (input) INTEGER
* Leading dimension of VL. Must be at least max(1,max(NN)).
*
* VR (workspace) COMPLEX*16 array, dimension (LDVR, max(NN))
* VR holds the computed right eigenvectors.
*
* LDVR (input) INTEGER
* Leading dimension of VR. Must be at least max(1,max(NN)).
*
* LRE (workspace) COMPLEX*16 array, dimension (LDLRE, max(NN))
* LRE holds the computed right or left eigenvectors.
*
* LDLRE (input) INTEGER
* Leading dimension of LRE. Must be at least max(1,max(NN)).
*
* RESULT (output) DOUBLE PRECISION array, dimension (7)
* The values computed by the seven tests described above.
* The values are currently limited to 1/ulp, to avoid
* overflow.
*
* WORK (workspace) COMPLEX*16 array, dimension (NWORK)
*
* NWORK (input) INTEGER
* The number of entries in WORK. This must be at least
* 5*NN(j)+2*NN(j)**2 for all j.
*
* RWORK (workspace) DOUBLE PRECISION array, dimension (2*max(NN))
*
* IWORK (workspace) INTEGER array, dimension (max(NN))
*
* INFO (output) INTEGER
* If 0, then everything ran OK.
* -1: NSIZES < 0
* -2: Some NN(j) < 0
* -3: NTYPES < 0
* -6: THRESH < 0
* -9: LDA < 1 or LDA < NMAX, where NMAX is max( NN(j) ).
* -14: LDVL < 1 or LDVL < NMAX, where NMAX is max( NN(j) ).
* -16: LDVR < 1 or LDVR < NMAX, where NMAX is max( NN(j) ).
* -18: LDLRE < 1 or LDLRE < NMAX, where NMAX is max( NN(j) ).
* -21: NWORK too small.
* If ZLATMR, CLATMS, CLATME or ZGEEV returns an error code,
* the absolute value of it is returned.
*
*-----------------------------------------------------------------------
*
* Some Local Variables and Parameters:
* ---- ----- --------- --- ----------
*
* ZERO, ONE Real 0 and 1.
* MAXTYP The number of types defined.
* NMAX Largest value in NN.
* NERRS The number of tests which have exceeded THRESH
* COND, CONDS,
* IMODE Values to be passed to the matrix generators.
* ANORM Norm of A; passed to matrix generators.
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -