Contents


NAME

     ssytrd - reduce a real symmetric matrix A to real  symmetric
     tridiagonal  form  T by an orthogonal similarity transforma-
     tion

SYNOPSIS

     SUBROUTINE SSYTRD(UPLO, N, A, LDA, D, E, TAU, WORK, LWORK, INFO)

     CHARACTER * 1 UPLO
     INTEGER N, LDA, LWORK, INFO
     REAL A(LDA,*), D(*), E(*), TAU(*), WORK(*)

     SUBROUTINE SSYTRD_64(UPLO, N, A, LDA, D, E, TAU, WORK, LWORK, INFO)

     CHARACTER * 1 UPLO
     INTEGER*8 N, LDA, LWORK, INFO
     REAL A(LDA,*), D(*), E(*), TAU(*), WORK(*)

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

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

     SUBROUTINE SYTRD_64(UPLO, N, A, [LDA], D, E, TAU, [WORK], [LWORK],
            [INFO])

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

  C INTERFACE
     #include <sunperf.h>

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

     void ssytrd_64(char uplo, long n, float *a, long lda,  float
               *d, float *e, float *tau, long *info);

PURPOSE

     ssytrd reduces a real symmetric matrix A to  real  symmetric
     tridiagonal    form    T   by   an   orthogonal   similarity
     transformation:  Q**T * A * Q = T.

ARGUMENTS

     UPLO (input)
               = 'U':  Upper triangle of A is stored;
               = 'L':  Lower triangle of A is stored.

     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).

     WORK (workspace)
               On exit, if INFO = 0, WORK(1) returns the  optimal
               LWORK.

     LWORK (input)
               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.

     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).