Diff for /rpl/lapack/lapack/dhseqr.f between versions 1.9 and 1.19

version 1.9, 2011/11/21 20:42:53 version 1.19, 2023/08/07 08:38:52
Line 2 Line 2
 *  *
 *  =========== DOCUMENTATION ===========  *  =========== DOCUMENTATION ===========
 *  *
 * Online html documentation available at   * Online html documentation available at
 *            http://www.netlib.org/lapack/explore-html/   *            http://www.netlib.org/lapack/explore-html/
 *  *
 *> \htmlonly  *> \htmlonly
 *> Download DHSEQR + dependencies   *> Download DHSEQR + dependencies
 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dhseqr.f">   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dhseqr.f">
 *> [TGZ]</a>   *> [TGZ]</a>
 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dhseqr.f">   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dhseqr.f">
 *> [ZIP]</a>   *> [ZIP]</a>
 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dhseqr.f">   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dhseqr.f">
 *> [TXT]</a>  *> [TXT]</a>
 *> \endhtmlonly   *> \endhtmlonly
 *  *
 *  Definition:  *  Definition:
 *  ===========  *  ===========
 *  *
 *       SUBROUTINE DHSEQR( JOB, COMPZ, N, ILO, IHI, H, LDH, WR, WI, Z,  *       SUBROUTINE DHSEQR( JOB, COMPZ, N, ILO, IHI, H, LDH, WR, WI, Z,
 *                          LDZ, WORK, LWORK, INFO )  *                          LDZ, WORK, LWORK, INFO )
 *   *
 *       .. Scalar Arguments ..  *       .. Scalar Arguments ..
 *       INTEGER            IHI, ILO, INFO, LDH, LDZ, LWORK, N  *       INTEGER            IHI, ILO, INFO, LDH, LDZ, LWORK, N
 *       CHARACTER          COMPZ, JOB  *       CHARACTER          COMPZ, JOB
Line 29 Line 29
 *       DOUBLE PRECISION   H( LDH, * ), WI( * ), WORK( * ), WR( * ),  *       DOUBLE PRECISION   H( LDH, * ), WI( * ), WORK( * ), WR( * ),
 *      $                   Z( LDZ, * )  *      $                   Z( LDZ, * )
 *       ..  *       ..
 *    *
 *  *
 *> \par Purpose:  *> \par Purpose:
 *  =============  *  =============
Line 70 Line 70
 *> \param[in] N  *> \param[in] N
 *> \verbatim  *> \verbatim
 *>          N is INTEGER  *>          N is INTEGER
 *>           The order of the matrix H.  N .GE. 0.  *>           The order of the matrix H.  N >= 0.
 *> \endverbatim  *> \endverbatim
 *>  *>
 *> \param[in] ILO  *> \param[in] ILO
Line 87 Line 87
 *>           set by a previous call to DGEBAL, and then passed to ZGEHRD  *>           set by a previous call to DGEBAL, and then passed to ZGEHRD
 *>           when the matrix output by DGEBAL is reduced to Hessenberg  *>           when the matrix output by DGEBAL is reduced to Hessenberg
 *>           form. Otherwise ILO and IHI should be set to 1 and N  *>           form. Otherwise ILO and IHI should be set to 1 and N
 *>           respectively.  If N.GT.0, then 1.LE.ILO.LE.IHI.LE.N.  *>           respectively.  If N > 0, then 1 <= ILO <= IHI <= N.
 *>           If N = 0, then ILO = 1 and IHI = 0.  *>           If N = 0, then ILO = 1 and IHI = 0.
 *> \endverbatim  *> \endverbatim
 *>  *>
