Statistiques
| Révision :

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

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

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