Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dlaed8 (3p)

Name

dlaed8 - edc, when the original matrix is dense

Synopsis

SUBROUTINE DLAED8(ICOMPQ, K, N, QSIZ, D, Q, LDQ, INDXQ, RHO, CUTPNT, Z,
DLAMDA,  Q2,  LDQ2,  W,  PERM, GIVPTR, GIVCOL, GIVNUM, INDXP,
INDX, INFO)


INTEGER CUTPNT, GIVPTR, ICOMPQ, INFO, K, LDQ, LDQ2, N, QSIZ

DOUBLE PRECISION RHO

INTEGER GIVCOL(2,*), INDX(*), INDXP(*), INDXQ(*), PERM(*)

DOUBLE PRECISION D(*), DLAMDA(*),  GIVNUM(2,*),  Q(LDQ,*),  Q2(LDQ2,*),
W(*), Z(*)


SUBROUTINE DLAED8_64(ICOMPQ, K, N, QSIZ, D, Q, LDQ, INDXQ, RHO, CUTPNT,
Z, DLAMDA, Q2, LDQ2, W, PERM, GIVPTR, GIVCOL, GIVNUM,  INDXP,
INDX, INFO)


INTEGER*8 CUTPNT, GIVPTR, ICOMPQ, INFO, K, LDQ, LDQ2, N, QSIZ

DOUBLE PRECISION RHO

INTEGER*8 GIVCOL(2,*), INDX(*), INDXP(*), INDXQ(*), PERM(*)

DOUBLE  PRECISION  D(*),  DLAMDA(*), GIVNUM(2,*), Q(LDQ,*), Q2(LDQ2,*),
W(*), Z(*)


F95 INTERFACE
SUBROUTINE LAED8( ICOMPQ, K, N, QSIZ, D, Q, LDQ, INDXQ, RHO, CUTPNT, Z,
DLAMDA,  Q2,  LDQ2,  W,  PERM, GIVPTR, GIVCOL, GIVNUM, INDXP,
INDX, INFO )


INTEGER :: ICOMPQ, K, N, QSIZ, LDQ, CUTPNT, LDQ2, GIVPTR, INFO

INTEGER, DIMENSION(:) :: INDXQ, PERM, INDXP, INDX

REAL(8), DIMENSION(:,:) :: Q, Q2, GIVNUM

REAL(8), DIMENSION(:) :: D, Z, DLAMDA, W

INTEGER, DIMENSION(:,:) :: GIVCOL

REAL(8) :: RHO


SUBROUTINE LAED8_64(ICOMPQ, K, N, QSIZ, D, Q, LDQ, INDXQ, RHO,  CUTPNT,
Z,  DLAMDA, Q2, LDQ2, W, PERM, GIVPTR, GIVCOL, GIVNUM, INDXP,
INDX, INFO)


INTEGER(8) :: ICOMPQ, K, N, QSIZ, LDQ, CUTPNT, LDQ2, GIVPTR, INFO

INTEGER(8), DIMENSION(:) :: INDXQ, PERM, INDXP, INDX

REAL(8), DIMENSION(:,:) :: Q, Q2, GIVNUM

REAL(8), DIMENSION(:) :: D, Z, DLAMDA, W

INTEGER(8), DIMENSION(:,:) :: GIVCOL

REAL(8) :: RHO


C INTERFACE
#include <sunperf.h>

void dlaed8 (int icompq, int *k, int n, int qsiz, double *d, double *q,
int ldq, int *indxq, double *rho, int cutpnt, double *z, dou-
ble *dlamda, double *q2, int ldq2, double *w, int *perm,  int
*givptr, int *givcol, double *givnum, int *info);


void  dlaed8_64  (long  icompq,  long *k, long n, long qsiz, double *d,
double *q, long ldq, long *indxq, double *rho,  long  cutpnt,
double  *z, double *dlamda, double *q2, long ldq2, double *w,
long *perm, long *givptr, long *givcol, double *givnum,  long
*info);

Description

Oracle Solaris Studio Performance Library                           dlaed8(3P)



NAME
       dlaed8  - merge eigenvalues and deflates secular equation. Used by dst-
       edc, when the original matrix is dense


SYNOPSIS
       SUBROUTINE DLAED8(ICOMPQ, K, N, QSIZ, D, Q, LDQ, INDXQ, RHO, CUTPNT, Z,
                 DLAMDA,  Q2,  LDQ2,  W,  PERM, GIVPTR, GIVCOL, GIVNUM, INDXP,
                 INDX, INFO)


       INTEGER CUTPNT, GIVPTR, ICOMPQ, INFO, K, LDQ, LDQ2, N, QSIZ

       DOUBLE PRECISION RHO

       INTEGER GIVCOL(2,*), INDX(*), INDXP(*), INDXQ(*), PERM(*)

       DOUBLE PRECISION D(*), DLAMDA(*),  GIVNUM(2,*),  Q(LDQ,*),  Q2(LDQ2,*),
                 W(*), Z(*)


       SUBROUTINE DLAED8_64(ICOMPQ, K, N, QSIZ, D, Q, LDQ, INDXQ, RHO, CUTPNT,
                 Z, DLAMDA, Q2, LDQ2, W, PERM, GIVPTR, GIVCOL, GIVNUM,  INDXP,
                 INDX, INFO)


       INTEGER*8 CUTPNT, GIVPTR, ICOMPQ, INFO, K, LDQ, LDQ2, N, QSIZ

       DOUBLE PRECISION RHO

       INTEGER*8 GIVCOL(2,*), INDX(*), INDXP(*), INDXQ(*), PERM(*)

       DOUBLE  PRECISION  D(*),  DLAMDA(*), GIVNUM(2,*), Q(LDQ,*), Q2(LDQ2,*),
                 W(*), Z(*)


   F95 INTERFACE
       SUBROUTINE LAED8( ICOMPQ, K, N, QSIZ, D, Q, LDQ, INDXQ, RHO, CUTPNT, Z,
                 DLAMDA,  Q2,  LDQ2,  W,  PERM, GIVPTR, GIVCOL, GIVNUM, INDXP,
                 INDX, INFO )


       INTEGER :: ICOMPQ, K, N, QSIZ, LDQ, CUTPNT, LDQ2, GIVPTR, INFO

       INTEGER, DIMENSION(:) :: INDXQ, PERM, INDXP, INDX

       REAL(8), DIMENSION(:,:) :: Q, Q2, GIVNUM

       REAL(8), DIMENSION(:) :: D, Z, DLAMDA, W

       INTEGER, DIMENSION(:,:) :: GIVCOL

       REAL(8) :: RHO


       SUBROUTINE LAED8_64(ICOMPQ, K, N, QSIZ, D, Q, LDQ, INDXQ, RHO,  CUTPNT,
                 Z,  DLAMDA, Q2, LDQ2, W, PERM, GIVPTR, GIVCOL, GIVNUM, INDXP,
                 INDX, INFO)


       INTEGER(8) :: ICOMPQ, K, N, QSIZ, LDQ, CUTPNT, LDQ2, GIVPTR, INFO

       INTEGER(8), DIMENSION(:) :: INDXQ, PERM, INDXP, INDX

       REAL(8), DIMENSION(:,:) :: Q, Q2, GIVNUM

       REAL(8), DIMENSION(:) :: D, Z, DLAMDA, W

       INTEGER(8), DIMENSION(:,:) :: GIVCOL

       REAL(8) :: RHO


   C INTERFACE
       #include <sunperf.h>

       void dlaed8 (int icompq, int *k, int n, int qsiz, double *d, double *q,
                 int ldq, int *indxq, double *rho, int cutpnt, double *z, dou-
                 ble *dlamda, double *q2, int ldq2, double *w, int *perm,  int
                 *givptr, int *givcol, double *givnum, int *info);


       void  dlaed8_64  (long  icompq,  long *k, long n, long qsiz, double *d,
                 double *q, long ldq, long *indxq, double *rho,  long  cutpnt,
                 double  *z, double *dlamda, double *q2, long ldq2, double *w,
                 long *perm, long *givptr, long *givcol, double *givnum,  long
                 *info);


PURPOSE
       dlaed8 merges the two sets of eigenvalues together into a single sorted
       set. Then it tries to deflate the size of the problem.  There  are  two
       ways  in  which  deflation  can occur: when two or more eigenvalues are
       close together or if there is a tiny element in the Z vector. For  each
       such  occurrence  the  order of the related secular equation problem is
       reduced by one.


