aboutsummaryrefslogtreecommitdiff
path: root/SRC/zlaqr2.f
diff options
context:
space:
mode:
authorjulie <julielangou@users.noreply.github.com>2011-10-06 06:53:11 +0000
committerjulie <julielangou@users.noreply.github.com>2011-10-06 06:53:11 +0000
commite1d39294aee16fa6db9ba079b14442358217db71 (patch)
tree30e5aa04c1f6596991fda5334f63dfb9b8027849 /SRC/zlaqr2.f
parent5fe0466a14e395641f4f8a300ecc9dcb8058081b (diff)
Integrating Doxygen in comments
Diffstat (limited to 'SRC/zlaqr2.f')
-rw-r--r--SRC/zlaqr2.f415
1 files changed, 270 insertions, 145 deletions
diff --git a/SRC/zlaqr2.f b/SRC/zlaqr2.f
index a4ac8186..5e0b103f 100644
--- a/SRC/zlaqr2.f
+++ b/SRC/zlaqr2.f
@@ -1,10 +1,277 @@
+*> \brief \b ZLAQR2
+*
+* =========== DOCUMENTATION ===========
+*
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
+*
+* Definition
+* ==========
+*
+* SUBROUTINE ZLAQR2( WANTT, WANTZ, N, KTOP, KBOT, NW, H, LDH, ILOZ,
+* IHIZ, Z, LDZ, NS, ND, SH, V, LDV, NH, T, LDT,
+* NV, WV, LDWV, WORK, LWORK )
+*
+* .. Scalar Arguments ..
+* INTEGER IHIZ, ILOZ, KBOT, KTOP, LDH, LDT, LDV, LDWV,
+* $ LDZ, LWORK, N, ND, NH, NS, NV, NW
+* LOGICAL WANTT, WANTZ
+* ..
+* .. Array Arguments ..
+* COMPLEX*16 H( LDH, * ), SH( * ), T( LDT, * ), V( LDV, * ),
+* $ WORK( * ), WV( LDWV, * ), Z( LDZ, * )
+* ..
+*
+* Purpose
+* =======
+*
+*>\details \b Purpose:
+*>\verbatim
+*>
+*> ZLAQR2 is identical to ZLAQR3 except that it avoids
+*> recursion by calling ZLAHQR instead of ZLAQR4.
+*>
+*> Aggressive early deflation:
+*>
+*> ZLAQR2 accepts as input an upper Hessenberg matrix
+*> H and performs an unitary similarity transformation
+*> designed to detect and deflate fully converged eigenvalues from
+*> a trailing principal submatrix. On output H has been over-
+*> written by a new Hessenberg matrix that is a perturbation of
+*> an unitary similarity transformation of H. It is to be
+*> hoped that the final version of H has many zero subdiagonal
+*> entries.
+*>
+*>
+*>\endverbatim
+*
+* Arguments
+* =========
+*
+*> \param[in] WANTT
+*> \verbatim
+*> WANTT is LOGICAL
+*> If .TRUE., then the Hessenberg matrix H is fully updated
+*> so that the triangular Schur factor may be
+*> computed (in cooperation with the calling subroutine).
+*> If .FALSE., then only enough of H is updated to preserve
+*> the eigenvalues.
+*> \endverbatim
+*>
+*> \param[in] WANTZ
+*> \verbatim
+*> WANTZ is LOGICAL
+*> If .TRUE., then the unitary matrix Z is updated so
+*> so that the unitary Schur factor may be computed
+*> (in cooperation with the calling subroutine).
+*> If .FALSE., then Z is not referenced.
+*> \endverbatim
+*>
+*> \param[in] N
+*> \verbatim
+*> N is INTEGER
+*> The order of the matrix H and (if WANTZ is .TRUE.) the
+*> order of the unitary matrix Z.
+*> \endverbatim
+*>
+*> \param[in] KTOP
+*> \verbatim
+*> KTOP is INTEGER
+*> It is assumed that either KTOP = 1 or H(KTOP,KTOP-1)=0.
+*> KBOT and KTOP together determine an isolated block
+*> along the diagonal of the Hessenberg matrix.
+*> \endverbatim
+*>
+*> \param[in] KBOT
+*> \verbatim
+*> KBOT is INTEGER
+*> It is assumed without a check that either
+*> KBOT = N or H(KBOT+1,KBOT)=0. KBOT and KTOP together
+*> determine an isolated block along the diagonal of the
+*> Hessenberg matrix.
+*> \endverbatim
+*>
+*> \param[in] NW
+*> \verbatim
+*> NW is INTEGER
+*> Deflation window size. 1 .LE. NW .LE. (KBOT-KTOP+1).
+*> \endverbatim
+*>
+*> \param[in,out] H
+*> \verbatim
+*> H is COMPLEX*16 array, dimension (LDH,N)
+*> On input the initial N-by-N section of H stores the
+*> Hessenberg matrix undergoing aggressive early deflation.
+*> On output H has been transformed by a unitary
+*> similarity transformation, perturbed, and the returned
+*> to Hessenberg form that (it is to be hoped) has some
+*> zero subdiagonal entries.
+*> \endverbatim
+*>
+*> \param[in] LDH
+*> \verbatim
+*> LDH is integer
+*> Leading dimension of H just as declared in the calling
+*> subroutine. N .LE. LDH
+*> \endverbatim
+*>
+*> \param[in] ILOZ
+*> \verbatim
+*> ILOZ is INTEGER
+*> \param[in] IHIZ
+*> \verbatim
+*> IHIZ is INTEGER
+*> Specify the rows of Z to which transformations must be
+*> applied if WANTZ is .TRUE.. 1 .LE. ILOZ .LE. IHIZ .LE. N.
+*> \endverbatim
+*> \endverbatim
+*>
+*> \param[in,out] Z
+*> \verbatim
+*> Z is COMPLEX*16 array, dimension (LDZ,N)
+*> IF WANTZ is .TRUE., then on output, the unitary
+*> similarity transformation mentioned above has been
+*> accumulated into Z(ILOZ:IHIZ,ILO:IHI) from the right.
+*> If WANTZ is .FALSE., then Z is unreferenced.
+*> \endverbatim
+*>
+*> \param[in] LDZ
+*> \verbatim
+*> LDZ is integer
+*> The leading dimension of Z just as declared in the
+*> calling subroutine. 1 .LE. LDZ.
+*> \endverbatim
+*>
+*> \param[out] NS
+*> \verbatim
+*> NS is integer
+*> The number of unconverged (ie approximate) eigenvalues
+*> returned in SR and SI that may be used as shifts by the
+*> calling subroutine.
+*> \endverbatim
+*>
+*> \param[out] ND
+*> \verbatim
+*> ND is integer
+*> The number of converged eigenvalues uncovered by this
+*> subroutine.
+*> \endverbatim
+*>
+*> \param[out] SH
+*> \verbatim
+*> SH is COMPLEX*16 array, dimension KBOT
+*> On output, approximate eigenvalues that may
+*> be used for shifts are stored in SH(KBOT-ND-NS+1)
+*> through SR(KBOT-ND). Converged eigenvalues are
+*> stored in SH(KBOT-ND+1) through SH(KBOT).
+*> \endverbatim
+*>
+*> \param[out] V
+*> \verbatim
+*> V is COMPLEX*16 array, dimension (LDV,NW)
+*> An NW-by-NW work array.
+*> \endverbatim
+*>
+*> \param[in] LDV
+*> \verbatim
+*> LDV is integer scalar
+*> The leading dimension of V just as declared in the
+*> calling subroutine. NW .LE. LDV
+*> \endverbatim
+*>
+*> \param[in] NH
+*> \verbatim
+*> NH is integer scalar
+*> The number of columns of T. NH.GE.NW.
+*> \endverbatim
+*>
+*> \param[out] T
+*> \verbatim
+*> T is COMPLEX*16 array, dimension (LDT,NW)
+*> \endverbatim
+*>
+*> \param[in] LDT
+*> \verbatim
+*> LDT is integer
+*> The leading dimension of T just as declared in the
+*> calling subroutine. NW .LE. LDT
+*> \endverbatim
+*>
+*> \param[in] NV
+*> \verbatim
+*> NV is integer
+*> The number of rows of work array WV available for
+*> workspace. NV.GE.NW.
+*> \endverbatim
+*>
+*> \param[out] WV
+*> \verbatim
+*> WV is COMPLEX*16 array, dimension (LDWV,NW)
+*> \endverbatim
+*>
+*> \param[in] LDWV
+*> \verbatim
+*> LDWV is integer
+*> The leading dimension of W just as declared in the
+*> calling subroutine. NW .LE. LDV
+*> \endverbatim
+*>
+*> \param[out] WORK
+*> \verbatim
+*> WORK is COMPLEX*16 array, dimension LWORK.
+*> On exit, WORK(1) is set to an estimate of the optimal value
+*> of LWORK for the given values of N, NW, KTOP and KBOT.
+*> \endverbatim
+*>
+*> \param[in] LWORK
+*> \verbatim
+*> LWORK is integer
+*> The dimension of the work array WORK. LWORK = 2*NW
+*> suffices, but greater efficiency may result from larger
+*> values of LWORK.
+*> \endverbatim
+*> \verbatim
+*> If LWORK = -1, then a workspace query is assumed; ZLAQR2
+*> only estimates the optimal workspace size for the given
+*> values of N, NW, KTOP and KBOT. The estimate is returned
+*> in WORK(1). No error message related to LWORK is issued
+*> by XERBLA. Neither H nor Z are accessed.
+*> \endverbatim
+*>
+*
+* Authors
+* =======
+*
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
+*
+*> \date November 2011
+*
+*> \ingroup complex16OTHERauxiliary
+*
+*
+* Further Details
+* ===============
+*>\details \b Further \b Details
+*> \verbatim
+*>
+*> Based on contributions by
+*> Karen Braman and Ralph Byers, Department of Mathematics,
+*> University of Kansas, USA
+*>
+*> \endverbatim
+*>
+* =====================================================================
SUBROUTINE ZLAQR2( WANTT, WANTZ, N, KTOP, KBOT, NW, H, LDH, ILOZ,
$ IHIZ, Z, LDZ, NS, ND, SH, V, LDV, NH, T, LDT,
$ NV, WV, LDWV, WORK, LWORK )
*
-* -- LAPACK auxiliary routine (version 3.2.1) --
-* Univ. of Tennessee, Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..
-* -- April 2009 --
+* -- LAPACK auxiliary routine (version 3.2.1) --
+* -- LAPACK is a software package provided by Univ. of Tennessee, --
+* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
+* November 2011
*
* .. Scalar Arguments ..
INTEGER IHIZ, ILOZ, KBOT, KTOP, LDH, LDT, LDV, LDWV,
@@ -16,148 +283,6 @@
$ WORK( * ), WV( LDWV, * ), Z( LDZ, * )
* ..
*
-* Purpose
-* =======
-*
-* ZLAQR2 is identical to ZLAQR3 except that it avoids
-* recursion by calling ZLAHQR instead of ZLAQR4.
-*
-* Aggressive early deflation:
-*
-* ZLAQR2 accepts as input an upper Hessenberg matrix
-* H and performs an unitary similarity transformation
-* designed to detect and deflate fully converged eigenvalues from
-* a trailing principal submatrix. On output H has been over-
-* written by a new Hessenberg matrix that is a perturbation of
-* an unitary similarity transformation of H. It is to be
-* hoped that the final version of H has many zero subdiagonal
-* entries.
-*
-*
-* Arguments
-* =========
-*
-* WANTT (input) LOGICAL
-* If .TRUE., then the Hessenberg matrix H is fully updated
-* so that the triangular Schur factor may be
-* computed (in cooperation with the calling subroutine).
-* If .FALSE., then only enough of H is updated to preserve
-* the eigenvalues.
-*
-* WANTZ (input) LOGICAL
-* If .TRUE., then the unitary matrix Z is updated so
-* so that the unitary Schur factor may be computed
-* (in cooperation with the calling subroutine).
-* If .FALSE., then Z is not referenced.
-*
-* N (input) INTEGER
-* The order of the matrix H and (if WANTZ is .TRUE.) the
-* order of the unitary matrix Z.
-*
-* KTOP (input) INTEGER
-* It is assumed that either KTOP = 1 or H(KTOP,KTOP-1)=0.
-* KBOT and KTOP together determine an isolated block
-* along the diagonal of the Hessenberg matrix.
-*
-* KBOT (input) INTEGER
-* It is assumed without a check that either
-* KBOT = N or H(KBOT+1,KBOT)=0. KBOT and KTOP together
-* determine an isolated block along the diagonal of the
-* Hessenberg matrix.
-*
-* NW (input) INTEGER
-* Deflation window size. 1 .LE. NW .LE. (KBOT-KTOP+1).
-*
-* H (input/output) COMPLEX*16 array, dimension (LDH,N)
-* On input the initial N-by-N section of H stores the
-* Hessenberg matrix undergoing aggressive early deflation.
-* On output H has been transformed by a unitary
-* similarity transformation, perturbed, and the returned
-* to Hessenberg form that (it is to be hoped) has some
-* zero subdiagonal entries.
-*
-* LDH (input) integer
-* Leading dimension of H just as declared in the calling
-* subroutine. N .LE. LDH
-*
-* ILOZ (input) INTEGER
-* IHIZ (input) INTEGER
-* Specify the rows of Z to which transformations must be
-* applied if WANTZ is .TRUE.. 1 .LE. ILOZ .LE. IHIZ .LE. N.
-*
-* Z (input/output) COMPLEX*16 array, dimension (LDZ,N)
-* IF WANTZ is .TRUE., then on output, the unitary
-* similarity transformation mentioned above has been
-* accumulated into Z(ILOZ:IHIZ,ILO:IHI) from the right.
-* If WANTZ is .FALSE., then Z is unreferenced.
-*
-* LDZ (input) integer
-* The leading dimension of Z just as declared in the
-* calling subroutine. 1 .LE. LDZ.
-*
-* NS (output) integer
-* The number of unconverged (ie approximate) eigenvalues
-* returned in SR and SI that may be used as shifts by the
-* calling subroutine.
-*
-* ND (output) integer
-* The number of converged eigenvalues uncovered by this
-* subroutine.
-*
-* SH (output) COMPLEX*16 array, dimension KBOT
-* On output, approximate eigenvalues that may
-* be used for shifts are stored in SH(KBOT-ND-NS+1)
-* through SR(KBOT-ND). Converged eigenvalues are
-* stored in SH(KBOT-ND+1) through SH(KBOT).
-*
-* V (workspace) COMPLEX*16 array, dimension (LDV,NW)
-* An NW-by-NW work array.
-*
-* LDV (input) integer scalar
-* The leading dimension of V just as declared in the
-* calling subroutine. NW .LE. LDV
-*
-* NH (input) integer scalar
-* The number of columns of T. NH.GE.NW.
-*
-* T (workspace) COMPLEX*16 array, dimension (LDT,NW)
-*
-* LDT (input) integer
-* The leading dimension of T just as declared in the
-* calling subroutine. NW .LE. LDT
-*
-* NV (input) integer
-* The number of rows of work array WV available for
-* workspace. NV.GE.NW.
-*
-* WV (workspace) COMPLEX*16 array, dimension (LDWV,NW)
-*
-* LDWV (input) integer
-* The leading dimension of W just as declared in the
-* calling subroutine. NW .LE. LDV
-*
-* WORK (workspace) COMPLEX*16 array, dimension LWORK.
-* On exit, WORK(1) is set to an estimate of the optimal value
-* of LWORK for the given values of N, NW, KTOP and KBOT.
-*
-* LWORK (input) integer
-* The dimension of the work array WORK. LWORK = 2*NW
-* suffices, but greater efficiency may result from larger
-* values of LWORK.
-*
-* If LWORK = -1, then a workspace query is assumed; ZLAQR2
-* only estimates the optimal workspace size for the given
-* values of N, NW, KTOP and KBOT. The estimate is returned
-* in WORK(1). No error message related to LWORK is issued
-* by XERBLA. Neither H nor Z are accessed.
-*
-* Further Details
-* ===============
-*
-* Based on contributions by
-* Karen Braman and Ralph Byers, Department of Mathematics,
-* University of Kansas, USA
-*
* ================================================================
*
* .. Parameters ..