LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
iparmq.f
Go to the documentation of this file.
1 *> \brief \b IPARMQ
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download IPARMQ + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/iparmq.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/iparmq.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/iparmq.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * INTEGER FUNCTION IPARMQ( ISPEC, NAME, OPTS, N, ILO, IHI, LWORK )
22 *
23 * .. Scalar Arguments ..
24 * INTEGER IHI, ILO, ISPEC, LWORK, N
25 * CHARACTER NAME*( * ), OPTS*( * )
26 *
27 *
28 *> \par Purpose:
29 * =============
30 *>
31 *> \verbatim
32 *>
33 *> This program sets problem and machine dependent parameters
34 *> useful for xHSEQR and related subroutines for eigenvalue
35 *> problems. It is called whenever
36 *> IPARMQ is called with 12 <= ISPEC <= 16
37 *> \endverbatim
38 *
39 * Arguments:
40 * ==========
41 *
42 *> \param[in] ISPEC
43 *> \verbatim
44 *> ISPEC is integer scalar
45 *> ISPEC specifies which tunable parameter IPARMQ should
46 *> return.
47 *>
48 *> ISPEC=12: (INMIN) Matrices of order nmin or less
49 *> are sent directly to xLAHQR, the implicit
50 *> double shift QR algorithm. NMIN must be
51 *> at least 11.
52 *>
53 *> ISPEC=13: (INWIN) Size of the deflation window.
54 *> This is best set greater than or equal to
55 *> the number of simultaneous shifts NS.
56 *> Larger matrices benefit from larger deflation
57 *> windows.
58 *>
59 *> ISPEC=14: (INIBL) Determines when to stop nibbling and
60 *> invest in an (expensive) multi-shift QR sweep.
61 *> If the aggressive early deflation subroutine
62 *> finds LD converged eigenvalues from an order
63 *> NW deflation window and LD.GT.(NW*NIBBLE)/100,
64 *> then the next QR sweep is skipped and early
65 *> deflation is applied immediately to the
66 *> remaining active diagonal block. Setting
67 *> IPARMQ(ISPEC=14) = 0 causes TTQRE to skip a
68 *> multi-shift QR sweep whenever early deflation
69 *> finds a converged eigenvalue. Setting
70 *> IPARMQ(ISPEC=14) greater than or equal to 100
71 *> prevents TTQRE from skipping a multi-shift
72 *> QR sweep.
73 *>
74 *> ISPEC=15: (NSHFTS) The number of simultaneous shifts in
75 *> a multi-shift QR iteration.
76 *>
77 *> ISPEC=16: (IACC22) IPARMQ is set to 0, 1 or 2 with the
78 *> following meanings.
79 *> 0: During the multi-shift QR/QZ sweep,
80 *> blocked eigenvalue reordering, blocked
81 *> Hessenberg-triangular reduction,
82 *> reflections and/or rotations are not
83 *> accumulated when updating the
84 *> far-from-diagonal matrix entries.
85 *> 1: During the multi-shift QR/QZ sweep,
86 *> blocked eigenvalue reordering, blocked
87 *> Hessenberg-triangular reduction,
88 *> reflections and/or rotations are
89 *> accumulated, and matrix-matrix
90 *> multiplication is used to update the
91 *> far-from-diagonal matrix entries.
92 *> 2: During the multi-shift QR/QZ sweep,
93 *> blocked eigenvalue reordering, blocked
94 *> Hessenberg-triangular reduction,
95 *> reflections and/or rotations are
96 *> accumulated, and 2-by-2 block structure
97 *> is exploited during matrix-matrix
98 *> multiplies.
99 *> (If xTRMM is slower than xGEMM, then
100 *> IPARMQ(ISPEC=16)=1 may be more efficient than
101 *> IPARMQ(ISPEC=16)=2 despite the greater level of
102 *> arithmetic work implied by the latter choice.)
103 *> \endverbatim
104 *>
105 *> \param[in] NAME
106 *> \verbatim
107 *> NAME is character string
108 *> Name of the calling subroutine
109 *> \endverbatim
110 *>
111 *> \param[in] OPTS
112 *> \verbatim
113 *> OPTS is character string
114 *> This is a concatenation of the string arguments to
115 *> TTQRE.
116 *> \endverbatim
117 *>
118 *> \param[in] N
119 *> \verbatim
120 *> N is integer scalar
121 *> N is the order of the Hessenberg matrix H.
122 *> \endverbatim
123 *>
124 *> \param[in] ILO
125 *> \verbatim
126 *> ILO is INTEGER
127 *> \endverbatim
128 *>
129 *> \param[in] IHI
130 *> \verbatim
131 *> IHI is INTEGER
132 *> It is assumed that H is already upper triangular
133 *> in rows and columns 1:ILO-1 and IHI+1:N.
134 *> \endverbatim
135 *>
136 *> \param[in] LWORK
137 *> \verbatim
138 *> LWORK is integer scalar
139 *> The amount of workspace available.
140 *> \endverbatim
141 *
142 * Authors:
143 * ========
144 *
145 *> \author Univ. of Tennessee
146 *> \author Univ. of California Berkeley
147 *> \author Univ. of Colorado Denver
148 *> \author NAG Ltd.
149 *
150 *> \date November 2015
151 *
152 *> \ingroup auxOTHERauxiliary
153 *
154 *> \par Further Details:
155 * =====================
156 *>
157 *> \verbatim
158 *>
159 *> Little is known about how best to choose these parameters.
160 *> It is possible to use different values of the parameters
161 *> for each of CHSEQR, DHSEQR, SHSEQR and ZHSEQR.
162 *>
163 *> It is probably best to choose different parameters for
164 *> different matrices and different parameters at different
165 *> times during the iteration, but this has not been
166 *> implemented --- yet.
167 *>
168 *>
169 *> The best choices of most of the parameters depend
170 *> in an ill-understood way on the relative execution
171 *> rate of xLAQR3 and xLAQR5 and on the nature of each
172 *> particular eigenvalue problem. Experiment may be the
173 *> only practical way to determine which choices are most
174 *> effective.
175 *>
176 *> Following is a list of default values supplied by IPARMQ.
177 *> These defaults may be adjusted in order to attain better
178 *> performance in any particular computational environment.
179 *>
180 *> IPARMQ(ISPEC=12) The xLAHQR vs xLAQR0 crossover point.
181 *> Default: 75. (Must be at least 11.)
182 *>
183 *> IPARMQ(ISPEC=13) Recommended deflation window size.
184 *> This depends on ILO, IHI and NS, the
185 *> number of simultaneous shifts returned
186 *> by IPARMQ(ISPEC=15). The default for
187 *> (IHI-ILO+1).LE.500 is NS. The default
188 *> for (IHI-ILO+1).GT.500 is 3*NS/2.
189 *>
190 *> IPARMQ(ISPEC=14) Nibble crossover point. Default: 14.
191 *>
192 *> IPARMQ(ISPEC=15) Number of simultaneous shifts, NS.
193 *> a multi-shift QR iteration.
194 *>
195 *> If IHI-ILO+1 is ...
196 *>
197 *> greater than ...but less ... the
198 *> or equal to ... than default is
199 *>
200 *> 0 30 NS = 2+
201 *> 30 60 NS = 4+
202 *> 60 150 NS = 10
203 *> 150 590 NS = **
204 *> 590 3000 NS = 64
205 *> 3000 6000 NS = 128
206 *> 6000 infinity NS = 256
207 *>
208 *> (+) By default matrices of this order are
209 *> passed to the implicit double shift routine
210 *> xLAHQR. See IPARMQ(ISPEC=12) above. These
211 *> values of NS are used only in case of a rare
212 *> xLAHQR failure.
213 *>
214 *> (**) The asterisks (**) indicate an ad-hoc
215 *> function increasing from 10 to 64.
216 *>
217 *> IPARMQ(ISPEC=16) Select structured matrix multiply.
218 *> (See ISPEC=16 above for details.)
219 *> Default: 3.
220 *> \endverbatim
221 *>
222 * =====================================================================
223  INTEGER FUNCTION iparmq( ISPEC, NAME, OPTS, N, ILO, IHI, LWORK )
224 *
225 * -- LAPACK auxiliary routine (version 3.6.0) --
226 * -- LAPACK is a software package provided by Univ. of Tennessee, --
227 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
228 * November 2015
229 *
230 * .. Scalar Arguments ..
231  INTEGER IHI, ILO, ISPEC, LWORK, N
232  CHARACTER NAME*( * ), OPTS*( * )
233 *
234 * ================================================================
235 * .. Parameters ..
236  INTEGER INMIN, INWIN, INIBL, ISHFTS, IACC22
237  parameter ( inmin = 12, inwin = 13, inibl = 14,
238  $ ishfts = 15, iacc22 = 16 )
239  INTEGER NMIN, K22MIN, KACMIN, NIBBLE, KNWSWP
240  parameter ( nmin = 75, k22min = 14, kacmin = 14,
241  $ nibble = 14, knwswp = 500 )
242  REAL TWO
243  parameter ( two = 2.0 )
244 * ..
245 * .. Local Scalars ..
246  INTEGER NH, NS
247  INTEGER I, IC, IZ
248  CHARACTER SUBNAM*6
249 * ..
250 * .. Intrinsic Functions ..
251  INTRINSIC log, max, mod, nint, real
252 * ..
253 * .. Executable Statements ..
254  IF( ( ispec.EQ.ishfts ) .OR. ( ispec.EQ.inwin ) .OR.
255  $ ( ispec.EQ.iacc22 ) ) THEN
256 *
257 * ==== Set the number simultaneous shifts ====
258 *
259  nh = ihi - ilo + 1
260  ns = 2
261  IF( nh.GE.30 )
262  $ ns = 4
263  IF( nh.GE.60 )
264  $ ns = 10
265  IF( nh.GE.150 )
266  $ ns = max( 10, nh / nint( log( REAL( NH ) ) / log( TWO ) ) )
267  IF( nh.GE.590 )
268  $ ns = 64
269  IF( nh.GE.3000 )
270  $ ns = 128
271  IF( nh.GE.6000 )
272  $ ns = 256
273  ns = max( 2, ns-mod( ns, 2 ) )
274  END IF
275 *
276  IF( ispec.EQ.inmin ) THEN
277 *
278 *
279 * ===== Matrices of order smaller than NMIN get sent
280 * . to xLAHQR, the classic double shift algorithm.
281 * . This must be at least 11. ====
282 *
283  iparmq = nmin
284 *
285  ELSE IF( ispec.EQ.inibl ) THEN
286 *
287 * ==== INIBL: skip a multi-shift qr iteration and
288 * . whenever aggressive early deflation finds
289 * . at least (NIBBLE*(window size)/100) deflations. ====
290 *
291  iparmq = nibble
292 *
293  ELSE IF( ispec.EQ.ishfts ) THEN
294 *
295 * ==== NSHFTS: The number of simultaneous shifts =====
296 *
297  iparmq = ns
298 *
299  ELSE IF( ispec.EQ.inwin ) THEN
300 *
301 * ==== NW: deflation window size. ====
302 *
303  IF( nh.LE.knwswp ) THEN
304  iparmq = ns
305  ELSE
306  iparmq = 3*ns / 2
307  END IF
308 *
309  ELSE IF( ispec.EQ.iacc22 ) THEN
310 *
311 * ==== IACC22: Whether to accumulate reflections
312 * . before updating the far-from-diagonal elements
313 * . and whether to use 2-by-2 block structure while
314 * . doing it. A small amount of work could be saved
315 * . by making this choice dependent also upon the
316 * . NH=IHI-ILO+1.
317 *
318 *
319 * Convert NAME to upper case if the first character is lower case.
320 *
321  iparmq = 0
322  subnam = name
323  ic = ichar( subnam( 1: 1 ) )
324  iz = ichar( 'Z' )
325  IF( iz.EQ.90 .OR. iz.EQ.122 ) THEN
326 *
327 * ASCII character set
328 *
329  IF( ic.GE.97 .AND. ic.LE.122 ) THEN
330  subnam( 1: 1 ) = char( ic-32 )
331  DO i = 2, 6
332  ic = ichar( subnam( i: i ) )
333  IF( ic.GE.97 .AND. ic.LE.122 )
334  $ subnam( i: i ) = char( ic-32 )
335  END DO
336  END IF
337 *
338  ELSE IF( iz.EQ.233 .OR. iz.EQ.169 ) THEN
339 *
340 * EBCDIC character set
341 *
342  IF( ( ic.GE.129 .AND. ic.LE.137 ) .OR.
343  $ ( ic.GE.145 .AND. ic.LE.153 ) .OR.
344  $ ( ic.GE.162 .AND. ic.LE.169 ) ) THEN
345  subnam( 1: 1 ) = char( ic+64 )
346  DO i = 2, 6
347  ic = ichar( subnam( i: i ) )
348  IF( ( ic.GE.129 .AND. ic.LE.137 ) .OR.
349  $ ( ic.GE.145 .AND. ic.LE.153 ) .OR.
350  $ ( ic.GE.162 .AND. ic.LE.169 ) )subnam( i:
351  $ i ) = char( ic+64 )
352  END DO
353  END IF
354 *
355  ELSE IF( iz.EQ.218 .OR. iz.EQ.250 ) THEN
356 *
357 * Prime machines: ASCII+128
358 *
359  IF( ic.GE.225 .AND. ic.LE.250 ) THEN
360  subnam( 1: 1 ) = char( ic-32 )
361  DO i = 2, 6
362  ic = ichar( subnam( i: i ) )
363  IF( ic.GE.225 .AND. ic.LE.250 )
364  $ subnam( i: i ) = char( ic-32 )
365  END DO
366  END IF
367  END IF
368 *
369  IF( subnam( 2:6 ).EQ.'GGHRD' .OR.
370  $ subnam( 2:6 ).EQ.'GGHD3' ) THEN
371  iparmq = 1
372  IF( nh.GE.k22min )
373  $ iparmq = 2
374  ELSE IF ( subnam( 4:6 ).EQ.'EXC' ) THEN
375  IF( nh.GE.kacmin )
376  $ iparmq = 1
377  IF( nh.GE.k22min )
378  $ iparmq = 2
379  ELSE IF ( subnam( 2:6 ).EQ.'HSEQR' .OR.
380  $ subnam( 2:5 ).EQ.'LAQR' ) THEN
381  IF( ns.GE.kacmin )
382  $ iparmq = 1
383  IF( ns.GE.k22min )
384  $ iparmq = 2
385  END IF
386 *
387  ELSE
388 * ===== invalid value of ispec =====
389  iparmq = -1
390 *
391  END IF
392 *
393 * ==== End of IPARMQ ====
394 *
395  END
integer function iparmq(ISPEC, NAME, OPTS, N, ILO, IHI, LWORK)
IPARMQ
Definition: iparmq.f:224