LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
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 scalar
              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.GT.(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.)
[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 scalar
               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 scalar
               The amount of workspace available.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2015
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).LE.500 is NS.  The default
                        for (IHI-ILO+1).GT.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.

Definition at line 224 of file iparmq.f.

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 *
integer function iparmq(ISPEC, NAME, OPTS, N, ILO, IHI, LWORK)
IPARMQ
Definition: iparmq.f:224

Here is the caller graph for this function: