LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
zlatrz.f
Go to the documentation of this file.
1 *> \brief \b ZLATRZ factors an upper trapezoidal matrix by means of unitary transformations.
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download ZLATRZ + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlatrz.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlatrz.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlatrz.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE ZLATRZ( M, N, L, A, LDA, TAU, WORK )
22 *
23 * .. Scalar Arguments ..
24 * INTEGER L, LDA, M, N
25 * ..
26 * .. Array Arguments ..
27 * COMPLEX*16 A( LDA, * ), TAU( * ), WORK( * )
28 * ..
29 *
30 *
31 *> \par Purpose:
32 * =============
33 *>
34 *> \verbatim
35 *>
36 *> ZLATRZ 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.
40 *> \endverbatim
41 *
42 * Arguments:
43 * ==========
44 *
45 *> \param[in] M
46 *> \verbatim
47 *> M is INTEGER
48 *> The number of rows of the matrix A. M >= 0.
49 *> \endverbatim
50 *>
51 *> \param[in] N
52 *> \verbatim
53 *> N is INTEGER
54 *> The number of columns of the matrix A. N >= 0.
55 *> \endverbatim
56 *>
57 *> \param[in] L
58 *> \verbatim
59 *> L is INTEGER
60 *> The number of columns of the matrix A containing the
61 *> meaningful part of the Householder vectors. N-M >= L >= 0.
62 *> \endverbatim
63 *>
64 *> \param[in,out] A
65 *> \verbatim
66 *> A is COMPLEX*16 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.
73 *> \endverbatim
74 *>
75 *> \param[in] LDA
76 *> \verbatim
77 *> LDA is INTEGER
78 *> The leading dimension of the array A. LDA >= max(1,M).
79 *> \endverbatim
80 *>
81 *> \param[out] TAU
82 *> \verbatim
83 *> TAU is COMPLEX*16 array, dimension (M)
84 *> The scalar factors of the elementary reflectors.
85 *> \endverbatim
86 *>
87 *> \param[out] WORK
88 *> \verbatim
89 *> WORK is COMPLEX*16 array, dimension (M)
90 *> \endverbatim
91 *
92 * Authors:
93 * ========
94 *
95 *> \author Univ. of Tennessee
96 *> \author Univ. of California Berkeley
97 *> \author Univ. of Colorado Denver
98 *> \author NAG Ltd.
99 *
100 *> \date September 2012
101 *
102 *> \ingroup complex16OTHERcomputational
103 *
104 *> \par Contributors:
105 * ==================
106 *>
107 *> A. Petitet, Computer Science Dept., Univ. of Tenn., Knoxville, USA
108 *
109 *> \par Further Details:
110 * =====================
111 *>
112 *> \verbatim
113 *>
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
117 *>
118 *> Z( k ) = ( I 0 ),
119 *> ( 0 T( k ) )
120 *>
121 *> where
122 *>
123 *> T( k ) = I - tau*u( k )*u( k )**H, u( k ) = ( 1 ),
124 *> ( 0 )
125 *> ( z( k ) )
126 *>
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.
129 *>
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.
134 *>
135 *> Z is given by
136 *>
137 *> Z = Z( 1 ) * Z( 2 ) * ... * Z( m ).
138 *> \endverbatim
139 *>
140 * =====================================================================
141  SUBROUTINE zlatrz( M, N, L, A, LDA, TAU, WORK )
142 *
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..--
146 * September 2012
147 *
148 * .. Scalar Arguments ..
149  INTEGER l, lda, m, n
150 * ..
151 * .. Array Arguments ..
152  COMPLEX*16 a( lda, * ), tau( * ), work( * )
153 * ..
154 *
155 * =====================================================================
156 *
157 * .. Parameters ..
158  COMPLEX*16 zero
159  parameter( zero = ( 0.0d+0, 0.0d+0 ) )
160 * ..
161 * .. Local Scalars ..
162  INTEGER i
163  COMPLEX*16 alpha
164 * ..
165 * .. External Subroutines ..
166  EXTERNAL zlacgv, zlarfg, zlarz
167 * ..
168 * .. Intrinsic Functions ..
169  INTRINSIC dconjg
170 * ..
171 * .. Executable Statements ..
172 *
173 * Quick return if possible
174 *
175  IF( m.EQ.0 ) THEN
176  return
177  ELSE IF( m.EQ.n ) THEN
178  DO 10 i = 1, n
179  tau( i ) = zero
180  10 continue
181  return
182  END IF
183 *
184  DO 20 i = m, 1, -1
185 *
186 * Generate elementary reflector H(i) to annihilate
187 * [ A(i,i) A(i,n-l+1:n) ]
188 *
189  CALL zlacgv( l, a( i, n-l+1 ), lda )
190  alpha = dconjg( a( i, i ) )
191  CALL zlarfg( l+1, alpha, a( i, n-l+1 ), lda, tau( i ) )
192  tau( i ) = dconjg( tau( i ) )
193 *
194 * Apply H(i) to A(1:i-1,i:n) from the right
195 *
196  CALL zlarz( 'Right', i-1, n-i+1, l, a( i, n-l+1 ), lda,
197  $ dconjg( tau( i ) ), a( 1, i ), lda, work )
198  a( i, i ) = dconjg( alpha )
199 *
200  20 continue
201 *
202  return
203 *
204 * End of ZLATRZ
205 *
206  END