LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
cupmtr.f
Go to the documentation of this file.
1 *> \brief \b CUPMTR
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download CUPMTR + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cupmtr.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cupmtr.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cupmtr.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE CUPMTR( SIDE, UPLO, TRANS, M, N, AP, TAU, C, LDC, WORK,
22 * INFO )
23 *
24 * .. Scalar Arguments ..
25 * CHARACTER SIDE, TRANS, UPLO
26 * INTEGER INFO, LDC, M, N
27 * ..
28 * .. Array Arguments ..
29 * COMPLEX AP( * ), C( LDC, * ), TAU( * ), WORK( * )
30 * ..
31 *
32 *
33 *> \par Purpose:
34 * =============
35 *>
36 *> \verbatim
37 *>
38 *> CUPMTR 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 *> nq-1 elementary reflectors, as returned by CHPTRD using packed
47 *> storage:
48 *>
49 *> if UPLO = 'U', Q = H(nq-1) . . . H(2) H(1);
50 *>
51 *> if UPLO = 'L', Q = H(1) H(2) . . . H(nq-1).
52 *> \endverbatim
53 *
54 * Arguments:
55 * ==========
56 *
57 *> \param[in] SIDE
58 *> \verbatim
59 *> SIDE is CHARACTER*1
60 *> = 'L': apply Q or Q**H from the Left;
61 *> = 'R': apply Q or Q**H from the Right.
62 *> \endverbatim
63 *>
64 *> \param[in] UPLO
65 *> \verbatim
66 *> UPLO is CHARACTER*1
67 *> = 'U': Upper triangular packed storage used in previous
68 *> call to CHPTRD;
69 *> = 'L': Lower triangular packed storage used in previous
70 *> call to CHPTRD.
71 *> \endverbatim
72 *>
73 *> \param[in] TRANS
74 *> \verbatim
75 *> TRANS is CHARACTER*1
76 *> = 'N': No transpose, apply Q;
77 *> = 'C': Conjugate transpose, apply Q**H.
78 *> \endverbatim
79 *>
80 *> \param[in] M
81 *> \verbatim
82 *> M is INTEGER
83 *> The number of rows of the matrix C. M >= 0.
84 *> \endverbatim
85 *>
86 *> \param[in] N
87 *> \verbatim
88 *> N is INTEGER
89 *> The number of columns of the matrix C. N >= 0.
90 *> \endverbatim
91 *>
92 *> \param[in] AP
93 *> \verbatim
94 *> AP is COMPLEX array, dimension
95 *> (M*(M+1)/2) if SIDE = 'L'
96 *> (N*(N+1)/2) if SIDE = 'R'
97 *> The vectors which define the elementary reflectors, as
98 *> returned by CHPTRD. AP is modified by the routine but
99 *> restored on exit.
100 *> \endverbatim
101 *>
102 *> \param[in] TAU
103 *> \verbatim
104 *> TAU is COMPLEX array, dimension (M-1) if SIDE = 'L'
105 *> or (N-1) if SIDE = 'R'
106 *> TAU(i) must contain the scalar factor of the elementary
107 *> reflector H(i), as returned by CHPTRD.
108 *> \endverbatim
109 *>
110 *> \param[in,out] C
111 *> \verbatim
112 *> C is COMPLEX array, dimension (LDC,N)
113 *> On entry, the M-by-N matrix C.
114 *> On exit, C is overwritten by Q*C or Q**H*C or C*Q**H or C*Q.
115 *> \endverbatim
116 *>
117 *> \param[in] LDC
118 *> \verbatim
119 *> LDC is INTEGER
120 *> The leading dimension of the array C. LDC >= max(1,M).
121 *> \endverbatim
122 *>
123 *> \param[out] WORK
124 *> \verbatim
125 *> WORK is COMPLEX array, dimension
126 *> (N) if SIDE = 'L'
127 *> (M) if SIDE = 'R'
128 *> \endverbatim
129 *>
130 *> \param[out] INFO
131 *> \verbatim
132 *> INFO is INTEGER
133 *> = 0: successful exit
134 *> < 0: if INFO = -i, the i-th argument had an illegal value
135 *> \endverbatim
136 *
137 * Authors:
138 * ========
139 *
140 *> \author Univ. of Tennessee
141 *> \author Univ. of California Berkeley
142 *> \author Univ. of Colorado Denver
143 *> \author NAG Ltd.
144 *
145 *> \date November 2011
146 *
147 *> \ingroup complexOTHERcomputational
148 *
149 * =====================================================================
150  SUBROUTINE cupmtr( SIDE, UPLO, TRANS, M, N, AP, TAU, C, LDC, WORK,
151  $ info )
152 *
153 * -- LAPACK computational routine (version 3.4.0) --
154 * -- LAPACK is a software package provided by Univ. of Tennessee, --
155 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
156 * November 2011
157 *
158 * .. Scalar Arguments ..
159  CHARACTER side, trans, uplo
160  INTEGER info, ldc, m, n
161 * ..
162 * .. Array Arguments ..
163  COMPLEX ap( * ), c( ldc, * ), tau( * ), work( * )
164 * ..
165 *
166 * =====================================================================
167 *
168 * .. Parameters ..
169  COMPLEX one
170  parameter( one = ( 1.0e+0, 0.0e+0 ) )
171 * ..
172 * .. Local Scalars ..
173  LOGICAL forwrd, left, notran, upper
174  INTEGER i, i1, i2, i3, ic, ii, jc, mi, ni, nq
175  COMPLEX aii, taui
176 * ..
177 * .. External Functions ..
178  LOGICAL lsame
179  EXTERNAL lsame
180 * ..
181 * .. External Subroutines ..
182  EXTERNAL clarf, xerbla
183 * ..
184 * .. Intrinsic Functions ..
185  INTRINSIC conjg, max
186 * ..
187 * .. Executable Statements ..
188 *
189 * Test the input arguments
190 *
191  info = 0
192  left = lsame( side, 'L' )
193  notran = lsame( trans, 'N' )
194  upper = lsame( uplo, 'U' )
195 *
196 * NQ is the order of Q
197 *
198  IF( left ) THEN
199  nq = m
200  ELSE
201  nq = n
202  END IF
203  IF( .NOT.left .AND. .NOT.lsame( side, 'R' ) ) THEN
204  info = -1
205  ELSE IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
206  info = -2
207  ELSE IF( .NOT.notran .AND. .NOT.lsame( trans, 'C' ) ) THEN
208  info = -3
209  ELSE IF( m.LT.0 ) THEN
210  info = -4
211  ELSE IF( n.LT.0 ) THEN
212  info = -5
213  ELSE IF( ldc.LT.max( 1, m ) ) THEN
214  info = -9
215  END IF
216  IF( info.NE.0 ) THEN
217  CALL xerbla( 'CUPMTR', -info )
218  return
219  END IF
220 *
221 * Quick return if possible
222 *
223  IF( m.EQ.0 .OR. n.EQ.0 )
224  $ return
225 *
226  IF( upper ) THEN
227 *
228 * Q was determined by a call to CHPTRD with UPLO = 'U'
229 *
230  forwrd = ( left .AND. notran ) .OR.
231  $ ( .NOT.left .AND. .NOT.notran )
232 *
233  IF( forwrd ) THEN
234  i1 = 1
235  i2 = nq - 1
236  i3 = 1
237  ii = 2
238  ELSE
239  i1 = nq - 1
240  i2 = 1
241  i3 = -1
242  ii = nq*( nq+1 ) / 2 - 1
243  END IF
244 *
245  IF( left ) THEN
246  ni = n
247  ELSE
248  mi = m
249  END IF
250 *
251  DO 10 i = i1, i2, i3
252  IF( left ) THEN
253 *
254 * H(i) or H(i)**H is applied to C(1:i,1:n)
255 *
256  mi = i
257  ELSE
258 *
259 * H(i) or H(i)**H is applied to C(1:m,1:i)
260 *
261  ni = i
262  END IF
263 *
264 * Apply H(i) or H(i)**H
265 *
266  IF( notran ) THEN
267  taui = tau( i )
268  ELSE
269  taui = conjg( tau( i ) )
270  END IF
271  aii = ap( ii )
272  ap( ii ) = one
273  CALL clarf( side, mi, ni, ap( ii-i+1 ), 1, taui, c, ldc,
274  $ work )
275  ap( ii ) = aii
276 *
277  IF( forwrd ) THEN
278  ii = ii + i + 2
279  ELSE
280  ii = ii - i - 1
281  END IF
282  10 continue
283  ELSE
284 *
285 * Q was determined by a call to CHPTRD with UPLO = 'L'.
286 *
287  forwrd = ( left .AND. .NOT.notran ) .OR.
288  $ ( .NOT.left .AND. notran )
289 *
290  IF( forwrd ) THEN
291  i1 = 1
292  i2 = nq - 1
293  i3 = 1
294  ii = 2
295  ELSE
296  i1 = nq - 1
297  i2 = 1
298  i3 = -1
299  ii = nq*( nq+1 ) / 2 - 1
300  END IF
301 *
302  IF( left ) THEN
303  ni = n
304  jc = 1
305  ELSE
306  mi = m
307  ic = 1
308  END IF
309 *
310  DO 20 i = i1, i2, i3
311  aii = ap( ii )
312  ap( ii ) = one
313  IF( left ) THEN
314 *
315 * H(i) or H(i)**H is applied to C(i+1:m,1:n)
316 *
317  mi = m - i
318  ic = i + 1
319  ELSE
320 *
321 * H(i) or H(i)**H is applied to C(1:m,i+1:n)
322 *
323  ni = n - i
324  jc = i + 1
325  END IF
326 *
327 * Apply H(i) or H(i)**H
328 *
329  IF( notran ) THEN
330  taui = tau( i )
331  ELSE
332  taui = conjg( tau( i ) )
333  END IF
334  CALL clarf( side, mi, ni, ap( ii ), 1, taui, c( ic, jc ),
335  $ ldc, work )
336  ap( ii ) = aii
337 *
338  IF( forwrd ) THEN
339  ii = ii + nq - i + 1
340  ELSE
341  ii = ii - nq + i - 2
342  END IF
343  20 continue
344  END IF
345  return
346 *
347 * End of CUPMTR
348 *
349  END