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

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

Contents


DPPCO(3F)							     DPPCO(3F)


NAME    [Toc]    [Back]

     DPPCO   - DPPCO factors a double precision	symmetric positive definite
     matrix stored in packed form and estimates	the condition of the matrix.

     If	 RCOND	is not needed, DPPFA is	slightly faster.  To solve  A*X	= B ,
     follow DPPCO by DPPSL.  To	compute	 INVERSE(A)*C ,	follow DPPCO by	DPPSL.
     To	compute	 DETERMINANT(A)	, follow DPPCO by DPPDI.  To compute
     INVERSE(A)	, follow DPPCO by DPPDI.

SYNOPSYS    [Toc]    [Back]

      SUBROUTINE DPPCO(AP,N,RCOND,Z,INFO)

DESCRIPTION    [Toc]    [Back]

     On	Entry

     AP	DOUBLE PRECISION (N*(N+1)/2)
	the packed form	of a symmetric matrix  A .  The
	columns	of the upper triangle are stored sequentially
	in a one-dimensional array of length  N*(N+1)/2	.
	See comments below for details.

     N INTEGER
	the order of the matrix	 A .  On Return

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

     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 .
	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 DOUBLE PRECISION(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
	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.	Packed Storage The following



									Page 1






DPPCO(3F)							     DPPCO(3F)



     program segment will pack the upper triangle of a symmetric matrix.
	K = 0
	DO 20 J	= 1, N
	DO 10 I	= 1, J
	K = K +	1
	AP(K) =	A(I,J)
	10    CONTINUE
	20 CONTINUE LINPACK.  This version dated 08/14/78 .  Cleve Moler,
     University	of New Mexico, Argonne National	Lab.  Subroutines and
     Functions LINPACK DPPFA BLAS DAXPY,DDOT,DSCAL,DASUM Fortran
     DABS,DMAX1,DREAL,DSIGN


									PPPPaaaaggggeeee 2222
[ Back ]
 Similar pages
Name OS Title
DPBCO IRIX DPBCO factors a double precision symmetric positive definite matrix stored in band form and estimates the cond
DPPFA IRIX DPPFA factors a double precision symmetric positive definite matrix stored in packed form. DPPFA is usually ca
SPPCO IRIX SPPCO factors a real symmetric positive definite matrix stored in packed form and estimates the condition of t
DPBFA IRIX DPBFA factors a double precision symmetric positive definite matrix stored in band form. DPBFA is usually call
DPOCO IRIX DPOCO factors a double precision symmetric positive definite matrix and estimates the condition of the matrix.
DSPCO IRIX DSPCO factors a double precision symmetric matrix stored in packed form by elimination with symmetric pivoting
DSPFA IRIX DSPFA factors a double precision symmetric matrix stored in packed form by elimination with symmetric pivoting
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
SPPFA IRIX SPPFA factors a real symmetric positive definite matrix stored in packed form. SPPFA is usually called by SPPC
Copyright © 2004-2005 DeniX Solutions SRL
newsletter delivery service