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

◆ cunghr()

subroutine cunghr ( integer  n,
integer  ilo,
integer  ihi,
complex, dimension( lda, * )  a,
integer  lda,
complex, dimension( * )  tau,
complex, dimension( * )  work,
integer  lwork,
integer  info 
)

CUNGHR

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

Purpose:
 CUNGHR generates a complex unitary matrix Q which is defined as the
 product of IHI-ILO elementary reflectors of order N, as returned by
 CGEHRD:

 Q = H(ilo) H(ilo+1) . . . H(ihi-1).
Parameters
[in]N
          N is INTEGER
          The order of the matrix Q. N >= 0.
[in]ILO
          ILO is INTEGER
[in]IHI
          IHI is INTEGER

          ILO and IHI must have the same values as in the previous call
          of CGEHRD. Q is equal to the unit matrix except in the
          submatrix Q(ilo+1:ihi,ilo+1:ihi).
          1 <= ILO <= IHI <= N, if N > 0; ILO=1 and IHI=0, if N=0.
[in,out]A
          A is COMPLEX array, dimension (LDA,N)
          On entry, the vectors which define the elementary reflectors,
          as returned by CGEHRD.
          On exit, the N-by-N unitary matrix Q.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A. LDA >= max(1,N).
[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 CGEHRD.
[out]WORK
          WORK is COMPLEX array, dimension (MAX(1,LWORK))
          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
[in]LWORK
          LWORK is INTEGER
          The dimension of the array WORK. LWORK >= IHI-ILO.
          For optimum performance LWORK >= (IHI-ILO)*NB, where NB is
          the optimal blocksize.

          If LWORK = -1, then a workspace query is assumed; the routine
          only calculates the optimal size of the WORK array, returns
          this value as the first entry of the WORK array, and no error
          message related to LWORK is issued by XERBLA.
[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 125 of file cunghr.f.

126*
127* -- LAPACK computational routine --
128* -- LAPACK is a software package provided by Univ. of Tennessee, --
129* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
130*
131* .. Scalar Arguments ..
132 INTEGER IHI, ILO, INFO, LDA, LWORK, N
133* ..
134* .. Array Arguments ..
135 COMPLEX A( LDA, * ), TAU( * ), WORK( * )
136* ..
137*
138* =====================================================================
139*
140* .. Parameters ..
141 COMPLEX ZERO, ONE
142 parameter( zero = ( 0.0e+0, 0.0e+0 ),
143 $ one = ( 1.0e+0, 0.0e+0 ) )
144* ..
145* .. Local Scalars ..
146 LOGICAL LQUERY
147 INTEGER I, IINFO, J, LWKOPT, NB, NH
148* ..
149* .. External Subroutines ..
150 EXTERNAL cungqr, xerbla
151* ..
152* .. External Functions ..
153 INTEGER ILAENV
154 REAL SROUNDUP_LWORK
155 EXTERNAL ilaenv, sroundup_lwork
156* ..
157* .. Intrinsic Functions ..
158 INTRINSIC max, min
159* ..
160* .. Executable Statements ..
161*
162* Test the input arguments
163*
164 info = 0
165 nh = ihi - ilo
166 lquery = ( lwork.EQ.-1 )
167 IF( n.LT.0 ) THEN
168 info = -1
169 ELSE IF( ilo.LT.1 .OR. ilo.GT.max( 1, n ) ) THEN
170 info = -2
171 ELSE IF( ihi.LT.min( ilo, n ) .OR. ihi.GT.n ) THEN
172 info = -3
173 ELSE IF( lda.LT.max( 1, n ) ) THEN
174 info = -5
175 ELSE IF( lwork.LT.max( 1, nh ) .AND. .NOT.lquery ) THEN
176 info = -8
177 END IF
178*
179 IF( info.EQ.0 ) THEN
180 nb = ilaenv( 1, 'CUNGQR', ' ', nh, nh, nh, -1 )
181 lwkopt = max( 1, nh )*nb
182 work( 1 ) = sroundup_lwork(lwkopt)
183 END IF
184*
185 IF( info.NE.0 ) THEN
186 CALL xerbla( 'CUNGHR', -info )
187 RETURN
188 ELSE IF( lquery ) THEN
189 RETURN
190 END IF
191*
192* Quick return if possible
193*
194 IF( n.EQ.0 ) THEN
195 work( 1 ) = 1
196 RETURN
197 END IF
198*
199* Shift the vectors which define the elementary reflectors one
200* column to the right, and set the first ilo and the last n-ihi
201* rows and columns to those of the unit matrix
202*
203 DO 40 j = ihi, ilo + 1, -1
204 DO 10 i = 1, j - 1
205 a( i, j ) = zero
206 10 CONTINUE
207 DO 20 i = j + 1, ihi
208 a( i, j ) = a( i, j-1 )
209 20 CONTINUE
210 DO 30 i = ihi + 1, n
211 a( i, j ) = zero
212 30 CONTINUE
213 40 CONTINUE
214 DO 60 j = 1, ilo
215 DO 50 i = 1, n
216 a( i, j ) = zero
217 50 CONTINUE
218 a( j, j ) = one
219 60 CONTINUE
220 DO 80 j = ihi + 1, n
221 DO 70 i = 1, n
222 a( i, j ) = zero
223 70 CONTINUE
224 a( j, j ) = one
225 80 CONTINUE
226*
227 IF( nh.GT.0 ) THEN
228*
229* Generate Q(ilo+1:ihi,ilo+1:ihi)
230*
231 CALL cungqr( nh, nh, nh, a( ilo+1, ilo+1 ), lda, tau( ilo ),
232 $ work, lwork, iinfo )
233 END IF
234 work( 1 ) = sroundup_lwork(lwkopt)
235 RETURN
236*
237* End of CUNGHR
238*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
integer function ilaenv(ispec, name, opts, n1, n2, n3, n4)
ILAENV
Definition ilaenv.f:162
real function sroundup_lwork(lwork)
SROUNDUP_LWORK
subroutine cungqr(m, n, k, a, lda, tau, work, lwork, info)
CUNGQR
Definition cungqr.f:128
Here is the call graph for this function:
Here is the caller graph for this function: