LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine slatm7 ( integer  MODE,
real  COND,
integer  IRSIGN,
integer  IDIST,
integer, dimension( 4 )  ISEED,
real, dimension( * )  D,
integer  N,
integer  RANK,
integer  INFO 
)

SLATM7

Purpose:
    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
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
September 2012

Definition at line 124 of file slatm7.f.

124 *
125 * -- LAPACK computational routine (version 3.4.2) --
126 * -- LAPACK is a software package provided by Univ. of Tennessee, --
127 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
128 * September 2012
129 *
130 * .. Scalar Arguments ..
131  REAL cond
132  INTEGER idist, info, irsign, mode, n, rank
133 * ..
134 * .. Array Arguments ..
135  REAL d( * )
136  INTEGER iseed( 4 )
137 * ..
138 *
139 * =====================================================================
140 *
141 * .. Parameters ..
142  REAL one
143  parameter ( one = 1.0e0 )
144  REAL zero
145  parameter ( zero = 0.0e0 )
146  REAL half
147  parameter ( half = 0.5e0 )
148 * ..
149 * .. Local Scalars ..
150  REAL alpha, temp
151  INTEGER i
152 * ..
153 * .. External Functions ..
154  REAL slaran
155  EXTERNAL slaran
156 * ..
157 * .. External Subroutines ..
158  EXTERNAL slarnv, xerbla
159 * ..
160 * .. Intrinsic Functions ..
161  INTRINSIC abs, exp, log, real
162 * ..
163 * .. Executable Statements ..
164 *
165 * Decode and Test the input parameters. Initialize flags & seed.
166 *
167  info = 0
168 *
169 * Quick return if possible
170 *
171  IF( n.EQ.0 )
172  $ RETURN
173 *
174 * Set INFO if an error
175 *
176  IF( mode.LT.-6 .OR. mode.GT.6 ) THEN
177  info = -1
178  ELSE IF( ( mode.NE.-6 .AND. mode.NE.0 .AND. mode.NE.6 ) .AND.
179  $ ( irsign.NE.0 .AND. irsign.NE.1 ) ) THEN
180  info = -2
181  ELSE IF( ( mode.NE.-6 .AND. mode.NE.0 .AND. mode.NE.6 ) .AND.
182  $ cond.LT.one ) THEN
183  info = -3
184  ELSE IF( ( mode.EQ.6 .OR. mode.EQ.-6 ) .AND.
185  $ ( idist.LT.1 .OR. idist.GT.3 ) ) THEN
186  info = -4
187  ELSE IF( n.LT.0 ) THEN
188  info = -7
189  END IF
190 *
191  IF( info.NE.0 ) THEN
192  CALL xerbla( 'SLATM7', -info )
193  RETURN
194  END IF
195 *
196 * Compute D according to COND and MODE
197 *
198  IF( mode.NE.0 ) THEN
199  GO TO ( 100, 130, 160, 190, 210, 230 )abs( mode )
200 *
201 * One large D value:
202 *
203  100 CONTINUE
204  DO 110 i = 2, rank
205  d( i ) = one / cond
206  110 CONTINUE
207  DO 120 i = rank + 1, n
208  d( i ) = zero
209  120 CONTINUE
210  d( 1 ) = one
211  GO TO 240
212 *
213 * One small D value:
214 *
215  130 CONTINUE
216  DO 140 i = 1, rank - 1
217  d( i ) = one
218  140 CONTINUE
219  DO 150 i = rank + 1, n
220  d( i ) = zero
221  150 CONTINUE
222  d( rank ) = one / cond
223  GO TO 240
224 *
225 * Exponentially distributed D values:
226 *
227  160 CONTINUE
228  d( 1 ) = one
229  IF( n.GT.1 .AND. rank.GT.1 ) THEN
230  alpha = cond**( -one / REAL( RANK-1 ) )
231  DO 170 i = 2, rank
232  d( i ) = alpha**( i-1 )
233  170 CONTINUE
234  DO 180 i = rank + 1, n
235  d( i ) = zero
236  180 CONTINUE
237  END IF
238  GO TO 240
239 *
240 * Arithmetically distributed D values:
241 *
242  190 CONTINUE
243  d( 1 ) = one
244  IF( n.GT.1 ) THEN
245  temp = one / cond
246  alpha = ( one-temp ) / REAL( n-1 )
247  DO 200 i = 2, n
248  d( i ) = REAL( n-i )*alpha + temp
249  200 CONTINUE
250  END IF
251  GO TO 240
252 *
253 * Randomly distributed D values on ( 1/COND , 1):
254 *
255  210 CONTINUE
256  alpha = log( one / cond )
257  DO 220 i = 1, n
258  d( i ) = exp( alpha*slaran( iseed ) )
259  220 CONTINUE
260  GO TO 240
261 *
262 * Randomly distributed D values from IDIST
263 *
264  230 CONTINUE
265  CALL slarnv( idist, iseed, n, d )
266 *
267  240 CONTINUE
268 *
269 * If MODE neither -6 nor 0 nor 6, and IRSIGN = 1, assign
270 * random signs to D
271 *
272  IF( ( mode.NE.-6 .AND. mode.NE.0 .AND. mode.NE.6 ) .AND.
273  $ irsign.EQ.1 ) THEN
274  DO 250 i = 1, n
275  temp = slaran( iseed )
276  IF( temp.GT.half )
277  $ d( i ) = -d( i )
278  250 CONTINUE
279  END IF
280 *
281 * Reverse if MODE < 0
282 *
283  IF( mode.LT.0 ) THEN
284  DO 260 i = 1, n / 2
285  temp = d( i )
286  d( i ) = d( n+1-i )
287  d( n+1-i ) = temp
288  260 CONTINUE
289  END IF
290 *
291  END IF
292 *
293  RETURN
294 *
295 * End of SLATM7
296 *
subroutine slarnv(IDIST, ISEED, N, X)
SLARNV returns a vector of random numbers from a uniform or normal distribution.
Definition: slarnv.f:99
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
real function slaran(ISEED)
SLARAN
Definition: slaran.f:69

Here is the call graph for this function:

Here is the caller graph for this function: