1ZCGESV(1)        LAPACK PROTOTYPE driver routine (version 3.2)       ZCGESV(1)
2
3
4

NAME

6       ZCGESV  - computes the solution to a complex system of linear equations
7       A * X = B,
8

SYNOPSIS

10       SUBROUTINE ZCGESV( N, NRHS, A, LDA, IPIV, B, LDB, X, LDX, WORK,
11
12           +              SWORK, RWORK, ITER, INFO )
13
14           INTEGER        INFO, ITER, LDA, LDB, LDX, N, NRHS
15
16           INTEGER        IPIV( * )
17
18           DOUBLE         PRECISION RWORK( * )
19
20           COMPLEX        SWORK( * )
21
22           COMPLEX*16     A( LDA, * ), B( LDB, * ), WORK( N, * ),
23
24           +              X( LDX, * )
25

PURPOSE

27       ZCGESV computes the solution to a complex system of linear equations
28          A * X = B, where A is an N-by-N matrix and X  and  B  are  N-by-NRHS
29       matrices.  ZCGESV first attempts to factorize the matrix in COMPLEX and
30       use this factorization within an iterative refinement procedure to pro‐
31       duce  a  solution  with COMPLEX*16 normwise backward error quality (see
32       below).  If the approach fails the method switches to a COMPLEX*16 fac‐
33       torization and solve.
34       The  iterative  refinement is not going to be a winning strategy if the
35       ratio COMPLEX performance over COMPLEX*16 performance is too  small.  A
36       reasonable  strategy should take the number of right-hand sides and the
37       size of the matrix into account. This might be  done  with  a  call  to
38       ILAENV in the future. Up to now, we always try iterative refinement.
39       The iterative refinement process is stopped if
40           ITER > ITERMAX
41       or for all the RHS we have:
42           RNRM < SQRT(N)*XNRM*ANRM*EPS*BWDMAX
43       where
44           o ITER is the number of the current iteration in the iterative
45             refinement process
46           o RNRM is the infinity-norm of the residual
47           o XNRM is the infinity-norm of the solution
48           o ANRM is the infinity-operator-norm of the matrix A
49           o  EPS  is  the  machine  epsilon returned by DLAMCH('Epsilon') The
50       value ITERMAX and BWDMAX are fixed to 30 and 1.0D+00
51       respectively.
52

ARGUMENTS

54       N       (input) INTEGER
55               The number of linear equations, i.e., the order of  the  matrix
56               A.  N >= 0.
57
58       NRHS    (input) INTEGER
59               The  number of right hand sides, i.e., the number of columns of
60               the matrix B.  NRHS >= 0.
61
62       A       (input or input/ouptut) COMPLEX*16 array,
63               dimension (LDA,N) On entry, the N-by-N  coefficient  matrix  A.
64               On  exit,  if  iterative  refinement has been successfully used
65               (INFO.EQ.0 and ITER.GE.0, see description  below),  then  A  is
66               unchanged,  if  double  precision  factorization  has been used
67               (INFO.EQ.0 and ITER.LT.0,  see  description  below),  then  the
68               array A contains the factors L and U from the factorization A =
69               P*L*U; the unit diagonal elements of L are not stored.
70
71       LDA     (input) INTEGER
72               The leading dimension of the array A.  LDA >= max(1,N).
73
74       IPIV    (output) INTEGER array, dimension (N)
75               The pivot indices that define the permutation matrix P;  row  i
76               of  the  matrix was interchanged with row IPIV(i).  Corresponds
77               either to the single precision factorization (if INFO.EQ.0  and
78               ITER.GE.0)  or the double precision factorization (if INFO.EQ.0
79               and ITER.LT.0).
80
81       B       (input) COMPLEX*16 array, dimension (LDB,NRHS)
82               The N-by-NRHS right hand side matrix B.
83
84       LDB     (input) INTEGER
85               The leading dimension of the array B.  LDB >= max(1,N).
86
87       X       (output) COMPLEX*16 array, dimension (LDX,NRHS)
88               If INFO = 0, the N-by-NRHS solution matrix X.
89
90       LDX     (input) INTEGER
91               The leading dimension of the array X.  LDX >= max(1,N).
92
93       WORK    (workspace) COMPLEX*16 array, dimension (N*NRHS)
94               This array is used to hold the residual vectors.
95
96       SWORK   (workspace) COMPLEX array, dimension (N*(N+NRHS))
97               This array is used to use the single precision matrix  and  the
98               right-hand sides or solutions in single precision.
99
100       RWORK   (workspace) DOUBLE PRECISION array, dimension (N)
101
102       ITER    (output) INTEGER
103               <  0: iterative refinement has failed, COMPLEX*16 factorization
104               has been performed -1 : the routine fell back to full precision
105               for  implementation- or machine-specific reasons -2 : narrowing
106               the precision induced an overflow, the  routine  fell  back  to
107               full precision -3 : failure of CGETRF
108               -31:  stop the iterative refinement after the 30th iterations >
109               0: iterative refinement has been sucessfully used.  Returns the
110               number of iterations
111
112       INFO    (output) INTEGER
113               = 0:  successful exit
114               < 0:  if INFO = -i, the i-th argument had an illegal value
115               >  0:   if  INFO  = i, U(i,i) computed in COMPLEX*16 is exactly
116               zero.  The factorization has been completed, but the  factor  U
117               is  exactly  singular,  so  the solution could not be computed.
118               =========
119
120
121
122 LAPACK PROTOTYPE driver routine (Nvoevresmiboenr 32.020)8                       ZCGESV(1)
Impressum