Line 100 Line 100
 *>           (the Schur form); 2-by-2 diagonal blocks (corresponding to  *>           (the Schur form); 2-by-2 diagonal blocks (corresponding to
 *>           complex conjugate pairs of eigenvalues) are returned in  *>           complex conjugate pairs of eigenvalues) are returned in
 *>           standard form, with H(i,i) = H(i+1,i+1) and  *>           standard form, with H(i,i) = H(i+1,i+1) and
 *>           H(i+1,i)*H(i,i+1).LT.0. If INFO = 0 and JOB = 'E', the  *>           H(i+1,i)*H(i,i+1) < 0. If INFO = 0 and JOB = 'E', the
 *>           contents of H are unspecified on exit.  (The output value of  *>           contents of H are unspecified on exit.  (The output value of
 *>           H when INFO.GT.0 is given under the description of INFO  *>           H when INFO > 0 is given under the description of INFO
 *>           below.)  *>           below.)
 *>  *>
 *>           Unlike earlier versions of DHSEQR, this subroutine may  *>           Unlike earlier versions of DHSEQR, this subroutine may
 *>           explicitly H(i,j) = 0 for i.GT.j and j = 1, 2, ... ILO-1  *>           explicitly H(i,j) = 0 for i > j and j = 1, 2, ... ILO-1
 *>           or j = IHI+1, IHI+2, ... N.  *>           or j = IHI+1, IHI+2, ... N.
 *> \endverbatim  *> \endverbatim
 *>  *>
 *> \param[in] LDH  *> \param[in] LDH
 *> \verbatim  *> \verbatim
 *>          LDH is INTEGER  *>          LDH is INTEGER
 *>           The leading dimension of the array H. LDH .GE. max(1,N).  *>           The leading dimension of the array H. LDH >= max(1,N).
 *> \endverbatim  *> \endverbatim
 *>  *>
 *> \param[out] WR  *> \param[out] WR
Line 128 Line 128
 *>           The real and imaginary parts, respectively, of the computed  *>           The real and imaginary parts, respectively, of the computed
 *>           eigenvalues. If two eigenvalues are computed as a complex  *>           eigenvalues. If two eigenvalues are computed as a complex
 *>           conjugate pair, they are stored in consecutive elements of  *>           conjugate pair, they are stored in consecutive elements of
 *>           WR and WI, say the i-th and (i+1)th, with WI(i) .GT. 0 and  *>           WR and WI, say the i-th and (i+1)th, with WI(i) > 0 and
 *>           WI(i+1) .LT. 0. If JOB = 'S', the eigenvalues are stored in  *>           WI(i+1) < 0. If JOB = 'S', the eigenvalues are stored in
 *>           the same order as on the diagonal of the Schur form returned  *>           the same order as on the diagonal of the Schur form returned
 *>           in H, with WR(i) = H(i,i) and, if H(i:i+1,i:i+1) is a 2-by-2  *>           in H, with WR(i) = H(i,i) and, if H(i:i+1,i:i+1) is a 2-by-2
 *>           diagonal block, WI(i) = sqrt(-H(i+1,i)*H(i,i+1)) and  *>           diagonal block, WI(i) = sqrt(-H(i+1,i)*H(i,i+1)) and
Line 148 Line 148
 *>           if INFO = 0, Z contains Q*Z.  *>           if INFO = 0, Z contains Q*Z.
 *>           Normally Q is the orthogonal matrix generated by DORGHR  *>           Normally Q is the orthogonal matrix generated by DORGHR
 *>           after the call to DGEHRD which formed the Hessenberg matrix  *>           after the call to DGEHRD which formed the Hessenberg matrix
 *>           H. (The output value of Z when INFO.GT.0 is given under  *>           H. (The output value of Z when INFO > 0 is given under
 *>           the description of INFO below.)  *>           the description of INFO below.)
 *> \endverbatim  *> \endverbatim
 *>  *>
Line 156 Line 156
 *> \verbatim  *> \verbatim
 *>          LDZ is INTEGER  *>          LDZ is INTEGER
 *>           The leading dimension of the array Z.  if COMPZ = 'I' or  *>           The leading dimension of the array Z.  if COMPZ = 'I' or
 *>           COMPZ = 'V', then LDZ.GE.MAX(1,N).  Otherwize, LDZ.GE.1.  *>           COMPZ = 'V', then LDZ >= MAX(1,N).  Otherwise, LDZ >= 1.
 *> \endverbatim  *> \endverbatim
 *>  *>
 *> \param[out] WORK  *> \param[out] WORK
