1DORMRQ(1) LAPACK routine (version 3.2) DORMRQ(1)
2
3
4
6 DORMRQ - overwrites the general real M-by-N matrix C with SIDE = 'L'
7 SIDE = 'R' TRANS = 'N'
8
10 SUBROUTINE DORMRQ( SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, WORK,
11 LWORK, INFO )
12
13 CHARACTER SIDE, TRANS
14
15 INTEGER INFO, K, LDA, LDC, LWORK, M, N
16
17 DOUBLE PRECISION A( LDA, * ), C( LDC, * ), TAU( * ), WORK(
18 * )
19
21 DORMRQ 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 DGERQF. 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 A (input) DOUBLE PRECISION array, dimension
50 (LDA,M) if SIDE = 'L', (LDA,N) if SIDE = 'R' The i-th row must
51 contain the vector which defines the elementary reflector H(i),
52 for i = 1,2,...,k, as returned by DGERQF in the last k rows of
53 its array argument A. A is modified by the routine but
54 restored on exit.
55
56 LDA (input) INTEGER
57 The leading dimension of the array A. LDA >= max(1,K).
58
59 TAU (input) DOUBLE PRECISION array, dimension (K)
60 TAU(i) must contain the scalar factor of the elementary reflec‐
61 tor H(i), as returned by DGERQF.
62
63 C (input/output) DOUBLE PRECISION array, dimension (LDC,N)
64 On entry, the M-by-N matrix C. On exit, C is overwritten by
65 Q*C or Q**T*C or C*Q**T or C*Q.
66
67 LDC (input) INTEGER
68 The leading dimension of the array C. LDC >= max(1,M).
69
70 WORK (workspace/output) DOUBLE PRECISION array, dimension
71 (MAX(1,LWORK))
72 On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
73
74 LWORK (input) INTEGER
75 The dimension of the array WORK. If SIDE = 'L', LWORK >=
76 max(1,N); if SIDE = 'R', LWORK >= max(1,M). For optimum per‐
77 formance LWORK >= N*NB if SIDE = 'L', and LWORK >= M*NB if SIDE
78 = 'R', where NB is the optimal blocksize. If LWORK = -1, then
79 a workspace query is assumed; the routine only calculates the
80 optimal size of the WORK array, returns this value as the first
81 entry of the WORK array, and no error message related to LWORK
82 is issued by XERBLA.
83
84 INFO (output) INTEGER
85 = 0: successful exit
86 < 0: if INFO = -i, the i-th argument had an illegal value
87
88
89
90 LAPACK routine (version 3.2) November 2008 DORMRQ(1)