sgehd2 - reduce a general square matrix to upper Hessenberg form using an unblocked algorithm
SUBROUTINE SGEHD2(N, ILO, IHI, A, LDA, TAU, WORK, INFO) INTEGER IHI, ILO, INFO, LDA, N REAL A(LDA,*), TAU(*), WORK(*) SUBROUTINE SGEHD2_64(N, ILO, IHI, A, LDA, TAU, WORK, INFO) INTEGER*8 IHI, ILO, INFO, LDA, N REAL A(LDA,*), TAU(*), WORK(*) F95 INTERFACE SUBROUTINE GEHD2(N, ILO, IHI, A, LDA, TAU, WORK, INFO) REAL, DIMENSION(:,:) :: A INTEGER :: N, ILO, IHI, LDA, INFO REAL, DIMENSION(:) :: TAU, WORK SUBROUTINE GEHD2_64(N, ILO, IHI, A, LDA, TAU, WORK, INFO) REAL, DIMENSION(:,:) :: A INTEGER(8) :: N, ILO, IHI, LDA, INFO REAL, DIMENSION(:) :: TAU, WORK C INTERFACE #include <sunperf.h> void sgehd2 (int n, int ilo, int ihi, float *a, int lda, float *tau, int *info); void sgehd2_64 (long n, long ilo, long ihi, float *a, long lda, float *tau, long *info);
Oracle Solaris Studio Performance Library                           sgehd2(3P)
NAME
       sgehd2  - reduce a general square matrix to upper Hessenberg form using
       an unblocked algorithm
SYNOPSIS
       SUBROUTINE SGEHD2(N, ILO, IHI, A, LDA, TAU, WORK, INFO)
       INTEGER IHI, ILO, INFO, LDA, N
       REAL A(LDA,*), TAU(*), WORK(*)
       SUBROUTINE SGEHD2_64(N, ILO, IHI, A, LDA, TAU, WORK, INFO)
       INTEGER*8 IHI, ILO, INFO, LDA, N
       REAL A(LDA,*), TAU(*), WORK(*)
   F95 INTERFACE
       SUBROUTINE GEHD2(N, ILO, IHI, A, LDA, TAU, WORK, INFO)
       REAL, DIMENSION(:,:) :: A
       INTEGER :: N, ILO, IHI, LDA, INFO
       REAL, DIMENSION(:) :: TAU, WORK
       SUBROUTINE GEHD2_64(N, ILO, IHI, A, LDA, TAU, WORK, INFO)
       REAL, DIMENSION(:,:) :: A
       INTEGER(8) :: N, ILO, IHI, LDA, INFO
       REAL, DIMENSION(:) :: TAU, WORK
   C INTERFACE
       #include <sunperf.h>
       void sgehd2 (int n, int ilo, int ihi, float *a, int  lda,  float  *tau,
                 int *info);
       void  sgehd2_64  (long n, long ilo, long ihi, float *a, long lda, float
                 *tau, long *info);
PURPOSE
       sgehd2 reduces a real general matrix A to upper Hessenberg form H by an
       orthogonal similarity transformation:  Q**T*A*Q=H.
ARGUMENTS
       N (input)
                 N is INTEGER
                 The order of the matrix A. N >= 0.
       ILO (input)
                 ILO is INTEGER
       IHI (input)
                 IHI is INTEGER
                 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 SGEBAL; otherwise they should be set to 1
                 and N respectively. See Further Details.
                 1 <= ILO <= IHI <= max(1,N).
       A (input/output)
                 A is REAL array, dimension (LDA,N)
                 On entry, the n by n general matrix to be reduced.
                 On exit, the upper triangle and the first  subdiagonal  of  A
                 are  overwritten  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
                 reflectors. See Further Details.
       LDA (input)
                 LDA is INTEGER
                 The leading dimension of the array A. LDA >= max(1,N).
       TAU (output)
                 TAU is REAL array, dimension (N-1)
                 The scalar factors of the elementary reflectors (see  Further
                 Details).
       WORK (output)
                 WORK is REAL array, dimension (N)
       INFO (output)
                 INFO is INTEGER
                 = 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**T
       where tau is a complex scalar, and v is a complex 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
       modified element of the upper Hessenberg matrix H, and vi denotes an
       element of the vector defining H(i).
                                  7 Nov 2015                        sgehd2(3P)