3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download ZUNMHR + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zunmhr.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zunmhr.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zunmhr.f">
21 * SUBROUTINE ZUNMHR( SIDE, TRANS, M, N, ILO, IHI, A, LDA, TAU, C,
22 * LDC, WORK, LWORK, INFO )
24 * .. Scalar Arguments ..
25 * CHARACTER SIDE, TRANS
26 * INTEGER IHI, ILO, INFO, LDA, LDC, LWORK, M, N
28 * .. Array Arguments ..
29 * COMPLEX*16 A( LDA, * ), C( LDC, * ), TAU( * ), WORK( * )
38 *> ZUNMHR overwrites the general complex M-by-N matrix C with
40 *> SIDE = 'L' SIDE = 'R'
41 *> TRANS = 'N': Q * C C * Q
42 *> TRANS = 'C': Q**H * C C * Q**H
44 *> where Q is a complex unitary matrix of order nq, with nq = m if
45 *> SIDE = 'L' and nq = n if SIDE = 'R'. Q is defined as the product of
46 *> IHI-ILO elementary reflectors, as returned by ZGEHRD:
48 *> Q = H(ilo) H(ilo+1) . . . H(ihi-1).
56 *> SIDE is CHARACTER*1
57 *> = 'L': apply Q or Q**H from the Left;
58 *> = 'R': apply Q or Q**H from the Right.
63 *> TRANS is CHARACTER*1
64 *> = 'N': apply Q (No transpose)
65 *> = 'C': apply Q**H (Conjugate transpose)
71 *> The number of rows of the matrix C. M >= 0.
77 *> The number of columns of the matrix C. N >= 0.
89 *> ILO and IHI must have the same values as in the previous call
90 *> of ZGEHRD. Q is equal to the unit matrix except in the
91 *> submatrix Q(ilo+1:ihi,ilo+1:ihi).
92 *> If SIDE = 'L', then 1 <= ILO <= IHI <= M, if M > 0, and
93 *> ILO = 1 and IHI = 0, if M = 0;
94 *> if SIDE = 'R', then 1 <= ILO <= IHI <= N, if N > 0, and
95 *> ILO = 1 and IHI = 0, if N = 0.
100 *> A is COMPLEX*16 array, dimension
101 *> (LDA,M) if SIDE = 'L'
102 *> (LDA,N) if SIDE = 'R'
103 *> The vectors which define the elementary reflectors, as
104 *> returned by ZGEHRD.
110 *> The leading dimension of the array A.
111 *> LDA >= max(1,M) if SIDE = 'L'; LDA >= max(1,N) if SIDE = 'R'.
116 *> TAU is COMPLEX*16 array, dimension
117 *> (M-1) if SIDE = 'L'
118 *> (N-1) if SIDE = 'R'
119 *> TAU(i) must contain the scalar factor of the elementary
120 *> reflector H(i), as returned by ZGEHRD.
125 *> C is COMPLEX*16 array, dimension (LDC,N)
126 *> On entry, the M-by-N matrix C.
127 *> On exit, C is overwritten by Q*C or Q**H*C or C*Q**H or C*Q.
133 *> The leading dimension of the array C. LDC >= max(1,M).
138 *> WORK is COMPLEX*16 array, dimension (MAX(1,LWORK))
139 *> On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
145 *> The dimension of the array WORK.
146 *> If SIDE = 'L', LWORK >= max(1,N);
147 *> if SIDE = 'R', LWORK >= max(1,M).
148 *> For optimum performance LWORK >= N*NB if SIDE = 'L', and
149 *> LWORK >= M*NB if SIDE = 'R', where NB is the optimal
152 *> If LWORK = -1, then a workspace query is assumed; the routine
153 *> only calculates the optimal size of the WORK array, returns
154 *> this value as the first entry of the WORK array, and no error
155 *> message related to LWORK is issued by XERBLA.
161 *> = 0: successful exit
162 *> < 0: if INFO = -i, the i-th argument had an illegal value
168 *> \author Univ. of Tennessee
169 *> \author Univ. of California Berkeley
170 *> \author Univ. of Colorado Denver
173 *> \date November 2011
175 *> \ingroup complex16OTHERcomputational
177 * =====================================================================
178 SUBROUTINE ZUNMHR( SIDE, TRANS, M, N, ILO, IHI, A, LDA, TAU, C,
179 $ LDC, WORK, LWORK, INFO )
181 * -- LAPACK computational routine (version 3.4.0) --
182 * -- LAPACK is a software package provided by Univ. of Tennessee, --
183 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
186 * .. Scalar Arguments ..
187 CHARACTER SIDE, TRANS
188 INTEGER IHI, ILO, INFO, LDA, LDC, LWORK, M, N
190 * .. Array Arguments ..
191 COMPLEX*16 A( LDA, * ), C( LDC, * ), TAU( * ), WORK( * )
194 * =====================================================================
196 * .. Local Scalars ..
198 INTEGER I1, I2, IINFO, LWKOPT, MI, NB, NH, NI, NQ, NW
200 * .. External Functions ..
203 EXTERNAL LSAME, ILAENV
205 * .. External Subroutines ..
206 EXTERNAL XERBLA, ZUNMQR
208 * .. Intrinsic Functions ..
211 * .. Executable Statements ..
213 * Test the input arguments
217 LEFT = LSAME( SIDE, 'L' )
218 LQUERY = ( LWORK.EQ.-1 )
220 * NQ is the order of Q and NW is the minimum dimension of WORK
229 IF( .NOT.LEFT .AND. .NOT.LSAME( SIDE, 'R' ) ) THEN
231 ELSE IF( .NOT.LSAME( TRANS, 'N' ) .AND. .NOT.LSAME( TRANS, 'C' ) )
234 ELSE IF( M.LT.0 ) THEN
236 ELSE IF( N.LT.0 ) THEN
238 ELSE IF( ILO.LT.1 .OR. ILO.GT.MAX( 1, NQ ) ) THEN
240 ELSE IF( IHI.LT.MIN( ILO, NQ ) .OR. IHI.GT.NQ ) THEN
242 ELSE IF( LDA.LT.MAX( 1, NQ ) ) THEN
244 ELSE IF( LDC.LT.MAX( 1, M ) ) THEN
246 ELSE IF( LWORK.LT.MAX( 1, NW ) .AND. .NOT.LQUERY ) THEN
252 NB = ILAENV( 1, 'ZUNMQR', SIDE // TRANS, NH, N, NH, -1 )
254 NB = ILAENV( 1, 'ZUNMQR', SIDE // TRANS, M, NH, NH, -1 )
256 LWKOPT = MAX( 1, NW )*NB
261 CALL XERBLA( 'ZUNMHR', -INFO )
263 ELSE IF( LQUERY ) THEN
267 * Quick return if possible
269 IF( M.EQ.0 .OR. N.EQ.0 .OR. NH.EQ.0 ) THEN
286 CALL ZUNMQR( SIDE, TRANS, MI, NI, NH, A( ILO+1, ILO ), LDA,
287 $ TAU( ILO ), C( I1, I2 ), LDC, WORK, LWORK, IINFO )