1DORMHR(1) LAPACK routine (version 3.1) DORMHR(1)
2
3
4
6 DORMHR - the general real M-by-N matrix C with SIDE = 'L' SIDE = 'R'
7 TRANS = 'N'
8
10 SUBROUTINE DORMHR( SIDE, TRANS, M, N, ILO, IHI, A, LDA, TAU, C, LDC,
11 WORK, LWORK, INFO )
12
13 CHARACTER SIDE, TRANS
14
15 INTEGER IHI, ILO, INFO, LDA, LDC, LWORK, M, N
16
17 DOUBLE PRECISION A( LDA, * ), C( LDC, * ), TAU( * ), WORK(
18 * )
19
21 DORMHR overwrites the general real M-by-N matrix C with TRANS = 'T':
22 Q**T * C C * Q**T
23
24 where Q is a real orthogonal matrix of order nq, with nq = m if SIDE =
25 'L' and nq = n if SIDE = 'R'. Q is defined as the product of IHI-ILO
26 elementary reflectors, as returned by DGEHRD:
27
28 Q = H(ilo) H(ilo+1) . . . H(ihi-1).
29
30
32 SIDE (input) CHARACTER*1
33 = 'L': apply Q or Q**T from the Left;
34 = 'R': apply Q or Q**T from the Right.
35
36 TRANS (input) CHARACTER*1
37 = 'N': No transpose, apply Q;
38 = 'T': Transpose, apply Q**T.
39
40 M (input) INTEGER
41 The number of rows of the matrix C. M >= 0.
42
43 N (input) INTEGER
44 The number of columns of the matrix C. N >= 0.
45
46 ILO (input) INTEGER
47 IHI (input) INTEGER ILO and IHI must have the same values
48 as in the previous call of DGEHRD. Q is equal to the unit
49 matrix except in the submatrix Q(ilo+1:ihi,ilo+1:ihi). If SIDE
50 = 'L', then 1 <= ILO <= IHI <= M, if M > 0, and ILO = 1 and IHI
51 = 0, if M = 0; if SIDE = 'R', then 1 <= ILO <= IHI <= N, if N >
52 0, and ILO = 1 and IHI = 0, if N = 0.
53
54 A (input) DOUBLE PRECISION array, dimension
55 (LDA,M) if SIDE = 'L' (LDA,N) if SIDE = 'R' The vectors which
56 define the elementary reflectors, as returned by DGEHRD.
57
58 LDA (input) INTEGER
59 The leading dimension of the array A. LDA >= max(1,M) if SIDE
60 = 'L'; LDA >= max(1,N) if SIDE = 'R'.
61
62 TAU (input) DOUBLE PRECISION array, dimension
63 (M-1) if SIDE = 'L' (N-1) if SIDE = 'R' TAU(i) must contain the
64 scalar factor of the elementary reflector H(i), as returned by
65 DGEHRD.
66
67 C (input/output) DOUBLE PRECISION array, dimension (LDC,N)
68 On entry, the M-by-N matrix C. On exit, C is overwritten by
69 Q*C or Q**T*C or C*Q**T or C*Q.
70
71 LDC (input) INTEGER
72 The leading dimension of the array C. LDC >= max(1,M).
73
74 WORK (workspace/output) DOUBLE PRECISION array, dimension
75 (MAX(1,LWORK))
76 On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
77
78 LWORK (input) INTEGER
79 The dimension of the array WORK. If SIDE = 'L', LWORK >=
80 max(1,N); if SIDE = 'R', LWORK >= max(1,M). For optimum per‐
81 formance LWORK >= N*NB if SIDE = 'L', and LWORK >= M*NB if SIDE
82 = 'R', where NB is the optimal blocksize.
83
84 If LWORK = -1, then a workspace query is assumed; the routine
85 only calculates the optimal size of the WORK array, returns
86 this value as the first entry of the WORK array, and no error
87 message related to LWORK 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
93
94
95 LAPACK routine (version 3.1) November 2006 DORMHR(1)