LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
cungtr.f
Go to the documentation of this file.
1*> \brief \b CUNGTR
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download CUNGTR + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cungtr.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cungtr.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cungtr.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE CUNGTR( UPLO, N, A, LDA, TAU, WORK, LWORK, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER UPLO
23* INTEGER INFO, LDA, LWORK, N
24* ..
25* .. Array Arguments ..
26* COMPLEX A( LDA, * ), TAU( * ), WORK( * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> CUNGTR generates a complex unitary matrix Q which is defined as the
36*> product of n-1 elementary reflectors of order N, as returned by
37*> CHETRD:
38*>
39*> if UPLO = 'U', Q = H(n-1) . . . H(2) H(1),
40*>
41*> if UPLO = 'L', Q = H(1) H(2) . . . H(n-1).
42*> \endverbatim
43*
44* Arguments:
45* ==========
46*
47*> \param[in] UPLO
48*> \verbatim
49*> UPLO is CHARACTER*1
50*> = 'U': Upper triangle of A contains elementary reflectors
51*> from CHETRD;
52*> = 'L': Lower triangle of A contains elementary reflectors
53*> from CHETRD.
54*> \endverbatim
55*>
56*> \param[in] N
57*> \verbatim
58*> N is INTEGER
59*> The order of the matrix Q. N >= 0.
60*> \endverbatim
61*>
62*> \param[in,out] A
63*> \verbatim
64*> A is COMPLEX array, dimension (LDA,N)
65*> On entry, the vectors which define the elementary reflectors,
66*> as returned by CHETRD.
67*> On exit, the N-by-N unitary matrix Q.
68*> \endverbatim
69*>
70*> \param[in] LDA
71*> \verbatim
72*> LDA is INTEGER
73*> The leading dimension of the array A. LDA >= N.
74*> \endverbatim
75*>
76*> \param[in] TAU
77*> \verbatim
78*> TAU is COMPLEX array, dimension (N-1)
79*> TAU(i) must contain the scalar factor of the elementary
80*> reflector H(i), as returned by CHETRD.
81*> \endverbatim
82*>
83*> \param[out] WORK
84*> \verbatim
85*> WORK is COMPLEX array, dimension (MAX(1,LWORK))
86*> On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
87*> \endverbatim
88*>
89*> \param[in] LWORK
90*> \verbatim
91*> LWORK is INTEGER
92*> The dimension of the array WORK. LWORK >= N-1.
93*> For optimum performance LWORK >= (N-1)*NB, where NB is
94*> the optimal blocksize.
95*>
96*> If LWORK = -1, then a workspace query is assumed; the routine
97*> only calculates the optimal size of the WORK array, returns
98*> this value as the first entry of the WORK array, and no error
99*> message related to LWORK is issued by XERBLA.
100*> \endverbatim
101*>
102*> \param[out] INFO
103*> \verbatim
104*> INFO is INTEGER
105*> = 0: successful exit
106*> < 0: if INFO = -i, the i-th argument had an illegal value
107*> \endverbatim
108*
109* Authors:
110* ========
111*
112*> \author Univ. of Tennessee
113*> \author Univ. of California Berkeley
114*> \author Univ. of Colorado Denver
115*> \author NAG Ltd.
116*
117*> \ingroup ungtr
118*
119* =====================================================================
120 SUBROUTINE cungtr( UPLO, N, A, LDA, TAU, WORK, LWORK, INFO )
121*
122* -- LAPACK computational routine --
123* -- LAPACK is a software package provided by Univ. of Tennessee, --
124* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
125*
126* .. Scalar Arguments ..
127 CHARACTER UPLO
128 INTEGER INFO, LDA, LWORK, N
129* ..
130* .. Array Arguments ..
131 COMPLEX A( LDA, * ), TAU( * ), WORK( * )
132* ..
133*
134* =====================================================================
135*
136* .. Parameters ..
137 COMPLEX ZERO, ONE
138 parameter( zero = ( 0.0e+0, 0.0e+0 ),
139 $ one = ( 1.0e+0, 0.0e+0 ) )
140* ..
141* .. Local Scalars ..
142 LOGICAL LQUERY, UPPER
143 INTEGER I, IINFO, J, LWKOPT, NB
144* ..
145* .. External Functions ..
146 LOGICAL LSAME
147 INTEGER ILAENV
148 REAL SROUNDUP_LWORK
149 EXTERNAL ilaenv, lsame, sroundup_lwork
150* ..
151* .. External Subroutines ..
152 EXTERNAL cungql, cungqr, xerbla
153* ..
154* .. Intrinsic Functions ..
155 INTRINSIC max
156* ..
157* .. Executable Statements ..
158*
159* Test the input arguments
160*
161 info = 0
162 lquery = ( lwork.EQ.-1 )
163 upper = lsame( uplo, 'U' )
164 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
165 info = -1
166 ELSE IF( n.LT.0 ) THEN
167 info = -2
168 ELSE IF( lda.LT.max( 1, n ) ) THEN
169 info = -4
170 ELSE IF( lwork.LT.max( 1, n-1 ) .AND. .NOT.lquery ) THEN
171 info = -7
172 END IF
173*
174 IF( info.EQ.0 ) THEN
175 IF ( upper ) THEN
176 nb = ilaenv( 1, 'CUNGQL', ' ', n-1, n-1, n-1, -1 )
177 ELSE
178 nb = ilaenv( 1, 'CUNGQR', ' ', n-1, n-1, n-1, -1 )
179 END IF
180 lwkopt = max( 1, n-1 )*nb
181 work( 1 ) = sroundup_lwork(lwkopt)
182 END IF
183*
184 IF( info.NE.0 ) THEN
185 CALL xerbla( 'CUNGTR', -info )
186 RETURN
187 ELSE IF( lquery ) THEN
188 RETURN
189 END IF
190*
191* Quick return if possible
192*
193 IF( n.EQ.0 ) THEN
194 work( 1 ) = 1
195 RETURN
196 END IF
197*
198 IF( upper ) THEN
199*
200* Q was determined by a call to CHETRD with UPLO = 'U'
201*
202* Shift the vectors which define the elementary reflectors one
203* column to the left, and set the last row and column of Q to
204* those of the unit matrix
205*
206 DO 20 j = 1, n - 1
207 DO 10 i = 1, j - 1
208 a( i, j ) = a( i, j+1 )
209 10 CONTINUE
210 a( n, j ) = zero
211 20 CONTINUE
212 DO 30 i = 1, n - 1
213 a( i, n ) = zero
214 30 CONTINUE
215 a( n, n ) = one
216*
217* Generate Q(1:n-1,1:n-1)
218*
219 CALL cungql( n-1, n-1, n-1, a, lda, tau, work, lwork,
220 $ iinfo )
221*
222 ELSE
223*
224* Q was determined by a call to CHETRD with UPLO = 'L'.
225*
226* Shift the vectors which define the elementary reflectors one
227* column to the right, and set the first row and column of Q to
228* those of the unit matrix
229*
230 DO 50 j = n, 2, -1
231 a( 1, j ) = zero
232 DO 40 i = j + 1, n
233 a( i, j ) = a( i, j-1 )
234 40 CONTINUE
235 50 CONTINUE
236 a( 1, 1 ) = one
237 DO 60 i = 2, n
238 a( i, 1 ) = zero
239 60 CONTINUE
240 IF( n.GT.1 ) THEN
241*
242* Generate Q(2:n,2:n)
243*
244 CALL cungqr( n-1, n-1, n-1, a( 2, 2 ), lda, tau, work,
245 $ lwork, iinfo )
246 END IF
247 END IF
248 work( 1 ) = sroundup_lwork(lwkopt)
249 RETURN
250*
251* End of CUNGTR
252*
253 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine cungql(m, n, k, a, lda, tau, work, lwork, info)
CUNGQL
Definition cungql.f:126
subroutine cungqr(m, n, k, a, lda, tau, work, lwork, info)
CUNGQR
Definition cungqr.f:126
subroutine cungtr(uplo, n, a, lda, tau, work, lwork, info)
CUNGTR
Definition cungtr.f:121