*nix Documentation Project
·  Home
 +   man pages
·  Linux HOWTOs
·  FreeBSD Tips
·  *niX Forums

  man pages->IRIX man pages -> complib/DSVDC (3)              
Title
Content
Arch
Section
 

Contents


DSVDC(3F)							     DSVDC(3F)


NAME    [Toc]    [Back]

     DSVDC   - DSVDC is	a subroutine to	reduce a double	precision 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.

SYNOPSYS    [Toc]    [Back]

      SUBROUTINE DSVDC(X,LDX,N,P,S,E,U,LDU,V,LDV,WORK,JOB,INFO)

DESCRIPTION    [Toc]    [Back]

     On	Entry

     X DOUBLE PRECISION(LDX,P),	where LDX .GE. N.
	X contains the matrix whose singular value
	decomposition is to be computed.  X is
	destroyed by DSVDC.

     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 DOUBLE PRECISION(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






DSVDC(3F)							     DSVDC(3F)



	in V.  On Return

     S DOUBLE PRECISION(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 DOUBLE PRECISION(P).
	E ordinarily contains zeros.  However see the
	discussion of INFO for exceptions.

     U DOUBLE PRECISION(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 DOUBLE PRECISION(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.

     DSVDC uses	the following functions	and subprograms. External DROT BLAS
     DAXPY,DDOT,DSCAL,DSWAP,DNRM2,DROTG	Fortran	DABS,DMAX1,MAX0,MIN0,MOD,DSQRT


									PPPPaaaaggggeeee 2222
[ Back ]
 Similar pages
Name OS Title
SSVDC IRIX SSVDC is a subroutine to reduce a real NxP matrix X by orthogonal transformations U and V to diagonal form. Th
CSVDC IRIX CSVDC is a subroutine to reduce a complex NxP matrix X by unitary transformations U and V to diagonal form. Th
ORTRAN IRIX EISPACK routine. This subroutine accumulates the orthogonal similarity transformations used in the reduction o
dgghrd IRIX reduce a pair of real matrices (A,B) to generalized upper Hessenberg form using orthogonal transformations, wh
sgghrd IRIX reduce a pair of real matrices (A,B) to generalized upper Hessenberg form using orthogonal transformations, wh
DGECO IRIX DGECO factors a double precision matrix by Gaussian elimination and estimates the condition of the matrix. If
DPOCO IRIX DPOCO factors a double precision symmetric positive definite matrix and estimates the condition of the matrix.
DGBCO IRIX DGBCO factors a double precision band matrix by Gaussian elimination and estimates the condition of the matrix
DTRCO IRIX DTRCO estimates the condition of a double precision triangular matrix.
sgbbrd IRIX reduce a real general m-by-n band matrix A to upper bidiagonal form B by an orthogonal transformation
Copyright © 2004-2005 DeniX Solutions SRL
newsletter delivery service