LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine chetrd ( character  UPLO,
integer  N,
complex, dimension( lda, * )  A,
integer  LDA,
real, dimension( * )  D,
real, dimension( * )  E,
complex, dimension( * )  TAU,
complex, dimension( * )  WORK,
integer  LWORK,
integer  INFO 
)

CHETRD

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

Purpose:
 CHETRD reduces a complex Hermitian matrix A to real symmetric
 tridiagonal form T by a unitary similarity transformation:
 Q**H * A * Q = T.
Parameters
[in]UPLO
          UPLO is CHARACTER*1
          = 'U':  Upper triangle of A is stored;
          = 'L':  Lower triangle of A is stored.
[in]N
          N is INTEGER
          The order of the matrix A.  N >= 0.
[in,out]A
          A is COMPLEX array, dimension (LDA,N)
          On entry, the Hermitian matrix A.  If UPLO = 'U', the leading
          N-by-N upper triangular part of A contains the upper
          triangular part of the matrix A, and the strictly lower
          triangular part of A is not referenced.  If UPLO = 'L', the
          leading N-by-N lower triangular part of A contains the lower
          triangular part of the matrix A, and the strictly upper
          triangular part of A is not referenced.
          On exit, if UPLO = 'U', the diagonal and first superdiagonal
          of A are overwritten by the corresponding elements of the
          tridiagonal matrix T, and the elements above the first
          superdiagonal, with the array TAU, represent the unitary
          matrix Q as a product of elementary reflectors; if UPLO
          = 'L', the diagonal and first subdiagonal of A are over-
          written by the corresponding elements of the tridiagonal
          matrix T, and the elements below the first subdiagonal, with
          the array TAU, represent the unitary matrix Q as a product
          of elementary reflectors. See Further Details.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.  LDA >= max(1,N).
[out]D
          D is REAL array, dimension (N)
          The diagonal elements of the tridiagonal matrix T:
          D(i) = A(i,i).
[out]E
          E is REAL array, dimension (N-1)
          The off-diagonal elements of the tridiagonal matrix T:
          E(i) = A(i,i+1) if UPLO = 'U', E(i) = A(i+1,i) if UPLO = 'L'.
[out]TAU
          TAU is COMPLEX array, dimension (N-1)
          The scalar factors of the elementary reflectors (see Further
          Details).
