LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zlatm2.f
Go to the documentation of this file.
1*> \brief \b ZLATM2
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*16 FUNCTION ZLATM2( M, N, I, J, KL, KU, IDIST,
12* ISEED, D, IGRADE, DL, DR, IPVTNG, IWORK, SPARSE )
13*
14* .. Scalar Arguments ..
15*
16* INTEGER I, IDIST, IGRADE, IPVTNG, J, KL, KU, M, N
17* DOUBLE PRECISION SPARSE
18* ..
19*
20* .. Array Arguments ..
21*
22* INTEGER ISEED( 4 ), IWORK( * )
23* COMPLEX*16 D( * ), DL( * ), DR( * )
24* ..
25*
26*
27*> \par Purpose:
28* =============
29*>
30*> \verbatim
31*>
32*> ZLATM2 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*> ZLATMR 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 ZLATMR which has already checked the parameters.
37*>
38*> Use of ZLATM2 differs from CLATM3 in the order in which the random
39*> number generator is called to fill in random matrix entries.
40*> With ZLATM2, the generator is called to fill in the pivoted matrix
41*> columnwise. With ZLATM3, the generator is called to fill in the
42*> matrix columnwise, after which it is pivoted. Thus, ZLATM3 can
43*> be used to construct random matrices which differ only in their
44*> order of rows and/or columns. ZLATM2 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*16 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*16 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*16 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 ZLATM3. Not modified.
182*> \endverbatim
183*>
184*> \param[in] SPARSE
185*> \verbatim
186*> SPARSE is DOUBLE PRECISION between 0. and 1.
187*> On entry specifies the sparsity of the matrix
188*> if sparse matrix is to be generated.
189*> SPARSE should lie between 0 and 1.
190*> A uniform ( 0, 1 ) random number x is generated and
191*> compared to SPARSE; if x is larger the matrix entry
192*> is unchanged and if x is smaller the entry is set
193*> to zero. Thus on the average a fraction SPARSE of the
194*> entries will be set to zero.
195*> Not modified.
196*> \endverbatim
197*
198* Authors:
199* ========
200*
201*> \author Univ. of Tennessee
202*> \author Univ. of California Berkeley
203*> \author Univ. of Colorado Denver
204*> \author NAG Ltd.
205*
206*> \ingroup complex16_matgen
207*
208* =====================================================================
209 COMPLEX*16 FUNCTION zlatm2( M, N, I, J, KL, KU, IDIST,
210 $ ISEED, D, IGRADE, DL, DR, IPVTNG, IWORK, SPARSE )
211*
212* -- LAPACK auxiliary routine --
213* -- LAPACK is a software package provided by Univ. of Tennessee, --
214* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
215*
216* .. Scalar Arguments ..
217*
218 INTEGER i, idist, igrade, ipvtng, j, kl, ku, m, n
219 DOUBLE PRECISION sparse
220* ..
221*
222* .. Array Arguments ..
223*
224 INTEGER iseed( 4 ), iwork( * )
225 COMPLEX*16 d( * ), dl( * ), dr( * )
226* ..
227*
228* =====================================================================
229*
230* .. Parameters ..
231*
232 COMPLEX*16 czero
233 parameter( czero = ( 0.0d0, 0.0d0 ) )
234 DOUBLE PRECISION zero
235 parameter( zero = 0.0d0 )
236* ..
237*
238* .. Local Scalars ..
239*
240 INTEGER isub, jsub
241 COMPLEX*16 ctemp
242* ..
243*
244* .. External Functions ..
245*
246 DOUBLE PRECISION dlaran
247 COMPLEX*16 zlarnd
248 EXTERNAL dlaran, zlarnd
249* ..
250*
251* .. Intrinsic Functions ..
252*
253 INTRINSIC dconjg
254* ..
255*
256*-----------------------------------------------------------------------
257*
258* .. Executable Statements ..
259*
260*
261* Check for I and J in range
262*
263 IF( i.LT.1 .OR. i.GT.m .OR. j.LT.1 .OR. j.GT.n ) THEN
264 zlatm2 = czero
265 RETURN
266 END IF
267*
268* Check for banding
269*
270 IF( j.GT.i+ku .OR. j.LT.i-kl ) THEN
271 zlatm2 = czero
272 RETURN
273 END IF
274*
275* Check for sparsity
276*
277 IF( sparse.GT.zero ) THEN
278 IF( dlaran( iseed ).LT.sparse ) THEN
279 zlatm2 = czero
280 RETURN
281 END IF
282 END IF
283*
284* Compute subscripts depending on IPVTNG
285*
286 IF( ipvtng.EQ.0 ) THEN
287 isub = i
288 jsub = j
289 ELSE IF( ipvtng.EQ.1 ) THEN
290 isub = iwork( i )
291 jsub = j
292 ELSE IF( ipvtng.EQ.2 ) THEN
293 isub = i
294 jsub = iwork( j )
295 ELSE IF( ipvtng.EQ.3 ) THEN
296 isub = iwork( i )
297 jsub = iwork( j )
298 END IF
299*
300* Compute entry and grade it according to IGRADE
301*
302 IF( isub.EQ.jsub ) THEN
303 ctemp = d( isub )
304 ELSE
305 ctemp = zlarnd( idist, iseed )
306 END IF
307 IF( igrade.EQ.1 ) THEN
308 ctemp = ctemp*dl( isub )
309 ELSE IF( igrade.EQ.2 ) THEN
310 ctemp = ctemp*dr( jsub )
311 ELSE IF( igrade.EQ.3 ) THEN
312 ctemp = ctemp*dl( isub )*dr( jsub )
313 ELSE IF( igrade.EQ.4 .AND. isub.NE.jsub ) THEN
314 ctemp = ctemp*dl( isub ) / dl( jsub )
315 ELSE IF( igrade.EQ.5 ) THEN
316 ctemp = ctemp*dl( isub )*dconjg( dl( jsub ) )
317 ELSE IF( igrade.EQ.6 ) THEN
318 ctemp = ctemp*dl( isub )*dl( jsub )
319 END IF
320 zlatm2 = ctemp
321 RETURN
322*
323* End of ZLATM2
324*
325 END
double precision function dlaran(iseed)
DLARAN
Definition dlaran.f:67
complex *16 function zlarnd(idist, iseed)
ZLARND
Definition zlarnd.f:75
complex *16 function zlatm2(m, n, i, j, kl, ku, idist, iseed, d, igrade, dl, dr, ipvtng, iwork, sparse)
ZLATM2
Definition zlatm2.f:211