Statistiques
| Révision :

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

Historique | Voir | Annoter | Télécharger (7,11 ko)

1 1 pfleura2
      SUBROUTINE DTZRZF( M, N, A, LDA, TAU, WORK, LWORK, INFO )
2 1 pfleura2
*
3 1 pfleura2
*  -- LAPACK routine (version 3.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
*     November 2006
7 1 pfleura2
*
8 1 pfleura2
*     .. Scalar Arguments ..
9 1 pfleura2
      INTEGER            INFO, LDA, LWORK, 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
*  DTZRZF reduces the M-by-N ( M<=N ) real upper trapezoidal matrix A
19 1 pfleura2
*  to upper triangular form by means of orthogonal transformations.
20 1 pfleura2
*
21 1 pfleura2
*  The upper trapezoidal matrix A is factored as
22 1 pfleura2
*
23 1 pfleura2
*     A = ( R  0 ) * Z,
24 1 pfleura2
*
25 1 pfleura2
*  where Z is an N-by-N orthogonal matrix and R is an M-by-M upper
26 1 pfleura2
*  triangular matrix.
27 1 pfleura2
*
28 1 pfleura2
*  Arguments
29 1 pfleura2
*  =========
30 1 pfleura2
*
31 1 pfleura2
*  M       (input) INTEGER
32 1 pfleura2
*          The number of rows of the matrix A.  M >= 0.
33 1 pfleura2
*
34 1 pfleura2
*  N       (input) INTEGER
35 1 pfleura2
*          The number of columns of the matrix A.  N >= M.
36 1 pfleura2
*
37 1 pfleura2
*  A       (input/output) DOUBLE PRECISION array, dimension (LDA,N)
38 1 pfleura2
*          On entry, the leading M-by-N upper trapezoidal part of the
39 1 pfleura2
*          array A must contain the matrix to be factorized.
40 1 pfleura2
*          On exit, the leading M-by-M upper triangular part of A
41 1 pfleura2
*          contains the upper triangular matrix R, and elements M+1 to
42 1 pfleura2
*          N of the first M rows of A, with the array TAU, represent the
43 1 pfleura2
*          orthogonal matrix Z as a product of M elementary reflectors.
44 1 pfleura2
*
45 1 pfleura2
*  LDA     (input) INTEGER
46 1 pfleura2
*          The leading dimension of the array A.  LDA >= max(1,M).
47 1 pfleura2
*
48 1 pfleura2
*  TAU     (output) DOUBLE PRECISION array, dimension (M)
49 1 pfleura2
*          The scalar factors of the elementary reflectors.
50 1 pfleura2
*
51 1 pfleura2
*  WORK    (workspace/output) DOUBLE PRECISION array, dimension (MAX(1,LWORK))
52 1 pfleura2
*          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
53 1 pfleura2
*
54 1 pfleura2
*  LWORK   (input) INTEGER
55 1 pfleura2
*          The dimension of the array WORK.  LWORK >= max(1,M).
56 1 pfleura2
*          For optimum performance LWORK >= M*NB, where NB is
57 1 pfleura2
*          the optimal blocksize.
58 1 pfleura2
*
59 1 pfleura2
*          If LWORK = -1, then a workspace query is assumed; the routine
60 1 pfleura2
*          only calculates the optimal size of the WORK array, returns
61 1 pfleura2
*          this value as the first entry of the WORK array, and no error
62 1 pfleura2
*          message related to LWORK is issued by XERBLA.
63 1 pfleura2
*
64 1 pfleura2
*  INFO    (output) INTEGER
65 1 pfleura2
*          = 0:  successful exit
66 1 pfleura2
*          < 0:  if INFO = -i, the i-th argument had an illegal value
67 1 pfleura2
*
68 1 pfleura2
*  Further Details
69 1 pfleura2
*  ===============
70 1 pfleura2
*
71 1 pfleura2
*  Based on contributions by
72 1 pfleura2
*    A. Petitet, Computer Science Dept., Univ. of Tenn., Knoxville, USA
73 1 pfleura2
*
74 1 pfleura2
*  The factorization is obtained by Householder's method.  The kth
75 1 pfleura2
*  transformation matrix, Z( k ), which is used to introduce zeros into
76 1 pfleura2
*  the ( m - k + 1 )th row of A, is given in the form
77 1 pfleura2
*
78 1 pfleura2
*     Z( k ) = ( I     0   ),
79 1 pfleura2
*              ( 0  T( k ) )
80 1 pfleura2
*
81 1 pfleura2
*  where
82 1 pfleura2
*
83 1 pfleura2
*     T( k ) = I - tau*u( k )*u( k )',   u( k ) = (   1    ),
84 1 pfleura2
*                                                 (   0    )
85 1 pfleura2
*                                                 ( z( k ) )
86 1 pfleura2
*
87 1 pfleura2
*  tau is a scalar and z( k ) is an ( n - m ) element vector.
88 1 pfleura2
*  tau and z( k ) are chosen to annihilate the elements of the kth row
89 1 pfleura2
*  of X.
90 1 pfleura2
*
91 1 pfleura2
*  The scalar tau is returned in the kth element of TAU and the vector
92 1 pfleura2
*  u( k ) in the kth row of A, such that the elements of z( k ) are
93 1 pfleura2
*  in  a( k, m + 1 ), ..., a( k, n ). The elements of R are returned in
94 1 pfleura2
*  the upper triangular part of A.
95 1 pfleura2
*
96 1 pfleura2
*  Z is given by
97 1 pfleura2
*
98 1 pfleura2
*     Z =  Z( 1 ) * Z( 2 ) * ... * Z( m ).
99 1 pfleura2
*
100 1 pfleura2
*  =====================================================================
101 1 pfleura2
*
102 1 pfleura2
*     .. Parameters ..
103 1 pfleura2
      DOUBLE PRECISION   ZERO
104 1 pfleura2
      PARAMETER          ( ZERO = 0.0D+0 )
105 1 pfleura2
*     ..
106 1 pfleura2
*     .. Local Scalars ..
107 1 pfleura2
      LOGICAL            LQUERY
108 1 pfleura2
      INTEGER            I, IB, IWS, KI, KK, LDWORK, LWKOPT, M1, MU, NB,
109 1 pfleura2
     $                   NBMIN, NX
110 1 pfleura2
*     ..
111 1 pfleura2
*     .. External Subroutines ..
112 1 pfleura2
      EXTERNAL           DLARZB, DLARZT, DLATRZ, XERBLA
113 1 pfleura2
*     ..
114 1 pfleura2
*     .. Intrinsic Functions ..
115 1 pfleura2
      INTRINSIC          MAX, MIN
116 1 pfleura2
*     ..
117 1 pfleura2
*     .. External Functions ..
118 1 pfleura2
      INTEGER            ILAENV
119 1 pfleura2
      EXTERNAL           ILAENV
120 1 pfleura2
*     ..
121 1 pfleura2
*     .. Executable Statements ..
122 1 pfleura2
*
123 1 pfleura2
*     Test the input arguments
124 1 pfleura2
*
125 1 pfleura2
      INFO = 0
126 1 pfleura2
      LQUERY = ( LWORK.EQ.-1 )
127 1 pfleura2
      IF( M.LT.0 ) THEN
128 1 pfleura2
         INFO = -1
129 1 pfleura2
      ELSE IF( N.LT.M ) THEN
130 1 pfleura2
         INFO = -2
131 1 pfleura2
      ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
132 1 pfleura2
         INFO = -4
133 1 pfleura2
      END IF
134 1 pfleura2
*
135 1 pfleura2
      IF( INFO.EQ.0 ) THEN
136 1 pfleura2
         IF( M.EQ.0 .OR. M.EQ.N ) THEN
137 1 pfleura2
            LWKOPT = 1
138 1 pfleura2
         ELSE
139 1 pfleura2
*
140 1 pfleura2
*           Determine the block size.
141 1 pfleura2
*
142 1 pfleura2
            NB = ILAENV( 1, 'DGERQF', ' ', M, N, -1, -1 )
143 1 pfleura2
            LWKOPT = M*NB
144 1 pfleura2
         END IF
145 1 pfleura2
         WORK( 1 ) = LWKOPT
146 1 pfleura2
*
147 1 pfleura2
         IF( LWORK.LT.MAX( 1, M ) .AND. .NOT.LQUERY ) THEN
148 1 pfleura2
            INFO = -7
149 1 pfleura2
         END IF
150 1 pfleura2
      END IF
151 1 pfleura2
*
152 1 pfleura2
      IF( INFO.NE.0 ) THEN
153 1 pfleura2
         CALL XERBLA( 'DTZRZF', -INFO )
154 1 pfleura2
         RETURN
155 1 pfleura2
      ELSE IF( LQUERY ) THEN
156 1 pfleura2
         RETURN
157 1 pfleura2
      END IF
158 1 pfleura2
*
159 1 pfleura2
*     Quick return if possible
160 1 pfleura2
*
161 1 pfleura2
      IF( M.EQ.0 ) THEN
162 1 pfleura2
         RETURN
163 1 pfleura2
      ELSE IF( M.EQ.N ) THEN
164 1 pfleura2
         DO 10 I = 1, N
165 1 pfleura2
            TAU( I ) = ZERO
166 1 pfleura2
   10    CONTINUE
167 1 pfleura2
         RETURN
168 1 pfleura2
      END IF
169 1 pfleura2
*
170 1 pfleura2
      NBMIN = 2
171 1 pfleura2
      NX = 1
172 1 pfleura2
      IWS = M
173 1 pfleura2
      IF( NB.GT.1 .AND. NB.LT.M ) THEN
174 1 pfleura2
*
175 1 pfleura2
*        Determine when to cross over from blocked to unblocked code.
176 1 pfleura2
*
177 1 pfleura2
         NX = MAX( 0, ILAENV( 3, 'DGERQF', ' ', M, N, -1, -1 ) )
178 1 pfleura2
         IF( NX.LT.M ) THEN
179 1 pfleura2
*
180 1 pfleura2
*           Determine if workspace is large enough for blocked code.
181 1 pfleura2
*
182 1 pfleura2
            LDWORK = M
183 1 pfleura2
            IWS = LDWORK*NB
184 1 pfleura2
            IF( LWORK.LT.IWS ) THEN
185 1 pfleura2
*
186 1 pfleura2
*              Not enough workspace to use optimal NB:  reduce NB and
187 1 pfleura2
*              determine the minimum value of NB.
188 1 pfleura2
*
189 1 pfleura2
               NB = LWORK / LDWORK
190 1 pfleura2
               NBMIN = MAX( 2, ILAENV( 2, 'DGERQF', ' ', M, N, -1,
191 1 pfleura2
     $                 -1 ) )
192 1 pfleura2
            END IF
193 1 pfleura2
         END IF
194 1 pfleura2
      END IF
195 1 pfleura2
*
196 1 pfleura2
      IF( NB.GE.NBMIN .AND. NB.LT.M .AND. NX.LT.M ) THEN
197 1 pfleura2
*
198 1 pfleura2
*        Use blocked code initially.
199 1 pfleura2
*        The last kk rows are handled by the block method.
200 1 pfleura2
*
201 1 pfleura2
         M1 = MIN( M+1, N )
202 1 pfleura2
         KI = ( ( M-NX-1 ) / NB )*NB
203 1 pfleura2
         KK = MIN( M, KI+NB )
204 1 pfleura2
*
205 1 pfleura2
         DO 20 I = M - KK + KI + 1, M - KK + 1, -NB
206 1 pfleura2
            IB = MIN( M-I+1, NB )
207 1 pfleura2
*
208 1 pfleura2
*           Compute the TZ factorization of the current block
209 1 pfleura2
*           A(i:i+ib-1,i:n)
210 1 pfleura2
*
211 1 pfleura2
            CALL DLATRZ( IB, N-I+1, N-M, A( I, I ), LDA, TAU( I ),
212 1 pfleura2
     $                   WORK )
213 1 pfleura2
            IF( I.GT.1 ) THEN
214 1 pfleura2
*
215 1 pfleura2
*              Form the triangular factor of the block reflector
216 1 pfleura2
*              H = H(i+ib-1) . . . H(i+1) H(i)
217 1 pfleura2
*
218 1 pfleura2
               CALL DLARZT( 'Backward', 'Rowwise', N-M, IB, A( I, M1 ),
219 1 pfleura2
     $                      LDA, TAU( I ), WORK, LDWORK )
220 1 pfleura2
*
221 1 pfleura2
*              Apply H to A(1:i-1,i:n) from the right
222 1 pfleura2
*
223 1 pfleura2
               CALL DLARZB( 'Right', 'No transpose', 'Backward',
224 1 pfleura2
     $                      'Rowwise', I-1, N-I+1, IB, N-M, A( I, M1 ),
225 1 pfleura2
     $                      LDA, WORK, LDWORK, A( 1, I ), LDA,
226 1 pfleura2
     $                      WORK( IB+1 ), LDWORK )
227 1 pfleura2
            END IF
228 1 pfleura2
   20    CONTINUE
229 1 pfleura2
         MU = I + NB - 1
230 1 pfleura2
      ELSE
231 1 pfleura2
         MU = M
232 1 pfleura2
      END IF
233 1 pfleura2
*
234 1 pfleura2
*     Use unblocked code to factor the last or only block
235 1 pfleura2
*
236 1 pfleura2
      IF( MU.GT.0 )
237 1 pfleura2
     $   CALL DLATRZ( MU, N, N-M, A, LDA, TAU, WORK )
238 1 pfleura2
*
239 1 pfleura2
      WORK( 1 ) = LWKOPT
240 1 pfleura2
*
241 1 pfleura2
      RETURN
242 1 pfleura2
*
243 1 pfleura2
*     End of DTZRZF
244 1 pfleura2
*
245 1 pfleura2
      END