KTH framework for Nek5000 toolboxes; testing version  0.0.1
dormbr.f
Go to the documentation of this file.
1  SUBROUTINE dormbr( VECT, SIDE, TRANS, M, N, K, A, LDA, TAU, C,
2  $ LDC, 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, VECT
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 * If VECT = 'Q', DORMBR overwrites the general real M-by-N matrix C
21 * with
22 * SIDE = 'L' SIDE = 'R'
23 * TRANS = 'N': Q * C C * Q
24 * TRANS = 'T': Q**T * C C * Q**T
25 *
26 * If VECT = 'P', DORMBR overwrites the general real M-by-N matrix C
27 * with
28 * SIDE = 'L' SIDE = 'R'
29 * TRANS = 'N': P * C C * P
30 * TRANS = 'T': P**T * C C * P**T
31 *
32 * Here Q and P**T are the orthogonal matrices determined by DGEBRD when
33 * reducing a real matrix A to bidiagonal form: A = Q * B * P**T. Q and
34 * P**T are defined as products of elementary reflectors H(i) and G(i)
35 * respectively.
36 *
37 * Let nq = m if SIDE = 'L' and nq = n if SIDE = 'R'. Thus nq is the
38 * order of the orthogonal matrix Q or P**T that is applied.
39 *
40 * If VECT = 'Q', A is assumed to have been an NQ-by-K matrix:
41 * if nq >= k, Q = H(1) H(2) . . . H(k);
42 * if nq < k, Q = H(1) H(2) . . . H(nq-1).
43 *
44 * If VECT = 'P', A is assumed to have been a K-by-NQ matrix:
45 * if k < nq, P = G(1) G(2) . . . G(k);
46 * if k >= nq, P = G(1) G(2) . . . G(nq-1).
47 *
48 * Arguments
49 * =========
50 *
51 * VECT (input) CHARACTER*1
52 * = 'Q': apply Q or Q**T;
53 * = 'P': apply P or P**T.
54 *
55 * SIDE (input) CHARACTER*1
56 * = 'L': apply Q, Q**T, P or P**T from the Left;
57 * = 'R': apply Q, Q**T, P or P**T from the Right.
58 *
59 * TRANS (input) CHARACTER*1
60 * = 'N': No transpose, apply Q or P;
61 * = 'T': Transpose, apply Q**T or P**T.
62 *
63 * M (input) INTEGER
64 * The number of rows of the matrix C. M >= 0.
65 *
66 * N (input) INTEGER
67 * The number of columns of the matrix C. N >= 0.
68 *
69 * K (input) INTEGER
70 * If VECT = 'Q', the number of columns in the original
71 * matrix reduced by DGEBRD.
72 * If VECT = 'P', the number of rows in the original
73 * matrix reduced by DGEBRD.
74 * K >= 0.
75 *
76 * A (input) DOUBLE PRECISION array, dimension
77 * (LDA,min(nq,K)) if VECT = 'Q'
78 * (LDA,nq) if VECT = 'P'
79 * The vectors which define the elementary reflectors H(i) and
80 * G(i), whose products determine the matrices Q and P, as
81 * returned by DGEBRD.
82 *
83 * LDA (input) INTEGER
84 * The leading dimension of the array A.
85 * If VECT = 'Q', LDA >= max(1,nq);
86 * if VECT = 'P', LDA >= max(1,min(nq,K)).
87 *
88 * TAU (input) DOUBLE PRECISION array, dimension (min(nq,K))
89 * TAU(i) must contain the scalar factor of the elementary
90 * reflector H(i) or G(i) which determines Q or P, as returned
91 * by DGEBRD in the array argument TAUQ or TAUP.
92 *
93 * C (input/output) DOUBLE PRECISION array, dimension (LDC,N)
94 * On entry, the M-by-N matrix C.
95 * On exit, C is overwritten by Q*C or Q**T*C or C*Q**T or C*Q
96 * or P*C or P**T*C or C*P or C*P**T.
97 *
98 * LDC (input) INTEGER
99 * The leading dimension of the array C. LDC >= max(1,M).
100 *
101 * WORK (workspace/output) DOUBLE PRECISION array, dimension (LWORK)
102 * On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
103 *
104 * LWORK (input) INTEGER
105 * The dimension of the array WORK.
106 * If SIDE = 'L', LWORK >= max(1,N);
107 * if SIDE = 'R', LWORK >= max(1,M).
108 * For optimum performance LWORK >= N*NB if SIDE = 'L', and
109 * LWORK >= M*NB if SIDE = 'R', where NB is the optimal
110 * blocksize.
111 *
112 * If LWORK = -1, then a workspace query is assumed; the routine
113 * only calculates the optimal size of the WORK array, returns
114 * this value as the first entry of the WORK array, and no error
115 * message related to LWORK is issued by XERBLA.
116 *
117 * INFO (output) INTEGER
118 * = 0: successful exit
119 * < 0: if INFO = -i, the i-th argument had an illegal value
120 *
121 * =====================================================================
122 *
123 * .. Local Scalars ..
124  LOGICAL APPLYQ, LEFT, LQUERY, NOTRAN
125  CHARACTER TRANST
126  INTEGER I1, I2, IINFO, LWKOPT, MI, NB, NI, NQ, NW
127 * ..
128 * .. External Functions ..
129  LOGICAL LSAME
130  INTEGER ILAENV
131  EXTERNAL lsame, ilaenv
132 * ..
133 * .. External Subroutines ..
134  EXTERNAL dormlq, dormqr, xerbla
135 * ..
136 * .. Intrinsic Functions ..
137  INTRINSIC max, min
138 * ..
139 * .. Executable Statements ..
140 *
141 * Test the input arguments
142 *
143  info = 0
144  applyq = lsame( vect, 'Q' )
145  left = lsame( side, 'L' )
146  notran = lsame( trans, 'N' )
147  lquery = ( lwork.EQ.-1 )
148 *
149 * NQ is the order of Q or P and NW is the minimum dimension of WORK
150 *
151  IF( left ) THEN
152  nq = m
153  nw = n
154  ELSE
155  nq = n
156  nw = m
157  END IF
158  IF( .NOT.applyq .AND. .NOT.lsame( vect, 'P' ) ) THEN
159  info = -1
160  ELSE IF( .NOT.left .AND. .NOT.lsame( side, 'R' ) ) THEN
161  info = -2
162  ELSE IF( .NOT.notran .AND. .NOT.lsame( trans, 'T' ) ) THEN
163  info = -3
164  ELSE IF( m.LT.0 ) THEN
165  info = -4
166  ELSE IF( n.LT.0 ) THEN
167  info = -5
168  ELSE IF( k.LT.0 ) THEN
169  info = -6
170  ELSE IF( ( applyq .AND. lda.LT.max( 1, nq ) ) .OR.
171  $ ( .NOT.applyq .AND. lda.LT.max( 1, min( nq, k ) ) ) )
172  $ THEN
173  info = -8
174  ELSE IF( ldc.LT.max( 1, m ) ) THEN
175  info = -11
176  ELSE IF( lwork.LT.max( 1, nw ) .AND. .NOT.lquery ) THEN
177  info = -13
178  END IF
179 *
180  IF( info.EQ.0 ) THEN
181  IF( applyq ) THEN
182  IF( left ) THEN
183  nb = ilaenv( 1, 'DORMQR', side // trans, m-1, n, m-1,
184  $ -1 )
185  ELSE
186  nb = ilaenv( 1, 'DORMQR', side // trans, m, n-1, n-1,
187  $ -1 )
188  END IF
189  ELSE
190  IF( left ) THEN
191  nb = ilaenv( 1, 'DORMLQ', side // trans, m-1, n, m-1,
192  $ -1 )
193  ELSE
194  nb = ilaenv( 1, 'DORMLQ', side // trans, m, n-1, n-1,
195  $ -1 )
196  END IF
197  END IF
198  lwkopt = max( 1, nw )*nb
199  work( 1 ) = lwkopt
200  END IF
201 *
202  IF( info.NE.0 ) THEN
203  CALL xerbla( 'DORMBR', -info )
204  RETURN
205  ELSE IF( lquery ) THEN
206  RETURN
207  END IF
208 *
209 * Quick return if possible
210 *
211  work( 1 ) = 1
212  IF( m.EQ.0 .OR. n.EQ.0 )
213  $ RETURN
214 *
215  IF( applyq ) THEN
216 *
217 * Apply Q
218 *
219  IF( nq.GE.k ) THEN
220 *
221 * Q was determined by a call to DGEBRD with nq >= k
222 *
223  CALL dormqr( side, trans, m, n, k, a, lda, tau, c, ldc,
224  $ work, lwork, iinfo )
225  ELSE IF( nq.GT.1 ) THEN
226 *
227 * Q was determined by a call to DGEBRD with nq < k
228 *
229  IF( left ) THEN
230  mi = m - 1
231  ni = n
232  i1 = 2
233  i2 = 1
234  ELSE
235  mi = m
236  ni = n - 1
237  i1 = 1
238  i2 = 2
239  END IF
240  CALL dormqr( side, trans, mi, ni, nq-1, a( 2, 1 ), lda, tau,
241  $ c( i1, i2 ), ldc, work, lwork, iinfo )
242  END IF
243  ELSE
244 *
245 * Apply P
246 *
247  IF( notran ) THEN
248  transt = 'T'
249  ELSE
250  transt = 'N'
251  END IF
252  IF( nq.GT.k ) THEN
253 *
254 * P was determined by a call to DGEBRD with nq > k
255 *
256  CALL dormlq( side, transt, m, n, k, a, lda, tau, c, ldc,
257  $ work, lwork, iinfo )
258  ELSE IF( nq.GT.1 ) THEN
259 *
260 * P was determined by a call to DGEBRD with nq <= k
261 *
262  IF( left ) THEN
263  mi = m - 1
264  ni = n
265  i1 = 2
266  i2 = 1
267  ELSE
268  mi = m
269  ni = n - 1
270  i1 = 1
271  i2 = 2
272  END IF
273  CALL dormlq( side, transt, mi, ni, nq-1, a( 1, 2 ), lda,
274  $ tau, c( i1, i2 ), ldc, work, lwork, iinfo )
275  END IF
276  END IF
277  work( 1 ) = lwkopt
278  RETURN
279 *
280 * End of DORMBR
281 *
282  END
subroutine dormbr(VECT, SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, WORK, LWORK, INFO)
Definition: dormbr.f:3
subroutine dormlq(SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, WORK, LWORK, INFO)
Definition: dormlq.f:3
subroutine dormqr(SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, WORK, LWORK, INFO)
Definition: dormqr.f:3
subroutine xerbla(SRNAME, INFO)
Definition: xerbla.f:2