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

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

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

Purpose:
 DLARFT forms the triangular factor T of a real 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**T

 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**T * 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 DOUBLE PRECISION 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 DOUBLE PRECISION array, dimension (K)
          TAU(i) must contain the scalar factor of the elementary
          reflector H(i).
[out]T
          T is DOUBLE PRECISION 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 dlarft.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  DOUBLE PRECISION t( ldt, * ), tau( * ), v( ldv, * )
177 * ..
178 *
179 * =====================================================================
180 *
181 * .. Parameters ..
182  DOUBLE PRECISION one, zero
183  parameter ( one = 1.0d+0, zero = 0.0d+0 )
184 * ..
185 * .. Local Scalars ..
186  INTEGER i, j, prevlastv, lastv
187 * ..
188 * .. External Subroutines ..
189  EXTERNAL dgemv, dtrmv
190 * ..
191 * .. External Functions ..
192  LOGICAL lsame
193  EXTERNAL lsame
194 * ..
195 * .. Executable Statements ..
196 *
197 * Quick return if possible
198 *
199  IF( n.EQ.0 )
200  $ RETURN
201 *
202  IF( lsame( direct, 'F' ) ) THEN
203  prevlastv = n
204  DO i = 1, k
205  prevlastv = max( i, prevlastv )
206  IF( tau( i ).EQ.zero ) THEN
207 *
208 * H(i) = I
209 *
210  DO j = 1, i
211  t( j, i ) = zero
212  END DO
213  ELSE
214 *
215 * general case
216 *
217  IF( lsame( storev, 'C' ) ) THEN
218 * Skip any trailing zeros.
219  DO lastv = n, i+1, -1
220  IF( v( lastv, i ).NE.zero ) EXIT
221  END DO
222  DO j = 1, i-1
223  t( j, i ) = -tau( i ) * v( i , j )
224  END DO
225  j = min( lastv, prevlastv )
226 *
227 * T(1:i-1,i) := - tau(i) * V(i:j,1:i-1)**T * V(i:j,i)
228 *
229  CALL dgemv( 'Transpose', j-i, i-1, -tau( i ),
230  $ v( i+1, 1 ), ldv, v( i+1, i ), 1, one,
231  $ t( 1, i ), 1 )
232  ELSE
233 * Skip any trailing zeros.
234  DO lastv = n, i+1, -1
235  IF( v( i, lastv ).NE.zero ) EXIT
236  END DO
237  DO j = 1, i-1
238  t( j, i ) = -tau( i ) * v( j , i )
239  END DO
240  j = min( lastv, prevlastv )
241 *
242 * T(1:i-1,i) := - tau(i) * V(1:i-1,i:j) * V(i,i:j)**T
243 *
244  CALL dgemv( 'No transpose', i-1, j-i, -tau( i ),
245  $ v( 1, i+1 ), ldv, v( i, i+1 ), ldv, one,
246  $ t( 1, i ), 1 )
247  END IF
248 *
249 * T(1:i-1,i) := T(1:i-1,1:i-1) * T(1:i-1,i)
250 *
251  CALL dtrmv( 'Upper', 'No transpose', 'Non-unit', i-1, t,
252  $ ldt, t( 1, i ), 1 )
253  t( i, i ) = tau( i )
254  IF( i.GT.1 ) THEN
255  prevlastv = max( prevlastv, lastv )
256  ELSE
257  prevlastv = lastv
258  END IF
259  END IF
260  END DO
261  ELSE
262  prevlastv = 1
263  DO i = k, 1, -1
264  IF( tau( i ).EQ.zero ) THEN
265 *
266 * H(i) = I
267 *
268  DO j = i, k
269  t( j, i ) = zero
270  END DO
271  ELSE
272 *
273 * general case
274 *
275  IF( i.LT.k ) THEN
276  IF( lsame( storev, 'C' ) ) THEN
277 * Skip any leading zeros.
278  DO lastv = 1, i-1
279  IF( v( lastv, i ).NE.zero ) EXIT
280  END DO
281  DO j = i+1, k
282  t( j, i ) = -tau( i ) * v( n-k+i , j )
283  END DO
284  j = max( lastv, prevlastv )
285 *
286 * T(i+1:k,i) = -tau(i) * V(j:n-k+i,i+1:k)**T * V(j:n-k+i,i)
287 *
288  CALL dgemv( 'Transpose', n-k+i-j, k-i, -tau( i ),
289  $ v( j, i+1 ), ldv, v( j, i ), 1, one,
290  $ t( i+1, i ), 1 )
291  ELSE
292 * Skip any leading zeros.
293  DO lastv = 1, i-1
294  IF( v( i, lastv ).NE.zero ) EXIT
295  END DO
296  DO j = i+1, k
297  t( j, i ) = -tau( i ) * v( j, n-k+i )
298  END DO
299  j = max( lastv, prevlastv )
300 *
301 * T(i+1:k,i) = -tau(i) * V(i+1:k,j:n-k+i) * V(i,j:n-k+i)**T
302 *
303  CALL dgemv( 'No transpose', k-i, n-k+i-j,
304  $ -tau( i ), v( i+1, j ), ldv, v( i, j ), ldv,
305  $ one, t( i+1, i ), 1 )
306  END IF
307 *
308 * T(i+1:k,i) := T(i+1:k,i+1:k) * T(i+1:k,i)
309 *
310  CALL dtrmv( 'Lower', 'No transpose', 'Non-unit', k-i,
311  $ t( i+1, i+1 ), ldt, t( i+1, i ), 1 )
312  IF( i.GT.1 ) THEN
313  prevlastv = min( prevlastv, lastv )
314  ELSE
315  prevlastv = lastv
316  END IF
317  END IF
318  t( i, i ) = tau( i )
319  END IF
320  END DO
321  END IF
322  RETURN
323 *
324 * End of DLARFT
325 *
subroutine dgemv(TRANS, M, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
DGEMV
Definition: dgemv.f:158
subroutine dtrmv(UPLO, TRANS, DIAG, N, A, LDA, X, INCX)
DTRMV
Definition: dtrmv.f:149
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: