summaryrefslogtreecommitdiff
path: root/SRC/sgghrd.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/sgghrd.f
parent5fe0466a14e395641f4f8a300ecc9dcb8058081b (diff)
downloadlapack-e1d39294aee16fa6db9ba079b14442358217db71.tar.gz
lapack-e1d39294aee16fa6db9ba079b14442358217db71.tar.bz2
lapack-e1d39294aee16fa6db9ba079b14442358217db71.zip
Integrating Doxygen in comments
Diffstat (limited to 'SRC/sgghrd.f')
-rw-r--r--SRC/sgghrd.f312
1 files changed, 200 insertions, 112 deletions
diff --git a/SRC/sgghrd.f b/SRC/sgghrd.f
index 765aa3ab..fef49c04 100644
--- a/SRC/sgghrd.f
+++ b/SRC/sgghrd.f
@@ -1,10 +1,208 @@
+*> \brief \b SGGHRD
+*
+* =========== DOCUMENTATION ===========
+*
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
+*
+* Definition
+* ==========
+*
+* SUBROUTINE SGGHRD( COMPQ, COMPZ, N, ILO, IHI, A, LDA, B, LDB, Q,
+* LDQ, Z, LDZ, INFO )
+*
+* .. Scalar Arguments ..
+* CHARACTER COMPQ, COMPZ
+* INTEGER IHI, ILO, INFO, LDA, LDB, LDQ, LDZ, N
+* ..
+* .. Array Arguments ..
+* REAL A( LDA, * ), B( LDB, * ), Q( LDQ, * ),
+* $ Z( LDZ, * )
+* ..
+*
+* Purpose
+* =======
+*
+*>\details \b Purpose:
+*>\verbatim
+*>
+*> SGGHRD reduces a pair of real matrices (A,B) to generalized upper
+*> Hessenberg form using orthogonal transformations, where A is a
+*> general matrix and B is upper triangular. The form of the
+*> generalized eigenvalue problem is
+*> A*x = lambda*B*x,
+*> and B is typically made upper triangular by computing its QR
+*> factorization and moving the orthogonal matrix Q to the left side
+*> of the equation.
+*>
+*> This subroutine simultaneously reduces A to a Hessenberg matrix H:
+*> Q**T*A*Z = H
+*> and transforms B to another upper triangular matrix T:
+*> Q**T*B*Z = T
+*> in order to reduce the problem to its standard form
+*> H*y = lambda*T*y
+*> where y = Z**T*x.
+*>
+*> The orthogonal matrices Q and Z are determined as products of Givens
+*> rotations. They may either be formed explicitly, or they may be
+*> postmultiplied into input matrices Q1 and Z1, so that
+*>
+*> Q1 * A * Z1**T = (Q1*Q) * H * (Z1*Z)**T
+*>
+*> Q1 * B * Z1**T = (Q1*Q) * T * (Z1*Z)**T
+*>
+*> If Q1 is the orthogonal matrix from the QR factorization of B in the
+*> original equation A*x = lambda*B*x, then SGGHRD reduces the original
+*> problem to generalized Hessenberg form.
+*>
+*>\endverbatim
+*
+* Arguments
+* =========
+*
+*> \param[in] COMPQ
+*> \verbatim
+*> COMPQ is CHARACTER*1
+*> = 'N': do not compute Q;
+*> = 'I': Q is initialized to the unit matrix, and the
+*> orthogonal matrix Q is returned;
+*> = 'V': Q must contain an orthogonal matrix Q1 on entry,
+*> and the product Q1*Q is returned.
+*> \endverbatim
+*>
+*> \param[in] COMPZ
+*> \verbatim
+*> COMPZ is CHARACTER*1
+*> = 'N': do not compute Z;
+*> = 'I': Z is initialized to the unit matrix, and the
+*> orthogonal matrix Z is returned;
+*> = 'V': Z must contain an orthogonal matrix Z1 on entry,
+*> and the product Z1*Z is returned.
+*> \endverbatim
+*>
+*> \param[in] N
+*> \verbatim
+*> N is INTEGER
+*> The order of the matrices A and B. N >= 0.
+*> \endverbatim
+*>
+*> \param[in] ILO
+*> \verbatim
+*> ILO is INTEGER
+*> \param[in] IHI
+*> \verbatim
+*> IHI is INTEGER
+*> ILO and IHI mark the rows and columns of A which are to be
+*> reduced. It is assumed that A is already upper triangular
+*> in rows and columns 1:ILO-1 and IHI+1:N. ILO and IHI are
+*> normally set by a previous call to SGGBAL; otherwise they
+*> should be set to 1 and N respectively.
+*> 1 <= ILO <= IHI <= N, if N > 0; ILO=1 and IHI=0, if N=0.
+*> \endverbatim
+*> \endverbatim
+*>
+*> \param[in,out] A
+*> \verbatim
+*> A is REAL array, dimension (LDA, N)
+*> On entry, the N-by-N general matrix to be reduced.
+*> On exit, the upper triangle and the first subdiagonal of A
+*> are overwritten with the upper Hessenberg matrix H, and the
+*> rest is set to zero.
+*> \endverbatim
+*>
+*> \param[in] LDA
+*> \verbatim
+*> LDA is INTEGER
+*> The leading dimension of the array A. LDA >= max(1,N).
+*> \endverbatim
+*>
+*> \param[in,out] B
+*> \verbatim
+*> B is REAL array, dimension (LDB, N)
+*> On entry, the N-by-N upper triangular matrix B.
+*> On exit, the upper triangular matrix T = Q**T B Z. The
+*> elements below the diagonal are set to zero.
+*> \endverbatim
+*>
+*> \param[in] LDB
+*> \verbatim
+*> LDB is INTEGER
+*> The leading dimension of the array B. LDB >= max(1,N).
+*> \endverbatim
+*>
+*> \param[in,out] Q
+*> \verbatim
+*> Q is REAL array, dimension (LDQ, N)
+*> On entry, if COMPQ = 'V', the orthogonal matrix Q1,
+*> typically from the QR factorization of B.
+*> On exit, if COMPQ='I', the orthogonal matrix Q, and if
+*> COMPQ = 'V', the product Q1*Q.
+*> Not referenced if COMPQ='N'.
+*> \endverbatim
+*>
+*> \param[in] LDQ
+*> \verbatim
+*> LDQ is INTEGER
+*> The leading dimension of the array Q.
+*> LDQ >= N if COMPQ='V' or 'I'; LDQ >= 1 otherwise.
+*> \endverbatim
+*>
+*> \param[in,out] Z
+*> \verbatim
+*> Z is REAL array, dimension (LDZ, N)
+*> On entry, if COMPZ = 'V', the orthogonal matrix Z1.
+*> On exit, if COMPZ='I', the orthogonal matrix Z, and if
+*> COMPZ = 'V', the product Z1*Z.
+*> Not referenced if COMPZ='N'.
+*> \endverbatim
+*>
+*> \param[in] LDZ
+*> \verbatim
+*> LDZ is INTEGER
+*> The leading dimension of the array Z.
+*> LDZ >= N if COMPZ='V' or 'I'; LDZ >= 1 otherwise.
+*> \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 realOTHERcomputational
+*
+*
+* Further Details
+* ===============
+*>\details \b Further \b Details
+*> \verbatim
+*>
+*> This routine reduces A to Hessenberg and B to triangular form by
+*> an unblocked reduction, as described in _Matrix_Computations_,
+*> by Golub and Van Loan (Johns Hopkins Press.)
+*>
+*> \endverbatim
+*>
+* =====================================================================
SUBROUTINE SGGHRD( COMPQ, COMPZ, N, ILO, IHI, A, LDA, B, LDB, Q,
$ LDQ, Z, LDZ, INFO )
*
-* -- LAPACK routine (version 3.2) --
+* -- LAPACK computational 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 COMPQ, COMPZ
@@ -15,116 +213,6 @@
$ Z( LDZ, * )
* ..
*
-* Purpose
-* =======
-*
-* SGGHRD reduces a pair of real matrices (A,B) to generalized upper
-* Hessenberg form using orthogonal transformations, where A is a
-* general matrix and B is upper triangular. The form of the
-* generalized eigenvalue problem is
-* A*x = lambda*B*x,
-* and B is typically made upper triangular by computing its QR
-* factorization and moving the orthogonal matrix Q to the left side
-* of the equation.
-*
-* This subroutine simultaneously reduces A to a Hessenberg matrix H:
-* Q**T*A*Z = H
-* and transforms B to another upper triangular matrix T:
-* Q**T*B*Z = T
-* in order to reduce the problem to its standard form
-* H*y = lambda*T*y
-* where y = Z**T*x.
-*
-* The orthogonal matrices Q and Z are determined as products of Givens
-* rotations. They may either be formed explicitly, or they may be
-* postmultiplied into input matrices Q1 and Z1, so that
-*
-* Q1 * A * Z1**T = (Q1*Q) * H * (Z1*Z)**T
-*
-* Q1 * B * Z1**T = (Q1*Q) * T * (Z1*Z)**T
-*
-* If Q1 is the orthogonal matrix from the QR factorization of B in the
-* original equation A*x = lambda*B*x, then SGGHRD reduces the original
-* problem to generalized Hessenberg form.
-*
-* Arguments
-* =========
-*
-* COMPQ (input) CHARACTER*1
-* = 'N': do not compute Q;
-* = 'I': Q is initialized to the unit matrix, and the
-* orthogonal matrix Q is returned;
-* = 'V': Q must contain an orthogonal matrix Q1 on entry,
-* and the product Q1*Q is returned.
-*
-* COMPZ (input) CHARACTER*1
-* = 'N': do not compute Z;
-* = 'I': Z is initialized to the unit matrix, and the
-* orthogonal matrix Z is returned;
-* = 'V': Z must contain an orthogonal matrix Z1 on entry,
-* and the product Z1*Z is returned.
-*
-* N (input) INTEGER
-* The order of the matrices A and B. N >= 0.
-*
-* ILO (input) INTEGER
-* IHI (input) INTEGER
-* ILO and IHI mark the rows and columns of A which are to be
-* reduced. It is assumed that A is already upper triangular
-* in rows and columns 1:ILO-1 and IHI+1:N. ILO and IHI are
-* normally set by a previous call to SGGBAL; otherwise they
-* should be set to 1 and N respectively.
-* 1 <= ILO <= IHI <= N, if N > 0; ILO=1 and IHI=0, if N=0.
-*
-* A (input/output) REAL array, dimension (LDA, N)
-* On entry, the N-by-N general matrix to be reduced.
-* On exit, the upper triangle and the first subdiagonal of A
-* are overwritten with the upper Hessenberg matrix H, and the
-* rest is set to zero.
-*
-* LDA (input) INTEGER
-* The leading dimension of the array A. LDA >= max(1,N).
-*
-* B (input/output) REAL array, dimension (LDB, N)
-* On entry, the N-by-N upper triangular matrix B.
-* On exit, the upper triangular matrix T = Q**T B Z. The
-* elements below the diagonal are set to zero.
-*
-* LDB (input) INTEGER
-* The leading dimension of the array B. LDB >= max(1,N).
-*
-* Q (input/output) REAL array, dimension (LDQ, N)
-* On entry, if COMPQ = 'V', the orthogonal matrix Q1,
-* typically from the QR factorization of B.
-* On exit, if COMPQ='I', the orthogonal matrix Q, and if
-* COMPQ = 'V', the product Q1*Q.
-* Not referenced if COMPQ='N'.
-*
-* LDQ (input) INTEGER
-* The leading dimension of the array Q.
-* LDQ >= N if COMPQ='V' or 'I'; LDQ >= 1 otherwise.
-*
-* Z (input/output) REAL array, dimension (LDZ, N)
-* On entry, if COMPZ = 'V', the orthogonal matrix Z1.
-* On exit, if COMPZ='I', the orthogonal matrix Z, and if
-* COMPZ = 'V', the product Z1*Z.
-* Not referenced if COMPZ='N'.
-*
-* LDZ (input) INTEGER
-* The leading dimension of the array Z.
-* LDZ >= N if COMPZ='V' or 'I'; LDZ >= 1 otherwise.
-*
-* INFO (output) INTEGER
-* = 0: successful exit.
-* < 0: if INFO = -i, the i-th argument had an illegal value.
-*
-* Further Details
-* ===============
-*
-* This routine reduces A to Hessenberg and B to triangular form by
-* an unblocked reduction, as described in _Matrix_Computations_,
-* by Golub and Van Loan (Johns Hopkins Press.)
-*
* =====================================================================
*
* .. Parameters ..