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

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

Contents


SSIDI(3F)							     SSIDI(3F)


NAME    [Toc]    [Back]

     SSIDI   - SSIDI computes the determinant, inertia and inverse of a	real
     symmetric matrix using the	factors	from SSIFA.

SYNOPSYS    [Toc]    [Back]

      SUBROUTINE SSIDI(A,LDA,N,KPVT,DET,INERT,WORK,JOB)

DESCRIPTION    [Toc]    [Back]

     On	Entry

     A REAL(LDA,N)
	the output from	SSIFA.

     LDA INTEGER
	the leading dimension of the array A.

     N INTEGER
	the order of the matrix	A.

     KPVT INTEGER(N)
	the pivot vector from SSIFA.

     WORK REAL(N)
	work vector.  Contents destroyed.

     JOB INTEGER
	JOB has	the decimal expansion  ABC  where
	If  C .NE. 0, the inverse is computed,
	If  B .NE. 0, the determinant is computed,
	If  A .NE. 0, the inertia is computed.
	For example, JOB = 111	gives all three.  On Return Variables not
     requested by JOB are not used.

     A contains	the upper triangle of the inverse of
	the original matrix.  The strict lower triangle
	is never referenced.

     DET REAL(2)
	determinant of original	matrix.
	Determinant = DET(1) * 10.0**DET(2)
	with 1.0 .LE. ABS(DET(1)) .LT. 10.0
	or DET(1) = 0.0.

     INERT INTEGER(3)
	the inertia of the original matrix.
	INERT(1)  =  number of positive	eigenvalues.
	INERT(2)  =  number of negative	eigenvalues.
	INERT(3)  =  number of zero eigenvalues.  Error	Condition

     A division	by zero	may occur if the inverse is requested and  SSICO  has
     set RCOND .EQ. 0.0	or  SSIFA  has set  INFO .NE. 0	.  LINPACK.  This



									Page 1






SSIDI(3F)							     SSIDI(3F)



     version dated 08/14/78 .  James Bunch, Univ. Calif. San Diego, Argonne
     Nat. Lab Subroutines and Functions	BLAS SAXPY,SCOPY,SDOT,SSWAP Fortran
     ABS,IABS,MOD


									PPPPaaaaggggeeee 2222
[ Back ]
 Similar pages
Name OS Title
SSPDI IRIX SSPDI computes the determinant, inertia and inverse of a real symmetric matrix using the factors from SSPFA, w
DSPDI IRIX DSPDI computes the determinant, inertia and inverse of a double precision symmetric matrix using the factors f
DSIDI IRIX DSIDI computes the determinant, inertia and inverse of a double precision symmetric matrix using the factors f
CHIDI IRIX CHIDI computes the determinant, inertia and inverse of a complex Hermitian matrix using the factors from CHIFA
CHPDI IRIX CHPDI computes the determinant, inertia and inverse of a complex Hermitian matrix using the factors from CHPFA
SPPDI IRIX SPPDI computes the determinant and inverse of a real symmetric positive definite matrix using the factors comp
CSPDI IRIX CSPDI computes the determinant and inverse of a complex symmetric matrix using the factors from CSPFA, where t
CSIDI IRIX CSIDI computes the determinant and inverse of a complex symmetric matrix using the factors from CSIFA.
SSIFA IRIX SSIFA factors a real symmetric matrix by elimination with symmetric pivoting. To solve A*X = B , follow SSIFA
SPODI IRIX SPODI computes the determinant and inverse of a certain real symmetric positive definite matrix (see below) us
Copyright © 2004-2005 DeniX Solutions SRL
newsletter delivery service