aboutsummaryrefslogtreecommitdiff
path: root/SRC/dgges.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/dgges.f
parent5fe0466a14e395641f4f8a300ecc9dcb8058081b (diff)
Integrating Doxygen in comments
Diffstat (limited to 'SRC/dgges.f')
-rw-r--r--SRC/dgges.f444
1 files changed, 279 insertions, 165 deletions
diff --git a/SRC/dgges.f b/SRC/dgges.f
index 60007d28..2312f122 100644
--- a/SRC/dgges.f
+++ b/SRC/dgges.f
@@ -1,11 +1,288 @@
+*> \brief <b> DGGES computes the eigenvalues, the Schur form, and, optionally, the matrix of Schur vectors for GE matrices</b>
+*
+* =========== DOCUMENTATION ===========
+*
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
+*
+* Definition
+* ==========
+*
+* SUBROUTINE DGGES( JOBVSL, JOBVSR, SORT, SELCTG, N, A, LDA, B, LDB,
+* SDIM, ALPHAR, ALPHAI, BETA, VSL, LDVSL, VSR,
+* LDVSR, WORK, LWORK, BWORK, INFO )
+*
+* .. Scalar Arguments ..
+* CHARACTER JOBVSL, JOBVSR, SORT
+* INTEGER INFO, LDA, LDB, LDVSL, LDVSR, LWORK, N, SDIM
+* ..
+* .. Array Arguments ..
+* LOGICAL BWORK( * )
+* DOUBLE PRECISION A( LDA, * ), ALPHAI( * ), ALPHAR( * ),
+* $ B( LDB, * ), BETA( * ), VSL( LDVSL, * ),
+* $ VSR( LDVSR, * ), WORK( * )
+* ..
+* .. Function Arguments ..
+* LOGICAL SELCTG
+* EXTERNAL SELCTG
+* ..
+*
+* Purpose
+* =======
+*
+*>\details \b Purpose:
+*>\verbatim
+*>
+*> DGGES computes for a pair of N-by-N real nonsymmetric matrices (A,B),
+*> the generalized eigenvalues, the generalized real Schur form (S,T),
+*> optionally, the left and/or right matrices of Schur vectors (VSL and
+*> VSR). This gives the generalized Schur factorization
+*>
+*> (A,B) = ( (VSL)*S*(VSR)**T, (VSL)*T*(VSR)**T )
+*>
+*> Optionally, it also orders the eigenvalues so that a selected cluster
+*> of eigenvalues appears in the leading diagonal blocks of the upper
+*> quasi-triangular matrix S and the upper triangular matrix T.The
+*> leading columns of VSL and VSR then form an orthonormal basis for the
+*> corresponding left and right eigenspaces (deflating subspaces).
+*>
+*> (If only the generalized eigenvalues are needed, use the driver
+*> DGGEV instead, which is faster.)
+*>
+*> A generalized eigenvalue for a pair of matrices (A,B) is a scalar w
+*> or a ratio alpha/beta = w, such that A - w*B is singular. It is
+*> usually represented as the pair (alpha,beta), as there is a
+*> reasonable interpretation for beta=0 or both being zero.
+*>
+*> A pair of matrices (S,T) is in generalized real Schur form if T is
+*> upper triangular with non-negative diagonal and S is block upper
+*> triangular with 1-by-1 and 2-by-2 blocks. 1-by-1 blocks correspond
+*> to real generalized eigenvalues, while 2-by-2 blocks of S will be
+*> "standardized" by making the corresponding elements of T have the
+*> form:
+*> [ a 0 ]
+*> [ 0 b ]
+*>
+*> and the pair of corresponding 2-by-2 blocks in S and T will have a
+*> complex conjugate pair of generalized eigenvalues.
+*>
+*>
+*>\endverbatim
+*
+* Arguments
+* =========
+*
+*> \param[in] JOBVSL
+*> \verbatim
+*> JOBVSL is CHARACTER*1
+*> = 'N': do not compute the left Schur vectors;
+*> = 'V': compute the left Schur vectors.
+*> \endverbatim
+*>
+*> \param[in] JOBVSR
+*> \verbatim
+*> JOBVSR is CHARACTER*1
+*> = 'N': do not compute the right Schur vectors;
+*> = 'V': compute the right Schur vectors.
+*> \endverbatim
+*>
+*> \param[in] SORT
+*> \verbatim
+*> SORT is CHARACTER*1
+*> Specifies whether or not to order the eigenvalues on the
+*> diagonal of the generalized Schur form.
+*> = 'N': Eigenvalues are not ordered;
+*> = 'S': Eigenvalues are ordered (see SELCTG);
+*> \endverbatim
+*>
+*> \param[in] SELCTG
+*> \verbatim
+*> SELCTG is procedure) LOGICAL FUNCTION of three DOUBLE PRECISION arguments
+*> SELCTG must be declared EXTERNAL in the calling subroutine.
+*> If SORT = 'N', SELCTG is not referenced.
+*> If SORT = 'S', SELCTG is used to select eigenvalues to sort
+*> to the top left of the Schur form.
+*> An eigenvalue (ALPHAR(j)+ALPHAI(j))/BETA(j) is selected if
+*> SELCTG(ALPHAR(j),ALPHAI(j),BETA(j)) is true; i.e. if either
+*> one of a complex conjugate pair of eigenvalues is selected,
+*> then both complex eigenvalues are selected.
+*> \endverbatim
+*> \verbatim
+*> Note that in the ill-conditioned case, a selected complex
+*> eigenvalue may no longer satisfy SELCTG(ALPHAR(j),ALPHAI(j),
+*> BETA(j)) = .TRUE. after ordering. INFO is to be set to N+2
+*> in this case.
+*> \endverbatim
+*>
+*> \param[in] N
+*> \verbatim
+*> N is INTEGER
+*> The order of the matrices A, B, VSL, and VSR. N >= 0.
+*> \endverbatim
+*>
+*> \param[in,out] A
+*> \verbatim
+*> A is DOUBLE PRECISION array, dimension (LDA, N)
+*> On entry, the first of the pair of matrices.
+*> On exit, A has been overwritten by its generalized Schur
+*> form S.
+*> \endverbatim
+*>
+*> \param[in] LDA
+*> \verbatim
+*> LDA is INTEGER
+*> The leading dimension of A. LDA >= max(1,N).
+*> \endverbatim
+*>
+*> \param[in,out] B
+*> \verbatim
+*> B is DOUBLE PRECISION array, dimension (LDB, N)
+*> On entry, the second of the pair of matrices.
+*> On exit, B has been overwritten by its generalized Schur
+*> form T.
+*> \endverbatim
+*>
+*> \param[in] LDB
+*> \verbatim
+*> LDB is INTEGER
+*> The leading dimension of B. LDB >= max(1,N).
+*> \endverbatim
+*>
+*> \param[out] SDIM
+*> \verbatim
+*> SDIM is INTEGER
+*> If SORT = 'N', SDIM = 0.
+*> If SORT = 'S', SDIM = number of eigenvalues (after sorting)
+*> for which SELCTG is true. (Complex conjugate pairs for which
+*> SELCTG is true for either eigenvalue count as 2.)
+*> \endverbatim
+*>
+*> \param[out] ALPHAR
+*> \verbatim
+*> ALPHAR is DOUBLE PRECISION array, dimension (N)
+*> \endverbatim
+*>
+*> \param[out] ALPHAI
+*> \verbatim
+*> ALPHAI is DOUBLE PRECISION array, dimension (N)
+*> \endverbatim
+*>
+*> \param[out] BETA
+*> \verbatim
+*> BETA is DOUBLE PRECISION array, dimension (N)
+*> On exit, (ALPHAR(j) + ALPHAI(j)*i)/BETA(j), j=1,...,N, will
+*> be the generalized eigenvalues. ALPHAR(j) + ALPHAI(j)*i,
+*> and BETA(j),j=1,...,N are the diagonals of the complex Schur
+*> form (S,T) that would result if the 2-by-2 diagonal blocks of
+*> the real Schur form of (A,B) were further reduced to
+*> triangular form using 2-by-2 complex unitary transformations.
+*> If ALPHAI(j) is zero, then the j-th eigenvalue is real; if
+*> positive, then the j-th and (j+1)-st eigenvalues are a
+*> complex conjugate pair, with ALPHAI(j+1) negative.
+*> \endverbatim
+*> \verbatim
+*> Note: the quotients ALPHAR(j)/BETA(j) and ALPHAI(j)/BETA(j)
+*> may easily over- or underflow, and BETA(j) may even be zero.
+*> Thus, the user should avoid naively computing the ratio.
+*> However, ALPHAR and ALPHAI will be always less than and
+*> usually comparable with norm(A) in magnitude, and BETA always
+*> less than and usually comparable with norm(B).
+*> \endverbatim
+*>
+*> \param[out] VSL
+*> \verbatim
+*> VSL is DOUBLE PRECISION array, dimension (LDVSL,N)
+*> If JOBVSL = 'V', VSL will contain the left Schur vectors.
+*> Not referenced if JOBVSL = 'N'.
+*> \endverbatim
+*>
+*> \param[in] LDVSL
+*> \verbatim
+*> LDVSL is INTEGER
+*> The leading dimension of the matrix VSL. LDVSL >=1, and
+*> if JOBVSL = 'V', LDVSL >= N.
+*> \endverbatim
+*>
+*> \param[out] VSR
+*> \verbatim
+*> VSR is DOUBLE PRECISION array, dimension (LDVSR,N)
+*> If JOBVSR = 'V', VSR will contain the right Schur vectors.
+*> Not referenced if JOBVSR = 'N'.
+*> \endverbatim
+*>
+*> \param[in] LDVSR
+*> \verbatim
+*> LDVSR is INTEGER
+*> The leading dimension of the matrix VSR. LDVSR >= 1, and
+*> if JOBVSR = 'V', LDVSR >= N.
+*> \endverbatim
+*>
+*> \param[out] WORK
+*> \verbatim
+*> WORK is DOUBLE PRECISION array, dimension (MAX(1,LWORK))
+*> On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
+*> \endverbatim
+*>
+*> \param[in] LWORK
+*> \verbatim
+*> LWORK is INTEGER
+*> The dimension of the array WORK.
+*> If N = 0, LWORK >= 1, else LWORK >= 8*N+16.
+*> For good performance , LWORK must generally be larger.
+*> \endverbatim
+*> \verbatim
+*> If LWORK = -1, then a workspace query is assumed; the routine
+*> only calculates the optimal size of the WORK array, returns
+*> this value as the first entry of the WORK array, and no error
+*> message related to LWORK is issued by XERBLA.
+*> \endverbatim
+*>
+*> \param[out] BWORK
+*> \verbatim
+*> BWORK is LOGICAL array, dimension (N)
+*> Not referenced if SORT = 'N'.
+*> \endverbatim
+*>
+*> \param[out] INFO
+*> \verbatim
+*> INFO is INTEGER
+*> = 0: successful exit
+*> < 0: if INFO = -i, the i-th argument had an illegal value.
+*> = 1,...,N:
+*> The QZ iteration failed. (A,B) are not in Schur
+*> form, but ALPHAR(j), ALPHAI(j), and BETA(j) should
+*> be correct for j=INFO+1,...,N.
+*> > N: =N+1: other than QZ iteration failed in DHGEQZ.
+*> =N+2: after reordering, roundoff changed values of
+*> some complex eigenvalues so that leading
+*> eigenvalues in the Generalized Schur form no
+*> longer satisfy SELCTG=.TRUE. This could also
+*> be caused due to scaling.
+*> =N+3: reordering failed in DTGSEN.
+*> \endverbatim
+*>
+*
+* Authors
+* =======
+*
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
+*
+*> \date November 2011
+*
+*> \ingroup doubleGEeigen
+*
+* =====================================================================
SUBROUTINE DGGES( JOBVSL, JOBVSR, SORT, SELCTG, N, A, LDA, B, LDB,
$ SDIM, ALPHAR, ALPHAI, BETA, VSL, LDVSL, VSR,
$ LDVSR, WORK, LWORK, BWORK, INFO )
*
-* -- LAPACK driver routine (version 3.2) --
+* -- LAPACK eigen routine (version 3.2) --
* -- LAPACK is a software package provided by Univ. of Tennessee, --
* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
-* November 2006
+* November 2011
*
* .. Scalar Arguments ..
CHARACTER JOBVSL, JOBVSR, SORT
@@ -22,169 +299,6 @@
EXTERNAL SELCTG
* ..
*
-* Purpose
-* =======
-*
-* DGGES computes for a pair of N-by-N real nonsymmetric matrices (A,B),
-* the generalized eigenvalues, the generalized real Schur form (S,T),
-* optionally, the left and/or right matrices of Schur vectors (VSL and
-* VSR). This gives the generalized Schur factorization
-*
-* (A,B) = ( (VSL)*S*(VSR)**T, (VSL)*T*(VSR)**T )
-*
-* Optionally, it also orders the eigenvalues so that a selected cluster
-* of eigenvalues appears in the leading diagonal blocks of the upper
-* quasi-triangular matrix S and the upper triangular matrix T.The
-* leading columns of VSL and VSR then form an orthonormal basis for the
-* corresponding left and right eigenspaces (deflating subspaces).
-*
-* (If only the generalized eigenvalues are needed, use the driver
-* DGGEV instead, which is faster.)
-*
-* A generalized eigenvalue for a pair of matrices (A,B) is a scalar w
-* or a ratio alpha/beta = w, such that A - w*B is singular. It is
-* usually represented as the pair (alpha,beta), as there is a
-* reasonable interpretation for beta=0 or both being zero.
-*
-* A pair of matrices (S,T) is in generalized real Schur form if T is
-* upper triangular with non-negative diagonal and S is block upper
-* triangular with 1-by-1 and 2-by-2 blocks. 1-by-1 blocks correspond
-* to real generalized eigenvalues, while 2-by-2 blocks of S will be
-* "standardized" by making the corresponding elements of T have the
-* form:
-* [ a 0 ]
-* [ 0 b ]
-*
-* and the pair of corresponding 2-by-2 blocks in S and T will have a
-* complex conjugate pair of generalized eigenvalues.
-*
-*
-* Arguments
-* =========
-*
-* JOBVSL (input) CHARACTER*1
-* = 'N': do not compute the left Schur vectors;
-* = 'V': compute the left Schur vectors.
-*
-* JOBVSR (input) CHARACTER*1
-* = 'N': do not compute the right Schur vectors;
-* = 'V': compute the right Schur vectors.
-*
-* SORT (input) CHARACTER*1
-* Specifies whether or not to order the eigenvalues on the
-* diagonal of the generalized Schur form.
-* = 'N': Eigenvalues are not ordered;
-* = 'S': Eigenvalues are ordered (see SELCTG);
-*
-* SELCTG (external procedure) LOGICAL FUNCTION of three DOUBLE PRECISION arguments
-* SELCTG must be declared EXTERNAL in the calling subroutine.
-* If SORT = 'N', SELCTG is not referenced.
-* If SORT = 'S', SELCTG is used to select eigenvalues to sort
-* to the top left of the Schur form.
-* An eigenvalue (ALPHAR(j)+ALPHAI(j))/BETA(j) is selected if
-* SELCTG(ALPHAR(j),ALPHAI(j),BETA(j)) is true; i.e. if either
-* one of a complex conjugate pair of eigenvalues is selected,
-* then both complex eigenvalues are selected.
-*
-* Note that in the ill-conditioned case, a selected complex
-* eigenvalue may no longer satisfy SELCTG(ALPHAR(j),ALPHAI(j),
-* BETA(j)) = .TRUE. after ordering. INFO is to be set to N+2
-* in this case.
-*
-* N (input) INTEGER
-* The order of the matrices A, B, VSL, and VSR. N >= 0.
-*
-* A (input/output) DOUBLE PRECISION array, dimension (LDA, N)
-* On entry, the first of the pair of matrices.
-* On exit, A has been overwritten by its generalized Schur
-* form S.
-*
-* LDA (input) INTEGER
-* The leading dimension of A. LDA >= max(1,N).
-*
-* B (input/output) DOUBLE PRECISION array, dimension (LDB, N)
-* On entry, the second of the pair of matrices.
-* On exit, B has been overwritten by its generalized Schur
-* form T.
-*
-* LDB (input) INTEGER
-* The leading dimension of B. LDB >= max(1,N).
-*
-* SDIM (output) INTEGER
-* If SORT = 'N', SDIM = 0.
-* If SORT = 'S', SDIM = number of eigenvalues (after sorting)
-* for which SELCTG is true. (Complex conjugate pairs for which
-* SELCTG is true for either eigenvalue count as 2.)
-*
-* ALPHAR (output) DOUBLE PRECISION array, dimension (N)
-*
-* ALPHAI (output) DOUBLE PRECISION array, dimension (N)
-*
-* BETA (output) DOUBLE PRECISION array, dimension (N)
-* On exit, (ALPHAR(j) + ALPHAI(j)*i)/BETA(j), j=1,...,N, will
-* be the generalized eigenvalues. ALPHAR(j) + ALPHAI(j)*i,
-* and BETA(j),j=1,...,N are the diagonals of the complex Schur
-* form (S,T) that would result if the 2-by-2 diagonal blocks of
-* the real Schur form of (A,B) were further reduced to
-* triangular form using 2-by-2 complex unitary transformations.
-* If ALPHAI(j) is zero, then the j-th eigenvalue is real; if
-* positive, then the j-th and (j+1)-st eigenvalues are a
-* complex conjugate pair, with ALPHAI(j+1) negative.
-*
-* Note: the quotients ALPHAR(j)/BETA(j) and ALPHAI(j)/BETA(j)
-* may easily over- or underflow, and BETA(j) may even be zero.
-* Thus, the user should avoid naively computing the ratio.
-* However, ALPHAR and ALPHAI will be always less than and
-* usually comparable with norm(A) in magnitude, and BETA always
-* less than and usually comparable with norm(B).
-*
-* VSL (output) DOUBLE PRECISION array, dimension (LDVSL,N)
-* If JOBVSL = 'V', VSL will contain the left Schur vectors.
-* Not referenced if JOBVSL = 'N'.
-*
-* LDVSL (input) INTEGER
-* The leading dimension of the matrix VSL. LDVSL >=1, and
-* if JOBVSL = 'V', LDVSL >= N.
-*
-* VSR (output) DOUBLE PRECISION array, dimension (LDVSR,N)
-* If JOBVSR = 'V', VSR will contain the right Schur vectors.
-* Not referenced if JOBVSR = 'N'.
-*
-* LDVSR (input) INTEGER
-* The leading dimension of the matrix VSR. LDVSR >= 1, and
-* if JOBVSR = 'V', LDVSR >= N.
-*
-* WORK (workspace/output) DOUBLE PRECISION array, dimension (MAX(1,LWORK))
-* On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
-*
-* LWORK (input) INTEGER
-* The dimension of the array WORK.
-* If N = 0, LWORK >= 1, else LWORK >= 8*N+16.
-* For good performance , LWORK must generally be larger.
-*
-* If LWORK = -1, then a workspace query is assumed; the routine
-* only calculates the optimal size of the WORK array, returns
-* this value as the first entry of the WORK array, and no error
-* message related to LWORK is issued by XERBLA.
-*
-* BWORK (workspace) LOGICAL array, dimension (N)
-* Not referenced if SORT = 'N'.
-*
-* INFO (output) INTEGER
-* = 0: successful exit
-* < 0: if INFO = -i, the i-th argument had an illegal value.
-* = 1,...,N:
-* The QZ iteration failed. (A,B) are not in Schur
-* form, but ALPHAR(j), ALPHAI(j), and BETA(j) should
-* be correct for j=INFO+1,...,N.
-* > N: =N+1: other than QZ iteration failed in DHGEQZ.
-* =N+2: after reordering, roundoff changed values of
-* some complex eigenvalues so that leading
-* eigenvalues in the Generalized Schur form no
-* longer satisfy SELCTG=.TRUE. This could also
-* be caused due to scaling.
-* =N+3: reordering failed in DTGSEN.
-*
* =====================================================================
*
* .. Parameters ..