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

NAME

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

ARGUMENTS

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