Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

slaeda (3p)

Name

slaeda - one modification of the diagonal matrix. Used when the original matrix is dense

Synopsis

SUBROUTINE SLAEDA( N, TLVLS, CURLVL, CURPBM, PRMPTR, PERM, GIVPTR, GIV-
COL, GIVNUM, Q, QPTR, Z, ZTEMP, INFO )


INTEGER CURLVL, CURPBM, INFO, N, TLVLS

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

REAL GIVNUM(2,*), Q(*),Z(*), ZTEMP(*)


SUBROUTINE SLAEDA_64( N, TLVLS, CURLVL, CURPBM, PRMPTR,  PERM,  GIVPTR,
GIVCOL, GIVNUM, Q, QPTR, Z, ZTEMP, INFO )


INTEGER*8 CURLVL, CURPBM, INFO, N, TLVLS

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

REAL GIVNUM(2,*), Q(*),Z(*), ZTEMP(*)


F95 INTERFACE
SUBROUTINE  LAEDA( N, TLVLS, CURLVL, CURPBM, PRMPTR, PERM, GIVPTR, GIV-
COL, GIVNUM, Q, QPTR, Z, ZTEMP, INFO )


REAL, DIMENSION(:,:) :: GIVNUM

INTEGER :: N, TLVLS, CURLVL, CURPBM, INFO

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

REAL, DIMENSION(:) :: Q, Z, ZTEMP

INTEGER, DIMENSION(:,:) :: GIVCOL


SUBROUTINE LAEDA_64( N, TLVLS, CURLVL, CURPBM,  PRMPTR,  PERM,  GIVPTR,
GIVCOL, GIVNUM, Q, QPTR, Z, ZTEMP, INFO )


REAL, DIMENSION(:,:) :: GIVNUM

INTEGER(8) :: N, TLVLS, CURLVL, CURPBM, INFO

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

REAL, DIMENSION(:) :: Q, Z, ZTEMP

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


C INTERFACE
#include <sunperf.h>

void slaeda (int n, int tlvls, int curlvl, int curpbm, int *prmptr, int
*perm, int *givptr, int *givcol, float *givnum, float *q, int
*qptr, float *z, int *info);


void  slaeda_64  (long  n,  long  tlvls, long curlvl, long curpbm, long
*prmptr,  long  *perm,  long  *givptr,  long  *givcol,  float
*givnum, float *q, long *qptr, float *z, long *info);

Description

Oracle Solaris Studio Performance Library                           slaeda(3P)



NAME
       slaeda  - is used by sstedc. Compute the Z vector determining the rank-
       one modification of the diagonal matrix. Used when the original  matrix
       is dense


SYNOPSIS
       SUBROUTINE SLAEDA( N, TLVLS, CURLVL, CURPBM, PRMPTR, PERM, GIVPTR, GIV-
                 COL, GIVNUM, Q, QPTR, Z, ZTEMP, INFO )


       INTEGER CURLVL, CURPBM, INFO, N, TLVLS

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

       REAL GIVNUM(2,*), Q(*),Z(*), ZTEMP(*)


       SUBROUTINE SLAEDA_64( N, TLVLS, CURLVL, CURPBM, PRMPTR,  PERM,  GIVPTR,
                 GIVCOL, GIVNUM, Q, QPTR, Z, ZTEMP, INFO )


       INTEGER*8 CURLVL, CURPBM, INFO, N, TLVLS

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

       REAL GIVNUM(2,*), Q(*),Z(*), ZTEMP(*)


   F95 INTERFACE
       SUBROUTINE  LAEDA( N, TLVLS, CURLVL, CURPBM, PRMPTR, PERM, GIVPTR, GIV-
                 COL, GIVNUM, Q, QPTR, Z, ZTEMP, INFO )


       REAL, DIMENSION(:,:) :: GIVNUM

       INTEGER :: N, TLVLS, CURLVL, CURPBM, INFO

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

       REAL, DIMENSION(:) :: Q, Z, ZTEMP

       INTEGER, DIMENSION(:,:) :: GIVCOL


       SUBROUTINE LAEDA_64( N, TLVLS, CURLVL, CURPBM,  PRMPTR,  PERM,  GIVPTR,
                 GIVCOL, GIVNUM, Q, QPTR, Z, ZTEMP, INFO )


       REAL, DIMENSION(:,:) :: GIVNUM

       INTEGER(8) :: N, TLVLS, CURLVL, CURPBM, INFO

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

       REAL, DIMENSION(:) :: Q, Z, ZTEMP

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


   C INTERFACE
       #include <sunperf.h>

       void slaeda (int n, int tlvls, int curlvl, int curpbm, int *prmptr, int
                 *perm, int *givptr, int *givcol, float *givnum, float *q, int
                 *qptr, float *z, int *info);


       void  slaeda_64  (long  n,  long  tlvls, long curlvl, long curpbm, long
                 *prmptr,  long  *perm,  long  *givptr,  long  *givcol,  float
                 *givnum, float *q, long *qptr, float *z, long *info);


PURPOSE
       slaeda  computes  the  Z  vector corresponding to the merge step in the
       CURLVLth step of the merge process with TLVLS steps  for  the  CURPBMth
       problem.


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


       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).


       PRMPTR (input)
                 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 incidentally 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)
                 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 rotations.


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


       Q (input)
                 Q is REAL array, dimension (N**2)
                 Contains the square eigenblocks from previous levels, the
                 starting positions for blocks are given by QPTR.


       QPTR (input)
                 QPTR is INTEGER array, dimension (N+2)
                 Contains a list of pointers which indicate where in Q an
                 eigenblock is stored.  SQRT( QPTR(i+1) - QPTR(i) ) indicates
                 the size of the block.


       Z (output)
                 Z is REAL array, dimension (N)
                 On output 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).


       ZTEMP (output)
                 ZTEMP is REAL array, dimension (N)


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




                                  7 Nov 2015                        slaeda(3P)