7474* > (1 + (M-1)*abs(INCV)) if SIDE = 'L'
7575* > or (1 + (N-1)*abs(INCV)) if SIDE = 'R'
7676* > The vector v in the representation of H. V is not used if
77- * > TAU = 0.
77+ * > TAU = 0. V(1) is not referenced or modified.
7878* > \endverbatim
7979* >
8080* > \param[in] INCV
110110* > or (M) if SIDE = 'R'
111111* > \endverbatim
112112*
113+ * To take advantage of the fact that v(1) = 1, we do the following
114+ * v = [ 1 v_2 ]**T
115+ * If SIDE='L'
116+ * |-----|
117+ * | C_1 |
118+ * C =| C_2 |
119+ * |-----|
120+ * C_1\in\mathbb{R}^{1\times n}, C_2\in\mathbb{R}^{m-1\times n}
121+ * So we compute:
122+ * C = HC = (I - \tau vv**T)C
123+ * = C - \tau vv**T C
124+ * w = C**T v = [ C_1**T C_2**T ] [ 1 v_2 ]**T
125+ * = C_1**T + C_2**T v ( DGEMM then DAXPY )
126+ * C = C - \tau vv**T C
127+ * = C - \tau vw**T
128+ * Giving us C_1 = C_1 - \tau w**T ( DAXPY )
129+ * and
130+ * C_2 = C_2 - \tau v_2w**T ( DGER )
131+ * If SIDE='R'
132+ *
133+ * C = [ C_1 C_2 ]
134+ * C_1\in\mathbb{R}^{m\times 1}, C_2\in\mathbb{R}^{m\times n-1}
135+ * So we compute:
136+ * C = CH = C(I - \tau vv**T)
137+ * = C - \tau Cvv**T
138+ *
139+ * w = Cv = [ C_1 C_2 ] [ 1 v_2 ]**T
140+ * = C_1 + C_2v_2 ( DGEMM then DAXPY )
141+ * C = C - \tau Cvv**T
142+ * = C - \tau wv**T
143+ * Giving us C_1 = C_1 - \tau w ( DAXPY )
144+ * and
145+ * C_2 = C_2 - \tau wv_2**T ( DGER )
146+ *
113147* Authors:
114148* ========
115149*
@@ -175,7 +209,9 @@ SUBROUTINE DLARF1F( SIDE, M, N, V, INCV, TAU, C, LDC, WORK )
175209 I = 1
176210 END IF
177211! Look for the last non- zero row in V.
178- DO WHILE ( LASTV.GT. 0 .AND. V( I ).EQ. ZERO )
212+ ! Since we are assuming that V(1 ) = 1 , and it is not stored, so we
213+ ! shouldn' t access it.
214+ DO WHILE( LASTV.GT.1 .AND. V( I ).EQ.ZERO )
179215 LASTV = LASTV - 1
180216 I = I - INCV
181217 END DO
@@ -186,67 +222,63 @@ SUBROUTINE DLARF1F( SIDE, M, N, V, INCV, TAU, C, LDC, WORK )
186222! Scan for the last non-zero row in C(:,1:lastv).
187223 LASTC = ILADLR(M, LASTV, C, LDC)
188224 END IF
189- END IF
190- IF ( LASTC .EQ. 0 .OR. LASTV .EQ. 0 ) THEN
225+ ELSE
226+ ! TAU is 0, so H = I. Meaning HC = C = CH.
191227 RETURN
192228 END IF
193229 IF( APPLYLEFT ) THEN
194230*
195231* Form H * C
196232*
197- IF ( LASTV.GT. 0 ) THEN
198- ! Check if m = 1 . This means v = 1 , So we just need to compute
199- ! C := HC = (1 - \tau)C.
200- IF ( M.EQ. 1 .OR. LASTV.EQ. 1 ) THEN
201- CALL DSCAL(LASTC, ONE - TAU, C, LDC)
202- ELSE
233+ ! Check if lastv = 1. This means v = 1, So we just need to compute
234+ ! C := HC = (1-\tau)C.
235+ IF( LASTV.EQ.1 ) THEN
236+ CALL DSCAL(LASTC, ONE - TAU, C, LDC)
237+ ELSE
203238*
204- * w(1:lastc,1) := C(1:lastv,1:lastc)**T * v(1:lastv,1)
239+ * w(1:lastc,1) := C(1:lastv,1:lastc)**T * v(1:lastv,1)
205240*
206- ! w(1 :lastc,1 ) := C(2 :lastv,1 :lastc)** T * v(2 :lastv,1 )
207- CALL DGEMV( ' Transpose' , LASTV-1 , LASTC, ONE, C(1+1 ,1 ),
208- $ LDC, V(1 + INCV), INCV, ZERO, WORK, 1 )
209- ! w(1 :lastc,1 ) += C(1 ,1 :lastc)** T * v(1 ,1 ) = C(1 ,1 :lastc)** T
210- CALL DAXPY(LASTC, ONE, C, LDC, WORK, 1 )
241+ ! w(1:lastc,1) := C(2:lastv,1:lastc)**T * v(2:lastv,1)
242+ CALL DGEMV( ' Transpose' , LASTV-1, LASTC, ONE, C(1+1,1),
243+ $ LDC, V(1+INCV), INCV, ZERO, WORK, 1)
244+ ! w(1:lastc,1) += C(1,1:lastc)**T * v(1,1) = C(1,1:lastc)**T
245+ CALL DAXPY(LASTC, ONE, C, LDC, WORK, 1)
211246*
212247* C(1:lastv,1:lastc) := C(...) - tau * v(1:lastv,1) * w(1:lastc,1)**T
213248*
214249 ! C(1, 1:lastc) := C(...) - tau * v(1,1) * w(1:lastc,1)**T
215250 ! = C(...) - tau * w(1:lastc,1)**T
216- CALL DAXPY(LASTC, - TAU, WORK, 1 , C, LDC)
217- ! C(2 :lastv,1 :lastc) := C(...) - tau * v(2 :lastv,1 )* w(1 :lastc,1 )** T
218- CALL DGER(LASTV-1 , LASTC, - TAU, V(1 + INCV), INCV, WORK, 1 ,
219- $ C(1+1 ,1 ), LDC)
220- END IF
251+ CALL DAXPY(LASTC, -TAU, WORK, 1, C, LDC)
252+ ! C(2:lastv,1:lastc) := C(...) - tau * v(2:lastv,1)*w(1:lastc,1)**T
253+ CALL DGER(LASTV-1, LASTC, -TAU, V(1+INCV), INCV, WORK, 1,
254+ $ C(1+1,1), LDC)
221255 END IF
222256 ELSE
223257*
224258* Form C * H
225259*
226- IF ( LASTV.GT. 0 ) THEN
227- ! Check if n = 1 . This means v = 1 , so we just need to compute
228- ! C := CH = C(1 - \tau).
229- IF ( N.EQ. 1 .OR. LASTV.EQ. 1 ) THEN
230- CALL DSCAL(LASTC, ONE - TAU, C, 1 )
231- ELSE
232- *
233- * w(1:lastc,1) := C(1:lastc,1:lastv) * v(1:lastv,1)
234- *
235- ! w(1 :lastc,1 ) := C(1 :lastc,2 :lastv) * v(2 :lastv,1 )
236- CALL DGEMV( ' No transpose' , LASTC, LASTV-1 , ONE,
237- $ C(1 ,1+1 ), LDC, V(1 + INCV), INCV, ZERO, WORK, 1 )
238- ! w(1 :lastc,1 ) += C(1 :lastc,1 ) v(1 ,1 ) = C(1 :lastc,1 )
239- CALL DAXPY(LASTC, ONE, C, 1 , WORK, 1 )
240- *
241- * C(1:lastc,1:lastv) := C(...) - tau * w(1:lastc,1) * v(1:lastv,1)**T
242- *
243- ! C(1 :lastc,1 ) := C(...) - tau * w(1 :lastc,1 ) * v(1 ,1 )** T
244- ! = C(...) - tau * w(1 :lastc,1 )
245- CALL DAXPY(LASTC, - TAU, WORK, 1 , C, 1 )
246- ! C(1 :lastc,2 :lastv) := C(...) - tau * w(1 :lastc,1 ) * v(2 :lastv)** T
247- CALL DGER( LASTC, LASTV-1 , - TAU, WORK, 1 , V(1 + INCV),
248- $ INCV, C(1 ,1+1 ), LDC )
249- END IF
260+ ! Check if n = 1. This means v = 1, so we just need to compute
261+ ! C := CH = C(1-\tau).
262+ IF( LASTV.EQ.1 ) THEN
263+ CALL DSCAL(LASTC, ONE - TAU, C, 1)
264+ ELSE
265+ *
266+ * w(1:lastc,1) := C(1:lastc,1:lastv) * v(1:lastv,1)
267+ *
268+ ! w(1:lastc,1) := C(1:lastc,2:lastv) * v(2:lastv,1)
269+ CALL DGEMV( ' No transpose' , LASTC, LASTV-1, ONE,
270+ $ C(1,1+1), LDC, V(1+INCV), INCV, ZERO, WORK, 1 )
271+ ! w(1:lastc,1) += C(1:lastc,1) v(1,1) = C(1:lastc,1)
272+ CALL DAXPY(LASTC, ONE, C, 1, WORK, 1)
273+ *
274+ * C(1:lastc,1:lastv) := C(...) - tau * w(1:lastc,1) * v(1:lastv,1)**T
275+ *
276+ ! C(1:lastc,1) := C(...) - tau * w(1:lastc,1) * v(1,1)**T
277+ ! = C(...) - tau * w(1:lastc,1)
278+ CALL DAXPY(LASTC, -TAU, WORK, 1, C, 1)
279+ ! C(1:lastc,2:lastv) := C(...) - tau * w(1:lastc,1) * v(2:lastv)**T
280+ CALL DGER( LASTC, LASTV-1, -TAU, WORK, 1, V(1+INCV),
281+ $ INCV, C(1,1+1), LDC )
250282 END IF
251283 END IF
252284 RETURN
0 commit comments