LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Macros Modules Pages
dlarf1l.f
Go to the documentation of this file.
1*> \brief \b DLARF1L applies an elementary reflector to a general rectangular
2* matrix assuming v(lastv) = 1 where lastv is the last non-zero
3* element
4*
5* =========== DOCUMENTATION ===========
6*
7* Online html documentation available at
8* http://www.netlib.org/lapack/explore-html/
9*
10*> Download DLARF1L + dependencies
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlarf1l.f">
12*> [TGZ]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlarf1l.f">
14*> [ZIP]</a>
15*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlarf1l.f">
16*> [TXT]</a>
17*
18* Definition:
19* ===========
20*
21* SUBROUTINE DLARF1L( SIDE, M, N, V, INCV, TAU, C, LDC, WORK )
22*
23* .. Scalar Arguments ..
24* CHARACTER SIDE
25* INTEGER INCV, LDC, M, N
26* DOUBLE PRECISION TAU
27* ..
28* .. Array Arguments ..
29* DOUBLE PRECISION C( LDC, * ), V( * ), WORK( * )
30* ..
31*
32*
33*> \par Purpose:
34* =============
35*>
36*> \verbatim
37*>
38*> DLARF1L applies a real elementary reflector H to a real m by n matrix
39*> C, from either the left or the right. H is represented in the form
40*>
41*> H = I - tau * v * v**T
42*>
43*> where tau is a real scalar and v is a real vector.
44*>
45*> If tau = 0, then H is taken to be the unit matrix.
46*> \endverbatim
47*
48* Arguments:
49* ==========
50*
51*> \param[in] SIDE
52*> \verbatim
53*> SIDE is CHARACTER*1
54*> = 'L': form H * C
55*> = 'R': form C * H
56*> \endverbatim
57*>
58*> \param[in] M
59*> \verbatim
60*> M is INTEGER
61*> The number of rows of the matrix C.
62*> \endverbatim
63*>
64*> \param[in] N
65*> \verbatim
66*> N is INTEGER
67*> The number of columns of the matrix C.
68*> \endverbatim
69*>
70*> \param[in] V
71*> \verbatim
72*> V is DOUBLE PRECISION array, dimension
73*> (1 + (M-1)*abs(INCV)) if SIDE = 'L'
74*> or (1 + (N-1)*abs(INCV)) if SIDE = 'R'
75*> The vector v in the representation of H. V is not used if
76*> TAU = 0.
77*> \endverbatim
78*>
79*> \param[in] INCV
80*> \verbatim
81*> INCV is INTEGER
82*> The increment between elements of v. INCV <> 0.
83*> \endverbatim
84*>
85*> \param[in] TAU
86*> \verbatim
87*> TAU is DOUBLE PRECISION
88*> The value tau in the representation of H.
89*> \endverbatim
90*>
91*> \param[in,out] C
92*> \verbatim
93*> C is DOUBLE PRECISION array, dimension (LDC,N)
94*> On entry, the m by n matrix C.
95*> On exit, C is overwritten by the matrix H * C if SIDE = 'L',
96*> or C * H if SIDE = 'R'.
97*> \endverbatim
98*>
99*> \param[in] LDC
100*> \verbatim
101*> LDC is INTEGER
102*> The leading dimension of the array C. LDC >= max(1,M).
103*> \endverbatim
104*>
105*> \param[out] WORK
106*> \verbatim
107*> WORK is DOUBLE PRECISION array, dimension
108*> (N) if SIDE = 'L'
109*> or (M) if SIDE = 'R'
110*> \endverbatim
111*
112* Authors:
113* ========
114*
115*> \author Univ. of Tennessee
116*> \author Univ. of California Berkeley
117*> \author Univ. of Colorado Denver
118*> \author NAG Ltd.
119*
120*> \ingroup larf
121*
122* =====================================================================
123 SUBROUTINE dlarf1l( SIDE, M, N, V, INCV, TAU, C, LDC, WORK )
124*
125* -- LAPACK auxiliary routine --
126* -- LAPACK is a software package provided by Univ. of Tennessee, --
127* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
128*
129* .. Scalar Arguments ..
130 CHARACTER SIDE
131 INTEGER INCV, LDC, M, N
132 DOUBLE PRECISION TAU
133* ..
134* .. Array Arguments ..
135 DOUBLE PRECISION C( LDC, * ), V( * ), WORK( * )
136* ..
137*
138* =====================================================================
139*
140* .. Parameters ..
141 DOUBLE PRECISION ONE, ZERO
142 parameter( one = 1.0d+0, zero = 0.0d+0 )
143* ..
144* .. Local Scalars ..
145 LOGICAL APPLYLEFT
146 INTEGER I, FIRSTV, LASTV, LASTC
147* ..
148* .. External Subroutines ..
149 EXTERNAL dgemv, dger
150* ..
151* .. External Functions ..
152 LOGICAL LSAME
153 INTEGER ILADLR, ILADLC
154 EXTERNAL lsame, iladlr, iladlc
155* ..
156* .. Executable Statements ..
157*
158 applyleft = lsame( side, 'L' )
159 firstv = 1
160 lastc = 0
161 IF( tau.NE.zero ) THEN
162! Set up variables for scanning V. LASTV begins pointing to the end
163! of V.
164 IF( applyleft ) THEN
165 lastv = m
166 ELSE
167 lastv = n
168 END IF
169 i = 1
170! Look for the last non-zero row in V.
171 DO WHILE( lastv.GT.firstv .AND. v( i ).EQ.zero )
172 firstv = firstv + 1
173 i = i + incv
174 END DO
175 IF( applyleft ) THEN
176! Scan for the last non-zero column in C(1:lastv,:).
177 lastc = iladlc(lastv, n, c, ldc)
178 ELSE
179! Scan for the last non-zero row in C(:,1:lastv).
180 lastc = iladlr(m, lastv, c, ldc)
181 END IF
182 END IF
183 IF( lastc.EQ.0 ) THEN
184 RETURN
185 END IF
186 IF( applyleft ) THEN
187*
188* Form H * C
189*
190 IF( lastv.GT.0 ) THEN
191 ! Check if m = 1. This means v = 1, So we just need to compute
192 ! C := HC = (1-\tau)C.
193 IF( lastv.EQ.firstv ) THEN
194 CALL dscal(lastc, one - tau, c( firstv, 1), ldc)
195 ELSE
196*
197* w(1:lastc,1) := C(1:lastv,1:lastc)**T * v(1:lastv,1)
198*
199 ! w(1:lastc,1) := C(1:lastv-1,1:lastc)**T * v(1:lastv-1,1)
200 CALL dgemv( 'Transpose', lastv-firstv, lastc, one,
201 $ c(firstv,1), ldc, v(i), incv, zero,
202 $ work, 1)
203 ! w(1:lastc,1) += C(lastv,1:lastc)**T * v(lastv,1) = C(lastv,1:lastc)**T
204 CALL daxpy(lastc, one, c(lastv,1), ldc, work, 1)
205*
206* C(1:lastv,1:lastc) := C(...) - tau * v(1:lastv,1) * w(1:lastc,1)**T
207*
208 ! C(lastv, 1:lastc) := C(...) - tau * v(lastv,1) * w(1:lastc,1)**T
209 ! = C(...) - tau * w(1:lastc,1)**T
210 CALL daxpy(lastc, -tau, work, 1, c(lastv,1), ldc)
211 ! C(1:lastv-1,1:lastc) := C(...) - tau * v(1:lastv-1,1)*w(1:lastc,1)**T
212 CALL dger(lastv-firstv, lastc, -tau, v(i), incv,
213 $ work, 1, c(firstv,1), ldc)
214 END IF
215 END IF
216 ELSE
217*
218* Form C * H
219*
220 IF( lastv.GT.0 ) THEN
221 ! Check if n = 1. This means v = 1, so we just need to compute
222 ! C := CH = C(1-\tau).
223 IF( lastv.EQ.firstv ) THEN
224 CALL dscal(lastc, one - tau, c, 1)
225 ELSE
226*
227* w(1:lastc,1) := C(1:lastc,1:lastv) * v(1:lastv,1)
228*
229 ! w(1:lastc,1) := C(1:lastc,1:lastv-1) * v(1:lastv-1,1)
230 CALL dgemv( 'No transpose', lastc, lastv-firstv,
231 $ one, c(1,firstv), ldc, v(i), incv, zero, work, 1 )
232 ! w(1:lastc,1) += C(1:lastc,lastv) * v(lastv,1) = C(1:lastc,lastv)
233 CALL daxpy(lastc, one, c(1,lastv), 1, work, 1)
234*
235* C(1:lastc,1:lastv) := C(...) - tau * w(1:lastc,1) * v(1:lastv,1)**T
236*
237 ! C(1:lastc,lastv) := C(...) - tau * w(1:lastc,1) * v(lastv,1)**T
238 ! = C(...) - tau * w(1:lastc,1)
239 CALL daxpy(lastc, -tau, work, 1, c(1,lastv), 1)
240 ! C(1:lastc,1:lastv-1) := C(...) - tau * w(1:lastc,1) * v(1:lastv-1)**T
241 CALL dger( lastc, lastv-firstv, -tau, work, 1, v(i),
242 $ incv, c(1,firstv), ldc )
243 END IF
244 END IF
245 END IF
246 RETURN
247*
248* End of DLARF1L
249*
250 END
subroutine daxpy(n, da, dx, incx, dy, incy)
DAXPY
Definition daxpy.f:89
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 dlarf1l(side, m, n, v, incv, tau, c, ldc, work)
DLARF1L applies an elementary reflector to a general rectangular
Definition dlarf1l.f:124
subroutine dscal(n, da, dx, incx)
DSCAL
Definition dscal.f:79