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