Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dgehrd (3p)

Name

dgehrd - reduce a real general matrix A to upper Hessenberg form H by an orthogonal similarity transformation

Synopsis

SUBROUTINE DGEHRD(N, ILO, IHI, A, LDA, TAU, WORKIN, LWORKIN, INFO)

INTEGER N, ILO, IHI, LDA, LWORKIN, INFO
DOUBLE PRECISION A(LDA,*), TAU(*), WORKIN(*)

SUBROUTINE DGEHRD_64(N, ILO, IHI, A, LDA, TAU, WORKIN, LWORKIN, INFO)

INTEGER*8 N, ILO, IHI, LDA, LWORKIN, INFO
DOUBLE PRECISION A(LDA,*), TAU(*), WORKIN(*)




F95 INTERFACE
SUBROUTINE GEHRD(N, ILO, IHI, A, LDA, TAU, WORKIN, LWORKIN,
INFO)

INTEGER :: N, ILO, IHI, LDA, LWORKIN, INFO
REAL(8), DIMENSION(:) :: TAU, WORKIN
REAL(8), DIMENSION(:,:) :: A

SUBROUTINE GEHRD_64(N, ILO, IHI, A, LDA, TAU, WORKIN, LWORKIN,
INFO)

INTEGER(8) :: N, ILO, IHI, LDA, LWORKIN, INFO
REAL(8), DIMENSION(:) :: TAU, WORKIN
REAL(8), DIMENSION(:,:) :: A




C INTERFACE
#include <sunperf.h>

void dgehrd(int n, int ilo, int ihi, double *a, int lda,  double  *tau,
int *info);

void  dgehrd_64(long n, long ilo, long ihi, double *a, long lda, double
*tau, long *info);

Description

Oracle Solaris Studio Performance Library                           dgehrd(3P)



NAME
       dgehrd  -  reduce a real general matrix A to upper Hessenberg form H by
       an orthogonal similarity transformation


SYNOPSIS
       SUBROUTINE DGEHRD(N, ILO, IHI, A, LDA, TAU, WORKIN, LWORKIN, INFO)

       INTEGER N, ILO, IHI, LDA, LWORKIN, INFO
       DOUBLE PRECISION A(LDA,*), TAU(*), WORKIN(*)

       SUBROUTINE DGEHRD_64(N, ILO, IHI, A, LDA, TAU, WORKIN, LWORKIN, INFO)

       INTEGER*8 N, ILO, IHI, LDA, LWORKIN, INFO
       DOUBLE PRECISION A(LDA,*), TAU(*), WORKIN(*)




   F95 INTERFACE
       SUBROUTINE GEHRD(N, ILO, IHI, A, LDA, TAU, WORKIN, LWORKIN,
              INFO)

       INTEGER :: N, ILO, IHI, LDA, LWORKIN, INFO
       REAL(8), DIMENSION(:) :: TAU, WORKIN
       REAL(8), DIMENSION(:,:) :: A

       SUBROUTINE GEHRD_64(N, ILO, IHI, A, LDA, TAU, WORKIN, LWORKIN,
              INFO)

       INTEGER(8) :: N, ILO, IHI, LDA, LWORKIN, INFO
       REAL(8), DIMENSION(:) :: TAU, WORKIN
       REAL(8), DIMENSION(:,:) :: A




   C INTERFACE
       #include <sunperf.h>

       void dgehrd(int n, int ilo, int ihi, double *a, int lda,  double  *tau,
                 int *info);

       void  dgehrd_64(long n, long ilo, long ihi, double *a, long lda, double
                 *tau, long *info);



PURPOSE
       dgehrd reduces a real general matrix A to upper Hessenberg form H by an
       orthogonal similarity transformation:  Q' * A * Q = H .


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


       ILO (input)
                 It  is assumed that A is already upper triangular in rows and
                 columns 1:ILO-1 and IHI+1:N. ILO and IHI are normally set  by
                 a  previous call to DGEBAL; otherwise they should be set to 1
                 and N respectively. See Further Details.


       IHI (input)
                 See the description of ILO.


       A (input/output)
                 On entry, the N-by-N general matrix to be reduced.  On  exit,
                 the  upper  triangle and the first subdiagonal of A are over-
                 written with the upper Hessenberg matrix H, and the  elements
                 below  the  first  subdiagonal, with the array TAU, represent
                 the orthogonal matrix Q as a product  of  elementary  reflec-
                 tors. See Further Details.


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


       TAU (output) REAL array, dimension (N-1)
                 The  scalar factors of the elementary reflectors (see Further
                 Details). Elements 1:ILO-1 and IHI:N-1  of  TAU  are  set  to
                 zero.


       WORKIN (workspace)
                 On  exit, if INFO = 0, WORKIN(1) returns the optimal LWORKIN.


       LWORKIN (input)
                 The length of the array WORKIN.  LWORKIN  >=  max(1,N).   For
                 optimum  performance LWORKIN >= N*NB, where NB is the optimal
                 blocksize.

                 If LWORKIN = -1, then a workspace query is assumed; the  rou-
                 tine  only  calculates  the optimal size of the WORKIN array,
                 returns this value as the first entry of  the  WORKIN  array,
                 and  no error message related to LWORKIN is issued by XERBLA.


       INFO (output)
                 = 0:  successful exit
                 < 0:  if INFO = -i, the i-th argument had an illegal value.

FURTHER DETAILS
       The matrix Q is  represented  as  a  product  of  (ihi-ilo)  elementary
       reflectors

          Q = H(ilo) H(ilo+1) . . . H(ihi-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, v(i+1) = 1 and v(ihi+1:n) = 0; v(i+2:ihi) is stored on exit
       in A(i+2:ihi,i), and tau in TAU(i).

       The contents of A are illustrated by the following example, with n = 7,
       ilo = 2 and ihi = 6:

       on entry,                on exit,

       (a  a  a  a  a  a  a)    (a  a   h   h   h  h  a)
       (   a  a  a  a  a  a)    (   a   h   h   h  h  a)
       (   a  a  a  a  a  a)    (   h   h   h   h  h  h)
       (   a  a  a  a  a  a)    (   v2  h   h   h  h  h)
       (   a  a  a  a  a  a)    (   v2  v3  h   h  h  h)
       (   a  a  a  a  a  a)    (   v2  v3  v4  h  h  h)
       (                  a)    (                     a)

       where  a denotes an element of the original matrix A, h denotes a modi-
       fied element of the upper Hessenberg matrix H, and vi denotes  an  ele-
       ment of the vector defining H(i).




                                  7 Nov 2015                        dgehrd(3P)