LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ dormbr()

subroutine dormbr ( character  vect,
character  side,
character  trans,
integer  m,
integer  n,
integer  k,
double precision, dimension( lda, * )  a,
integer  lda,
double precision, dimension( * )  tau,
double precision, dimension( ldc, * )  c,
integer  ldc,
double precision, dimension( * )  work,
integer  lwork,
integer  info 
)

DORMBR

Download DORMBR + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 If VECT = 'Q', DORMBR overwrites the general real M-by-N matrix C
 with
                 SIDE = 'L'     SIDE = 'R'
 TRANS = 'N':      Q * C          C * Q
 TRANS = 'T':      Q**T * C       C * Q**T

 If VECT = 'P', DORMBR overwrites the general real M-by-N matrix C
 with
                 SIDE = 'L'     SIDE = 'R'
 TRANS = 'N':      P * C          C * P
 TRANS = 'T':      P**T * C       C * P**T

 Here Q and P**T are the orthogonal matrices determined by DGEBRD when
 reducing a real matrix A to bidiagonal form: A = Q * B * P**T. Q and
 P**T are defined as products of elementary reflectors H(i) and G(i)
 respectively.

 Let nq = m if SIDE = 'L' and nq = n if SIDE = 'R'. Thus nq is the
 order of the orthogonal matrix Q or P**T that is applied.

 If VECT = 'Q', A is assumed to have been an NQ-by-K matrix:
 if nq >= k, Q = H(1) H(2) . . . H(k);
 if nq < k, Q = H(1) H(2) . . . H(nq-1).

 If VECT = 'P', A is assumed to have been a K-by-NQ matrix:
 if k < nq, P = G(1) G(2) . . . G(k);
 if k >= nq, P = G(1) G(2) . . . G(nq-1).
Parameters
[in]VECT
          VECT is CHARACTER*1
          = 'Q': apply Q or Q**T;
          = 'P': apply P or P**T.
[in]SIDE
          SIDE is CHARACTER*1
          = 'L': apply Q, Q**T, P or P**T from the Left;
          = 'R': apply Q, Q**T, P or P**T from the Right.
[in]TRANS
          TRANS is CHARACTER*1
          = 'N':  No transpose, apply Q  or P;
          = 'T':  Transpose, apply Q**T or P**T.
[in]M
          M is INTEGER
          The number of rows of the matrix C. M >= 0.
[in]N
          N is INTEGER
          The number of columns of the matrix C. N >= 0.
[in]K
          K is INTEGER
          If VECT = 'Q', the number of columns in the original
          matrix reduced by DGEBRD.
          If VECT = 'P', the number of rows in the original
          matrix reduced by DGEBRD.
          K >= 0.
[in]A
          A is DOUBLE PRECISION array, dimension
                                (LDA,min(nq,K)) if VECT = 'Q'
                                (LDA,nq)        if VECT = 'P'
          The vectors which define the elementary reflectors H(i) and
          G(i), whose products determine the matrices Q and P, as
          returned by DGEBRD.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.
          If VECT = 'Q', LDA >= max(1,nq);
          if VECT = 'P', LDA >= max(1,min(nq,K)).
[in]TAU
          TAU is DOUBLE PRECISION array, dimension (min(nq,K))
          TAU(i) must contain the scalar factor of the elementary
          reflector H(i) or G(i) which determines Q or P, as returned
          by DGEBRD in the array argument TAUQ or TAUP.
[in,out]C
          C is DOUBLE PRECISION array, dimension (LDC,N)
          On entry, the M-by-N matrix C.
          On exit, C is overwritten by Q*C or Q**T*C or C*Q**T or C*Q
          or P*C or P**T*C or C*P or C*P**T.
[in]LDC
          LDC is INTEGER
          The leading dimension of the array C. LDC >= max(1,M).
[out]WORK
          WORK is DOUBLE PRECISION array, dimension (MAX(1,LWORK))
          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
[in]LWORK
          LWORK is INTEGER
          The dimension of the array WORK.
          If SIDE = 'L', LWORK >= max(1,N);
          if SIDE = 'R', LWORK >= max(1,M).
          For optimum performance LWORK >= N*NB if SIDE = 'L', and
          LWORK >= M*NB if SIDE = 'R', where NB is the optimal
          blocksize.

          If LWORK = -1, then a workspace query is assumed; the routine
          only calculates the optimal size of the WORK array, returns
          this value as the first entry of the WORK array, and no error
          message related to LWORK is issued by XERBLA.
[out]INFO
          INFO is INTEGER
          = 0:  successful exit
          < 0:  if INFO = -i, the i-th argument had an illegal value
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 193 of file dormbr.f.

