1*> \brief \b ZLATB5
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 ZLATB5( PATH, IMAT, N, TYPE, KL, KU, ANORM, MODE,
12*                          CNDNUM, DIST )
13*
14*       .. Scalar Arguments ..
15*       DOUBLE PRECISION   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*> ZLATB5 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 DOUBLE PRECISION
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 DOUBLE PRECISION
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 December 2016
110*
111*> \ingroup complex16_lin
112*
113*  =====================================================================
114      SUBROUTINE ZLATB5( PATH, IMAT, N, TYPE, KL, KU, ANORM, MODE,
115     $                   CNDNUM, DIST )
116*
117*  -- LAPACK test routine (version 3.7.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*     December 2016
121*
122*     .. Scalar Arguments ..
123      DOUBLE PRECISION   ANORM, CNDNUM
124      INTEGER            IMAT, KL, KU, MODE, N
125      CHARACTER          DIST, TYPE
126      CHARACTER*3        PATH
127*     ..
128*
129*  =====================================================================
130*
131*     .. Parameters ..
132      DOUBLE PRECISION   SHRINK, TENTH
133      PARAMETER          ( SHRINK = 0.25D0, TENTH = 0.1D+0 )
134      DOUBLE PRECISION   ONE
135      PARAMETER          ( ONE = 1.0D+0 )
136      DOUBLE PRECISION   TWO
137      PARAMETER          ( TWO = 2.0D+0 )
138*     ..
139*     .. Local Scalars ..
140      DOUBLE PRECISION   BADC1, BADC2, EPS, LARGE, SMALL
141      LOGICAL            FIRST
142      CHARACTER*2        C2
143*     ..
144*     .. External Functions ..
145      DOUBLE PRECISION   DLAMCH
146      EXTERNAL           DLAMCH
147*     ..
148*     .. Intrinsic Functions ..
149      INTRINSIC          MAX, SQRT
150*     ..
151*     .. External Subroutines ..
152      EXTERNAL           DLABAD
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 = DLAMCH( 'Precision' )
167         BADC2 = TENTH / EPS
168         BADC1 = SQRT( BADC2 )
169         SMALL = DLAMCH( '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 DLABAD( 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.0D12
204         MODE = 2
205      ELSE IF( IMAT.EQ.4 ) THEN
206         CNDNUM = 1.0D12
207         MODE = 1
208      ELSE IF( IMAT.EQ.5 ) THEN
209         CNDNUM = 1.0D12
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 ZLATB5
233*
234      END
235