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

◆ cupgtr()

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

CUPGTR

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

Purpose:
 CUPGTR 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
 CHPTRD 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 CHPTRD;
          = 'L': Lower triangular packed storage used in previous
                 call to CHPTRD.
[in]N
          N is INTEGER
          The order of the matrix Q. N >= 0.
[in]AP
          AP is COMPLEX array, dimension (N*(N+1)/2)
          The vectors which define the elementary reflectors, as
          returned by CHPTRD.
[in]TAU
          TAU is COMPLEX array, dimension (N-1)
          TAU(i) must contain the scalar factor of the elementary
          reflector H(i), as returned by CHPTRD.
[out]Q
          Q is COMPLEX 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 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 113 of file cupgtr.f.

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 AP( * ), Q( LDQ, * ), TAU( * ), WORK( * )
125* ..
126*
127* =====================================================================
128*
129* .. Parameters ..
130 COMPLEX CZERO, CONE
131 parameter( czero = ( 0.0e+0, 0.0e+0 ),
132 $ cone = ( 1.0e+0, 0.0e+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 cung2l, cung2r, xerbla
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( 'CUPGTR', -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 CHPTRD 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 cung2l( n-1, n-1, n-1, q, ldq, tau, work, iinfo )
196*
197 ELSE
198*
199* Q was determined by a call to CHPTRD 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 cung2r( 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 CUPGTR
229*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine cung2l(m, n, k, a, lda, tau, work, info)
CUNG2L generates all or part of the unitary matrix Q from a QL factorization determined by cgeqlf (un...
Definition cung2l.f:114
subroutine cung2r(m, n, k, a, lda, tau, work, info)
CUNG2R
Definition cung2r.f:114
Here is the call graph for this function:
Here is the caller graph for this function: