Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

clals0 (3p)

Name

clals0 - apply back multiplying factors in solving the least squares problem using divide and conquer SVD approach. Used by cgelsd

Synopsis

SUBROUTINE CLALS0(ICOMPQ, NL, NR, SQRE, NRHS, B, LDB, BX,  LDBX,  PERM,
GIVPTR, GIVCOL, LDGCOL, GIVNUM, LDGNUM, POLES, DIFL, DIFR, Z,
K, C, S, RWORK, INFO)


INTEGER GIVPTR, ICOMPQ, INFO, K, LDB, LDBX,  LDGCOL,  LDGNUM,  NL,  NR,
NRHS, SQRE

REAL C, S

INTEGER GIVCOL(LDGCOL,*), PERM(*)

REAL   DIFL(*),   DIFR(LDGNUM,*),   GIVNUM(LDGNUM,*),  POLES(LDGNUM,*),
RWORK(*), Z(*)

COMPLEX B(LDB,*), BX(LDBX,*)


SUBROUTINE CLALS0_64(ICOMPQ, NL, NR, SQRE,  NRHS,  B,  LDB,  BX,  LDBX,
PERM,  GIVPTR,  GIVCOL,  LDGCOL, GIVNUM, LDGNUM, POLES, DIFL,
DIFR, Z, K, C, S, RWORK, INFO)


INTEGER*8 GIVPTR, ICOMPQ, INFO, K, LDB, LDBX, LDGCOL, LDGNUM,  NL,  NR,
NRHS, SQRE

REAL C, S

INTEGER*8 GIVCOL(LDGCOL,*), PERM(*)

REAL   DIFL(*),   DIFR(LDGNUM,*),   GIVNUM(LDGNUM,*),  POLES(LDGNUM,*),
RWORK(*), Z(*)

COMPLEX B(LDB,*), BX(LDBX,*)


F95 INTERFACE
SUBROUTINE LALS0(ICOMPQ, NL, NR, SQRE, NRHS, B, LDB,  BX,  LDBX,  PERM,
GIVPTR, GIVCOL, LDGCOL, GIVNUM, LDGNUM, POLES, DIFL, DIFR, Z,
K, C, S, RWORK, INFO)


REAL, DIMENSION(:,:) :: GIVNUM, POLES, DIFR

INTEGER :: ICOMPQ, NL, NR,  SQRE,  NRHS,  LDB,  LDBX,  GIVPTR,  LDGCOL,
LDGNUM, K, INFO

INTEGER, DIMENSION(:) :: PERM

REAL, DIMENSION(:) :: DIFL, Z, RWORK

COMPLEX, DIMENSION(:,:) :: B, BX

INTEGER, DIMENSION(:,:) :: GIVCOL

REAL :: C, S


SUBROUTINE LALS0_64(ICOMPQ, NL, NR, SQRE, NRHS, B, LDB, BX, LDBX, PERM,
GIVPTR, GIVCOL, LDGCOL, GIVNUM, LDGNUM, POLES, DIFL, DIFR, Z,
K, C, S, RWORK, INFO)


REAL, DIMENSION(:,:) :: GIVNUM, POLES, DIFR

INTEGER(8)  ::  ICOMPQ,  NL, NR, SQRE, NRHS, LDB, LDBX, GIVPTR, LDGCOL,
LDGNUM, K, INFO

INTEGER(8), DIMENSION(:) :: PERM

REAL, DIMENSION(:) :: DIFL, Z, RWORK

COMPLEX, DIMENSION(:,:) :: B, BX

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

REAL :: C, S


C INTERFACE
#include <sunperf.h>

void clals0 (int icompq, int nl, int nr, int sqre, int nrhs,  floatcom-
plex  *b, int ldb, floatcomplex *bx, int ldbx, int *perm, int
givptr, int *givcol, int ldgcol, float *givnum,  int  ldgnum,
float  *poles,  float  *difl,  float  *difr, float *z, int k,
float c, float s, int *info);


void clals0_64 (long icompq, long nl, long nr, long  sqre,  long  nrhs,
floatcomplex  *b, long ldb, floatcomplex *bx, long ldbx, long
*perm, long givptr, long *givcol, long ldgcol, float *givnum,
long  ldgnum,  float  *poles, float *difl, float *difr, float
*z, long k, float c, float s, long *info);

Description

Oracle Solaris Studio Performance Library                           clals0(3P)



NAME
       clals0  -  apply  back multiplying factors in solving the least squares
       problem using divide and conquer SVD approach. Used by cgelsd