195*
196* -- LAPACK computational routine --
197* -- LAPACK is a software package provided by Univ. of Tennessee, --
198* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
199*
200* .. Scalar Arguments ..
201 CHARACTER SIDE, TRANS, VECT
202 INTEGER INFO, K, LDA, LDC, LWORK, M, N
203* ..
204* .. Array Arguments ..
205 DOUBLE PRECISION A( LDA, * ), C( LDC, * ), TAU( * ), WORK( * )
206* ..
207*
208* =====================================================================
209*
210* .. Local Scalars ..
211 LOGICAL APPLYQ, LEFT, LQUERY, NOTRAN
212 CHARACTER TRANST
213 INTEGER I1, I2, IINFO, LWKOPT, MI, NB, NI, NQ, NW
214* ..
215* .. External Functions ..
216 LOGICAL LSAME
217 INTEGER ILAENV
218 EXTERNAL lsame, ilaenv
219* ..
220* .. External Subroutines ..
221 EXTERNAL dormlq, dormqr, xerbla
222* ..
223* .. Intrinsic Functions ..
224 INTRINSIC max, min
225* ..
226* .. Executable Statements ..
227*
228* Test the input arguments
229*
230 info = 0
231 applyq = lsame( vect, 'Q' )
232 left = lsame( side, 'L' )
233 notran = lsame( trans, 'N' )
234 lquery = ( lwork.EQ.-1 )
235*
236* NQ is the order of Q or P and NW is the minimum dimension of WORK
237*
238 IF( left ) THEN
239 nq = m
240 nw = max( 1, n )
241 ELSE
242 nq = n
243 nw = max( 1, m )
244 END IF
245 IF( .NOT.applyq .AND. .NOT.lsame( vect, 'P' ) ) THEN
246 info = -1
247 ELSE IF( .NOT.left .AND. .NOT.lsame( side, 'R' ) ) THEN
248 info = -2
249 ELSE IF( .NOT.notran .AND. .NOT.lsame( trans, 'T' ) ) THEN
250 info = -3
251 ELSE IF( m.LT.0 ) THEN
252 info = -4
253 ELSE IF( n.LT.0 ) THEN
254 info = -5
255 ELSE IF( k.LT.0 ) THEN
256 info = -6
257 ELSE IF( ( applyq .AND. lda.LT.max( 1, nq ) ) .OR.
258 $ ( .NOT.applyq .AND. lda.LT.max( 1, min( nq, k ) ) ) )
259 $ THEN
260 info = -8
261 ELSE IF( ldc.LT.max( 1, m ) ) THEN
262 info = -11
263 ELSE IF( lwork.LT.nw .AND. .NOT.lquery ) THEN
264 info = -13
265 END IF
266*
267 IF( info.EQ.0 ) THEN
268 IF( applyq ) THEN
269 IF( left ) THEN
270 nb = ilaenv( 1, 'DORMQR', side // trans, m-1, n, m-1,
271 $ -1 )
272 ELSE
273 nb = ilaenv( 1, 'DORMQR', side // trans, m, n-1, n-1,
274 $ -1 )
275 END IF
276 ELSE
277 IF( left ) THEN
278 nb = ilaenv( 1, 'DORMLQ', side // trans, m-1, n, m-1,
279 $ -1 )
280 ELSE
281 nb = ilaenv( 1, 'DORMLQ', side // trans, m, n-1, n-1,
282 $ -1 )
283 END IF
284 END IF
285 lwkopt = nw*nb
286 work( 1 ) = lwkopt
287 END IF
288*
289 IF( info.NE.0 ) THEN
290 CALL xerbla( 'DORMBR', -info )
291 RETURN
292 ELSE IF( lquery ) THEN
293 RETURN
294 END IF
295*
296* Quick return if possible
297*
298 work( 1 ) = 1
299 IF( m.EQ.0 .OR. n.EQ.0 )
300 $ RETURN
301*
302 IF( applyq ) THEN
303*
304* Apply Q
305*
306 IF( nq.GE.k ) THEN
307*
308* Q was determined by a call to DGEBRD with nq >= k
309*
310 CALL dormqr( side, trans, m, n, k, a, lda, tau, c, ldc,
311 $ work, lwork, iinfo )
312 ELSE IF( nq.GT.1 ) THEN
313*
314* Q was determined by a call to DGEBRD with nq < k
315*
316 IF( left ) THEN
317 mi = m - 1
318 ni = n
319 i1 = 2
320 i2 = 1
321 ELSE
322 mi = m
323 ni = n - 1
324 i1 = 1
325 i2 = 2
326 END IF
327 CALL dormqr( side, trans, mi, ni, nq-1, a( 2, 1 ), lda, tau,
328 $ c( i1, i2 ), ldc, work, lwork, iinfo )
329 END IF
330 ELSE
331*
332* Apply P
333*
334 IF( notran ) THEN
335 transt = 'T'
336 ELSE
337 transt = 'N'
338 END IF
339 IF( nq.GT.k ) THEN
340*
341* P was determined by a call to DGEBRD with nq > k
342*
343 CALL dormlq( side, transt, m, n, k, a, lda, tau, c, ldc,
344 $ work, lwork, iinfo )
345 ELSE IF( nq.GT.1 ) THEN
346*
347* P was determined by a call to DGEBRD with nq <= k
348*
349 IF( left ) THEN
350 mi = m - 1
351 ni = n
352 i1 = 2
353 i2 = 1
354 ELSE
355 mi = m
356 ni = n - 1
357 i1 = 1
358 i2 = 2
359 END IF
360 CALL dormlq( side, transt, mi, ni, nq-1, a( 1, 2 ), lda,
361 $ tau, c( i1, i2 ), ldc, work, lwork, iinfo )
362 END IF
363 END IF
364 work( 1 ) = lwkopt
365 RETURN
366*
367* End of DORMBR
368*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
integer function ilaenv(ispec, name, opts, n1, n2, n3, n4)
ILAENV
Definition ilaenv.f:162
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine dormlq(side, trans, m, n, k, a, lda, tau, c, ldc, work, lwork, info)
DORMLQ
Definition dormlq.f:167
subroutine dormqr(side, trans, m, n, k, a, lda, tau, c, ldc, work, lwork, info)
DORMQR
Definition dormqr.f:167
Here is the call graph for this function:
Here is the caller graph for this function: