LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ zupgtr()

subroutine zupgtr ( character uplo,
integer n,
complex*16, dimension( * ) ap,
complex*16, dimension( * ) tau,
complex*16, dimension( ldq, * ) q,
integer ldq,
complex*16, dimension( * ) work,
integer info )

ZUPGTR

Download ZUPGTR + dependencies [TGZ] [ZIP] [TXT]

Purpose:
!>
!> ZUPGTR generates a complex unitary matrix Q which is defined as the
!> product of n-1 elementary reflectors H(i) of order n, as returned by
!> ZHPTRD using packed storage:
!>
!> if UPLO = 'U', Q = H(n-1) . . . H(2) H(1),
!>
!> if UPLO = 'L', Q = H(1) H(2) . . . H(n-1).
!> 
Parameters
[in]UPLO
!>          UPLO is CHARACTER*1
!>          = 'U': Upper triangular packed storage used in previous
!>                 call to ZHPTRD;
!>          = 'L': Lower triangular packed storage used in previous
!>                 call to ZHPTRD.
!> 
[in]N
!>          N is INTEGER
!>          The order of the matrix Q. N >= 0.
!> 
[in]AP
!>          AP is COMPLEX*16 array, dimension (N*(N+1)/2)
!>          The vectors which define the elementary reflectors, as
!>          returned by ZHPTRD.
!> 
[in]TAU
!>          TAU is COMPLEX*16 array, dimension (N-1)
!>          TAU(i) must contain the scalar factor of the elementary
!>          reflector H(i), as returned by ZHPTRD.
!> 
[out]Q
!>          Q is COMPLEX*16 array, dimension (LDQ,N)
!>          The N-by-N unitary matrix Q.
!> 
[in]LDQ
!>          LDQ is INTEGER
!>          The leading dimension of the array Q. LDQ >= max(1,N).
!> 
[out]WORK
!>          WORK is COMPLEX*16 array, dimension (N-1)
!> 
[out]INFO
!>          INFO is INTEGER
!>          = 0:  successful exit
!>          < 0:  if INFO = -i, the i-th argument had an illegal value
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 111 of file zupgtr.f.

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*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
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
Here is the call graph for this function:
Here is the caller graph for this function: