dsptrd - metric tridiagonal form T by an orthogonal similarity transformation
SUBROUTINE DSPTRD(UPLO, N, AP, D, E, TAU, INFO) CHARACTER*1 UPLO INTEGER N, INFO DOUBLE PRECISION AP(*), D(*), E(*), TAU(*) SUBROUTINE DSPTRD_64(UPLO, N, AP, D, E, TAU, INFO) CHARACTER*1 UPLO INTEGER*8 N, INFO DOUBLE PRECISION AP(*), D(*), E(*), TAU(*) F95 INTERFACE SUBROUTINE SPTRD(UPLO, N, AP, D, E, TAU, INFO) CHARACTER(LEN=1) :: UPLO INTEGER :: N, INFO REAL(8), DIMENSION(:) :: AP, D, E, TAU SUBROUTINE SPTRD_64(UPLO, N, AP, D, E, TAU, INFO) CHARACTER(LEN=1) :: UPLO INTEGER(8) :: N, INFO REAL(8), DIMENSION(:) :: AP, D, E, TAU C INTERFACE #include <sunperf.h> void dsptrd(char uplo, int n, double *ap, double *d, double *e, double *tau, int *info); void dsptrd_64(char uplo, long n, double *ap, double *d, double *e, double *tau, long *info);
Oracle Solaris Studio Performance Library dsptrd(3P)
NAME
dsptrd - reduce a real symmetric matrix A stored in packed form to sym-
metric tridiagonal form T by an orthogonal similarity transformation
SYNOPSIS
SUBROUTINE DSPTRD(UPLO, N, AP, D, E, TAU, INFO)
CHARACTER*1 UPLO
INTEGER N, INFO
DOUBLE PRECISION AP(*), D(*), E(*), TAU(*)
SUBROUTINE DSPTRD_64(UPLO, N, AP, D, E, TAU, INFO)
CHARACTER*1 UPLO
INTEGER*8 N, INFO
DOUBLE PRECISION AP(*), D(*), E(*), TAU(*)
F95 INTERFACE
SUBROUTINE SPTRD(UPLO, N, AP, D, E, TAU, INFO)
CHARACTER(LEN=1) :: UPLO
INTEGER :: N, INFO
REAL(8), DIMENSION(:) :: AP, D, E, TAU
SUBROUTINE SPTRD_64(UPLO, N, AP, D, E, TAU, INFO)
CHARACTER(LEN=1) :: UPLO
INTEGER(8) :: N, INFO
REAL(8), DIMENSION(:) :: AP, D, E, TAU
C INTERFACE
#include <sunperf.h>
void dsptrd(char uplo, int n, double *ap, double *d, double *e, double
*tau, int *info);
void dsptrd_64(char uplo, long n, double *ap, double *d, double *e,
double *tau, long *info);
PURPOSE
dsptrd reduces a real symmetric matrix A stored in packed form to sym-
metric 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.
AP (input/output)
Double precision array, dimension (N*(N+1)/2) On entry, the
upper or lower triangle of the symmetric matrix A, packed
columnwise in a linear array. The j-th column of A is stored
in the array AP as follows: if UPLO = 'U', AP(i + (j-1)*j/2)
= A(i,j) for 1<=i<=j; if UPLO = 'L', AP(i + (j-1)*(2*n-j)/2)
= A(i,j) for j<=i<=n. On exit, if UPLO = 'U', the diagonal
and first superdiagonal of A are overwritten by the corre-
sponding elements of the tridiagonal matrix T, and the ele-
ments above the first superdiagonal, with the array TAU, rep-
resent 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
tridiagonal matrix T, and the elements below the first subdi-
agonal, with the array TAU, represent the orthogonal matrix Q
as a product of elementary reflectors. See Further Details.
D (output)
Double precision array, dimension (N) The diagonal elements
of the tridiagonal matrix T: D(i) = A(i,i).
E (output)
Double precision array, dimension (N-1) The off-diagonal ele-
ments 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)
Double precision array, dimension (N-1) 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 illegal 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 AP, overwrit-
ing A(1:i-1,i+1), and tau is stored 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 AP, overwrit-
ing A(i+2:n,i), and tau is stored in TAU(i).
7 Nov 2015 dsptrd(3P)