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