root / src / gaussj.f90 @ 12
Historique | Voir | Annoter | Télécharger (3,89 ko)
1 | 1 | pfleura2 | SUBROUTINE gaussj(a,n,np,b,m,mp) |
---|---|---|---|
2 | 1 | pfleura2 | |
3 | 12 | pfleura2 | ! This routine solves the system AX=B by inverting A. |
4 | 12 | pfleura2 | ! This is based on Gauss-Jordan pivoting. |
5 | 12 | pfleura2 | ! Input: |
6 | 12 | pfleura2 | ! A is NxN REAL(KREAL) matrix, order N |
7 | 12 | pfleura2 | ! B is NxM REAL(KREAL) matrix (each ocolumn j of this B matrix corresponds to |
8 | 12 | pfleura2 | ! a AX=B_j problem in fact). |
9 | 12 | pfleura2 | ! np: actual size of A(np,np) |
10 | 12 | pfleura2 | ! mp: actual size of B(np,mp) |
11 | 12 | pfleura2 | ! |
12 | 12 | pfleura2 | ! Output: |
13 | 12 | pfleura2 | ! A is destroyed and contains A inverse |
14 | 12 | pfleura2 | ! B is destroyed and contains the solution X vectors. |
15 | 12 | pfleura2 | ! |
16 | 12 | pfleura2 | ! Adapted from "Numerical Recipes in F77" |
17 | 12 | pfleura2 | |
18 | 12 | pfleura2 | !---------------------------------------------------------------------- |
19 | 12 | pfleura2 | ! Copyright 2003-2014 Ecole Normale Supérieure de Lyon, |
20 | 12 | pfleura2 | ! Centre National de la Recherche Scientifique, |
21 | 12 | pfleura2 | ! Université Claude Bernard Lyon 1. All rights reserved. |
22 | 12 | pfleura2 | ! |
23 | 12 | pfleura2 | ! This work is registered with the Agency for the Protection of Programs |
24 | 12 | pfleura2 | ! as IDDN.FR.001.100009.000.S.P.2014.000.30625 |
25 | 12 | pfleura2 | ! |
26 | 12 | pfleura2 | ! Authors: P. Fleurat-Lessard, P. Dayal |
27 | 12 | pfleura2 | ! Contact: optnpath@gmail.com |
28 | 12 | pfleura2 | ! |
29 | 12 | pfleura2 | ! This file is part of "Opt'n Path". |
30 | 12 | pfleura2 | ! |
31 | 12 | pfleura2 | ! "Opt'n Path" is free software: you can redistribute it and/or modify |
32 | 12 | pfleura2 | ! it under the terms of the GNU Affero General Public License as |
33 | 12 | pfleura2 | ! published by the Free Software Foundation, either version 3 of the License, |
34 | 12 | pfleura2 | ! or (at your option) any later version. |
35 | 12 | pfleura2 | ! |
36 | 12 | pfleura2 | ! "Opt'n Path" is distributed in the hope that it will be useful, |
37 | 12 | pfleura2 | ! but WITHOUT ANY WARRANTY; without even the implied warranty of |
38 | 12 | pfleura2 | ! |
39 | 12 | pfleura2 | ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the |
40 | 12 | pfleura2 | ! GNU Affero General Public License for more details. |
41 | 12 | pfleura2 | ! |
42 | 12 | pfleura2 | ! You should have received a copy of the GNU Affero General Public License |
43 | 12 | pfleura2 | ! along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>. |
44 | 12 | pfleura2 | ! |
45 | 12 | pfleura2 | ! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr, |
46 | 12 | pfleura2 | ! for commercial licensing opportunities. |
47 | 12 | pfleura2 | !---------------------------------------------------------------------- |
48 | 12 | pfleura2 | |
49 | 12 | pfleura2 | |
50 | 1 | pfleura2 | IMPLICIT NONE |
51 | 1 | pfleura2 | |
52 | 1 | pfleura2 | INTEGER, PARAMETER :: KINT=KIND(1) |
53 | 1 | pfleura2 | INTEGER, PARAMETER :: KREAL=KIND(1.0D0) |
54 | 1 | pfleura2 | |
55 | 1 | pfleura2 | |
56 | 1 | pfleura2 | INTEGER(KINT) :: m,mp,n,np,NMAX |
57 | 1 | pfleura2 | REAL(KREAL) :: a(np,np),b(np,mp) |
58 | 1 | pfleura2 | PARAMETER (NMAX=50) |
59 | 1 | pfleura2 | INTEGER(KINT) :: i,icol,irow,j,k,l,ll,indxc(NMAX),indxr(NMAX),ipiv(NMAX) |
60 | 1 | pfleura2 | REAL(KREAL) :: big,dum,pivinv |
61 | 1 | pfleura2 | do 11 j=1,n |
62 | 1 | pfleura2 | ipiv(j)=0 |
63 | 1 | pfleura2 | 11 continue |
64 | 1 | pfleura2 | do 22 i=1,n |
65 | 1 | pfleura2 | big=0.d0 |
66 | 1 | pfleura2 | do 13 j=1,n |
67 | 1 | pfleura2 | if(ipiv(j).ne.1)then |
68 | 1 | pfleura2 | do 12 k=1,n |
69 | 1 | pfleura2 | if (ipiv(k).eq.0) then |
70 | 1 | pfleura2 | if (abs(a(j,k)).ge.big)then |
71 | 1 | pfleura2 | big=abs(a(j,k)) |
72 | 1 | pfleura2 | irow=j |
73 | 1 | pfleura2 | icol=k |
74 | 1 | pfleura2 | endif |
75 | 1 | pfleura2 | else if (ipiv(k).gt.1) then |
76 | 2 | pfleura2 | Write(*,*) 'singular matrix in gaussj' |
77 | 2 | pfleura2 | STOP |
78 | 1 | pfleura2 | endif |
79 | 1 | pfleura2 | 12 continue |
80 | 1 | pfleura2 | endif |
81 | 1 | pfleura2 | 13 continue |
82 | 1 | pfleura2 | ipiv(icol)=ipiv(icol)+1 |
83 | 1 | pfleura2 | if (irow.ne.icol) then |
84 | 1 | pfleura2 | do 14 l=1,n |
85 | 1 | pfleura2 | dum=a(irow,l) |
86 | 1 | pfleura2 | a(irow,l)=a(icol,l) |
87 | 1 | pfleura2 | a(icol,l)=dum |
88 | 1 | pfleura2 | 14 continue |
89 | 1 | pfleura2 | do 15 l=1,m |
90 | 1 | pfleura2 | dum=b(irow,l) |
91 | 1 | pfleura2 | b(irow,l)=b(icol,l) |
92 | 1 | pfleura2 | b(icol,l)=dum |
93 | 1 | pfleura2 | 15 continue |
94 | 1 | pfleura2 | endif |
95 | 1 | pfleura2 | indxr(i)=irow |
96 | 1 | pfleura2 | indxc(i)=icol |
97 | 2 | pfleura2 | if (a(icol,icol).eq.0.d0) THEN |
98 | 2 | pfleura2 | WRITE(*,*) 'singular matrix in gaussj' |
99 | 2 | pfleura2 | STOP |
100 | 2 | pfleura2 | END IF |
101 | 1 | pfleura2 | pivinv=1.d0/a(icol,icol) |
102 | 1 | pfleura2 | a(icol,icol)=1.d0 |
103 | 1 | pfleura2 | do 16 l=1,n |
104 | 1 | pfleura2 | a(icol,l)=a(icol,l)*pivinv |
105 | 1 | pfleura2 | 16 continue |
106 | 1 | pfleura2 | do 17 l=1,m |
107 | 1 | pfleura2 | b(icol,l)=b(icol,l)*pivinv |
108 | 1 | pfleura2 | 17 continue |
109 | 1 | pfleura2 | do 21 ll=1,n |
110 | 1 | pfleura2 | if(ll.ne.icol)then |
111 | 1 | pfleura2 | dum=a(ll,icol) |
112 | 1 | pfleura2 | a(ll,icol)=0.d0 |
113 | 1 | pfleura2 | do 18 l=1,n |
114 | 1 | pfleura2 | a(ll,l)=a(ll,l)-a(icol,l)*dum |
115 | 1 | pfleura2 | 18 continue |
116 | 1 | pfleura2 | do 19 l=1,m |
117 | 1 | pfleura2 | b(ll,l)=b(ll,l)-b(icol,l)*dum |
118 | 1 | pfleura2 | 19 continue |
119 | 1 | pfleura2 | endif |
120 | 1 | pfleura2 | 21 continue |
121 | 1 | pfleura2 | 22 continue |
122 | 1 | pfleura2 | do 24 l=n,1,-1 |
123 | 1 | pfleura2 | if(indxr(l).ne.indxc(l))then |
124 | 1 | pfleura2 | do 23 k=1,n |
125 | 1 | pfleura2 | dum=a(k,indxr(l)) |
126 | 1 | pfleura2 | a(k,indxr(l))=a(k,indxc(l)) |
127 | 1 | pfleura2 | a(k,indxc(l))=dum |
128 | 1 | pfleura2 | 23 continue |
129 | 1 | pfleura2 | endif |
130 | 1 | pfleura2 | 24 continue |
131 | 1 | pfleura2 | return |
132 | 1 | pfleura2 | END |