1 *> \brief \b CLARF applies an elementary reflector to a general rectangular matrix.
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download CLARF + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/clarf.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/clarf.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/clarf.f">
21 * SUBROUTINE CLARF( SIDE, M, N, V, INCV, TAU, C, LDC, WORK )
23 * .. Scalar Arguments ..
25 * INTEGER INCV, LDC, M, N
28 * .. Array Arguments ..
29 * COMPLEX C( LDC, * ), V( * ), WORK( * )
38 *> CLARF applies a complex elementary reflector H to a complex M-by-N
39 *> matrix C, from either the left or the right. H is represented in the
42 *> H = I - tau * v * v**H
44 *> where tau is a complex scalar and v is a complex vector.
46 *> If tau = 0, then H is taken to be the unit matrix.
48 *> To apply H**H (the conjugate transpose of H), supply conjg(tau) instead
57 *> SIDE is CHARACTER*1
65 *> The number of rows of the matrix C.
71 *> The number of columns of the matrix C.
76 *> V is COMPLEX array, dimension
77 *> (1 + (M-1)*abs(INCV)) if SIDE = 'L'
78 *> or (1 + (N-1)*abs(INCV)) if SIDE = 'R'
79 *> The vector v in the representation of H. V is not used if
86 *> The increment between elements of v. INCV <> 0.
92 *> The value tau in the representation of H.
97 *> C is COMPLEX array, dimension (LDC,N)
98 *> On entry, the M-by-N matrix C.
99 *> On exit, C is overwritten by the matrix H * C if SIDE = 'L',
100 *> or C * H if SIDE = 'R'.
106 *> The leading dimension of the array C. LDC >= max(1,M).
111 *> WORK is COMPLEX array, dimension
113 *> or (M) if SIDE = 'R'
119 *> \author Univ. of Tennessee
120 *> \author Univ. of California Berkeley
121 *> \author Univ. of Colorado Denver
124 *> \date September 2012
126 *> \ingroup complexOTHERauxiliary
128 * =====================================================================
129 SUBROUTINE CLARF( SIDE, M, N, V, INCV, TAU, C, LDC, WORK )
131 * -- LAPACK auxiliary routine (version 3.4.2) --
132 * -- LAPACK is a software package provided by Univ. of Tennessee, --
133 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
136 * .. Scalar Arguments ..
138 INTEGER INCV, LDC, M, N
141 * .. Array Arguments ..
142 COMPLEX C( LDC, * ), V( * ), WORK( * )
145 * =====================================================================
149 PARAMETER ( ONE = ( 1.0E+0, 0.0E+0 ),
150 $ ZERO = ( 0.0E+0, 0.0E+0 ) )
152 * .. Local Scalars ..
154 INTEGER I, LASTV, LASTC
156 * .. External Subroutines ..
157 EXTERNAL CGEMV, CGERC
159 * .. External Functions ..
161 INTEGER ILACLR, ILACLC
162 EXTERNAL LSAME, ILACLR, ILACLC
164 * .. Executable Statements ..
166 APPLYLEFT = LSAME( SIDE, 'L' )
169 IF( TAU.NE.ZERO ) THEN
170 ! Set up variables for scanning V. LASTV begins pointing to the end
178 I = 1 + (LASTV-1) * INCV
182 ! Look for the last non-zero row in V.
183 DO WHILE( LASTV.GT.0 .AND. V( I ).EQ.ZERO )
188 ! Scan for the last non-zero column in C(1:lastv,:).
189 LASTC = ILACLC(LASTV, N, C, LDC)
191 ! Scan for the last non-zero row in C(:,1:lastv).
192 LASTC = ILACLR(M, LASTV, C, LDC)
195 ! Note that lastc.eq.0 renders the BLAS operations null; no special
196 ! case is needed at this level.
201 IF( LASTV.GT.0 ) THEN
203 * w(1:lastc,1) := C(1:lastv,1:lastc)**H * v(1:lastv,1)
205 CALL CGEMV( 'Conjugate transpose', LASTV, LASTC, ONE,
206 $ C, LDC, V, INCV, ZERO, WORK, 1 )
208 * C(1:lastv,1:lastc) := C(...) - v(1:lastv,1) * w(1:lastc,1)**H
210 CALL CGERC( LASTV, LASTC, -TAU, V, INCV, WORK, 1, C, LDC )
216 IF( LASTV.GT.0 ) THEN
218 * w(1:lastc,1) := C(1:lastc,1:lastv) * v(1:lastv,1)
220 CALL CGEMV( 'No transpose', LASTC, LASTV, ONE, C, LDC,
221 $ V, INCV, ZERO, WORK, 1 )
223 * C(1:lastc,1:lastv) := C(...) - w(1:lastc,1) * v(1:lastv,1)**H
225 CALL CGERC( LASTC, LASTV, -TAU, WORK, 1, V, INCV, C, LDC )