dsytd2


NAME

dsytd2 - reduce a real symmetric matrix A to symmetric tridiagonal 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, double *d, double *e, double *tau, long *info);


PURPOSE

dsytd2 reduces a real symmetric matrix A to symmetric tridiagonal 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:

* 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 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 orthogonal matrix Q as a product of elementary reflectors; if UPLO

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