LAPACK
3.4.2
LAPACK: Linear Algebra PACKage
|
Functions/Subroutines | |
subroutine | slagge (M, N, KL, KU, D, A, LDA, ISEED, WORK, INFO) |
SLAGGE | |
subroutine | slagsy (N, K, D, A, LDA, ISEED, WORK, INFO) |
SLAGSY | |
subroutine | slahilb (N, NRHS, A, LDA, X, LDX, B, LDB, WORK, INFO) |
SLAHILB | |
subroutine | slakf2 (M, N, A, LDA, B, D, E, Z, LDZ) |
SLAKF2 | |
REAL function | slaran (ISEED) |
SLARAN | |
subroutine | slarge (N, A, LDA, ISEED, WORK, INFO) |
SLARGE | |
REAL function | slarnd (IDIST, ISEED) |
SLARND | |
subroutine | slaror (SIDE, INIT, M, N, A, LDA, ISEED, X, INFO) |
SLAROR | |
subroutine | slarot (LROWS, LLEFT, LRIGHT, NL, C, S, A, LDA, XLEFT, XRIGHT) |
SLAROT | |
subroutine | slatm1 (MODE, COND, IRSIGN, IDIST, ISEED, D, N, INFO) |
SLATM1 | |
REAL function | slatm2 (M, N, I, J, KL, KU, IDIST, ISEED, D, IGRADE, DL, DR, IPVTNG, IWORK, SPARSE) |
SLATM2 | |
REAL function | slatm3 (M, N, I, J, ISUB, JSUB, KL, KU, IDIST, ISEED, D, IGRADE, DL, DR, IPVTNG, IWORK, SPARSE) |
SLATM3 | |
subroutine | slatm5 (PRTYPE, M, N, A, LDA, B, LDB, C, LDC, D, LDD, E, LDE, F, LDF, R, LDR, L, LDL, ALPHA, QBLCKA, QBLCKB) |
SLATM5 | |
subroutine | slatm6 (TYPE, N, A, LDA, B, X, LDX, Y, LDY, ALPHA, BETA, WX, WY, S, DIF) |
SLATM6 | |
subroutine | slatm7 (MODE, COND, IRSIGN, IDIST, ISEED, D, N, RANK, INFO) |
SLATM7 | |
subroutine | slatme (N, DIST, ISEED, D, MODE, COND, DMAX, EI, RSIGN, UPPER, SIM, DS, MODES, CONDS, KL, KU, ANORM, A, LDA, WORK, INFO) |
SLATME | |
subroutine | slatmr (M, N, DIST, ISEED, SYM, D, MODE, COND, DMAX, RSIGN, GRADE, DL, MODEL, CONDL, DR, MODER, CONDR, PIVTNG, IPIVOT, KL, KU, SPARSE, ANORM, PACK, A, LDA, IWORK, INFO) |
SLATMR | |
subroutine | slatms (M, N, DIST, ISEED, SYM, D, MODE, COND, DMAX, KL, KU, PACK, A, LDA, WORK, INFO) |
SLATMS | |
subroutine | slatmt (M, N, DIST, ISEED, SYM, D, MODE, COND, DMAX, RANK, KL, KU, PACK, A, LDA, WORK, INFO) |
SLATMT |
This is the group of real LAPACK TESTING MATGEN routines.
subroutine slagge | ( | integer | M, |
integer | N, | ||
integer | KL, | ||
integer | KU, | ||
real, dimension( * ) | D, | ||
real, dimension( lda, * ) | A, | ||
integer | LDA, | ||
integer, dimension( 4 ) | ISEED, | ||
real, dimension( * ) | WORK, | ||
integer | INFO | ||
) |
SLAGGE
SLAGGE generates a real general m by n matrix A, by pre- and post- multiplying a real diagonal matrix D with random orthogonal matrices: A = U*D*V. The lower and upper bandwidths may then be reduced to kl and ku by additional orthogonal transformations.
[in] | M | M is INTEGER The number of rows of the matrix A. M >= 0. |
[in] | N | N is INTEGER The number of columns of the matrix A. N >= 0. |
[in] | KL | KL is INTEGER The number of nonzero subdiagonals within the band of A. 0 <= KL <= M-1. |
[in] | KU | KU is INTEGER The number of nonzero superdiagonals within the band of A. 0 <= KU <= N-1. |
[in] | D | D is REAL array, dimension (min(M,N)) The diagonal elements of the diagonal matrix D. |
[out] | A | A is REAL array, dimension (LDA,N) The generated m by n matrix A. |
[in] | LDA | LDA is INTEGER The leading dimension of the array A. LDA >= M. |
[in,out] | ISEED | ISEED is INTEGER array, dimension (4) On entry, the seed of the random number generator; the array elements must be between 0 and 4095, and ISEED(4) must be odd. On exit, the seed is updated. |
[out] | WORK | WORK is REAL array, dimension (M+N) |
[out] | INFO | INFO is INTEGER = 0: successful exit < 0: if INFO = -i, the i-th argument had an illegal value |
Definition at line 114 of file slagge.f.
subroutine slagsy | ( | integer | N, |
integer | K, | ||
real, dimension( * ) | D, | ||
real, dimension( lda, * ) | A, | ||
integer | LDA, | ||
integer, dimension( 4 ) | ISEED, | ||
real, dimension( * ) | WORK, | ||
integer | INFO | ||
) |
SLAGSY
SLAGSY generates a real symmetric matrix A, by pre- and post- multiplying a real diagonal matrix D with a random orthogonal matrix: A = U*D*U'. The semi-bandwidth may then be reduced to k by additional orthogonal transformations.
[in] | N | N is INTEGER The order of the matrix A. N >= 0. |
[in] | K | K is INTEGER The number of nonzero subdiagonals within the band of A. 0 <= K <= N-1. |
[in] | D | D is REAL array, dimension (N) The diagonal elements of the diagonal matrix D. |
[out] | A | A is REAL array, dimension (LDA,N) The generated n by n symmetric matrix A (the full matrix is stored). |
[in] | LDA | LDA is INTEGER The leading dimension of the array A. LDA >= N. |
[in,out] | ISEED | ISEED is INTEGER array, dimension (4) On entry, the seed of the random number generator; the array elements must be between 0 and 4095, and ISEED(4) must be odd. On exit, the seed is updated. |
[out] | WORK | WORK is REAL array, dimension (2*N) |
[out] | INFO | INFO is INTEGER = 0: successful exit < 0: if INFO = -i, the i-th argument had an illegal value |
Definition at line 102 of file slagsy.f.
subroutine slahilb | ( | integer | N, |
integer | NRHS, | ||
real, dimension(lda, n) | A, | ||
integer | LDA, | ||
real, dimension(ldx, nrhs) | X, | ||
integer | LDX, | ||
real, dimension(ldb, nrhs) | B, | ||
integer | LDB, | ||
real, dimension(n) | WORK, | ||
integer | INFO | ||
) |
SLAHILB
SLAHILB generates an N by N scaled Hilbert matrix in A along with NRHS right-hand sides in B and solutions in X such that A*X=B. The Hilbert matrix is scaled by M = LCM(1, 2, ..., 2*N-1) so that all entries are integers. The right-hand sides are the first NRHS columns of M * the identity matrix, and the solutions are the first NRHS columns of the inverse Hilbert matrix. The condition number of the Hilbert matrix grows exponentially with its size, roughly as O(e ** (3.5*N)). Additionally, the inverse Hilbert matrices beyond a relatively small dimension cannot be generated exactly without extra precision. Precision is exhausted when the largest entry in the inverse Hilbert matrix is greater than 2 to the power of the number of bits in the fraction of the data type used plus one, which is 24 for single precision. In single, the generated solution is exact for N <= 6 and has small componentwise error for 7 <= N <= 11.
[in] | N | N is INTEGER The dimension of the matrix A. |
[in] | NRHS | NRHS is INTEGER The requested number of right-hand sides. |
[out] | A | A is REAL array, dimension (LDA, N) The generated scaled Hilbert matrix. |
[in] | LDA | LDA is INTEGER The leading dimension of the array A. LDA >= N. |
[out] | X | X is REAL array, dimension (LDX, NRHS) The generated exact solutions. Currently, the first NRHS columns of the inverse Hilbert matrix. |
[in] | LDX | LDX is INTEGER The leading dimension of the array X. LDX >= N. |
[out] | B | B is REAL array, dimension (LDB, NRHS) The generated right-hand sides. Currently, the first NRHS columns of LCM(1, 2, ..., 2*N-1) * the identity matrix. |
[in] | LDB | LDB is INTEGER The leading dimension of the array B. LDB >= N. |
[out] | WORK | WORK is REAL array, dimension (N) |
[out] | INFO | INFO is INTEGER = 0: successful exit = 1: N is too large; the data is still generated but may not be not exact. < 0: if INFO = -i, the i-th argument had an illegal value |
Definition at line 125 of file slahilb.f.
subroutine slakf2 | ( | integer | M, |
integer | N, | ||
real, dimension( lda, * ) | A, | ||
integer | LDA, | ||
real, dimension( lda, * ) | B, | ||
real, dimension( lda, * ) | D, | ||
real, dimension( lda, * ) | E, | ||
real, dimension( ldz, * ) | Z, | ||
integer | LDZ | ||
) |
SLAKF2
Form the 2*M*N by 2*M*N matrix Z = [ kron(In, A) -kron(B', Im) ] [ kron(In, D) -kron(E', Im) ], where In is the identity matrix of size n and X' is the transpose of X. kron(X, Y) is the Kronecker product between the matrices X and Y.
[in] | M | M is INTEGER Size of matrix, must be >= 1. |
[in] | N | N is INTEGER Size of matrix, must be >= 1. |
[in] | A | A is REAL, dimension ( LDA, M ) The matrix A in the output matrix Z. |
[in] | LDA | LDA is INTEGER The leading dimension of A, B, D, and E. ( LDA >= M+N ) |
[in] | B | B is REAL, dimension ( LDA, N ) |
[in] | D | D is REAL, dimension ( LDA, M ) |
[in] | E | E is REAL, dimension ( LDA, N ) The matrices used in forming the output matrix Z. |
[out] | Z | Z is REAL, dimension ( LDZ, 2*M*N ) The resultant Kronecker M*N*2 by M*N*2 matrix (see above.) |
[in] | LDZ | LDZ is INTEGER The leading dimension of Z. ( LDZ >= 2*M*N ) |
Definition at line 106 of file slakf2.f.
REAL function slaran | ( | integer, dimension( 4 ) | ISEED | ) |
SLARAN
SLARAN returns a random real number from a uniform (0,1) distribution.
[in,out] | ISEED | ISEED is INTEGER array, dimension (4) On entry, the seed of the random number generator; the array elements must be between 0 and 4095, and ISEED(4) must be odd. On exit, the seed is updated. |
This routine uses a multiplicative congruential method with modulus 2**48 and multiplier 33952834046453 (see G.S.Fishman, 'Multiplicative congruential random number generators with modulus 2**b: an exhaustive analysis for b = 32 and a partial analysis for b = 48', Math. Comp. 189, pp 331-344, 1990). 48-bit integers are stored in 4 integer array elements with 12 bits per element. Hence the routine is portable across machines with integers of 32 bits or more.
Definition at line 68 of file slaran.f.
subroutine slarge | ( | integer | N, |
real, dimension( lda, * ) | A, | ||
integer | LDA, | ||
integer, dimension( 4 ) | ISEED, | ||
real, dimension( * ) | WORK, | ||
integer | INFO | ||
) |
SLARGE
SLARGE pre- and post-multiplies a real general n by n matrix A with a random orthogonal matrix: A = U*D*U'.
[in] | N | N is INTEGER The order of the matrix A. N >= 0. |
[in,out] | A | A is REAL array, dimension (LDA,N) On entry, the original n by n matrix A. On exit, A is overwritten by U*A*U' for some random orthogonal matrix U. |
[in] | LDA | LDA is INTEGER The leading dimension of the array A. LDA >= N. |
[in,out] | ISEED | ISEED is INTEGER array, dimension (4) On entry, the seed of the random number generator; the array elements must be between 0 and 4095, and ISEED(4) must be odd. On exit, the seed is updated. |
[out] | WORK | WORK is REAL array, dimension (2*N) |
[out] | INFO | INFO is INTEGER = 0: successful exit < 0: if INFO = -i, the i-th argument had an illegal value |
Definition at line 88 of file slarge.f.
REAL function slarnd | ( | integer | IDIST, |
integer, dimension( 4 ) | ISEED | ||
) |
SLARND
SLARND returns a random real number from a uniform or normal distribution.
[in] | IDIST | IDIST is INTEGER Specifies the distribution of the random numbers: = 1: uniform (0,1) = 2: uniform (-1,1) = 3: normal (0,1) |
[in,out] | ISEED | ISEED is INTEGER array, dimension (4) On entry, the seed of the random number generator; the array elements must be between 0 and 4095, and ISEED(4) must be odd. On exit, the seed is updated. |
This routine calls the auxiliary routine SLARAN to generate a random real number from a uniform (0,1) distribution. The Box-Muller method is used to transform numbers from a uniform to a normal distribution.
Definition at line 74 of file slarnd.f.
subroutine slaror | ( | character | SIDE, |
character | INIT, | ||
integer | M, | ||
integer | N, | ||
real, dimension( lda, * ) | A, | ||
integer | LDA, | ||
integer, dimension( 4 ) | ISEED, | ||
real, dimension( * ) | X, | ||
integer | INFO | ||
) |
SLAROR
SLAROR pre- or post-multiplies an M by N matrix A by a random orthogonal matrix U, overwriting A. A may optionally be initialized to the identity matrix before multiplying by U. U is generated using the method of G.W. Stewart (SIAM J. Numer. Anal. 17, 1980, 403-409).
[in] | SIDE | SIDE is CHARACTER*1 Specifies whether A is multiplied on the left or right by U. = 'L': Multiply A on the left (premultiply) by U = 'R': Multiply A on the right (postmultiply) by U' = 'C' or 'T': Multiply A on the left by U and the right by U' (Here, U' means U-transpose.) |
[in] | INIT | INIT is CHARACTER*1 Specifies whether or not A should be initialized to the identity matrix. = 'I': Initialize A to (a section of) the identity matrix before applying U. = 'N': No initialization. Apply U to the input matrix A. INIT = 'I' may be used to generate square or rectangular orthogonal matrices: For M = N and SIDE = 'L' or 'R', the rows will be orthogonal to each other, as will the columns. If M < N, SIDE = 'R' produces a dense matrix whose rows are orthogonal and whose columns are not, while SIDE = 'L' produces a matrix whose rows are orthogonal, and whose first M columns are orthogonal, and whose remaining columns are zero. If M > N, SIDE = 'L' produces a dense matrix whose columns are orthogonal and whose rows are not, while SIDE = 'R' produces a matrix whose columns are orthogonal, and whose first M rows are orthogonal, and whose remaining rows are zero. |
[in] | M | M is INTEGER The number of rows of A. |
[in] | N | N is INTEGER The number of columns of A. |
[in,out] | A | A is REAL array, dimension (LDA, N) On entry, the array A. On exit, overwritten by U A ( if SIDE = 'L' ), or by A U ( if SIDE = 'R' ), or by U A U' ( if SIDE = 'C' or 'T'). |
[in] | LDA | LDA is INTEGER The leading dimension of the array A. LDA >= max(1,M). |
[in,out] | ISEED | ISEED is 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 SLAROR to continue the same random number sequence. |
[out] | X | X is REAL array, dimension (3*MAX( M, N )) Workspace of length 2*M + N if SIDE = 'L', 2*N + M if SIDE = 'R', 3*N if SIDE = 'C' or 'T'. |
[out] | INFO | INFO is INTEGER An error flag. It is set to: = 0: normal return < 0: if INFO = -k, the k-th argument had an illegal value = 1: if the random numbers generated by SLARND are bad. |
Definition at line 147 of file slaror.f.
subroutine slarot | ( | logical | LROWS, |
logical | LLEFT, | ||
logical | LRIGHT, | ||
integer | NL, | ||
real | C, | ||
real | S, | ||
real, dimension( * ) | A, | ||
integer | LDA, | ||
real | XLEFT, | ||
real | XRIGHT | ||
) |
SLAROT
SLAROT applies a (Givens) rotation to two adjacent rows or columns, where one element of the first and/or last column/row for use on matrices stored in some format other than GE, so that elements of the matrix may be used or modified for which no array element is provided. One example is a symmetric matrix in SB format (bandwidth=4), for which UPLO='L': Two adjacent rows will have the format: row j: C> C> C> C> C> . . . . row j+1: C> C> C> C> C> . . . . '*' indicates elements for which storage is provided, '.' indicates elements for which no storage is provided, but are not necessarily zero; their values are determined by symmetry. ' ' indicates elements which are necessarily zero, and have no storage provided. Those columns which have two '*'s can be handled by SROT. Those columns which have no '*'s can be ignored, since as long as the Givens rotations are carefully applied to preserve symmetry, their values are determined. Those columns which have one '*' have to be handled separately, by using separate variables "p" and "q": row j: C> C> C> C> C> p . . . row j+1: q C> C> C> C> C> . . . . The element p would have to be set correctly, then that column is rotated, setting p to its new value. The next call to SLAROT would rotate columns j and j+1, using p, and restore symmetry. The element q would start out being zero, and be made non-zero by the rotation. Later, rotations would presumably be chosen to zero q out. Typical Calling Sequences: rotating the i-th and (i+1)-st rows. ------- ------- --------- General dense matrix: CALL SLAROT(.TRUE.,.FALSE.,.FALSE., N, C,S, A(i,1),LDA, DUMMY, DUMMY) General banded matrix in GB format: j = MAX(1, i-KL ) NL = MIN( N, i+KU+1 ) + 1-j CALL SLAROT( .TRUE., i-KL.GE.1, i+KU.LT.N, NL, C,S, A(KU+i+1-j,j),LDA-1, XLEFT, XRIGHT ) [ note that i+1-j is just MIN(i,KL+1) ] Symmetric banded matrix in SY format, bandwidth K, lower triangle only: j = MAX(1, i-K ) NL = MIN( K+1, i ) + 1 CALL SLAROT( .TRUE., i-K.GE.1, .TRUE., NL, C,S, A(i,j), LDA, XLEFT, XRIGHT ) Same, but upper triangle only: NL = MIN( K+1, N-i ) + 1 CALL SLAROT( .TRUE., .TRUE., i+K.LT.N, NL, C,S, A(i,i), LDA, XLEFT, XRIGHT ) Symmetric banded matrix in SB format, bandwidth K, lower triangle only: [ same as for SY, except:] . . . . A(i+1-j,j), LDA-1, XLEFT, XRIGHT ) [ note that i+1-j is just MIN(i,K+1) ] Same, but upper triangle only: . . . A(K+1,i), LDA-1, XLEFT, XRIGHT ) Rotating columns is just the transpose of rotating rows, except for GB and SB: (rotating columns i and i+1) GB: j = MAX(1, i-KU ) NL = MIN( N, i+KL+1 ) + 1-j CALL SLAROT( .TRUE., i-KU.GE.1, i+KL.LT.N, NL, C,S, A(KU+j+1-i,i),LDA-1, XTOP, XBOTTM ) [note that KU+j+1-i is just MAX(1,KU+2-i)] SB: (upper triangle) . . . . . . A(K+j+1-i,i),LDA-1, XTOP, XBOTTM ) SB: (lower triangle) . . . . . . A(1,i),LDA-1, XTOP, XBOTTM )
LROWS - LOGICAL If .TRUE., then SLAROT will rotate two rows. If .FALSE., then it will rotate two columns. Not modified. LLEFT - LOGICAL If .TRUE., then XLEFT will be used instead of the corresponding element of A for the first element in the second row (if LROWS=.FALSE.) or column (if LROWS=.TRUE.) If .FALSE., then the corresponding element of A will be used. Not modified. LRIGHT - LOGICAL If .TRUE., then XRIGHT will be used instead of the corresponding element of A for the last element in the first row (if LROWS=.FALSE.) or column (if LROWS=.TRUE.) If .FALSE., then the corresponding element of A will be used. Not modified. NL - INTEGER The length of the rows (if LROWS=.TRUE.) or columns (if LROWS=.FALSE.) to be rotated. If XLEFT and/or XRIGHT are used, the columns/rows they are in should be included in NL, e.g., if LLEFT = LRIGHT = .TRUE., then NL must be at least 2. The number of rows/columns to be rotated exclusive of those involving XLEFT and/or XRIGHT may not be negative, i.e., NL minus how many of LLEFT and LRIGHT are .TRUE. must be at least zero; if not, XERBLA will be called. Not modified. C, S - REAL Specify the Givens rotation to be applied. If LROWS is true, then the matrix ( c s ) (-s c ) is applied from the left; if false, then the transpose thereof is applied from the right. For a Givens rotation, C**2 + S**2 should be 1, but this is not checked. Not modified. A - REAL array. The array containing the rows/columns to be rotated. The first element of A should be the upper left element to be rotated. Read and modified. LDA - INTEGER The "effective" leading dimension of A. If A contains a matrix stored in GE or SY format, then this is just the leading dimension of A as dimensioned in the calling routine. If A contains a matrix stored in band (GB or SB) format, then this should be *one less* than the leading dimension used in the calling routine. Thus, if A were dimensioned A(LDA,*) in SLAROT, then A(1,j) would be the j-th element in the first of the two rows to be rotated, and A(2,j) would be the j-th in the second, regardless of how the array may be stored in the calling routine. [A cannot, however, actually be dimensioned thus, since for band format, the row number may exceed LDA, which is not legal FORTRAN.] If LROWS=.TRUE., then LDA must be at least 1, otherwise it must be at least NL minus the number of .TRUE. values in XLEFT and XRIGHT. Not modified. XLEFT - REAL If LLEFT is .TRUE., then XLEFT will be used and modified instead of A(2,1) (if LROWS=.TRUE.) or A(1,2) (if LROWS=.FALSE.). Read and modified. XRIGHT - REAL If LRIGHT is .TRUE., then XRIGHT will be used and modified instead of A(1,NL) (if LROWS=.TRUE.) or A(NL,1) (if LROWS=.FALSE.). Read and modified.
Definition at line 226 of file slarot.f.
subroutine slatm1 | ( | integer | MODE, |
real | COND, | ||
integer | IRSIGN, | ||
integer | IDIST, | ||
integer, dimension( 4 ) | ISEED, | ||
real, dimension( * ) | D, | ||
integer | N, | ||
integer | INFO | ||
) |
SLATM1
SLATM1 computes the entries of D(1..N) as specified by MODE, COND and IRSIGN. IDIST and ISEED determine the generation of random numbers. SLATM1 is called by SLATMR to generate random test matrices for LAPACK programs.
[in] | MODE | MODE is INTEGER On entry describes how D is to be computed: MODE = 0 means do not change D. MODE = 1 sets D(1)=1 and D(2:N)=1.0/COND MODE = 2 sets D(1:N-1)=1 and D(N)=1.0/COND MODE = 3 sets D(I)=COND**(-(I-1)/(N-1)) MODE = 4 sets D(i)=1 - (i-1)/(N-1)*(1 - 1/COND) MODE = 5 sets D to random numbers in the range ( 1/COND , 1 ) such that their logarithms are uniformly distributed. MODE = 6 set D to random numbers from same distribution as the rest of the matrix. MODE < 0 has the same meaning as ABS(MODE), except that the order of the elements of D is reversed. Thus if MODE is positive, D has entries ranging from 1 to 1/COND, if negative, from 1/COND to 1, Not modified. |
[in] | COND | COND is REAL On entry, used as described under MODE above. If used, it must be >= 1. Not modified. |
[in] | IRSIGN | IRSIGN is INTEGER On entry, if MODE neither -6, 0 nor 6, determines sign of entries of D 0 => leave entries of D unchanged 1 => multiply each entry of D by 1 or -1 with probability .5 |
[in] | IDIST | IDIST is CHARACTER*1 On entry, IDIST specifies the type of distribution to be used to generate a random matrix . 1 => UNIFORM( 0, 1 ) 2 => UNIFORM( -1, 1 ) 3 => NORMAL( 0, 1 ) Not modified. |
[in,out] | ISEED | ISEED is INTEGER array, dimension ( 4 ) On entry ISEED specifies the seed of the random number generator. 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 SLATM1 to continue the same random number sequence. Changed on exit. |
[in,out] | D | D is REAL array, dimension ( MIN( M , N ) ) Array to be computed according to MODE, COND and IRSIGN. May be changed on exit if MODE is nonzero. |
[in] | N | N is INTEGER Number of entries of D. Not modified. |
[out] | INFO | INFO is INTEGER 0 => normal termination -1 => if MODE not in range -6 to 6 -2 => if MODE neither -6, 0 nor 6, and IRSIGN neither 0 nor 1 -3 => if MODE neither -6, 0 nor 6 and COND less than 1 -4 => if MODE equals 6 or -6 and IDIST not in range 1 to 3 -7 => if N negative |
Definition at line 136 of file slatm1.f.
REAL function slatm2 | ( | integer | M, |
integer | N, | ||
integer | I, | ||
integer | J, | ||
integer | KL, | ||
integer | KU, | ||
integer | IDIST, | ||
integer, dimension( 4 ) | ISEED, | ||
real, dimension( * ) | D, | ||
integer | IGRADE, | ||
real, dimension( * ) | DL, | ||
real, dimension( * ) | DR, | ||
integer | IPVTNG, | ||
integer, dimension( * ) | IWORK, | ||
real | SPARSE | ||
) |
SLATM2
SLATM2 returns the (I,J) entry of a random matrix of dimension (M, N) described by the other paramters. It is called by the SLATMR routine in order to build random test matrices. No error checking on parameters is done, because this routine is called in a tight loop by SLATMR which has already checked the parameters. Use of SLATM2 differs from SLATM3 in the order in which the random number generator is called to fill in random matrix entries. With SLATM2, the generator is called to fill in the pivoted matrix columnwise. With SLATM3, the generator is called to fill in the matrix columnwise, after which it is pivoted. Thus, SLATM3 can be used to construct random matrices which differ only in their order of rows and/or columns. SLATM2 is used to construct band matrices while avoiding calling the random number generator for entries outside the band (and therefore generating random numbers The matrix whose (I,J) entry is returned is constructed as follows (this routine only computes one entry): If I is outside (1..M) or J is outside (1..N), return zero (this is convenient for generating matrices in band format). Generate a matrix A with random entries of distribution IDIST. Set the diagonal to D. Grade the matrix, if desired, from the left (by DL) and/or from the right (by DR or DL) as specified by IGRADE. Permute, if desired, the rows and/or columns as specified by IPVTNG and IWORK. Band the matrix to have lower bandwidth KL and upper bandwidth KU. Set random entries to zero as specified by SPARSE.
[in] | M | M is INTEGER Number of rows of matrix. Not modified. |
[in] | N | N is INTEGER Number of columns of matrix. Not modified. |
[in] | I | I is INTEGER Row of entry to be returned. Not modified. |
[in] | J | J is INTEGER Column of entry to be returned. Not modified. |
[in] | KL | KL is INTEGER Lower bandwidth. Not modified. |
[in] | KU | KU is INTEGER Upper bandwidth. Not modified. |
[in] | IDIST | IDIST is INTEGER On entry, IDIST specifies the type of distribution to be used to generate a random matrix . 1 => UNIFORM( 0, 1 ) 2 => UNIFORM( -1, 1 ) 3 => NORMAL( 0, 1 ) Not modified. |
[in,out] | ISEED | ISEED is INTEGER array of dimension ( 4 ) Seed for random number generator. Changed on exit. |
[in] | D | D is REAL array of dimension ( MIN( I , J ) ) Diagonal entries of matrix. Not modified. |
[in] | IGRADE | IGRADE is INTEGER Specifies grading of matrix as follows: 0 => no grading 1 => matrix premultiplied by diag( DL ) 2 => matrix postmultiplied by diag( DR ) 3 => matrix premultiplied by diag( DL ) and postmultiplied by diag( DR ) 4 => matrix premultiplied by diag( DL ) and postmultiplied by inv( diag( DL ) ) 5 => matrix premultiplied by diag( DL ) and postmultiplied by diag( DL ) Not modified. |
[in] | DL | DL is REAL array ( I or J, as appropriate ) Left scale factors for grading matrix. Not modified. |
[in] | DR | DR is REAL array ( I or J, as appropriate ) Right scale factors for grading matrix. Not modified. |
[in] | IPVTNG | IPVTNG is INTEGER On entry specifies pivoting permutations as follows: 0 => none. 1 => row pivoting. 2 => column pivoting. 3 => full pivoting, i.e., on both sides. Not modified. |
[out] | IWORK | IWORK is INTEGER array ( I or J, as appropriate ) This array specifies the permutation used. The row (or column) in position K was originally in position IWORK( K ). This differs from IWORK for SLATM3. Not modified. |
[in] | SPARSE | SPARSE is REAL between 0. and 1. On entry specifies the sparsity of the matrix if sparse matix is to be generated. SPARSE should lie between 0 and 1. A uniform ( 0, 1 ) random number x is generated and compared to SPARSE; if x is larger the matrix entry is unchanged and if x is smaller the entry is set to zero. Thus on the average a fraction SPARSE of the entries will be set to zero. Not modified. |
Definition at line 208 of file slatm2.f.
REAL function slatm3 | ( | integer | M, |
integer | N, | ||
integer | I, | ||
integer | J, | ||
integer | ISUB, | ||
integer | JSUB, | ||
integer | KL, | ||
integer | KU, | ||
integer | IDIST, | ||
integer, dimension( 4 ) | ISEED, | ||
real, dimension( * ) | D, | ||
integer | IGRADE, | ||
real, dimension( * ) | DL, | ||
real, dimension( * ) | DR, | ||
integer | IPVTNG, | ||
integer, dimension( * ) | IWORK, | ||
real | SPARSE | ||
) |
SLATM3
SLATM3 returns the (ISUB,JSUB) entry of a random matrix of dimension (M, N) described by the other paramters. (ISUB,JSUB) is the final position of the (I,J) entry after pivoting according to IPVTNG and IWORK. SLATM3 is called by the SLATMR routine in order to build random test matrices. No error checking on parameters is done, because this routine is called in a tight loop by SLATMR which has already checked the parameters. Use of SLATM3 differs from SLATM2 in the order in which the random number generator is called to fill in random matrix entries. With SLATM2, the generator is called to fill in the pivoted matrix columnwise. With SLATM3, the generator is called to fill in the matrix columnwise, after which it is pivoted. Thus, SLATM3 can be used to construct random matrices which differ only in their order of rows and/or columns. SLATM2 is used to construct band matrices while avoiding calling the random number generator for entries outside the band (and therefore generating random numbers in different orders for different pivot orders). The matrix whose (ISUB,JSUB) entry is returned is constructed as follows (this routine only computes one entry): If ISUB is outside (1..M) or JSUB is outside (1..N), return zero (this is convenient for generating matrices in band format). Generate a matrix A with random entries of distribution IDIST. Set the diagonal to D. Grade the matrix, if desired, from the left (by DL) and/or from the right (by DR or DL) as specified by IGRADE. Permute, if desired, the rows and/or columns as specified by IPVTNG and IWORK. Band the matrix to have lower bandwidth KL and upper bandwidth KU. Set random entries to zero as specified by SPARSE.
[in] | M | M is INTEGER Number of rows of matrix. Not modified. |
[in] | N | N is INTEGER Number of columns of matrix. Not modified. |
[in] | I | I is INTEGER Row of unpivoted entry to be returned. Not modified. |
[in] | J | J is INTEGER Column of unpivoted entry to be returned. Not modified. |
[in,out] | ISUB | ISUB is INTEGER Row of pivoted entry to be returned. Changed on exit. |
[in,out] | JSUB | JSUB is INTEGER Column of pivoted entry to be returned. Changed on exit. |
[in] | KL | KL is INTEGER Lower bandwidth. Not modified. |
[in] | KU | KU is INTEGER Upper bandwidth. Not modified. |
[in] | IDIST | IDIST is INTEGER On entry, IDIST specifies the type of distribution to be used to generate a random matrix . 1 => UNIFORM( 0, 1 ) 2 => UNIFORM( -1, 1 ) 3 => NORMAL( 0, 1 ) Not modified. |
[in,out] | ISEED | ISEED is INTEGER array of dimension ( 4 ) Seed for random number generator. Changed on exit. |
[in] | D | D is REAL array of dimension ( MIN( I , J ) ) Diagonal entries of matrix. Not modified. |
[in] | IGRADE | IGRADE is INTEGER Specifies grading of matrix as follows: 0 => no grading 1 => matrix premultiplied by diag( DL ) 2 => matrix postmultiplied by diag( DR ) 3 => matrix premultiplied by diag( DL ) and postmultiplied by diag( DR ) 4 => matrix premultiplied by diag( DL ) and postmultiplied by inv( diag( DL ) ) 5 => matrix premultiplied by diag( DL ) and postmultiplied by diag( DL ) Not modified. |
[in] | DL | DL is REAL array ( I or J, as appropriate ) Left scale factors for grading matrix. Not modified. |
[in] | DR | DR is REAL array ( I or J, as appropriate ) Right scale factors for grading matrix. Not modified. |
[in] | IPVTNG | IPVTNG is INTEGER On entry specifies pivoting permutations as follows: 0 => none. 1 => row pivoting. 2 => column pivoting. 3 => full pivoting, i.e., on both sides. Not modified. |
[in] | IWORK | IWORK is INTEGER array ( I or J, as appropriate ) This array specifies the permutation used. The row (or column) originally in position K is in position IWORK( K ) after pivoting. This differs from IWORK for SLATM2. Not modified. |
[in] | SPARSE | SPARSE is REAL between 0. and 1. On entry specifies the sparsity of the matrix if sparse matix is to be generated. SPARSE should lie between 0 and 1. A uniform ( 0, 1 ) random number x is generated and compared to SPARSE; if x is larger the matrix entry is unchanged and if x is smaller the entry is set to zero. Thus on the average a fraction SPARSE of the entries will be set to zero. Not modified. |
Definition at line 225 of file slatm3.f.
subroutine slatm5 | ( | integer | PRTYPE, |
integer | M, | ||
integer | N, | ||
real, dimension( lda, * ) | A, | ||
integer | LDA, | ||
real, dimension( ldb, * ) | B, | ||
integer | LDB, | ||
real, dimension( ldc, * ) | C, | ||
integer | LDC, | ||
real, dimension( ldd, * ) | D, | ||
integer | LDD, | ||
real, dimension( lde, * ) | E, | ||
integer | LDE, | ||
real, dimension( ldf, * ) | F, | ||
integer | LDF, | ||
real, dimension( ldr, * ) | R, | ||
integer | LDR, | ||
real, dimension( ldl, * ) | L, | ||
integer | LDL, | ||
real | ALPHA, | ||
integer | QBLCKA, | ||
integer | QBLCKB | ||
) |
SLATM5
SLATM5 generates matrices involved in the Generalized Sylvester equation: A * R - L * B = C D * R - L * E = F They also satisfy (the diagonalization condition) [ I -L ] ( [ A -C ], [ D -F ] ) [ I R ] = ( [ A ], [ D ] ) [ I ] ( [ B ] [ E ] ) [ I ] ( [ B ] [ E ] )
[in] | PRTYPE | PRTYPE is INTEGER "Points" to a certian type of the matrices to generate (see futher details). |
[in] | M | M is INTEGER Specifies the order of A and D and the number of rows in C, F, R and L. |
[in] | N | N is INTEGER Specifies the order of B and E and the number of columns in C, F, R and L. |
[out] | A | A is REAL array, dimension (LDA, M). On exit A M-by-M is initialized according to PRTYPE. |
[in] | LDA | LDA is INTEGER The leading dimension of A. |
[out] | B | B is REAL array, dimension (LDB, N). On exit B N-by-N is initialized according to PRTYPE. |
[in] | LDB | LDB is INTEGER The leading dimension of B. |
[out] | C | C is REAL array, dimension (LDC, N). On exit C M-by-N is initialized according to PRTYPE. |
[in] | LDC | LDC is INTEGER The leading dimension of C. |
[out] | D | D is REAL array, dimension (LDD, M). On exit D M-by-M is initialized according to PRTYPE. |
[in] | LDD | LDD is INTEGER The leading dimension of D. |
[out] | E | E is REAL array, dimension (LDE, N). On exit E N-by-N is initialized according to PRTYPE. |
[in] | LDE | LDE is INTEGER The leading dimension of E. |
[out] | F | F is REAL array, dimension (LDF, N). On exit F M-by-N is initialized according to PRTYPE. |
[in] | LDF | LDF is INTEGER The leading dimension of F. |
[out] | R | R is REAL array, dimension (LDR, N). On exit R M-by-N is initialized according to PRTYPE. |
[in] | LDR | LDR is INTEGER The leading dimension of R. |
[out] | L | L is REAL array, dimension (LDL, N). On exit L M-by-N is initialized according to PRTYPE. |
[in] | LDL | LDL is INTEGER The leading dimension of L. |
[in] | ALPHA | ALPHA is REAL Parameter used in generating PRTYPE = 1 and 5 matrices. |
[in] | QBLCKA | QBLCKA is INTEGER When PRTYPE = 3, specifies the distance between 2-by-2 blocks on the diagonal in A. Otherwise, QBLCKA is not referenced. QBLCKA > 1. |
[in] | QBLCKB | QBLCKB is INTEGER When PRTYPE = 3, specifies the distance between 2-by-2 blocks on the diagonal in B. Otherwise, QBLCKB is not referenced. QBLCKB > 1. |
PRTYPE = 1: A and B are Jordan blocks, D and E are identity matrices A : if (i == j) then A(i, j) = 1.0 if (j == i + 1) then A(i, j) = -1.0 else A(i, j) = 0.0, i, j = 1...M B : if (i == j) then B(i, j) = 1.0 - ALPHA if (j == i + 1) then B(i, j) = 1.0 else B(i, j) = 0.0, i, j = 1...N D : if (i == j) then D(i, j) = 1.0 else D(i, j) = 0.0, i, j = 1...M E : if (i == j) then E(i, j) = 1.0 else E(i, j) = 0.0, i, j = 1...N L = R are chosen from [-10...10], which specifies the right hand sides (C, F). PRTYPE = 2 or 3: Triangular and/or quasi- triangular. A : if (i <= j) then A(i, j) = [-1...1] else A(i, j) = 0.0, i, j = 1...M if (PRTYPE = 3) then A(k + 1, k + 1) = A(k, k) A(k + 1, k) = [-1...1] sign(A(k, k + 1) = -(sin(A(k + 1, k)) k = 1, M - 1, QBLCKA B : if (i <= j) then B(i, j) = [-1...1] else B(i, j) = 0.0, i, j = 1...N if (PRTYPE = 3) then B(k + 1, k + 1) = B(k, k) B(k + 1, k) = [-1...1] sign(B(k, k + 1) = -(sign(B(k + 1, k)) k = 1, N - 1, QBLCKB D : if (i <= j) then D(i, j) = [-1...1]. else D(i, j) = 0.0, i, j = 1...M E : if (i <= j) then D(i, j) = [-1...1] else E(i, j) = 0.0, i, j = 1...N L, R are chosen from [-10...10], which specifies the right hand sides (C, F). PRTYPE = 4 Full A(i, j) = [-10...10] D(i, j) = [-1...1] i,j = 1...M B(i, j) = [-10...10] E(i, j) = [-1...1] i,j = 1...N R(i, j) = [-10...10] L(i, j) = [-1...1] i = 1..M ,j = 1...N L, R specifies the right hand sides (C, F). PRTYPE = 5 special case common and/or close eigs.
Definition at line 267 of file slatm5.f.
subroutine slatm6 | ( | integer | TYPE, |
integer | N, | ||
real, dimension( lda, * ) | A, | ||
integer | LDA, | ||
real, dimension( lda, * ) | B, | ||
real, dimension( ldx, * ) | X, | ||
integer | LDX, | ||
real, dimension( ldy, * ) | Y, | ||
integer | LDY, | ||
real | ALPHA, | ||
real | BETA, | ||
real | WX, | ||
real | WY, | ||
real, dimension( * ) | S, | ||
real, dimension( * ) | DIF | ||
) |
SLATM6
SLATM6 generates test matrices for the generalized eigenvalue problem, their corresponding right and left eigenvector matrices, and also reciprocal condition numbers for all eigenvalues and the reciprocal condition numbers of eigenvectors corresponding to the 1th and 5th eigenvalues. Test Matrices ============= Two kinds of test matrix pairs (A, B) = inverse(YH) * (Da, Db) * inverse(X) are used in the tests: Type 1: Da = 1+a 0 0 0 0 Db = 1 0 0 0 0 0 2+a 0 0 0 0 1 0 0 0 0 0 3+a 0 0 0 0 1 0 0 0 0 0 4+a 0 0 0 0 1 0 0 0 0 0 5+a , 0 0 0 0 1 , and Type 2: Da = 1 -1 0 0 0 Db = 1 0 0 0 0 1 1 0 0 0 0 1 0 0 0 0 0 1 0 0 0 0 1 0 0 0 0 0 1+a 1+b 0 0 0 1 0 0 0 0 -1-b 1+a , 0 0 0 0 1 . In both cases the same inverse(YH) and inverse(X) are used to compute (A, B), giving the exact eigenvectors to (A,B) as (YH, X): YH: = 1 0 -y y -y X = 1 0 -x -x x 0 1 -y y -y 0 1 x -x -x 0 0 1 0 0 0 0 1 0 0 0 0 0 1 0 0 0 0 1 0 0 0 0 0 1, 0 0 0 0 1 , where a, b, x and y will have all values independently of each other.
[in] | TYPE | TYPE is INTEGER Specifies the problem type (see futher details). |
[in] | N | N is INTEGER Size of the matrices A and B. |
[out] | A | A is REAL array, dimension (LDA, N). On exit A N-by-N is initialized according to TYPE. |
[in] | LDA | LDA is INTEGER The leading dimension of A and of B. |
[out] | B | B is REAL array, dimension (LDA, N). On exit B N-by-N is initialized according to TYPE. |
[out] | X | X is REAL array, dimension (LDX, N). On exit X is the N-by-N matrix of right eigenvectors. |
[in] | LDX | LDX is INTEGER The leading dimension of X. |
[out] | Y | Y is REAL array, dimension (LDY, N). On exit Y is the N-by-N matrix of left eigenvectors. |
[in] | LDY | LDY is INTEGER The leading dimension of Y. |
[in] | ALPHA | ALPHA is REAL |
[in] | BETA | BETA is REAL Weighting constants for matrix A. |
[in] | WX | WX is REAL Constant for right eigenvector matrix. |
[in] | WY | WY is REAL Constant for left eigenvector matrix. |
[out] | S | S is REAL array, dimension (N) S(i) is the reciprocal condition number for eigenvalue i. |
[out] | DIF | DIF is REAL array, dimension (N) DIF(i) is the reciprocal condition number for eigenvector i. |
Definition at line 176 of file slatm6.f.
subroutine slatm7 | ( | integer | MODE, |
real | COND, | ||
integer | IRSIGN, | ||
integer | IDIST, | ||
integer, dimension( 4 ) | ISEED, | ||
real, dimension( * ) | D, | ||
integer | N, | ||
integer | RANK, | ||
integer | INFO | ||
) |
SLATM7
SLATM7 computes the entries of D as specified by MODE COND and IRSIGN. IDIST and ISEED determine the generation of random numbers. SLATM7 is called by SLATMT to generate random test matrices.
MODE - INTEGER On entry describes how D is to be computed: MODE = 0 means do not change D. MODE = 1 sets D(1)=1 and D(2:RANK)=1.0/COND MODE = 2 sets D(1:RANK-1)=1 and D(RANK)=1.0/COND MODE = 3 sets D(I)=COND**(-(I-1)/(RANK-1)) I=1:RANK MODE = 4 sets D(i)=1 - (i-1)/(N-1)*(1 - 1/COND) MODE = 5 sets D to random numbers in the range ( 1/COND , 1 ) such that their logarithms are uniformly distributed. MODE = 6 set D to random numbers from same distribution as the rest of the matrix. MODE < 0 has the same meaning as ABS(MODE), except that the order of the elements of D is reversed. Thus if MODE is positive, D has entries ranging from 1 to 1/COND, if negative, from 1/COND to 1, Not modified. COND - REAL On entry, used as described under MODE above. If used, it must be >= 1. Not modified. IRSIGN - INTEGER On entry, if MODE neither -6, 0 nor 6, determines sign of entries of D 0 => leave entries of D unchanged 1 => multiply each entry of D by 1 or -1 with probability .5 IDIST - CHARACTER*1 On entry, IDIST specifies the type of distribution to be used to generate a random matrix . 1 => UNIFORM( 0, 1 ) 2 => UNIFORM( -1, 1 ) 3 => NORMAL( 0, 1 ) Not modified. ISEED - INTEGER array, dimension ( 4 ) On entry ISEED specifies the seed of the random number generator. 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 SLATM7 to continue the same random number sequence. Changed on exit. D - REAL array, dimension ( MIN( M , N ) ) Array to be computed according to MODE, COND and IRSIGN. May be changed on exit if MODE is nonzero. N - INTEGER Number of entries of D. Not modified. RANK - INTEGER The rank of matrix to be generated for modes 1,2,3 only. D( RANK+1:N ) = 0. Not modified. INFO - INTEGER 0 => normal termination -1 => if MODE not in range -6 to 6 -2 => if MODE neither -6, 0 nor 6, and IRSIGN neither 0 nor 1 -3 => if MODE neither -6, 0 nor 6 and COND less than 1 -4 => if MODE equals 6 or -6 and IDIST not in range 1 to 3 -7 => if N negative
Definition at line 122 of file slatm7.f.
subroutine slatme | ( | integer | N, |
character | DIST, | ||
integer, dimension( 4 ) | ISEED, | ||
real, dimension( * ) | D, | ||
integer | MODE, | ||
real | COND, | ||
real | DMAX, | ||
character, dimension( * ) | EI, | ||
character | RSIGN, | ||
character | UPPER, | ||
character | SIM, | ||
real, dimension( * ) | DS, | ||
integer | MODES, | ||
real | CONDS, | ||
integer | KL, | ||
integer | KU, | ||
real | ANORM, | ||
real, dimension( lda, * ) | A, | ||
integer | LDA, | ||
real, dimension( * ) | WORK, | ||
integer | INFO | ||
) |
SLATME
SLATME generates random non-symmetric square matrices with specified eigenvalues for testing LAPACK programs. SLATME operates by applying the following sequence of operations: 1. Set the diagonal to D, where D may be input or computed according to MODE, COND, DMAX, and RSIGN as described below. 2. If complex conjugate pairs are desired (MODE=0 and EI(1)='R', or MODE=5), certain pairs of adjacent elements of D are interpreted as the real and complex parts of a complex conjugate pair; A thus becomes block diagonal, with 1x1 and 2x2 blocks. 3. If UPPER='T', the upper triangle of A is set to random values out of distribution DIST. 4. If SIM='T', A is multiplied on the left by a random matrix X, whose singular values are specified by DS, MODES, and CONDS, and on the right by X inverse. 5. If KL < N-1, the lower bandwidth is reduced to KL using Householder transformations. If KU < N-1, the upper bandwidth is reduced to KU. 6. If ANORM is not negative, the matrix is scaled to have maximum-element-norm ANORM. (Note: since the matrix cannot be reduced beyond Hessenberg form, no packing options are available.)
[in] | N | N is INTEGER The number of columns (or rows) of A. Not modified. |
[in] | DIST | DIST is CHARACTER*1 On entry, DIST specifies the type of distribution to be used to generate the random eigen-/singular values, and for the upper triangle (see UPPER). 'U' => UNIFORM( 0, 1 ) ( 'U' for uniform ) 'S' => UNIFORM( -1, 1 ) ( 'S' for symmetric ) 'N' => NORMAL( 0, 1 ) ( 'N' for normal ) Not modified. |
[in,out] | ISEED | ISEED is INTEGER array, dimension ( 4 ) On entry ISEED specifies the seed of the random number generator. They should lie between 0 and 4095 inclusive, and ISEED(4) should 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 SLATME to continue the same random number sequence. Changed on exit. |
[in,out] | D | D is REAL array, dimension ( N ) This array is used to specify the eigenvalues of A. If MODE=0, then D is assumed to contain the eigenvalues (but see the description of EI), otherwise they will be computed according to MODE, COND, DMAX, and RSIGN and placed in D. Modified if MODE is nonzero. |
[in] | MODE | MODE is INTEGER On entry this describes how the eigenvalues are to be specified: MODE = 0 means use D (with EI) as input MODE = 1 sets D(1)=1 and D(2:N)=1.0/COND MODE = 2 sets D(1:N-1)=1 and D(N)=1.0/COND MODE = 3 sets D(I)=COND**(-(I-1)/(N-1)) MODE = 4 sets D(i)=1 - (i-1)/(N-1)*(1 - 1/COND) MODE = 5 sets D to random numbers in the range ( 1/COND , 1 ) such that their logarithms are uniformly distributed. Each odd-even pair of elements will be either used as two real eigenvalues or as the real and imaginary part of a complex conjugate pair of eigenvalues; the choice of which is done is random, with 50-50 probability, for each pair. MODE = 6 set D to random numbers from same distribution as the rest of the matrix. MODE < 0 has the same meaning as ABS(MODE), except that the order of the elements of D is reversed. Thus if MODE is between 1 and 4, D has entries ranging from 1 to 1/COND, if between -1 and -4, D has entries ranging from 1/COND to 1, Not modified. |
[in] | COND | COND is REAL On entry, this is used as described under MODE above. If used, it must be >= 1. Not modified. |
[in] | DMAX | DMAX is REAL If MODE is neither -6, 0 nor 6, the contents of D, as computed according to MODE and COND, will be scaled by DMAX / max(abs(D(i))). Note that DMAX need not be positive: if DMAX is negative (or zero), D will be scaled by a negative number (or zero). Not modified. |
[in] | EI | EI is CHARACTER*1 array, dimension ( N ) If MODE is 0, and EI(1) is not ' ' (space character), this array specifies which elements of D (on input) are real eigenvalues and which are the real and imaginary parts of a complex conjugate pair of eigenvalues. The elements of EI may then only have the values 'R' and 'I'. If EI(j)='R' and EI(j+1)='I', then the j-th eigenvalue is CMPLX( D(j) , D(j+1) ), and the (j+1)-th is the complex conjugate thereof. If EI(j)=EI(j+1)='R', then the j-th eigenvalue is D(j) (i.e., real). EI(1) may not be 'I', nor may two adjacent elements of EI both have the value 'I'. If MODE is not 0, then EI is ignored. If MODE is 0 and EI(1)=' ', then the eigenvalues will all be real. Not modified. |
[in] | RSIGN | RSIGN is CHARACTER*1 If MODE is not 0, 6, or -6, and RSIGN='T', then the elements of D, as computed according to MODE and COND, will be multiplied by a random sign (+1 or -1). If RSIGN='F', they will not be. RSIGN may only have the values 'T' or 'F'. Not modified. |
[in] | UPPER | UPPER is CHARACTER*1 If UPPER='T', then the elements of A above the diagonal (and above the 2x2 diagonal blocks, if A has complex eigenvalues) will be set to random numbers out of DIST. If UPPER='F', they will not. UPPER may only have the values 'T' or 'F'. Not modified. |
[in] | SIM | SIM is CHARACTER*1 If SIM='T', then A will be operated on by a "similarity transform", i.e., multiplied on the left by a matrix X and on the right by X inverse. X = U S V, where U and V are random unitary matrices and S is a (diagonal) matrix of singular values specified by DS, MODES, and CONDS. If SIM='F', then A will not be transformed. Not modified. |
[in,out] | DS | DS is REAL array, dimension ( N ) This array is used to specify the singular values of X, in the same way that D specifies the eigenvalues of A. If MODE=0, the DS contains the singular values, which may not be zero. Modified if MODE is nonzero. |
[in] | MODES | MODES is INTEGER |
[in] | CONDS | CONDS is REAL Same as MODE and COND, but for specifying the diagonal of S. MODES=-6 and +6 are not allowed (since they would result in randomly ill-conditioned eigenvalues.) |
[in] | KL | KL is INTEGER This specifies the lower bandwidth of the matrix. KL=1 specifies upper Hessenberg form. If KL is at least N-1, then A will have full lower bandwidth. KL must be at least 1. Not modified. |
[in] | KU | KU is INTEGER This specifies the upper bandwidth of the matrix. KU=1 specifies lower Hessenberg form. If KU is at least N-1, then A will have full upper bandwidth; if KU and KL are both at least N-1, then A will be dense. Only one of KU and KL may be less than N-1. KU must be at least 1. Not modified. |
[in] | ANORM | ANORM is REAL If ANORM is not negative, then A will be scaled by a non- negative real number to make the maximum-element-norm of A to be ANORM. Not modified. |
[out] | A | A is REAL array, dimension ( LDA, N ) On exit A is the desired test matrix. Modified. |
[in] | LDA | LDA is INTEGER LDA specifies the first dimension of A as declared in the calling program. LDA must be at least N. Not modified. |
[out] | WORK | WORK is REAL array, dimension ( 3*N ) Workspace. Modified. |
[out] | INFO | INFO is INTEGER Error code. On exit, INFO will be set to one of the following values: 0 => normal return -1 => N negative -2 => DIST illegal string -5 => MODE not in range -6 to 6 -6 => COND less than 1.0, and MODE neither -6, 0 nor 6 -8 => EI(1) is not ' ' or 'R', EI(j) is not 'R' or 'I', or two adjacent elements of EI are 'I'. -9 => RSIGN is not 'T' or 'F' -10 => UPPER is not 'T' or 'F' -11 => SIM is not 'T' or 'F' -12 => MODES=0 and DS has a zero singular value. -13 => MODES is not in the range -5 to 5. -14 => MODES is nonzero and CONDS is less than 1. -15 => KL is less than 1. -16 => KU is less than 1, or KL and KU are both less than N-1. -19 => LDA is less than N. 1 => Error return from SLATM1 (computing D) 2 => Cannot scale to DMAX (max. eigenvalue is 0) 3 => Error return from SLATM1 (computing DS) 4 => Error return from SLARGE 5 => Zero singular value from SLATM1. |
Definition at line 329 of file slatme.f.
subroutine slatmr | ( | integer | M, |
integer | N, | ||
character | DIST, | ||
integer, dimension( 4 ) | ISEED, | ||
character | SYM, | ||
real, dimension( * ) | D, | ||
integer | MODE, | ||
real | COND, | ||
real | DMAX, | ||
character | RSIGN, | ||
character | GRADE, | ||
real, dimension( * ) | DL, | ||
integer | MODEL, | ||
real | CONDL, | ||
real, dimension( * ) | DR, | ||
integer | MODER, | ||
real | CONDR, | ||
character | PIVTNG, | ||
integer, dimension( * ) | IPIVOT, | ||
integer | KL, | ||
integer | KU, | ||
real | SPARSE, | ||
real | ANORM, | ||
character | PACK, | ||
real, dimension( lda, * ) | A, | ||
integer | LDA, | ||
integer, dimension( * ) | IWORK, | ||
integer | INFO | ||
) |
SLATMR
SLATMR generates random matrices of various types for testing LAPACK programs. SLATMR operates by applying the following sequence of operations: Generate a matrix A with random entries of distribution DIST which is symmetric if SYM='S', and nonsymmetric if SYM='N'. Set the diagonal to D, where D may be input or computed according to MODE, COND, DMAX and RSIGN as described below. Grade the matrix, if desired, from the left and/or right as specified by GRADE. The inputs DL, MODEL, CONDL, DR, MODER and CONDR also determine the grading as described below. Permute, if desired, the rows and/or columns as specified by PIVTNG and IPIVOT. Set random entries to zero, if desired, to get a random sparse matrix as specified by SPARSE. Make A a band matrix, if desired, by zeroing out the matrix outside a band of lower bandwidth KL and upper bandwidth KU. Scale A, if desired, to have maximum entry ANORM. Pack the matrix if desired. Options specified by PACK are: no packing zero out upper half (if symmetric) zero out lower half (if symmetric) store the upper half columnwise (if symmetric or square upper triangular) store the lower half columnwise (if symmetric or square lower triangular) same as upper half rowwise if symmetric store the lower triangle in banded format (if symmetric) store the upper triangle in banded format (if symmetric) store the entire matrix in banded format Note: If two calls to SLATMR differ only in the PACK parameter, they will generate mathematically equivalent matrices. If two calls to SLATMR both have full bandwidth (KL = M-1 and KU = N-1), and differ only in the PIVTNG and PACK parameters, then the matrices generated will differ only in the order of the rows and/or columns, and otherwise contain the same data. This consistency cannot be and is not maintained with less than full bandwidth.
[in] | M | M is INTEGER Number of rows of A. Not modified. |
[in] | N | N is INTEGER Number of columns of A. Not modified. |
[in] | DIST | DIST is CHARACTER*1 On entry, DIST specifies the type of distribution to be used to generate a random matrix . 'U' => UNIFORM( 0, 1 ) ( 'U' for uniform ) 'S' => UNIFORM( -1, 1 ) ( 'S' for symmetric ) 'N' => NORMAL( 0, 1 ) ( 'N' for normal ) Not modified. |
[in,out] | ISEED | ISEED is INTEGER array, dimension (4) On entry ISEED specifies the seed of the random number generator. They should lie between 0 and 4095 inclusive, and ISEED(4) should 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 SLATMR to continue the same random number sequence. Changed on exit. |
[in] | SYM | SYM is CHARACTER*1 If SYM='S' or 'H', generated matrix is symmetric. If SYM='N', generated matrix is nonsymmetric. Not modified. |
[in] | D | D is REAL array, dimension (min(M,N)) On entry this array specifies the diagonal entries of the diagonal of A. D may either be specified on entry, or set according to MODE and COND as described below. May be changed on exit if MODE is nonzero. |
[in] | MODE | MODE is INTEGER On entry describes how D is to be used: MODE = 0 means use D as input MODE = 1 sets D(1)=1 and D(2:N)=1.0/COND MODE = 2 sets D(1:N-1)=1 and D(N)=1.0/COND MODE = 3 sets D(I)=COND**(-(I-1)/(N-1)) MODE = 4 sets D(i)=1 - (i-1)/(N-1)*(1 - 1/COND) MODE = 5 sets D to random numbers in the range ( 1/COND , 1 ) such that their logarithms are uniformly distributed. MODE = 6 set D to random numbers from same distribution as the rest of the matrix. MODE < 0 has the same meaning as ABS(MODE), except that the order of the elements of D is reversed. Thus if MODE is positive, D has entries ranging from 1 to 1/COND, if negative, from 1/COND to 1, Not modified. |
[in] | COND | COND is REAL On entry, used as described under MODE above. If used, it must be >= 1. Not modified. |
[in] | DMAX | DMAX is REAL If MODE neither -6, 0 nor 6, the diagonal is scaled by DMAX / max(abs(D(i))), so that maximum absolute entry of diagonal is abs(DMAX). If DMAX is negative (or zero), diagonal will be scaled by a negative number (or zero). |
[in] | RSIGN | RSIGN is CHARACTER*1 If MODE neither -6, 0 nor 6, specifies sign of diagonal as follows: 'T' => diagonal entries are multiplied by 1 or -1 with probability .5 'F' => diagonal unchanged Not modified. |
[in] | GRADE | GRADE is CHARACTER*1 Specifies grading of matrix as follows: 'N' => no grading 'L' => matrix premultiplied by diag( DL ) (only if matrix nonsymmetric) 'R' => matrix postmultiplied by diag( DR ) (only if matrix nonsymmetric) 'B' => matrix premultiplied by diag( DL ) and postmultiplied by diag( DR ) (only if matrix nonsymmetric) 'S' or 'H' => matrix premultiplied by diag( DL ) and postmultiplied by diag( DL ) ('S' for symmetric, or 'H' for Hermitian) 'E' => matrix premultiplied by diag( DL ) and postmultiplied by inv( diag( DL ) ) ( 'E' for eigenvalue invariance) (only if matrix nonsymmetric) Note: if GRADE='E', then M must equal N. Not modified. |
[in,out] | DL | DL is REAL array, dimension (M) If MODEL=0, then on entry this array specifies the diagonal entries of a diagonal matrix used as described under GRADE above. If MODEL is not zero, then DL will be set according to MODEL and CONDL, analogous to the way D is set according to MODE and COND (except there is no DMAX parameter for DL). If GRADE='E', then DL cannot have zero entries. Not referenced if GRADE = 'N' or 'R'. Changed on exit. |
[in] | MODEL | MODEL is INTEGER This specifies how the diagonal array DL is to be computed, just as MODE specifies how D is to be computed. Not modified. |
[in] | CONDL | CONDL is REAL When MODEL is not zero, this specifies the condition number of the computed DL. Not modified. |
[in,out] | DR | DR is REAL array, dimension (N) If MODER=0, then on entry this array specifies the diagonal entries of a diagonal matrix used as described under GRADE above. If MODER is not zero, then DR will be set according to MODER and CONDR, analogous to the way D is set according to MODE and COND (except there is no DMAX parameter for DR). Not referenced if GRADE = 'N', 'L', 'H', 'S' or 'E'. Changed on exit. |
[in] | MODER | MODER is INTEGER This specifies how the diagonal array DR is to be computed, just as MODE specifies how D is to be computed. Not modified. |
[in] | CONDR | CONDR is REAL When MODER is not zero, this specifies the condition number of the computed DR. Not modified. |
[in] | PIVTNG | PIVTNG is CHARACTER*1 On entry specifies pivoting permutations as follows: 'N' or ' ' => none. 'L' => left or row pivoting (matrix must be nonsymmetric). 'R' => right or column pivoting (matrix must be nonsymmetric). 'B' or 'F' => both or full pivoting, i.e., on both sides. In this case, M must equal N If two calls to SLATMR both have full bandwidth (KL = M-1 and KU = N-1), and differ only in the PIVTNG and PACK parameters, then the matrices generated will differ only in the order of the rows and/or columns, and otherwise contain the same data. This consistency cannot be maintained with less than full bandwidth. |
[in] | IPIVOT | IPIVOT is INTEGER array, dimension (N or M) This array specifies the permutation used. After the basic matrix is generated, the rows, columns, or both are permuted. If, say, row pivoting is selected, SLATMR starts with the *last* row and interchanges the M-th and IPIVOT(M)-th rows, then moves to the next-to-last row, interchanging the (M-1)-th and the IPIVOT(M-1)-th rows, and so on. In terms of "2-cycles", the permutation is (1 IPIVOT(1)) (2 IPIVOT(2)) ... (M IPIVOT(M)) where the rightmost cycle is applied first. This is the *inverse* of the effect of pivoting in LINPACK. The idea is that factoring (with pivoting) an identity matrix which has been inverse-pivoted in this way should result in a pivot vector identical to IPIVOT. Not referenced if PIVTNG = 'N'. Not modified. |
[in] | SPARSE | SPARSE is REAL On entry specifies the sparsity of the matrix if a sparse matrix is to be generated. SPARSE should lie between 0 and 1. To generate a sparse matrix, for each matrix entry a uniform ( 0, 1 ) random number x is generated and compared to SPARSE; if x is larger the matrix entry is unchanged and if x is smaller the entry is set to zero. Thus on the average a fraction SPARSE of the entries will be set to zero. Not modified. |
[in] | KL | KL is INTEGER On entry specifies the lower bandwidth of the matrix. For example, KL=0 implies upper triangular, KL=1 implies upper Hessenberg, and KL at least M-1 implies the matrix is not banded. Must equal KU if matrix is symmetric. Not modified. |
[in] | KU | KU is INTEGER On entry specifies the upper bandwidth of the matrix. For example, KU=0 implies lower triangular, KU=1 implies lower Hessenberg, and KU at least N-1 implies the matrix is not banded. Must equal KL if matrix is symmetric. Not modified. |
[in] | ANORM | ANORM is REAL On entry specifies maximum entry of output matrix (output matrix will by multiplied by a constant so that its largest absolute entry equal ANORM) if ANORM is nonnegative. If ANORM is negative no scaling is done. Not modified. |
[in] | PACK | PACK is CHARACTER*1 On entry specifies packing of matrix as follows: 'N' => no packing 'U' => zero out all subdiagonal entries (if symmetric) 'L' => zero out all superdiagonal entries (if symmetric) 'C' => store the upper triangle columnwise (only if matrix symmetric or square upper triangular) 'R' => store the lower triangle columnwise (only if matrix symmetric or square lower triangular) (same as upper half rowwise if symmetric) 'B' => store the lower triangle in band storage scheme (only if matrix symmetric) 'Q' => store the upper triangle in band storage scheme (only if matrix symmetric) 'Z' => store the entire matrix in band storage scheme (pivoting can be provided for by using this option to store A in the trailing rows of the allocated storage) Using these options, the various LAPACK packed and banded storage schemes can be obtained: GB - use 'Z' PB, SB or TB - use 'B' or 'Q' PP, SP or TP - use 'C' or 'R' If two calls to SLATMR differ only in the PACK parameter, they will generate mathematically equivalent matrices. Not modified. |
[in,out] | A | A is REAL array, dimension (LDA,N) On exit A is the desired test matrix. Only those entries of A which are significant on output will be referenced (even if A is in packed or band storage format). The 'unoccupied corners' of A in band format will be zeroed out. |
[in] | LDA | LDA is INTEGER on entry LDA specifies the first dimension of A as declared in the calling program. If PACK='N', 'U' or 'L', LDA must be at least max ( 1, M ). If PACK='C' or 'R', LDA must be at least 1. If PACK='B', or 'Q', LDA must be MIN ( KU+1, N ) If PACK='Z', LDA must be at least KUU+KLL+1, where KUU = MIN ( KU, N-1 ) and KLL = MIN ( KL, N-1 ) Not modified. |
[out] | IWORK | IWORK is INTEGER array, dimension ( N or M) Workspace. Not referenced if PIVTNG = 'N'. Changed on exit. |
[out] | INFO | INFO is INTEGER Error parameter on exit: 0 => normal return -1 => M negative or unequal to N and SYM='S' or 'H' -2 => N negative -3 => DIST illegal string -5 => SYM illegal string -7 => MODE not in range -6 to 6 -8 => COND less than 1.0, and MODE neither -6, 0 nor 6 -10 => MODE neither -6, 0 nor 6 and RSIGN illegal string -11 => GRADE illegal string, or GRADE='E' and M not equal to N, or GRADE='L', 'R', 'B' or 'E' and SYM = 'S' or 'H' -12 => GRADE = 'E' and DL contains zero -13 => MODEL not in range -6 to 6 and GRADE= 'L', 'B', 'H', 'S' or 'E' -14 => CONDL less than 1.0, GRADE='L', 'B', 'H', 'S' or 'E', and MODEL neither -6, 0 nor 6 -16 => MODER not in range -6 to 6 and GRADE= 'R' or 'B' -17 => CONDR less than 1.0, GRADE='R' or 'B', and MODER neither -6, 0 nor 6 -18 => PIVTNG illegal string, or PIVTNG='B' or 'F' and M not equal to N, or PIVTNG='L' or 'R' and SYM='S' or 'H' -19 => IPIVOT contains out of range number and PIVTNG not equal to 'N' -20 => KL negative -21 => KU negative, or SYM='S' or 'H' and KU not equal to KL -22 => SPARSE not in range 0. to 1. -24 => PACK illegal string, or PACK='U', 'L', 'B' or 'Q' and SYM='N', or PACK='C' and SYM='N' and either KL not equal to 0 or N not equal to M, or PACK='R' and SYM='N', and either KU not equal to 0 or N not equal to M -26 => LDA too small 1 => Error return from SLATM1 (computing D) 2 => Cannot scale diagonal to DMAX (max. entry is 0) 3 => Error return from SLATM1 (computing DL) 4 => Error return from SLATM1 (computing DR) 5 => ANORM is positive, but matrix constructed prior to attempting to scale it to have norm ANORM, is zero |
Definition at line 469 of file slatmr.f.
subroutine slatms | ( | integer | M, |
integer | N, | ||
character | DIST, | ||
integer, dimension( 4 ) | ISEED, | ||
character | SYM, | ||
real, dimension( * ) | D, | ||
integer | MODE, | ||
real | COND, | ||
real | DMAX, | ||
integer | KL, | ||
integer | KU, | ||
character | PACK, | ||
real, dimension( lda, * ) | A, | ||
integer | LDA, | ||
real, dimension( * ) | WORK, | ||
integer | INFO | ||
) |
SLATMS
SLATMS generates random matrices with specified singular values (or symmetric/hermitian with specified eigenvalues) for testing LAPACK programs. SLATMS operates by applying the following sequence of operations: Set the diagonal to D, where D may be input or computed according to MODE, COND, DMAX, and SYM as described below. Generate a matrix with the appropriate band structure, by one of two methods: Method A: Generate a dense M x N matrix by multiplying D on the left and the right by random unitary matrices, then: Reduce the bandwidth according to KL and KU, using Householder transformations. Method B: Convert the bandwidth-0 (i.e., diagonal) matrix to a bandwidth-1 matrix using Givens rotations, "chasing" out-of-band elements back, much as in QR; then convert the bandwidth-1 to a bandwidth-2 matrix, etc. Note that for reasonably small bandwidths (relative to M and N) this requires less storage, as a dense matrix is not generated. Also, for symmetric matrices, only one triangle is generated. Method A is chosen if the bandwidth is a large fraction of the order of the matrix, and LDA is at least M (so a dense matrix can be stored.) Method B is chosen if the bandwidth is small (< 1/2 N for symmetric, < .3 N+M for non-symmetric), or LDA is less than M and not less than the bandwidth. Pack the matrix if desired. Options specified by PACK are: no packing zero out upper half (if symmetric) zero out lower half (if symmetric) store the upper half columnwise (if symmetric or upper triangular) store the lower half columnwise (if symmetric or lower triangular) store the lower triangle in banded format (if symmetric or lower triangular) store the upper triangle in banded format (if symmetric or upper triangular) store the entire matrix in banded format If Method B is chosen, and band format is specified, then the matrix will be generated in the band format, so no repacking will be necessary.
[in] | M | M is INTEGER The number of rows of A. Not modified. |
[in] | N | N is INTEGER The number of columns of A. Not modified. |
[in] | DIST | DIST is CHARACTER*1 On entry, DIST specifies the type of distribution to be used to generate the random eigen-/singular values. 'U' => UNIFORM( 0, 1 ) ( 'U' for uniform ) 'S' => UNIFORM( -1, 1 ) ( 'S' for symmetric ) 'N' => NORMAL( 0, 1 ) ( 'N' for normal ) Not modified. |
[in,out] | ISEED | ISEED is INTEGER array, dimension ( 4 ) On entry ISEED specifies the seed of the random number generator. They should lie between 0 and 4095 inclusive, and ISEED(4) should 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 SLATMS to continue the same random number sequence. Changed on exit. |
[in] | SYM | SYM is CHARACTER*1 If SYM='S' or 'H', the generated matrix is symmetric, with eigenvalues specified by D, COND, MODE, and DMAX; they may be positive, negative, or zero. If SYM='P', the generated matrix is symmetric, with eigenvalues (= singular values) specified by D, COND, MODE, and DMAX; they will not be negative. If SYM='N', the generated matrix is nonsymmetric, with singular values specified by D, COND, MODE, and DMAX; they will not be negative. Not modified. |
[in,out] | D | D is REAL array, dimension ( MIN( M , N ) ) This array is used to specify the singular values or eigenvalues of A (see SYM, above.) If MODE=0, then D is assumed to contain the singular/eigenvalues, otherwise they will be computed according to MODE, COND, and DMAX, and placed in D. Modified if MODE is nonzero. |
[in] | MODE | MODE is INTEGER On entry this describes how the singular/eigenvalues are to be specified: MODE = 0 means use D as input MODE = 1 sets D(1)=1 and D(2:N)=1.0/COND MODE = 2 sets D(1:N-1)=1 and D(N)=1.0/COND MODE = 3 sets D(I)=COND**(-(I-1)/(N-1)) MODE = 4 sets D(i)=1 - (i-1)/(N-1)*(1 - 1/COND) MODE = 5 sets D to random numbers in the range ( 1/COND , 1 ) such that their logarithms are uniformly distributed. MODE = 6 set D to random numbers from same distribution as the rest of the matrix. MODE < 0 has the same meaning as ABS(MODE), except that the order of the elements of D is reversed. Thus if MODE is positive, D has entries ranging from 1 to 1/COND, if negative, from 1/COND to 1, If SYM='S' or 'H', and MODE is neither 0, 6, nor -6, then the elements of D will also be multiplied by a random sign (i.e., +1 or -1.) Not modified. |
[in] | COND | COND is REAL On entry, this is used as described under MODE above. If used, it must be >= 1. Not modified. |
[in] | DMAX | DMAX is REAL If MODE is neither -6, 0 nor 6, the contents of D, as computed according to MODE and COND, will be scaled by DMAX / max(abs(D(i))); thus, the maximum absolute eigen- or singular value (which is to say the norm) will be abs(DMAX). Note that DMAX need not be positive: if DMAX is negative (or zero), D will be scaled by a negative number (or zero). Not modified. |
[in] | KL | KL is INTEGER This specifies the lower bandwidth of the matrix. For example, KL=0 implies upper triangular, KL=1 implies upper Hessenberg, and KL being at least M-1 means that the matrix has full lower bandwidth. KL must equal KU if the matrix is symmetric. Not modified. |
[in] | KU | KU is INTEGER This specifies the upper bandwidth of the matrix. For example, KU=0 implies lower triangular, KU=1 implies lower Hessenberg, and KU being at least N-1 means that the matrix has full upper bandwidth. KL must equal KU if the matrix is symmetric. Not modified. |
[in] | PACK | PACK is CHARACTER*1 This specifies packing of matrix as follows: 'N' => no packing 'U' => zero out all subdiagonal entries (if symmetric) 'L' => zero out all superdiagonal entries (if symmetric) 'C' => store the upper triangle columnwise (only if the matrix is symmetric or upper triangular) 'R' => store the lower triangle columnwise (only if the matrix is symmetric or lower triangular) 'B' => store the lower triangle in band storage scheme (only if matrix symmetric or lower triangular) 'Q' => store the upper triangle in band storage scheme (only if matrix symmetric or upper triangular) 'Z' => store the entire matrix in band storage scheme (pivoting can be provided for by using this option to store A in the trailing rows of the allocated storage) Using these options, the various LAPACK packed and banded storage schemes can be obtained: GB - use 'Z' PB, SB or TB - use 'B' or 'Q' PP, SP or TP - use 'C' or 'R' If two calls to SLATMS differ only in the PACK parameter, they will generate mathematically equivalent matrices. Not modified. |
[in,out] | A | A is REAL array, dimension ( LDA, N ) On exit A is the desired test matrix. A is first generated in full (unpacked) form, and then packed, if so specified by PACK. Thus, the first M elements of the first N columns will always be modified. If PACK specifies a packed or banded storage scheme, all LDA elements of the first N columns will be modified; the elements of the array which do not correspond to elements of the generated matrix are set to zero. Modified. |
[in] | LDA | LDA is INTEGER LDA specifies the first dimension of A as declared in the calling program. If PACK='N', 'U', 'L', 'C', or 'R', then LDA must be at least M. If PACK='B' or 'Q', then LDA must be at least MIN( KL, M-1) (which is equal to MIN(KU,N-1)). If PACK='Z', LDA must be large enough to hold the packed array: MIN( KU, N-1) + MIN( KL, M-1) + 1. Not modified. |
[out] | WORK | WORK is REAL array, dimension ( 3*MAX( N , M ) ) Workspace. Modified. |
[out] | INFO | INFO is INTEGER Error code. On exit, INFO will be set to one of the following values: 0 => normal return -1 => M negative or unequal to N and SYM='S', 'H', or 'P' -2 => N negative -3 => DIST illegal string -5 => SYM illegal string -7 => MODE not in range -6 to 6 -8 => COND less than 1.0, and MODE neither -6, 0 nor 6 -10 => KL negative -11 => KU negative, or SYM='S' or 'H' and KU not equal to KL -12 => PACK illegal string, or PACK='U' or 'L', and SYM='N'; or PACK='C' or 'Q' and SYM='N' and KL is not zero; or PACK='R' or 'B' and SYM='N' and KU is not zero; or PACK='U', 'L', 'C', 'R', 'B', or 'Q', and M is not N. -14 => LDA is less than M, or PACK='Z' and LDA is less than MIN(KU,N-1) + MIN(KL,M-1) + 1. 1 => Error return from SLATM1 2 => Cannot scale to DMAX (max. sing. value is 0) 3 => Error return from SLAGGE or SLAGSY |
Definition at line 321 of file slatms.f.
subroutine slatmt | ( | integer | M, |
integer | N, | ||
character | DIST, | ||
integer, dimension( 4 ) | ISEED, | ||
character | SYM, | ||
real, dimension( * ) | D, | ||
integer | MODE, | ||
real | COND, | ||
real | DMAX, | ||
integer | RANK, | ||
integer | KL, | ||
integer | KU, | ||
character | PACK, | ||
real, dimension( lda, * ) | A, | ||
integer | LDA, | ||
real, dimension( * ) | WORK, | ||
integer | INFO | ||
) |
SLATMT
SLATMT generates random matrices with specified singular values (or symmetric/hermitian with specified eigenvalues) for testing LAPACK programs. SLATMT operates by applying the following sequence of operations: Set the diagonal to D, where D may be input or computed according to MODE, COND, DMAX, and SYM as described below. Generate a matrix with the appropriate band structure, by one of two methods: Method A: Generate a dense M x N matrix by multiplying D on the left and the right by random unitary matrices, then: Reduce the bandwidth according to KL and KU, using Householder transformations. Method B: Convert the bandwidth-0 (i.e., diagonal) matrix to a bandwidth-1 matrix using Givens rotations, "chasing" out-of-band elements back, much as in QR; then convert the bandwidth-1 to a bandwidth-2 matrix, etc. Note that for reasonably small bandwidths (relative to M and N) this requires less storage, as a dense matrix is not generated. Also, for symmetric matrices, only one triangle is generated. Method A is chosen if the bandwidth is a large fraction of the order of the matrix, and LDA is at least M (so a dense matrix can be stored.) Method B is chosen if the bandwidth is small (< 1/2 N for symmetric, < .3 N+M for non-symmetric), or LDA is less than M and not less than the bandwidth. Pack the matrix if desired. Options specified by PACK are: no packing zero out upper half (if symmetric) zero out lower half (if symmetric) store the upper half columnwise (if symmetric or upper triangular) store the lower half columnwise (if symmetric or lower triangular) store the lower triangle in banded format (if symmetric or lower triangular) store the upper triangle in banded format (if symmetric or upper triangular) store the entire matrix in banded format If Method B is chosen, and band format is specified, then the matrix will be generated in the band format, so no repacking will be necessary.
[in] | M | M is INTEGER The number of rows of A. Not modified. |
[in] | N | N is INTEGER The number of columns of A. Not modified. |
[in] | DIST | DIST is CHARACTER*1 On entry, DIST specifies the type of distribution to be used to generate the random eigen-/singular values. 'U' => UNIFORM( 0, 1 ) ( 'U' for uniform ) 'S' => UNIFORM( -1, 1 ) ( 'S' for symmetric ) 'N' => NORMAL( 0, 1 ) ( 'N' for normal ) Not modified. |
[in,out] | ISEED | ISEED is INTEGER array, dimension ( 4 ) On entry ISEED specifies the seed of the random number generator. They should lie between 0 and 4095 inclusive, and ISEED(4) should 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 SLATMT to continue the same random number sequence. Changed on exit. |
[in] | SYM | SYM is CHARACTER*1 If SYM='S' or 'H', the generated matrix is symmetric, with eigenvalues specified by D, COND, MODE, and DMAX; they may be positive, negative, or zero. If SYM='P', the generated matrix is symmetric, with eigenvalues (= singular values) specified by D, COND, MODE, and DMAX; they will not be negative. If SYM='N', the generated matrix is nonsymmetric, with singular values specified by D, COND, MODE, and DMAX; they will not be negative. Not modified. |
[in,out] | D | D is REAL array, dimension ( MIN( M , N ) ) This array is used to specify the singular values or eigenvalues of A (see SYM, above.) If MODE=0, then D is assumed to contain the singular/eigenvalues, otherwise they will be computed according to MODE, COND, and DMAX, and placed in D. Modified if MODE is nonzero. |
[in] | MODE | MODE is INTEGER On entry this describes how the singular/eigenvalues are to be specified: MODE = 0 means use D as input MODE = 1 sets D(1)=1 and D(2:RANK)=1.0/COND MODE = 2 sets D(1:RANK-1)=1 and D(RANK)=1.0/COND MODE = 3 sets D(I)=COND**(-(I-1)/(RANK-1)) MODE = 4 sets D(i)=1 - (i-1)/(N-1)*(1 - 1/COND) MODE = 5 sets D to random numbers in the range ( 1/COND , 1 ) such that their logarithms are uniformly distributed. MODE = 6 set D to random numbers from same distribution as the rest of the matrix. MODE < 0 has the same meaning as ABS(MODE), except that the order of the elements of D is reversed. Thus if MODE is positive, D has entries ranging from 1 to 1/COND, if negative, from 1/COND to 1, If SYM='S' or 'H', and MODE is neither 0, 6, nor -6, then the elements of D will also be multiplied by a random sign (i.e., +1 or -1.) Not modified. |
[in] | COND | COND is REAL On entry, this is used as described under MODE above. If used, it must be >= 1. Not modified. |
[in] | DMAX | DMAX is REAL If MODE is neither -6, 0 nor 6, the contents of D, as computed according to MODE and COND, will be scaled by DMAX / max(abs(D(i))); thus, the maximum absolute eigen- or singular value (which is to say the norm) will be abs(DMAX). Note that DMAX need not be positive: if DMAX is negative (or zero), D will be scaled by a negative number (or zero). Not modified. |
[in] | RANK | RANK is INTEGER The rank of matrix to be generated for modes 1,2,3 only. D( RANK+1:N ) = 0. Not modified. |
[in] | KL | KL is INTEGER This specifies the lower bandwidth of the matrix. For example, KL=0 implies upper triangular, KL=1 implies upper Hessenberg, and KL being at least M-1 means that the matrix has full lower bandwidth. KL must equal KU if the matrix is symmetric. Not modified. |
[in] | KU | KU is INTEGER This specifies the upper bandwidth of the matrix. For example, KU=0 implies lower triangular, KU=1 implies lower Hessenberg, and KU being at least N-1 means that the matrix has full upper bandwidth. KL must equal KU if the matrix is symmetric. Not modified. |
[in] | PACK | PACK is CHARACTER*1 This specifies packing of matrix as follows: 'N' => no packing 'U' => zero out all subdiagonal entries (if symmetric) 'L' => zero out all superdiagonal entries (if symmetric) 'C' => store the upper triangle columnwise (only if the matrix is symmetric or upper triangular) 'R' => store the lower triangle columnwise (only if the matrix is symmetric or lower triangular) 'B' => store the lower triangle in band storage scheme (only if matrix symmetric or lower triangular) 'Q' => store the upper triangle in band storage scheme (only if matrix symmetric or upper triangular) 'Z' => store the entire matrix in band storage scheme (pivoting can be provided for by using this option to store A in the trailing rows of the allocated storage) Using these options, the various LAPACK packed and banded storage schemes can be obtained: GB - use 'Z' PB, SB or TB - use 'B' or 'Q' PP, SP or TP - use 'C' or 'R' If two calls to SLATMT differ only in the PACK parameter, they will generate mathematically equivalent matrices. Not modified. |
[in,out] | A | A is REAL array, dimension ( LDA, N ) On exit A is the desired test matrix. A is first generated in full (unpacked) form, and then packed, if so specified by PACK. Thus, the first M elements of the first N columns will always be modified. If PACK specifies a packed or banded storage scheme, all LDA elements of the first N columns will be modified; the elements of the array which do not correspond to elements of the generated matrix are set to zero. Modified. |
[in] | LDA | LDA is INTEGER LDA specifies the first dimension of A as declared in the calling program. If PACK='N', 'U', 'L', 'C', or 'R', then LDA must be at least M. If PACK='B' or 'Q', then LDA must be at least MIN( KL, M-1) (which is equal to MIN(KU,N-1)). If PACK='Z', LDA must be large enough to hold the packed array: MIN( KU, N-1) + MIN( KL, M-1) + 1. Not modified. |
[out] | WORK | WORK is REAL array, dimension ( 3*MAX( N , M ) ) Workspace. Modified. |
[out] | INFO | INFO is INTEGER Error code. On exit, INFO will be set to one of the following values: 0 => normal return -1 => M negative or unequal to N and SYM='S', 'H', or 'P' -2 => N negative -3 => DIST illegal string -5 => SYM illegal string -7 => MODE not in range -6 to 6 -8 => COND less than 1.0, and MODE neither -6, 0 nor 6 -10 => KL negative -11 => KU negative, or SYM='S' or 'H' and KU not equal to KL -12 => PACK illegal string, or PACK='U' or 'L', and SYM='N'; or PACK='C' or 'Q' and SYM='N' and KL is not zero; or PACK='R' or 'B' and SYM='N' and KU is not zero; or PACK='U', 'L', 'C', 'R', 'B', or 'Q', and M is not N. -14 => LDA is less than M, or PACK='Z' and LDA is less than MIN(KU,N-1) + MIN(KL,M-1) + 1. 1 => Error return from SLATM7 2 => Cannot scale to DMAX (max. sing. value is 0) 3 => Error return from SLAGGE or SLAGSY |
Definition at line 331 of file slatmt.f.