SYNOPSIS
       SUBROUTINE CLALS0(ICOMPQ, NL, NR, SQRE, NRHS, B, LDB, BX,  LDBX,  PERM,
                 GIVPTR, GIVCOL, LDGCOL, GIVNUM, LDGNUM, POLES, DIFL, DIFR, Z,
                 K, C, S, RWORK, INFO)


       INTEGER GIVPTR, ICOMPQ, INFO, K, LDB, LDBX,  LDGCOL,  LDGNUM,  NL,  NR,
                 NRHS, SQRE

       REAL C, S

       INTEGER GIVCOL(LDGCOL,*), PERM(*)

       REAL   DIFL(*),   DIFR(LDGNUM,*),   GIVNUM(LDGNUM,*),  POLES(LDGNUM,*),
                 RWORK(*), Z(*)

       COMPLEX B(LDB,*), BX(LDBX,*)


       SUBROUTINE CLALS0_64(ICOMPQ, NL, NR, SQRE,  NRHS,  B,  LDB,  BX,  LDBX,
                 PERM,  GIVPTR,  GIVCOL,  LDGCOL, GIVNUM, LDGNUM, POLES, DIFL,
                 DIFR, Z, K, C, S, RWORK, INFO)


       INTEGER*8 GIVPTR, ICOMPQ, INFO, K, LDB, LDBX, LDGCOL, LDGNUM,  NL,  NR,
                 NRHS, SQRE

       REAL C, S

       INTEGER*8 GIVCOL(LDGCOL,*), PERM(*)

       REAL   DIFL(*),   DIFR(LDGNUM,*),   GIVNUM(LDGNUM,*),  POLES(LDGNUM,*),
                 RWORK(*), Z(*)

       COMPLEX B(LDB,*), BX(LDBX,*)


   F95 INTERFACE
       SUBROUTINE LALS0(ICOMPQ, NL, NR, SQRE, NRHS, B, LDB,  BX,  LDBX,  PERM,
                 GIVPTR, GIVCOL, LDGCOL, GIVNUM, LDGNUM, POLES, DIFL, DIFR, Z,
                 K, C, S, RWORK, INFO)


       REAL, DIMENSION(:,:) :: GIVNUM, POLES, DIFR

       INTEGER :: ICOMPQ, NL, NR,  SQRE,  NRHS,  LDB,  LDBX,  GIVPTR,  LDGCOL,
                 LDGNUM, K, INFO

       INTEGER, DIMENSION(:) :: PERM

       REAL, DIMENSION(:) :: DIFL, Z, RWORK

       COMPLEX, DIMENSION(:,:) :: B, BX

       INTEGER, DIMENSION(:,:) :: GIVCOL

       REAL :: C, S


       SUBROUTINE LALS0_64(ICOMPQ, NL, NR, SQRE, NRHS, B, LDB, BX, LDBX, PERM,
                 GIVPTR, GIVCOL, LDGCOL, GIVNUM, LDGNUM, POLES, DIFL, DIFR, Z,
                 K, C, S, RWORK, INFO)


       REAL, DIMENSION(:,:) :: GIVNUM, POLES, DIFR

       INTEGER(8)  ::  ICOMPQ,  NL, NR, SQRE, NRHS, LDB, LDBX, GIVPTR, LDGCOL,
                 LDGNUM, K, INFO

       INTEGER(8), DIMENSION(:) :: PERM

       REAL, DIMENSION(:) :: DIFL, Z, RWORK

       COMPLEX, DIMENSION(:,:) :: B, BX

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

       REAL :: C, S


   C INTERFACE
       #include <sunperf.h>

       void clals0 (int icompq, int nl, int nr, int sqre, int nrhs,  floatcom-
                 plex  *b, int ldb, floatcomplex *bx, int ldbx, int *perm, int
                 givptr, int *givcol, int ldgcol, float *givnum,  int  ldgnum,
                 float  *poles,  float  *difl,  float  *difr, float *z, int k,
                 float c, float s, int *info);


       void clals0_64 (long icompq, long nl, long nr, long  sqre,  long  nrhs,
                 floatcomplex  *b, long ldb, floatcomplex *bx, long ldbx, long
                 *perm, long givptr, long *givcol, long ldgcol, float *givnum,
                 long  ldgnum,  float  *poles, float *difl, float *difr, float
                 *z, long k, float c, float s, long *info);


