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

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

Contents


CHPDI(3F)							     CHPDI(3F)


NAME    [Toc]    [Back]

     CHPDI   - CHPDI computes the determinant, inertia and inverse of a
     complex Hermitian matrix using the	factors	from CHPFA, where the matrix
     is	stored in packed form.

SYNOPSYS    [Toc]    [Back]

      SUBROUTINE CHPDI(AP,N,KPVT,DET,INERT,WORK,JOB)

DESCRIPTION    [Toc]    [Back]

     On	Entry

     AP	COMPLEX	(N*(N+1)/2)
	the output from	CHPFA.

     N INTEGER
	the order of the matrix	A.  KVPT    INTEGER(N)
	the pivot vector from CHPFA.

     WORK COMPLEX(N)
	work vector.  Contents ignored.

     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.

     AP	contains the upper triangle of the inverse of
	the original matrix, stored in packed form.
	The columns of the upper triangle are stored
	sequentially in	a one-dimensional array.

     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	will occur if the inverse is requested and  CHPCO  has
     set RCOND .EQ. 0.0	or  CHPFA  has set  INFO .NE. 0	.  LINPACK.  This
     version dated 08/14/78 .  James Bunch, Univ. Calif. San Diego, Argonne
     Nat. Lab.	Subroutines and	Functions BLAS CAXPY,CCOPY,CDOTC,CSWAP Fortran
     ABS,CABS,CMPLX,CONJG,IABS,MOD,REAL


									PPPPaaaaggggeeee 1111
[ Back ]
 Similar pages
Name OS Title
CHIDI IRIX CHIDI computes the determinant, inertia and inverse of a complex Hermitian matrix using the factors from CHIFA
CPPDI IRIX CPPDI computes the determinant and inverse of a complex Hermitian positive definite matrix using the factors c
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
SSPDI IRIX SSPDI computes the determinant, inertia and inverse of a real symmetric matrix using the factors from SSPFA, w
SSIDI IRIX SSIDI computes the determinant, inertia and inverse of a real symmetric matrix using the factors from SSIFA.
CSIDI IRIX CSIDI computes the determinant and inverse of a complex symmetric matrix using the factors from CSIFA.
CSPDI IRIX CSPDI computes the determinant and inverse of a complex symmetric matrix using the factors from CSPFA, where t
CPODI IRIX CPODI computes the determinant and inverse of a certain complex Hermitian positive definite matrix (see below)
CPBDI IRIX CPBDI computes the determinant of a complex Hermitian positive definite band matrix using the factors computed
Copyright © 2004-2005 DeniX Solutions SRL
newsletter delivery service