KTH framework for Nek5000 toolboxes; testing version  0.0.1
dormlq.f
Go to the documentation of this file.
1  SUBROUTINE dormlq( SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC,
2  $ WORK, LWORK, INFO )
3 *
4 * -- LAPACK routine (version 3.0) --
5 * Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,
6 * Courant Institute, Argonne National Lab, and Rice University
7 * June 30, 1999
8 *
9 * .. Scalar Arguments ..
10  CHARACTER SIDE, TRANS
11  INTEGER INFO, K, LDA, LDC, LWORK, M, N
12 * ..
13 * .. Array Arguments ..
14  DOUBLE PRECISION A( LDA, * ), C( LDC, * ), TAU( * ), WORK( * )
15 * ..
16 *
17 * Purpose
18 * =======
19 *
20 * DORMLQ overwrites the general real M-by-N matrix C with
21 *
22 * SIDE = 'L' SIDE = 'R'
23 * TRANS = 'N': Q * C C * Q
24 * TRANS = 'T': Q**T * C C * Q**T
25 *
26 * where Q is a real orthogonal matrix defined as the product of k
27 * elementary reflectors
28 *
29 * Q = H(k) . . . H(2) H(1)
30 *
31 * as returned by DGELQF. Q is of order M if SIDE = 'L' and of order N
32 * if SIDE = 'R'.
33 *
34 * Arguments
35 * =========
36 *
37 * SIDE (input) CHARACTER*1
38 * = 'L': apply Q or Q**T from the Left;
39 * = 'R': apply Q or Q**T from the Right.
40 *
41 * TRANS (input) CHARACTER*1
42 * = 'N': No transpose, apply Q;
43 * = 'T': Transpose, apply Q**T.
44 *
45 * M (input) INTEGER
46 * The number of rows of the matrix C. M >= 0.
47 *
48 * N (input) INTEGER
49 * The number of columns of the matrix C. N >= 0.
50 *
51 * K (input) INTEGER
52 * The number of elementary reflectors whose product defines
53 * the matrix Q.
54 * If SIDE = 'L', M >= K >= 0;
55 * if SIDE = 'R', N >= K >= 0.
56 *
57 * A (input) DOUBLE PRECISION array, dimension
58 * (LDA,M) if SIDE = 'L',
59 * (LDA,N) if SIDE = 'R'
60 * The i-th row must contain the vector which defines the
61 * elementary reflector H(i), for i = 1,2,...,k, as returned by
62 * DGELQF in the first k rows of its array argument A.
63 * A is modified by the routine but restored on exit.
64 *
65 * LDA (input) INTEGER
66 * The leading dimension of the array A. LDA >= max(1,K).
67 *
68 * TAU (input) DOUBLE PRECISION array, dimension (K)
69 * TAU(i) must contain the scalar factor of the elementary
70 * reflector H(i), as returned by DGELQF.
71 *
72 * C (input/output) DOUBLE PRECISION array, dimension (LDC,N)
73 * On entry, the M-by-N matrix C.
74 * On exit, C is overwritten by Q*C or Q**T*C or C*Q**T or C*Q.
75 *
76 * LDC (input) INTEGER
77 * The leading dimension of the array C. LDC >= max(1,M).
78 *
79 * WORK (workspace/output) DOUBLE PRECISION array, dimension (LWORK)
80 * On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
81 *
82 * LWORK (input) INTEGER
83 * The dimension of the array WORK.
84 * If SIDE = 'L', LWORK >= max(1,N);
85 * if SIDE = 'R', LWORK >= max(1,M).
86 * For optimum performance LWORK >= N*NB if SIDE = 'L', and
87 * LWORK >= M*NB if SIDE = 'R', where NB is the optimal
88 * blocksize.
89 *
90 * If LWORK = -1, then a workspace query is assumed; the routine
91 * only calculates the optimal size of the WORK array, returns
92 * this value as the first entry of the WORK array, and no error
93 * message related to LWORK is issued by XERBLA.
94 *
95 * INFO (output) INTEGER
96 * = 0: successful exit
97 * < 0: if INFO = -i, the i-th argument had an illegal value
98 *
99 * =====================================================================
100 *
101 * .. Parameters ..
102  INTEGER NBMAX, LDT
103  parameter( nbmax = 64, ldt = nbmax+1 )
104 * ..
105 * .. Local Scalars ..
106  LOGICAL LEFT, LQUERY, NOTRAN
107  CHARACTER TRANST
108  INTEGER I, I1, I2, I3, IB, IC, IINFO, IWS, JC, LDWORK,
109  $ lwkopt, mi, nb, nbmin, ni, nq, nw
110 * ..
111 * .. Local Arrays ..
112  DOUBLE PRECISION T( LDT, NBMAX )
113 * ..
114 * .. External Functions ..
115  LOGICAL LSAME
116  INTEGER ILAENV
117  EXTERNAL lsame, ilaenv
118 * ..
119 * .. External Subroutines ..
120  EXTERNAL dlarfb, dlarft, dorml2, xerbla
121 * ..
122 * .. Intrinsic Functions ..
123  INTRINSIC max, min
124 * ..
125 * .. Executable Statements ..
126 *
127 * Test the input arguments
128 *
129  info = 0
130  left = lsame( side, 'L' )
131  notran = lsame( trans, 'N' )
132  lquery = ( lwork.EQ.-1 )
133 *
134 * NQ is the order of Q and NW is the minimum dimension of WORK
135 *
136  IF( left ) THEN
137  nq = m
138  nw = n
139  ELSE
140  nq = n
141  nw = m
142  END IF
143  IF( .NOT.left .AND. .NOT.lsame( side, 'R' ) ) THEN
144  info = -1
145  ELSE IF( .NOT.notran .AND. .NOT.lsame( trans, 'T' ) ) THEN
146  info = -2
147  ELSE IF( m.LT.0 ) THEN
148  info = -3
149  ELSE IF( n.LT.0 ) THEN
150  info = -4
151  ELSE IF( k.LT.0 .OR. k.GT.nq ) THEN
152  info = -5
153  ELSE IF( lda.LT.max( 1, k ) ) THEN
154  info = -7
155  ELSE IF( ldc.LT.max( 1, m ) ) THEN
156  info = -10
157  ELSE IF( lwork.LT.max( 1, nw ) .AND. .NOT.lquery ) THEN
158  info = -12
159  END IF
160 *
161  IF( info.EQ.0 ) THEN
162 *
163 * Determine the block size. NB may be at most NBMAX, where NBMAX
164 * is used to define the local array T.
165 *
166  nb = min( nbmax, ilaenv( 1, 'DORMLQ', side // trans, m, n, k,
167  $ -1 ) )
168  lwkopt = max( 1, nw )*nb
169  work( 1 ) = lwkopt
170  END IF
171 *
172  IF( info.NE.0 ) THEN
173  CALL xerbla( 'DORMLQ', -info )
174  RETURN
175  ELSE IF( lquery ) THEN
176  RETURN
177  END IF
178 *
179 * Quick return if possible
180 *
181  IF( m.EQ.0 .OR. n.EQ.0 .OR. k.EQ.0 ) THEN
182  work( 1 ) = 1
183  RETURN
184  END IF
185 *
186  nbmin = 2
187  ldwork = nw
188  IF( nb.GT.1 .AND. nb.LT.k ) THEN
189  iws = nw*nb
190  IF( lwork.LT.iws ) THEN
191  nb = lwork / ldwork
192  nbmin = max( 2, ilaenv( 2, 'DORMLQ', side // trans, m, n, k,
193  $ -1 ) )
194  END IF
195  ELSE
196  iws = nw
197  END IF
198 *
199  IF( nb.LT.nbmin .OR. nb.GE.k ) THEN
200 *
201 * Use unblocked code
202 *
203  CALL dorml2( side, trans, m, n, k, a, lda, tau, c, ldc, work,
204  $ iinfo )
205  ELSE
206 *
207 * Use blocked code
208 *
209  IF( ( left .AND. notran ) .OR.
210  $ ( .NOT.left .AND. .NOT.notran ) ) THEN
211  i1 = 1
212  i2 = k
213  i3 = nb
214  ELSE
215  i1 = ( ( k-1 ) / nb )*nb + 1
216  i2 = 1
217  i3 = -nb
218  END IF
219 *
220  IF( left ) THEN
221  ni = n
222  jc = 1
223  ELSE
224  mi = m
225  ic = 1
226  END IF
227 *
228  IF( notran ) THEN
229  transt = 'T'
230  ELSE
231  transt = 'N'
232  END IF
233 *
234  DO 10 i = i1, i2, i3
235  ib = min( nb, k-i+1 )
236 *
237 * Form the triangular factor of the block reflector
238 * H = H(i) H(i+1) . . . H(i+ib-1)
239 *
240  CALL dlarft( 'Forward', 'Rowwise', nq-i+1, ib, a( i, i ),
241  $ lda, tau( i ), t, ldt )
242  IF( left ) THEN
243 *
244 * H or H' is applied to C(i:m,1:n)
245 *
246  mi = m - i + 1
247  ic = i
248  ELSE
249 *
250 * H or H' is applied to C(1:m,i:n)
251 *
252  ni = n - i + 1
253  jc = i
254  END IF
255 *
256 * Apply H or H'
257 *
258  CALL dlarfb( side, transt, 'Forward', 'Rowwise', mi, ni, ib,
259  $ a( i, i ), lda, t, ldt, c( ic, jc ), ldc, work,
260  $ ldwork )
261  10 CONTINUE
262  END IF
263  work( 1 ) = lwkopt
264  RETURN
265 *
266 * End of DORMLQ
267 *
268  END
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 dorml2(SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, WORK, INFO)
Definition: dorml2.f:3
subroutine dormlq(SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, WORK, LWORK, INFO)
Definition: dormlq.f:3
subroutine xerbla(SRNAME, INFO)
Definition: xerbla.f:2