1       INTEGER          FUNCTION ILAENV( ISPEC, NAME, OPTS, N1, N2, N3,
  2      $                 N4 )
  3 *
  4 *  -- LAPACK auxiliary routine (version 3.1) --
  5 *     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
  6 *     November 2006
  7 *
  8 *     .. Scalar Arguments ..
  9       CHARACTER** )    NAME, OPTS
 10       INTEGER            ISPEC, N1, N2, N3, N4
 11 *     ..
 12 *
 13 *  Purpose
 14 *  =======
 15 *
 16 *  ILAENV returns problem-dependent parameters for the local
 17 *  environment.  See ISPEC for a description of the parameters.
 18 *
 19 *  In this version, the problem-dependent parameters are contained in
 20 *  the integer array IPARMS in the common block CLAENV and the value
 21 *  with index ISPEC is copied to ILAENV.  This version of ILAENV is
 22 *  to be used in conjunction with XLAENV in TESTING and TIMING.
 23 *
 24 *  Arguments
 25 *  =========
 26 *
 27 *  ISPEC   (input) INTEGER
 28 *          Specifies the parameter to be returned as the value of
 29 *          ILAENV.
 30 *          = 1: the optimal blocksize; if this value is 1, an unblocked
 31 *               algorithm will give the best performance.
 32 *          = 2: the minimum block size for which the block routine
 33 *               should be used; if the usable block size is less than
 34 *               this value, an unblocked routine should be used.
 35 *          = 3: the crossover point (in a block routine, for N less
 36 *               than this value, an unblocked routine should be used)
 37 *          = 4: the number of shifts, used in the nonsymmetric
 38 *               eigenvalue routines
 39 *          = 5: the minimum column dimension for blocking to be used;
 40 *               rectangular blocks must have dimension at least k by m,
 41 *               where k is given by ILAENV(2,...) and m by ILAENV(5,...)
 42 *          = 6: the crossover point for the SVD (when reducing an m by n
 43 *               matrix to bidiagonal form, if max(m,n)/min(m,n) exceeds
 44 *               this value, a QR factorization is used first to reduce
 45 *               the matrix to a triangular form.)
 46 *          = 7: the number of processors
 47 *          = 8: the crossover point for the multishift QR and QZ methods
 48 *               for nonsymmetric eigenvalue problems.
 49 *          = 9: maximum size of the subproblems at the bottom of the
 50 *               computation tree in the divide-and-conquer algorithm
 51 *          =10: ieee NaN arithmetic can be trusted not to trap
 52 *          =11: infinity arithmetic can be trusted not to trap
 53 *          12 <= ISPEC <= 16:
 54 *               xHSEQR or one of its subroutines,
 55 *               see IPARMQ for detailed explanation
 56 *
 57 *          Other specifications (up to 100) can be added later.
 58 *
 59 *  NAME    (input) CHARACTER*(*)
 60 *          The name of the calling subroutine.
 61 *
 62 *  OPTS    (input) CHARACTER*(*)
 63 *          The character options to the subroutine NAME, concatenated
 64 *          into a single character string.  For example, UPLO = 'U',
 65 *          TRANS = 'T', and DIAG = 'N' for a triangular routine would
 66 *          be specified as OPTS = 'UTN'.
 67 *
 68 *  N1      (input) INTEGER
 69 *  N2      (input) INTEGER
 70 *  N3      (input) INTEGER
 71 *  N4      (input) INTEGER
 72 *          Problem dimensions for the subroutine NAME; these may not all
 73 *          be required.
 74 *
 75 * (ILAENV) (output) INTEGER
 76 *          >= 0: the value of the parameter specified by ISPEC
 77 *          < 0:  if ILAENV = -k, the k-th argument had an illegal value.
 78 *
 79 *  Further Details
 80 *  ===============
 81 *
 82 *  The following conventions have been used when calling ILAENV from the
 83 *  LAPACK routines:
 84 *  1)  OPTS is a concatenation of all of the character options to
 85 *      subroutine NAME, in the same order that they appear in the
 86 *      argument list for NAME, even if they are not used in determining
 87 *      the value of the parameter specified by ISPEC.
 88 *  2)  The problem dimensions N1, N2, N3, N4 are specified in the order
 89 *      that they appear in the argument list for NAME.  N1 is used
 90 *      first, N2 second, and so on, and unused problem dimensions are
 91 *      passed a value of -1.
 92 *  3)  The parameter value returned by ILAENV is checked for validity in
 93 *      the calling subroutine.  For example, ILAENV is used to retrieve
 94 *      the optimal blocksize for STRTRI as follows:
 95 *
 96 *      NB = ILAENV( 1, 'STRTRI', UPLO // DIAG, N, -1, -1, -1 )
 97 *      IF( NB.LE.1 ) NB = MAX( 1, N )
 98 *
 99 *  =====================================================================
100 *
101 *     .. Intrinsic Functions ..
102       INTRINSIC          INTMIN, REAL
103 *     ..
104 *     .. External Functions ..
105       INTEGER            IEEECK
106       EXTERNAL           IEEECK
107 *     ..
108 *     .. Arrays in Common ..
109       INTEGER            IPARMS( 100 )
110 *     ..
111 *     .. Common blocks ..
112       COMMON             / CLAENV / IPARMS
113 *     ..
114 *     .. Save statement ..
115       SAVE               / CLAENV /
116 *     ..
117 *     .. Executable Statements ..
118 *
119       IF( ISPEC.GE.1 .AND. ISPEC.LE.5 ) THEN
120 *
121 *        Return a value from the common block.
122 *
123          ILAENV = IPARMS( ISPEC )
124 *
125       ELSE IF( ISPEC.EQ.6 ) THEN
126 *
127 *        Compute SVD crossover point.
128 *
129          ILAENV = INTREALMIN( N1, N2 ) )*1.6E0 )
130 *
131       ELSE IF( ISPEC.GE.7 .AND. ISPEC.LE.9 ) THEN
132 *
133 *        Return a value from the common block.
134 *
135          ILAENV = IPARMS( ISPEC )
136 *
137       ELSE IF( ISPEC.EQ.10 ) THEN
138 *
139 *        IEEE NaN arithmetic can be trusted not to trap
140 *
141 C        ILAENV = 0
142          ILAENV = 1
143          IF( ILAENV.EQ.1 ) THEN
144             ILAENV = IEEECK( 10.01.0 )
145          END IF
146 *
147       ELSE IF( ISPEC.EQ.11 ) THEN
148 *
149 *        Infinity arithmetic can be trusted not to trap
150 *
151 C        ILAENV = 0
152          ILAENV = 1
153          IF( ILAENV.EQ.1 ) THEN
154             ILAENV = IEEECK( 00.01.0 )
155          END IF
156 *
157       ELSE IF(( ISPEC.GE.12 ) .AND. (ISPEC.LE.16)) THEN
158 *
159 *     12 <= ISPEC <= 16: xHSEQR or one of its subroutines. 
160 *
161          ILAENV = IPARMS( ISPEC )
162 *         WRITE(*,*) 'ISPEC = ',ISPEC,' ILAENV =',ILAENV
163 *         ILAENV = IPARMQ( ISPEC, NAME, OPTS, N1, N2, N3, N4 )
164 *
165       ELSE
166 *
167 *        Invalid value for ISPEC
168 *
169          ILAENV = -1
170       END IF
171 *
172       RETURN
173 *
174 *     End of ILAENV
175 *
176       END
177       INTEGER FUNCTION IPARMQ( ISPEC, NAME, OPTS, N, ILO, IHI, LWORK )
178 *
179       INTEGER            INMIN, INWIN, INIBL, ISHFTS, IACC22
180       PARAMETER          ( INMIN = 12, INWIN = 13, INIBL = 14,
181      $                   ISHFTS = 15, IACC22 = 16 )
182       INTEGER            NMIN, K22MIN, KACMIN, NIBBLE, KNWSWP
183       PARAMETER          ( NMIN = 11, K22MIN = 14, KACMIN = 14,
184      $                   NIBBLE = 14, KNWSWP = 500 )
185       REAL               TWO
186       PARAMETER          ( TWO = 2.0 )
187 *     ..
188 *     .. Scalar Arguments ..
189       INTEGER            IHI, ILO, ISPEC, LWORK, N
190       CHARACTER          NAME** ), OPTS** )
191 *     ..
192 *     .. Local Scalars ..
193       INTEGER            NH, NS
194 *     ..
195 *     .. Intrinsic Functions ..
196       INTRINSIC          LOGMAXMODNINT, REAL
197 *     ..
198 *     .. Executable Statements ..
199       IF( ( ISPEC.EQ.ISHFTS ) .OR. ( ISPEC.EQ.INWIN ) .OR.
200      $    ( ISPEC.EQ.IACC22 ) ) THEN
201 *
202 *        ==== Set the number simultaneous shifts ====
203 *
204          NH = IHI - ILO + 1
205          NS = 2
206          IF( NH.GE.30 )
207      $      NS = 4
208          IF( NH.GE.60 )
209      $      NS = 10
210          IF( NH.GE.150 )
211      $      NS = MAX10, NH / NINTLOGREAL( NH ) ) / LOG( TWO ) ) )
212          IF( NH.GE.590 )
213      $      NS = 64
214          IF( NH.GE.3000 )
215      $      NS = 128
216          IF( NH.GE.6000 )
217      $      NS = 256
218          NS = MAX2, NS-MOD( NS, 2 ) )
219       END IF
220 *
221       IF( ISPEC.EQ.INMIN ) THEN
222 *
223 *
224 *        ===== Matrices of order smaller than NMIN get sent
225 *        .     to LAHQR, the classic double shift algorithm.
226 *        .     This must be at least 11. ====
227 *
228          IPARMQ = NMIN
229 *
230       ELSE IF( ISPEC.EQ.INIBL ) THEN
231 *
232 *        ==== INIBL: skip a multi-shift qr iteration and
233 *        .    whenever aggressive early deflation finds
234 *        .    at least (NIBBLE*(window size)/100) deflations. ====
235 *
236          IPARMQ = NIBBLE
237 *
238       ELSE IF( ISPEC.EQ.ISHFTS ) THEN
239 *
240 *        ==== NSHFTS: The number of simultaneous shifts =====
241 *
242          IPARMQ = NS
243 *
244       ELSE IF( ISPEC.EQ.INWIN ) THEN
245 *
246 *        ==== NW: deflation window size.  ====
247 *
248          IF( NH.LE.KNWSWP ) THEN
249             IPARMQ = NS
250          ELSE
251             IPARMQ = 3*NS / 2
252          END IF
253 *
254       ELSE IF( ISPEC.EQ.IACC22 ) THEN
255 *
256 *        ==== IACC22: Whether to accumulate reflections
257 *        .     before updating the far-from-diagonal elements
258 *        .     and whether to use 2-by-2 block structure while
259 *        .     doing it.  A small amount of work could be saved
260 *        .     by making this choice dependent also upon the
261 *        .     NH=IHI-ILO+1.
262 *
263          IPARMQ = 0
264          IF( NS.GE.KACMIN )
265      $      IPARMQ = 1
266          IF( NS.GE.K22MIN )
267      $      IPARMQ = 2
268 *
269       ELSE
270 *        ===== invalid value of ispec =====
271          IPARMQ = -1
272 *
273       END IF
274 *
275 *     ==== End of IPARMQ ====
276 *
277       END