LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
zunmhr.f
Go to the documentation of this file.
1 *> \brief \b ZUNMHR
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download ZUNMHR + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zunmhr.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zunmhr.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zunmhr.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE ZUNMHR( SIDE, TRANS, M, N, ILO, IHI, A, LDA, TAU, C,
22 * LDC, WORK, LWORK, INFO )
23 *
24 * .. Scalar Arguments ..
25 * CHARACTER SIDE, TRANS
26 * INTEGER IHI, ILO, INFO, LDA, LDC, LWORK, M, N
27 * ..
28 * .. Array Arguments ..
29 * COMPLEX*16 A( LDA, * ), C( LDC, * ), TAU( * ), WORK( * )
30 * ..
31 *
32 *
33 *> \par Purpose:
34 * =============
35 *>
36 *> \verbatim
37 *>
38 *> ZUNMHR overwrites the general complex M-by-N matrix C with
39 *>
40 *> SIDE = 'L' SIDE = 'R'
41 *> TRANS = 'N': Q * C C * Q
42 *> TRANS = 'C': Q**H * C C * Q**H
43 *>
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:
47 *>
48 *> Q = H(ilo) H(ilo+1) . . . H(ihi-1).
49 *> \endverbatim
50 *
51 * Arguments:
52 * ==========
53 *
54 *> \param[in] SIDE
55 *> \verbatim
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.
59 *> \endverbatim
60 *>
61 *> \param[in] TRANS
62 *> \verbatim
63 *> TRANS is CHARACTER*1
64 *> = 'N': apply Q (No transpose)
65 *> = 'C': apply Q**H (Conjugate transpose)
66 *> \endverbatim
67 *>
68 *> \param[in] M
69 *> \verbatim
70 *> M is INTEGER
71 *> The number of rows of the matrix C. M >= 0.
72 *> \endverbatim
73 *>
74 *> \param[in] N
75 *> \verbatim
76 *> N is INTEGER
77 *> The number of columns of the matrix C. N >= 0.
78 *> \endverbatim
79 *>
80 *> \param[in] ILO
81 *> \verbatim
82 *> ILO is INTEGER
83 *> \endverbatim
84 *>
85 *> \param[in] IHI
86 *> \verbatim
87 *> IHI is INTEGER
88 *>
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.
96 *> \endverbatim
97 *>
98 *> \param[in] A
99 *> \verbatim
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.
105 *> \endverbatim
106 *>
107 *> \param[in] LDA
108 *> \verbatim
109 *> LDA is INTEGER
110 *> The leading dimension of the array A.
111 *> LDA >= max(1,M) if SIDE = 'L'; LDA >= max(1,N) if SIDE = 'R'.
112 *> \endverbatim
113 *>
114 *> \param[in] TAU
115 *> \verbatim
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.
121 *> \endverbatim
122 *>
123 *> \param[in,out] C
124 *> \verbatim
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.
128 *> \endverbatim
129 *>
130 *> \param[in] LDC
131 *> \verbatim
132 *> LDC is INTEGER
133 *> The leading dimension of the array C. LDC >= max(1,M).
134 *> \endverbatim
135 *>
136 *> \param[out] WORK
137 *> \verbatim
138 *> WORK is COMPLEX*16 array, dimension (MAX(1,LWORK))
139 *> On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
140 *> \endverbatim
141 *>
142 *> \param[in] LWORK
143 *> \verbatim
144 *> LWORK is INTEGER
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
150 *> blocksize.
151 *>
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.
156 *> \endverbatim
157 *>
158 *> \param[out] INFO
159 *> \verbatim
160 *> INFO is INTEGER
161 *> = 0: successful exit
162 *> < 0: if INFO = -i, the i-th argument had an illegal value
163 *> \endverbatim
164 *
165 * Authors:
166 * ========
167 *
168 *> \author Univ. of Tennessee
169 *> \author Univ. of California Berkeley
170 *> \author Univ. of Colorado Denver
171 *> \author NAG Ltd.
172 *
173 *> \date November 2011
174 *
175 *> \ingroup complex16OTHERcomputational
176 *
177 * =====================================================================
178  SUBROUTINE zunmhr( SIDE, TRANS, M, N, ILO, IHI, A, LDA, TAU, C,
179  $ ldc, work, lwork, info )
180 *
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..--
184 * November 2011
185 *
186 * .. Scalar Arguments ..
187  CHARACTER side, trans
188  INTEGER ihi, ilo, info, lda, ldc, lwork, m, n
189 * ..
190 * .. Array Arguments ..
191  COMPLEX*16 a( lda, * ), c( ldc, * ), tau( * ), work( * )
192 * ..
193 *
194 * =====================================================================
195 *
196 * .. Local Scalars ..
197  LOGICAL left, lquery
198  INTEGER i1, i2, iinfo, lwkopt, mi, nb, nh, ni, nq, nw
199 * ..
200 * .. External Functions ..
201  LOGICAL lsame
202  INTEGER ilaenv
203  EXTERNAL lsame, ilaenv
204 * ..
205 * .. External Subroutines ..
206  EXTERNAL xerbla, zunmqr
207 * ..
208 * .. Intrinsic Functions ..
209  INTRINSIC max, min
210 * ..
211 * .. Executable Statements ..
212 *
213 * Test the input arguments
214 *
215  info = 0
216  nh = ihi - ilo
217  left = lsame( side, 'L' )
218  lquery = ( lwork.EQ.-1 )
219 *
220 * NQ is the order of Q and NW is the minimum dimension of WORK
221 *
222  IF( left ) THEN
223  nq = m
224  nw = n
225  ELSE
226  nq = n
227  nw = m
228  END IF
229  IF( .NOT.left .AND. .NOT.lsame( side, 'R' ) ) THEN
230  info = -1
231  ELSE IF( .NOT.lsame( trans, 'N' ) .AND. .NOT.lsame( trans, 'C' ) )
232  $ THEN
233  info = -2
234  ELSE IF( m.LT.0 ) THEN
235  info = -3
236  ELSE IF( n.LT.0 ) THEN
237  info = -4
238  ELSE IF( ilo.LT.1 .OR. ilo.GT.max( 1, nq ) ) THEN
239  info = -5
240  ELSE IF( ihi.LT.min( ilo, nq ) .OR. ihi.GT.nq ) THEN
241  info = -6
242  ELSE IF( lda.LT.max( 1, nq ) ) THEN
243  info = -8
244  ELSE IF( ldc.LT.max( 1, m ) ) THEN
245  info = -11
246  ELSE IF( lwork.LT.max( 1, nw ) .AND. .NOT.lquery ) THEN
247  info = -13
248  END IF
249 *
250  IF( info.EQ.0 ) THEN
251  IF( left ) THEN
252  nb = ilaenv( 1, 'ZUNMQR', side // trans, nh, n, nh, -1 )
253  ELSE
254  nb = ilaenv( 1, 'ZUNMQR', side // trans, m, nh, nh, -1 )
255  END IF
256  lwkopt = max( 1, nw )*nb
257  work( 1 ) = lwkopt
258  END IF
259 *
260  IF( info.NE.0 ) THEN
261  CALL xerbla( 'ZUNMHR', -info )
262  return
263  ELSE IF( lquery ) THEN
264  return
265  END IF
266 *
267 * Quick return if possible
268 *
269  IF( m.EQ.0 .OR. n.EQ.0 .OR. nh.EQ.0 ) THEN
270  work( 1 ) = 1
271  return
272  END IF
273 *
274  IF( left ) THEN
275  mi = nh
276  ni = n
277  i1 = ilo + 1
278  i2 = 1
279  ELSE
280  mi = m
281  ni = nh
282  i1 = 1
283  i2 = ilo + 1
284  END IF
285 *
286  CALL zunmqr( side, trans, mi, ni, nh, a( ilo+1, ilo ), lda,
287  $ tau( ilo ), c( i1, i2 ), ldc, work, lwork, iinfo )
288 *
289  work( 1 ) = lwkopt
290  return
291 *
292 * End of ZUNMHR
293 *
294  END