Statistiques
| Révision :

root / src / lapack / double / dlatrz.f @ 10

Historique | Voir | Annoter | Télécharger (3,83 ko)

1 1 pfleura2
      SUBROUTINE DLATRZ( M, N, L, A, LDA, TAU, WORK )
2 1 pfleura2
*
3 1 pfleura2
*  -- LAPACK routine (version 3.2.2) --
4 1 pfleura2
*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
5 1 pfleura2
*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
6 1 pfleura2
*     June 2010
7 1 pfleura2
*
8 1 pfleura2
*     .. Scalar Arguments ..
9 1 pfleura2
      INTEGER            L, LDA, M, N
10 1 pfleura2
*     ..
11 1 pfleura2
*     .. Array Arguments ..
12 1 pfleura2
      DOUBLE PRECISION   A( LDA, * ), TAU( * ), WORK( * )
13 1 pfleura2
*     ..
14 1 pfleura2
*
15 1 pfleura2
*  Purpose
16 1 pfleura2
*  =======
17 1 pfleura2
*
18 1 pfleura2
*  DLATRZ factors the M-by-(M+L) real upper trapezoidal matrix
19 1 pfleura2
*  [ A1 A2 ] = [ A(1:M,1:M) A(1:M,N-L+1:N) ] as ( R  0 ) * Z, by means
20 1 pfleura2
*  of orthogonal transformations.  Z is an (M+L)-by-(M+L) orthogonal
21 1 pfleura2
*  matrix and, R and A1 are M-by-M upper triangular matrices.
22 1 pfleura2
*
23 1 pfleura2
*  Arguments
24 1 pfleura2
*  =========
25 1 pfleura2
*
26 1 pfleura2
*  M       (input) INTEGER
27 1 pfleura2
*          The number of rows of the matrix A.  M >= 0.
28 1 pfleura2
*
29 1 pfleura2
*  N       (input) INTEGER
30 1 pfleura2
*          The number of columns of the matrix A.  N >= 0.
31 1 pfleura2
*
32 1 pfleura2
*  L       (input) INTEGER
33 1 pfleura2
*          The number of columns of the matrix A containing the
34 1 pfleura2
*          meaningful part of the Householder vectors. N-M >= L >= 0.
35 1 pfleura2
*
36 1 pfleura2
*  A       (input/output) DOUBLE PRECISION array, dimension (LDA,N)
37 1 pfleura2
*          On entry, the leading M-by-N upper trapezoidal part of the
38 1 pfleura2
*          array A must contain the matrix to be factorized.
39 1 pfleura2
*          On exit, the leading M-by-M upper triangular part of A
40 1 pfleura2
*          contains the upper triangular matrix R, and elements N-L+1 to
41 1 pfleura2
*          N of the first M rows of A, with the array TAU, represent the
42 1 pfleura2
*          orthogonal matrix Z as a product of M elementary reflectors.
43 1 pfleura2
*
44 1 pfleura2
*  LDA     (input) INTEGER
45 1 pfleura2
*          The leading dimension of the array A.  LDA >= max(1,M).
46 1 pfleura2
*
47 1 pfleura2
*  TAU     (output) DOUBLE PRECISION array, dimension (M)
48 1 pfleura2
*          The scalar factors of the elementary reflectors.
49 1 pfleura2
*
50 1 pfleura2
*  WORK    (workspace) DOUBLE PRECISION array, dimension (M)
51 1 pfleura2
*
52 1 pfleura2
*  Further Details
53 1 pfleura2
*  ===============
54 1 pfleura2
*
55 1 pfleura2
*  Based on contributions by
56 1 pfleura2
*    A. Petitet, Computer Science Dept., Univ. of Tenn., Knoxville, USA
57 1 pfleura2
*
58 1 pfleura2
*  The factorization is obtained by Householder's method.  The kth
59 1 pfleura2
*  transformation matrix, Z( k ), which is used to introduce zeros into
60 1 pfleura2
*  the ( m - k + 1 )th row of A, is given in the form
61 1 pfleura2
*
62 1 pfleura2
*     Z( k ) = ( I     0   ),
63 1 pfleura2
*              ( 0  T( k ) )
64 1 pfleura2
*
65 1 pfleura2
*  where
66 1 pfleura2
*
67 1 pfleura2
*     T( k ) = I - tau*u( k )*u( k )',   u( k ) = (   1    ),
68 1 pfleura2
*                                                 (   0    )
69 1 pfleura2
*                                                 ( z( k ) )
70 1 pfleura2
*
71 1 pfleura2
*  tau is a scalar and z( k ) is an l element vector. tau and z( k )
72 1 pfleura2
*  are chosen to annihilate the elements of the kth row of A2.
73 1 pfleura2
*
74 1 pfleura2
*  The scalar tau is returned in the kth element of TAU and the vector
75 1 pfleura2
*  u( k ) in the kth row of A2, such that the elements of z( k ) are
76 1 pfleura2
*  in  a( k, l + 1 ), ..., a( k, n ). The elements of R are returned in
77 1 pfleura2
*  the upper triangular part of A1.
78 1 pfleura2
*
79 1 pfleura2
*  Z is given by
80 1 pfleura2
*
81 1 pfleura2
*     Z =  Z( 1 ) * Z( 2 ) * ... * Z( m ).
82 1 pfleura2
*
83 1 pfleura2
*  =====================================================================
84 1 pfleura2
*
85 1 pfleura2
*     .. Parameters ..
86 1 pfleura2
      DOUBLE PRECISION   ZERO
87 1 pfleura2
      PARAMETER          ( ZERO = 0.0D+0 )
88 1 pfleura2
*     ..
89 1 pfleura2
*     .. Local Scalars ..
90 1 pfleura2
      INTEGER            I
91 1 pfleura2
*     ..
92 1 pfleura2
*     .. External Subroutines ..
93 1 pfleura2
      EXTERNAL           DLARFG, DLARZ
94 1 pfleura2
*     ..
95 1 pfleura2
*     .. Executable Statements ..
96 1 pfleura2
*
97 1 pfleura2
*     Test the input arguments
98 1 pfleura2
*
99 1 pfleura2
*     Quick return if possible
100 1 pfleura2
*
101 1 pfleura2
      IF( M.EQ.0 ) THEN
102 1 pfleura2
         RETURN
103 1 pfleura2
      ELSE IF( M.EQ.N ) THEN
104 1 pfleura2
         DO 10 I = 1, N
105 1 pfleura2
            TAU( I ) = ZERO
106 1 pfleura2
   10    CONTINUE
107 1 pfleura2
         RETURN
108 1 pfleura2
      END IF
109 1 pfleura2
*
110 1 pfleura2
      DO 20 I = M, 1, -1
111 1 pfleura2
*
112 1 pfleura2
*        Generate elementary reflector H(i) to annihilate
113 1 pfleura2
*        [ A(i,i) A(i,n-l+1:n) ]
114 1 pfleura2
*
115 1 pfleura2
         CALL DLARFG( L+1, A( I, I ), A( I, N-L+1 ), LDA, TAU( I ) )
116 1 pfleura2
*
117 1 pfleura2
*        Apply H(i) to A(1:i-1,i:n) from the right
118 1 pfleura2
*
119 1 pfleura2
         CALL DLARZ( 'Right', I-1, N-I+1, L, A( I, N-L+1 ), LDA,
120 1 pfleura2
     $               TAU( I ), A( 1, I ), LDA, WORK )
121 1 pfleura2
*
122 1 pfleura2
   20 CONTINUE
123 1 pfleura2
*
124 1 pfleura2
      RETURN
125 1 pfleura2
*
126 1 pfleura2
*     End of DLATRZ
127 1 pfleura2
*
128 1 pfleura2
      END