Statistiques
| Révision :

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

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

1 1 pfleura2
      SUBROUTINE DGEQR2( M, N, A, LDA, TAU, WORK, INFO )
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            INFO, 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
*  DGEQR2 computes a QR factorization of a real m by n matrix A:
19 1 pfleura2
*  A = Q * R.
20 1 pfleura2
*
21 1 pfleura2
*  Arguments
22 1 pfleura2
*  =========
23 1 pfleura2
*
24 1 pfleura2
*  M       (input) INTEGER
25 1 pfleura2
*          The number of rows of the matrix A.  M >= 0.
26 1 pfleura2
*
27 1 pfleura2
*  N       (input) INTEGER
28 1 pfleura2
*          The number of columns of the matrix A.  N >= 0.
29 1 pfleura2
*
30 1 pfleura2
*  A       (input/output) DOUBLE PRECISION array, dimension (LDA,N)
31 1 pfleura2
*          On entry, the m by n matrix A.
32 1 pfleura2
*          On exit, the elements on and above the diagonal of the array
33 1 pfleura2
*          contain the min(m,n) by n upper trapezoidal matrix R (R is
34 1 pfleura2
*          upper triangular if m >= n); the elements below the diagonal,
35 1 pfleura2
*          with the array TAU, represent the orthogonal matrix Q as a
36 1 pfleura2
*          product of elementary reflectors (see Further Details).
37 1 pfleura2
*
38 1 pfleura2
*  LDA     (input) INTEGER
39 1 pfleura2
*          The leading dimension of the array A.  LDA >= max(1,M).
40 1 pfleura2
*
41 1 pfleura2
*  TAU     (output) DOUBLE PRECISION array, dimension (min(M,N))
42 1 pfleura2
*          The scalar factors of the elementary reflectors (see Further
43 1 pfleura2
*          Details).
44 1 pfleura2
*
45 1 pfleura2
*  WORK    (workspace) DOUBLE PRECISION array, dimension (N)
46 1 pfleura2
*
47 1 pfleura2
*  INFO    (output) INTEGER
48 1 pfleura2
*          = 0: successful exit
49 1 pfleura2
*          < 0: if INFO = -i, the i-th argument had an illegal value
50 1 pfleura2
*
51 1 pfleura2
*  Further Details
52 1 pfleura2
*  ===============
53 1 pfleura2
*
54 1 pfleura2
*  The matrix Q is represented as a product of elementary reflectors
55 1 pfleura2
*
56 1 pfleura2
*     Q = H(1) H(2) . . . H(k), where k = min(m,n).
57 1 pfleura2
*
58 1 pfleura2
*  Each H(i) has the form
59 1 pfleura2
*
60 1 pfleura2
*     H(i) = I - tau * v * v'
61 1 pfleura2
*
62 1 pfleura2
*  where tau is a real scalar, and v is a real vector with
63 1 pfleura2
*  v(1:i-1) = 0 and v(i) = 1; v(i+1:m) is stored on exit in A(i+1:m,i),
64 1 pfleura2
*  and tau in TAU(i).
65 1 pfleura2
*
66 1 pfleura2
*  =====================================================================
67 1 pfleura2
*
68 1 pfleura2
*     .. Parameters ..
69 1 pfleura2
      DOUBLE PRECISION   ONE
70 1 pfleura2
      PARAMETER          ( ONE = 1.0D+0 )
71 1 pfleura2
*     ..
72 1 pfleura2
*     .. Local Scalars ..
73 1 pfleura2
      INTEGER            I, K
74 1 pfleura2
      DOUBLE PRECISION   AII
75 1 pfleura2
*     ..
76 1 pfleura2
*     .. External Subroutines ..
77 1 pfleura2
      EXTERNAL           DLARF, DLARFG, XERBLA
78 1 pfleura2
*     ..
79 1 pfleura2
*     .. Intrinsic Functions ..
80 1 pfleura2
      INTRINSIC          MAX, MIN
81 1 pfleura2
*     ..
82 1 pfleura2
*     .. Executable Statements ..
83 1 pfleura2
*
84 1 pfleura2
*     Test the input arguments
85 1 pfleura2
*
86 1 pfleura2
      INFO = 0
87 1 pfleura2
      IF( M.LT.0 ) THEN
88 1 pfleura2
         INFO = -1
89 1 pfleura2
      ELSE IF( N.LT.0 ) THEN
90 1 pfleura2
         INFO = -2
91 1 pfleura2
      ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
92 1 pfleura2
         INFO = -4
93 1 pfleura2
      END IF
94 1 pfleura2
      IF( INFO.NE.0 ) THEN
95 1 pfleura2
         CALL XERBLA( 'DGEQR2', -INFO )
96 1 pfleura2
         RETURN
97 1 pfleura2
      END IF
98 1 pfleura2
*
99 1 pfleura2
      K = MIN( M, N )
100 1 pfleura2
*
101 1 pfleura2
      DO 10 I = 1, K
102 1 pfleura2
*
103 1 pfleura2
*        Generate elementary reflector H(i) to annihilate A(i+1:m,i)
104 1 pfleura2
*
105 1 pfleura2
         CALL DLARFG( M-I+1, A( I, I ), A( MIN( I+1, M ), I ), 1,
106 1 pfleura2
     $                TAU( I ) )
107 1 pfleura2
         IF( I.LT.N ) THEN
108 1 pfleura2
*
109 1 pfleura2
*           Apply H(i) to A(i:m,i+1:n) from the left
110 1 pfleura2
*
111 1 pfleura2
            AII = A( I, I )
112 1 pfleura2
            A( I, I ) = ONE
113 1 pfleura2
            CALL DLARF( 'Left', M-I+1, N-I, A( I, I ), 1, TAU( I ),
114 1 pfleura2
     $                  A( I, I+1 ), LDA, WORK )
115 1 pfleura2
            A( I, I ) = AII
116 1 pfleura2
         END IF
117 1 pfleura2
   10 CONTINUE
118 1 pfleura2
      RETURN
119 1 pfleura2
*
120 1 pfleura2
*     End of DGEQR2
121 1 pfleura2
*
122 1 pfleura2
      END