LAPACK 3.3.0

clatm1.f

Go to the documentation of this file.
00001       SUBROUTINE CLATM1( MODE, COND, IRSIGN, IDIST, ISEED, D, N, INFO )
00002 *
00003 *  -- LAPACK auxiliary test routine (version 3.1) --
00004 *     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
00005 *     June 2010
00006 *
00007 *     .. Scalar Arguments ..
00008       INTEGER            IDIST, INFO, IRSIGN, MODE, N
00009       REAL               COND
00010 *     ..
00011 *     .. Array Arguments ..
00012       INTEGER            ISEED( 4 )
00013       COMPLEX            D( * )
00014 *     ..
00015 *
00016 *  Purpose
00017 *  =======
00018 *
00019 *     CLATM1 computes the entries of D(1..N) as specified by
00020 *     MODE, COND and IRSIGN. IDIST and ISEED determine the generation
00021 *     of random numbers. CLATM1 is called by CLATMR to generate
00022 *     random test matrices for LAPACK programs.
00023 *
00024 *  Arguments
00025 *  =========
00026 *
00027 *  MODE     (input) INTEGER
00028 *           On entry describes how D is to be computed:
00029 *           MODE = 0 means do not change D.
00030 *           MODE = 1 sets D(1)=1 and D(2:N)=1.0/COND
00031 *           MODE = 2 sets D(1:N-1)=1 and D(N)=1.0/COND
00032 *           MODE = 3 sets D(I)=COND**(-(I-1)/(N-1))
00033 *           MODE = 4 sets D(i)=1 - (i-1)/(N-1)*(1 - 1/COND)
00034 *           MODE = 5 sets D to random numbers in the range
00035 *                    ( 1/COND , 1 ) such that their logarithms
00036 *                    are uniformly distributed.
00037 *           MODE = 6 set D to random numbers from same distribution
00038 *                    as the rest of the matrix.
00039 *           MODE < 0 has the same meaning as ABS(MODE), except that
00040 *              the order of the elements of D is reversed.
00041 *           Thus if MODE is positive, D has entries ranging from
00042 *              1 to 1/COND, if negative, from 1/COND to 1,
00043 *           Not modified.
00044 *
00045 *  COND     (input) REAL
00046 *           On entry, used as described under MODE above.
00047 *           If used, it must be >= 1. Not modified.
00048 *
00049 *  IRSIGN   (input) INTEGER
00050 *           On entry, if MODE neither -6, 0 nor 6, determines sign of
00051 *           entries of D
00052 *           0 => leave entries of D unchanged
00053 *           1 => multiply each entry of D by random complex number
00054 *                uniformly distributed with absolute value 1
00055 *
00056 *  IDIST    (input) CHARACTER*1
00057 *           On entry, IDIST specifies the type of distribution to be
00058 *           used to generate a random matrix .
00059 *           1 => real and imaginary parts each UNIFORM( 0, 1 )
00060 *           2 => real and imaginary parts each UNIFORM( -1, 1 )
00061 *           3 => real and imaginary parts each NORMAL( 0, 1 )
00062 *           4 => complex number uniform in DISK( 0, 1 )
00063 *           Not modified.
00064 *
00065 *  ISEED    (input/output) INTEGER array, dimension ( 4 )
00066 *           On entry ISEED specifies the seed of the random number
00067 *           generator. The random number generator uses a
00068 *           linear congruential sequence limited to small
00069 *           integers, and so should produce machine independent
00070 *           random numbers. The values of ISEED are changed on
00071 *           exit, and can be used in the next call to CLATM1
00072 *           to continue the same random number sequence.
00073 *           Changed on exit.
00074 *
00075 *  D        (input/output) COMPLEX array, dimension ( MIN( M , N ) )
00076 *           Array to be computed according to MODE, COND and IRSIGN.
00077 *           May be changed on exit if MODE is nonzero.
00078 *
00079 *  N        (input) INTEGER
00080 *           Number of entries of D. Not modified.
00081 *
00082 *  INFO     (output) INTEGER
00083 *            0  => normal termination
00084 *           -1  => if MODE not in range -6 to 6
00085 *           -2  => if MODE neither -6, 0 nor 6, and
00086 *                  IRSIGN neither 0 nor 1
00087 *           -3  => if MODE neither -6, 0 nor 6 and COND less than 1
00088 *           -4  => if MODE equals 6 or -6 and IDIST not in range 1 to 4
00089 *           -7  => if N negative
00090 *
00091 *  =====================================================================
00092 *
00093 *     .. Parameters ..
00094       REAL               ONE
00095       PARAMETER          ( ONE = 1.0E0 )
00096 *     ..
00097 *     .. Local Scalars ..
00098       INTEGER            I
00099       REAL               ALPHA, TEMP
00100       COMPLEX            CTEMP
00101 *     ..
00102 *     .. External Functions ..
00103       REAL               SLARAN
00104       COMPLEX            CLARND
00105       EXTERNAL           SLARAN, CLARND
00106 *     ..
00107 *     .. External Subroutines ..
00108       EXTERNAL           CLARNV, XERBLA
00109 *     ..
00110 *     .. Intrinsic Functions ..
00111       INTRINSIC          ABS, EXP, LOG, REAL
00112 *     ..
00113 *     .. Executable Statements ..
00114 *
00115 *     Decode and Test the input parameters. Initialize flags & seed.
00116 *
00117       INFO = 0
00118 *
00119 *     Quick return if possible
00120 *
00121       IF( N.EQ.0 )
00122      $   RETURN
00123 *
00124 *     Set INFO if an error
00125 *
00126       IF( MODE.LT.-6 .OR. MODE.GT.6 ) THEN
00127          INFO = -1
00128       ELSE IF( ( MODE.NE.-6 .AND. MODE.NE.0 .AND. MODE.NE.6 ) .AND.
00129      $         ( IRSIGN.NE.0 .AND. IRSIGN.NE.1 ) ) THEN
00130          INFO = -2
00131       ELSE IF( ( MODE.NE.-6 .AND. MODE.NE.0 .AND. MODE.NE.6 ) .AND.
00132      $         COND.LT.ONE ) THEN
00133          INFO = -3
00134       ELSE IF( ( MODE.EQ.6 .OR. MODE.EQ.-6 ) .AND.
00135      $         ( IDIST.LT.1 .OR. IDIST.GT.4 ) ) THEN
00136          INFO = -4
00137       ELSE IF( N.LT.0 ) THEN
00138          INFO = -7
00139       END IF
00140 *
00141       IF( INFO.NE.0 ) THEN
00142          CALL XERBLA( 'CLATM1', -INFO )
00143          RETURN
00144       END IF
00145 *
00146 *     Compute D according to COND and MODE
00147 *
00148       IF( MODE.NE.0 ) THEN
00149          GO TO ( 10, 30, 50, 70, 90, 110 )ABS( MODE )
00150 *
00151 *        One large D value:
00152 *
00153    10    CONTINUE
00154          DO 20 I = 1, N
00155             D( I ) = ONE / COND
00156    20    CONTINUE
00157          D( 1 ) = ONE
00158          GO TO 120
00159 *
00160 *        One small D value:
00161 *
00162    30    CONTINUE
00163          DO 40 I = 1, N
00164             D( I ) = ONE
00165    40    CONTINUE
00166          D( N ) = ONE / COND
00167          GO TO 120
00168 *
00169 *        Exponentially distributed D values:
00170 *
00171    50    CONTINUE
00172          D( 1 ) = ONE
00173          IF( N.GT.1 ) THEN
00174             ALPHA = COND**( -ONE / REAL( N-1 ) )
00175             DO 60 I = 2, N
00176                D( I ) = ALPHA**( I-1 )
00177    60       CONTINUE
00178          END IF
00179          GO TO 120
00180 *
00181 *        Arithmetically distributed D values:
00182 *
00183    70    CONTINUE
00184          D( 1 ) = ONE
00185          IF( N.GT.1 ) THEN
00186             TEMP = ONE / COND
00187             ALPHA = ( ONE-TEMP ) / REAL( N-1 )
00188             DO 80 I = 2, N
00189                D( I ) = REAL( N-I )*ALPHA + TEMP
00190    80       CONTINUE
00191          END IF
00192          GO TO 120
00193 *
00194 *        Randomly distributed D values on ( 1/COND , 1):
00195 *
00196    90    CONTINUE
00197          ALPHA = LOG( ONE / COND )
00198          DO 100 I = 1, N
00199             D( I ) = EXP( ALPHA*SLARAN( ISEED ) )
00200   100    CONTINUE
00201          GO TO 120
00202 *
00203 *        Randomly distributed D values from IDIST
00204 *
00205   110    CONTINUE
00206          CALL CLARNV( IDIST, ISEED, N, D )
00207 *
00208   120    CONTINUE
00209 *
00210 *        If MODE neither -6 nor 0 nor 6, and IRSIGN = 1, assign
00211 *        random signs to D
00212 *
00213          IF( ( MODE.NE.-6 .AND. MODE.NE.0 .AND. MODE.NE.6 ) .AND.
00214      $       IRSIGN.EQ.1 ) THEN
00215             DO 130 I = 1, N
00216                CTEMP = CLARND( 3, ISEED )
00217                D( I ) = D( I )*( CTEMP / ABS( CTEMP ) )
00218   130       CONTINUE
00219          END IF
00220 *
00221 *        Reverse if MODE < 0
00222 *
00223          IF( MODE.LT.0 ) THEN
00224             DO 140 I = 1, N / 2
00225                CTEMP = D( I )
00226                D( I ) = D( N+1-I )
00227                D( N+1-I ) = CTEMP
00228   140       CONTINUE
00229          END IF
00230 *
00231       END IF
00232 *
00233       RETURN
00234 *
00235 *     End of CLATM1
00236 *
00237       END
 All Files Functions