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

NAME

6       DORMR3  -  overwrites  the general real m by n matrix C with   Q * C if
7       SIDE = 'L' and TRANS = 'N', or   Q'* C if SIDE = 'L' and TRANS  =  'T',
8       or   C * Q if SIDE = 'R' and TRANS = 'N', or   C * Q' if SIDE = 'R' and
9       TRANS = 'T',
10

SYNOPSIS

12       SUBROUTINE DORMR3( SIDE, TRANS, M, N, K, L, A, LDA, TAU, C, LDC,  WORK,
13                          INFO )
14
15           CHARACTER      SIDE, TRANS
16
17           INTEGER        INFO, K, L, LDA, LDC, M, N
18
19           DOUBLE         PRECISION  A( LDA, * ), C( LDC, * ), TAU( * ), WORK(
20                          * )
21

PURPOSE

23       DORMR3 overwrites the general real m by n matrix C with where  Q  is  a
24       real  orthogonal  matrix defined as the product of k elementary reflec‐
25       tors
26             Q = H(1) H(2) . . . H(k)
27       as returned by DTZRZF. Q is of order m if SIDE = 'L' and of order n  if
28       SIDE = 'R'.
29

ARGUMENTS

31       SIDE    (input) CHARACTER*1
32               = 'L': apply Q or Q' from the Left
33               = 'R': apply Q or Q' from the Right
34
35       TRANS   (input) CHARACTER*1
36               = 'N': apply Q  (No transpose)
37               = 'T': apply Q' (Transpose)
38
39       M       (input) INTEGER
40               The number of rows of the matrix C. M >= 0.
41
42       N       (input) INTEGER
43               The number of columns of the matrix C. N >= 0.
44
45       K       (input) INTEGER
46               The  number  of elementary reflectors whose product defines the
47               matrix Q.  If SIDE = 'L', M >= K >= 0; if SIDE = 'R', N >= K >=
48               0.
49
50       L       (input) INTEGER
51               The number of columns of the matrix A containing the meaningful
52               part of the Householder reflectors.  If SIDE = 'L', M >=  L  >=
53               0, if SIDE = 'R', N >= L >= 0.
54
55       A       (input) DOUBLE PRECISION array, dimension
56               (LDA,M)  if SIDE = 'L', (LDA,N) if SIDE = 'R' The i-th row must
57               contain the vector which defines the elementary reflector H(i),
58               for  i = 1,2,...,k, as returned by DTZRZF in the last k rows of
59               its array argument  A.   A  is  modified  by  the  routine  but
60               restored on exit.
61
62       LDA     (input) INTEGER
63               The leading dimension of the array A. LDA >= max(1,K).
64
65       TAU     (input) DOUBLE PRECISION array, dimension (K)
66               TAU(i) must contain the scalar factor of the elementary reflec‐
67               tor H(i), as returned by DTZRZF.
68
69       C       (input/output) DOUBLE PRECISION array, dimension (LDC,N)
70               On entry, the m-by-n matrix C.  On exit, C  is  overwritten  by
71               Q*C or Q'*C or C*Q' or C*Q.
72
73       LDC     (input) INTEGER
74               The leading dimension of the array C. LDC >= max(1,M).
75
76       WORK    (workspace) DOUBLE PRECISION array, dimension
77               (N) if SIDE = 'L', (M) if SIDE = 'R'
78
79       INFO    (output) INTEGER
80               = 0: successful exit
81               < 0: if INFO = -i, the i-th argument had an illegal value
82

FURTHER DETAILS

84       Based on contributions by
85         A. Petitet, Computer Science Dept., Univ. of Tenn., Knoxville, USA
86
87
88
89 LAPACK routine (version 3.2)    November 2008                       DORMR3(1)
Impressum