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