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

NAME

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

SYNOPSIS

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

PURPOSE

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

ARGUMENTS

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