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