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