Line 169 Line 169
 *> \param[in] LWORK  *> \param[in] LWORK
 *> \verbatim  *> \verbatim
 *>          LWORK is INTEGER  *>          LWORK is INTEGER
 *>           The dimension of the array WORK.  LWORK .GE. max(1,N)  *>           The dimension of the array WORK.  LWORK >= max(1,N)
 *>           is sufficient and delivers very good and sometimes  *>           is sufficient and delivers very good and sometimes
 *>           optimal performance.  However, LWORK as large as 11*N  *>           optimal performance.  However, LWORK as large as 11*N
 *>           may be required for optimal performance.  A workspace  *>           may be required for optimal performance.  A workspace
Line 187 Line 187
 *> \param[out] INFO  *> \param[out] INFO
 *> \verbatim  *> \verbatim
 *>          INFO is INTEGER  *>          INFO is INTEGER
 *>             =  0:  successful exit  *>             = 0:  successful exit
 *>           .LT. 0:  if INFO = -i, the i-th argument had an illegal  *>             < 0:  if INFO = -i, the i-th argument had an illegal
 *>                    value  *>                    value
 *>           .GT. 0:  if INFO = i, DHSEQR failed to compute all of  *>             > 0:  if INFO = i, DHSEQR failed to compute all of
 *>                the eigenvalues.  Elements 1:ilo-1 and i+1:n of WR  *>                the eigenvalues.  Elements 1:ilo-1 and i+1:n of WR
 *>                and WI contain those eigenvalues which have been  *>                and WI contain those eigenvalues which have been
 *>                successfully computed.  (Failures are rare.)  *>                successfully computed.  (Failures are rare.)
 *>  *>
 *>                If INFO .GT. 0 and JOB = 'E', then on exit, the  *>                If INFO > 0 and JOB = 'E', then on exit, the
 *>                remaining unconverged eigenvalues are the eigen-  *>                remaining unconverged eigenvalues are the eigen-
 *>                values of the upper Hessenberg matrix rows and  *>                values of the upper Hessenberg matrix rows and
 *>                columns ILO through INFO of the final, output  *>                columns ILO through INFO of the final, output
 *>                value of H.  *>                value of H.
 *>  *>
 *>                If INFO .GT. 0 and JOB   = 'S', then on exit  *>                If INFO > 0 and JOB   = 'S', then on exit
 *>  *>
 *>           (*)  (initial value of H)*U  = U*(final value of H)  *>           (*)  (initial value of H)*U  = U*(final value of H)
 *>  *>
Line 209 Line 209
 *>                value of H is upper Hessenberg and quasi-triangular  *>                value of H is upper Hessenberg and quasi-triangular
 *>                in rows and columns INFO+1 through IHI.  *>                in rows and columns INFO+1 through IHI.
 *>  *>
 *>                If INFO .GT. 0 and COMPZ = 'V', then on exit  *>                If INFO > 0 and COMPZ = 'V', then on exit
 *>  *>
 *>                  (final value of Z)  =  (initial value of Z)*U  *>                  (final value of Z)  =  (initial value of Z)*U
 *>  *>
 *>                where U is the orthogonal matrix in (*) (regard-  *>                where U is the orthogonal matrix in (*) (regard-
 *>                less of the value of JOB.)  *>                less of the value of JOB.)
 *>  *>
 *>                If INFO .GT. 0 and COMPZ = 'I', then on exit  *>                If INFO > 0 and COMPZ = 'I', then on exit
 *>                      (final value of Z)  = U  *>                      (final value of Z)  = U
 *>                where U is the orthogonal matrix in (*) (regard-  *>                where U is the orthogonal matrix in (*) (regard-
 *>                less of the value of JOB.)  *>                less of the value of JOB.)
 *>  *>
 *>                If INFO .GT. 0 and COMPZ = 'N', then Z is not  *>                If INFO > 0 and COMPZ = 'N', then Z is not
 *>                accessed.  *>                accessed.
 *> \endverbatim  *> \endverbatim
 *  *
 *  Authors:  *  Authors:
 *  ========  *  ========
 *  *
 *> \author Univ. of Tennessee   *> \author Univ. of Tennessee
 *> \author Univ. of California Berkeley   *> \author Univ. of California Berkeley
 *> \author Univ. of Colorado Denver   *> \author Univ. of Colorado Denver
 *> \author NAG Ltd.   *> \author NAG Ltd.
 *  
 *> \date November 2011  
 *  *
 *> \ingroup doubleOTHERcomputational  *> \ingroup doubleOTHERcomputational
 *  *
