Skip to content

Commit b8a6443

Browse files
develop DLARF1F and implement in ORM2R, #1011
1 parent dd2e5ef commit b8a6443

File tree

3 files changed

+291
-7
lines changed

3 files changed

+291
-7
lines changed

SRC/CMakeLists.txt

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -307,7 +307,7 @@ set(DLASRC
307307
dlaqgb.f dlaqge.f dlaqp2.f dlaqps.f dlaqp2rk.f dlaqp3rk.f dlaqsb.f dlaqsp.f dlaqsy.f
308308
dlaqr0.f dlaqr1.f dlaqr2.f dlaqr3.f dlaqr4.f dlaqr5.f
309309
dlaqtr.f dlar1v.f dlar2v.f iladlr.f iladlc.f
310-
dlarf.f dlarfb.f dlarfb_gett.f dlarfg.f dlarfgp.f dlarft.f dlarfx.f dlarfy.f
310+
dlarf.f dlarf1f.f dlarfb.f dlarfb_gett.f dlarfg.f dlarfgp.f dlarft.f dlarfx.f dlarfy.f
311311
dlargv.f dlarmm.f dlarrv.f dlartv.f
312312
dlarz.f dlarzb.f dlarzt.f dlaswp.f dlasy2.f
313313
dlasyf.f dlasyf_rook.f dlasyf_rk.f dlasyf_aa.f

SRC/dlarf1f.f

Lines changed: 288 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,288 @@
1+
*> \brief \b DLARF1F applies an elementary reflector to a general rectangular matrix.
2+
*
3+
* =========== DOCUMENTATION ===========
4+
*
5+
* Online html documentation available at
6+
* http://www.netlib.org/lapack/explore-html/
7+
*
8+
*> \htmlonly
9+
*> Download DLARF + dependencies
10+
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlarf.f">
11+
*> [TGZ]</a>
12+
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlarf.f">
13+
*> [ZIP]</a>
14+
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlarf.f">
15+
*> [TXT]</a>
16+
*> \endhtmlonly
17+
*
18+
* Definition:
19+
* ===========
20+
*
21+
* SUBROUTINE DLARF1F( 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+
*> DLARF1F 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+
*> It is assumed that v(1) = 1. v(1) is not referenced.
45+
*>
46+
*> If tau = 0, then H is taken to be the unit matrix.
47+
*> \endverbatim
48+
*
49+
* Arguments:
50+
* ==========
51+
*
52+
*> \param[in] SIDE
53+
*> \verbatim
54+
*> SIDE is CHARACTER*1
55+
*> = 'L': form H * C
56+
*> = 'R': form C * H
57+
*> \endverbatim
58+
*>
59+
*> \param[in] M
60+
*> \verbatim
61+
*> M is INTEGER
62+
*> The number of rows of the matrix C.
63+
*> \endverbatim
64+
*>
65+
*> \param[in] N
66+
*> \verbatim
67+
*> N is INTEGER
68+
*> The number of columns of the matrix C.
69+
*> \endverbatim
70+
*>
71+
*> \param[in] V
72+
*> \verbatim
73+
*> V is DOUBLE PRECISION array, dimension
74+
*> (1 + (M-1)*abs(INCV)) if SIDE = 'L'
75+
*> or (1 + (N-1)*abs(INCV)) if SIDE = 'R'
76+
*> The vector v in the representation of H. V is not used if
77+
*> TAU = 0.
78+
*> \endverbatim
79+
*>
80+
*> \param[in] INCV
81+
*> \verbatim
82+
*> INCV is INTEGER
83+
*> The increment between elements of v. INCV <> 0.
84+
*> \endverbatim
85+
*>
86+
*> \param[in] TAU
87+
*> \verbatim
88+
*> TAU is DOUBLE PRECISION
89+
*> The value tau in the representation of H.
90+
*> \endverbatim
91+
*>
92+
*> \param[in,out] C
93+
*> \verbatim
94+
*> C is DOUBLE PRECISION array, dimension (LDC,N)
95+
*> On entry, the m by n matrix C.
96+
*> On exit, C is overwritten by the matrix H * C if SIDE = 'L',
97+
*> or C * H if SIDE = 'R'.
98+
*> \endverbatim
99+
*>
100+
*> \param[in] LDC
101+
*> \verbatim
102+
*> LDC is INTEGER
103+
*> The leading dimension of the array C. LDC >= max(1,M).
104+
*> \endverbatim
105+
*>
106+
*> \param[out] WORK
107+
*> \verbatim
108+
*> WORK is DOUBLE PRECISION array, dimension
109+
*> (N) if SIDE = 'L'
110+
*> or (M) if SIDE = 'R'
111+
*> \endverbatim
112+
*
113+
* Authors:
114+
* ========
115+
*
116+
*> \author Univ. of Tennessee
117+
*> \author Univ. of California Berkeley
118+
*> \author Univ. of Colorado Denver
119+
*> \author NAG Ltd.
120+
*
121+
*> \ingroup larf1f
122+
*
123+
*> \par Further Details:
124+
* =====================
125+
*>
126+
*> \verbatim
127+
*>
128+
*> The algorithm update matrix C by blocks.
129+
*> C is presected in the form of 4 blocks:
130+
*> C11 - 1-by-1, C12 - 1-by-n, C21 - m-by-1 and C22 - (m-1)-by-(n-1)
131+
*>
132+
*> C = ( C11 | C12 )
133+
*> (_____|___________________)
134+
*> ( | )
135+
*> ( | )
136+
*> ( C21 | C22 )
137+
*> ( | )
138+
*> ( | )
139+
*>
140+
*> \endverbatim
141+
*
142+
* =====================================================================
143+
SUBROUTINE DLARF1F( SIDE, M, N, V, INCV, TAU, C, LDC, WORK )
144+
*
145+
* -- LAPACK auxiliary routine --
146+
* -- LAPACK is a software package provided by Univ. of Tennessee, --
147+
* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
148+
*
149+
* .. Scalar Arguments ..
150+
CHARACTER SIDE
151+
INTEGER INCV, LDC, M, N
152+
DOUBLE PRECISION TAU
153+
* ..
154+
* .. Array Arguments ..
155+
DOUBLE PRECISION C( LDC, * ), V( * ), WORK( * )
156+
* ..
157+
*
158+
* =====================================================================
159+
*
160+
* .. Parameters ..
161+
DOUBLE PRECISION ONE, ZERO
162+
PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
163+
* ..
164+
* .. Local Scalars ..
165+
LOGICAL APPLYLEFT
166+
INTEGER I, LASTV, LASTC
167+
DOUBLE PRECISION C11, DOT1, DDOT
168+
* ..
169+
* .. External Subroutines ..
170+
EXTERNAL DGEMV, DGER, DDOT, DAXPY, DCOPY
171+
* ..
172+
* .. External Functions ..
173+
LOGICAL LSAME
174+
INTEGER ILADLR, ILADLC
175+
EXTERNAL LSAME, ILADLR, ILADLC
176+
* ..
177+
* .. Executable Statements ..
178+
*
179+
APPLYLEFT = LSAME( SIDE, 'L' )
180+
LASTV = 0
181+
LASTC = 0
182+
IF( TAU.NE.ZERO ) THEN
183+
! Set up variables for scanning V. LASTV begins pointing to the end
184+
! of V.
185+
IF( APPLYLEFT ) THEN
186+
LASTV = M
187+
ELSE
188+
LASTV = N
189+
END IF
190+
IF( INCV.GT.0 ) THEN
191+
I = 1 + (LASTV-1) * INCV
192+
ELSE
193+
I = 1
194+
END IF
195+
! Look for the last non-zero row in V.
196+
DO WHILE( LASTV.GT.0 .AND. V( I ).EQ.ZERO )
197+
LASTV = LASTV - 1
198+
I = I - INCV
199+
END DO
200+
IF( APPLYLEFT ) THEN
201+
! Scan for the last non-zero column in C(1:lastv,:).
202+
LASTC = ILADLC(LASTV, N, C, LDC)
203+
ELSE
204+
! Scan for the last non-zero row in C(:,1:lastv).
205+
LASTC = ILADLR(M, LASTV, C, LDC)
206+
END IF
207+
END IF
208+
209+
IF( LASTC.EQ.0 ) THEN
210+
RETURN
211+
END IF
212+
213+
IF( APPLYLEFT ) THEN
214+
*
215+
* Form H * C
216+
*
217+
IF( LASTV.GT.0 ) THEN
218+
DOT1 = - TAU * DDOT( LASTV - 1, V( 1 + INCV ), INCV,
219+
$ C( 2, 1 ), 1 )
220+
221+
C11 = (ONE - TAU) * C( 1, 1 ) + DOT1
222+
*
223+
* Prepare WORK
224+
*
225+
CALL DCOPY( LASTC - 1, C( 1, 2 ), LDC, WORK, 1 )
226+
227+
CALL DGEMV( 'Transpose', LASTV - 1, LASTC - 1, -TAU,
228+
$ C( 2, 2 ), LDC, V( 1 + INCV ), INCV, -TAU, WORK, 1 )
229+
*
230+
* Update C12
231+
*
232+
CALL DAXPY( LASTC - 1, ONE, WORK, 1, C( 1, 2 ), LDC )
233+
*
234+
* Update C21
235+
*
236+
CALL DAXPY( LASTV - 1, -TAU * C( 1, 1 ) + DOT1,
237+
$ V( 1 + INCV ), INCV, C( 2, 1 ), 1 )
238+
*
239+
* Update C11
240+
*
241+
C( 1, 1 ) = C11
242+
*
243+
* Update C22
244+
*
245+
CALL DGER( LASTV - 1, LASTC - 1, ONE, V( 1 + INCV ),
246+
$ INCV, WORK, 1, C( 2, 2 ), LDC )
247+
END IF
248+
ELSE
249+
*
250+
* Form C * H
251+
*
252+
IF( LASTV.GT.0 ) THEN
253+
DOT1 = - TAU * DDOT( LASTV - 1, V( 1 + INCV ), INCV,
254+
$ C( 1, 2 ), LDC )
255+
256+
C11 = (ONE - TAU) * C( 1, 1 ) + DOT1
257+
*
258+
* Prepare WORK
259+
*
260+
CALL DCOPY( LASTC - 1, C( 2, 1 ), 1, WORK, 1 )
261+
262+
CALL DGEMV( 'No transpose', LASTC - 1, LASTV - 1, -TAU,
263+
$ C( 2, 2 ), LDC, V( 1 + INCV ), INCV, -TAU, WORK, 1 )
264+
*
265+
* Update C12
266+
*
267+
CALL DAXPY( LASTV - 1, -TAU * C( 1, 1 ) + DOT1,
268+
$ V( 1 + INCV ), INCV, C( 1, 2 ), LDC )
269+
*
270+
* Update C11
271+
*
272+
C( 1, 1 ) = C11
273+
*
274+
* Update C21
275+
*
276+
CALL DAXPY( LASTC - 1, ONE, WORK, 1, C( 2, 1 ), 1 )
277+
*
278+
* Update C22
279+
*
280+
CALL DGER( LASTC - 1, LASTV - 1, ONE, WORK, 1,
281+
$ V( 1 + INCV ), INCV, C( 2, 2 ), LDC )
282+
END IF
283+
END IF
284+
RETURN
285+
*
286+
* End of DLARF1F
287+
*
288+
END

SRC/dorm2r.f

Lines changed: 2 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -178,14 +178,13 @@ SUBROUTINE DORM2R( SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC,
178178
* .. Local Scalars ..
179179
LOGICAL LEFT, NOTRAN
180180
INTEGER I, I1, I2, I3, IC, JC, MI, NI, NQ
181-
DOUBLE PRECISION AII
182181
* ..
183182
* .. External Functions ..
184183
LOGICAL LSAME
185184
EXTERNAL LSAME
186185
* ..
187186
* .. External Subroutines ..
188-
EXTERNAL DLARF, XERBLA
187+
EXTERNAL DLARF1F, XERBLA
189188
* ..
190189
* .. Intrinsic Functions ..
191190
INTRINSIC MAX
@@ -266,12 +265,9 @@ SUBROUTINE DORM2R( SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC,
266265
*
267266
* Apply H(i)
268267
*
269-
AII = A( I, I )
270-
A( I, I ) = ONE
271-
CALL DLARF( SIDE, MI, NI, A( I, I ), 1, TAU( I ), C( IC,
268+
CALL DLARF1F( SIDE, MI, NI, A( I, I ), 1, TAU( I ), C( IC,
272269
$ JC ),
273270
$ LDC, WORK )
274-
A( I, I ) = AII
275271
10 CONTINUE
276272
RETURN
277273
*

0 commit comments

Comments
 (0)