| 
SSVDC(3F)							     SSVDC(3F)
      SSVDC   - SSVDC is	a subroutine to	reduce a real NxP matrix X by
     orthogonal	transformations	U and V	to diagonal form.  The diagonal
     elements S(I) are the singular values of X.  The columns of U are the
     corresponding left	singular vectors, and the columns of V the right
     singular vectors.
      SUBROUTINE SSVDC(X,LDX,N,P,S,E,U,LDU,V,LDV,WORK,JOB,INFO)
      On	Entry
     X REAL(LDX,P), where LDX .GE. N.
	X contains the matrix whose singular value
	decomposition is to be computed.  X is
	destroyed by SSVDC.
     LDX INTEGER
	LDX is the leading dimension of	the array X.
     N INTEGER
	N is the number	of columns of the matrix X.
     P INTEGER
	P is the number	of rows	of the matrix X.
     LDU INTEGER
	LDU is the leading dimension of	the array U.
	(See below).
     LDV INTEGER
	LDV is the leading dimension of	the array V.
	(See below).
     WORK REAL(N)
	work is	a scratch array.
     JOB INTEGER
	JOB controls the computation of	the singular
	vectors.  It has the decimal expansion AB
	with the following meaning
	A .EQ. 0  Do not compute the left singular
	vectors.
	A .EQ. 1  Return the N left singular vectors
	in U.
	A .GE. 2  Return the first MIN(N,P) singular
	vectors	in U.
	B .EQ. 0  Do not compute the right singular
	vectors.
	B .EQ. 1  Return the right singular vectors
									Page 1
SSVDC(3F)							     SSVDC(3F)
	in V.  On Return
     S REAL(MM), where MM=MIN(N+1,P).
	The first MIN(N,P) entries of S	contain	the
	singular values	of X arranged in descending
	order of magnitude.
     E REAL(P).
	E ordinarily contains zeros.  However, see the
	discussion of INFO for exceptions.
     U REAL(LDU,K), where LDU .GE. N.  If JOBA .EQ. 1, then
	K .EQ. N.  If JOBA .GE.	2 , then
	K .EQ. MIN(N,P).
	U contains the matrix of right singular	vectors.
	U is not referenced if JOBA .EQ. 0.  If	N .LE. P
	or if JOBA .EQ.	2, then	U may be identified with X
	in the subroutine call.
     V REAL(LDV,P), where LDV .GE. P.
	V contains the matrix of right singular	vectors.
	V is not referenced if JOB .EQ.	0.  If P .LE. N,
	then V may be identified with X	in the
	subroutine call.
     INFO INTEGER.
	the singular values (and their corresponding
	singular vectors) S(INFO+1),S(INFO+2),...,S(M)
	are correct (here M=MIN(N,P)).	Thus if
	INFO .EQ. 0, all the singular values and their
	vectors	are correct.  In any event, the	matrix
	B = TRANS(U)*X*V is the	bidiagonal matrix
	with the elements of S on its diagonal and the
	elements of E on its super-diagonal (TRANS(U)
	is the transpose of U).	 Thus the singular
	values of X and	B are the same.	 LINPACK.  This	version	dated 03/19/79
     .	G. W. Stewart, University of Maryland, Argonne National	Lab.  External
     SROT BLAS SAXPY,SDOT,SSCAL,SSWAP,SNRM2,SROTG Fortran
     ABS,AMAX1,MAX0,MIN0,MOD,SQRT
									PPPPaaaaggggeeee 2222[ Back ] |