LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Macros Modules Pages
zlarz.f
Go to the documentation of this file.
1*> \brief \b ZLARZ applies an elementary reflector (as returned by stzrzf) to a general matrix.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download ZLARZ + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlarz.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlarz.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlarz.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE ZLARZ( SIDE, M, N, L, V, INCV, TAU, C, LDC, WORK )
20*
21* .. Scalar Arguments ..
22* CHARACTER SIDE
23* INTEGER INCV, L, LDC, M, N
24* COMPLEX*16 TAU
25* ..
26* .. Array Arguments ..
27* COMPLEX*16 C( LDC, * ), V( * ), WORK( * )
28* ..
29*
30*
31*> \par Purpose:
32* =============
33*>
34*> \verbatim
35*>
36*> ZLARZ applies a complex elementary reflector H to a complex
37*> M-by-N matrix C, from either the left or the right. H is represented
38*> in the form
39*>
40*> H = I - tau * v * v**H
41*>
42*> where tau is a complex scalar and v is a complex vector.
43*>
44*> If tau = 0, then H is taken to be the unit matrix.
45*>
46*> To apply H**H (the conjugate transpose of H), supply conjg(tau) instead
47*> tau.
48*>
49*> H is a product of k elementary reflectors as returned by ZTZRZF.
50*> \endverbatim
51*
52* Arguments:
53* ==========
54*
55*> \param[in] SIDE
56*> \verbatim
57*> SIDE is CHARACTER*1
58*> = 'L': form H * C
59*> = 'R': form C * H
60*> \endverbatim
61*>
62*> \param[in] M
63*> \verbatim
64*> M is INTEGER
65*> The number of rows of the matrix C.
66*> \endverbatim
67*>
68*> \param[in] N
69*> \verbatim
70*> N is INTEGER
71*> The number of columns of the matrix C.
72*> \endverbatim
73*>
74*> \param[in] L
75*> \verbatim
76*> L is INTEGER
77*> The number of entries of the vector V containing
78*> the meaningful part of the Householder vectors.
79*> If SIDE = 'L', M >= L >= 0, if SIDE = 'R', N >= L >= 0.
80*> \endverbatim
81*>
82*> \param[in] V
83*> \verbatim
84*> V is COMPLEX*16 array, dimension (1+(L-1)*abs(INCV))
85*> The vector v in the representation of H as returned by
86*> ZTZRZF. V is not used if TAU = 0.
87*> \endverbatim
88*>
89*> \param[in] INCV
90*> \verbatim
91*> INCV is INTEGER
92*> The increment between elements of v. INCV <> 0.
93*> \endverbatim
94*>
95*> \param[in] TAU
96*> \verbatim
97*> TAU is COMPLEX*16
98*> The value tau in the representation of H.
99*> \endverbatim
100*>
101*> \param[in,out] C
102*> \verbatim
103*> C is COMPLEX*16 array, dimension (LDC,N)
104*> On entry, the M-by-N matrix C.
105*> On exit, C is overwritten by the matrix H * C if SIDE = 'L',
106*> or C * H if SIDE = 'R'.
107*> \endverbatim
108*>
109*> \param[in] LDC
110*> \verbatim
111*> LDC is INTEGER
112*> The leading dimension of the array C. LDC >= max(1,M).
113*> \endverbatim
114*>
115*> \param[out] WORK
116*> \verbatim
117*> WORK is COMPLEX*16 array, dimension
118*> (N) if SIDE = 'L'
119*> or (M) if SIDE = 'R'
120*> \endverbatim
121*
122* Authors:
123* ========
124*
125*> \author Univ. of Tennessee
126*> \author Univ. of California Berkeley
127*> \author Univ. of Colorado Denver
128*> \author NAG Ltd.
129*
130*> \ingroup larz
131*
132*> \par Contributors:
133* ==================
134*>
135*> A. Petitet, Computer Science Dept., Univ. of Tenn., Knoxville, USA
136*
137*> \par Further Details:
138* =====================
139*>
140*> \verbatim
141*> \endverbatim
142*>
143* =====================================================================
144 SUBROUTINE zlarz( SIDE, M, N, L, V, INCV, TAU, C, LDC, WORK )
145*
146* -- LAPACK computational routine --
147* -- LAPACK is a software package provided by Univ. of Tennessee, --
148* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
149*
150* .. Scalar Arguments ..
151 CHARACTER SIDE
152 INTEGER INCV, L, LDC, M, N
153 COMPLEX*16 TAU
154* ..
155* .. Array Arguments ..
156 COMPLEX*16 C( LDC, * ), V( * ), WORK( * )
157* ..
158*
159* =====================================================================
160*
161* .. Parameters ..
162 COMPLEX*16 ONE, ZERO
163 parameter( one = ( 1.0d+0, 0.0d+0 ),
164 $ zero = ( 0.0d+0, 0.0d+0 ) )
165* ..
166* .. External Subroutines ..
167 EXTERNAL zaxpy, zcopy, zgemv, zgerc, zgeru,
168 $ zlacgv
169* ..
170* .. External Functions ..
171 LOGICAL LSAME
172 EXTERNAL lsame
173* ..
174* .. Executable Statements ..
175*
176 IF( lsame( side, 'L' ) ) THEN
177*
178* Form H * C
179*
180 IF( tau.NE.zero ) THEN
181*
182* w( 1:n ) = conjg( C( 1, 1:n ) )
183*
184 CALL zcopy( n, c, ldc, work, 1 )
185 CALL zlacgv( n, work, 1 )
186*
187* w( 1:n ) = conjg( w( 1:n ) + C( m-l+1:m, 1:n )**H * v( 1:l ) )
188*
189 CALL zgemv( 'Conjugate transpose', l, n, one, c( m-l+1,
190 $ 1 ),
191 $ ldc, v, incv, one, work, 1 )
192 CALL zlacgv( n, work, 1 )
193*
194* C( 1, 1:n ) = C( 1, 1:n ) - tau * w( 1:n )
195*
196 CALL zaxpy( n, -tau, work, 1, c, ldc )
197*
198* C( m-l+1:m, 1:n ) = C( m-l+1:m, 1:n ) - ...
199* tau * v( 1:l ) * w( 1:n )**H
200*
201 CALL zgeru( l, n, -tau, v, incv, work, 1, c( m-l+1, 1 ),
202 $ ldc )
203 END IF
204*
205 ELSE
206*
207* Form C * H
208*
209 IF( tau.NE.zero ) THEN
210*
211* w( 1:m ) = C( 1:m, 1 )
212*
213 CALL zcopy( m, c, 1, work, 1 )
214*
215* w( 1:m ) = w( 1:m ) + C( 1:m, n-l+1:n, 1:n ) * v( 1:l )
216*
217 CALL zgemv( 'No transpose', m, l, one, c( 1, n-l+1 ),
218 $ ldc,
219 $ v, incv, one, work, 1 )
220*
221* C( 1:m, 1 ) = C( 1:m, 1 ) - tau * w( 1:m )
222*
223 CALL zaxpy( m, -tau, work, 1, c, 1 )
224*
225* C( 1:m, n-l+1:n ) = C( 1:m, n-l+1:n ) - ...
226* tau * w( 1:m ) * v( 1:l )**H
227*
228 CALL zgerc( m, l, -tau, work, 1, v, incv, c( 1, n-l+1 ),
229 $ ldc )
230*
231 END IF
232*
233 END IF
234*
235 RETURN
236*
237* End of ZLARZ
238*
239 END
subroutine zaxpy(n, za, zx, incx, zy, incy)
ZAXPY
Definition zaxpy.f:88
subroutine zcopy(n, zx, incx, zy, incy)
ZCOPY
Definition zcopy.f:81
subroutine zgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
ZGEMV
Definition zgemv.f:160
subroutine zgeru(m, n, alpha, x, incx, y, incy, a, lda)
ZGERU
Definition zgeru.f:130
subroutine zgerc(m, n, alpha, x, incx, y, incy, a, lda)
ZGERC
Definition zgerc.f:130
subroutine zlacgv(n, x, incx)
ZLACGV conjugates a complex vector.
Definition zlacgv.f:72
subroutine zlarz(side, m, n, l, v, incv, tau, c, ldc, work)
ZLARZ applies an elementary reflector (as returned by stzrzf) to a general matrix.
Definition zlarz.f:145