Contents


NAME

     cgesvd - compute the singular value decomposition (SVD) of a
     complex  M-by-N  matrix  A,  optionally  computing  the left
     and/or right singular vectors

SYNOPSIS

     SUBROUTINE CGESVD(JOBU, JOBVT, M, N, A, LDA, SING, U, LDU, VT, LDVT,
           WORK, LDWORK, WORK2, INFO)

     CHARACTER * 1 JOBU, JOBVT
     COMPLEX A(LDA,*), U(LDU,*), VT(LDVT,*), WORK(*)
     INTEGER M, N, LDA, LDU, LDVT, LDWORK, INFO
     REAL SING(*), WORK2(*)

     SUBROUTINE CGESVD_64(JOBU, JOBVT, M, N, A, LDA, SING, U, LDU, VT,
           LDVT, WORK, LDWORK, WORK2, INFO)

     CHARACTER * 1 JOBU, JOBVT
     COMPLEX A(LDA,*), U(LDU,*), VT(LDVT,*), WORK(*)
     INTEGER*8 M, N, LDA, LDU, LDVT, LDWORK, INFO
     REAL SING(*), WORK2(*)

  F95 INTERFACE
     SUBROUTINE GESVD(JOBU, JOBVT, [M], [N], A, [LDA], SING, U, [LDU], VT,
            [LDVT], [WORK], [LDWORK], [WORK2], [INFO])

     CHARACTER(LEN=1) :: JOBU, JOBVT
     COMPLEX, DIMENSION(:) :: WORK
     COMPLEX, DIMENSION(:,:) :: A, U, VT
     INTEGER :: M, N, LDA, LDU, LDVT, LDWORK, INFO
     REAL, DIMENSION(:) :: SING, WORK2

     SUBROUTINE GESVD_64(JOBU, JOBVT, [M], [N], A, [LDA], SING, U, [LDU],
            VT, [LDVT], [WORK], [LDWORK], [WORK2], [INFO])

     CHARACTER(LEN=1) :: JOBU, JOBVT
     COMPLEX, DIMENSION(:) :: WORK
     COMPLEX, DIMENSION(:,:) :: A, U, VT
     INTEGER(8) :: M, N, LDA, LDU, LDVT, LDWORK, INFO
     REAL, DIMENSION(:) :: SING, WORK2

  C INTERFACE
     #include <sunperf.h>

     void cgesvd(char jobu, char jobvt, int m, int n, complex *a,
               int lda, float *sing, complex *u, int ldu, complex
               *vt, int ldvt, int *info);
     void cgesvd_64(char jobu, char jobvt, long m, long  n,  com-
               plex  *a,  long lda, float *sing, complex *u, long
               ldu, complex *vt, long ldvt, long *info);

PURPOSE

     cgesvd computes the singular value decomposition (SVD) of  a
     complex  M-by-N  matrix  A,  optionally  computing  the left
     and/or right singular vectors. The SVD is written
      = U * SIGMA * conjugate-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 unitary matrix,
     and V is an N-by-N unitary 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 V**H, not V.

ARGUMENTS

     JOBU (input)
               Specifies options for computing all or part of the
               matrix U:
               = 'A':  all M columns of U are returned  in  array
               U:
               = 'S':  the first min(m,n) columns of U (the  left
               singular  vectors)  are returned in the array U; =
               'O':  the first min(m,n) columns of  U  (the  left
               singular  vectors) are overwritten on the array A;
               = 'N':  no columns of U (no left singular vectors)
               are computed.

     JOBVT (input)
               Specifies options for computing all or part of the
               matrix V**H:
               = 'A':  all N rows of V**H  are  returned  in  the
               array VT;
               = 'S':  the first min(m,n) rows of V**H (the right
               singular  vectors) are returned in the array VT; =
               'O':  the first min(m,n) rows of V**H  (the  right
               singular  vectors) are overwritten on the array A;
               = 'N':  no rows of V**H (no  right  singular  vec-
               tors) are computed.

               JOBVT and JOBU cannot both be 'O'.
     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 JOBU =
               'O',   A  is  overwritten  with the first min(m,n)
               columns of U (the left  singular  vectors,  stored
               columnwise); if JOBVT = 'O', A is overwritten with
               the first min(m,n) rows of V**H (the right  singu-
               lar vectors, stored rowwise); if JOBU .ne. 'O' and
               JOBVT .ne. 'O', the contents of A are destroyed.

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

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

     U (input) (LDU,M) if JOBU = 'A' or (LDU,min(M,N)) if JOBU  =
               'S'.  If JOBU = 'A', U contains the M-by-M unitary
               matrix U; if JOBU =  'S',  U  contains  the  first
               min(m,n)  columns of U (the left singular vectors,
               stored columnwise); if JOBU = 'N' or 'O', U is not
               referenced.

     LDU (input)
               The leading dimension of the array U.  LDU  >=  1;
               if JOBU = 'S' or 'A', LDU >= M.

     VT (input)
               If JOBVT = 'A', VT  contains  the  N-by-N  unitary
               matrix V**H; if JOBVT = 'S', VT contains the first
               min(m,n) rows of V**H (the right singular vectors,
               stored  rowwise); if JOBVT = 'N' or 'O', VT is not
               referenced.

     LDVT (input)
               The leading dimension of the array VT.  LDVT >= 1;
               if JOBVT = 'A', LDVT >= N; if JOBVT = 'S', LDVT >=
               min(M,N).
     WORK (workspace)
               On exit, if INFO = 0, WORK(1) returns the  optimal
               LDWORK.

     LDWORK (input)
               The dimension of the  array  WORK.  LDWORK  >=  1.
               LDWORK  >=   2*MIN(M,N)+MAX(M,N)  For good perfor-
               mance, LDWORK should generally be larger.

               If LDWORK = -1, then a workspace query is assumed;
               the  routine  only  calculates the optimal size of
               the WORK array, returns this value  as  the  first
               entry  of  the  WORK  array,  and no error message
               related to LDWORK is issued by XERBLA.

     WORK2 (workspace)
               DIMENSION(5*MIN(M,N)).  On  exit,  if  INFO  >  0,
               WORK2(1:MIN(M,N)-1)   contains   the   unconverged
               superdiagonal  elements  of  an  upper  bidiagonal
               matrix  B  whose  diagonal  is in SING (not neces-
               sarily sorted).  B satisfies A = U * B * VT, so it
               has  the  same  singular values as A, and singular
               vectors related by U and VT.

     INFO (output)
               = 0:  successful exit.
               < 0:  if INFO = -i, the i-th argument had an ille-
               gal value.
               > 0:  if CBDSQR did not converge,  INFO  specifies
               how many superdiagonals of an intermediate bidiag-
               onal form B did not  converge  to  zero.  See  the
               description of WORK2 above for details.