1 SUBROUTINE DGESV
( N
, NRHS
, A
, LDA
, IPIV
, B
, LDB
, INFO
)
3 * -- LAPACK driver routine
(version
3.1) --
4 * Univ
. of Tennessee
, Univ
. of California Berkeley and NAG Ltd
..
7 * .. Scalar Arguments
..
8 INTEGER INFO
, LDA
, LDB
, N
, NRHS
10 * .. Array Arguments
..
12 DOUBLE PRECISION A
( LDA
, * ), B
( LDB
, * )
18 * DGESV computes the solution
to a
real system of linear equations
20 * where A is an N
-by
-N matrix and X and B are N
-by
-NRHS matrices
.
22 * The LU decomposition with partial pivoting and row interchanges is
25 * where P is a permutation matrix
, L is unit lower triangular
, and U is
26 * upper triangular
. The factored form of A is
then used
to solve the
27 * system of equations A
* X
= B
.
33 * The number of linear equations
, i
.e
., the order of the
36 * NRHS
(input
) INTEGER
37 * The number of right hand sides
, i
.e
., the number of columns
38 * of the matrix B
. NRHS
>= 0.
40 * A
(input
/output
) DOUBLE PRECISION array
, dimension (LDA
,N
)
41 * On entry
, the N
-by
-N coefficient matrix A
.
42 * On exit
, the factors L and U from the factorization
43 * A
= P*L*U
; the unit diagonal elements of L are not stored
.
46 * The leading
dimension of the array A
. LDA
>= max
(1,N
).
48 * IPIV
(output
) INTEGER array
, dimension (N
)
49 * The pivot indices that define the permutation matrix P
;
50 * row i of the matrix was interchanged with row IPIV
(i
).
52 * B
(input
/output
) DOUBLE PRECISION array
, dimension (LDB
,NRHS
)
53 * On entry
, the N
-by
-NRHS matrix of right hand side matrix B
.
54 * On exit
, if INFO
= 0, the N
-by
-NRHS solution matrix X
.
57 * The leading
dimension of the array B
. LDB
>= max
(1,N
).
59 * INFO
(output
) INTEGER
60 * = 0: successful exit
61 * < 0: if INFO
= -i
, the i
-th argument had an illegal value
62 * > 0: if INFO
= i
, U
(i
,i
) is exactly zero
. The factorization
63 * has been completed
, but the factor U is exactly
64 * singular
, so the solution could not be computed
.
66 * =====================================================================
68 * .. External Subroutines
..
69 EXTERNAL DGETRF
, DGETRS
, XERBLA
71 * .. Intrinsic Functions
..
74 * .. Executable Statements
..
76 * Test the input parameters
.
81 ELSE IF( NRHS
.LT
.0 ) THEN
83 ELSE IF( LDA
.LT
.MAX
( 1, N
) ) THEN
85 ELSE IF( LDB
.LT
.MAX
( 1, N
) ) THEN
89 CALL XERBLA
( 'DGESV ', -INFO
)
93 * Compute the LU factorization of A
.
95 CALL DGETRF
( N
, N
, A
, LDA
, IPIV
, INFO
)
98 * Solve the system A*X
= B
, overwriting B with X
.
100 CALL DGETRS
( 'No transpose', N
, NRHS
, A
, LDA
, IPIV
, B
, LDB
,