summaryrefslogtreecommitdiff
path: root/SRC/zlabrd.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/zlabrd.f
parent5fe0466a14e395641f4f8a300ecc9dcb8058081b (diff)
downloadlapack-e1d39294aee16fa6db9ba079b14442358217db71.tar.gz
lapack-e1d39294aee16fa6db9ba079b14442358217db71.tar.bz2
lapack-e1d39294aee16fa6db9ba079b14442358217db71.zip
Integrating Doxygen in comments
Diffstat (limited to 'SRC/zlabrd.f')
-rw-r--r--SRC/zlabrd.f279
1 files changed, 159 insertions, 120 deletions
diff --git a/SRC/zlabrd.f b/SRC/zlabrd.f
index ac41b178..729d7967 100644
--- a/SRC/zlabrd.f
+++ b/SRC/zlabrd.f
@@ -1,139 +1,178 @@
- SUBROUTINE ZLABRD( M, N, NB, A, LDA, D, E, TAUQ, TAUP, X, LDX, Y,
- $ LDY )
-*
-* -- LAPACK auxiliary 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 --
-*
-* .. Scalar Arguments ..
- INTEGER LDA, LDX, LDY, M, N, NB
-* ..
-* .. Array Arguments ..
- DOUBLE PRECISION D( * ), E( * )
- COMPLEX*16 A( LDA, * ), TAUP( * ), TAUQ( * ), X( LDX, * ),
- $ Y( LDY, * )
-* ..
-*
+*> \brief \b ZLABRD
+*
+* =========== DOCUMENTATION ===========
+*
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
+*
+* Definition
+* ==========
+*
+* SUBROUTINE ZLABRD( M, N, NB, A, LDA, D, E, TAUQ, TAUP, X, LDX, Y,
+* LDY )
+*
+* .. Scalar Arguments ..
+* INTEGER LDA, LDX, LDY, M, N, NB
+* ..
+* .. Array Arguments ..
+* DOUBLE PRECISION D( * ), E( * )
+* COMPLEX*16 A( LDA, * ), TAUP( * ), TAUQ( * ), X( LDX, * ),
+* $ Y( LDY, * )
+* ..
+*
* Purpose
* =======
*
-* ZLABRD reduces the first NB rows and columns of a complex general
-* m by n matrix A to upper or lower real bidiagonal form by a unitary
-* transformation Q**H * A * P, and returns the matrices X and Y which
-* are needed to apply the transformation to the unreduced part of A.
-*
-* If m >= n, A is reduced to upper bidiagonal form; if m < n, to lower
-* bidiagonal form.
-*
-* This is an auxiliary routine called by ZGEBRD
+*>\details \b Purpose:
+*>\verbatim
+*>
+*> ZLABRD reduces the first NB rows and columns of a complex general
+*> m by n matrix A to upper or lower real bidiagonal form by a unitary
+*> transformation Q**H * A * P, and returns the matrices X and Y which
+*> are needed to apply the transformation to the unreduced part of A.
+*>
+*> If m >= n, A is reduced to upper bidiagonal form; if m < n, to lower
+*> bidiagonal form.
+*>
+*> This is an auxiliary routine called by ZGEBRD
+*>
+*>\endverbatim
*
* Arguments
* =========
*
-* M (input) INTEGER
-* The number of rows in the matrix A.
-*
-* N (input) INTEGER
-* The number of columns in the matrix A.
-*
-* NB (input) INTEGER
-* The number of leading rows and columns of A to be reduced.
-*
-* A (input/output) COMPLEX*16 array, dimension (LDA,N)
-* On entry, the m by n general matrix to be reduced.
-* On exit, the first NB rows and columns of the matrix are
-* overwritten; the rest of the array is unchanged.
-* If m >= n, elements on and below the diagonal in the first NB
-* columns, with the array TAUQ, represent the unitary
-* matrix Q as a product of elementary reflectors; and
-* elements above the diagonal in the first NB rows, with the
-* array TAUP, represent the unitary matrix P as a product
-* of elementary reflectors.
-* If m < n, elements below the diagonal in the first NB
-* columns, with the array TAUQ, represent the unitary
-* matrix Q as a product of elementary reflectors, and
-* elements on and above the diagonal in the first NB rows,
-* with the array TAUP, represent the unitary matrix P as
-* a product of elementary reflectors.
-* See Further Details.
-*
-* LDA (input) INTEGER
-* The leading dimension of the array A. LDA >= max(1,M).
-*
-* D (output) DOUBLE PRECISION array, dimension (NB)
-* The diagonal elements of the first NB rows and columns of
-* the reduced matrix. D(i) = A(i,i).
-*
-* E (output) DOUBLE PRECISION array, dimension (NB)
-* The off-diagonal elements of the first NB rows and columns of
-* the reduced matrix.
-*
-* TAUQ (output) COMPLEX*16 array dimension (NB)
-* The scalar factors of the elementary reflectors which
-* represent the unitary matrix Q. See Further Details.
-*
-* TAUP (output) COMPLEX*16 array, dimension (NB)
-* The scalar factors of the elementary reflectors which
-* represent the unitary matrix P. See Further Details.
+*> \param[in] M
+*> \verbatim
+*> M is INTEGER
+*> The number of rows in the matrix A.
+*> \endverbatim
+*>
+*> \param[in] N
+*> \verbatim
+*> N is INTEGER
+*> The number of columns in the matrix A.
+*> \endverbatim
+*>
+*> \param[in] NB
+*> \verbatim
+*> NB is INTEGER
+*> The number of leading rows and columns of A to be reduced.
+*> \endverbatim
+*>
+*
+* Authors
+* =======
*
-* X (output) COMPLEX*16 array, dimension (LDX,NB)
-* The m-by-nb matrix X required to update the unreduced part
-* of A.
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
*
-* LDX (input) INTEGER
-* The leading dimension of the array X. LDX >= max(1,M).
+*> \date November 2011
*
-* Y (output) COMPLEX*16 array, dimension (LDY,NB)
-* The n-by-nb matrix Y required to update the unreduced part
-* of A.
+*> \ingroup complex16OTHERauxiliary
*
-* LDY (input) INTEGER
-* The leading dimension of the array Y. LDY >= max(1,N).
*
* Further Details
* ===============
+*>\details \b Further \b Details
+*> \verbatim
+* See Further Details.
+*>
+*> LDA (input) INTEGER
+*> The leading dimension of the array A. LDA >= max(1,M).
+*>
+*> D (output) DOUBLE PRECISION array, dimension (NB)
+*> The diagonal elements of the first NB rows and columns of
+*> the reduced matrix. D(i) = A(i,i).
+*>
+*> E (output) DOUBLE PRECISION array, dimension (NB)
+*> The off-diagonal elements of the first NB rows and columns of
+*> the reduced matrix.
+*>
+*> TAUQ (output) COMPLEX*16 array dimension (NB)
+*> The scalar factors of the elementary reflectors which
+*> represent the unitary matrix Q. See Further Details.
+*>
+*> TAUP (output) COMPLEX*16 array, dimension (NB)
+*> The scalar factors of the elementary reflectors which
+*> represent the unitary matrix P. See Further Details.
+*>
+*> X (output) COMPLEX*16 array, dimension (LDX,NB)
+*> The m-by-nb matrix X required to update the unreduced part
+*> of A.
+*>
+*> LDX (input) INTEGER
+*> The leading dimension of the array X. LDX >= max(1,M).
+*>
+*> Y (output) COMPLEX*16 array, dimension (LDY,NB)
+*> The n-by-nb matrix Y required to update the unreduced part
+*> of A.
+*>
+*> LDY (input) INTEGER
+*> The leading dimension of the array Y. LDY >= max(1,N).
+*>
+*>
+*> The matrices Q and P are represented as products of elementary
+*> reflectors:
+*>
+*> Q = H(1) H(2) . . . H(nb) and P = G(1) G(2) . . . G(nb)
+*>
+*> Each H(i) and G(i) has the form:
+*>
+*> H(i) = I - tauq * v * v**H and G(i) = I - taup * u * u**H
+*>
+*> where tauq and taup are complex scalars, and v and u are complex
+*> vectors.
+*>
+*> If m >= n, v(1:i-1) = 0, v(i) = 1, and v(i:m) is stored on exit in
+*> A(i:m,i); u(1:i) = 0, u(i+1) = 1, and u(i+1:n) is stored on exit in
+*> A(i,i+1:n); tauq is stored in TAUQ(i) and taup in TAUP(i).
+*>
+*> If m < n, v(1:i) = 0, v(i+1) = 1, and v(i+1:m) is stored on exit in
+*> A(i+2:m,i); u(1:i-1) = 0, u(i) = 1, and u(i:n) is stored on exit in
+*> A(i,i+1:n); tauq is stored in TAUQ(i) and taup in TAUP(i).
+*>
+*> The elements of the vectors v and u together form the m-by-nb matrix
+*> V and the nb-by-n matrix U**H which are needed, with X and Y, to apply
+*> the transformation to the unreduced part of the matrix, using a block
+*> update of the form: A := A - V*Y**H - X*U**H.
+*>
+*> The contents of A on exit are illustrated by the following examples
+*> with nb = 2:
+*>
+*> m = 6 and n = 5 (m > n): m = 5 and n = 6 (m < n):
+*>
+*> ( 1 1 u1 u1 u1 ) ( 1 u1 u1 u1 u1 u1 )
+*> ( v1 1 1 u2 u2 ) ( 1 1 u2 u2 u2 u2 )
+*> ( v1 v2 a a a ) ( v1 1 a a a a )
+*> ( v1 v2 a a a ) ( v1 v2 a a a a )
+*> ( v1 v2 a a a ) ( v1 v2 a a a a )
+*> ( v1 v2 a a a )
+*>
+*> where a denotes an element of the original matrix which is unchanged,
+*> vi denotes an element of the vector defining H(i), and ui an element
+*> of the vector defining G(i).
+*>
+*> \endverbatim
+*>
+* =====================================================================
+ SUBROUTINE ZLABRD( M, N, NB, A, LDA, D, E, TAUQ, TAUP, X, LDX, Y,
+ $ LDY )
*
-* The matrices Q and P are represented as products of elementary
-* reflectors:
-*
-* Q = H(1) H(2) . . . H(nb) and P = G(1) G(2) . . . G(nb)
-*
-* Each H(i) and G(i) has the form:
-*
-* H(i) = I - tauq * v * v**H and G(i) = I - taup * u * u**H
-*
-* where tauq and taup are complex scalars, and v and u are complex
-* vectors.
-*
-* If m >= n, v(1:i-1) = 0, v(i) = 1, and v(i:m) is stored on exit in
-* A(i:m,i); u(1:i) = 0, u(i+1) = 1, and u(i+1:n) is stored on exit in
-* A(i,i+1:n); tauq is stored in TAUQ(i) and taup in TAUP(i).
-*
-* If m < n, v(1:i) = 0, v(i+1) = 1, and v(i+1:m) is stored on exit in
-* A(i+2:m,i); u(1:i-1) = 0, u(i) = 1, and u(i:n) is stored on exit in
-* A(i,i+1:n); tauq is stored in TAUQ(i) and taup in TAUP(i).
-*
-* The elements of the vectors v and u together form the m-by-nb matrix
-* V and the nb-by-n matrix U**H which are needed, with X and Y, to apply
-* the transformation to the unreduced part of the matrix, using a block
-* update of the form: A := A - V*Y**H - X*U**H.
-*
-* The contents of A on exit are illustrated by the following examples
-* with nb = 2:
-*
-* m = 6 and n = 5 (m > n): m = 5 and n = 6 (m < n):
-*
-* ( 1 1 u1 u1 u1 ) ( 1 u1 u1 u1 u1 u1 )
-* ( v1 1 1 u2 u2 ) ( 1 1 u2 u2 u2 u2 )
-* ( v1 v2 a a a ) ( v1 1 a a a a )
-* ( v1 v2 a a a ) ( v1 v2 a a a a )
-* ( v1 v2 a a a ) ( v1 v2 a a a a )
-* ( v1 v2 a a a )
+* -- LAPACK auxiliary 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..--
+* November 2011
*
-* where a denotes an element of the original matrix which is unchanged,
-* vi denotes an element of the vector defining H(i), and ui an element
-* of the vector defining G(i).
+* .. Scalar Arguments ..
+ INTEGER LDA, LDX, LDY, M, N, NB
+* ..
+* .. Array Arguments ..
+ DOUBLE PRECISION D( * ), E( * )
+ COMPLEX*16 A( LDA, * ), TAUP( * ), TAUQ( * ), X( LDX, * ),
+ $ Y( LDY, * )
+* ..
*
* =====================================================================
*