1 SUBROUTINE ZUNMR3( SIDE, TRANS, M, N, K, L, A, LDA, TAU, C, LDC,
2 $ WORK, INFO )
3 *
4 * -- LAPACK routine (version 3.3.1) --
5 * -- LAPACK is a software package provided by Univ. of Tennessee, --
6 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
7 * -- April 2011 --
8 *
9 * .. Scalar Arguments ..
10 CHARACTER SIDE, TRANS
11 INTEGER INFO, K, L, LDA, LDC, M, N
12 * ..
13 * .. Array Arguments ..
14 COMPLEX*16 A( LDA, * ), C( LDC, * ), TAU( * ), WORK( * )
15 * ..
16 *
17 * Purpose
18 * =======
19 *
20 * ZUNMR3 overwrites the general complex m by n matrix C with
21 *
22 * Q * C if SIDE = 'L' and TRANS = 'N', or
23 *
24 * Q**H* C if SIDE = 'L' and TRANS = 'C', or
25 *
26 * C * Q if SIDE = 'R' and TRANS = 'N', or
27 *
28 * C * Q**H if SIDE = 'R' and TRANS = 'C',
29 *
30 * where Q is a complex unitary matrix defined as the product of k
31 * elementary reflectors
32 *
33 * Q = H(1) H(2) . . . H(k)
34 *
35 * as returned by ZTZRZF. Q is of order m if SIDE = 'L' and of order n
36 * if SIDE = 'R'.
37 *
38 * Arguments
39 * =========
40 *
41 * SIDE (input) CHARACTER*1
42 * = 'L': apply Q or Q**H from the Left
43 * = 'R': apply Q or Q**H from the Right
44 *
45 * TRANS (input) CHARACTER*1
46 * = 'N': apply Q (No transpose)
47 * = 'C': apply Q**H (Conjugate transpose)
48 *
49 * M (input) INTEGER
50 * The number of rows of the matrix C. M >= 0.
51 *
52 * N (input) INTEGER
53 * The number of columns of the matrix C. N >= 0.
54 *
55 * K (input) INTEGER
56 * The number of elementary reflectors whose product defines
57 * the matrix Q.
58 * If SIDE = 'L', M >= K >= 0;
59 * if SIDE = 'R', N >= K >= 0.
60 *
61 * L (input) INTEGER
62 * The number of columns of the matrix A containing
63 * the meaningful part of the Householder reflectors.
64 * If SIDE = 'L', M >= L >= 0, if SIDE = 'R', N >= L >= 0.
65 *
66 * A (input) COMPLEX*16 array, dimension
67 * (LDA,M) if SIDE = 'L',
68 * (LDA,N) if SIDE = 'R'
69 * The i-th row must contain the vector which defines the
70 * elementary reflector H(i), for i = 1,2,...,k, as returned by
71 * ZTZRZF in the last k rows of its array argument A.
72 * A is modified by the routine but restored on exit.
73 *
74 * LDA (input) INTEGER
75 * The leading dimension of the array A. LDA >= max(1,K).
76 *
77 * TAU (input) COMPLEX*16 array, dimension (K)
78 * TAU(i) must contain the scalar factor of the elementary
79 * reflector H(i), as returned by ZTZRZF.
80 *
81 * C (input/output) COMPLEX*16 array, dimension (LDC,N)
82 * On entry, the m-by-n matrix C.
83 * On exit, C is overwritten by Q*C or Q**H*C or C*Q**H or C*Q.
84 *
85 * LDC (input) INTEGER
86 * The leading dimension of the array C. LDC >= max(1,M).
87 *
88 * WORK (workspace) COMPLEX*16 array, dimension
89 * (N) if SIDE = 'L',
90 * (M) if SIDE = 'R'
91 *
92 * INFO (output) INTEGER
93 * = 0: successful exit
94 * < 0: if INFO = -i, the i-th argument had an illegal value
95 *
96 * Further Details
97 * ===============
98 *
99 * Based on contributions by
100 * A. Petitet, Computer Science Dept., Univ. of Tenn., Knoxville, USA
101 *
102 * =====================================================================
103 *
104 * .. Local Scalars ..
105 LOGICAL LEFT, NOTRAN
106 INTEGER I, I1, I2, I3, IC, JA, JC, MI, NI, NQ
107 COMPLEX*16 TAUI
108 * ..
109 * .. External Functions ..
110 LOGICAL LSAME
111 EXTERNAL LSAME
112 * ..
113 * .. External Subroutines ..
114 EXTERNAL XERBLA, ZLARZ
115 * ..
116 * .. Intrinsic Functions ..
117 INTRINSIC DCONJG, MAX
118 * ..
119 * .. Executable Statements ..
120 *
121 * Test the input arguments
122 *
123 INFO = 0
124 LEFT = LSAME( SIDE, 'L' )
125 NOTRAN = LSAME( TRANS, 'N' )
126 *
127 * NQ is the order of Q
128 *
129 IF( LEFT ) THEN
130 NQ = M
131 ELSE
132 NQ = N
133 END IF
134 IF( .NOT.LEFT .AND. .NOT.LSAME( SIDE, 'R' ) ) THEN
135 INFO = -1
136 ELSE IF( .NOT.NOTRAN .AND. .NOT.LSAME( TRANS, 'C' ) ) THEN
137 INFO = -2
138 ELSE IF( M.LT.0 ) THEN
139 INFO = -3
140 ELSE IF( N.LT.0 ) THEN
141 INFO = -4
142 ELSE IF( K.LT.0 .OR. K.GT.NQ ) THEN
143 INFO = -5
144 ELSE IF( L.LT.0 .OR. ( LEFT .AND. ( L.GT.M ) ) .OR.
145 $ ( .NOT.LEFT .AND. ( L.GT.N ) ) ) THEN
146 INFO = -6
147 ELSE IF( LDA.LT.MAX( 1, K ) ) THEN
148 INFO = -8
149 ELSE IF( LDC.LT.MAX( 1, M ) ) THEN
150 INFO = -11
151 END IF
152 IF( INFO.NE.0 ) THEN
153 CALL XERBLA( 'ZUNMR3', -INFO )
154 RETURN
155 END IF
156 *
157 * Quick return if possible
158 *
159 IF( M.EQ.0 .OR. N.EQ.0 .OR. K.EQ.0 )
160 $ RETURN
161 *
162 IF( ( LEFT .AND. .NOT.NOTRAN .OR. .NOT.LEFT .AND. NOTRAN ) ) THEN
163 I1 = 1
164 I2 = K
165 I3 = 1
166 ELSE
167 I1 = K
168 I2 = 1
169 I3 = -1
170 END IF
171 *
172 IF( LEFT ) THEN
173 NI = N
174 JA = M - L + 1
175 JC = 1
176 ELSE
177 MI = M
178 JA = N - L + 1
179 IC = 1
180 END IF
181 *
182 DO 10 I = I1, I2, I3
183 IF( LEFT ) THEN
184 *
185 * H(i) or H(i)**H is applied to C(i:m,1:n)
186 *
187 MI = M - I + 1
188 IC = I
189 ELSE
190 *
191 * H(i) or H(i)**H is applied to C(1:m,i:n)
192 *
193 NI = N - I + 1
194 JC = I
195 END IF
196 *
197 * Apply H(i) or H(i)**H
198 *
199 IF( NOTRAN ) THEN
200 TAUI = TAU( I )
201 ELSE
202 TAUI = DCONJG( TAU( I ) )
203 END IF
204 CALL ZLARZ( SIDE, MI, NI, L, A( I, JA ), LDA, TAUI,
205 $ C( IC, JC ), LDC, WORK )
206 *
207 10 CONTINUE
208 *
209 RETURN
210 *
211 * End of ZUNMR3
212 *
213 END
2 $ WORK, INFO )
3 *
4 * -- LAPACK routine (version 3.3.1) --
5 * -- LAPACK is a software package provided by Univ. of Tennessee, --
6 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
7 * -- April 2011 --
8 *
9 * .. Scalar Arguments ..
10 CHARACTER SIDE, TRANS
11 INTEGER INFO, K, L, LDA, LDC, M, N
12 * ..
13 * .. Array Arguments ..
14 COMPLEX*16 A( LDA, * ), C( LDC, * ), TAU( * ), WORK( * )
15 * ..
16 *
17 * Purpose
18 * =======
19 *
20 * ZUNMR3 overwrites the general complex m by n matrix C with
21 *
22 * Q * C if SIDE = 'L' and TRANS = 'N', or
23 *
24 * Q**H* C if SIDE = 'L' and TRANS = 'C', or
25 *
26 * C * Q if SIDE = 'R' and TRANS = 'N', or
27 *
28 * C * Q**H if SIDE = 'R' and TRANS = 'C',
29 *
30 * where Q is a complex unitary matrix defined as the product of k
31 * elementary reflectors
32 *
33 * Q = H(1) H(2) . . . H(k)
34 *
35 * as returned by ZTZRZF. Q is of order m if SIDE = 'L' and of order n
36 * if SIDE = 'R'.
37 *
38 * Arguments
39 * =========
40 *
41 * SIDE (input) CHARACTER*1
42 * = 'L': apply Q or Q**H from the Left
43 * = 'R': apply Q or Q**H from the Right
44 *
45 * TRANS (input) CHARACTER*1
46 * = 'N': apply Q (No transpose)
47 * = 'C': apply Q**H (Conjugate transpose)
48 *
49 * M (input) INTEGER
50 * The number of rows of the matrix C. M >= 0.
51 *
52 * N (input) INTEGER
53 * The number of columns of the matrix C. N >= 0.
54 *
55 * K (input) INTEGER
56 * The number of elementary reflectors whose product defines
57 * the matrix Q.
58 * If SIDE = 'L', M >= K >= 0;
59 * if SIDE = 'R', N >= K >= 0.
60 *
61 * L (input) INTEGER
62 * The number of columns of the matrix A containing
63 * the meaningful part of the Householder reflectors.
64 * If SIDE = 'L', M >= L >= 0, if SIDE = 'R', N >= L >= 0.
65 *
66 * A (input) COMPLEX*16 array, dimension
67 * (LDA,M) if SIDE = 'L',
68 * (LDA,N) if SIDE = 'R'
69 * The i-th row must contain the vector which defines the
70 * elementary reflector H(i), for i = 1,2,...,k, as returned by
71 * ZTZRZF in the last k rows of its array argument A.
72 * A is modified by the routine but restored on exit.
73 *
74 * LDA (input) INTEGER
75 * The leading dimension of the array A. LDA >= max(1,K).
76 *
77 * TAU (input) COMPLEX*16 array, dimension (K)
78 * TAU(i) must contain the scalar factor of the elementary
79 * reflector H(i), as returned by ZTZRZF.
80 *
81 * C (input/output) COMPLEX*16 array, dimension (LDC,N)
82 * On entry, the m-by-n matrix C.
83 * On exit, C is overwritten by Q*C or Q**H*C or C*Q**H or C*Q.
84 *
85 * LDC (input) INTEGER
86 * The leading dimension of the array C. LDC >= max(1,M).
87 *
88 * WORK (workspace) COMPLEX*16 array, dimension
89 * (N) if SIDE = 'L',
90 * (M) if SIDE = 'R'
91 *
92 * INFO (output) INTEGER
93 * = 0: successful exit
94 * < 0: if INFO = -i, the i-th argument had an illegal value
95 *
96 * Further Details
97 * ===============
98 *
99 * Based on contributions by
100 * A. Petitet, Computer Science Dept., Univ. of Tenn., Knoxville, USA
101 *
102 * =====================================================================
103 *
104 * .. Local Scalars ..
105 LOGICAL LEFT, NOTRAN
106 INTEGER I, I1, I2, I3, IC, JA, JC, MI, NI, NQ
107 COMPLEX*16 TAUI
108 * ..
109 * .. External Functions ..
110 LOGICAL LSAME
111 EXTERNAL LSAME
112 * ..
113 * .. External Subroutines ..
114 EXTERNAL XERBLA, ZLARZ
115 * ..
116 * .. Intrinsic Functions ..
117 INTRINSIC DCONJG, MAX
118 * ..
119 * .. Executable Statements ..
120 *
121 * Test the input arguments
122 *
123 INFO = 0
124 LEFT = LSAME( SIDE, 'L' )
125 NOTRAN = LSAME( TRANS, 'N' )
126 *
127 * NQ is the order of Q
128 *
129 IF( LEFT ) THEN
130 NQ = M
131 ELSE
132 NQ = N
133 END IF
134 IF( .NOT.LEFT .AND. .NOT.LSAME( SIDE, 'R' ) ) THEN
135 INFO = -1
136 ELSE IF( .NOT.NOTRAN .AND. .NOT.LSAME( TRANS, 'C' ) ) THEN
137 INFO = -2
138 ELSE IF( M.LT.0 ) THEN
139 INFO = -3
140 ELSE IF( N.LT.0 ) THEN
141 INFO = -4
142 ELSE IF( K.LT.0 .OR. K.GT.NQ ) THEN
143 INFO = -5
144 ELSE IF( L.LT.0 .OR. ( LEFT .AND. ( L.GT.M ) ) .OR.
145 $ ( .NOT.LEFT .AND. ( L.GT.N ) ) ) THEN
146 INFO = -6
147 ELSE IF( LDA.LT.MAX( 1, K ) ) THEN
148 INFO = -8
149 ELSE IF( LDC.LT.MAX( 1, M ) ) THEN
150 INFO = -11
151 END IF
152 IF( INFO.NE.0 ) THEN
153 CALL XERBLA( 'ZUNMR3', -INFO )
154 RETURN
155 END IF
156 *
157 * Quick return if possible
158 *
159 IF( M.EQ.0 .OR. N.EQ.0 .OR. K.EQ.0 )
160 $ RETURN
161 *
162 IF( ( LEFT .AND. .NOT.NOTRAN .OR. .NOT.LEFT .AND. NOTRAN ) ) THEN
163 I1 = 1
164 I2 = K
165 I3 = 1
166 ELSE
167 I1 = K
168 I2 = 1
169 I3 = -1
170 END IF
171 *
172 IF( LEFT ) THEN
173 NI = N
174 JA = M - L + 1
175 JC = 1
176 ELSE
177 MI = M
178 JA = N - L + 1
179 IC = 1
180 END IF
181 *
182 DO 10 I = I1, I2, I3
183 IF( LEFT ) THEN
184 *
185 * H(i) or H(i)**H is applied to C(i:m,1:n)
186 *
187 MI = M - I + 1
188 IC = I
189 ELSE
190 *
191 * H(i) or H(i)**H is applied to C(1:m,i:n)
192 *
193 NI = N - I + 1
194 JC = I
195 END IF
196 *
197 * Apply H(i) or H(i)**H
198 *
199 IF( NOTRAN ) THEN
200 TAUI = TAU( I )
201 ELSE
202 TAUI = DCONJG( TAU( I ) )
203 END IF
204 CALL ZLARZ( SIDE, MI, NI, L, A( I, JA ), LDA, TAUI,
205 $ C( IC, JC ), LDC, WORK )
206 *
207 10 CONTINUE
208 *
209 RETURN
210 *
211 * End of ZUNMR3
212 *
213 END