LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zlatm1.f
Go to the documentation of this file.
1*> \brief \b ZLATM1
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8* Definition:
9* ===========
10*
11* SUBROUTINE ZLATM1( MODE, COND, IRSIGN, IDIST, ISEED, D, N, INFO )
12*
13* .. Scalar Arguments ..
14* INTEGER IDIST, INFO, IRSIGN, MODE, N
15* DOUBLE PRECISION COND
16* ..
17* .. Array Arguments ..
18* INTEGER ISEED( 4 )
19* COMPLEX*16 D( * )
20* ..
21*
22*
23*> \par Purpose:
24* =============
25*>
26*> \verbatim
27*>
28*> ZLATM1 computes the entries of D(1..N) as specified by
29*> MODE, COND and IRSIGN. IDIST and ISEED determine the generation
30*> of random numbers. ZLATM1 is called by ZLATMR to generate
31*> random test matrices for LAPACK programs.
32*> \endverbatim
33*
34* Arguments:
35* ==========
36*
37*> \param[in] MODE
38*> \verbatim
39*> MODE is INTEGER
40*> On entry describes how D is to be computed:
41*> MODE = 0 means do not change D.
42*> MODE = 1 sets D(1)=1 and D(2:N)=1.0/COND
43*> MODE = 2 sets D(1:N-1)=1 and D(N)=1.0/COND
44*> MODE = 3 sets D(I)=COND**(-(I-1)/(N-1))
45*> MODE = 4 sets D(i)=1 - (i-1)/(N-1)*(1 - 1/COND)
46*> MODE = 5 sets D to random numbers in the range
47*> ( 1/COND , 1 ) such that their logarithms
48*> are uniformly distributed.
49*> MODE = 6 set D to random numbers from same distribution
50*> as the rest of the matrix.
51*> MODE < 0 has the same meaning as ABS(MODE), except that
52*> the order of the elements of D is reversed.
53*> Thus if MODE is positive, D has entries ranging from
54*> 1 to 1/COND, if negative, from 1/COND to 1,
55*> Not modified.
56*> \endverbatim
57*>
58*> \param[in] COND
59*> \verbatim
60*> COND is DOUBLE PRECISION
61*> On entry, used as described under MODE above.
62*> If used, it must be >= 1. Not modified.
63*> \endverbatim
64*>
65*> \param[in] IRSIGN
66*> \verbatim
67*> IRSIGN is INTEGER
68*> On entry, if MODE neither -6, 0 nor 6, determines sign of
69*> entries of D
70*> 0 => leave entries of D unchanged
71*> 1 => multiply each entry of D by random complex number
72*> uniformly distributed with absolute value 1
73*> \endverbatim
74*>
75*> \param[in] IDIST
76*> \verbatim
77*> IDIST is INTEGER
78*> On entry, IDIST specifies the type of distribution to be
79*> used to generate a random matrix .
80*> 1 => real and imaginary parts each UNIFORM( 0, 1 )
81*> 2 => real and imaginary parts each UNIFORM( -1, 1 )
82*> 3 => real and imaginary parts each NORMAL( 0, 1 )
83*> 4 => complex number uniform in DISK( 0, 1 )
84*> Not modified.
85*> \endverbatim
86*>
87*> \param[in,out] ISEED
88*> \verbatim
89*> ISEED is INTEGER array, dimension ( 4 )
90*> On entry ISEED specifies the seed of the random number
91*> generator. The random number generator uses a
92*> linear congruential sequence limited to small
93*> integers, and so should produce machine independent
94*> random numbers. The values of ISEED are changed on
95*> exit, and can be used in the next call to ZLATM1
96*> to continue the same random number sequence.
97*> Changed on exit.
98*> \endverbatim
99*>
100*> \param[in,out] D
101*> \verbatim
102*> D is COMPLEX*16 array, dimension ( N )
103*> Array to be computed according to MODE, COND and IRSIGN.
104*> May be changed on exit if MODE is nonzero.
105*> \endverbatim
106*>
107*> \param[in] N
108*> \verbatim
109*> N is INTEGER
110*> Number of entries of D. Not modified.
111*> \endverbatim
112*>
113*> \param[out] INFO
114*> \verbatim
115*> INFO is INTEGER
116*> 0 => normal termination
117*> -1 => if MODE not in range -6 to 6
118*> -2 => if MODE neither -6, 0 nor 6, and
119*> IRSIGN neither 0 nor 1
120*> -3 => if MODE neither -6, 0 nor 6 and COND less than 1
121*> -4 => if MODE equals 6 or -6 and IDIST not in range 1 to 4
122*> -7 => if N negative
123*> \endverbatim
124*
125* Authors:
126* ========
127*
128*> \author Univ. of Tennessee
129*> \author Univ. of California Berkeley
130*> \author Univ. of Colorado Denver
131*> \author NAG Ltd.
132*
133*> \ingroup complex16_matgen
134*
135* =====================================================================
136 SUBROUTINE zlatm1( MODE, COND, IRSIGN, IDIST, ISEED, D, N, INFO )
137*
138* -- LAPACK auxiliary routine --
139* -- LAPACK is a software package provided by Univ. of Tennessee, --
140* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
141*
142* .. Scalar Arguments ..
143 INTEGER IDIST, INFO, IRSIGN, MODE, N
144 DOUBLE PRECISION COND
145* ..
146* .. Array Arguments ..
147 INTEGER ISEED( 4 )
148 COMPLEX*16 D( * )
149* ..
150*
151* =====================================================================
152*
153* .. Parameters ..
154 DOUBLE PRECISION ONE
155 parameter( one = 1.0d0 )
156* ..
157* .. Local Scalars ..
158 INTEGER I
159 DOUBLE PRECISION ALPHA, TEMP
160 COMPLEX*16 CTEMP
161* ..
162* .. External Functions ..
163 DOUBLE PRECISION DLARAN
164 COMPLEX*16 ZLARND
165 EXTERNAL dlaran, zlarnd
166* ..
167* .. External Subroutines ..
168 EXTERNAL xerbla, zlarnv
169* ..
170* .. Intrinsic Functions ..
171 INTRINSIC abs, dble, exp, log
172* ..
173* .. Executable Statements ..
174*
175* Decode and Test the input parameters. Initialize flags & seed.
176*
177 info = 0
178*
179* Quick return if possible
180*
181 IF( n.EQ.0 )
182 $ RETURN
183*
184* Set INFO if an error
185*
186 IF( mode.LT.-6 .OR. mode.GT.6 ) THEN
187 info = -1
188 ELSE IF( ( mode.NE.-6 .AND. mode.NE.0 .AND. mode.NE.6 ) .AND.
189 $ ( irsign.NE.0 .AND. irsign.NE.1 ) ) THEN
190 info = -2
191 ELSE IF( ( mode.NE.-6 .AND. mode.NE.0 .AND. mode.NE.6 ) .AND.
192 $ cond.LT.one ) THEN
193 info = -3
194 ELSE IF( ( mode.EQ.6 .OR. mode.EQ.-6 ) .AND.
195 $ ( idist.LT.1 .OR. idist.GT.4 ) ) THEN
196 info = -4
197 ELSE IF( n.LT.0 ) THEN
198 info = -7
199 END IF
200*
201 IF( info.NE.0 ) THEN
202 CALL xerbla( 'ZLATM1', -info )
203 RETURN
204 END IF
205*
206* Compute D according to COND and MODE
207*
208 IF( mode.NE.0 ) THEN
209 GO TO ( 10, 30, 50, 70, 90, 110 )abs( mode )
210*
211* One large D value:
212*
213 10 CONTINUE
214 DO 20 i = 1, n
215 d( i ) = one / cond
216 20 CONTINUE
217 d( 1 ) = one
218 GO TO 120
219*
220* One small D value:
221*
222 30 CONTINUE
223 DO 40 i = 1, n
224 d( i ) = one
225 40 CONTINUE
226 d( n ) = one / cond
227 GO TO 120
228*
229* Exponentially distributed D values:
230*
231 50 CONTINUE
232 d( 1 ) = one
233 IF( n.GT.1 ) THEN
234 alpha = cond**( -one / dble( n-1 ) )
235 DO 60 i = 2, n
236 d( i ) = alpha**( i-1 )
237 60 CONTINUE
238 END IF
239 GO TO 120
240*
241* Arithmetically distributed D values:
242*
243 70 CONTINUE
244 d( 1 ) = one
245 IF( n.GT.1 ) THEN
246 temp = one / cond
247 alpha = ( one-temp ) / dble( n-1 )
248 DO 80 i = 2, n
249 d( i ) = dble( n-i )*alpha + temp
250 80 CONTINUE
251 END IF
252 GO TO 120
253*
254* Randomly distributed D values on ( 1/COND , 1):
255*
256 90 CONTINUE
257 alpha = log( one / cond )
258 DO 100 i = 1, n
259 d( i ) = exp( alpha*dlaran( iseed ) )
260 100 CONTINUE
261 GO TO 120
262*
263* Randomly distributed D values from IDIST
264*
265 110 CONTINUE
266 CALL zlarnv( idist, iseed, n, d )
267*
268 120 CONTINUE
269*
270* If MODE neither -6 nor 0 nor 6, and IRSIGN = 1, assign
271* random signs to D
272*
273 IF( ( mode.NE.-6 .AND. mode.NE.0 .AND. mode.NE.6 ) .AND.
274 $ irsign.EQ.1 ) THEN
275 DO 130 i = 1, n
276 ctemp = zlarnd( 3, iseed )
277 d( i ) = d( i )*( ctemp / abs( ctemp ) )
278 130 CONTINUE
279 END IF
280*
281* Reverse if MODE < 0
282*
283 IF( mode.LT.0 ) THEN
284 DO 140 i = 1, n / 2
285 ctemp = d( i )
286 d( i ) = d( n+1-i )
287 d( n+1-i ) = ctemp
288 140 CONTINUE
289 END IF
290*
291 END IF
292*
293 RETURN
294*
295* End of ZLATM1
296*
297 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zlarnv(idist, iseed, n, x)
ZLARNV returns a vector of random numbers from a uniform or normal distribution.
Definition zlarnv.f:99
subroutine zlatm1(mode, cond, irsign, idist, iseed, d, n, info)
ZLATM1
Definition zlatm1.f:137