Line 261 Line 259
 *>                      This depends on ILO, IHI and NS.  NS is the  *>                      This depends on ILO, IHI and NS.  NS is the
 *>                      number of simultaneous shifts returned  *>                      number of simultaneous shifts returned
 *>                      by ILAENV(ISPEC=15).  (See ISPEC=15 below.)  *>                      by ILAENV(ISPEC=15).  (See ISPEC=15 below.)
 *>                      The default for (IHI-ILO+1).LE.500 is NS.  *>                      The default for (IHI-ILO+1) <= 500 is NS.
 *>                      The default for (IHI-ILO+1).GT.500 is 3*NS/2.  *>                      The default for (IHI-ILO+1) >  500 is 3*NS/2.
 *>  *>
 *>            ISPEC=14: Nibble crossover point. (See IPARMQ for  *>            ISPEC=14: Nibble crossover point. (See IPARMQ for
 *>                      details.)  Default: 14% of deflation window  *>                      details.)  Default: 14% of deflation window
Line 316 Line 314
       SUBROUTINE DHSEQR( JOB, COMPZ, N, ILO, IHI, H, LDH, WR, WI, Z,        SUBROUTINE DHSEQR( JOB, COMPZ, N, ILO, IHI, H, LDH, WR, WI, Z,
      $                   LDZ, WORK, LWORK, INFO )       $                   LDZ, WORK, LWORK, INFO )
 *  *
 *  -- LAPACK computational routine (version 3.4.0) --  *  -- LAPACK computational routine --
 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --  *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--  *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
 *     November 2011  
 *  *
 *     .. Scalar Arguments ..  *     .. Scalar Arguments ..
       INTEGER            IHI, ILO, INFO, LDH, LDZ, LWORK, N        INTEGER            IHI, ILO, INFO, LDH, LDZ, LWORK, N
Line 338 Line 335
 *     .    DLAHQR because of insufficient subdiagonal scratch space.  *     .    DLAHQR because of insufficient subdiagonal scratch space.
 *     .    (This is a hard limit.) ====  *     .    (This is a hard limit.) ====
       INTEGER            NTINY        INTEGER            NTINY
       PARAMETER          ( NTINY = 11 )        PARAMETER          ( NTINY = 15 )
 *  *
 *     ==== NL allocates some local workspace to help small matrices  *     ==== NL allocates some local workspace to help small matrices
 *     .    through a rare DLAHQR failure.  NL .GT. NTINY = 11 is  *     .    through a rare DLAHQR failure.  NL > NTINY = 15 is
 *     .    required and NL .LE. NMIN = ILAENV(ISPEC=12,...) is recom-  *     .    required and NL <= NMIN = ILAENV(ISPEC=12,...) is recom-
 *     .    mended.  (The default value of NMIN is 75.)  Using NL = 49  *     .    mended.  (The default value of NMIN is 75.)  Using NL = 49
 *     .    allows up to six simultaneous shifts and a 16-by-16  *     .    allows up to six simultaneous shifts and a 16-by-16
 *     .    deflation window.  ====  *     .    deflation window.  ====

Removed from v.1.9  
changed lines
  Added in v.1.19


CVSweb interface <joel.bertrand@systella.fr>