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


FURTHER DETAILS

Based on contributions by

   Ming Gu and Huan Ren, Computer Science Division, University of
   California at Berkeley, USA