LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dlatb9.f
Go to the documentation of this file.
1*> \brief \b DLATB9
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 DLATB9( PATH, IMAT, M, P, N, TYPE, KLA, KUA, KLB, KUB,
12* ANORM, BNORM, MODEA, MODEB, CNDNMA, CNDNMB,
13* DISTA, DISTB )
14*
15* .. Scalar Arguments ..
16* CHARACTER DISTA, DISTB, TYPE
17* CHARACTER*3 PATH
18* INTEGER IMAT, KLA, KLB, KUA, KUB, M, MODEA, MODEB, N, P
19* DOUBLE PRECISION ANORM, BNORM, CNDNMA, CNDNMB
20* ..
21*
22*
23*> \par Purpose:
24* =============
25*>
26*> \verbatim
27*>
28*> DLATB9 sets parameters for the matrix generator based on the type of
29*> matrix to be generated.
30*> \endverbatim
31*
32* Arguments:
33* ==========
34*
35*> \param[in] PATH
36*> \verbatim
37*> PATH is CHARACTER*3
38*> The LAPACK path name.
39*> \endverbatim
40*>
41*> \param[in] IMAT
42*> \verbatim
43*> IMAT is INTEGER
44*> An integer key describing which matrix to generate for this
45*> path.
46*> = 1: A: diagonal, B: upper triangular
47*> = 2: A: upper triangular, B: upper triangular
48*> = 3: A: lower triangular, B: upper triangular
49*> Else: A: general dense, B: general dense
50*> \endverbatim
51*>
52*> \param[in] M
53*> \verbatim
54*> M is INTEGER
55*> The number of rows in the matrix to be generated.
56*> \endverbatim
57*>
58*> \param[in] P
59*> \verbatim
60*> P is INTEGER
61*> \endverbatim
62*>
63*> \param[in] N
64*> \verbatim
65*> N is INTEGER
66*> The number of columns in the matrix to be generated.
67*> \endverbatim
68*>
69*> \param[out] TYPE
70*> \verbatim
71*> TYPE is CHARACTER*1
72*> The type of the matrix to be generated:
73*> = 'S': symmetric matrix;
74*> = 'P': symmetric positive (semi)definite matrix;
75*> = 'N': nonsymmetric matrix.
76*> \endverbatim
77*>
78*> \param[out] KLA
79*> \verbatim
80*> KLA is INTEGER
81*> The lower band width of the matrix to be generated.
82*> \endverbatim
83*>
84*> \param[out] KUA
85*> \verbatim
86*> KUA is INTEGER
87*> The upper band width of the matrix to be generated.
88*> \endverbatim
89*>
90*> \param[out] KLB
91*> \verbatim
92*> KLB is INTEGER
93*> The lower band width of the matrix to be generated.
94*> \endverbatim
95*>
96*> \param[out] KUB
97*> \verbatim
98*> KUA is INTEGER
99*> The upper band width of the matrix to be generated.
100*> \endverbatim
101*>
102*> \param[out] ANORM
103*> \verbatim
104*> ANORM is DOUBLE PRECISION
105*> The desired norm of the matrix to be generated. The diagonal
106*> matrix of singular values or eigenvalues is scaled by this
107*> value.
108*> \endverbatim
109*>
110*> \param[out] BNORM
111*> \verbatim
112*> BNORM is DOUBLE PRECISION
113*> The desired norm of the matrix to be generated. The diagonal
114*> matrix of singular values or eigenvalues is scaled by this
115*> value.
116*> \endverbatim
117*>
118*> \param[out] MODEA
119*> \verbatim
120*> MODEA is INTEGER
121*> A key indicating how to choose the vector of eigenvalues.
122*> \endverbatim
123*>
124*> \param[out] MODEB
125*> \verbatim
126*> MODEB is INTEGER
127*> A key indicating how to choose the vector of eigenvalues.
128*> \endverbatim
129*>
130*> \param[out] CNDNMA
131*> \verbatim
132*> CNDNMA is DOUBLE PRECISION
133*> The desired condition number.
134*> \endverbatim
135*>
136*> \param[out] CNDNMB
137*> \verbatim
138*> CNDNMB is DOUBLE PRECISION
139*> The desired condition number.
140*> \endverbatim
141*>
142*> \param[out] DISTA
143*> \verbatim
144*> DISTA is CHARACTER*1
145*> The type of distribution to be used by the random number
146*> generator.
147*> \endverbatim
148*>
149*> \param[out] DISTB
150*> \verbatim
151*> DISTB is CHARACTER*1
152*> The type of distribution to be used by the random number
153*> generator.
154*> \endverbatim
155*
156* Authors:
157* ========
158*
159*> \author Univ. of Tennessee
160*> \author Univ. of California Berkeley
161*> \author Univ. of Colorado Denver
162*> \author NAG Ltd.
163*
164*> \ingroup double_eig
165*
166* =====================================================================
167 SUBROUTINE dlatb9( PATH, IMAT, M, P, N, TYPE, KLA, KUA, KLB, KUB,
168 $ ANORM, BNORM, MODEA, MODEB, CNDNMA, CNDNMB,
169 $ DISTA, DISTB )
170*
171* -- LAPACK test routine --
172* -- LAPACK is a software package provided by Univ. of Tennessee, --
173* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
174*
175* .. Scalar Arguments ..
176 CHARACTER DISTA, DISTB, TYPE
177 CHARACTER*3 PATH
178 INTEGER IMAT, KLA, KLB, KUA, KUB, M, MODEA, MODEB, N, P
179 DOUBLE PRECISION ANORM, BNORM, CNDNMA, CNDNMB
180* ..
181*
182* =====================================================================
183*
184* .. Parameters ..
185 DOUBLE PRECISION SHRINK, TENTH
186 PARAMETER ( SHRINK = 0.25d0, tenth = 0.1d+0 )
187 DOUBLE PRECISION ONE, TEN
188 parameter( one = 1.0d+0, ten = 1.0d+1 )
189* ..
190* .. Local Scalars ..
191 LOGICAL FIRST
192 DOUBLE PRECISION BADC1, BADC2, EPS, LARGE, SMALL
193* ..
194* .. External Functions ..
195 LOGICAL LSAMEN
196 DOUBLE PRECISION DLAMCH
197 EXTERNAL lsamen, dlamch
198* ..
199* .. Intrinsic Functions ..
200 INTRINSIC max, sqrt
201* ..
202* .. Save statement ..
203 SAVE eps, small, large, badc1, badc2, first
204* ..
205* .. Data statements ..
206 DATA first / .true. /
207* ..
208* .. Executable Statements ..
209*
210* Set some constants for use in the subroutine.
211*
212 IF( first ) THEN
213 first = .false.
214 eps = dlamch( 'Precision' )
215 badc2 = tenth / eps
216 badc1 = sqrt( badc2 )
217 small = dlamch( 'Safe minimum' )
218 large = one / small
219 small = shrink*( small / eps )
220 large = one / small
221 END IF
222*
223* Set some parameters we don't plan to change.
224*
225 TYPE = 'N'
226 dista = 'S'
227 distb = 'S'
228 modea = 3
229 modeb = 4
230*
231* Set the lower and upper bandwidths.
232*
233 IF( lsamen( 3, path, 'GRQ' ) .OR. lsamen( 3, path, 'LSE' ) .OR.
234 $ lsamen( 3, path, 'GSV' ) ) THEN
235*
236* A: M by N, B: P by N
237*
238 IF( imat.EQ.1 ) THEN
239*
240* A: diagonal, B: upper triangular
241*
242 kla = 0
243 kua = 0
244 klb = 0
245 kub = max( n-1, 0 )
246*
247 ELSE IF( imat.EQ.2 ) THEN
248*
249* A: upper triangular, B: upper triangular
250*
251 kla = 0
252 kua = max( n-1, 0 )
253 klb = 0
254 kub = max( n-1, 0 )
255*
256 ELSE IF( imat.EQ.3 ) THEN
257*
258* A: lower triangular, B: upper triangular
259*
260 kla = max( m-1, 0 )
261 kua = 0
262 klb = 0
263 kub = max( n-1, 0 )
264*
265 ELSE
266*
267* A: general dense, B: general dense
268*
269 kla = max( m-1, 0 )
270 kua = max( n-1, 0 )
271 klb = max( p-1, 0 )
272 kub = max( n-1, 0 )
273*
274 END IF
275*
276 ELSE IF( lsamen( 3, path, 'GQR' ) .OR. lsamen( 3, path, 'GLM' ) )
277 $ THEN
278*
279* A: N by M, B: N by P
280*
281 IF( imat.EQ.1 ) THEN
282*
283* A: diagonal, B: lower triangular
284*
285 kla = 0
286 kua = 0
287 klb = max( n-1, 0 )
288 kub = 0
289 ELSE IF( imat.EQ.2 ) THEN
290*
291* A: lower triangular, B: diagonal
292*
293 kla = max( n-1, 0 )
294 kua = 0
295 klb = 0
296 kub = 0
297*
298 ELSE IF( imat.EQ.3 ) THEN
299*
300* A: lower triangular, B: upper triangular
301*
302 kla = max( n-1, 0 )
303 kua = 0
304 klb = 0
305 kub = max( p-1, 0 )
306*
307 ELSE
308*
309* A: general dense, B: general dense
310*
311 kla = max( n-1, 0 )
312 kua = max( m-1, 0 )
313 klb = max( n-1, 0 )
314 kub = max( p-1, 0 )
315 END IF
316*
317 END IF
318*
319* Set the condition number and norm.
320*
321 cndnma = ten*ten
322 cndnmb = ten
323 IF( lsamen( 3, path, 'GQR' ) .OR. lsamen( 3, path, 'GRQ' ) .OR.
324 $ lsamen( 3, path, 'GSV' ) ) THEN
325 IF( imat.EQ.5 ) THEN
326 cndnma = badc1
327 cndnmb = badc1
328 ELSE IF( imat.EQ.6 ) THEN
329 cndnma = badc2
330 cndnmb = badc2
331 ELSE IF( imat.EQ.7 ) THEN
332 cndnma = badc1
333 cndnmb = badc2
334 ELSE IF( imat.EQ.8 ) THEN
335 cndnma = badc2
336 cndnmb = badc1
337 END IF
338 END IF
339*
340 anorm = ten
341 bnorm = ten*ten*ten
342 IF( lsamen( 3, path, 'GQR' ) .OR. lsamen( 3, path, 'GRQ' ) ) THEN
343 IF( imat.EQ.7 ) THEN
344 anorm = small
345 bnorm = large
346 ELSE IF( imat.EQ.8 ) THEN
347 anorm = large
348 bnorm = small
349 END IF
350 END IF
351*
352 IF( n.LE.1 ) THEN
353 cndnma = one
354 cndnmb = one
355 END IF
356*
357 RETURN
358*
359* End of DLATB9
360*
361 END
subroutine dlatb9(path, imat, m, p, n, type, kla, kua, klb, kub, anorm, bnorm, modea, modeb, cndnma, cndnmb, dista, distb)
DLATB9
Definition dlatb9.f:170