LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
clarzt.f
Go to the documentation of this file.
1*> \brief \b CLARZT forms the triangular factor T of a block reflector H = I - vtvH.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download CLARZT + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/clarzt.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/clarzt.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/clarzt.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE CLARZT( DIRECT, STOREV, N, K, V, LDV, TAU, T, LDT )
20*
21* .. Scalar Arguments ..
22* CHARACTER DIRECT, STOREV
23* INTEGER K, LDT, LDV, N
24* ..
25* .. Array Arguments ..
26* COMPLEX T( LDT, * ), TAU( * ), V( LDV, * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> CLARZT forms the triangular factor T of a complex block reflector
36*> H of order > n, which is defined as a product of k elementary
37*> reflectors.
38*>
39*> If DIRECT = 'F', H = H(1) H(2) . . . H(k) and T is upper triangular;
40*>
41*> If DIRECT = 'B', H = H(k) . . . H(2) H(1) and T is lower triangular.
42*>
43*> If STOREV = 'C', the vector which defines the elementary reflector
44*> H(i) is stored in the i-th column of the array V, and
45*>
46*> H = I - V * T * V**H
47*>
48*> If STOREV = 'R', the vector which defines the elementary reflector
49*> H(i) is stored in the i-th row of the array V, and
50*>
51*> H = I - V**H * T * V
52*>
53*> Currently, only STOREV = 'R' and DIRECT = 'B' are supported.
54*> \endverbatim
55*
56* Arguments:
57* ==========
58*
59*> \param[in] DIRECT
60*> \verbatim
61*> DIRECT is CHARACTER*1
62*> Specifies the order in which the elementary reflectors are
63*> multiplied to form the block reflector:
64*> = 'F': H = H(1) H(2) . . . H(k) (Forward, not supported yet)
65*> = 'B': H = H(k) . . . H(2) H(1) (Backward)
66*> \endverbatim
67*>
68*> \param[in] STOREV
69*> \verbatim
70*> STOREV is CHARACTER*1
71*> Specifies how the vectors which define the elementary
72*> reflectors are stored (see also Further Details):
73*> = 'C': columnwise (not supported yet)
74*> = 'R': rowwise
75*> \endverbatim
76*>
77*> \param[in] N
78*> \verbatim
79*> N is INTEGER
80*> The order of the block reflector H. N >= 0.
81*> \endverbatim
82*>
83*> \param[in] K
84*> \verbatim
85*> K is INTEGER
86*> The order of the triangular factor T (= the number of
87*> elementary reflectors). K >= 1.
88*> \endverbatim
89*>
90*> \param[in,out] V
91*> \verbatim
92*> V is COMPLEX array, dimension
93*> (LDV,K) if STOREV = 'C'
94*> (LDV,N) if STOREV = 'R'
95*> The matrix V. See further details.
96*> \endverbatim
97*>
98*> \param[in] LDV
99*> \verbatim
100*> LDV is INTEGER
101*> The leading dimension of the array V.
102*> If STOREV = 'C', LDV >= max(1,N); if STOREV = 'R', LDV >= K.
103*> \endverbatim
104*>
105*> \param[in] TAU
106*> \verbatim
107*> TAU is COMPLEX array, dimension (K)
108*> TAU(i) must contain the scalar factor of the elementary
109*> reflector H(i).
110*> \endverbatim
111*>
112*> \param[out] T
113*> \verbatim
114*> T is COMPLEX array, dimension (LDT,K)
115*> The k by k triangular factor T of the block reflector.
116*> If DIRECT = 'F', T is upper triangular; if DIRECT = 'B', T is
117*> lower triangular. The rest of the array is not used.
118*> \endverbatim
119*>
120*> \param[in] LDT
121*> \verbatim
122*> LDT is INTEGER
123*> The leading dimension of the array T. LDT >= K.
124*> \endverbatim
125*
126* Authors:
127* ========
128*
129*> \author Univ. of Tennessee
130*> \author Univ. of California Berkeley
131*> \author Univ. of Colorado Denver
132*> \author NAG Ltd.
133*
134*> \ingroup larzt
135*
136*> \par Contributors:
137* ==================
138*>
139*> A. Petitet, Computer Science Dept., Univ. of Tenn., Knoxville, USA
140*
141*> \par Further Details:
142* =====================
143*>
144*> \verbatim
145*>
146*> The shape of the matrix V and the storage of the vectors which define
147*> the H(i) is best illustrated by the following example with n = 5 and
148*> k = 3. The elements equal to 1 are not stored; the corresponding
149*> array elements are modified but restored on exit. The rest of the
150*> array is not used.
151*>
152*> DIRECT = 'F' and STOREV = 'C': DIRECT = 'F' and STOREV = 'R':
153*>
154*> ______V_____
155*> ( v1 v2 v3 ) / \
156*> ( v1 v2 v3 ) ( v1 v1 v1 v1 v1 . . . . 1 )
157*> V = ( v1 v2 v3 ) ( v2 v2 v2 v2 v2 . . . 1 )
158*> ( v1 v2 v3 ) ( v3 v3 v3 v3 v3 . . 1 )
159*> ( v1 v2 v3 )
160*> . . .
161*> . . .
162*> 1 . .
163*> 1 .
164*> 1
165*>
166*> DIRECT = 'B' and STOREV = 'C': DIRECT = 'B' and STOREV = 'R':
167*>
168*> ______V_____
169*> 1 / \
170*> . 1 ( 1 . . . . v1 v1 v1 v1 v1 )
171*> . . 1 ( . 1 . . . v2 v2 v2 v2 v2 )
172*> . . . ( . . 1 . . v3 v3 v3 v3 v3 )
173*> . . .
174*> ( v1 v2 v3 )
175*> ( v1 v2 v3 )
176*> V = ( v1 v2 v3 )
177*> ( v1 v2 v3 )
178*> ( v1 v2 v3 )
179*> \endverbatim
180*>
181* =====================================================================
182 SUBROUTINE clarzt( DIRECT, STOREV, N, K, V, LDV, TAU, T, LDT )
183*
184* -- LAPACK computational routine --
185* -- LAPACK is a software package provided by Univ. of Tennessee, --
186* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
187*
188* .. Scalar Arguments ..
189 CHARACTER DIRECT, STOREV
190 INTEGER K, LDT, LDV, N
191* ..
192* .. Array Arguments ..
193 COMPLEX T( LDT, * ), TAU( * ), V( LDV, * )
194* ..
195*
196* =====================================================================
197*
198* .. Parameters ..
199 COMPLEX ZERO
200 parameter( zero = ( 0.0e+0, 0.0e+0 ) )
201* ..
202* .. Local Scalars ..
203 INTEGER I, INFO, J
204* ..
205* .. External Subroutines ..
206 EXTERNAL cgemv, clacgv, ctrmv, xerbla
207* ..
208* .. External Functions ..
209 LOGICAL LSAME
210 EXTERNAL lsame
211* ..
212* .. Executable Statements ..
213*
214* Check for currently supported options
215*
216 info = 0
217 IF( .NOT.lsame( direct, 'B' ) ) THEN
218 info = -1
219 ELSE IF( .NOT.lsame( storev, 'R' ) ) THEN
220 info = -2
221 END IF
222 IF( info.NE.0 ) THEN
223 CALL xerbla( 'CLARZT', -info )
224 RETURN
225 END IF
226*
227 DO 20 i = k, 1, -1
228 IF( tau( i ).EQ.zero ) THEN
229*
230* H(i) = I
231*
232 DO 10 j = i, k
233 t( j, i ) = zero
234 10 CONTINUE
235 ELSE
236*
237* general case
238*
239 IF( i.LT.k ) THEN
240*
241* T(i+1:k,i) = - tau(i) * V(i+1:k,1:n) * V(i,1:n)**H
242*
243 CALL clacgv( n, v( i, 1 ), ldv )
244 CALL cgemv( 'No transpose', k-i, n, -tau( i ),
245 $ v( i+1, 1 ), ldv, v( i, 1 ), ldv, zero,
246 $ t( i+1, i ), 1 )
247 CALL clacgv( n, v( i, 1 ), ldv )
248*
249* T(i+1:k,i) = T(i+1:k,i+1:k) * T(i+1:k,i)
250*
251 CALL ctrmv( 'Lower', 'No transpose', 'Non-unit', k-i,
252 $ t( i+1, i+1 ), ldt, t( i+1, i ), 1 )
253 END IF
254 t( i, i ) = tau( i )
255 END IF
256 20 CONTINUE
257 RETURN
258*
259* End of CLARZT
260*
261 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine cgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
CGEMV
Definition cgemv.f:160
subroutine clacgv(n, x, incx)
CLACGV conjugates a complex vector.
Definition clacgv.f:72
subroutine clarzt(direct, storev, n, k, v, ldv, tau, t, ldt)
CLARZT forms the triangular factor T of a block reflector H = I - vtvH.
Definition clarzt.f:183
subroutine ctrmv(uplo, trans, diag, n, a, lda, x, incx)
CTRMV
Definition ctrmv.f:147