LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
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*> Download IPARMQ + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/iparmq.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/iparmq.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/iparmq.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* INTEGER FUNCTION IPARMQ( ISPEC, NAME, OPTS, N, ILO, IHI, LWORK )
20*
21* .. Scalar Arguments ..
22* INTEGER IHI, ILO, ISPEC, LWORK, N
23* CHARACTER NAME*( * ), OPTS*( * )
24*
25*
26*> \par Purpose:
27* =============
28*>
29*> \verbatim
30*>
31*> This program sets problem and machine dependent parameters
32*> useful for xHSEQR and related subroutines for eigenvalue
33*> problems. It is called whenever
34*> IPARMQ is called with 12 <= ISPEC <= 16
35*> \endverbatim
36*
37* Arguments:
38* ==========
39*
40*> \param[in] ISPEC
41*> \verbatim
42*> ISPEC is INTEGER
43*> ISPEC specifies which tunable parameter IPARMQ should
44*> return.
45*>
46*> ISPEC=12: (INMIN) Matrices of order nmin or less
47*> are sent directly to xLAHQR, the implicit
48*> double shift QR algorithm. NMIN must be
49*> at least 11.
50*>
51*> ISPEC=13: (INWIN) Size of the deflation window.
52*> This is best set greater than or equal to
53*> the number of simultaneous shifts NS.
54*> Larger matrices benefit from larger deflation
55*> windows.
56*>
57*> ISPEC=14: (INIBL) Determines when to stop nibbling and
58*> invest in an (expensive) multi-shift QR sweep.
59*> If the aggressive early deflation subroutine
60*> finds LD converged eigenvalues from an order
61*> NW deflation window and LD > (NW*NIBBLE)/100,
62*> then the next QR sweep is skipped and early
63*> deflation is applied immediately to the
64*> remaining active diagonal block. Setting
65*> IPARMQ(ISPEC=14) = 0 causes TTQRE to skip a
66*> multi-shift QR sweep whenever early deflation
67*> finds a converged eigenvalue. Setting
68*> IPARMQ(ISPEC=14) greater than or equal to 100
69*> prevents TTQRE from skipping a multi-shift
70*> QR sweep.
71*>
72*> ISPEC=15: (NSHFTS) The number of simultaneous shifts in
73*> a multi-shift QR iteration.
74*>
75*> ISPEC=16: (IACC22) IPARMQ is set to 0, 1 or 2 with the
76*> following meanings.
77*> 0: During the multi-shift QR/QZ sweep,
78*> blocked eigenvalue reordering, blocked
79*> Hessenberg-triangular reduction,
80*> reflections and/or rotations are not
81*> accumulated when updating the
82*> far-from-diagonal matrix entries.
83*> 1: During the multi-shift QR/QZ sweep,
84*> blocked eigenvalue reordering, blocked
85*> Hessenberg-triangular reduction,
86*> reflections and/or rotations are
87*> accumulated, and matrix-matrix
88*> multiplication is used to update the
89*> far-from-diagonal matrix entries.
90*> 2: During the multi-shift QR/QZ sweep,
91*> blocked eigenvalue reordering, blocked
92*> Hessenberg-triangular reduction,
93*> reflections and/or rotations are
94*> accumulated, and 2-by-2 block structure
95*> is exploited during matrix-matrix
96*> multiplies.
97*> (If xTRMM is slower than xGEMM, then
98*> IPARMQ(ISPEC=16)=1 may be more efficient than
99*> IPARMQ(ISPEC=16)=2 despite the greater level of
100*> arithmetic work implied by the latter choice.)
101*>
102*> ISPEC=17: (ICOST) An estimate of the relative cost of flops
103*> within the near-the-diagonal shift chase compared
104*> to flops within the BLAS calls of a QZ sweep.
105*> \endverbatim
106*>
107*> \param[in] NAME
108*> \verbatim
109*> NAME is CHARACTER string
110*> Name of the calling subroutine
111*> \endverbatim
112*>
113*> \param[in] OPTS
114*> \verbatim
115*> OPTS is CHARACTER string
116*> This is a concatenation of the string arguments to
117*> TTQRE.
118*> \endverbatim
119*>
120*> \param[in] N
121*> \verbatim
122*> N is INTEGER
123*> N is the order of the Hessenberg matrix H.
124*> \endverbatim
125*>
126*> \param[in] ILO
127*> \verbatim
128*> ILO is INTEGER
129*> \endverbatim
130*>
131*> \param[in] IHI
132*> \verbatim
133*> IHI is INTEGER
134*> It is assumed that H is already upper triangular
135*> in rows and columns 1:ILO-1 and IHI+1:N.
136*> \endverbatim
137*>
138*> \param[in] LWORK
139*> \verbatim
140*> LWORK is INTEGER
141*> The amount of workspace available.
142*> \endverbatim
143*
144* Authors:
145* ========
146*
147*> \author Univ. of Tennessee
148*> \author Univ. of California Berkeley
149*> \author Univ. of Colorado Denver
150*> \author NAG Ltd.
151*
152*> \ingroup iparmq
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) <= 500 is NS. The default
188*> for (IHI-ILO+1) > 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*>
221*> IPARMQ(ISPEC=17) Relative cost heuristic for blocksize selection.
222*> Expressed as a percentage.
223*> Default: 10.
224*> \endverbatim
225*>
226* =====================================================================
227 INTEGER FUNCTION iparmq( ISPEC, NAME, OPTS, N, ILO, IHI,
228 $ LWORK )
229*
230* -- LAPACK auxiliary routine --
231* -- LAPACK is a software package provided by Univ. of Tennessee, --
232* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
233*
234* .. Scalar Arguments ..
235 INTEGER ihi, ilo, ispec, lwork, n
236 CHARACTER name*( * ), opts*( * )
237*
238* ================================================================
239* .. Parameters ..
240 INTEGER inmin, inwin, inibl, ishfts, iacc22, icost
241 parameter( inmin = 12, inwin = 13, inibl = 14,
242 $ ishfts = 15, iacc22 = 16, icost = 17 )
243 INTEGER nmin, k22min, kacmin, nibble, knwswp, rcost
244 parameter( nmin = 75, k22min = 14, kacmin = 14,
245 $ nibble = 14, knwswp = 500, rcost = 10 )
246 REAL two
247 parameter( two = 2.0 )
248* ..
249* .. Local Scalars ..
250 INTEGER nh, ns
251 INTEGER i, ic, iz
252 CHARACTER subnam*6
253* ..
254* .. Intrinsic Functions ..
255 INTRINSIC log, max, mod, nint, real
256* ..
257* .. Executable Statements ..
258 IF( ( ispec.EQ.ishfts ) .OR. ( ispec.EQ.inwin ) .OR.
259 $ ( ispec.EQ.iacc22 ) ) THEN
260*
261* ==== Set the number simultaneous shifts ====
262*
263 nh = ihi - ilo + 1
264 ns = 2
265 IF( nh.GE.30 )
266 $ ns = 4
267 IF( nh.GE.60 )
268 $ ns = 10
269 IF( nh.GE.150 )
270 $ ns = max( 10, nh / nint( log( real( nh ) ) / log( two ) ) )
271 IF( nh.GE.590 )
272 $ ns = 64
273 IF( nh.GE.3000 )
274 $ ns = 128
275 IF( nh.GE.6000 )
276 $ ns = 256
277 ns = max( 2, ns-mod( ns, 2 ) )
278 END IF
279*
280 IF( ispec.EQ.inmin ) THEN
281*
282*
283* ===== Matrices of order smaller than NMIN get sent
284* . to xLAHQR, the classic double shift algorithm.
285* . This must be at least 11. ====
286*
287 iparmq = nmin
288*
289 ELSE IF( ispec.EQ.inibl ) THEN
290*
291* ==== INIBL: skip a multi-shift qr iteration and
292* . whenever aggressive early deflation finds
293* . at least (NIBBLE*(window size)/100) deflations. ====
294*
295 iparmq = nibble
296*
297 ELSE IF( ispec.EQ.ishfts ) THEN
298*
299* ==== NSHFTS: The number of simultaneous shifts =====
300*
301 iparmq = ns
302*
303 ELSE IF( ispec.EQ.inwin ) THEN
304*
305* ==== NW: deflation window size. ====
306*
307 IF( nh.LE.knwswp ) THEN
308 iparmq = ns
309 ELSE
310 iparmq = 3*ns / 2
311 END IF
312*
313 ELSE IF( ispec.EQ.iacc22 ) THEN
314*
315* ==== IACC22: Whether to accumulate reflections
316* . before updating the far-from-diagonal elements
317* . and whether to use 2-by-2 block structure while
318* . doing it. A small amount of work could be saved
319* . by making this choice dependent also upon the
320* . NH=IHI-ILO+1.
321*
322*
323* Convert NAME to upper case if the first character is lower case.
324*
325 iparmq = 0
326 subnam = name
327 ic = ichar( subnam( 1: 1 ) )
328 iz = ichar( 'Z' )
329 IF( iz.EQ.90 .OR. iz.EQ.122 ) THEN
330*
331* ASCII character set
332*
333 IF( ic.GE.97 .AND. ic.LE.122 ) THEN
334 subnam( 1: 1 ) = char( ic-32 )
335 DO i = 2, 6
336 ic = ichar( subnam( i: i ) )
337 IF( ic.GE.97 .AND. ic.LE.122 )
338 $ subnam( i: i ) = char( ic-32 )
339 END DO
340 END IF
341*
342 ELSE IF( iz.EQ.233 .OR. iz.EQ.169 ) THEN
343*
344* EBCDIC character set
345*
346 IF( ( ic.GE.129 .AND. ic.LE.137 ) .OR.
347 $ ( ic.GE.145 .AND. ic.LE.153 ) .OR.
348 $ ( ic.GE.162 .AND. ic.LE.169 ) ) THEN
349 subnam( 1: 1 ) = char( ic+64 )
350 DO i = 2, 6
351 ic = ichar( subnam( i: i ) )
352 IF( ( ic.GE.129 .AND. ic.LE.137 ) .OR.
353 $ ( ic.GE.145 .AND. ic.LE.153 ) .OR.
354 $ ( ic.GE.162 .AND. ic.LE.169 ) )subnam( i:
355 $ i ) = char( ic+64 )
356 END DO
357 END IF
358*
359 ELSE IF( iz.EQ.218 .OR. iz.EQ.250 ) THEN
360*
361* Prime machines: ASCII+128
362*
363 IF( ic.GE.225 .AND. ic.LE.250 ) THEN
364 subnam( 1: 1 ) = char( ic-32 )
365 DO i = 2, 6
366 ic = ichar( subnam( i: i ) )
367 IF( ic.GE.225 .AND. ic.LE.250 )
368 $ subnam( i: i ) = char( ic-32 )
369 END DO
370 END IF
371 END IF
372*
373 IF( subnam( 2:6 ).EQ.'GGHRD' .OR.
374 $ subnam( 2:6 ).EQ.'GGHD3' ) THEN
375 iparmq = 1
376 IF( nh.GE.k22min )
377 $ iparmq = 2
378 ELSE IF ( subnam( 4:6 ).EQ.'EXC' ) THEN
379 IF( nh.GE.kacmin )
380 $ iparmq = 1
381 IF( nh.GE.k22min )
382 $ iparmq = 2
383 ELSE IF ( subnam( 2:6 ).EQ.'HSEQR' .OR.
384 $ subnam( 2:5 ).EQ.'LAQR' ) THEN
385 IF( ns.GE.kacmin )
386 $ iparmq = 1
387 IF( ns.GE.k22min )
388 $ iparmq = 2
389 END IF
390*
391 ELSE IF( ispec.EQ.icost ) THEN
392*
393* === Relative cost of near-the-diagonal chase vs
394* BLAS updates ===
395*
396 iparmq = rcost
397 ELSE
398* ===== invalid value of ispec =====
399 iparmq = -1
400*
401 END IF
402*
403* ==== End of IPARMQ ====
404*
405 END
integer function iparmq(ispec, name, opts, n, ilo, ihi, lwork)
IPARMQ
Definition iparmq.f:229