Contents


NAME

     dorghr - generate  a  real  orthogonal  matrix  Q  which  is
     defined  as  the product of IHI-ILO elementary reflectors of
     order N, as returned by SGEHRD

SYNOPSIS

     SUBROUTINE DORGHR(N, ILO, IHI, A, LDA, TAU, WORK, LWORK, INFO)

     INTEGER N, ILO, IHI, LDA, LWORK, INFO
     DOUBLE PRECISION A(LDA,*), TAU(*), WORK(*)

     SUBROUTINE DORGHR_64(N, ILO, IHI, A, LDA, TAU, WORK, LWORK, INFO)

     INTEGER*8 N, ILO, IHI, LDA, LWORK, INFO
     DOUBLE PRECISION A(LDA,*), TAU(*), WORK(*)

  F95 INTERFACE
     SUBROUTINE ORGHR([N], ILO, IHI, A, [LDA], TAU, [WORK], [LWORK], [INFO])

     INTEGER :: N, ILO, IHI, LDA, LWORK, INFO
     REAL(8), DIMENSION(:) :: TAU, WORK
     REAL(8), DIMENSION(:,:) :: A

     SUBROUTINE ORGHR_64([N], ILO, IHI, A, [LDA], TAU, [WORK], [LWORK],
            [INFO])

     INTEGER(8) :: N, ILO, IHI, LDA, LWORK, INFO
     REAL(8), DIMENSION(:) :: TAU, WORK
     REAL(8), DIMENSION(:,:) :: A

  C INTERFACE
     #include <sunperf.h>

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

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

PURPOSE

     dorghr generates a real orthogonal matrix Q which is defined
     as  the product of IHI-ILO elementary reflectors of order N,
     as returned by SGEHRD:

     Q = H(ilo) H(ilo+1) . . . H(ihi-1).

ARGUMENTS

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

     ILO (input)
               ILO and IHI must have the same values  as  in  the
               previous  call  of  SGEHRD. Q is equal to the unit
               matrix      except      in      the      submatrix
               Q(ilo+1:ihi,ilo+1:ihi).   1 <= ILO <= IHI <= N, if
               N > 0; ILO=1 and IHI=0, if N=0.

     IHI (input)
               See the description of ILO.

     A (input/output)
               On entry, the vectors which define the  elementary
               reflectors,  as  returned by SGEHRD.  On exit, the
               N-by-N orthogonal matrix Q.

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

     TAU (input)
               TAU(i) must contain the scalar factor of the  ele-
               mentary reflector H(i), as returned by SGEHRD.

     WORK (workspace)
               On exit, if INFO = 0, WORK(1) returns the  optimal
               LWORK.

     LWORK (input)
               The dimension of the array WORK. LWORK >= IHI-ILO.
               For  optimum  performance  LWORK  >= (IHI-ILO)*NB,
               where NB is the optimal blocksize.

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

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