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

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

Contents


DGBCO(3F)							     DGBCO(3F)


NAME    [Toc]    [Back]

     DGBCO   - DGBCO factors a double precision	band matrix by Gaussian
     elimination and estimates the condition of	the matrix.

     If	 RCOND	is not needed, DGBFA is	slightly faster.  To solve  A*X	= B ,
     follow DGBCO by DGBSL.  To	compute	 INVERSE(A)*C ,	follow DGBCO by	DGBSL.
     To	compute	 DETERMINANT(A)	, follow DGBCO by DGBDI.

SYNOPSYS    [Toc]    [Back]

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

DESCRIPTION    [Toc]    [Back]

     On	Entry

     ABD DOUBLE	PRECISION(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 DOUBLE PRECISION
	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






DGBCO(3F)							     DGBCO(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 DOUBLE PRECISION(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 used:  LINPACK DGBFA BLAS DAXPY,DDOT,DSCAL,DASUM	Fortran
     DABS,DMAX1,MAX0,MIN0,DSIGN


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