1       SUBROUTINE DLATB5( PATH, IMAT, N, TYPE, KL, KU, ANORM, MODE,
  2      $                   CNDNUM, DIST )
  3 *
  4 *  -- LAPACK test routine (version 3.1) --
  5 *     Craig Lucas, University of Manchester / NAG Ltd.
  6 *     October, 2008
  7 *
  8 *     .. Scalar Arguments ..
  9       DOUBLE PRECISION   ANORM, CNDNUM
 10       INTEGER            IMAT, KL, KU, MODE, N
 11       CHARACTER          DIST, TYPE
 12       CHARACTER*3        PATH
 13 *     ..
 14 *
 15 *  Purpose
 16 *  =======
 17 *
 18 *  DLATB5 sets parameters for the matrix generator based on the type
 19 *  of matrix to be generated.
 20 *
 21 *  Arguments
 22 *  =========
 23 *
 24 *  PATH    (input) CHARACTER*3
 25 *          The LAPACK path name.
 26 *
 27 *  IMAT    (input) INTEGER
 28 *          An integer key describing which matrix to generate for this
 29 *          path.
 30 *
 31 *  N       (input) INTEGER
 32 *          The number of rows and columns in the matrix to be generated.
 33 *
 34 *  TYPE    (output) CHARACTER*1
 35 *          The type of the matrix to be generated:
 36 *          = 'S':  symmetric matrix
 37 *          = 'P':  symmetric positive (semi)definite matrix
 38 *          = 'N':  nonsymmetric matrix
 39 *
 40 *  KL      (output) INTEGER
 41 *          The lower band width of the matrix to be generated.
 42 *
 43 *  KU      (output) INTEGER
 44 *          The upper band width of the matrix to be generated.
 45 *
 46 *  ANORM   (output) DOUBLE PRECISION
 47 *          The desired norm of the matrix to be generated.  The diagonal
 48 *          matrix of singular values or eigenvalues is scaled by this
 49 *          value.
 50 *
 51 *  MODE    (output) INTEGER
 52 *          A key indicating how to choose the vector of eigenvalues.
 53 *
 54 *  CNDNUM  (output) DOUBLE PRECISION
 55 *          The desired condition number.
 56 *
 57 *  DIST    (output) CHARACTER*1
 58 *          The type of distribution to be used by the random number
 59 *          generator.
 60 *
 61 *  =====================================================================
 62 *
 63 *     .. Parameters ..
 64       DOUBLE PRECISION   SHRINK, TENTH
 65       PARAMETER          ( SHRINK = 0.25D0, TENTH = 0.1D+0 )
 66       DOUBLE PRECISION   ONE
 67       PARAMETER          ( ONE = 1.0D+0 )
 68       DOUBLE PRECISION   TWO
 69       PARAMETER          ( TWO = 2.0D+0 )
 70 *     ..
 71 *     .. Local Scalars ..
 72       DOUBLE PRECISION   BADC1, BADC2, EPS, LARGE, SMALL
 73       LOGICAL            FIRST
 74       CHARACTER*2        C2
 75 *     ..
 76 *     .. External Functions ..
 77       DOUBLE PRECISION   DLAMCH
 78       EXTERNAL           DLAMCH
 79 *     ..
 80 *     .. Intrinsic Functions ..
 81       INTRINSIC          MAXSQRT
 82 *     ..
 83 *     .. External Subroutines ..
 84       EXTERNAL           DLABAD
 85 *     ..
 86 *     .. Save statement ..
 87       SAVE               EPS, SMALL, LARGE, BADC1, BADC2, FIRST
 88 *     ..
 89 *     .. Data statements ..
 90       DATA               FIRST / .TRUE. /
 91 *     ..
 92 *     .. Executable Statements ..
 93 *
 94 *     Set some constants for use in the subroutine.
 95 *
 96       IF( FIRST ) THEN
 97          FIRST = .FALSE.
 98          EPS = DLAMCH( 'Precision' )
 99          BADC2 = TENTH / EPS
100          BADC1 = SQRT( BADC2 )
101          SMALL = DLAMCH( 'Safe minimum' )
102          LARGE = ONE / SMALL
103 *
104 *        If it looks like we're on a Cray, take the square root of
105 *        SMALL and LARGE to avoid overflow and underflow problems.
106 *
107          CALL DLABAD( SMALL, LARGE )
108          SMALL = SHRINK*( SMALL / EPS )
109          LARGE = ONE / SMALL
110       END IF
111 *
112       C2 = PATH( 23 )
113 *
114 *     Set some parameters
115 *
116       DIST = 'S'
117       MODE = 3
118 *
119 *     Set TYPE, the type of matrix to be generated.
120 *
121       TYPE = C2( 11 )
122 *
123 *     Set the lower and upper bandwidths.
124 *
125       IF( IMAT.EQ.1 ) THEN
126          KL = 0
127       ELSE
128          KL = MAX( N-10 )
129       END IF
130       KU = KL
131 *
132 *     Set the condition number and norm.etc
133 *
134       IF( IMAT.EQ.3 ) THEN
135          CNDNUM = 1.0D12
136          MODE = 2
137       ELSE IF( IMAT.EQ.4 ) THEN
138          CNDNUM = 1.0D12
139          MODE = 1
140       ELSE IF( IMAT.EQ.5 ) THEN
141          CNDNUM = 1.0D12
142          MODE = 3
143       ELSE IF( IMAT.EQ.6 ) THEN
144          CNDNUM = BADC1
145       ELSE IF( IMAT.EQ.7 ) THEN
146          CNDNUM = BADC2
147       ELSE
148          CNDNUM = TWO
149       END IF
150 *
151       IF( IMAT.EQ.8 ) THEN
152          ANORM = SMALL
153       ELSE IF( IMAT.EQ.9 ) THEN
154          ANORM = LARGE
155       ELSE
156          ANORM = ONE
157       END IF
158 *
159       IF( N.LE.1 )
160      $   CNDNUM = ONE
161 *
162       RETURN
163 *
164 *     End of DLATB5
165 *
166       END