Contents


NAME

     sbdsdc - compute the singular value decomposition (SVD) of a
     real N-by-N (upper or lower) bidiagonal matrix B

SYNOPSIS

     SUBROUTINE SBDSDC(UPLO, COMPQ, N, D, E, U, LDU, VT, LDVT, Q, IQ,
           WORK, IWORK, INFO)

     CHARACTER * 1 UPLO, COMPQ
     INTEGER N, LDU, LDVT, INFO
     INTEGER IQ(*), IWORK(*)
     REAL D(*), E(*), U(LDU,*), VT(LDVT,*), Q(*), WORK(*)

     SUBROUTINE SBDSDC_64(UPLO, COMPQ, N, D, E, U, LDU, VT, LDVT, Q, IQ,
           WORK, IWORK, INFO)

     CHARACTER * 1 UPLO, COMPQ
     INTEGER*8 N, LDU, LDVT, INFO
     INTEGER*8 IQ(*), IWORK(*)
     REAL D(*), E(*), U(LDU,*), VT(LDVT,*), Q(*), WORK(*)

  F95 INTERFACE
     SUBROUTINE BDSDC(UPLO, COMPQ, [N], D, E, U, [LDU], VT, [LDVT], Q, IQ,
            [WORK], [IWORK], [INFO])

     CHARACTER(LEN=1) :: UPLO, COMPQ
     INTEGER :: N, LDU, LDVT, INFO
     INTEGER, DIMENSION(:) :: IQ, IWORK
     REAL, DIMENSION(:) :: D, E, Q, WORK
     REAL, DIMENSION(:,:) :: U, VT

     SUBROUTINE BDSDC_64(UPLO, COMPQ, [N], D, E, U, [LDU], VT, [LDVT], Q,
            IQ, [WORK], [IWORK], [INFO])

     CHARACTER(LEN=1) :: UPLO, COMPQ
     INTEGER(8) :: N, LDU, LDVT, INFO
     INTEGER(8), DIMENSION(:) :: IQ, IWORK
     REAL, DIMENSION(:) :: D, E, Q, WORK
     REAL, DIMENSION(:,:) :: U, VT

  C INTERFACE
     #include <sunperf.h>

     void sbdsdc(char uplo, char compq, int n,  float  *d,  float
               *e,  float *u, int ldu, float *vt, int ldvt, float
               *q, int *iq, int *info);
     void sbdsdc_64(char uplo, char  compq,  long  n,  float  *d,
               float  *e,  float  *u,  long  ldu, float *vt, long
               ldvt, float *q, long *iq, long *info);

PURPOSE

     sbdsdc computes the singular value decomposition (SVD) of  a
     real N-by-N (upper or lower) bidiagonal matrix B:  B = U * S
     * VT, using a divide and conquer method, where S is a diago-
     nal matrix with non-negative diagonal elements (the singular
     values of B), and U and VT are orthogonal matrices  of  left
     and right singular vectors, respectively. SBDSDC can be used
     to compute all singular  values,  and  optionally,  singular
     vectors or singular vectors in compact form.

     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.  See SLASD3 for details.

     The code currently call SLASDQ if singular values  only  are
     desired.   However,  it  can be slightly modified to compute
     singular values using the divide and conquer method.

ARGUMENTS

     UPLO (input)
               = 'U':  B is upper bidiagonal.
               = 'L':  B is lower bidiagonal.

     COMPQ (input)
               Specifies whether singular vectors are to be  com-
               puted as follows:
               = 'N':  Compute singular values only;
               = 'P':  Compute singular values and compute singu-
               lar  vectors  in  compact  form;  =  'I':  Compute
               singular values and singular vectors.

     N (input) The order of the matrix B.  N >= 0.

     D (input/output)
               On entry, the n diagonal elements of the  bidiago-
               nal  matrix  B.   On exit, if INFO=0, the singular
               values of B.
     E (input/output)
               On entry, the elements of E contain the  offdiago-
               nal elements of the bidiagonal matrix whose SVD is
               desired.  On exit, E has been destroyed.

     U (output)
               If  COMPQ = 'I', then:  On exit, if INFO  =  0,  U
               contains the left singular vectors of the bidiago-
               nal matrix.  For other values of COMPQ, U  is  not
               referenced.

     LDU (input)
               The leading dimension of the array U.  LDU  >=  1.
               If  singular vectors are desired, then LDU >= max(
               1, N ).

     VT (output)
               If  COMPQ = 'I', then:  On exit, if INFO = 0,  VT'
               contains the right singular vectors of the bidiag-
               onal matrix.  For other values of COMPQ, VT is not
               referenced.

     LDVT (input)
               The leading dimension of the array VT.  LDVT >= 1.
               If singular vectors are desired, then LDVT >= max(
               1, N ).

     Q (input) If  COMPQ = 'P', then:  On exit, if INFO  =  0,  Q
               and IQ contain the left and right singular vectors
               in a compact form,  requiring  O(N  log  N)  space
               instead  of 2*N**2.  In particular, Q contains all
               the REAL  data  in  LDQ  >=  N*(11  +  2*SMLSIZ  +
               8*INT(LOG_2(N/(SMLSIZ+1)))) words of memory, where
               SMLSIZ is returned by ILAENV and is equal  to  the
               maximum  size  of the subproblems at the bottom of
               the computation  tree  (usually  about  25).   For
               other values of COMPQ, Q is not referenced.

     IQ (output)
               If  COMPQ = 'P', then:  On exit, if INFO  =  0,  Q
               and IQ contain the left and right singular vectors
               in a compact form,  requiring  O(N  log  N)  space
               instead of 2*N**2.  In particular, IQ contains all
               INTEGER    data    in    LDIQ    >=     N*(3     +
               3*INT(LOG_2(N/(SMLSIZ+1)))) words of memory, where
               SMLSIZ is returned by ILAENV and is equal  to  the
               maximum  size  of the subproblems at the bottom of
               the computation  tree  (usually  about  25).   For
               other values of COMPQ, IQ is not referenced.

     WORK (workspace)
               If COMPQ = 'N' then LWORK >= (2 * N).  If COMPQ  =
               'P'  then  LWORK  >= (6 * N).  If COMPQ = 'I' then
               LWORK >= (3 * N**2 + 4 * N).

     IWORK (workspace)
               dimension(8*N)

     INFO (output)
               = 0:  successful exit.
               < 0:  if INFO = -i, the i-th argument had an ille-
               gal value.
               > 0:  The algorithm failed to compute an  singular
               value.   The  update process of divide and conquer
               failed.

FURTHER DETAILS

     Based on contributions by
        Ming Gu and Huan Ren, Computer Science Division,  Univer-
     sity of
        California at Berkeley, USA