Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

chptrd (3p)

Name

chptrd - reduce a complex Hermitian matrix A stored in packed form to real symmetric tridiagonal form T by a unitary similarity transforma- tion

Synopsis

SUBROUTINE CHPTRD(UPLO, N, AP, D, E, TAU, INFO)

CHARACTER*1 UPLO
COMPLEX AP(*), TAU(*)
INTEGER N, INFO
REAL D(*), E(*)

SUBROUTINE CHPTRD_64(UPLO, N, AP, D, E, TAU, INFO)

CHARACTER*1 UPLO
COMPLEX AP(*), TAU(*)
INTEGER*8 N, INFO
REAL D(*), E(*)




F95 INTERFACE
SUBROUTINE HPTRD(UPLO, N, AP, D, E, TAU, INFO)

CHARACTER(LEN=1) :: UPLO
COMPLEX, DIMENSION(:) :: AP, TAU
INTEGER :: N, INFO
REAL, DIMENSION(:) :: D, E

SUBROUTINE HPTRD_64(UPLO, N, AP, D, E, TAU, INFO)

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




C INTERFACE
#include <sunperf.h>

void  chptrd(char uplo, int n, complex *ap, float *d, float *e, complex
*tau, int *info);

void chptrd_64(char uplo, long n, complex *ap, float *d, float *e, com-
plex *tau, long *info);

Description

Oracle Solaris Studio Performance Library                           chptrd(3P)



NAME
       chptrd  -  reduce a complex Hermitian matrix A stored in packed form to
       real symmetric tridiagonal form T by a unitary  similarity  transforma-
       tion


SYNOPSIS
       SUBROUTINE CHPTRD(UPLO, N, AP, D, E, TAU, INFO)

       CHARACTER*1 UPLO
       COMPLEX AP(*), TAU(*)
       INTEGER N, INFO
       REAL D(*), E(*)

       SUBROUTINE CHPTRD_64(UPLO, N, AP, D, E, TAU, INFO)

       CHARACTER*1 UPLO
       COMPLEX AP(*), TAU(*)
       INTEGER*8 N, INFO
       REAL D(*), E(*)




   F95 INTERFACE
       SUBROUTINE HPTRD(UPLO, N, AP, D, E, TAU, INFO)

       CHARACTER(LEN=1) :: UPLO
       COMPLEX, DIMENSION(:) :: AP, TAU
       INTEGER :: N, INFO
       REAL, DIMENSION(:) :: D, E

       SUBROUTINE HPTRD_64(UPLO, N, AP, D, E, TAU, INFO)

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




   C INTERFACE
       #include <sunperf.h>

       void  chptrd(char uplo, int n, complex *ap, float *d, float *e, complex
                 *tau, int *info);

       void chptrd_64(char uplo, long n, complex *ap, float *d, float *e, com-
                 plex *tau, long *info);



PURPOSE
       chptrd  reduces  a  complex Hermitian matrix A stored in packed form to
       real symmetric tridiagonal form T by a unitary  similarity  transforma-
       tion: Q**H * 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) COMPLEX array, dimension (N*(N+1)/2)
                 On entry, the upper or lower triangle of the Hermitian 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  overwrit-
                 ten  by  the corresponding elements of the tridiagonal matrix
                 T, and the elements above the first superdiagonal,  with  the
                 array  TAU,  represent  the  unitary matrix Q as a product of
                 elementary reflectors; if UPLO = 'L', the diagonal and  first
                 subdiagonal  of A are over- written by the corresponding ele-
                 ments of the tridiagonal matrix T, and the elements below the
                 first  subdiagonal, with the array TAU, represent the unitary
                 matrix Q as a product of elementary reflectors.  See  Further
                 Details.


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


       E (output) REAL array, dimension (N-1)
                 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) COMPLEX 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 complex scalar, and v is a complex vector with v(i+1:n)
       = 0 and v(i) = 1;  v(1:i-1)  is  stored  on  exit  in  AP,  overwriting
       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 complex scalar, and v is a complex vector with v(1:i)  =
       0  and  v(i+1)  =  1;  v(i+2:n)  is  stored  on exit in AP, overwriting
       A(i+2:n,i), and tau is stored in TAU(i).




                                  7 Nov 2015                        chptrd(3P)