Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dlaed1 (3p)

Name

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

Synopsis

SUBROUTINE DLAED1(N, D, Q, LDQ, INDXQ, RHO, CUTPNT, WORK, IWORK, INFO)


INTEGER CUTPNT, INFO, LDQ, N

DOUBLE PRECISION RHO

INTEGER INDXQ(*), IWORK(*)

DOUBLE PRECISION D(*), Q(LDQ,*), WORK(*)


SUBROUTINE  DLAED1_64(N,  D,  Q,  LDQ, INDXQ, RHO, CUTPNT, WORK, IWORK,
INFO)


INTEGER*8 CUTPNT, INFO, LDQ, N

DOUBLE PRECISION RHO

INTEGER*8 INDXQ(*), IWORK(*)

DOUBLE PRECISION D(*), Q(LDQ,*), WORK(*)


F95 INTERFACE
SUBROUTINE LAED1(N, D, Q, LDQ, INDXQ, RHO, CUTPNT, WORK, IWORK, INFO)


INTEGER :: N, LDQ, CUTPNT, INFO

INTEGER, DIMENSION(:) :: INDXQ, IWORK

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

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

REAL(8) :: RHO


SUBROUTINE LAED1_64(N, D, Q, LDQ,  INDXQ,  RHO,  CUTPNT,  WORK,  IWORK,
INFO)


INTEGER(8) :: N, LDQ, CUTPNT, INFO

INTEGER(8), DIMENSION(:) :: INDXQ, IWORK

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

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

REAL(8) :: RHO


C INTERFACE
#include <sunperf.h>

void  dlaed1  (int n, double *d, double *q, int ldq, int *indxq, double
rho, int cutpnt, int *info);


void dlaed1_64 (long n, double *d, double *q, long  ldq,  long  *indxq,
double rho, long cutpnt, long *info);

Description

Oracle Solaris Studio Performance Library                           dlaed1(3P)



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


SYNOPSIS
       SUBROUTINE DLAED1(N, D, Q, LDQ, INDXQ, RHO, CUTPNT, WORK, IWORK, INFO)


       INTEGER CUTPNT, INFO, LDQ, N

       DOUBLE PRECISION RHO

       INTEGER INDXQ(*), IWORK(*)

       DOUBLE PRECISION D(*), Q(LDQ,*), WORK(*)


       SUBROUTINE  DLAED1_64(N,  D,  Q,  LDQ, INDXQ, RHO, CUTPNT, WORK, IWORK,
                 INFO)


       INTEGER*8 CUTPNT, INFO, LDQ, N

       DOUBLE PRECISION RHO

       INTEGER*8 INDXQ(*), IWORK(*)

       DOUBLE PRECISION D(*), Q(LDQ,*), WORK(*)


   F95 INTERFACE
       SUBROUTINE LAED1(N, D, Q, LDQ, INDXQ, RHO, CUTPNT, WORK, IWORK, INFO)


       INTEGER :: N, LDQ, CUTPNT, INFO

       INTEGER, DIMENSION(:) :: INDXQ, IWORK

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

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

       REAL(8) :: RHO


       SUBROUTINE LAED1_64(N, D, Q, LDQ,  INDXQ,  RHO,  CUTPNT,  WORK,  IWORK,
                 INFO)


       INTEGER(8) :: N, LDQ, CUTPNT, INFO

       INTEGER(8), DIMENSION(:) :: INDXQ, IWORK

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

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

       REAL(8) :: RHO


   C INTERFACE
       #include <sunperf.h>

       void  dlaed1  (int n, double *d, double *q, int ldq, int *indxq, double
                 rho, int cutpnt, int *info);


       void dlaed1_64 (long n, double *d, double *q, long  ldq,  long  *indxq,
                 double rho, long cutpnt, long *info);


PURPOSE
       dlaed1 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 eigenvectors of a
       tridiagonal matrix. DLAED7 handles the case in which  eigenvalues  only
       or  eigenvalues  and eigenvectors of a full symmetric matrix (which was
       reduced to tridiagonal form) are desired.

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

       where Z = Q**T*u, 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 DLAED2.

       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 DLAED3).  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
       N (input)
                 N is INTEGER
                 The dimension of the symmetric tridiagonal matrix. N >= 0.


       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 (input/output)
                 INDXQ is INTEGER array, dimension (N)
                 On entry, the permutation which separately sorts the two sub-
                 problems in D into ascending order.
                 On exit, the permutation which will reintegrate the  subprob-
                 lems back into sorted order, i.e., D(INDXQ(I=1,N)) will be in
                 ascending order.


       RHO (input)
                 RHO is DOUBLE PRECISION
                 The subdiagonal entry used to create the rank-1 modification.


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


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


       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                        dlaed1(3P)