ssytrd - reduce a real symmetric matrix A to real symmetric tridiagonal form T by an orthogonal similarity transformation
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(*)
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
#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);
ssytrd reduces a real symmetric matrix A to real symmetric tridiagonal form T by an orthogonal similarity transformation: Q**T * A * Q = T.
= 'U': Upper triangle of A is stored;
= 'L': Lower triangle of A is stored.
D(i) = A(i,i).
E(i) = A(i,i+1) if UPLO = 'U', E(i) = A(i+1,i) if UPLO = 'L'.
WORK(1) returns the optimal LWORK.
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.
= 0: successful exit
< 0: if INFO = -i, the i-th argument had an illegal value
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).