KTH framework for Nek5000 toolboxes; testing version  0.0.1
dgeqrf.f
Go to the documentation of this file.
1  SUBROUTINE dgeqrf( M, N, A, LDA, TAU, WORK, LWORK, INFO )
2 *
3 * -- LAPACK routine (version 3.0) --
4 * Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,
5 * Courant Institute, Argonne National Lab, and Rice University
6 * June 30, 1999
7 *
8 * .. Scalar Arguments ..
9  INTEGER INFO, LDA, LWORK, M, N
10 * ..
11 * .. Array Arguments ..
12  DOUBLE PRECISION A( LDA, * ), TAU( * ), WORK( * )
13 * ..
14 *
15 * Purpose
16 * =======
17 *
18 * DGEQRF computes a QR factorization of a real M-by-N matrix A:
19 * A = Q * R.
20 *
21 * Arguments
22 * =========
23 *
24 * M (input) INTEGER
25 * The number of rows of the matrix A. M >= 0.
26 *
27 * N (input) INTEGER
28 * The number of columns of the matrix A. N >= 0.
29 *
30 * A (input/output) DOUBLE PRECISION array, dimension (LDA,N)
31 * On entry, the M-by-N matrix A.
32 * On exit, the elements on and above the diagonal of the array
33 * contain the min(M,N)-by-N upper trapezoidal matrix R (R is
34 * upper triangular if m >= n); the elements below the diagonal,
35 * with the array TAU, represent the orthogonal matrix Q as a
36 * product of min(m,n) elementary reflectors (see Further
37 * Details).
38 *
39 * LDA (input) INTEGER
40 * The leading dimension of the array A. LDA >= max(1,M).
41 *
42 * TAU (output) DOUBLE PRECISION array, dimension (min(M,N))
43 * The scalar factors of the elementary reflectors (see Further
44 * Details).
45 *
46 * WORK (workspace/output) DOUBLE PRECISION array, dimension (LWORK)
47 * On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
48 *
49 * LWORK (input) INTEGER
50 * The dimension of the array WORK. LWORK >= max(1,N).
51 * For optimum performance LWORK >= N*NB, where NB is
52 * the optimal blocksize.
53 *
54 * If LWORK = -1, then a workspace query is assumed; the routine
55 * only calculates the optimal size of the WORK array, returns
56 * this value as the first entry of the WORK array, and no error
57 * message related to LWORK is issued by XERBLA.
58 *
59 * INFO (output) INTEGER
60 * = 0: successful exit
61 * < 0: if INFO = -i, the i-th argument had an illegal value
62 *
63 * Further Details
64 * ===============
65 *
66 * The matrix Q is represented as a product of elementary reflectors
67 *
68 * Q = H(1) H(2) . . . H(k), where k = min(m,n).
69 *
70 * Each H(i) has the form
71 *
72 * H(i) = I - tau * v * v'
73 *
74 * where tau is a real scalar, and v is a real vector with
75 * v(1:i-1) = 0 and v(i) = 1; v(i+1:m) is stored on exit in A(i+1:m,i),
76 * and tau in TAU(i).
77 *
78 * =====================================================================
79 *
80 * .. Local Scalars ..
81  LOGICAL LQUERY
82  INTEGER I, IB, IINFO, IWS, K, LDWORK, LWKOPT, NB,
83  $ NBMIN, NX
84 * ..
85 * .. External Subroutines ..
86  EXTERNAL dgeqr2, dlarfb, dlarft, xerbla
87 * ..
88 * .. Intrinsic Functions ..
89  INTRINSIC max, min
90 * ..
91 * .. External Functions ..
92  INTEGER ILAENV
93  EXTERNAL ilaenv
94 * ..
95 * .. Executable Statements ..
96 *
97 * Test the input arguments
98 *
99  info = 0
100  nb = ilaenv( 1, 'DGEQRF', ' ', m, n, -1, -1 )
101  lwkopt = n*nb
102  work( 1 ) = lwkopt
103  lquery = ( lwork.EQ.-1 )
104  IF( m.LT.0 ) THEN
105  info = -1
106  ELSE IF( n.LT.0 ) THEN
107  info = -2
108  ELSE IF( lda.LT.max( 1, m ) ) THEN
109  info = -4
110  ELSE IF( lwork.LT.max( 1, n ) .AND. .NOT.lquery ) THEN
111  info = -7
112  END IF
113  IF( info.NE.0 ) THEN
114  CALL xerbla( 'DGEQRF', -info )
115  RETURN
116  ELSE IF( lquery ) THEN
117  RETURN
118  END IF
119 *
120 * Quick return if possible
121 *
122  k = min( m, n )
123  IF( k.EQ.0 ) THEN
124  work( 1 ) = 1
125  RETURN
126  END IF
127 *
128  nbmin = 2
129  nx = 0
130  iws = n
131  IF( nb.GT.1 .AND. nb.LT.k ) THEN
132 *
133 * Determine when to cross over from blocked to unblocked code.
134 *
135  nx = max( 0, ilaenv( 3, 'DGEQRF', ' ', m, n, -1, -1 ) )
136  IF( nx.LT.k ) THEN
137 *
138 * Determine if workspace is large enough for blocked code.
139 *
140  ldwork = n
141  iws = ldwork*nb
142  IF( lwork.LT.iws ) THEN
143 *
144 * Not enough workspace to use optimal NB: reduce NB and
145 * determine the minimum value of NB.
146 *
147  nb = lwork / ldwork
148  nbmin = max( 2, ilaenv( 2, 'DGEQRF', ' ', m, n, -1,
149  $ -1 ) )
150  END IF
151  END IF
152  END IF
153 *
154  IF( nb.GE.nbmin .AND. nb.LT.k .AND. nx.LT.k ) THEN
155 *
156 * Use blocked code initially
157 *
158  DO 10 i = 1, k - nx, nb
159  ib = min( k-i+1, nb )
160 *
161 * Compute the QR factorization of the current block
162 * A(i:m,i:i+ib-1)
163 *
164  CALL dgeqr2( m-i+1, ib, a( i, i ), lda, tau( i ), work,
165  $ iinfo )
166  IF( i+ib.LE.n ) THEN
167 *
168 * Form the triangular factor of the block reflector
169 * H = H(i) H(i+1) . . . H(i+ib-1)
170 *
171  CALL dlarft( 'Forward', 'Columnwise', m-i+1, ib,
172  $ a( i, i ), lda, tau( i ), work, ldwork )
173 *
174 * Apply H' to A(i:m,i+ib:n) from the left
175 *
176  CALL dlarfb( 'Left', 'Transpose', 'Forward',
177  $ 'Columnwise', m-i+1, n-i-ib+1, ib,
178  $ a( i, i ), lda, work, ldwork, a( i, i+ib ),
179  $ lda, work( ib+1 ), ldwork )
180  END IF
181  10 CONTINUE
182  ELSE
183  i = 1
184  END IF
185 *
186 * Use unblocked code to factor the last or only block.
187 *
188  IF( i.LE.k )
189  $ CALL dgeqr2( m-i+1, n-i+1, a( i, i ), lda, tau( i ), work,
190  $ iinfo )
191 *
192  work( 1 ) = iws
193  RETURN
194 *
195 * End of DGEQRF
196 *
197  END
subroutine dgeqr2(M, N, A, LDA, TAU, WORK, INFO)
Definition: dgeqr2.f:2
subroutine dgeqrf(M, N, A, LDA, TAU, WORK, LWORK, INFO)
Definition: dgeqrf.f:2
subroutine dlarfb(SIDE, TRANS, DIRECT, STOREV, M, N, K, V, LDV, T, LDT, C, LDC, WORK, LDWORK)
Definition: dlarfb.f:3
subroutine dlarft(DIRECT, STOREV, N, K, V, LDV, TAU, T, LDT)
Definition: dlarft.f:2
subroutine xerbla(SRNAME, INFO)
Definition: xerbla.f:2