LAPACK 3.12.0
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 229 of file iparmq.f.

230*
231* -- LAPACK auxiliary routine --
232* -- LAPACK is a software package provided by Univ. of Tennessee, --
233* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
234*
235* .. Scalar Arguments ..
236 INTEGER IHI, ILO, ISPEC, LWORK, N
237 CHARACTER NAME*( * ), OPTS*( * )
238*
239* ================================================================
240* .. Parameters ..
241 INTEGER INMIN, INWIN, INIBL, ISHFTS, IACC22, ICOST
242 parameter( inmin = 12, inwin = 13, inibl = 14,
243 $ ishfts = 15, iacc22 = 16, icost = 17 )
244 INTEGER NMIN, K22MIN, KACMIN, NIBBLE, KNWSWP, RCOST
245 parameter( nmin = 75, k22min = 14, kacmin = 14,
246 $ nibble = 14, knwswp = 500, rcost = 10 )
247 REAL TWO
248 parameter( two = 2.0 )
249* ..
250* .. Local Scalars ..
251 INTEGER NH, NS
252 INTEGER I, IC, IZ
253 CHARACTER SUBNAM*6
254* ..
255* .. Intrinsic Functions ..
256 INTRINSIC log, max, mod, nint, real
257* ..
258* .. Executable Statements ..
259 IF( ( ispec.EQ.ishfts ) .OR. ( ispec.EQ.inwin ) .OR.
260 $ ( ispec.EQ.iacc22 ) ) THEN
261*
262* ==== Set the number simultaneous shifts ====
263*
264 nh = ihi - ilo + 1
265 ns = 2
266 IF( nh.GE.30 )
267 $ ns = 4
268 IF( nh.GE.60 )
269 $ ns = 10
270 IF( nh.GE.150 )
271 $ ns = max( 10, nh / nint( log( real( nh ) ) / log( two ) ) )
272 IF( nh.GE.590 )
273 $ ns = 64
274 IF( nh.GE.3000 )
275 $ ns = 128
276 IF( nh.GE.6000 )
277 $ ns = 256
278 ns = max( 2, ns-mod( ns, 2 ) )
279 END IF
280*
281 IF( ispec.EQ.inmin ) THEN
282*
283*
284* ===== Matrices of order smaller than NMIN get sent
285* . to xLAHQR, the classic double shift algorithm.
286* . This must be at least 11. ====
287*
288 iparmq = nmin
289*
290 ELSE IF( ispec.EQ.inibl ) THEN
291*
292* ==== INIBL: skip a multi-shift qr iteration and
293* . whenever aggressive early deflation finds
294* . at least (NIBBLE*(window size)/100) deflations. ====
295*
296 iparmq = nibble
297*
298 ELSE IF( ispec.EQ.ishfts ) THEN
299*
300* ==== NSHFTS: The number of simultaneous shifts =====
301*
302 iparmq = ns
303*
304 ELSE IF( ispec.EQ.inwin ) THEN
305*
306* ==== NW: deflation window size. ====
307*
308 IF( nh.LE.knwswp ) THEN
309 iparmq = ns
310 ELSE
311 iparmq = 3*ns / 2
312 END IF
313*
314 ELSE IF( ispec.EQ.iacc22 ) THEN
315*
316* ==== IACC22: Whether to accumulate reflections
317* . before updating the far-from-diagonal elements
318* . and whether to use 2-by-2 block structure while
319* . doing it. A small amount of work could be saved
320* . by making this choice dependent also upon the
321* . NH=IHI-ILO+1.
322*
323*
324* Convert NAME to upper case if the first character is lower case.
325*
326 iparmq = 0
327 subnam = name
328 ic = ichar( subnam( 1: 1 ) )
329 iz = ichar( 'Z' )
330 IF( iz.EQ.90 .OR. iz.EQ.122 ) THEN
331*
332* ASCII character set
333*
334 IF( ic.GE.97 .AND. ic.LE.122 ) THEN
335 subnam( 1: 1 ) = char( ic-32 )
336 DO i = 2, 6
337 ic = ichar( subnam( i: i ) )
338 IF( ic.GE.97 .AND. ic.LE.122 )
339 $ subnam( i: i ) = char( ic-32 )
340 END DO
341 END IF
342*
343 ELSE IF( iz.EQ.233 .OR. iz.EQ.169 ) THEN
344*
345* EBCDIC character set
346*
347 IF( ( ic.GE.129 .AND. ic.LE.137 ) .OR.
348 $ ( ic.GE.145 .AND. ic.LE.153 ) .OR.
349 $ ( ic.GE.162 .AND. ic.LE.169 ) ) THEN
350 subnam( 1: 1 ) = char( ic+64 )
351 DO i = 2, 6
352 ic = ichar( subnam( i: i ) )
353 IF( ( ic.GE.129 .AND. ic.LE.137 ) .OR.
354 $ ( ic.GE.145 .AND. ic.LE.153 ) .OR.
355 $ ( ic.GE.162 .AND. ic.LE.169 ) )subnam( i:
356 $ i ) = char( ic+64 )
357 END DO
358 END IF
359*
360 ELSE IF( iz.EQ.218 .OR. iz.EQ.250 ) THEN
361*
362* Prime machines: ASCII+128
363*
364 IF( ic.GE.225 .AND. ic.LE.250 ) THEN
365 subnam( 1: 1 ) = char( ic-32 )
366 DO i = 2, 6
367 ic = ichar( subnam( i: i ) )
368 IF( ic.GE.225 .AND. ic.LE.250 )
369 $ subnam( i: i ) = char( ic-32 )
370 END DO
371 END IF
372 END IF
373*
374 IF( subnam( 2:6 ).EQ.'GGHRD' .OR.
375 $ subnam( 2:6 ).EQ.'GGHD3' ) THEN
376 iparmq = 1
377 IF( nh.GE.k22min )
378 $ iparmq = 2
379 ELSE IF ( subnam( 4:6 ).EQ.'EXC' ) THEN
380 IF( nh.GE.kacmin )
381 $ iparmq = 1
382 IF( nh.GE.k22min )
383 $ iparmq = 2
384 ELSE IF ( subnam( 2:6 ).EQ.'HSEQR' .OR.
385 $ subnam( 2:5 ).EQ.'LAQR' ) THEN
386 IF( ns.GE.kacmin )
387 $ iparmq = 1
388 IF( ns.GE.k22min )
389 $ iparmq = 2
390 END IF
391*
392 ELSE IF( ispec.EQ.icost ) THEN
393*
394* === Relative cost of near-the-diagonal chase vs
395* BLAS updates ===
396*
397 iparmq = rcost
398 ELSE
399* ===== invalid value of ispec =====
400 iparmq = -1
401*
402 END IF
403*
404* ==== End of IPARMQ ====
405*
integer function iparmq(ispec, name, opts, n, ilo, ihi, lwork)
IPARMQ
Definition iparmq.f:230
Here is the call graph for this function:
Here is the caller graph for this function: