LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
clatm2.f
Go to the documentation of this file.
1*> \brief \b CLATM2
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8* Definition:
9* ===========
10*
11* COMPLEX FUNCTION CLATM2( M, N, I, J, KL, KU, IDIST, ISEED, D,
12* IGRADE, DL, DR, IPVTNG, IWORK, SPARSE )
13*
14* .. Scalar Arguments ..
15*
16* INTEGER I, IDIST, IGRADE, IPVTNG, J, KL, KU, M, N
17* REAL SPARSE
18* ..
19*
20* .. Array Arguments ..
21*
22* INTEGER ISEED( 4 ), IWORK( * )
23* COMPLEX D( * ), DL( * ), DR( * )
24* ..
25*
26*
27*> \par Purpose:
28* =============
29*>
30*> \verbatim
31*>
32*> CLATM2 returns the (I,J) entry of a random matrix of dimension
33*> (M, N) described by the other parameters. It is called by the
34*> CLATMR routine in order to build random test matrices. No error
35*> checking on parameters is done, because this routine is called in
36*> a tight loop by CLATMR which has already checked the parameters.
37*>
38*> Use of CLATM2 differs from CLATM3 in the order in which the random
39*> number generator is called to fill in random matrix entries.
40*> With CLATM2, the generator is called to fill in the pivoted matrix
41*> columnwise. With CLATM3, the generator is called to fill in the
42*> matrix columnwise, after which it is pivoted. Thus, CLATM3 can
43*> be used to construct random matrices which differ only in their
44*> order of rows and/or columns. CLATM2 is used to construct band
45*> matrices while avoiding calling the random number generator for
46*> entries outside the band (and therefore generating random numbers
47*>
48*> The matrix whose (I,J) entry is returned is constructed as
49*> follows (this routine only computes one entry):
50*>
51*> If I is outside (1..M) or J is outside (1..N), return zero
52*> (this is convenient for generating matrices in band format).
53*>
54*> Generate a matrix A with random entries of distribution IDIST.
55*>
56*> Set the diagonal to D.
57*>
58*> Grade the matrix, if desired, from the left (by DL) and/or
59*> from the right (by DR or DL) as specified by IGRADE.
60*>
61*> Permute, if desired, the rows and/or columns as specified by
62*> IPVTNG and IWORK.
63*>
64*> Band the matrix to have lower bandwidth KL and upper
65*> bandwidth KU.
66*>
67*> Set random entries to zero as specified by SPARSE.
68*> \endverbatim
69*
70* Arguments:
71* ==========
72*
73*> \param[in] M
74*> \verbatim
75*> M is INTEGER
76*> Number of rows of matrix. Not modified.
77*> \endverbatim
78*>
79*> \param[in] N
80*> \verbatim
81*> N is INTEGER
82*> Number of columns of matrix. Not modified.
83*> \endverbatim
84*>
85*> \param[in] I
86*> \verbatim
87*> I is INTEGER
88*> Row of entry to be returned. Not modified.
89*> \endverbatim
90*>
91*> \param[in] J
92*> \verbatim
93*> J is INTEGER
94*> Column of entry to be returned. Not modified.
95*> \endverbatim
96*>
97*> \param[in] KL
98*> \verbatim
99*> KL is INTEGER
100*> Lower bandwidth. Not modified.
101*> \endverbatim
102*>
103*> \param[in] KU
104*> \verbatim
105*> KU is INTEGER
106*> Upper bandwidth. Not modified.
107*> \endverbatim
108*>
109*> \param[in] IDIST
110*> \verbatim
111*> IDIST is INTEGER
112*> On entry, IDIST specifies the type of distribution to be
113*> used to generate a random matrix .
114*> 1 => real and imaginary parts each UNIFORM( 0, 1 )
115*> 2 => real and imaginary parts each UNIFORM( -1, 1 )
116*> 3 => real and imaginary parts each NORMAL( 0, 1 )
117*> 4 => complex number uniform in DISK( 0 , 1 )
118*> Not modified.
119*> \endverbatim
120*>
121*> \param[in,out] ISEED
122*> \verbatim
123*> ISEED is INTEGER array of dimension ( 4 )
124*> Seed for random number generator.
125*> Changed on exit.
126*> \endverbatim
127*>
128*> \param[in] D
129*> \verbatim
130*> D is COMPLEX array of dimension ( MIN( I , J ) )
131*> Diagonal entries of matrix. Not modified.
132*> \endverbatim
133*>
134*> \param[in] IGRADE
135*> \verbatim
136*> IGRADE is INTEGER
137*> Specifies grading of matrix as follows:
138*> 0 => no grading
139*> 1 => matrix premultiplied by diag( DL )
140*> 2 => matrix postmultiplied by diag( DR )
141*> 3 => matrix premultiplied by diag( DL ) and
142*> postmultiplied by diag( DR )
143*> 4 => matrix premultiplied by diag( DL ) and
144*> postmultiplied by inv( diag( DL ) )
145*> 5 => matrix premultiplied by diag( DL ) and
146*> postmultiplied by diag( CONJG(DL) )
147*> 6 => matrix premultiplied by diag( DL ) and
148*> postmultiplied by diag( DL )
149*> Not modified.
150*> \endverbatim
151*>
152*> \param[in] DL
153*> \verbatim
154*> DL is COMPLEX array ( I or J, as appropriate )
155*> Left scale factors for grading matrix. Not modified.
156*> \endverbatim
157*>
158*> \param[in] DR
159*> \verbatim
160*> DR is COMPLEX array ( I or J, as appropriate )
161*> Right scale factors for grading matrix. Not modified.
162*> \endverbatim
163*>
164*> \param[in] IPVTNG
165*> \verbatim
166*> IPVTNG is INTEGER
167*> On entry specifies pivoting permutations as follows:
168*> 0 => none.
169*> 1 => row pivoting.
170*> 2 => column pivoting.
171*> 3 => full pivoting, i.e., on both sides.
172*> Not modified.
173*> \endverbatim
174*>
175*> \param[out] IWORK
176*> \verbatim
177*> IWORK is INTEGER array ( I or J, as appropriate )
178*> This array specifies the permutation used. The
179*> row (or column) in position K was originally in
180*> position IWORK( K ).
181*> This differs from IWORK for CLATM3. Not modified.
182*> \endverbatim
183*>
184*> \param[in] SPARSE
185*> \verbatim
186*> SPARSE is REAL
187*> Value between 0. and 1.
188*> On entry specifies the sparsity of the matrix
189*> if sparse matrix is to be generated.
190*> SPARSE should lie between 0 and 1.
191*> A uniform ( 0, 1 ) random number x is generated and
192*> compared to SPARSE; if x is larger the matrix entry
193*> is unchanged and if x is smaller the entry is set
194*> to zero. Thus on the average a fraction SPARSE of the
195*> entries will be set to zero.
196*> Not modified.
197*> \endverbatim
198*
199* Authors:
200* ========
201*
202*> \author Univ. of Tennessee
203*> \author Univ. of California Berkeley
204*> \author Univ. of Colorado Denver
205*> \author NAG Ltd.
206*
207*> \ingroup complex_matgen
208*
209* =====================================================================
210 COMPLEX FUNCTION clatm2( M, N, I, J, KL, KU, IDIST, ISEED, D,
211 $ IGRADE, DL, DR, IPVTNG, IWORK, SPARSE )
212*
213* -- LAPACK auxiliary routine --
214* -- LAPACK is a software package provided by Univ. of Tennessee, --
215* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
216*
217* .. Scalar Arguments ..
218*
219 INTEGER i, idist, igrade, ipvtng, j, kl, ku, m, n
220 REAL sparse
221* ..
222*
223* .. Array Arguments ..
224*
225 INTEGER iseed( 4 ), iwork( * )
226 COMPLEX d( * ), dl( * ), dr( * )
227* ..
228*
229* =====================================================================
230*
231* .. Parameters ..
232*
233 COMPLEX czero
234 parameter( czero = ( 0.0e0, 0.0e0 ) )
235 REAL zero
236 parameter( zero = 0.0e0 )
237* ..
238*
239* .. Local Scalars ..
240*
241 INTEGER isub, jsub
242 COMPLEX ctemp
243* ..
244*
245* .. External Functions ..
246*
247 REAL slaran
248 COMPLEX clarnd
249 EXTERNAL slaran, clarnd
250* ..
251*
252* .. Intrinsic Functions ..
253*
254 INTRINSIC conjg
255* ..
256*
257*-----------------------------------------------------------------------
258*
259* .. Executable Statements ..
260*
261*
262* Check for I and J in range
263*
264 IF( i.LT.1 .OR. i.GT.m .OR. j.LT.1 .OR. j.GT.n ) THEN
265 clatm2 = czero
266 RETURN
267 END IF
268*
269* Check for banding
270*
271 IF( j.GT.i+ku .OR. j.LT.i-kl ) THEN
272 clatm2 = czero
273 RETURN
274 END IF
275*
276* Check for sparsity
277*
278 IF( sparse.GT.zero ) THEN
279 IF( slaran( iseed ).LT.sparse ) THEN
280 clatm2 = czero
281 RETURN
282 END IF
283 END IF
284*
285* Compute subscripts depending on IPVTNG
286*
287 IF( ipvtng.EQ.0 ) THEN
288 isub = i
289 jsub = j
290 ELSE IF( ipvtng.EQ.1 ) THEN
291 isub = iwork( i )
292 jsub = j
293 ELSE IF( ipvtng.EQ.2 ) THEN
294 isub = i
295 jsub = iwork( j )
296 ELSE IF( ipvtng.EQ.3 ) THEN
297 isub = iwork( i )
298 jsub = iwork( j )
299 END IF
300*
301* Compute entry and grade it according to IGRADE
302*
303 IF( isub.EQ.jsub ) THEN
304 ctemp = d( isub )
305 ELSE
306 ctemp = clarnd( idist, iseed )
307 END IF
308 IF( igrade.EQ.1 ) THEN
309 ctemp = ctemp*dl( isub )
310 ELSE IF( igrade.EQ.2 ) THEN
311 ctemp = ctemp*dr( jsub )
312 ELSE IF( igrade.EQ.3 ) THEN
313 ctemp = ctemp*dl( isub )*dr( jsub )
314 ELSE IF( igrade.EQ.4 .AND. isub.NE.jsub ) THEN
315 ctemp = ctemp*dl( isub ) / dl( jsub )
316 ELSE IF( igrade.EQ.5 ) THEN
317 ctemp = ctemp*dl( isub )*conjg( dl( jsub ) )
318 ELSE IF( igrade.EQ.6 ) THEN
319 ctemp = ctemp*dl( isub )*dl( jsub )
320 END IF
321 clatm2 = ctemp
322 RETURN
323*
324* End of CLATM2
325*
326 END
complex function clarnd(idist, iseed)
CLARND
Definition clarnd.f:75
complex function clatm2(m, n, i, j, kl, ku, idist, iseed, d, igrade, dl, dr, ipvtng, iwork, sparse)
CLATM2
Definition clatm2.f:212
real function slaran(iseed)
SLARAN
Definition slaran.f:67