summaryrefslogtreecommitdiff
path: root/2.3-1/src/fortran/lapack/dgesv.f
diff options
context:
space:
mode:
authoryash11122017-07-07 21:20:49 +0530
committeryash11122017-07-07 21:20:49 +0530
commit9e5793a7b05b23e6044a6d7a9ddd5db39ba375f0 (patch)
treef50d6e06d8fe6bc1a9053ef10d4b4d857800ab51 /2.3-1/src/fortran/lapack/dgesv.f
downloadScilab2C-9e5793a7b05b23e6044a6d7a9ddd5db39ba375f0.tar.gz
Scilab2C-9e5793a7b05b23e6044a6d7a9ddd5db39ba375f0.tar.bz2
Scilab2C-9e5793a7b05b23e6044a6d7a9ddd5db39ba375f0.zip
sci2c arduino updated
Diffstat (limited to '2.3-1/src/fortran/lapack/dgesv.f')
-rw-r--r--2.3-1/src/fortran/lapack/dgesv.f107
1 files changed, 107 insertions, 0 deletions
diff --git a/2.3-1/src/fortran/lapack/dgesv.f b/2.3-1/src/fortran/lapack/dgesv.f
new file mode 100644
index 00000000..220ef56f
--- /dev/null
+++ b/2.3-1/src/fortran/lapack/dgesv.f
@@ -0,0 +1,107 @@
+ SUBROUTINE DGESV( N, NRHS, A, LDA, IPIV, B, LDB, INFO )
+*
+* -- LAPACK driver routine (version 3.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2006
+*
+* .. Scalar Arguments ..
+ INTEGER INFO, LDA, LDB, N, NRHS
+* ..
+* .. Array Arguments ..
+ INTEGER IPIV( * )
+ DOUBLE PRECISION A( LDA, * ), B( LDB, * )
+* ..
+*
+* Purpose
+* =======
+*
+* DGESV computes the solution to a real system of linear equations
+* A * X = B,
+* where A is an N-by-N matrix and X and B are N-by-NRHS matrices.
+*
+* The LU decomposition with partial pivoting and row interchanges is
+* used to factor A as
+* A = P * L * U,
+* where P is a permutation matrix, L is unit lower triangular, and U is
+* upper triangular. The factored form of A is then used to solve the
+* system of equations A * X = B.
+*
+* 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/output) DOUBLE PRECISION array, dimension (LDA,N)
+* On entry, the N-by-N coefficient matrix A.
+* On exit, 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).
+*
+* B (input/output) DOUBLE PRECISION array, dimension (LDB,NRHS)
+* On entry, the N-by-NRHS matrix of right hand side matrix B.
+* On exit, if INFO = 0, the N-by-NRHS solution matrix X.
+*
+* LDB (input) INTEGER
+* The leading dimension of the array B. LDB >= max(1,N).
+*
+* 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) is exactly zero. The factorization
+* has been completed, but the factor U is exactly
+* singular, so the solution could not be computed.
+*
+* =====================================================================
+*
+* .. External Subroutines ..
+ EXTERNAL DGETRF, DGETRS, XERBLA
+* ..
+* .. Intrinsic Functions ..
+ INTRINSIC MAX
+* ..
+* .. Executable Statements ..
+*
+* Test the input parameters.
+*
+ INFO = 0
+ IF( N.LT.0 ) THEN
+ INFO = -1
+ ELSE IF( NRHS.LT.0 ) THEN
+ INFO = -2
+ ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
+ INFO = -4
+ ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
+ INFO = -7
+ END IF
+ IF( INFO.NE.0 ) THEN
+ CALL XERBLA( 'DGESV ', -INFO )
+ RETURN
+ END IF
+*
+* Compute the LU factorization of A.
+*
+ CALL DGETRF( N, N, A, LDA, IPIV, INFO )
+ IF( INFO.EQ.0 ) THEN
+*
+* Solve the system A*X = B, overwriting B with X.
+*
+ CALL DGETRS( 'No transpose', N, NRHS, A, LDA, IPIV, B, LDB,
+ $ INFO )
+ END IF
+ RETURN
+*
+* End of DGESV
+*
+ END