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

◆ zlatm1()

subroutine zlatm1 ( integer mode,
double precision cond,
integer irsign,
integer idist,
integer, dimension( 4 ) iseed,
complex*16, dimension( * ) d,
integer n,
integer info )

ZLATM1

Purpose:
!>
!>    ZLATM1 computes the entries of D(1..N) as specified by
!>    MODE, COND and IRSIGN. IDIST and ISEED determine the generation
!>    of random numbers. ZLATM1 is called by ZLATMR to generate
!>    random test matrices for LAPACK programs.
!> 
Parameters
[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 DOUBLE PRECISION
!>           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 random complex number
!>                uniformly distributed with absolute value 1
!> 
[in]IDIST
!>          IDIST is INTEGER
!>           On entry, IDIST specifies the type of distribution to be
!>           used to generate a random matrix .
!>           1 => real and imaginary parts each UNIFORM( 0, 1 )
!>           2 => real and imaginary parts each UNIFORM( -1, 1 )
!>           3 => real and imaginary parts each NORMAL( 0, 1 )
!>           4 => complex number uniform in DISK( 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 ZLATM1
!>           to continue the same random number sequence.
!>           Changed on exit.
!> 
[in,out]D
!>          D is COMPLEX*16 array, dimension ( 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 4
!>           -7  => if N negative
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 136 of file zlatm1.f.

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