Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

zhetd2 (3p)

Name

zhetd2 - reduce a Hermitian matrix to real symmetric tridiagonal form by an unitary similarity transformation (unblocked algorithm)

Synopsis

SUBROUTINE ZHETD2(UPLO, N, A, LDA, D, E, TAU, INFO)


CHARACTER*1 UPLO

INTEGER INFO, LDA, N

DOUBLE PRECISION D(*), E(*)

DOUBLE COMPLEX A(LDA,*), TAU(*)


SUBROUTINE ZHETD2_64(UPLO, N, A, LDA, D, E, TAU, INFO)


CHARACTER*1 UPLO

INTEGER*8 INFO, LDA, N

DOUBLE PRECISION D(*), E(*)

DOUBLE COMPLEX A(LDA,*), TAU(*)


F95 INTERFACE
SUBROUTINE HETD2(UPLO, N, A, LDA, D, E, TAU, INFO)


INTEGER :: N, LDA, INFO

CHARACTER(LEN=1) :: UPLO

COMPLEX(8), DIMENSION(:) :: TAU

REAL(8), DIMENSION(:) :: D, E

COMPLEX(8), DIMENSION(:,:) :: A


SUBROUTINE HETD2_64(UPLO, N, A, LDA, D, E, TAU, INFO)


INTEGER(8) :: N, LDA, INFO

CHARACTER(LEN=1) :: UPLO

COMPLEX(8), DIMENSION(:) :: TAU

REAL(8), DIMENSION(:) :: D, E

COMPLEX(8), DIMENSION(:,:) :: A


C INTERFACE
#include <sunperf.h>

void zhetd2 (char uplo, int n, doublecomplex *a, int  lda,  double  *d,
double *e, doublecomplex *tau, int *info);


void  zhetd2_64  (char uplo, long n, doublecomplex *a, long lda, double
*d, double *e, doublecomplex *tau, long *info);

Description

Oracle Solaris Studio Performance Library                           zhetd2(3P)



NAME
       zhetd2  -  reduce a Hermitian matrix to real symmetric tridiagonal form
       by an unitary similarity transformation (unblocked algorithm)


SYNOPSIS
       SUBROUTINE ZHETD2(UPLO, N, A, LDA, D, E, TAU, INFO)


       CHARACTER*1 UPLO

       INTEGER INFO, LDA, N

       DOUBLE PRECISION D(*), E(*)

       DOUBLE COMPLEX A(LDA,*), TAU(*)


       SUBROUTINE ZHETD2_64(UPLO, N, A, LDA, D, E, TAU, INFO)


       CHARACTER*1 UPLO

       INTEGER*8 INFO, LDA, N

       DOUBLE PRECISION D(*), E(*)

       DOUBLE COMPLEX A(LDA,*), TAU(*)


   F95 INTERFACE
       SUBROUTINE HETD2(UPLO, N, A, LDA, D, E, TAU, INFO)


       INTEGER :: N, LDA, INFO

       CHARACTER(LEN=1) :: UPLO

       COMPLEX(8), DIMENSION(:) :: TAU

       REAL(8), DIMENSION(:) :: D, E

       COMPLEX(8), DIMENSION(:,:) :: A


       SUBROUTINE HETD2_64(UPLO, N, A, LDA, D, E, TAU, INFO)


       INTEGER(8) :: N, LDA, INFO

       CHARACTER(LEN=1) :: UPLO

       COMPLEX(8), DIMENSION(:) :: TAU

       REAL(8), DIMENSION(:) :: D, E

       COMPLEX(8), DIMENSION(:,:) :: A


   C INTERFACE
       #include <sunperf.h>

       void zhetd2 (char uplo, int n, doublecomplex *a, int  lda,  double  *d,
                 double *e, doublecomplex *tau, int *info);


       void  zhetd2_64  (char uplo, long n, doublecomplex *a, long lda, double
                 *d, double *e, doublecomplex *tau, long *info);


PURPOSE
       zhetd2 reduces a complex Hermitian matrix A to real symmetric tridiago-
       nal form T by a unitary similarity transformation: Q**H*A*Q=T.


ARGUMENTS
       UPLO (input)
                 UPLO is CHARACTER*1
                 Specifies  whether  the upper or lower triangular part of the
                 Hermitian matrix A is stored:
                 = 'U':  Upper triangular,
                 = 'L':  Lower triangular.


       N (input)
                 N is INTEGER
                 The order of the matrix A. N >= 0.


       A (input/output)
                 A is COMPLEX*16 array, dimension (LDA,N)
                 On entry, the Hermitian matrix A. If UPLO = 'U', the  leading
                 N-by-N upper triangular part of A contains the upper triangu-
                 lar 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 super-
                 diagonal,  with the array TAU, represent the unitary matrix Q
                 as a product of elementary reflectors; if UPLO='L', the diag-
                 onal  and  first  subdiagonal of A are overwritten written by
                 the corresponding elements 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.


       LDA (input)
                 LDA is INTEGER
                 The leading dimension of the array A. LDA >= max(1,N).


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


       E (output)
                 E is DOUBLE PRECISION 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)
                 TAU is COMPLEX*16 array, dimension (N-1)
                 The scalar factors of the elementary reflectors (see  Further
                 Details).


       INFO (output)
                 INFO is INTEGER
                 = 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**H

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

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



                                  7 Nov 2015                        zhetd2(3P)