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

NAME

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

SYNOPSIS

10       SUBROUTINE SORMBR( 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           REAL           A( LDA, * ), C( LDC, * ), TAU( * ), WORK( * )
18

PURPOSE

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

ARGUMENTS

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