Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

claed8 (3p)

Name

claed8 - edc, when the original matrix is dense

Synopsis

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


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

REAL RHO

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

REAL D(*), DLAMDA(*), GIVNUM(2,*), W(*), Z(*)

COMPLEX Q(LDQ,*), Q2(LDQ2,*)


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


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

REAL RHO

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

REAL D(*), DLAMDA(*), GIVNUM(2,*), W(*), Z(*)

COMPLEX Q(LDQ,*), Q2(LDQ2,*)


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


REAL, DIMENSION(:,:) :: GIVNUM

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

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

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

COMPLEX, DIMENSION(:,:) :: Q, Q2

INTEGER, DIMENSION(:,:) :: GIVCOL

REAL :: RHO


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


REAL, DIMENSION(:,:) :: GIVNUM

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

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

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

COMPLEX, DIMENSION(:,:) :: Q, Q2

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

REAL :: RHO


C INTERFACE
#include <sunperf.h>

void claed8 (int *k, int n, int qsiz, floatcomplex *q, int  ldq,  float
*d,  float  *rho, int cutpnt, float *z, float *dlamda, float-
complex *q2, int ldq2, float *w, int *indxq, int  *perm,  int
*givptr, int *givcol, float *givnum, int *info);


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

Description

Oracle Solaris Studio Performance Library                           claed8(3P)



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


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


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

       REAL RHO

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

       REAL D(*), DLAMDA(*), GIVNUM(2,*), W(*), Z(*)

       COMPLEX Q(LDQ,*), Q2(LDQ2,*)


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


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

       REAL RHO

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

       REAL D(*), DLAMDA(*), GIVNUM(2,*), W(*), Z(*)

       COMPLEX Q(LDQ,*), Q2(LDQ2,*)


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


       REAL, DIMENSION(:,:) :: GIVNUM

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

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

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

       COMPLEX, DIMENSION(:,:) :: Q, Q2

       INTEGER, DIMENSION(:,:) :: GIVCOL

       REAL :: RHO


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


       REAL, DIMENSION(:,:) :: GIVNUM

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

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

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

       COMPLEX, DIMENSION(:,:) :: Q, Q2

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

       REAL :: RHO


   C INTERFACE
       #include <sunperf.h>

       void claed8 (int *k, int n, int qsiz, floatcomplex *q, int  ldq,  float
                 *d,  float  *rho, int cutpnt, float *z, float *dlamda, float-
                 complex *q2, int ldq2, float *w, int *indxq, int  *perm,  int
                 *givptr, int *givcol, float *givnum, int *info);


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


PURPOSE
       claed8 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
       K (output)
                 K is INTEGER
                 Contains the number of non-deflated eigenvalues.
                 This is 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 unitary matrix used to reduce the  dense
                 or band matrix to tridiagonal form.
                 QSIZ >= N if ICOMPQ = 1.


       Q (input/output)
                 Q is COMPLEX array, dimension (LDQ,N)
                 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 ).


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


       RHO (input/output)
                 RHO is REAL
                 Contains the off diagonal element associated with the  rank-1
                 cut  which originally split the two submatrices which are now
                 being recombined. RHO is modified during the  computation  to
                 the value required by SLAED3.


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


       Z (input)
                 Z is REAL array, dimension (N)
                 On input this vector contains the updating vector  (the  last
                 row  of the first sub-eigenvector matrix and the first row of
                 the second sub-eigenvector matrix). The  contents  of  Z  are
                 destroyed during the updating process.


       DLAMDA (output)
                 DLAMDA is REAL array, dimension (N)
                 Contains a copy of the first K eigenvalues which will be used
                 by SLAED3 to form the secular equation.


       Q2 (output)
                 Q2 is COMPLEX array, dimension (LDQ2,N)
                 If ICOMPQ = 0, Q2 is not referenced.  Otherwise,  contains  a
                 copy of the first K eigenvectors which will be used by SLAED7
                 in a matrix multiply (SGEMM) 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 REAL array, dimension (N)
                 This  will  hold  the  first k values of the final deflation-
                 altered z-vector and will be passed to SLAED3.


       INDXP (output)
                 INDXP is INTEGER array, dimension (N)
                 This will contain the permutation used to place deflated val-
                 ues of D at the end of the array. On output 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)
                 This  will  contain the permutation used to sort the contents
                 of D into ascending order.


       INDXQ (input)
                 INDXQ is INTEGER array, dimension (N)
                 This contains 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.


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


       GIVPTR (output)
                 GIVPTR is INTEGER
                 Contains the number of Givens rotations which took  place  in
                 this subproblem.


       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 REAL array, dimension (2, N)
                 Each number indicates the S value to be used  in  the  corre-
                 sponding Givens rotation.


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




                                  7 Nov 2015                        claed8(3P)