LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ dlatm7()

subroutine dlatm7 ( integer  mode,
double precision  cond,
integer  irsign,
integer  idist,
integer, dimension( 4 )  iseed,
double precision, dimension( * )  d,
integer  n,
integer  rank,
integer  info 
)

DLATM7

Purpose:
    DLATM7 computes the entries of D as specified by MODE
    COND and IRSIGN. IDIST and ISEED determine the generation
    of random numbers. DLATM7 is called by DLATMT 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   - DOUBLE PRECISION
           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 DLATM7
           to continue the same random number sequence.
           Changed on exit.

  D      - DOUBLE PRECISION 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.

Definition at line 120 of file dlatm7.f.

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