Contents


NAME

     dsytd2 - reduce a real symmetric matrix A to symmetric  tri-
     diagonal form T by an orthogonal similarity transformation

SYNOPSIS

     SUBROUTINE DSYTD2(UPLO, N, A, LDA, D, E, TAU, INFO)

     CHARACTER * 1 UPLO
     INTEGER N, LDA, INFO
     DOUBLE PRECISION A(LDA,*), D(*), E(*), TAU(*)

     SUBROUTINE DSYTD2_64(UPLO, N, A, LDA, D, E, TAU, INFO)

     CHARACTER * 1 UPLO
     INTEGER*8 N, LDA, INFO
     DOUBLE PRECISION A(LDA,*), D(*), E(*), TAU(*)

  F95 INTERFACE
     SUBROUTINE SYTD2(UPLO, N, A, [LDA], D, E, TAU, [INFO])

     CHARACTER(LEN=1) :: UPLO
     INTEGER :: N, LDA, INFO
     REAL(8), DIMENSION(:) :: D, E, TAU
     REAL(8), DIMENSION(:,:) :: A

     SUBROUTINE SYTD2_64(UPLO, N, A, [LDA], D, E, TAU, [INFO])

     CHARACTER(LEN=1) :: UPLO
     INTEGER(8) :: N, LDA, INFO
     REAL(8), DIMENSION(:) :: D, E, TAU
     REAL(8), DIMENSION(:,:) :: A

  C INTERFACE
     #include <sunperf.h>

     void dsytd2(char uplo, int n, double *a, int lda, double *d,
               double *e, double *tau, int *info);

     void dsytd2_64(char uplo, long n, double *a, long lda,  dou-
               ble *d, double *e, double *tau, long *info);

PURPOSE

     dsytd2 reduces a real symmetric matrix A to symmetric tridi-
     agonal form T by an orthogonal similarity transformation: Q'
     * A * Q = T.

ARGUMENTS

     UPLO (input)
               Specifies whether the upper  or  lower  triangular
               part of the symmetric matrix A is stored:
               = 'U':  Upper triangular
               = 'L':  Lower triangular

     N (input) The order of the matrix A.  N >= 0.

     A (input) On entry, the symmetric matrix A.  If UPLO =  'U',
               the leading n-by-n upper triangular part of A con-
               tains 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 tri-
               angular 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 super-
               diagonal of A are overwritten by the corresponding
               elements of the tridiagonal matrix T, and the ele-
               ments  above  the  first  superdiagonal,  with the
               array TAU, represent the orthogonal 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 tri-
               diagonal matrix T,  and  the  elements  below  the
               first  subdiagonal,  with the array TAU, represent
               the orthogonal matrix Q as a product of elementary
               reflectors. See Further Details.

     LDA (input)
               The leading dimension of  the  array  A.   LDA  >=
               max(1,N).

     D (output)
               The diagonal elements of the tridiagonal matrix T:
               D(i) = A(i,i).

     E (output)
               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'.

     TAU (output)
               The scalar factors of  the  elementary  reflectors
               (see Further Details).
     INFO (output)
               = 0:  successful exit
               < 0:  if INFO = -i, the i-th argument had an ille-
               gal value.

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'

     where tau is a real scalar, and v is a real 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'

     where tau is a real scalar, and v is a real 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).