LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
clatb5.f
Go to the documentation of this file.
1 *> \brief \b CLATB5
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 CLATB5( PATH, IMAT, N, TYPE, KL, KU, ANORM, MODE,
12 * CNDNUM, DIST )
13 *
14 * .. Scalar Arguments ..
15 * REAL ANORM, CNDNUM
16 * INTEGER IMAT, KL, KU, MODE, N
17 * CHARACTER DIST, TYPE
18 * CHARACTER*3 PATH
19 * ..
20 *
21 *
22 *> \par Purpose:
23 * =============
24 *>
25 *> \verbatim
26 *>
27 *> CLATB5 sets parameters for the matrix generator based on the type
28 *> of matrix to be generated.
29 *> \endverbatim
30 *
31 * Arguments:
32 * ==========
33 *
34 *> \param[in] PATH
35 *> \verbatim
36 *> PATH is CHARACTER*3
37 *> The LAPACK path name.
38 *> \endverbatim
39 *>
40 *> \param[in] IMAT
41 *> \verbatim
42 *> IMAT is INTEGER
43 *> An integer key describing which matrix to generate for this
44 *> path.
45 *> \endverbatim
46 *>
47 *> \param[in] N
48 *> \verbatim
49 *> N is INTEGER
50 *> The number of rows and columns in the matrix to be generated.
51 *> \endverbatim
52 *>
53 *> \param[out] TYPE
54 *> \verbatim
55 *> TYPE is CHARACTER*1
56 *> The type of the matrix to be generated:
57 *> = 'S': symmetric matrix
58 *> = 'P': symmetric positive (semi)definite matrix
59 *> = 'N': nonsymmetric matrix
60 *> \endverbatim
61 *>
62 *> \param[out] KL
63 *> \verbatim
64 *> KL is INTEGER
65 *> The lower band width of the matrix to be generated.
66 *> \endverbatim
67 *>
68 *> \param[out] KU
69 *> \verbatim
70 *> KU is INTEGER
71 *> The upper band width of the matrix to be generated.
72 *> \endverbatim
73 *>
74 *> \param[out] ANORM
75 *> \verbatim
76 *> ANORM is REAL
77 *> The desired norm of the matrix to be generated. The diagonal
78 *> matrix of singular values or eigenvalues is scaled by this
79 *> value.
80 *> \endverbatim
81 *>
82 *> \param[out] MODE
83 *> \verbatim
84 *> MODE is INTEGER
85 *> A key indicating how to choose the vector of eigenvalues.
86 *> \endverbatim
87 *>
88 *> \param[out] CNDNUM
89 *> \verbatim
90 *> CNDNUM is REAL
91 *> The desired condition number.
92 *> \endverbatim
93 *>
94 *> \param[out] DIST
95 *> \verbatim
96 *> DIST is CHARACTER*1
97 *> The type of distribution to be used by the random number
98 *> generator.
99 *> \endverbatim
100 *
101 * Authors:
102 * ========
103 *
104 *> \author Univ. of Tennessee
105 *> \author Univ. of California Berkeley
106 *> \author Univ. of Colorado Denver
107 *> \author NAG Ltd.
108 *
109 *> \date November 2011
110 *
111 *> \ingroup complex_lin
112 *
113 * =====================================================================
114  SUBROUTINE clatb5( PATH, IMAT, N, TYPE, KL, KU, ANORM, MODE,
115  $ cndnum, dist )
116 *
117 * -- LAPACK test routine (version 3.4.0) --
118 * -- LAPACK is a software package provided by Univ. of Tennessee, --
119 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
120 * November 2011
121 *
122 * .. Scalar Arguments ..
123  REAL anorm, cndnum
124  INTEGER imat, kl, ku, mode, n
125  CHARACTER dist, type
126  CHARACTER*3 path
127 * ..
128 *
129 * =====================================================================
130 *
131 * .. Parameters ..
132  REAL shrink, tenth
133  parameter( shrink = 0.25e0, tenth = 0.1e+0 )
134  REAL one
135  parameter( one = 1.0e+0 )
136  REAL two
137  parameter( two = 2.0e+0 )
138 * ..
139 * .. Local Scalars ..
140  REAL badc1, badc2, eps, large, small
141  LOGICAL first
142  CHARACTER*2 c2
143 * ..
144 * .. External Functions ..
145  REAL slamch
146  EXTERNAL slamch
147 * ..
148 * .. Intrinsic Functions ..
149  INTRINSIC max, sqrt
150 * ..
151 * .. External Subroutines ..
152  EXTERNAL slabad
153 * ..
154 * .. Save statement ..
155  SAVE eps, small, large, badc1, badc2, first
156 * ..
157 * .. Data statements ..
158  DATA first / .true. /
159 * ..
160 * .. Executable Statements ..
161 *
162 * Set some constants for use in the subroutine.
163 *
164  IF( first ) THEN
165  first = .false.
166  eps = slamch( 'Precision' )
167  badc2 = tenth / eps
168  badc1 = sqrt( badc2 )
169  small = slamch( 'Safe minimum' )
170  large = one / small
171 *
172 * If it looks like we're on a Cray, take the square root of
173 * SMALL and LARGE to avoid overflow and underflow problems.
174 *
175  CALL slabad( small, large )
176  small = shrink*( small / eps )
177  large = one / small
178  END IF
179 *
180  c2 = path( 2: 3 )
181 *
182 * Set some parameters
183 *
184  dist = 'S'
185  mode = 3
186 *
187 * Set TYPE, the type of matrix to be generated.
188 *
189  TYPE = c2( 1: 1 )
190 *
191 * Set the lower and upper bandwidths.
192 *
193  IF( imat.EQ.1 ) THEN
194  kl = 0
195  ELSE
196  kl = max( n-1, 0 )
197  END IF
198  ku = kl
199 *
200 * Set the condition number and norm.etc
201 *
202  IF( imat.EQ.3 ) THEN
203  cndnum = 1.0e4
204  mode = 2
205  ELSE IF( imat.EQ.4 ) THEN
206  cndnum = 1.0e4
207  mode = 1
208  ELSE IF( imat.EQ.5 ) THEN
209  cndnum = 1.0e4
210  mode = 3
211  ELSE IF( imat.EQ.6 ) THEN
212  cndnum = badc1
213  ELSE IF( imat.EQ.7 ) THEN
214  cndnum = badc2
215  ELSE
216  cndnum = two
217  END IF
218 *
219  IF( imat.EQ.8 ) THEN
220  anorm = small
221  ELSE IF( imat.EQ.9 ) THEN
222  anorm = large
223  ELSE
224  anorm = one
225  END IF
226 *
227  IF( n.LE.1 )
228  $ cndnum = one
229 *
230  return
231 *
232 * End of SLATB5
233 *
234  END