LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
ilaenv.f
Go to the documentation of this file.
1 *> \brief \b ILAENV
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 * Definition:
9 * ===========
10 *
11 * INTEGER FUNCTION ILAENV( ISPEC, NAME, OPTS, N1, N2, N3,
12 * N4 )
13 *
14 * .. Scalar Arguments ..
15 * CHARACTER*( * ) NAME, OPTS
16 * INTEGER ISPEC, N1, N2, N3, N4
17 * ..
18 *
19 *
20 *> \par Purpose:
21 * =============
22 *>
23 *> \verbatim
24 *>
25 *> ILAENV returns problem-dependent parameters for the local
26 *> environment. See ISPEC for a description of the parameters.
27 *>
28 *> In this version, the problem-dependent parameters are contained in
29 *> the integer array IPARMS in the common block CLAENV and the value
30 *> with index ISPEC is copied to ILAENV. This version of ILAENV is
31 *> to be used in conjunction with XLAENV in TESTING and TIMING.
32 *> \endverbatim
33 *
34 * Arguments:
35 * ==========
36 *
37 *> \param[in] ISPEC
38 *> \verbatim
39 *> ISPEC is INTEGER
40 *> Specifies the parameter to be returned as the value of
41 *> ILAENV.
42 *> = 1: the optimal blocksize; if this value is 1, an unblocked
43 *> algorithm will give the best performance.
44 *> = 2: the minimum block size for which the block routine
45 *> should be used; if the usable block size is less than
46 *> this value, an unblocked routine should be used.
47 *> = 3: the crossover point (in a block routine, for N less
48 *> than this value, an unblocked routine should be used)
49 *> = 4: the number of shifts, used in the nonsymmetric
50 *> eigenvalue routines
51 *> = 5: the minimum column dimension for blocking to be used;
52 *> rectangular blocks must have dimension at least k by m,
53 *> where k is given by ILAENV(2,...) and m by ILAENV(5,...)
54 *> = 6: the crossover point for the SVD (when reducing an m by n
55 *> matrix to bidiagonal form, if max(m,n)/min(m,n) exceeds
56 *> this value, a QR factorization is used first to reduce
57 *> the matrix to a triangular form.)
58 *> = 7: the number of processors
59 *> = 8: the crossover point for the multishift QR and QZ methods
60 *> for nonsymmetric eigenvalue problems.
61 *> = 9: maximum size of the subproblems at the bottom of the
62 *> computation tree in the divide-and-conquer algorithm
63 *> =10: ieee NaN arithmetic can be trusted not to trap
64 *> =11: infinity arithmetic can be trusted not to trap
65 *> 12 <= ISPEC <= 16:
66 *> xHSEQR or one of its subroutines,
67 *> see IPARMQ for detailed explanation
68 *>
69 *> Other specifications (up to 100) can be added later.
70 *> \endverbatim
71 *>
72 *> \param[in] NAME
73 *> \verbatim
74 *> NAME is CHARACTER*(*)
75 *> The name of the calling subroutine.
76 *> \endverbatim
77 *>
78 *> \param[in] OPTS
79 *> \verbatim
80 *> OPTS is CHARACTER*(*)
81 *> The character options to the subroutine NAME, concatenated
82 *> into a single character string. For example, UPLO = 'U',
83 *> TRANS = 'T', and DIAG = 'N' for a triangular routine would
84 *> be specified as OPTS = 'UTN'.
85 *> \endverbatim
86 *>
87 *> \param[in] N1
88 *> \verbatim
89 *> N1 is INTEGER
90 *> \endverbatim
91 *>
92 *> \param[in] N2
93 *> \verbatim
94 *> N2 is INTEGER
95 *> \endverbatim
96 *>
97 *> \param[in] N3
98 *> \verbatim
99 *> N3 is INTEGER
100 *> \endverbatim
101 *>
102 *> \param[in] N4
103 *> \verbatim
104 *> N4 is INTEGER
105 *>
106 *> Problem dimensions for the subroutine NAME; these may not all
107 *> be required.
108 *> \endverbatim
109 *>
110 *> \result ILAENV
111 *> \verbatim
112 *> ILAENV is INTEGER
113 *> >= 0: the value of the parameter specified by ISPEC
114 *> < 0: if ILAENV = -k, the k-th argument had an illegal value.
115 *> \endverbatim
116 *
117 * Authors:
118 * ========
119 *
120 *> \author Univ. of Tennessee
121 *> \author Univ. of California Berkeley
122 *> \author Univ. of Colorado Denver
123 *> \author NAG Ltd.
124 *
125 *> \date November 2011
126 *
127 *> \ingroup aux_eig
128 *
129 *> \par Further Details:
130 * =====================
131 *>
132 *> \verbatim
133 *>
134 *> The following conventions have been used when calling ILAENV from the
135 *> LAPACK routines:
136 *> 1) OPTS is a concatenation of all of the character options to
137 *> subroutine NAME, in the same order that they appear in the
138 *> argument list for NAME, even if they are not used in determining
139 *> the value of the parameter specified by ISPEC.
140 *> 2) The problem dimensions N1, N2, N3, N4 are specified in the order
141 *> that they appear in the argument list for NAME. N1 is used
142 *> first, N2 second, and so on, and unused problem dimensions are
143 *> passed a value of -1.
144 *> 3) The parameter value returned by ILAENV is checked for validity in
145 *> the calling subroutine. For example, ILAENV is used to retrieve
146 *> the optimal blocksize for STRTRI as follows:
147 *>
148 *> NB = ILAENV( 1, 'STRTRI', UPLO // DIAG, N, -1, -1, -1 )
149 *> IF( NB.LE.1 ) NB = MAX( 1, N )
150 *> \endverbatim
151 *>
152 * =====================================================================
153  INTEGER FUNCTION ilaenv( ISPEC, NAME, OPTS, N1, N2, N3,
154  $ n4 )
155 *
156 * -- LAPACK test routine (version 3.4.0) --
157 * -- LAPACK is a software package provided by Univ. of Tennessee, --
158 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
159 * November 2011
160 *
161 * .. Scalar Arguments ..
162  CHARACTER*( * ) name, opts
163  INTEGER ispec, n1, n2, n3, n4
164 * ..
165 *
166 * =====================================================================
167 *
168 * .. Intrinsic Functions ..
169  INTRINSIC int, min, real
170 * ..
171 * .. External Functions ..
172  INTEGER ieeeck
173  EXTERNAL ieeeck
174 * ..
175 * .. Arrays in Common ..
176  INTEGER iparms( 100 )
177 * ..
178 * .. Common blocks ..
179  common / claenv / iparms
180 * ..
181 * .. Save statement ..
182  SAVE / claenv /
183 * ..
184 * .. Executable Statements ..
185 *
186  IF( ispec.GE.1 .AND. ispec.LE.5 ) THEN
187 *
188 * Return a value from the common block.
189 *
190  ilaenv = iparms( ispec )
191 *
192  ELSE IF( ispec.EQ.6 ) THEN
193 *
194 * Compute SVD crossover point.
195 *
196  ilaenv = int( REAL( MIN( N1, N2 ) )*1.6e0 )
197 *
198  ELSE IF( ispec.GE.7 .AND. ispec.LE.9 ) THEN
199 *
200 * Return a value from the common block.
201 *
202  ilaenv = iparms( ispec )
203 *
204  ELSE IF( ispec.EQ.10 ) THEN
205 *
206 * IEEE NaN arithmetic can be trusted not to trap
207 *
208 C ILAENV = 0
209  ilaenv = 1
210  IF( ilaenv.EQ.1 ) THEN
211  ilaenv = ieeeck( 1, 0.0, 1.0 )
212  END IF
213 *
214  ELSE IF( ispec.EQ.11 ) THEN
215 *
216 * Infinity arithmetic can be trusted not to trap
217 *
218 C ILAENV = 0
219  ilaenv = 1
220  IF( ilaenv.EQ.1 ) THEN
221  ilaenv = ieeeck( 0, 0.0, 1.0 )
222  END IF
223 *
224  ELSE IF(( ispec.GE.12 ) .AND. (ispec.LE.16)) THEN
225 *
226 * 12 <= ISPEC <= 16: xHSEQR or one of its subroutines.
227 *
228  ilaenv = iparms( ispec )
229 * WRITE(*,*) 'ISPEC = ',ISPEC,' ILAENV =',ILAENV
230 * ILAENV = IPARMQ( ISPEC, NAME, OPTS, N1, N2, N3, N4 )
231 *
232  ELSE
233 *
234 * Invalid value for ISPEC
235 *
236  ilaenv = -1
237  END IF
238 *
239  return
240 *
241 * End of ILAENV
242 *
243  END
244  INTEGER FUNCTION iparmq( ISPEC, NAME, OPTS, N, ILO, IHI, LWORK )
245 *
246  INTEGER inmin, inwin, inibl, ishfts, iacc22
247  parameter( inmin = 12, inwin = 13, inibl = 14,
248  $ ishfts = 15, iacc22 = 16 )
249  INTEGER nmin, k22min, kacmin, nibble, knwswp
250  parameter( nmin = 11, k22min = 14, kacmin = 14,
251  $ nibble = 14, knwswp = 500 )
252  REAL two
253  parameter( two = 2.0 )
254 * ..
255 * .. Scalar Arguments ..
256  INTEGER ihi, ilo, ispec, lwork, n
257  CHARACTER name*( * ), opts*( * )
258 * ..
259 * .. Local Scalars ..
260  INTEGER nh, ns
261 * ..
262 * .. Intrinsic Functions ..
263  INTRINSIC log, max, mod, nint, real
264 * ..
265 * .. Executable Statements ..
266  IF( ( ispec.EQ.ishfts ) .OR. ( ispec.EQ.inwin ) .OR.
267  $ ( ispec.EQ.iacc22 ) ) THEN
268 *
269 * ==== Set the number simultaneous shifts ====
270 *
271  nh = ihi - ilo + 1
272  ns = 2
273  IF( nh.GE.30 )
274  $ ns = 4
275  IF( nh.GE.60 )
276  $ ns = 10
277  IF( nh.GE.150 )
278  $ ns = max( 10, nh / nint( log( REAL( NH ) ) / log( two ) ) )
279  IF( nh.GE.590 )
280  $ ns = 64
281  IF( nh.GE.3000 )
282  $ ns = 128
283  IF( nh.GE.6000 )
284  $ ns = 256
285  ns = max( 2, ns-mod( ns, 2 ) )
286  END IF
287 *
288  IF( ispec.EQ.inmin ) THEN
289 *
290 *
291 * ===== Matrices of order smaller than NMIN get sent
292 * . to LAHQR, the classic double shift algorithm.
293 * . This must be at least 11. ====
294 *
295  iparmq = nmin
296 *
297  ELSE IF( ispec.EQ.inibl ) THEN
298 *
299 * ==== INIBL: skip a multi-shift qr iteration and
300 * . whenever aggressive early deflation finds
301 * . at least (NIBBLE*(window size)/100) deflations. ====
302 *
303  iparmq = nibble
304 *
305  ELSE IF( ispec.EQ.ishfts ) THEN
306 *
307 * ==== NSHFTS: The number of simultaneous shifts =====
308 *
309  iparmq = ns
310 *
311  ELSE IF( ispec.EQ.inwin ) THEN
312 *
313 * ==== NW: deflation window size. ====
314 *
315  IF( nh.LE.knwswp ) THEN
316  iparmq = ns
317  ELSE
318  iparmq = 3*ns / 2
319  END IF
320 *
321  ELSE IF( ispec.EQ.iacc22 ) THEN
322 *
323 * ==== IACC22: Whether to accumulate reflections
324 * . before updating the far-from-diagonal elements
325 * . and whether to use 2-by-2 block structure while
326 * . doing it. A small amount of work could be saved
327 * . by making this choice dependent also upon the
328 * . NH=IHI-ILO+1.
329 *
330  iparmq = 0
331  IF( ns.GE.kacmin )
332  $ iparmq = 1
333  IF( ns.GE.k22min )
334  $ iparmq = 2
335 *
336  ELSE
337 * ===== invalid value of ispec =====
338  iparmq = -1
339 *
340  END IF
341 *
342 * ==== End of IPARMQ ====
343 *
344  END