LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
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.
Date
November 2011

Definition at line 128 of file cunghr.f.

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

Here is the call graph for this function:

Here is the caller graph for this function: