Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dlaed7 (3p)

Name

dlaed7 - compute the updated eigensystem of a diagonal matrix after modification by a rank-one symmetric matrix. Used by dstedc, when the original matrix is dense

Synopsis

SUBROUTINE  DLAED7(ICOMPQ,  N,  QSIZ, TLVLS, CURLVL, CURPBM, D, Q, LDQ,
INDXQ, RHO, CUTPNT, QSTORE, QPTR, PRMPTR, PERM, GIVPTR,  GIV-
COL, GIVNUM, WORK, IWORK, INFO)


INTEGER CURLVL, CURPBM, CUTPNT, ICOMPQ, INFO, LDQ, N, QSIZ, TLVLS

DOUBLE PRECISION RHO

INTEGER GIVCOL(2,*), GIVPTR(*), INDXQ(*), IWORK(*), PERM(*), PRMPTR(*),
QPTR(*)

DOUBLE PRECISION D(*), GIVNUM(2,*), Q(LDQ,*), QSTORE(*), WORK(*)


SUBROUTINE DLAED7_64(ICOMPQ, N, QSIZ, TLVLS, CURLVL, CURPBM, D, Q, LDQ,
INDXQ,  RHO, CUTPNT, QSTORE, QPTR, PRMPTR, PERM, GIVPTR, GIV-
COL, GIVNUM, WORK, IWORK, INFO)


INTEGER*8 CURLVL, CURPBM, CUTPNT, ICOMPQ, INFO, LDQ, N, QSIZ, TLVLS

DOUBLE PRECISION RHO

INTEGER*8  GIVCOL(2,*),   GIVPTR(*),   INDXQ(*),   IWORK(*),   PERM(*),
PRMPTR(*), QPTR(*)

DOUBLE PRECISION D(*), GIVNUM(2,*), Q(LDQ,*), QSTORE(*), WORK(*)


F95 INTERFACE
SUBROUTINE  LAED7(ICOMPQ,  N,  QSIZ,  TLVLS, CURLVL, CURPBM, D, Q, LDQ,
INDXQ, RHO, CUTPNT, QSTORE, QPTR, PRMPTR, PERM, GIVPTR,  GIV-
COL, GIVNUM, WORK, IWORK, INFO)


INTEGER :: ICOMPQ, N, QSIZ, TLVLS, CURLVL, CURPBM, LDQ, CUTPNT, INFO

INTEGER, DIMENSION(:) :: INDXQ, QPTR, PRMPTR, PERM, GIVPTR, IWORK

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

REAL(8),  DIMENSION(:)  ::  D,  QSTORE, WORK REAL(8), DIMENSION(:,:) ::
GIVNUM

INTEGER, DIMENSION(:,:) :: GIVCOL

REAL(8) :: RHO


SUBROUTINE LAED7_64(ICOMPQ, N, QSIZ, TLVLS, CURLVL, CURPBM, D, Q,  LDQ,
INDXQ,  RHO, CUTPNT, QSTORE, QPTR, PRMPTR, PERM, GIVPTR, GIV-
COL, GIVNUM, WORK, IWORK, INFO)


INTEGER(8) :: ICOMPQ, N, QSIZ, TLVLS, CURLVL, CURPBM, LDQ, CUTPNT, INFO

INTEGER(8), DIMENSION(:) :: INDXQ, QPTR, PRMPTR, PERM, GIVPTR, IWORK

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

REAL(8), DIMENSION(:) :: D, QSTORE, WORK

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

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

REAL(8) :: RHO


C INTERFACE
#include <sunperf.h>

void  dlaed7  (int  icompq, int n, int qsiz, int tlvls, int curlvl, int
curpbm, double *d, double *q, int  ldq,  int  *indxq,  double
rho,  int cutpnt, double *qstore, int *qptr, int *prmptr, int
*perm, int *givptr, int *givcol, double *givnum, int *info);


void dlaed7_64 (long icompq,  long  n,  long  qsiz,  long  tlvls,  long
curlvl,  long  curpbm,  double  *d, double *q, long ldq, long
*indxq, double rho, long cutpnt, double *qstore, long  *qptr,
long  *prmptr, long *perm, long *givptr, long *givcol, double
*givnum, long *info);

Description

Oracle Solaris Studio Performance Library                           dlaed7(3P)



NAME
       dlaed7  -  compute  the  updated eigensystem of a diagonal matrix after
       modification by a rank-one symmetric matrix. Used by dstedc,  when  the
       original matrix is dense


SYNOPSIS
       SUBROUTINE  DLAED7(ICOMPQ,  N,  QSIZ, TLVLS, CURLVL, CURPBM, D, Q, LDQ,
                 INDXQ, RHO, CUTPNT, QSTORE, QPTR, PRMPTR, PERM, GIVPTR,  GIV-
                 COL, GIVNUM, WORK, IWORK, INFO)


       INTEGER CURLVL, CURPBM, CUTPNT, ICOMPQ, INFO, LDQ, N, QSIZ, TLVLS

       DOUBLE PRECISION RHO

       INTEGER GIVCOL(2,*), GIVPTR(*), INDXQ(*), IWORK(*), PERM(*), PRMPTR(*),
                 QPTR(*)

       DOUBLE PRECISION D(*), GIVNUM(2,*), Q(LDQ,*), QSTORE(*), WORK(*)


       SUBROUTINE DLAED7_64(ICOMPQ, N, QSIZ, TLVLS, CURLVL, CURPBM, D, Q, LDQ,
                 INDXQ,  RHO, CUTPNT, QSTORE, QPTR, PRMPTR, PERM, GIVPTR, GIV-
                 COL, GIVNUM, WORK, IWORK, INFO)


       INTEGER*8 CURLVL, CURPBM, CUTPNT, ICOMPQ, INFO, LDQ, N, QSIZ, TLVLS

       DOUBLE PRECISION RHO

       INTEGER*8  GIVCOL(2,*),   GIVPTR(*),   INDXQ(*),   IWORK(*),   PERM(*),
                 PRMPTR(*), QPTR(*)

       DOUBLE PRECISION D(*), GIVNUM(2,*), Q(LDQ,*), QSTORE(*), WORK(*)


   F95 INTERFACE
       SUBROUTINE  LAED7(ICOMPQ,  N,  QSIZ,  TLVLS, CURLVL, CURPBM, D, Q, LDQ,
                 INDXQ, RHO, CUTPNT, QSTORE, QPTR, PRMPTR, PERM, GIVPTR,  GIV-
                 COL, GIVNUM, WORK, IWORK, INFO)


       INTEGER :: ICOMPQ, N, QSIZ, TLVLS, CURLVL, CURPBM, LDQ, CUTPNT, INFO

       INTEGER, DIMENSION(:) :: INDXQ, QPTR, PRMPTR, PERM, GIVPTR, IWORK

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

       REAL(8),  DIMENSION(:)  ::  D,  QSTORE, WORK REAL(8), DIMENSION(:,:) ::
                 GIVNUM

       INTEGER, DIMENSION(:,:) :: GIVCOL

       REAL(8) :: RHO


       SUBROUTINE LAED7_64(ICOMPQ, N, QSIZ, TLVLS, CURLVL, CURPBM, D, Q,  LDQ,
                 INDXQ,  RHO, CUTPNT, QSTORE, QPTR, PRMPTR, PERM, GIVPTR, GIV-
                 COL, GIVNUM, WORK, IWORK, INFO)


       INTEGER(8) :: ICOMPQ, N, QSIZ, TLVLS, CURLVL, CURPBM, LDQ, CUTPNT, INFO

       INTEGER(8), DIMENSION(:) :: INDXQ, QPTR, PRMPTR, PERM, GIVPTR, IWORK

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

       REAL(8), DIMENSION(:) :: D, QSTORE, WORK

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

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

       REAL(8) :: RHO


   C INTERFACE
       #include <sunperf.h>

       void  dlaed7  (int  icompq, int n, int qsiz, int tlvls, int curlvl, int
                 curpbm, double *d, double *q, int  ldq,  int  *indxq,  double
                 rho,  int cutpnt, double *qstore, int *qptr, int *prmptr, int
                 *perm, int *givptr, int *givcol, double *givnum, int *info);


       void dlaed7_64 (long icompq,  long  n,  long  qsiz,  long  tlvls,  long
                 curlvl,  long  curpbm,  double  *d, double *q, long ldq, long
                 *indxq, double rho, long cutpnt, double *qstore, long  *qptr,
                 long  *prmptr, long *perm, long *givptr, long *givcol, double
                 *givnum, long *info);


PURPOSE
       dlaed7 computes the updated eigensystem of a diagonal matrix after mod-
       ification by a rank-one symmetric matrix. This routine is used only for
       the eigenproblem which requires all eigenvalues and  optionally  eigen-
       vectors  of a dense symmetric matrix that has been reduced to tridiago-
       nal form. DLAED1 handles the case in which all eigenvalues  and  eigen-
       vectors of a symmetric tridiagonal matrix are desired.

       T = Q(in) (D(in)+RHO*Z*Z**T) Q**T(in)=Q(out)*D(out)*Q**T(out)

       where  Z = Q**Tu, u is a vector of length N with ones in the CUTPNT and
       CUTPNT + 1 th elements and zeros elsewhere.

       The eigenvectors of the original matrix are stored in Q, and the eigen-
       values are in D. The algorithm consists of three stages:

       The  first  stage  consists  of  deflating the size of the problem when
       there are multiple eigenvalues or if there is a zero in the  Z  vector.
       For  each  such occurence the dimension of the secular equation problem
       is reduced by one. This stage is performed by the routine DLAED8.

       The second stage consists of calculating the updated eigenvalues.  This
       is  done  by  finding the roots of the secular equation via the routine
       DLAED4 (as called by DLAED9).  This routine also calculates the  eigen-
       vectors of the current problem.

       The final stage consists of computing the updated eigenvectors directly
       using the updated eigenvalues. The eigenvectors for the current problem
       are multiplied with the eigenvectors from the overall problem.


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.


       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.


       TLVLS (input)
                 TLVLS is INTEGER
                 The total number of merging levels in the overall divide  and
                 conquer tree.


       CURLVL (input)
                 CURLVL is INTEGER
                 The current level in the overall merge routine,
                 0 <= CURLVL <= TLVLS.


       CURPBM (input)
                 CURPBM is INTEGER
                 The current problem in the current level in the overall merge
                 routine (counting from upper left to lower right).


       D (input/output)
                 D is DOUBLE PRECISION array, dimension (N)
                 On entry, the eigenvalues of the rank-1-perturbed matrix.
                 On exit, the eigenvalues of the repaired matrix.


       Q (input/output)
                 Q is DOUBLE PRECISION array, dimension (LDQ, N)
                 On entry, the eigenvectors of the rank-1-perturbed matrix.
                 On exit, the eigenvectors of the repaired tridiagonal matrix.


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


       INDXQ (output)
                 INDXQ is INTEGER array, dimension (N)
                 The  permutation  which  will reintegrate the subproblem just
                 solved back into sorted order, i.e., D(INDXQ(I = 1, N))  will
                 be in ascending order.


       RHO (input)
                 RHO is DOUBLE PRECISION
                 The  subdiagonal  element used to create the rank-1 modifica-
                 tion.


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


       QSTORE (input/output)
                 QSTORE  is  DOUBLE PRECISION array, dimension (N**2+1) Stores
                 eigenvectors of submatrices  encountered  during  divide  and
                 conquer,  packed  together.  QPTR  points to beginning of the
                 submatrices.


       QPTR (input/output)
                 QPTR is INTEGER array, dimension (N+2)
                 List of indices pointing to beginning of  submatrices  stored
                 in  QSTORE. The submatrices are numbered starting at the bot-
                 tom left of the divide and conquer tree, from left  to  right
                 and bottom to top.


       PRMPTR (input/output)
                 PRMPTR is INTEGER array, dimension (N lg N)
                 Contains  a  list  of pointers which indicate where in PERM a
                 level's permutation is stored.
                 PRMPTR(i+1) - PRMPTR(i) indicates the size of the permutation
                 and also the size of the full, non-deflated problem.


       PERM (input)
                 PERM is INTEGER array, dimension (N lg N)
                 Contains  the permutations (from deflation and sorting) to be
                 applied to each eigenblock.


       GIVPTR (input/output)
                 GIVPTR is INTEGER array, dimension (N lg N)
                 Contains a list of pointers which indicate where in GIVCOL  a
                 level's Givens rotations are stored.
                 GIVPTR(i+1)  - GIVPTR(i) indicates the number of Givens rota-
                 tions.


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


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


       WORK (output)
                 WORK is DOUBLE PRECISION array, dimension (3*N+2*QSIZ*N)


       IWORK (output)
                 IWORK is INTEGER array, dimension (4*N)


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




                                  7 Nov 2015                        dlaed7(3P)