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

NAME

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

ARGUMENTS

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