zcgesv man page on OpenIndiana

Man page or keyword search:  
man Server   20441 pages
apropos Keyword Search (all sections)
Output format
OpenIndiana logo
[printable version]

zcgesv(3P)		    Sun Performance Library		    zcgesv(3P)

NAME
       zcgesv  - computes the solution to a complex system of linear equations
       A * X = B

SYNOPSIS
       SUBROUTINE ZCGESV(N, NRHS, A, LDA, IPIV, B, LDB, X, LDX, WORK, SWORK, ITER, INFO)

       INTEGER N, NRHS, LDA, LDB, LDX, ITER, INFO
       INTEGER IPIV(*)
       COMPLEX SWORK(*)
       DOUBLE COMPLEX A(LDA,*), B(LDB,*), WORK(N,*), X(LDX,*)

       SUBROUTINE ZCGESV_64(N, NRHS, A, LDA, IPIV, B, LDB, X, LDX, WORK, SWORK, ITER, INFO)

       INTEGER*8 N, NRHS, LDA, LDB, LDX, ITER, INFO
       INTEGER*8 IPIV(*)
       COMPLEX SWORK(*)
       DOUBLE COMPLEX A(LDA,*), B(LDB,*), WORK(N,*), X(LDX,*)

   F95 INTERFACE
       SUBROUTINE CGESV([N], NRHS, A, [LDA], IPIV, B, [LDB], X, [LDX], [WORK], [SWORK], ITER, [INFO])

       INTEGER :: M, N, LDA, INFO
       INTEGER, DIMENSION(:) :: IPIV
       DOUBLE COMPLEX, DIMENSION(:,:) :: A, B, X, WORK

       SUBROUTINE CGESV_64(([N], NRHS, A, [LDA], IPIV, B, [LDB], X, [LDX], [WORK], [SWORK], ITER, [INFO])

       INTEGER(8) :: N, NRHS, LDA, LDB, LDX, ITER, INFO
       INTEGER(8), DIMENSION(:) :: IPIV
       DOUBLE COMPLEX, DIMENSION(:,:) :: A, B, X, WORK

   C INTERFACE
       #include <sunperf.h>

       void zcgesv(int n, int nrhs, doublecomplex *a, int lda, int *ipiv, dou‐
		 blecomplex *b, int ldb, doublecomplex *x, int ldx, doublecom‐
		 plex *work, complex *swork, int iter, int *info);

       void zcgesv_64(long n, long nrhs,  doublecomplex	 *a,  long  lda,  long
		 *ipiv,	 doublecomplex	*b,  long  ldb, doublecomplex *x, long
		 ldx, doublecomplex *work, complex  *swork,  long  iter,  long
		 *info);

PURPOSE
       zcgesv computes the solution to a complex system of linear equations
	    A * X = B,
       where A is an N-by-N matrix and X and B are N-by-NRHS matrices.
       zcgesv  first attempts to factorize the matrix in SINGLE COMPLEX PRECI‐
       SION and use this factorization within an iterative  refinement	proce‐
       dure to produce a solution with DOUBLE COMPLEX PRECISION normwise back‐
       ward error quality (see	below).	 If  the  approach  fails  the	method
       switches to a DOUBLE COMPLEX PRECISION factorization and solve.

       The  iterative  refinement is not going to be a winning strategy if the
       ratio SINGLE PRECISION performance over DOUBLE PRECISION performance is
       too  small.  A reasonable strategy should take the number of right-hand
       sides and the size of the matrix into account. This might be done  with
       a  call	to  ILAENV  in	the future. Up to now, we always try iterative
       refinement.  The iterative refinement process is stopped if
	   ITER > ITERMAX
       or for all the RHS we have:
	   RNRM < SQRT(N)*XNRM*ANRM*EPS*BWDMAX
       where
	   o ITER is the number of the current iteration in the iterative
	     refinement process
	   o RNRM is the infinity-norm of the residual
	   o XNRM is the infinity-norm of the solution
	   o ANRM is the infinity-operator-norm of the matrix A
	   o EPS is the machine	 epsilon  returned  by	DLAMCH('Epsilon')  The
       value ITERMAX and BWDMAX are fixed to 30 and 1.0D+00 respectively.

ARGUMENTS
       N (input) INTEGER
		 The number of linear equations, i.e., the order of the matrix
		 A.  N >= 0.

       NRHS (input)  INTEGER
		 The number of right hand sides, i.e., the number  of  columns
		 of the matrix B.  NRHS >= 0.

       A (input or input/output) DOUBLE COMPLEX array
		 On entry, the N-by-N coefficient matrix A.  On exit, if iter‐
		 ative refinement has been successfully	 used  (INFO.EQ.0  and
		 ITER.GE.0,  see  description  below), then A is unchanged, if
		 double precision factorization has been used  (INFO.EQ.0  and
		 ITER.LT.0,  see description below), then the array A contains
		 the factors L and U from the factorization  A	=  P*L*U;  the
		 unit diagonal elements of L are not stored.

       LDA (input) INTEGER
		 The leading dimension of the array A.	LDA >= max(1,N).

       IPIV (output) INTEGER array, dimension (N)
		 The pivot indices that define the permutation matrix P; row i
		 of the matrix was interchanged with row IPIV(i).  Corresponds
		 either	 to  the  single precision factorization (if INFO.EQ.0
		 and ITER.GE.0) or  the	 double	 precision  factorization  (if
		 INFO.EQ.0 and ITER.LT.0).

       B (input)  DOUBLE COMPLEX array, dimension (LDB,NRHS)
		 The N-by-NRHS matrix of right hand side matrix B.

       LDB (input) INTEGER
		 The leading dimension of the array B.	LDB >= max(1,N).

       X (output) DOUBLE COMPLEX array, dimension (LDX,NRHS)
		 If INFO = 0, the N-by-NRHS solution matrix X.

       LDX (input) INTEGER
		 The leading dimension of the array X.	LDX >= max(1,N).

       WORK    (workspace) DOUBLE COMPLEX array, dimension (N,NRHS)
		 This array is used to hold the residual vectors.

       SWORK   (workspace) COMPLEX array, dimension (N*(N+NRHS))
		 This array is used to use the single precision matrix and the
		 right-hand sides or solutions in single precision.

       ITER    (output) INTEGER
		 < 0: iterative refinement has failed, double  precision  fac‐
		 torization has been performed
		 -1 : taking into account machine parameters, N, NRHS, it is a
		 priori not worth working in SINGLE PRECISION
		 -2 : overflow of an entry when moving from double  to	SINGLE
		 PRECISION
		 -3 : failure of SGETRF
		 -31: stop the iterative refinement after the 30th iterations
		 > 0: iterative refinement has been sucessfully used.  Returns
		 the number of iterations

       INFO (output) INTEGER
		 = 0:  successful exit
		 < 0:  if INFO = -i, the i-th argument had an illegal value
		 > 0:  if INFO = i, U(i,i) computed  in	 DOUBLE	 PRECISION  is
		 exactly  zero.	 The factorization has been completed, but the
		 factor U is exactly singular, so the solution	could  not  be
		 computed.

				  6 Mar 2009			    zcgesv(3P)
[top]

List of man pages available for OpenIndiana

Copyright (c) for man pages and the logo by the respective OS vendor.

For those who want to learn more, the polarhome community provides shell access and support.

[legal] [privacy] [GNU] [policy] [cookies] [netiquette] [sponsors] [FAQ]
Tweet
Polarhome, production since 1999.
Member of Polarhome portal.
Based on Fawad Halim's script.
....................................................................
Vote for polarhome
Free Shell Accounts :: the biggest list on the net