1DORMRZ(1) LAPACK routine (version 3.2) DORMRZ(1)
2
3
4
6 DORMRZ - overwrites the general real M-by-N matrix C with SIDE = 'L'
7 SIDE = 'R' TRANS = 'N'
8
10 SUBROUTINE DORMRZ( SIDE, TRANS, M, N, K, L, A, LDA, TAU, C, LDC, WORK,
11 LWORK, INFO )
12
13 CHARACTER SIDE, TRANS
14
15 INTEGER INFO, K, L, LDA, LDC, LWORK, M, N
16
17 DOUBLE PRECISION A( LDA, * ), C( LDC, * ), TAU( * ), WORK(
18 * )
19
21 DORMRZ overwrites the general real M-by-N matrix C with TRANS = 'T':
22 Q**T * C C * Q**T
23 where Q is a real orthogonal matrix defined as the product of k elemen‐
24 tary reflectors
25 Q = H(1) H(2) . . . H(k)
26 as returned by DTZRZF. Q is of order M if SIDE = 'L' and of order N if
27 SIDE = 'R'.
28
30 SIDE (input) CHARACTER*1
31 = 'L': apply Q or Q**T from the Left;
32 = 'R': apply Q or Q**T from the Right.
33
34 TRANS (input) CHARACTER*1
35 = 'N': No transpose, apply Q;
36 = 'T': Transpose, apply Q**T.
37
38 M (input) INTEGER
39 The number of rows of the matrix C. M >= 0.
40
41 N (input) INTEGER
42 The number of columns of the matrix C. N >= 0.
43
44 K (input) INTEGER
45 The number of elementary reflectors whose product defines the
46 matrix Q. If SIDE = 'L', M >= K >= 0; if SIDE = 'R', N >= K >=
47 0.
48
49 L (input) INTEGER
50 The number of columns of the matrix A containing the meaningful
51 part of the Householder reflectors. If SIDE = 'L', M >= L >=
52 0, if SIDE = 'R', N >= L >= 0.
53
54 A (input) DOUBLE PRECISION array, dimension
55 (LDA,M) if SIDE = 'L', (LDA,N) if SIDE = 'R' The i-th row must
56 contain the vector which defines the elementary reflector H(i),
57 for i = 1,2,...,k, as returned by DTZRZF in the last k rows of
58 its array argument A. A is modified by the routine but
59 restored on exit.
60
61 LDA (input) INTEGER
62 The leading dimension of the array A. LDA >= max(1,K).
63
64 TAU (input) DOUBLE PRECISION array, dimension (K)
65 TAU(i) must contain the scalar factor of the elementary reflec‐
66 tor H(i), as returned by DTZRZF.
67
68 C (input/output) DOUBLE PRECISION array, dimension (LDC,N)
69 On entry, the M-by-N matrix C. On exit, C is overwritten by
70 Q*C or Q**H*C or C*Q**H or C*Q.
71
72 LDC (input) INTEGER
73 The leading dimension of the array C. LDC >= max(1,M).
74
75 WORK (workspace/output) DOUBLE PRECISION array, dimension
76 (MAX(1,LWORK))
77 On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
78
79 LWORK (input) INTEGER
80 The dimension of the array WORK. If SIDE = 'L', LWORK >=
81 max(1,N); if SIDE = 'R', LWORK >= max(1,M). For optimum per‐
82 formance LWORK >= N*NB if SIDE = 'L', and LWORK >= M*NB if SIDE
83 = 'R', where NB is the optimal blocksize. If LWORK = -1, then
84 a workspace query is assumed; the routine only calculates the
85 optimal size of the WORK array, returns this value as the first
86 entry of the WORK array, and no error message related to LWORK
87 is issued by XERBLA.
88
89 INFO (output) INTEGER
90 = 0: successful exit
91 < 0: if INFO = -i, the i-th argument had an illegal value
92
94 Based on contributions by
95 A. Petitet, Computer Science Dept., Univ. of Tenn., Knoxville, USA
96
97
98
99 LAPACK routine (version 3.2) November 2008 DORMRZ(1)