Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dlaed3 (3p)

Name

dlaed3 - vectors; used by dstedc when the original matrix is tridiagonal

Synopsis

SUBROUTINE DLAED3( K, N, N1, D, Q, LDQ, RHO, DLAMDA, Q2, INDX, CTOT, W,
S, INFO )


INTEGER INFO, K, LDQ, N, N1

DOUBLE PRECISION RHO

INTEGER CTOT(*),INDX(*)

DOUBLE PRECISION D(*),DLAMDA(*), Q(LDQ,*), Q2(*), S(*),W(*)


SUBROUTINE DLAED3_64( K, N, N1, D, Q, LDQ, RHO, DLAMDA, Q2, INDX, CTOT,
W, S, INFO )


INTEGER*8 INFO, K, LDQ, N, N1

DOUBLE PRECISION RHO

INTEGER*8 CTOT(*),INDX(*)

DOUBLE PRECISION D(*),DLAMDA(*), Q(LDQ,*), Q2(*), S(*),W(*)


F95 INTERFACE
SUBROUTINE LAED3( K, N, N1, D, Q, LDQ, RHO, DLAMDA, Q2, INDX, CTOT,  W,
S, INFO )


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

INTEGER :: K, N, N1, LDQ, INFO

INTEGER, DIMENSION(:) :: INDX, CTOT

REAL(8), DIMENSION(:) :: D, DLAMDA, Q2, W, S

REAL(8) :: RHO


SUBROUTINE  LAED3_64( K, N, N1, D, Q, LDQ, RHO, DLAMDA, Q2, INDX, CTOT,
W, S, INFO )


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

INTEGER(8) :: K, N, N1, LDQ, INFO

INTEGER(8), DIMENSION(:) :: INDX, CTOT

REAL(8), DIMENSION(:) :: D, DLAMDA, Q2, W, S

REAL(8) :: RHO


C INTERFACE
#include <sunperf.h>

void dlaed3 (int k, int n, int n1, double *d, double *q, int ldq,  dou-
ble  rho,  double  *dlamda, double *q2, int *indx, int *ctot,
double *w, int *info);


void dlaed3_64 (long k, long n, long n1, double  *d,  double  *q,  long
ldq, double rho, double *dlamda, double *q2, long *indx, long
*ctot, double *w, long *info);

Description

Oracle Solaris Studio Performance Library                           dlaed3(3P)



NAME
       dlaed3  - find the roots of the secular equation and updates the eigen-
       vectors; used by dstedc when the original matrix is tridiagonal


SYNOPSIS
       SUBROUTINE DLAED3( K, N, N1, D, Q, LDQ, RHO, DLAMDA, Q2, INDX, CTOT, W,
                 S, INFO )


       INTEGER INFO, K, LDQ, N, N1

       DOUBLE PRECISION RHO

       INTEGER CTOT(*),INDX(*)

       DOUBLE PRECISION D(*),DLAMDA(*), Q(LDQ,*), Q2(*), S(*),W(*)


       SUBROUTINE DLAED3_64( K, N, N1, D, Q, LDQ, RHO, DLAMDA, Q2, INDX, CTOT,
                 W, S, INFO )


       INTEGER*8 INFO, K, LDQ, N, N1

       DOUBLE PRECISION RHO

       INTEGER*8 CTOT(*),INDX(*)

       DOUBLE PRECISION D(*),DLAMDA(*), Q(LDQ,*), Q2(*), S(*),W(*)


   F95 INTERFACE
       SUBROUTINE LAED3( K, N, N1, D, Q, LDQ, RHO, DLAMDA, Q2, INDX, CTOT,  W,
                 S, INFO )


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

       INTEGER :: K, N, N1, LDQ, INFO

       INTEGER, DIMENSION(:) :: INDX, CTOT

       REAL(8), DIMENSION(:) :: D, DLAMDA, Q2, W, S

       REAL(8) :: RHO


       SUBROUTINE  LAED3_64( K, N, N1, D, Q, LDQ, RHO, DLAMDA, Q2, INDX, CTOT,
                 W, S, INFO )


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

       INTEGER(8) :: K, N, N1, LDQ, INFO

       INTEGER(8), DIMENSION(:) :: INDX, CTOT

       REAL(8), DIMENSION(:) :: D, DLAMDA, Q2, W, S

       REAL(8) :: RHO


   C INTERFACE
       #include <sunperf.h>

       void dlaed3 (int k, int n, int n1, double *d, double *q, int ldq,  dou-
                 ble  rho,  double  *dlamda, double *q2, int *indx, int *ctot,
                 double *w, int *info);


       void dlaed3_64 (long k, long n, long n1, double  *d,  double  *q,  long
                 ldq, double rho, double *dlamda, double *q2, long *indx, long
                 *ctot, double *w, long *info);


