1DORMBR(1)                LAPACK routine (version 3.2)                DORMBR(1)
2
3
4

NAME

6       DORMBR - VECT = 'Q', DORMBR overwrites the general real M-by-N matrix C
7       with  SIDE = 'L' SIDE = 'R' TRANS = 'N'
8

SYNOPSIS

10       SUBROUTINE DORMBR( VECT, SIDE, TRANS, M, N, K, A,  LDA,  TAU,  C,  LDC,
11                          WORK, LWORK, INFO )
12
13           CHARACTER      SIDE, TRANS, VECT
14
15           INTEGER        INFO, K, LDA, LDC, LWORK, M, N
16
17           DOUBLE         PRECISION  A( LDA, * ), C( LDC, * ), TAU( * ), WORK(
18                          * )
19

PURPOSE

21       If VECT = 'Q', DORMBR overwrites the general real M-by-N matrix C with
22                       SIDE = 'L'     SIDE = 'R'  TRANS  =  'N':       Q  *  C
23       C * Q TRANS = 'T':      Q**T * C       C * Q**T
24       If VECT = 'P', DORMBR overwrites the general real M-by-N matrix C with
25                       SIDE = 'L'     SIDE = 'R'
26       TRANS = 'N':      P * C          C * P
27       TRANS = 'T':      P**T * C       C * P**T
28       Here  Q  and P**T are the orthogonal matrices determined by DGEBRD when
29       reducing a real matrix A to bidiagonal form: A = Q * B *  P**T.  Q  and
30       P**T  are  defined  as  products of elementary reflectors H(i) and G(i)
31       respectively.
32       Let nq = m if SIDE = 'L' and nq = n if SIDE = 'R'. Thus nq is the order
33       of  the  orthogonal matrix Q or P**T that is applied.  If VECT = 'Q', A
34       is assumed to have been an NQ-by-K matrix: if nq >= k, Q = H(1) H(2)  .
35       . . H(k);
36       if nq < k, Q = H(1) H(2) . . . H(nq-1).
37       If VECT = 'P', A is assumed to have been a K-by-NQ matrix: if k < nq, P
38       = G(1) G(2) . . . G(k);
39       if k >= nq, P = G(1) G(2) . . . G(nq-1).
40

ARGUMENTS

42       VECT    (input) CHARACTER*1
43               = 'Q': apply Q or Q**T;
44               = 'P': apply P or P**T.
45
46       SIDE    (input) CHARACTER*1
47               = 'L': apply Q, Q**T, P or P**T from the Left;
48               = 'R': apply Q, Q**T, P or P**T from the Right.
49
50       TRANS   (input) CHARACTER*1
51               = 'N':  No transpose, apply Q  or P;
52               = 'T':  Transpose, apply Q**T or P**T.
53
54       M       (input) INTEGER
55               The number of rows of the matrix C. M >= 0.
56
57       N       (input) INTEGER
58               The number of columns of the matrix C. N >= 0.
59
60       K       (input) INTEGER
61               If VECT = 'Q', the number of columns  in  the  original  matrix
62               reduced  by  DGEBRD.   If VECT = 'P', the number of rows in the
63               original matrix reduced by DGEBRD.  K >= 0.
64
65       A       (input) DOUBLE PRECISION array, dimension
66               (LDA,min(nq,K)) if VECT = 'Q' (LDA,nq)        if VECT = 'P' The
67               vectors  which  define the elementary reflectors H(i) and G(i),
68               whose products determine the matrices Q and P, as  returned  by
69               DGEBRD.
70
71       LDA     (input) INTEGER
72               The  leading  dimension  of the array A.  If VECT = 'Q', LDA >=
73               max(1,nq); if VECT = 'P', LDA >= max(1,min(nq,K)).
74
75       TAU     (input) DOUBLE PRECISION array, dimension (min(nq,K))
76               TAU(i) must contain the scalar factor of the elementary reflec‐
77               tor H(i) or G(i) which determines Q or P, as returned by DGEBRD
78               in the array argument TAUQ or TAUP.
79
80       C       (input/output) DOUBLE PRECISION array, dimension (LDC,N)
81               On entry, the M-by-N matrix C.  On exit, C  is  overwritten  by
82               Q*C  or  Q**T*C  or  C*Q**T  or  C*Q or P*C or P**T*C or C*P or
83               C*P**T.
84
85       LDC     (input) INTEGER
86               The leading dimension of the array C. LDC >= max(1,M).
87
88       WORK      (workspace/output)   DOUBLE   PRECISION   array,    dimension
89       (MAX(1,LWORK))
90               On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
91
92       LWORK   (input) INTEGER
93               The  dimension  of  the  array  WORK.   If SIDE = 'L', LWORK >=
94               max(1,N); if SIDE = 'R', LWORK >= max(1,M).  For  optimum  per‐
95               formance LWORK >= N*NB if SIDE = 'L', and LWORK >= M*NB if SIDE
96               = 'R', where NB is the optimal blocksize.  If LWORK = -1,  then
97               a  workspace  query is assumed; the routine only calculates the
98               optimal size of the WORK array, returns this value as the first
99               entry  of the WORK array, and no error message related to LWORK
100               is issued by XERBLA.
101
102       INFO    (output) INTEGER
103               = 0:  successful exit
104               < 0:  if INFO = -i, the i-th argument had an illegal value
105
106
107
108 LAPACK routine (version 3.2)    November 2008                       DORMBR(1)
Impressum