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

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

Contents


CGBCO(3F)							     CGBCO(3F)


NAME    [Toc]    [Back]

     CGBCO   - CGBCO factors a complex band matrix by Gaussian elimination and
     estimates the condition of	the matrix.

     If	 RCOND	is not needed, CGBFA is	slightly faster.  To solve  A*X	= B ,
     follow CGBCO by CGBSL.  To	compute	 INVERSE(A)*C ,	follow CGBCO by	CGBSL.
     To	compute	 DETERMINANT(A)	, follow CGBCO by CGBDI.

SYNOPSYS    [Toc]    [Back]

      SUBROUTINE CGBCO(ABD,LDA,N,ML,MU,IPVT,RCOND,Z)

DESCRIPTION    [Toc]    [Back]

     On	Entry

     ABD COMPLEX(LDA, N)
	contains the matrix in band storage.  The columns
	of the matrix are stored in the	columns	of  ABD	 and
	the diagonals of the matrix are	stored in rows
	ML+1 through 2*ML+MU+1 of  ABD .
	See the	comments below for details.

     LDA INTEGER
	the leading dimension of the array  ABD	.
	LDA must be .GE. 2*ML +	MU + 1 .

     N INTEGER
	the order of the original matrix.

     ML	INTEGER
	number of diagonals below the main diagonal.
	0 .LE. ML .LT. N .

     MU	INTEGER
	number of diagonals above the main diagonal.
	0 .LE. MU .LT. N .
	More efficient if  ML .LE. MU .	 On Return

     ABD an upper triangular matrix in band storage and
	the multipliers	which were used	to obtain it.
	The factorization can be written  A = L*U  where
	L  is a	product	of permutation and unit	lower
	triangular matrices and	 U  is upper triangular.

     IPVT INTEGER(N)
	an integer vector of pivot indices.

     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 .



									Page 1






CGBCO(3F)							     CGBCO(3F)



	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.

     Z COMPLEX(N)
	a work vector whose contents are usually unimportant.
	If  A  is close	to a singular matrix, then  Z  is
	an approximate null vector in the sense	that
	NORM(A*Z) = RCOND*NORM(A)*NORM(Z) .  Band Storage
	if  A  is a band matrix, the following program segment
	will set up the	input.
	ML = (band width below the diagonal)
	MU = (band width above the diagonal)
	M = ML + MU + 1
	DO 20 J	= 1, N
	I1 = MAX0(1, J-MU)
	I2 = MIN0(N, J+Ml)
	DO 10 I	= I1, I2
	K = I -	J + M
	ABD(K,J) = A(I,J)
	10    CONTINUE
	20 CONTINUE
	This uses rows	ML+1  through  2*ML+MU+1  of  ABD .
	In addition, the first	ML  rows in  ABD  are used for
	elements generated during the triangularization.
	The total number of rows needed	in  ABD	 is  2*ML+MU+1 .
	The  ML+MU by ML+MU  upper left	triangle and the
	ML by ML  lower	right triangle are not referenced.  Example:  If the
     original matrix is
	11 12 13  0  0	0
	21 22 23 24  0	0
	0 32 33	34 35  0
	0  0 43	44 45 46
	0  0  0	54 55 56
	0  0  0	 0 65 66 then  N = 6, ML = 1, MU = 2, LDA .GE. 5  and ABD
     should contain
	*  *  *	 +  +  +  , * =	not used
	*  * 13	24 35 46  , + =	used for pivoting
	* 12 23	34 45 56
	11 22 33 44 55 66
	21 32 43 54 65	* LINPACK.  This version dated 08/14/78	.  Cleve
     Moler, University of New Mexico, Argonne National Lab.  Subroutines and
     Functions LINPACK CGBFA BLAS CAXPY,CDOTC,CSSCAL,SCASUM Fortran
     ABS,AIMAG,AMAX1,CMPLX,CONJG,MAX0,MIN0,REAL


									PPPPaaaaggggeeee 2222
[ Back ]
 Similar pages
Name OS Title
SGBCO IRIX SBGCO factors a real band matrix by Gaussian elimination and estimates the condition of the matrix. If RCOND i
DGBCO IRIX DGBCO factors a double precision band matrix by Gaussian elimination and estimates the condition of the matrix
CGECO IRIX CGECO factors a complex matrix by Gaussian elimination and estimates the condition of the matrix. If RCOND is
SGECO IRIX SGECO factors a real matrix by Gaussian elimination and estimates the condition of the matrix. If RCOND is not
DGECO IRIX DGECO factors a double precision matrix by Gaussian elimination and estimates the condition of the matrix. If
CHICO IRIX CHICO factors a complex Hermitian matrix by elimination with symmetric pivoting and estimates the condition of
CPBCO IRIX CPBCO factors a complex Hermitian positive definite matrix stored in band form and estimates the condition of
CSICO IRIX CSICO factors a complex symmetric matrix by elimination with symmetric pivoting and estimates the condition of
CGBFA IRIX CGBFA factors a complex band matrix by elimination. CGBFA is usually called by CGBCO, but it can be called dir
CPOCO IRIX CPOCO factors a complex Hermitian positive definite matrix and estimates the condition of the matrix. If RCOND
Copyright © 2004-2005 DeniX Solutions SRL
newsletter delivery service