PURPOSE
       dlaed3 finds the roots of the secular equation, as defined by the  val-
       ues  in D, W, and RHO, between 1 and K.  It makes the appropriate calls
       to DLAED4 and then updates the eigenvectors by multiplying  the  matrix
       of  eigenvectors  of  the  pair  of  eigensystems being combined by the
       matrix of eigenvectors of the K-by-K system which is solved here.

       This code makes very mild assumptions about floating point  arithmetic.
       It  will  work  on  machines  with a guard digit in add/subtract, or on
       those binary machines without guard digits which subtract like the Cray
       X-MP,  Cray  Y-MP,  Cray C-90, or Cray-2.  It could conceivably fail on
       hexadecimal or decimal machines without guard digits, but  we  know  of
       none.


ARGUMENTS
       K (input)
                 K is INTEGER
                 The  number of terms in the rational function to be solved by
                 DLAED4.  K >= 0.


       N (input)
                 N is INTEGER
                 The number of rows and columns in the Q matrix.
                 N >= K (deflation may result in N>K).


       N1 (input)
                 N1 is INTEGER
                 The location of the last eigenvalue in the leading submatrix.
                 min(1,N) <= N1 <= N/2.


       D (output)
                 D is DOUBLE PRECISION array, dimension (N)
                 D(I) contains the updated eigenvalues for
                 1 <= I <= K.


       Q (output)
                 Q is DOUBLE PRECISION array, dimension (LDQ,N)
                 Initially the first K columns are used as workspace.
                 On  output  the  columns 1 to K contain the updated eigenvec-
                 tors.


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


       RHO (input)
                 RHO is DOUBLE PRECISION
                 The value of the parameter in the rank one update equation.
                 RHO >= 0 required.


       DLAMDA (input/output)
                 DLAMDA is DOUBLE PRECISION array, dimension (K)
                 The first K elements of this array contain the old  roots  of
                 the  deflated  updating  problem.  These are the poles of the
                 secular equation. May be changed on output by  having  lowest
                 order  bit  set  to  zero on Cray X-MP, Cray Y-MP, Cray-2, or
                 Cray C-90, as described above.


       Q2 (input)
                 Q2 is DOUBLE PRECISION array, dimension (LDQ2, N)
                 The first K columns of this matrix contain  the  non-deflated
                 eigenvectors for the split problem.


       INDX (input)
                 INDX is INTEGER array, dimension (N)
                 The  permutation  is  used  to  arrange  the  columns  of the
                 deflated Q matrix into three groups (see DLAED2).   The  rows
                 of the eigenvectors found by DLAED4 must be likewise permuted
                 before the matrix multiply can take place.


       CTOT (input)
                 CTOT is INTEGER array, dimension (4)
                 A count of the total number of the various types  of  columns
                 in  Q,  as  described  in INDX. The fourth column type is any
                 column which has been deflated.


       W (input/output)
                 W is DOUBLE PRECISION array, dimension (K)
                 The first K elements of this array contain the components  of
                 the  deflation-adjusted updating vector. Destroyed on output.


       S (output)
                 S is DOUBLE PRECISION array, dimension (N1 + 1)*K
                 Will contain the eigenvectors of the  repaired  matrix  which
                 will be multiplied by the previously accumulated eigenvectors
                 to update the system.


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