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

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

Contents


CPBCO(3F)							     CPBCO(3F)


NAME    [Toc]    [Back]

     CPBCO   - CPBCO factors a complex Hermitian positive definite matrix
     stored in band form and estimates the condition of	the matrix.

     If	 RCOND	is not needed, CPBFA is	slightly faster.  To solve  A*X	= B ,
     follow CPBCO by CPBSL.  To	compute	 INVERSE(A)*C ,	follow CPBCO by	CPBSL.
     To	compute	 DETERMINANT(A)	, follow CPBCO by CPBDI.

SYNOPSYS    [Toc]    [Back]

      SUBROUTINE CPBCO(ABD,LDA,N,M,RCOND,Z,INFO)

DESCRIPTION    [Toc]    [Back]

     On	Entry

     ABD COMPLEX(LDA, N)
	the matrix to be factored.  The	columns	of the upper
	triangle are stored in the columns of ABD and the
	diagonals of the upper triangle	are stored in the
	rows of	ABD .  See the comments	below for details.

     LDA INTEGER
	the leading dimension of the array  ABD	.
	LDA must be .GE. M + 1 .

     N INTEGER
	the order of the matrix	 A .

     M INTEGER
	the number of diagonals	above the main diagonal.
	0 .LE. M .LT. N	.  On Return

     ABD an upper triangular matrix  R , stored	in band
	form, so that  A = CTRANS(R)*R .
	If  INFO .NE. 0	, the factorization is not complete.

     RCOND REAL
	an estimate of the reciprocal condition	of  A .
	For the	system	A*X = B	, relative perturbations
	in  A  and  B  of size	EPSILON	 may cause
	relative perturbations in  X  of size  EPSILON/RCOND .
	If  RCOND  is so small that the	logical	expression
	1.0 + RCOND .EQ. 1.0
	is true, then  A  may be singular to working
	precision.  In particular,  RCOND  is zero  if
	exact singularity is detected or the estimate
	underflows.  If	INFO .NE. 0 , RCOND is unchanged.

     Z COMPLEX(N)
	a work vector whose contents are usually unimportant.
	If  A  is singular to working precision, then  Z  is
	an approximate null vector in the sense	that



									Page 1






CPBCO(3F)							     CPBCO(3F)



	NORM(A*Z) = RCOND*NORM(A)*NORM(Z) .
	If  INFO .NE. 0	, Z  is	unchanged.

     INFO INTEGER
	= 0  for normal	return.
	= K  signals an	error condition.  The leading minor
	of order  K  is	not positive definite.	Band Storage
	If  A  is a Hermitian positive definite	band matrix,
	the following program segment will set up the input.
	M = (band width	above diagonal)
	DO 20 J	= 1, N
	I1 = MAX0(1, J-M)
	DO 10 I	= I1, J
	K = I-J+M+1
	ABD(K,J) = A(I,J)
	10    CONTINUE
	20 CONTINUE
	This uses  M + 1  rows of  A , except for the  M by M
	upper left triangle, which is ignored.	Example:  If the original
     matrix is
	11 12 13  0  0	0
	12 22 23 24  0	0
	13 23 33 34 35	0
	0 24 34	44 45 46
	0  0 35	45 55 56
	0  0  0	46 56 66 then  N = 6 , M = 2  and  ABD	should contain
	*  * 13	24 35 46
	* 12 23	34 45 56
	11 22 33 44 55 66 LINPACK.  This version dated 08/14/78	.  Cleve
     Moler, University of New Mexico, Argonne National Lab.  Subroutines and
     Functions LINPACK CPBFA BLAS CAXPY,CDOTC,CSSCAL,SCASUM Fortran
     ABS,AIMAG,AMAX1,CMPLX,CONJG,MAX0,MIN0,REAL


									PPPPaaaaggggeeee 2222
[ Back ]
 Similar pages
Name OS Title
CPPCO IRIX CPPCO factors a complex Hermitian positive definite matrix stored in packed form and estimates the condition o
SPBCO IRIX SPBCO factors a real symmetric positive definite matrix stored in band form and estimates the condition of the
CPBFA IRIX CPBFA factors a complex Hermitian positive definite matrix stored in band form. CPBFA is usually called by CPB
SPPCO IRIX SPPCO factors a real symmetric positive definite matrix stored in packed form and estimates the condition of t
DPBCO IRIX DPBCO factors a double precision symmetric positive definite matrix stored in band form and estimates the cond
CPOCO IRIX CPOCO factors a complex Hermitian positive definite matrix and estimates the condition of the matrix. If RCOND
CPBSL IRIX CPBSL solves the complex Hermitian positive definite band system A*X = B using the factors computed by CPBCO o
CPPFA IRIX CPPFA factors a complex Hermitian positive definite matrix stored in packed form. CPPFA is usually called by C
DPPCO IRIX DPPCO factors a double precision symmetric positive definite matrix stored in packed form and estimates the co
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