ARGUMENTS
       ICOMPQ (input)
                 ICOMPQ is INTEGER
                 = 0:  Compute eigenvalues only.
                 = 1:  Compute eigenvectors of original dense symmetric matrix
                 also.   On  entry,  Q  contains the orthogonal matrix used to
                 reduce the original matrix to tridiagonal form.


       K (output)
                 K is INTEGER
                 The number of non-deflated eigenvalues, and the order of  the
                 related secular equation.


       N (input)
                 N is INTEGER
                 The dimension of the symmetric tridiagonal matrix.  N >= 0.


       QSIZ (input)
                 QSIZ is INTEGER
                 The  dimension  of  the  orthogonal matrix used to reduce the
                 full matrix to tridiagonal form.
                 QSIZ >= N if ICOMPQ = 1.


       D (input/output)
                 D is DOUBLE PRECISION array, dimension (N)
                 On entry, the eigenvalues of the two submatrices to  be  com-
                 bined.
                 On  exit, the trailing (N-K) updated eigenvalues (those which
                 were deflated) sorted into increasing order.


       Q (input/output)
                 Q is DOUBLE PRECISION array, dimension (LDQ,N)
                 If ICOMPQ = 0, Q is not referenced. Otherwise,  on  entry,  Q
                 contains  the  eigenvectors  of  the  partially solved system
                 which has been previously updated in matrix  multiplies  with
                 other partially solved eigensystems.
                 On  exit,  Q contains the trailing (N-K) updated eigenvectors
                 (those which were deflated) in its last N-K columns.


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


       INDXQ (input)
                 INDXQ is INTEGER array, dimension (N)
                 The permutation which separately sorts the  two  sub-problems
                 in  D into ascending order.  Note that elements in the second
                 half of this permutation must  first  have  CUTPNT  added  to
                 their values in order to be accurate.


       RHO (input/output)
                 RHO is DOUBLE PRECISION
                 On entry, the off-diagonal element associated with the rank-1
                 cut which originally split the two submatrices which are  now
                 being recombined.
                 On  exit,  RHO  has  been  modified  to the value required by
                 DLAED3.


       CUTPNT (input)
                 CUTPNT is INTEGER
                 The location of the  last  eigenvalue  in  the  leading  sub-
                 matrix. min(1,N) <= CUTPNT <= N.


       Z (input)
                 Z is DOUBLE PRECISION array, dimension (N)
                 On entry, Z contains the updating vector (the last row of the
                 first sub-eigenvector matrix and the first row of the  second
                 sub-eigenvector matrix).
                 On  exit,  the  contents  of  Z are destroyed by the updating
                 process.


       DLAMDA (output)
                 DLAMDA is DOUBLE PRECISION array, dimension (N)
                 A copy of the first K  eigenvalues  which  will  be  used  by
                 DLAED3 to form the secular equation.


       Q2 (output)
                 Q2 is DOUBLE PRECISION array, dimension (LDQ2,N)
                 If  ICOMPQ  =  0, Q2 is not referenced.  Otherwise, a copy of
                 the first K eigenvectors which will be used by  DLAED7  in  a
                 matrix multiply (DGEMM) to update the new eigenvectors.


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


       W (output)
                 W is DOUBLE PRECISION array, dimension (N)
                 The  first  k  values of the final deflation-altered z-vector
                 and will be passed to DLAED3.


       PERM (output)
                 PERM is INTEGER array, dimension (N)
                 The permutations (from deflation and sorting) to  be  applied
                 to each eigenblock.


       GIVPTR (output)
                 GIVPTR is INTEGER
                 The  number of Givens rotations which took place in this sub-
                 problem.


       GIVCOL (output)
                 GIVCOL is INTEGER array, dimension (2, N)
                 Each pair of numbers indicates a  pair  of  columns  to  take
                 place in a Givens rotation.


       GIVNUM (output)
                 GIVNUM is DOUBLE PRECISION array, dimension (2, N)
                 Each  number  indicates  the S value to be used in the corre-
                 sponding Givens rotation.


       INDXP (output)
                 INDXP is INTEGER array, dimension (N)
                 The permutation used to place deflated values of D at the end
                 of  the  array. INDXP(1:K) points to the nondeflated D-values
                 and INDXP(K+1:N) points to the deflated eigenvalues.


       INDX (output)
                 INDX is INTEGER array, dimension (N)
                 The permutation used to sort the contents of D into ascending
                 order.


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




                                  7 Nov 2015                        dlaed8(3P)