[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 >= 1.
          For optimum performance LWORK >= N*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
Further Details:
  If UPLO = 'U', the matrix Q is represented as a product of elementary
  reflectors

     Q = H(n-1) . . . H(2) H(1).

  Each H(i) has the form

     H(i) = I - tau * v * v**H

  where tau is a complex scalar, and v is a complex vector with
  v(i+1:n) = 0 and v(i) = 1; v(1:i-1) is stored on exit in
  A(1:i-1,i+1), and tau in TAU(i).

  If UPLO = 'L', the matrix Q is represented as a product of elementary
  reflectors

     Q = H(1) H(2) . . . H(n-1).

  Each H(i) has the form

     H(i) = I - tau * v * v**H

  where tau is a complex scalar, and v is a complex vector with
  v(1:i) = 0 and v(i+1) = 1; v(i+2:n) is stored on exit in A(i+2:n,i),
  and tau in TAU(i).

  The contents of A on exit are illustrated by the following examples
  with n = 5:

  if UPLO = 'U':                       if UPLO = 'L':

    (  d   e   v2  v3  v4 )              (  d                  )
    (      d   e   v3  v4 )              (  e   d              )
    (          d   e   v4 )              (  v1  e   d          )
    (              d   e  )              (  v1  v2  e   d      )
    (                  d  )              (  v1  v2  v3  e   d  )

  where d and e denote diagonal and off-diagonal elements of T, and vi
  denotes an element of the vector defining H(i).

Definition at line 194 of file chetrd.f.

194 *
195 * -- LAPACK computational routine (version 3.4.0) --
196 * -- LAPACK is a software package provided by Univ. of Tennessee, --
197 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
198 * November 2011
199 *
200 * .. Scalar Arguments ..
201  CHARACTER uplo
202  INTEGER info, lda, lwork, n
203 * ..
204 * .. Array Arguments ..
205  REAL d( * ), e( * )
206  COMPLEX a( lda, * ), tau( * ), work( * )
207 * ..
208 *
209 * =====================================================================
210 *
211 * .. Parameters ..
212  REAL one
213  parameter ( one = 1.0e+0 )
214  COMPLEX cone
215  parameter ( cone = ( 1.0e+0, 0.0e+0 ) )
216 * ..
217 * .. Local Scalars ..
218  LOGICAL lquery, upper
219  INTEGER i, iinfo, iws, j, kk, ldwork, lwkopt, nb,
220  $ nbmin, nx
221 * ..
222 * .. External Subroutines ..
223  EXTERNAL cher2k, chetd2, clatrd, xerbla
224 * ..
225 * .. Intrinsic Functions ..
226  INTRINSIC max
227 * ..
228 * .. External Functions ..
229  LOGICAL lsame
230  INTEGER ilaenv
231  EXTERNAL lsame, ilaenv
232 * ..
233 * .. Executable Statements ..
234 *
235 * Test the input parameters
236 *
237  info = 0
238  upper = lsame( uplo, 'U' )
239  lquery = ( lwork.EQ.-1 )
240  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
241  info = -1
242  ELSE IF( n.LT.0 ) THEN
243  info = -2
244  ELSE IF( lda.LT.max( 1, n ) ) THEN
245  info = -4
246  ELSE IF( lwork.LT.1 .AND. .NOT.lquery ) THEN
247  info = -9
248  END IF
249 *
250  IF( info.EQ.0 ) THEN
251 *
252 * Determine the block size.
253 *
254  nb = ilaenv( 1, 'CHETRD', uplo, n, -1, -1, -1 )
255  lwkopt = n*nb
256  work( 1 ) = lwkopt
257  END IF
258 *
259  IF( info.NE.0 ) THEN
260  CALL xerbla( 'CHETRD', -info )
261  RETURN
262  ELSE IF( lquery ) THEN
263  RETURN
264  END IF
265 *
266 * Quick return if possible
267 *
268  IF( n.EQ.0 ) THEN
269  work( 1 ) = 1
270  RETURN
271  END IF
272 *
273  nx = n
274  iws = 1
275  IF( nb.GT.1 .AND. nb.LT.n ) THEN
276 *
277 * Determine when to cross over from blocked to unblocked code
278 * (last block is always handled by unblocked code).
279 *
280  nx = max( nb, ilaenv( 3, 'CHETRD', uplo, n, -1, -1, -1 ) )
281  IF( nx.LT.n ) THEN
282 *
283 * Determine if workspace is large enough for blocked code.
284 *
285  ldwork = n
286  iws = ldwork*nb
287  IF( lwork.LT.iws ) THEN
288 *
289 * Not enough workspace to use optimal NB: determine the
290 * minimum value of NB, and reduce NB or force use of
291 * unblocked code by setting NX = N.
292 *
293  nb = max( lwork / ldwork, 1 )
294  nbmin = ilaenv( 2, 'CHETRD', uplo, n, -1, -1, -1 )
295  IF( nb.LT.nbmin )
296  $ nx = n
297  END IF
298  ELSE
299  nx = n
300  END IF
301  ELSE
302  nb = 1
303  END IF
304 *
305  IF( upper ) THEN
306 *
307 * Reduce the upper triangle of A.
308 * Columns 1:kk are handled by the unblocked method.
309 *
310  kk = n - ( ( n-nx+nb-1 ) / nb )*nb
311  DO 20 i = n - nb + 1, kk + 1, -nb
312 *
313 * Reduce columns i:i+nb-1 to tridiagonal form and form the
314 * matrix W which is needed to update the unreduced part of
315 * the matrix
316 *
317  CALL clatrd( uplo, i+nb-1, nb, a, lda, e, tau, work,
318  $ ldwork )
319 *
320 * Update the unreduced submatrix A(1:i-1,1:i-1), using an
321 * update of the form: A := A - V*W**H - W*V**H
322 *
323  CALL cher2k( uplo, 'No transpose', i-1, nb, -cone,
324  $ a( 1, i ), lda, work, ldwork, one, a, lda )
325 *
326 * Copy superdiagonal elements back into A, and diagonal
327 * elements into D
328 *
329  DO 10 j = i, i + nb - 1
330  a( j-1, j ) = e( j-1 )
331  d( j ) = a( j, j )
332  10 CONTINUE
333  20 CONTINUE
334 *
335 * Use unblocked code to reduce the last or only block
336 *
337  CALL chetd2( uplo, kk, a, lda, d, e, tau, iinfo )
338  ELSE
339 *
340 * Reduce the lower triangle of A
341 *
342  DO 40 i = 1, n - nx, nb
343 *
344 * Reduce columns i:i+nb-1 to tridiagonal form and form the
345 * matrix W which is needed to update the unreduced part of
346 * the matrix
347 *
348  CALL clatrd( uplo, n-i+1, nb, a( i, i ), lda, e( i ),
349  $ tau( i ), work, ldwork )
350 *
351 * Update the unreduced submatrix A(i+nb:n,i+nb:n), using
352 * an update of the form: A := A - V*W**H - W*V**H
353 *
354  CALL cher2k( uplo, 'No transpose', n-i-nb+1, nb, -cone,
355  $ a( i+nb, i ), lda, work( nb+1 ), ldwork, one,
356  $ a( i+nb, i+nb ), lda )
357 *
358 * Copy subdiagonal elements back into A, and diagonal
359 * elements into D
360 *
361  DO 30 j = i, i + nb - 1
362  a( j+1, j ) = e( j )
363  d( j ) = a( j, j )
364  30 CONTINUE
365  40 CONTINUE
366 *
367 * Use unblocked code to reduce the last or only block
368 *
369  CALL chetd2( uplo, n-i+1, a( i, i ), lda, d( i ), e( i ),
370  $ tau( i ), iinfo )
371  END IF
372 *
373  work( 1 ) = lwkopt
374  RETURN
375 *
376 * End of CHETRD
377 *
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine chetd2(UPLO, N, A, LDA, D, E, TAU, INFO)
CHETD2 reduces a Hermitian matrix to real symmetric tridiagonal form by an unitary similarity transfo...
Definition: chetd2.f:177
subroutine clatrd(UPLO, N, NB, A, LDA, E, TAU, W, LDW)
CLATRD reduces the first nb rows and columns of a symmetric/Hermitian matrix A to real tridiagonal fo...
Definition: clatrd.f:201
subroutine cher2k(UPLO, TRANS, N, K, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
CHER2K
Definition: cher2k.f:199
integer function ilaenv(ISPEC, NAME, OPTS, N1, N2, N3, N4)
Definition: tstiee.f:83
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55

Here is the call graph for this function:

Here is the caller graph for this function: