LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine clarft ( character  DIRECT,
character  STOREV,
integer  N,
integer  K,
complex, dimension( ldv, * )  V,
integer  LDV,
complex, dimension( * )  TAU,
complex, dimension( ldt, * )  T,
integer  LDT 
)

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

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

Purpose:
 CLARFT 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
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)
          = '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
          = '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]V
          V is COMPLEX 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 array, dimension (K)
          TAU(i) must contain the scalar factor of the elementary
          reflector H(i).
[out]T
          T is COMPLEX 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.
Date
September 2012
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.

  DIRECT = 'F' and STOREV = 'C':         DIRECT = 'F' and STOREV = 'R':

               V = (  1       )                 V = (  1 v1 v1 v1 v1 )
                   ( v1  1    )                     (     1 v2 v2 v2 )
                   ( v1 v2  1 )                     (        1 v3 v3 )
                   ( v1 v2 v3 )
                   ( v1 v2 v3 )

  DIRECT = 'B' and STOREV = 'C':         DIRECT = 'B' and STOREV = 'R':

               V = ( v1 v2 v3 )                 V = ( v1 v1  1       )
                   ( v1 v2 v3 )                     ( v2 v2 v2  1    )
                   (  1 v2 v3 )                     ( v3 v3 v3 v3  1 )
                   (     1 v3 )
                   (        1 )

Definition at line 165 of file clarft.f.

165 *
166 * -- LAPACK auxiliary routine (version 3.4.2) --
167 * -- LAPACK is a software package provided by Univ. of Tennessee, --
168 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
169 * September 2012
170 *
171 * .. Scalar Arguments ..
172  CHARACTER direct, storev
173  INTEGER k, ldt, ldv, n
174 * ..
175 * .. Array Arguments ..
176  COMPLEX t( ldt, * ), tau( * ), v( ldv, * )
177 * ..
178 *
179 * =====================================================================
180 *
181 * .. Parameters ..
182  COMPLEX one, zero
183  parameter ( one = ( 1.0e+0, 0.0e+0 ),
184  $ zero = ( 0.0e+0, 0.0e+0 ) )
185 * ..
186 * .. Local Scalars ..
187  INTEGER i, j, prevlastv, lastv
188 * ..
189 * .. External Subroutines ..
190  EXTERNAL cgemv, clacgv, ctrmv
191 * ..
192 * .. External Functions ..
193  LOGICAL lsame
194  EXTERNAL lsame
195 * ..
196 * .. Executable Statements ..
197 *
198 * Quick return if possible
199 *
200  IF( n.EQ.0 )
201  $ RETURN
202 *
203  IF( lsame( direct, 'F' ) ) THEN
204  prevlastv = n
205  DO i = 1, k
206  prevlastv = max( prevlastv, i )
207  IF( tau( i ).EQ.zero ) THEN
208 *
209 * H(i) = I
210 *
211  DO j = 1, i
212  t( j, i ) = zero
213  END DO
214  ELSE
215 *
216 * general case
217 *
218  IF( lsame( storev, 'C' ) ) THEN
219 * Skip any trailing zeros.
220  DO lastv = n, i+1, -1
221  IF( v( lastv, i ).NE.zero ) EXIT
222  END DO
223  DO j = 1, i-1
224  t( j, i ) = -tau( i ) * conjg( v( i , j ) )
225  END DO
226  j = min( lastv, prevlastv )
227 *
228 * T(1:i-1,i) := - tau(i) * V(i:j,1:i-1)**H * V(i:j,i)
229 *
230  CALL cgemv( 'Conjugate transpose', j-i, i-1,
231  $ -tau( i ), v( i+1, 1 ), ldv,
232  $ v( i+1, i ), 1,
233  $ one, t( 1, i ), 1 )
234  ELSE
235 * Skip any trailing zeros.
236  DO lastv = n, i+1, -1
237  IF( v( i, lastv ).NE.zero ) EXIT
238  END DO
239  DO j = 1, i-1
240  t( j, i ) = -tau( i ) * v( j , i )
241  END DO
242  j = min( lastv, prevlastv )
243 *
244 * T(1:i-1,i) := - tau(i) * V(1:i-1,i:j) * V(i,i:j)**H
245 *
246  CALL cgemm( 'N', 'C', i-1, 1, j-i, -tau( i ),
247  $ v( 1, i+1 ), ldv, v( i, i+1 ), ldv,
248  $ one, t( 1, i ), ldt )
249  END IF
250 *
251 * T(1:i-1,i) := T(1:i-1,1:i-1) * T(1:i-1,i)
252 *
253  CALL ctrmv( 'Upper', 'No transpose', 'Non-unit', i-1, t,
254  $ ldt, t( 1, i ), 1 )
255  t( i, i ) = tau( i )
256  IF( i.GT.1 ) THEN
257  prevlastv = max( prevlastv, lastv )
258  ELSE
259  prevlastv = lastv
260  END IF
261  END IF
262  END DO
263  ELSE
264  prevlastv = 1
265  DO i = k, 1, -1
266  IF( tau( i ).EQ.zero ) THEN
267 *
268 * H(i) = I
269 *
270  DO j = i, k
271  t( j, i ) = zero
272  END DO
273  ELSE
274 *
275 * general case
276 *
277  IF( i.LT.k ) THEN
278  IF( lsame( storev, 'C' ) ) THEN
279 * Skip any leading zeros.
280  DO lastv = 1, i-1
281  IF( v( lastv, i ).NE.zero ) EXIT
282  END DO
283  DO j = i+1, k
284  t( j, i ) = -tau( i ) * conjg( v( n-k+i , j ) )
285  END DO
286  j = max( lastv, prevlastv )
287 *
288 * T(i+1:k,i) = -tau(i) * V(j:n-k+i,i+1:k)**H * V(j:n-k+i,i)
289 *
290  CALL cgemv( 'Conjugate transpose', n-k+i-j, k-i,
291  $ -tau( i ), v( j, i+1 ), ldv, v( j, i ),
292  $ 1, one, t( i+1, i ), 1 )
293  ELSE
294 * Skip any leading zeros.
295  DO lastv = 1, i-1
296  IF( v( i, lastv ).NE.zero ) EXIT
297  END DO
298  DO j = i+1, k
299  t( j, i ) = -tau( i ) * v( j, n-k+i )
300  END DO
301  j = max( lastv, prevlastv )
302 *
303 * T(i+1:k,i) = -tau(i) * V(i+1:k,j:n-k+i) * V(i,j:n-k+i)**H
304 *
305  CALL cgemm( 'N', 'C', k-i, 1, n-k+i-j, -tau( i ),
306  $ v( i+1, j ), ldv, v( i, j ), ldv,
307  $ one, t( i+1, i ), ldt )
308  END IF
309 *
310 * T(i+1:k,i) := T(i+1:k,i+1:k) * T(i+1:k,i)
311 *
312  CALL ctrmv( 'Lower', 'No transpose', 'Non-unit', k-i,
313  $ t( i+1, i+1 ), ldt, t( i+1, i ), 1 )
314  IF( i.GT.1 ) THEN
315  prevlastv = min( prevlastv, lastv )
316  ELSE
317  prevlastv = lastv
318  END IF
319  END IF
320  t( i, i ) = tau( i )
321  END IF
322  END DO
323  END IF
324  RETURN
325 *
326 * End of CLARFT
327 *
subroutine cgemv(TRANS, M, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
CGEMV
Definition: cgemv.f:160
subroutine ctrmv(UPLO, TRANS, DIAG, N, A, LDA, X, INCX)
CTRMV
Definition: ctrmv.f:149
subroutine clacgv(N, X, INCX)
CLACGV conjugates a complex vector.
Definition: clacgv.f:76
subroutine cgemm(TRANSA, TRANSB, M, N, K, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
CGEMM
Definition: cgemm.f:189
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55

Here is the call graph for this function:

Here is the caller graph for this function: