Contents


NAME

     sgesdd - compute the singular value decomposition (SVD) of a
     real  M-by-N  matrix  A,  optionally  computing the left and
     right singular vectors

SYNOPSIS

     SUBROUTINE SGESDD(JOBZ, M, N, A, LDA, S, U, LDU, VT, LDVT, WORK,
           LWORK, IWORK, INFO)

     CHARACTER * 1 JOBZ
     INTEGER M, N, LDA, LDU, LDVT, LWORK, INFO
     INTEGER IWORK(*)
     REAL A(LDA,*), S(*), U(LDU,*), VT(LDVT,*), WORK(*)

     SUBROUTINE SGESDD_64(JOBZ, M, N, A, LDA, S, U, LDU, VT, LDVT, WORK,
           LWORK, IWORK, INFO)

     CHARACTER * 1 JOBZ
     INTEGER*8 M, N, LDA, LDU, LDVT, LWORK, INFO
     INTEGER*8 IWORK(*)
     REAL A(LDA,*), S(*), U(LDU,*), VT(LDVT,*), WORK(*)

  F95 INTERFACE
     SUBROUTINE GESDD(JOBZ, [M], [N], A, [LDA], S, U, [LDU], VT, [LDVT],
            [WORK], [LWORK], [IWORK], [INFO])

     CHARACTER(LEN=1) :: JOBZ
     INTEGER :: M, N, LDA, LDU, LDVT, LWORK, INFO
     INTEGER, DIMENSION(:) :: IWORK
     REAL, DIMENSION(:) :: S, WORK
     REAL, DIMENSION(:,:) :: A, U, VT

     SUBROUTINE GESDD_64(JOBZ, [M], [N], A, [LDA], S, U, [LDU], VT, [LDVT],
            [WORK], [LWORK], [IWORK], [INFO])

     CHARACTER(LEN=1) :: JOBZ
     INTEGER(8) :: M, N, LDA, LDU, LDVT, LWORK, INFO
     INTEGER(8), DIMENSION(:) :: IWORK
     REAL, DIMENSION(:) :: S, WORK
     REAL, DIMENSION(:,:) :: A, U, VT

  C INTERFACE
     #include <sunperf.h>

     void sgesdd(char jobz, int m, int  n,  float  *a,  int  lda,
               float  *s, float *u, int ldu, float *vt, int ldvt,
               int *info);
     void sgesdd_64(char jobz, long m, long  n,  float  *a,  long
               lda, float *s, float *u, long ldu, float *vt, long
               ldvt, long *info);

PURPOSE

     sgesdd computes the singular value decomposition (SVD) of  a
     real  M-by-N  matrix  A,  optionally  computing the left and
     right singular vectors.  If singular vectors are desired, it
     uses a divide-and-conquer algorithm.

     The SVD is written
      = U * SIGMA * transpose(V)

     where SIGMA is an M-by-N matrix which is zero except for its
     min(m,n)  diagonal  elements,  U  is  an  M-by-M  orthogonal
     matrix, and V is an N-by-N orthogonal matrix.  The  diagonal
     elements  of  SIGMA  are  the singular values of A; they are
     real and non-negative, and are returned in descending order.
     The first min(m,n) columns of U and V are the left and right
     singular vectors of A.

     Note that the routine returns VT = V**T, not V.

     The divide and conquer algorithm 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

     JOBZ (input)
               Specifies options for computing all or part of the
               matrix U:
               = 'A':  all M columns of U and all N rows of  V**T
               are  returned  in the arrays U and VT; = 'S':  the
               first min(M,N) columns of U and the first min(M,N)
               rows  of V**T are returned in the arrays U and VT;
               = 'O':  If M >= N, the first N columns  of  U  are
               overwritten  on  the  array A and all rows of V**T
               are returned  in  the  array  VT;  otherwise,  all
               columns  of  U are returned in the array U and the
               first M rows of V**T are overwritten in the  array
               VT;  =  'N':   no columns of U or rows of V**T are
               computed.

     M (input) The number of rows of the input matrix A.  M >= 0.
     N (input) The number of columns of the input matrix A.  N >=
               0.

     A (input/output)
               On entry, the M-by-N matrix A.  On exit, if JOBZ =
               'O',  A is overwritten with the first N columns of
               U (the left singular vectors,  stored  columnwise)
               if  M >= N; A is overwritten with the first M rows
               of V**T (the right singular vectors,  stored  row-
               wise)  otherwise.   if JOBZ .ne. 'O', the contents
               of A are destroyed.

     LDA (input)
               The leading dimension of  the  array  A.   LDA  >=
               max(1,M).

     S (output)
               The singular values of A, sorted so that  S(i)  >=
               S(i+1).

     U (output)
               UCOL = M if JOBZ = 'A' or JOBZ = 'O' and  M  <  N;
               UCOL  =  min(M,N) if JOBZ = 'S'.  If JOBZ = 'A' or
               JOBZ = 'O' and  M  <  N,  U  contains  the  M-by-M
               orthogonal matrix U; if JOBZ = 'S', U contains the
               first min(M,N) columns of  U  (the  left  singular
               vectors,  stored  columnwise); if JOBZ = 'O' and M
               >= N, or JOBZ = 'N', U is not referenced.

     LDU (input)
               The leading dimension of the array U.  LDU  >=  1;
               if  JOBZ = 'S' or 'A' or JOBZ = 'O' and M < N, LDU
               >= M.

     VT (output)
               If JOBZ = 'A' or JOBZ = 'O' and M >=  N,  VT  con-
               tains the N-by-N orthogonal matrix V**T; if JOBZ =
               'S', VT contains the first min(M,N) rows  of  V**T
               (the  right  singular vectors, stored rowwise); if
               JOBZ = 'O' and M < N, or JOBZ =  'N',  VT  is  not
               referenced.

     LDVT (input)
               The leading dimension of the array VT.  LDVT >= 1;
               if JOBZ = 'A' or JOBZ = 'O' and M >= N, LDVT >= N;
               if JOBZ = 'S', LDVT >= min(M,N).

     WORK (workspace)
               On exit, if INFO = 0, WORK(1) returns the  optimal
               LWORK;

     LWORK (input)
               The dimension of the array WORK. LWORK >=  1.   If
               JOBZ    =    'N',    LWORK    >=    3*min(M,N)   +
               max(max(M,N),6*min(M,N)).  If JOBZ = 'O', LWORK >=
               3*min(M,N)*min(M,N)   +   max(max(M,N),5*min(M,N)*
               min(M,N)+4*min(M,N)).  If JOBZ = 'S' or 'A'  LWORK
               >=  3*min(M,N)*min(M,N) + max(max(M,N),4*min(M,N)*
               min(M,N)+4*min(M,N)).  For good performance, LWORK
               should  generally  be  larger.   If  LWORK < 0 but
               other input arguments are legal,  WORK(1)  returns
               optimal LWORK.

     IWORK (workspace)
               dimension(8*MIN(M,N))

     INFO (output)
               = 0:  successful exit.
               < 0:  if INFO = -i, the i-th argument had an ille-
               gal value.
               > 0:  SBDSDC did not  converge,  updating  process
               failed.

FURTHER DETAILS

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