LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ zlarzt()

subroutine zlarzt ( character direct,
character storev,
integer n,
integer k,
complex*16, dimension( ldv, * ) v,
integer ldv,
complex*16, dimension( * ) tau,
complex*16, dimension( ldt, * ) t,
integer ldt )

ZLARZT forms the triangular factor T of a block reflector H = I - vtvH.

Download ZLARZT + dependencies [TGZ] [ZIP] [TXT]

Purpose:
!>
!> ZLARZT forms the triangular factor T of a complex block reflector
!> H of order > n, which is defined as a product of k elementary
!> reflectors.
!>
!> If DIRECT = 'F', H = H(1) H(2) . . . H(k) and T is upper triangular;
!>
!> If DIRECT = 'B', H = H(k) . . . H(2) H(1) and T is lower triangular.
!>
!> If STOREV = 'C', the vector which defines the elementary reflector
!> H(i) is stored in the i-th column of the array V, and
!>
!>    H  =  I - V * T * V**H
!>
!> If STOREV = 'R', the vector which defines the elementary reflector
!> H(i) is stored in the i-th row of the array V, and
!>
!>    H  =  I - V**H * T * V
!>
!> Currently, only STOREV = 'R' and DIRECT = 'B' are supported.
!> 
Parameters
[in]DIRECT
!>          DIRECT is CHARACTER*1
!>          Specifies the order in which the elementary reflectors are
!>          multiplied to form the block reflector:
!>          = 'F': H = H(1) H(2) . . . H(k) (Forward, not supported yet)
!>          = 'B': H = H(k) . . . H(2) H(1) (Backward)
!> 
[in]STOREV
!>          STOREV is CHARACTER*1
!>          Specifies how the vectors which define the elementary
!>          reflectors are stored (see also Further Details):
!>          = 'C': columnwise                        (not supported yet)
!>          = 'R': rowwise
!> 
[in]N
!>          N is INTEGER
!>          The order of the block reflector H. N >= 0.
!> 
[in]K
!>          K is INTEGER
!>          The order of the triangular factor T (= the number of
!>          elementary reflectors). K >= 1.
!> 
[in,out]V
!>          V is COMPLEX*16 array, dimension
!>                               (LDV,K) if STOREV = 'C'
!>                               (LDV,N) if STOREV = 'R'
!>          The matrix V. See further details.
!> 
[in]LDV
!>          LDV is INTEGER
!>          The leading dimension of the array V.
!>          If STOREV = 'C', LDV >= max(1,N); if STOREV = 'R', LDV >= K.
!> 
[in]TAU
!>          TAU is COMPLEX*16 array, dimension (K)
!>          TAU(i) must contain the scalar factor of the elementary
!>          reflector H(i).
!> 
[out]T
!>          T is COMPLEX*16 array, dimension (LDT,K)
!>          The k by k triangular factor T of the block reflector.
!>          If DIRECT = 'F', T is upper triangular; if DIRECT = 'B', T is
!>          lower triangular. The rest of the array is not used.
!> 
[in]LDT
!>          LDT is INTEGER
!>          The leading dimension of the array T. LDT >= K.
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Contributors:
A. Petitet, Computer Science Dept., Univ. of Tenn., Knoxville, USA
Further Details:
!>
!>  The shape of the matrix V and the storage of the vectors which define
!>  the H(i) is best illustrated by the following example with n = 5 and
!>  k = 3. The elements equal to 1 are not stored; the corresponding
!>  array elements are modified but restored on exit. The rest of the
!>  array is not used.
!>
!>  DIRECT = 'F' and STOREV = 'C':         DIRECT = 'F' and STOREV = 'R':
!>
!>                                              ______V_____
!>         ( v1 v2 v3 )                        /            \
!>         ( v1 v2 v3 )                      ( v1 v1 v1 v1 v1 . . . . 1 )
!>     V = ( v1 v2 v3 )                      ( v2 v2 v2 v2 v2 . . . 1   )
!>         ( v1 v2 v3 )                      ( v3 v3 v3 v3 v3 . . 1     )
!>         ( v1 v2 v3 )
!>            .  .  .
!>            .  .  .
!>            1  .  .
!>               1  .
!>                  1
!>
!>  DIRECT = 'B' and STOREV = 'C':         DIRECT = 'B' and STOREV = 'R':
!>
!>                                                        ______V_____
!>            1                                          /            \
!>            .  1                           ( 1 . . . . v1 v1 v1 v1 v1 )
!>            .  .  1                        ( . 1 . . . v2 v2 v2 v2 v2 )
!>            .  .  .                        ( . . 1 . . v3 v3 v3 v3 v3 )
!>            .  .  .
!>         ( v1 v2 v3 )
!>         ( v1 v2 v3 )
!>     V = ( v1 v2 v3 )
!>         ( v1 v2 v3 )
!>         ( v1 v2 v3 )
!> 

Definition at line 182 of file zlarzt.f.

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*16 T( LDT, * ), TAU( * ), V( LDV, * )
194* ..
195*
196* =====================================================================
197*
198* .. Parameters ..
199 COMPLEX*16 ZERO
200 parameter( zero = ( 0.0d+0, 0.0d+0 ) )
201* ..
202* .. Local Scalars ..
203 INTEGER I, INFO, J
204* ..
205* .. External Subroutines ..
206 EXTERNAL xerbla, zgemv, zlacgv, ztrmv
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( 'ZLARZT', -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 zlacgv( n, v( i, 1 ), ldv )
244 CALL zgemv( '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 zlacgv( 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 ztrmv( '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 ZLARZT
260*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
ZGEMV
Definition zgemv.f:160
subroutine zlacgv(n, x, incx)
ZLACGV conjugates a complex vector.
Definition zlacgv.f:72
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine ztrmv(uplo, trans, diag, n, a, lda, x, incx)
ZTRMV
Definition ztrmv.f:147
Here is the call graph for this function:
Here is the caller graph for this function: