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