PURPOSE
       clals0 applies back the multiplying factors of either the left  or  the
       right  singular vector matrix of a diagonal matrix appended by a row to
       the right hand side matrix B in solving the least squares problem using
       the divide-and-conquer SVD approach.

       For the left singular vector matrix, three types of orthogonal matrices
       are involved:

       (1L) Givens rotations: the number of  such  rotations  is  GIVPTR;  the
       pairs  of  columns/rows  they were applied to are stored in GIVCOL; and
       the C- and S-values of these rotations are stored in GIVNUM.

       (2L) Permutation. The (NL+1)-st row of B is to be moved  to  the  first
       row, and for J=2:N, PERM(J)-th row of B is to be moved to the J-th row.

       (3L) The left singular vector matrix of the remaining matrix.

       For the right singular vector matrix, four types of orthogonal matrices
       are involved:

       (1R) The right singular vector matrix of the remaining matrix.

       (2R)  If SQRE = 1, one extra Givens rotation to generate the right null
       space.

       (3R) The inverse transformation of (2L).

       (4R) The inverse transformation of (1L).


ARGUMENTS
       ICOMPQ (input)
                 ICOMPQ is INTEGER
                 Specifies whether singular vectors are to be computed in  the
                 factored form:
                 = 0: Left singular vector matrix.
                 = 1: Right singular vector matrix.


       NL (input)
                 NL is INTEGER
                 The row dimension of the upper block. NL >= 1.


       NR (input)
                 NR is INTEGER
                 The row dimension of the lower block. NR >= 1.


       SQRE (input)
                 SQRE is INTEGER
                 = 0: the lower block is an NR-by-NR square matrix.
                 = 1: the lower block is an NR-by-(NR+1) rectangular matrix.
                 The bidiagonal matrix has row dimension N=NL+NR+1, and column
                 dimension M=N+SQRE.


       NRHS (input)
                 NRHS is INTEGER
                 The number of columns of B and BX. NRHS must be at least 1.


       B (input/output)
                 B is COMPLEX array, dimension (LDB, NRHS)
                 On input, B contains  the  right  hand  sides  of  the  least
                 squares  problem  in  rows 1 through M. On output, B contains
                 the solution X in rows 1 through N.


       LDB (input)
                 LDB is INTEGER
                 The  leading  dimension  of  B.  LDB   must   be   at   least
                 max(1,MAX(M,N)).


       BX (output)
                 BX is COMPLEX array, dimension (LDBX, NRHS)


       LDBX (input)
                 LDBX is INTEGER
                 The leading dimension of BX.


       PERM (input)
                 PERM is INTEGER array, dimension (N)
                 The  permutations (from deflation and sorting) applied to the
                 two blocks.


       GIVPTR (input)
                 GIVPTR is INTEGER
                 The number of Givens rotations which took place in this  sub-
                 problem.


       GIVCOL (input)
                 GIVCOL is INTEGER array, dimension (LDGCOL, 2)
                 Each  pair  of  numbers  indicates  a  pair  of  rows/columns
                 involved in a Givens rotation.


       LDGCOL (input)
                 LDGCOL is INTEGER
                 The leading dimension of GIVCOL, must be at least N.


       GIVNUM (input)
                 GIVNUM is REAL array, dimension (LDGNUM, 2)
                 Each number indicates the C or S value  used  in  the  corre-
                 sponding Givens rotation.


       LDGNUM (input)
                 LDGNUM is INTEGER
                 The  leading dimension of arrays DIFR, POLES and GIVNUM, must
                 be at least K.


       POLES (input)
                 POLES is REAL array, dimension (LDGNUM, 2)
                 On entry, POLES(1:K, 1)  contains  the  new  singular  values
                 obtained from solving the secular equation, and POLES(1:K, 2)
                 is an array containing the poles in the secular equation.


       DIFL (input)
                 DIFL is REAL array, dimension (K)
                 On entry, DIFL(I) is the distance between I-th updated (unde-
                 flated) singular value and the I-th (undeflated) old singular
                 value.


       DIFR (input)
                 DIFR is REAL array, dimension (LDGNUM, 2)
                 On entry, DIFR(I, 1)  contains  the  distances  between  I-th
                 updated  (undeflated)  singular  value  and the I+1-th (unde-
                 flated) old singular value. And DIFR(I, 2) is the normalizing
                 factor for the I-th right singular vector.


       Z (input)
                 Z is REAL array, dimension (K)
                 Contain the components of the deflation-adjusted updating row
                 vector.


       K (input)
                 K is INTEGER
                 Contains the dimension of the non-deflated matrix.   This  is
                 the order of the related secular equation. 1 <= K <=N.


       C (input)
                 C is REAL
                 C  contains  garbage  if  SQRE =0 and the C-value of a Givens
                 rotation related to the right null space if SQRE = 1.


       S (input)
                 S is REAL
                 S contains garbage if SQRE =0 and the  S-value  of  a  Givens
                 rotation related to the right null space if SQRE = 1.


       RWORK (output)
                 RWORK is REAL array, dimension (K*(1+NRHS)+2*NRHS)


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




                                  7 Nov 2015                        clals0(3P)