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

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

Contents


CSVDC(3F)							     CSVDC(3F)


NAME    [Toc]    [Back]

     CSVDC   - CSVDC is	a subroutine to	reduce a complex NxP matrix X by
     unitary 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 CSVDC(X,LDX,N,P,S,E,U,LDU,V,LDV,WORK,JOB,INFO)

DESCRIPTION    [Toc]    [Back]

     On	Entry

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

     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 COMPLEX(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)
	left singular vectors in U.
	B .EQ. 0    Do not compute the right singular
	vectors.
	B .EQ. 1    Return the right singular vectors



									Page 1






CSVDC(3F)							     CSVDC(3F)



	in V.  On Return

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

     U COMPLEX(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 .GT.	2, then	U may be identified with X
	in the subroutine call.

     V COMPLEX(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 = CTRANS(U)*X*V is the bidiagonal matrix
	with the elements of S on its diagonal and the
	elements of E on its super-diagonal (CTRANS(U)
	is the conjugate-transpose of U).  Thus	the
	singular values	of X and B are the same.  LINPACK.  This version dated
     03/19/79 .	 Stewart, G. W., University of Maryland, Argonne National Lab.

     CSVDC uses	the following functions	and subprograms. External CSROT	BLAS
     CAXPY,CDOTC,CSCAL,CSWAP,SCNRM2,SROTG Fortran ABS,AIMAG,AMAX1,CABS,CMPLX
     Fortran CONJG,MAX0,MIN0,MOD,REAL,SQRT


									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
cgghrd IRIX reduce a pair of complex matrices (A,B) to generalized upper Hessenberg form using unitary transformations, wh
zgghrd IRIX reduce a pair of complex matrices (A,B) to generalized upper Hessenberg form using unitary transformations, wh
chptrd IRIX reduce a complex Hermitian matrix A stored in packed form to real symmetric tridiagonal form T by a unitary si
zhptrd IRIX reduce a complex Hermitian matrix A stored in packed form to real symmetric tridiagonal form T by a unitary si
cgebrd IRIX reduce a general complex M-by-N matrix A to upper or lower bidiagonal form B by a unitary transformation
cgehd2 IRIX reduce a complex general matrix A to upper Hessenberg form H by a unitary similarity transformation
cgehrd IRIX reduce a complex general matrix A to upper Hessenberg form H by a unitary similarity transformation
zgebrd IRIX reduce a general complex M-by-N matrix A to upper or lower bidiagonal form B by a unitary transformation
zgehrd IRIX reduce a complex general matrix A to upper Hessenberg form H by a unitary similarity transformation
Copyright © 2004-2005 DeniX Solutions SRL
newsletter delivery service