1 *> \brief \b CLATRZ factors an upper trapezoidal matrix by means of unitary transformations.
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download CLATRZ + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/clatrz.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/clatrz.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/clatrz.f">
21 * SUBROUTINE CLATRZ( M, N, L, A, LDA, TAU, WORK )
23 * .. Scalar Arguments ..
24 * INTEGER L, LDA, M, N
26 * .. Array Arguments ..
27 * COMPLEX A( LDA, * ), TAU( * ), WORK( * )
36 *> CLATRZ factors the M-by-(M+L) complex upper trapezoidal matrix
37 *> [ A1 A2 ] = [ A(1:M,1:M) A(1:M,N-L+1:N) ] as ( R 0 ) * Z by means
38 *> of unitary transformations, where Z is an (M+L)-by-(M+L) unitary
39 *> matrix and, R and A1 are M-by-M upper triangular matrices.
48 *> The number of rows of the matrix A. M >= 0.
54 *> The number of columns of the matrix A. N >= 0.
60 *> The number of columns of the matrix A containing the
61 *> meaningful part of the Householder vectors. N-M >= L >= 0.
66 *> A is COMPLEX array, dimension (LDA,N)
67 *> On entry, the leading M-by-N upper trapezoidal part of the
68 *> array A must contain the matrix to be factorized.
69 *> On exit, the leading M-by-M upper triangular part of A
70 *> contains the upper triangular matrix R, and elements N-L+1 to
71 *> N of the first M rows of A, with the array TAU, represent the
72 *> unitary matrix Z as a product of M elementary reflectors.
78 *> The leading dimension of the array A. LDA >= max(1,M).
83 *> TAU is COMPLEX array, dimension (M)
84 *> The scalar factors of the elementary reflectors.
89 *> WORK is COMPLEX array, dimension (M)
95 *> \author Univ. of Tennessee
96 *> \author Univ. of California Berkeley
97 *> \author Univ. of Colorado Denver
100 *> \date September 2012
102 *> \ingroup complexOTHERcomputational
104 *> \par Contributors:
107 *> A. Petitet, Computer Science Dept., Univ. of Tenn., Knoxville, USA
109 *> \par Further Details:
110 * =====================
114 *> The factorization is obtained by Householder's method. The kth
115 *> transformation matrix, Z( k ), which is used to introduce zeros into
116 *> the ( m - k + 1 )th row of A, is given in the form
123 *> T( k ) = I - tau*u( k )*u( k )**H, u( k ) = ( 1 ),
127 *> tau is a scalar and z( k ) is an l element vector. tau and z( k )
128 *> are chosen to annihilate the elements of the kth row of A2.
130 *> The scalar tau is returned in the kth element of TAU and the vector
131 *> u( k ) in the kth row of A2, such that the elements of z( k ) are
132 *> in a( k, l + 1 ), ..., a( k, n ). The elements of R are returned in
133 *> the upper triangular part of A1.
137 *> Z = Z( 1 ) * Z( 2 ) * ... * Z( m ).
140 * =====================================================================
141 SUBROUTINE CLATRZ( M, N, L, A, LDA, TAU, WORK )
143 * -- LAPACK computational routine (version 3.4.2) --
144 * -- LAPACK is a software package provided by Univ. of Tennessee, --
145 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
148 * .. Scalar Arguments ..
151 * .. Array Arguments ..
152 COMPLEX A( LDA, * ), TAU( * ), WORK( * )
155 * =====================================================================
159 PARAMETER ( ZERO = ( 0.0E+0, 0.0E+0 ) )
161 * .. Local Scalars ..
165 * .. External Subroutines ..
166 EXTERNAL CLACGV, CLARFG, CLARZ
168 * .. Intrinsic Functions ..
171 * .. Executable Statements ..
173 * Quick return if possible
177 ELSE IF( M.EQ.N ) THEN
186 * Generate elementary reflector H(i) to annihilate
187 * [ A(i,i) A(i,n-l+1:n) ]
189 CALL CLACGV( L, A( I, N-L+1 ), LDA )
190 ALPHA = CONJG( A( I, I ) )
191 CALL CLARFG( L+1, ALPHA, A( I, N-L+1 ), LDA, TAU( I ) )
192 TAU( I ) = CONJG( TAU( I ) )
194 * Apply H(i) to A(1:i-1,i:n) from the right
196 CALL CLARZ( 'Right', I-1, N-I+1, L, A( I, N-L+1 ), LDA,
197 $ CONJG( TAU( I ) ), A( 1, I ), LDA, WORK )
198 A( I, I ) = CONJG( ALPHA )