LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ iparmq()

integer function iparmq ( integer ispec,
character, dimension( * ) name,
character, dimension( * ) opts,
integer n,
integer ilo,
integer ihi,
integer lwork )

IPARMQ

Download IPARMQ + dependencies [TGZ] [ZIP] [TXT]

Purpose:
!>
!>      This program sets problem and machine dependent parameters
!>      useful for xHSEQR and related subroutines for eigenvalue
!>      problems. It is called whenever
!>      IPARMQ is called with 12 <= ISPEC <= 16
!> 
Parameters
[in]ISPEC
!>          ISPEC is INTEGER
!>              ISPEC specifies which tunable parameter IPARMQ should
!>              return.
!>
!>              ISPEC=12: (INMIN)  Matrices of order nmin or less
!>                        are sent directly to xLAHQR, the implicit
!>                        double shift QR algorithm.  NMIN must be
!>                        at least 11.
!>
!>              ISPEC=13: (INWIN)  Size of the deflation window.
!>                        This is best set greater than or equal to
!>                        the number of simultaneous shifts NS.
!>                        Larger matrices benefit from larger deflation
!>                        windows.
!>
!>              ISPEC=14: (INIBL) Determines when to stop nibbling and
!>                        invest in an (expensive) multi-shift QR sweep.
!>                        If the aggressive early deflation subroutine
!>                        finds LD converged eigenvalues from an order
!>                        NW deflation window and LD > (NW*NIBBLE)/100,
!>                        then the next QR sweep is skipped and early
!>                        deflation is applied immediately to the
!>                        remaining active diagonal block.  Setting
!>                        IPARMQ(ISPEC=14) = 0 causes TTQRE to skip a
!>                        multi-shift QR sweep whenever early deflation
!>                        finds a converged eigenvalue.  Setting
!>                        IPARMQ(ISPEC=14) greater than or equal to 100
!>                        prevents TTQRE from skipping a multi-shift
!>                        QR sweep.
!>
!>              ISPEC=15: (NSHFTS) The number of simultaneous shifts in
!>                        a multi-shift QR iteration.
!>
!>              ISPEC=16: (IACC22) IPARMQ is set to 0, 1 or 2 with the
!>                        following meanings.
!>                        0:  During the multi-shift QR/QZ sweep,
!>                            blocked eigenvalue reordering, blocked
!>                            Hessenberg-triangular reduction,
!>                            reflections and/or rotations are not
!>                            accumulated when updating the
!>                            far-from-diagonal matrix entries.
!>                        1:  During the multi-shift QR/QZ sweep,
!>                            blocked eigenvalue reordering, blocked
!>                            Hessenberg-triangular reduction,
!>                            reflections and/or rotations are
!>                            accumulated, and matrix-matrix
!>                            multiplication is used to update the
!>                            far-from-diagonal matrix entries.
!>                        2:  During the multi-shift QR/QZ sweep,
!>                            blocked eigenvalue reordering, blocked
!>                            Hessenberg-triangular reduction,
!>                            reflections and/or rotations are
!>                            accumulated, and 2-by-2 block structure
!>                            is exploited during matrix-matrix
!>                            multiplies.
!>                        (If xTRMM is slower than xGEMM, then
!>                        IPARMQ(ISPEC=16)=1 may be more efficient than
!>                        IPARMQ(ISPEC=16)=2 despite the greater level of
!>                        arithmetic work implied by the latter choice.)
!>
!>              ISPEC=17: (ICOST) An estimate of the relative cost of flops
!>                        within the near-the-diagonal shift chase compared
!>                        to flops within the BLAS calls of a QZ sweep.
!> 
[in]NAME
!>          NAME is CHARACTER string
!>               Name of the calling subroutine
!> 
[in]OPTS
!>          OPTS is CHARACTER string
!>               This is a concatenation of the string arguments to
!>               TTQRE.
!> 
[in]N
!>          N is INTEGER
!>               N is the order of the Hessenberg matrix H.
!> 
[in]ILO
!>          ILO is INTEGER
!> 
[in]IHI
!>          IHI is INTEGER
!>               It is assumed that H is already upper triangular
!>               in rows and columns 1:ILO-1 and IHI+1:N.
!> 
[in]LWORK
!>          LWORK is INTEGER
!>               The amount of workspace available.
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
!>
!>       Little is known about how best to choose these parameters.
!>       It is possible to use different values of the parameters
!>       for each of CHSEQR, DHSEQR, SHSEQR and ZHSEQR.
!>
!>       It is probably best to choose different parameters for
!>       different matrices and different parameters at different
!>       times during the iteration, but this has not been
!>       implemented --- yet.
!>
!>
!>       The best choices of most of the parameters depend
!>       in an ill-understood way on the relative execution
!>       rate of xLAQR3 and xLAQR5 and on the nature of each
!>       particular eigenvalue problem.  Experiment may be the
!>       only practical way to determine which choices are most
!>       effective.
!>
!>       Following is a list of default values supplied by IPARMQ.
!>       These defaults may be adjusted in order to attain better
!>       performance in any particular computational environment.
!>
!>       IPARMQ(ISPEC=12) The xLAHQR vs xLAQR0 crossover point.
!>                        Default: 75. (Must be at least 11.)
!>
!>       IPARMQ(ISPEC=13) Recommended deflation window size.
!>                        This depends on ILO, IHI and NS, the
!>                        number of simultaneous shifts returned
!>                        by IPARMQ(ISPEC=15).  The default for
!>                        (IHI-ILO+1) <= 500 is NS.  The default
!>                        for (IHI-ILO+1) > 500 is 3*NS/2.
!>
!>       IPARMQ(ISPEC=14) Nibble crossover point.  Default: 14.
!>
!>       IPARMQ(ISPEC=15) Number of simultaneous shifts, NS.
!>                        a multi-shift QR iteration.
!>
!>                        If IHI-ILO+1 is ...
!>
!>                        greater than      ...but less    ... the
!>                        or equal to ...      than        default is
!>
!>                                0               30       NS =   2+
!>                               30               60       NS =   4+
!>                               60              150       NS =  10
!>                              150              590       NS =  **
!>                              590             3000       NS =  64
!>                             3000             6000       NS = 128
!>                             6000             infinity   NS = 256
!>
!>                    (+)  By default matrices of this order are
!>                         passed to the implicit double shift routine
!>                         xLAHQR.  See IPARMQ(ISPEC=12) above.   These
!>                         values of NS are used only in case of a rare
!>                         xLAHQR failure.
!>
!>                    (**) The asterisks (**) indicate an ad-hoc
!>                         function increasing from 10 to 64.
!>
!>       IPARMQ(ISPEC=16) Select structured matrix multiply.
!>                        (See ISPEC=16 above for details.)
!>                        Default: 3.
!>
!>       IPARMQ(ISPEC=17) Relative cost heuristic for blocksize selection.
!>                        Expressed as a percentage.
!>                        Default: 10.
!> 

Definition at line 227 of file iparmq.f.

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*
integer function iparmq(ispec, name, opts, n, ilo, ihi, lwork)
IPARMQ
Definition iparmq.f:229
Here is the call graph for this function:
Here is the caller graph for this function: