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

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

Contents


DGBFA(3F)							     DGBFA(3F)


NAME    [Toc]    [Back]

     DGBFA   - DGBFA factors a double precision	band matrix by elimination.

     DGBFA is usually called by	DGBCO, but it can be called directly with a
     saving in time if	RCOND  is not needed.

SYNOPSYS    [Toc]    [Back]

      SUBROUTINE DGBFA(ABD,LDA,N,ML,MU,IPVT,INFO)

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.

     INFO INTEGER
	= 0  normal value.
	= K  if	 U(K,K)	.EQ. 0.0 .  This is not	an error
	condition for this subroutine, but it does
	indicate that DGBSL will divide	by zero	if
	called.	 Use  RCOND  in	DGBCO for a reliable
	indication of singularity.  Band Storage



									Page 1






DGBFA(3F)							     DGBFA(3F)



	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.  LINPACK.  This
     version dated 08/14/78 .  Cleve Moler, University of New Mexico, Argonne
     National Lab.  Subroutines	and Functions BLAS DAXPY,DSCAL,IDAMAX Fortran
     MAX0,MIN0


									PPPPaaaaggggeeee 2222
[ Back ]
 Similar pages
Name OS Title
DGBDI IRIX DGBDI computes the determinant of a band matrix using the factors computed by DGBCO or DGBFA. If the inverse i
DGBCO IRIX DGBCO factors a double precision band matrix by Gaussian elimination 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
SGBFA IRIX SGBFA factors a real band matrix by elimination. SGBFA is usually called by SBGCO, but it can be called direct
DGECO IRIX DGECO factors a double precision matrix by Gaussian elimination and estimates the condition of the matrix. If
CGBFA IRIX CGBFA factors a complex band matrix by elimination. CGBFA is usually called by CGBCO, but it can be called dir
DPBDI IRIX DPBDI computes the determinant of a double precision symmetric positive definite band matrix using the factors
DSICO IRIX DSICO factors a double precision symmetric matrix by elimination with symmetric pivoting and estimates the con
DSIFA IRIX DSIFA factors a double precision symmetric matrix by elimination with symmetric pivoting. To solve A*X = B , f
DPOFA IRIX DPOFA factors a double precision symmetric positive definite matrix. DPOFA is usually called by DPOCO, but it
Copyright © 2004-2005 DeniX Solutions SRL
newsletter delivery service