summaryrefslogtreecommitdiff
path: root/SRC/ztrevc.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/ztrevc.f
parent5fe0466a14e395641f4f8a300ecc9dcb8058081b (diff)
downloadlapack-e1d39294aee16fa6db9ba079b14442358217db71.tar.gz
lapack-e1d39294aee16fa6db9ba079b14442358217db71.tar.bz2
lapack-e1d39294aee16fa6db9ba079b14442358217db71.zip
Integrating Doxygen in comments
Diffstat (limited to 'SRC/ztrevc.f')
-rw-r--r--SRC/ztrevc.f333
1 files changed, 213 insertions, 120 deletions
diff --git a/SRC/ztrevc.f b/SRC/ztrevc.f
index e74a4179..b06eb430 100644
--- a/SRC/ztrevc.f
+++ b/SRC/ztrevc.f
@@ -1,10 +1,221 @@
+*> \brief \b ZTREVC
+*
+* =========== DOCUMENTATION ===========
+*
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
+*
+* Definition
+* ==========
+*
+* SUBROUTINE ZTREVC( SIDE, HOWMNY, SELECT, N, T, LDT, VL, LDVL, VR,
+* LDVR, MM, M, WORK, RWORK, INFO )
+*
+* .. Scalar Arguments ..
+* CHARACTER HOWMNY, SIDE
+* INTEGER INFO, LDT, LDVL, LDVR, M, MM, N
+* ..
+* .. Array Arguments ..
+* LOGICAL SELECT( * )
+* DOUBLE PRECISION RWORK( * )
+* COMPLEX*16 T( LDT, * ), VL( LDVL, * ), VR( LDVR, * ),
+* $ WORK( * )
+* ..
+*
+* Purpose
+* =======
+*
+*>\details \b Purpose:
+*>\verbatim
+*>
+*> ZTREVC computes some or all of the right and/or left eigenvectors of
+*> a complex upper triangular matrix T.
+*> Matrices of this type are produced by the Schur factorization of
+*> a complex general matrix: A = Q*T*Q**H, as computed by ZHSEQR.
+*>
+*> The right eigenvector x and the left eigenvector y of T corresponding
+*> to an eigenvalue w are defined by:
+*>
+*> T*x = w*x, (y**H)*T = w*(y**H)
+*>
+*> where y**H denotes the conjugate transpose of the vector y.
+*> The eigenvalues are not input to this routine, but are read directly
+*> from the diagonal of T.
+*>
+*> This routine returns the matrices X and/or Y of right and left
+*> eigenvectors of T, or the products Q*X and/or Q*Y, where Q is an
+*> input matrix. If Q is the unitary factor that reduces a matrix A to
+*> Schur form T, then Q*X and Q*Y are the matrices of right and left
+*> eigenvectors of A.
+*>
+*>\endverbatim
+*
+* Arguments
+* =========
+*
+*> \param[in] SIDE
+*> \verbatim
+*> SIDE is CHARACTER*1
+*> = 'R': compute right eigenvectors only;
+*> = 'L': compute left eigenvectors only;
+*> = 'B': compute both right and left eigenvectors.
+*> \endverbatim
+*>
+*> \param[in] HOWMNY
+*> \verbatim
+*> HOWMNY is CHARACTER*1
+*> = 'A': compute all right and/or left eigenvectors;
+*> = 'B': compute all right and/or left eigenvectors,
+*> backtransformed using the matrices supplied in
+*> VR and/or VL;
+*> = 'S': compute selected right and/or left eigenvectors,
+*> as indicated by the logical array SELECT.
+*> \endverbatim
+*>
+*> \param[in] SELECT
+*> \verbatim
+*> SELECT is LOGICAL array, dimension (N)
+*> If HOWMNY = 'S', SELECT specifies the eigenvectors to be
+*> computed.
+*> The eigenvector corresponding to the j-th eigenvalue is
+*> computed if SELECT(j) = .TRUE..
+*> Not referenced if HOWMNY = 'A' or 'B'.
+*> \endverbatim
+*>
+*> \param[in] N
+*> \verbatim
+*> N is INTEGER
+*> The order of the matrix T. N >= 0.
+*> \endverbatim
+*>
+*> \param[in,out] T
+*> \verbatim
+*> T is COMPLEX*16 array, dimension (LDT,N)
+*> The upper triangular matrix T. T is modified, but restored
+*> on exit.
+*> \endverbatim
+*>
+*> \param[in] LDT
+*> \verbatim
+*> LDT is INTEGER
+*> The leading dimension of the array T. LDT >= max(1,N).
+*> \endverbatim
+*>
+*> \param[in,out] VL
+*> \verbatim
+*> VL is COMPLEX*16 array, dimension (LDVL,MM)
+*> On entry, if SIDE = 'L' or 'B' and HOWMNY = 'B', VL must
+*> contain an N-by-N matrix Q (usually the unitary matrix Q of
+*> Schur vectors returned by ZHSEQR).
+*> On exit, if SIDE = 'L' or 'B', VL contains:
+*> if HOWMNY = 'A', the matrix Y of left eigenvectors of T;
+*> if HOWMNY = 'B', the matrix Q*Y;
+*> if HOWMNY = 'S', the left eigenvectors of T specified by
+*> SELECT, stored consecutively in the columns
+*> of VL, in the same order as their
+*> eigenvalues.
+*> Not referenced if SIDE = 'R'.
+*> \endverbatim
+*>
+*> \param[in] LDVL
+*> \verbatim
+*> LDVL is INTEGER
+*> The leading dimension of the array VL. LDVL >= 1, and if
+*> SIDE = 'L' or 'B', LDVL >= N.
+*> \endverbatim
+*>
+*> \param[in,out] VR
+*> \verbatim
+*> VR is COMPLEX*16 array, dimension (LDVR,MM)
+*> On entry, if SIDE = 'R' or 'B' and HOWMNY = 'B', VR must
+*> contain an N-by-N matrix Q (usually the unitary matrix Q of
+*> Schur vectors returned by ZHSEQR).
+*> On exit, if SIDE = 'R' or 'B', VR contains:
+*> if HOWMNY = 'A', the matrix X of right eigenvectors of T;
+*> if HOWMNY = 'B', the matrix Q*X;
+*> if HOWMNY = 'S', the right eigenvectors of T specified by
+*> SELECT, stored consecutively in the columns
+*> of VR, in the same order as their
+*> eigenvalues.
+*> Not referenced if SIDE = 'L'.
+*> \endverbatim
+*>
+*> \param[in] LDVR
+*> \verbatim
+*> LDVR is INTEGER
+*> The leading dimension of the array VR. LDVR >= 1, and if
+*> SIDE = 'R' or 'B'; LDVR >= N.
+*> \endverbatim
+*>
+*> \param[in] MM
+*> \verbatim
+*> MM is INTEGER
+*> The number of columns in the arrays VL and/or VR. MM >= M.
+*> \endverbatim
+*>
+*> \param[out] M
+*> \verbatim
+*> M is INTEGER
+*> The number of columns in the arrays VL and/or VR actually
+*> used to store the eigenvectors. If HOWMNY = 'A' or 'B', M
+*> is set to N. Each selected eigenvector occupies one
+*> column.
+*> \endverbatim
+*>
+*> \param[out] WORK
+*> \verbatim
+*> WORK is COMPLEX*16 array, dimension (2*N)
+*> \endverbatim
+*>
+*> \param[out] RWORK
+*> \verbatim
+*> RWORK is DOUBLE PRECISION array, dimension (N)
+*> \endverbatim
+*>
+*> \param[out] INFO
+*> \verbatim
+*> INFO is INTEGER
+*> = 0: successful exit
+*> < 0: if INFO = -i, the i-th argument had an illegal value
+*> \endverbatim
+*>
+*
+* Authors
+* =======
+*
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
+*
+*> \date November 2011
+*
+*> \ingroup complex16OTHERcomputational
+*
+*
+* Further Details
+* ===============
+*>\details \b Further \b Details
+*> \verbatim
+*>
+*> The algorithm used in this program is basically backward (forward)
+*> substitution, with scaling to make the the code robust against
+*> possible overflow.
+*>
+*> Each eigenvector is normalized so that the element of largest
+*> magnitude has magnitude 1; here the magnitude of a complex number
+*> (x,y) is taken to be |x| + |y|.
+*>
+*> \endverbatim
+*>
+* =====================================================================
SUBROUTINE ZTREVC( SIDE, HOWMNY, SELECT, N, T, LDT, VL, LDVL, VR,
$ LDVR, MM, M, WORK, RWORK, INFO )
*
-* -- LAPACK routine (version 3.3.1) --
+* -- LAPACK computational routine (version 3.3.1) --
* -- LAPACK is a software package provided by Univ. of Tennessee, --
* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
-* -- April 2011 --
+* November 2011
*
* .. Scalar Arguments ..
CHARACTER HOWMNY, SIDE
@@ -17,124 +228,6 @@
$ WORK( * )
* ..
*
-* Purpose
-* =======
-*
-* ZTREVC computes some or all of the right and/or left eigenvectors of
-* a complex upper triangular matrix T.
-* Matrices of this type are produced by the Schur factorization of
-* a complex general matrix: A = Q*T*Q**H, as computed by ZHSEQR.
-*
-* The right eigenvector x and the left eigenvector y of T corresponding
-* to an eigenvalue w are defined by:
-*
-* T*x = w*x, (y**H)*T = w*(y**H)
-*
-* where y**H denotes the conjugate transpose of the vector y.
-* The eigenvalues are not input to this routine, but are read directly
-* from the diagonal of T.
-*
-* This routine returns the matrices X and/or Y of right and left
-* eigenvectors of T, or the products Q*X and/or Q*Y, where Q is an
-* input matrix. If Q is the unitary factor that reduces a matrix A to
-* Schur form T, then Q*X and Q*Y are the matrices of right and left
-* eigenvectors of A.
-*
-* Arguments
-* =========
-*
-* SIDE (input) CHARACTER*1
-* = 'R': compute right eigenvectors only;
-* = 'L': compute left eigenvectors only;
-* = 'B': compute both right and left eigenvectors.
-*
-* HOWMNY (input) CHARACTER*1
-* = 'A': compute all right and/or left eigenvectors;
-* = 'B': compute all right and/or left eigenvectors,
-* backtransformed using the matrices supplied in
-* VR and/or VL;
-* = 'S': compute selected right and/or left eigenvectors,
-* as indicated by the logical array SELECT.
-*
-* SELECT (input) LOGICAL array, dimension (N)
-* If HOWMNY = 'S', SELECT specifies the eigenvectors to be
-* computed.
-* The eigenvector corresponding to the j-th eigenvalue is
-* computed if SELECT(j) = .TRUE..
-* Not referenced if HOWMNY = 'A' or 'B'.
-*
-* N (input) INTEGER
-* The order of the matrix T. N >= 0.
-*
-* T (input/output) COMPLEX*16 array, dimension (LDT,N)
-* The upper triangular matrix T. T is modified, but restored
-* on exit.
-*
-* LDT (input) INTEGER
-* The leading dimension of the array T. LDT >= max(1,N).
-*
-* VL (input/output) COMPLEX*16 array, dimension (LDVL,MM)
-* On entry, if SIDE = 'L' or 'B' and HOWMNY = 'B', VL must
-* contain an N-by-N matrix Q (usually the unitary matrix Q of
-* Schur vectors returned by ZHSEQR).
-* On exit, if SIDE = 'L' or 'B', VL contains:
-* if HOWMNY = 'A', the matrix Y of left eigenvectors of T;
-* if HOWMNY = 'B', the matrix Q*Y;
-* if HOWMNY = 'S', the left eigenvectors of T specified by
-* SELECT, stored consecutively in the columns
-* of VL, in the same order as their
-* eigenvalues.
-* Not referenced if SIDE = 'R'.
-*
-* LDVL (input) INTEGER
-* The leading dimension of the array VL. LDVL >= 1, and if
-* SIDE = 'L' or 'B', LDVL >= N.
-*
-* VR (input/output) COMPLEX*16 array, dimension (LDVR,MM)
-* On entry, if SIDE = 'R' or 'B' and HOWMNY = 'B', VR must
-* contain an N-by-N matrix Q (usually the unitary matrix Q of
-* Schur vectors returned by ZHSEQR).
-* On exit, if SIDE = 'R' or 'B', VR contains:
-* if HOWMNY = 'A', the matrix X of right eigenvectors of T;
-* if HOWMNY = 'B', the matrix Q*X;
-* if HOWMNY = 'S', the right eigenvectors of T specified by
-* SELECT, stored consecutively in the columns
-* of VR, in the same order as their
-* eigenvalues.
-* Not referenced if SIDE = 'L'.
-*
-* LDVR (input) INTEGER
-* The leading dimension of the array VR. LDVR >= 1, and if
-* SIDE = 'R' or 'B'; LDVR >= N.
-*
-* MM (input) INTEGER
-* The number of columns in the arrays VL and/or VR. MM >= M.
-*
-* M (output) INTEGER
-* The number of columns in the arrays VL and/or VR actually
-* used to store the eigenvectors. If HOWMNY = 'A' or 'B', M
-* is set to N. Each selected eigenvector occupies one
-* column.
-*
-* WORK (workspace) COMPLEX*16 array, dimension (2*N)
-*
-* RWORK (workspace) DOUBLE PRECISION array, dimension (N)
-*
-* INFO (output) INTEGER
-* = 0: successful exit
-* < 0: if INFO = -i, the i-th argument had an illegal value
-*
-* Further Details
-* ===============
-*
-* The algorithm used in this program is basically backward (forward)
-* substitution, with scaling to make the the code robust against
-* possible overflow.
-*
-* Each eigenvector is normalized so that the element of largest
-* magnitude has magnitude 1; here the magnitude of a complex number
-* (x,y) is taken to be |x| + |y|.
-*
* =====================================================================
*
* .. Parameters ..