LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zupgtr.f
Go to the documentation of this file.
1*> \brief \b ZUPGTR
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download ZUPGTR + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zupgtr.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zupgtr.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zupgtr.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18* Definition:
19* ===========
20*
21* SUBROUTINE ZUPGTR( UPLO, N, AP, TAU, Q, LDQ, WORK, INFO )
22*
23* .. Scalar Arguments ..
24* CHARACTER UPLO
25* INTEGER INFO, LDQ, N
26* ..
27* .. Array Arguments ..
28* COMPLEX*16 AP( * ), Q( LDQ, * ), TAU( * ), WORK( * )
29* ..
30*
31*
32*> \par Purpose:
33* =============
34*>
35*> \verbatim
36*>
37*> ZUPGTR generates a complex unitary matrix Q which is defined as the
38*> product of n-1 elementary reflectors H(i) of order n, as returned by
39*> ZHPTRD using packed storage:
40*>
41*> if UPLO = 'U', Q = H(n-1) . . . H(2) H(1),
42*>
43*> if UPLO = 'L', Q = H(1) H(2) . . . H(n-1).
44*> \endverbatim
45*
46* Arguments:
47* ==========
48*
49*> \param[in] UPLO
50*> \verbatim
51*> UPLO is CHARACTER*1
52*> = 'U': Upper triangular packed storage used in previous
53*> call to ZHPTRD;
54*> = 'L': Lower triangular packed storage used in previous
55*> call to ZHPTRD.
56*> \endverbatim
57*>
58*> \param[in] N
59*> \verbatim
60*> N is INTEGER
61*> The order of the matrix Q. N >= 0.
62*> \endverbatim
63*>
64*> \param[in] AP
65*> \verbatim
66*> AP is COMPLEX*16 array, dimension (N*(N+1)/2)
67*> The vectors which define the elementary reflectors, as
68*> returned by ZHPTRD.
69*> \endverbatim
70*>
71*> \param[in] TAU
72*> \verbatim
73*> TAU is COMPLEX*16 array, dimension (N-1)
74*> TAU(i) must contain the scalar factor of the elementary
75*> reflector H(i), as returned by ZHPTRD.
76*> \endverbatim
77*>
78*> \param[out] Q
79*> \verbatim
80*> Q is COMPLEX*16 array, dimension (LDQ,N)
81*> The N-by-N unitary matrix Q.
82*> \endverbatim
83*>
84*> \param[in] LDQ
85*> \verbatim
86*> LDQ is INTEGER
87*> The leading dimension of the array Q. LDQ >= max(1,N).
88*> \endverbatim
89*>
90*> \param[out] WORK
91*> \verbatim
92*> WORK is COMPLEX*16 array, dimension (N-1)
93*> \endverbatim
94*>
95*> \param[out] INFO
96*> \verbatim
97*> INFO is INTEGER
98*> = 0: successful exit
99*> < 0: if INFO = -i, the i-th argument had an illegal value
100*> \endverbatim
101*
102* Authors:
103* ========
104*
105*> \author Univ. of Tennessee
106*> \author Univ. of California Berkeley
107*> \author Univ. of Colorado Denver
108*> \author NAG Ltd.
109*
110*> \ingroup upgtr
111*
112* =====================================================================
113 SUBROUTINE zupgtr( UPLO, N, AP, TAU, Q, LDQ, WORK, INFO )
114*
115* -- LAPACK computational routine --
116* -- LAPACK is a software package provided by Univ. of Tennessee, --
117* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
118*
119* .. Scalar Arguments ..
120 CHARACTER UPLO
121 INTEGER INFO, LDQ, N
122* ..
123* .. Array Arguments ..
124 COMPLEX*16 AP( * ), Q( LDQ, * ), TAU( * ), WORK( * )
125* ..
126*
127* =====================================================================
128*
129* .. Parameters ..
130 COMPLEX*16 CZERO, CONE
131 parameter( czero = ( 0.0d+0, 0.0d+0 ),
132 $ cone = ( 1.0d+0, 0.0d+0 ) )
133* ..
134* .. Local Scalars ..
135 LOGICAL UPPER
136 INTEGER I, IINFO, IJ, J
137* ..
138* .. External Functions ..
139 LOGICAL LSAME
140 EXTERNAL lsame
141* ..
142* .. External Subroutines ..
143 EXTERNAL xerbla, zung2l, zung2r
144* ..
145* .. Intrinsic Functions ..
146 INTRINSIC max
147* ..
148* .. Executable Statements ..
149*
150* Test the input arguments
151*
152 info = 0
153 upper = lsame( uplo, 'U' )
154 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
155 info = -1
156 ELSE IF( n.LT.0 ) THEN
157 info = -2
158 ELSE IF( ldq.LT.max( 1, n ) ) THEN
159 info = -6
160 END IF
161 IF( info.NE.0 ) THEN
162 CALL xerbla( 'ZUPGTR', -info )
163 RETURN
164 END IF
165*
166* Quick return if possible
167*
168 IF( n.EQ.0 )
169 $ RETURN
170*
171 IF( upper ) THEN
172*
173* Q was determined by a call to ZHPTRD with UPLO = 'U'
174*
175* Unpack the vectors which define the elementary reflectors and
176* set the last row and column of Q equal to those of the unit
177* matrix
178*
179 ij = 2
180 DO 20 j = 1, n - 1
181 DO 10 i = 1, j - 1
182 q( i, j ) = ap( ij )
183 ij = ij + 1
184 10 CONTINUE
185 ij = ij + 2
186 q( n, j ) = czero
187 20 CONTINUE
188 DO 30 i = 1, n - 1
189 q( i, n ) = czero
190 30 CONTINUE
191 q( n, n ) = cone
192*
193* Generate Q(1:n-1,1:n-1)
194*
195 CALL zung2l( n-1, n-1, n-1, q, ldq, tau, work, iinfo )
196*
197 ELSE
198*
199* Q was determined by a call to ZHPTRD with UPLO = 'L'.
200*
201* Unpack the vectors which define the elementary reflectors and
202* set the first row and column of Q equal to those of the unit
203* matrix
204*
205 q( 1, 1 ) = cone
206 DO 40 i = 2, n
207 q( i, 1 ) = czero
208 40 CONTINUE
209 ij = 3
210 DO 60 j = 2, n
211 q( 1, j ) = czero
212 DO 50 i = j + 1, n
213 q( i, j ) = ap( ij )
214 ij = ij + 1
215 50 CONTINUE
216 ij = ij + 2
217 60 CONTINUE
218 IF( n.GT.1 ) THEN
219*
220* Generate Q(2:n,2:n)
221*
222 CALL zung2r( n-1, n-1, n-1, q( 2, 2 ), ldq, tau, work,
223 $ iinfo )
224 END IF
225 END IF
226 RETURN
227*
228* End of ZUPGTR
229*
230 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zung2l(m, n, k, a, lda, tau, work, info)
ZUNG2L generates all or part of the unitary matrix Q from a QL factorization determined by cgeqlf (un...
Definition zung2l.f:114
subroutine zung2r(m, n, k, a, lda, tau, work, info)
ZUNG2R
Definition zung2r.f:114
subroutine zupgtr(uplo, n, ap, tau, q, ldq, work, info)
ZUPGTR
Definition zupgtr.f:114