root / src / Mat_util.f90 @ 12
Historique | Voir | Annoter | Télécharger (8,37 ko)
1 | 12 | pfleura2 | !---------------------------------------------------------------------- |
---|---|---|---|
2 | 12 | pfleura2 | ! Copyright 2003-2014 Ecole Normale Supérieure de Lyon, |
3 | 12 | pfleura2 | ! Centre National de la Recherche Scientifique, |
4 | 12 | pfleura2 | ! Université Claude Bernard Lyon 1. All rights reserved. |
5 | 12 | pfleura2 | ! |
6 | 12 | pfleura2 | ! This work is registered with the Agency for the Protection of Programs |
7 | 12 | pfleura2 | ! as IDDN.FR.001.100009.000.S.P.2014.000.30625 |
8 | 12 | pfleura2 | ! |
9 | 12 | pfleura2 | ! Authors: P. Fleurat-Lessard, P. Dayal |
10 | 12 | pfleura2 | ! Contact: optnpath@gmail.com |
11 | 12 | pfleura2 | ! |
12 | 12 | pfleura2 | ! This file is part of "Opt'n Path". |
13 | 12 | pfleura2 | ! |
14 | 12 | pfleura2 | ! "Opt'n Path" is free software: you can redistribute it and/or modify |
15 | 12 | pfleura2 | ! it under the terms of the GNU Affero General Public License as |
16 | 12 | pfleura2 | ! published by the Free Software Foundation, either version 3 of the License, |
17 | 12 | pfleura2 | ! or (at your option) any later version. |
18 | 12 | pfleura2 | ! |
19 | 12 | pfleura2 | ! "Opt'n Path" is distributed in the hope that it will be useful, |
20 | 12 | pfleura2 | ! but WITHOUT ANY WARRANTY; without even the implied warranty of |
21 | 12 | pfleura2 | ! |
22 | 12 | pfleura2 | ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the |
23 | 12 | pfleura2 | ! GNU Affero General Public License for more details. |
24 | 12 | pfleura2 | ! |
25 | 12 | pfleura2 | ! You should have received a copy of the GNU Affero General Public License |
26 | 12 | pfleura2 | ! along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>. |
27 | 12 | pfleura2 | ! |
28 | 12 | pfleura2 | ! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr, |
29 | 12 | pfleura2 | ! for commercial licensing opportunities. |
30 | 12 | pfleura2 | !---------------------------------------------------------------------- |
31 | 12 | pfleura2 | |
32 | 1 | pfleura2 | !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! |
33 | 1 | pfleura2 | ! |
34 | 1 | pfleura2 | SUBROUTINE GenInv(N,A,InvA,NReal) |
35 | 1 | pfleura2 | !!!!!!!!!!!!!!!! |
36 | 1 | pfleura2 | ! |
37 | 1 | pfleura2 | ! This subroutines calculates the generalized inverse of a matrix |
38 | 1 | pfleura2 | ! It first diagonalize the matrix A, then inverse all non-zero |
39 | 1 | pfleura2 | ! eigenvalues, and forms the InvA matrix using these new eigenvalues |
40 | 1 | pfleura2 | ! |
41 | 1 | pfleura2 | ! Input: |
42 | 1 | pfleura2 | ! N : dimension of A |
43 | 1 | pfleura2 | ! NReal :Actual dimension of A |
44 | 1 | pfleura2 | ! A(N,N) : Initial Matrix, stored in A(Nreal,Nreal) |
45 | 1 | pfleura2 | ! |
46 | 1 | pfleura2 | ! Output: |
47 | 1 | pfleura2 | ! InvA(N,N) : Inversed Matrix, stored in a (Nreal,NReal) matrix |
48 | 1 | pfleura2 | ! |
49 | 1 | pfleura2 | !!!!!!!!!!!!!!!!!!!!!!! |
50 | 1 | pfleura2 | |
51 | 1 | pfleura2 | Use Vartypes |
52 | 1 | pfleura2 | IMPLICIT NONE |
53 | 1 | pfleura2 | |
54 | 1 | pfleura2 | INTEGER(KINT), INTENT(IN) :: N,Nreal |
55 | 1 | pfleura2 | REAL(KREAL), INTENT(IN) :: A(NReal,NReal) |
56 | 1 | pfleura2 | REAL(KREAL), INTENT(OUT) :: InvA(NReal,NReal) |
57 | 1 | pfleura2 | ! |
58 | 1 | pfleura2 | |
59 | 1 | pfleura2 | INTEGER(KINT) :: I,J,K |
60 | 1 | pfleura2 | REAL(KREAL), ALLOCATABLE :: EigVec(:,:) ! (Nreal,Nreal) |
61 | 1 | pfleura2 | REAL(KREAL), ALLOCATABLE :: EigVal(:) ! (Nreal) |
62 | 1 | pfleura2 | REAL(KREAL), ALLOCATABLE :: ATmp(:,:) ! (NReal,Nreal) |
63 | 1 | pfleura2 | REAL(KREAL) :: ss |
64 | 1 | pfleura2 | ! |
65 | 1 | pfleura2 | REAL(KREAL), PARAMETER :: eps=1e-12 |
66 | 1 | pfleura2 | |
67 | 1 | pfleura2 | ALLOCATE(EigVec(Nreal,Nreal), EigVal(Nreal),ATmp(NReal,NReal)) |
68 | 1 | pfleura2 | ! A will be destroyed in Jacobi so we save it |
69 | 1 | pfleura2 | ATmp=A |
70 | 1 | pfleura2 | CALL JAcobi(ATmp,N,EigVal,EigVec,NReal) |
71 | 1 | pfleura2 | |
72 | 1 | pfleura2 | DO I=1,N |
73 | 1 | pfleura2 | IF (abs(EigVal(I)).GT.eps) EigVal(I)=1.d0/EigVal(I) |
74 | 1 | pfleura2 | END DO |
75 | 1 | pfleura2 | |
76 | 1 | pfleura2 | InvA=0.d0 |
77 | 1 | pfleura2 | do k = 1, n |
78 | 1 | pfleura2 | do j = 1, n |
79 | 1 | pfleura2 | ss = eigval(k) * eigvec(j,k) |
80 | 1 | pfleura2 | do i = 1, j |
81 | 1 | pfleura2 | InvA(i,j) = InvA(i,j) + ss * eigvec(i,k) |
82 | 1 | pfleura2 | end do |
83 | 1 | pfleura2 | end do |
84 | 1 | pfleura2 | end do |
85 | 1 | pfleura2 | do j = 1, n |
86 | 1 | pfleura2 | do i = 1, j-1 |
87 | 1 | pfleura2 | InvA(j,i) = InvA(i,j) |
88 | 1 | pfleura2 | end do |
89 | 1 | pfleura2 | end do |
90 | 1 | pfleura2 | |
91 | 1 | pfleura2 | |
92 | 1 | pfleura2 | DEALLOCATE(EigVec, EigVal,ATmp) |
93 | 1 | pfleura2 | END SUBROUTINE GenInv |
94 | 1 | pfleura2 | |
95 | 1 | pfleura2 | !============================================================ |
96 | 1 | pfleura2 | ! |
97 | 1 | pfleura2 | ! ++ Matrix diagonalization Using jacobi |
98 | 1 | pfleura2 | ! Works only for symmetric matrices |
99 | 1 | pfleura2 | ! EigvenVectors : V(i,i) |
100 | 1 | pfleura2 | ! Eigenvalues : D(i) |
101 | 1 | pfleura2 | ! PFL 30/05/03 |
102 | 12 | pfleura2 | ! This version uses packed matrices. |
103 | 1 | pfleura2 | ! it unpacks them before calling Jacobi ! |
104 | 1 | pfleura2 | ! we have AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j; |
105 | 1 | pfleura2 | ! |
106 | 1 | pfleura2 | !============================================================ |
107 | 1 | pfleura2 | ! |
108 | 1 | pfleura2 | SUBROUTINE JacPacked(N,AP,D,V,nreal) |
109 | 1 | pfleura2 | |
110 | 1 | pfleura2 | Use Vartypes |
111 | 1 | pfleura2 | IMPLICIT NONE |
112 | 1 | pfleura2 | |
113 | 1 | pfleura2 | INTEGER(KINT), INTENT(IN) :: N,NREAL |
114 | 1 | pfleura2 | REAL(KREAL) :: AP(N*(N+1)/2) |
115 | 1 | pfleura2 | REAL(KREAL), ALLOCATABLE :: A(:,:) |
116 | 1 | pfleura2 | REAL(KREAL) :: V(Nreal,Nreal),D(Nreal) |
117 | 1 | pfleura2 | INTEGER(KINT) :: i,j,nn |
118 | 1 | pfleura2 | |
119 | 1 | pfleura2 | allocate(A(nreal,nreal)) |
120 | 1 | pfleura2 | nn=n*(n+1)/2 |
121 | 1 | pfleura2 | ! WRITE(*,*) 'Jacpa 0' |
122 | 1 | pfleura2 | ! WRITE(*,'(I3,10(1X,F15.6))') n,(AP(i),i=1,min(nn,5)) |
123 | 1 | pfleura2 | ! WRITE(*,*) 'Jacpa 0' |
124 | 1 | pfleura2 | do j=1,n |
125 | 1 | pfleura2 | do i=1,j |
126 | 1 | pfleura2 | ! WRITE(*,*) i,j |
127 | 1 | pfleura2 | A(i,J)=AP(i + (j-1)*j/2) |
128 | 1 | pfleura2 | A(j,I)=A(i,J) |
129 | 1 | pfleura2 | end do |
130 | 1 | pfleura2 | end do |
131 | 1 | pfleura2 | ! do j=1,n |
132 | 1 | pfleura2 | ! WRITE(*,'(10(1X,F15.6))') (A(i,J),i=1,min(n,5)) |
133 | 1 | pfleura2 | ! end do |
134 | 1 | pfleura2 | |
135 | 1 | pfleura2 | ! WRITE(*,*) 'Jacpa 1' |
136 | 1 | pfleura2 | call Jacobi(A,n,D,V,Nreal) |
137 | 1 | pfleura2 | ! WRITE(*,*) 'Jacpa 2' |
138 | 1 | pfleura2 | ! DO i=1,n |
139 | 1 | pfleura2 | ! WRITE(*,'(1X,I3,10(1X,F15.6))') i,D(i),(V(j,i),j=1,min(n,5)) |
140 | 1 | pfleura2 | ! end do |
141 | 1 | pfleura2 | deallocate(a) |
142 | 1 | pfleura2 | |
143 | 1 | pfleura2 | end SUBROUTINE JacPacked |
144 | 1 | pfleura2 | |
145 | 1 | pfleura2 | |
146 | 1 | pfleura2 | |
147 | 1 | pfleura2 | ! |
148 | 1 | pfleura2 | !============================================================ |
149 | 1 | pfleura2 | ! |
150 | 1 | pfleura2 | ! ++ Matrix diagonalization Using jacobi |
151 | 1 | pfleura2 | ! Works only for symmetric matrices |
152 | 1 | pfleura2 | ! EigvenVectors : V |
153 | 1 | pfleura2 | ! Eigenvalues : D |
154 | 1 | pfleura2 | ! |
155 | 1 | pfleura2 | !============================================================ |
156 | 1 | pfleura2 | ! |
157 | 1 | pfleura2 | SUBROUTINE JACOBI(A,N,D,V,Nreal) |
158 | 1 | pfleura2 | |
159 | 1 | pfleura2 | !!!!!!!!!!!!!!!! |
160 | 1 | pfleura2 | ! |
161 | 1 | pfleura2 | ! Input: |
162 | 1 | pfleura2 | ! N : Dimension of A |
163 | 1 | pfleura2 | ! NReal : Actual dimensions of A, D and V. |
164 | 1 | pfleura2 | ! |
165 | 1 | pfleura2 | ! Input/output: |
166 | 1 | pfleura2 | ! A(N,N) : Matrix to be diagonalized, store in a (Nreal,Nreal) matrix |
167 | 1 | pfleura2 | ! Destroyed in output. |
168 | 1 | pfleura2 | ! Output: |
169 | 1 | pfleura2 | ! V(N,N) : Eigenvectors, stored in V(NReal, NReal) |
170 | 1 | pfleura2 | ! D(N) : Eigenvalues, stored in D(NReal) |
171 | 1 | pfleura2 | ! |
172 | 1 | pfleura2 | |
173 | 1 | pfleura2 | Use Vartypes |
174 | 1 | pfleura2 | |
175 | 1 | pfleura2 | IMPLICIT NONE |
176 | 1 | pfleura2 | INTEGER(KINT), parameter :: max_it=500 |
177 | 1 | pfleura2 | REAL(KREAL), ALLOCATABLE :: B(:),Z(:) |
178 | 1 | pfleura2 | |
179 | 1 | pfleura2 | INTEGER(KINT) :: N,NReal |
180 | 1 | pfleura2 | REAL(KREAL) :: A(NReal,NReal) |
181 | 1 | pfleura2 | REAL(KREAL) :: V(Nreal,Nreal),D(Nreal) |
182 | 1 | pfleura2 | |
183 | 1 | pfleura2 | INTEGER(KINT) :: I, J,IP, IQ, NROT |
184 | 1 | pfleura2 | REAL(KREAL) :: SM, H, Tresh, G, T, Theta, C, S, Tau |
185 | 1 | pfleura2 | |
186 | 1 | pfleura2 | allocate(B(N),Z(N)) |
187 | 1 | pfleura2 | |
188 | 1 | pfleura2 | DO IP=1,N |
189 | 1 | pfleura2 | DO IQ=1,N |
190 | 1 | pfleura2 | V(IP,IQ)=0. |
191 | 1 | pfleura2 | END DO |
192 | 1 | pfleura2 | V(IP,IP)=1. |
193 | 1 | pfleura2 | END DO |
194 | 1 | pfleura2 | DO IP=1,N |
195 | 1 | pfleura2 | B(IP)=A(IP,IP) |
196 | 1 | pfleura2 | D(IP)=B(IP) |
197 | 1 | pfleura2 | Z(IP)=0. |
198 | 1 | pfleura2 | END DO |
199 | 1 | pfleura2 | NROT=0 |
200 | 1 | pfleura2 | DO I=1,max_it |
201 | 1 | pfleura2 | SM=0. |
202 | 1 | pfleura2 | DO IP=1,N-1 |
203 | 1 | pfleura2 | DO IQ=IP+1,N |
204 | 1 | pfleura2 | SM=SM+ABS(A(IP,IQ)) |
205 | 1 | pfleura2 | END DO |
206 | 1 | pfleura2 | END DO |
207 | 1 | pfleura2 | IF(SM.EQ.0.) GOTO 100 |
208 | 1 | pfleura2 | IF(I.LT.4)THEN |
209 | 1 | pfleura2 | TRESH=0.2*SM/N**2 |
210 | 1 | pfleura2 | ELSE |
211 | 1 | pfleura2 | TRESH=0. |
212 | 1 | pfleura2 | ENDIF |
213 | 1 | pfleura2 | DO IP=1,N-1 |
214 | 1 | pfleura2 | DO IQ=IP+1,N |
215 | 1 | pfleura2 | G=100.*ABS(A(IP,IQ)) |
216 | 1 | pfleura2 | IF((I.GT.4).AND.(ABS(D(IP))+G.EQ.ABS(D(IP))) & |
217 | 1 | pfleura2 | .AND.(ABS(D(IQ))+G.EQ.ABS(D(IQ))))THEN |
218 | 1 | pfleura2 | A(IP,IQ)=0. |
219 | 1 | pfleura2 | ELSE IF(ABS(A(IP,IQ)).GT.TRESH)THEN |
220 | 1 | pfleura2 | H=D(IQ)-D(IP) |
221 | 1 | pfleura2 | IF(ABS(H)+G.EQ.ABS(H))THEN |
222 | 1 | pfleura2 | T=A(IP,IQ)/H |
223 | 1 | pfleura2 | ELSE |
224 | 1 | pfleura2 | THETA=0.5*H/A(IP,IQ) |
225 | 1 | pfleura2 | T=1./(ABS(THETA)+SQRT(1.+THETA**2)) |
226 | 1 | pfleura2 | IF(THETA.LT.0.)T=-T |
227 | 1 | pfleura2 | ENDIF |
228 | 1 | pfleura2 | C=1./SQRT(1+T**2) |
229 | 1 | pfleura2 | S=T*C |
230 | 1 | pfleura2 | TAU=S/(1.+C) |
231 | 1 | pfleura2 | H=T*A(IP,IQ) |
232 | 1 | pfleura2 | Z(IP)=Z(IP)-H |
233 | 1 | pfleura2 | Z(IQ)=Z(IQ)+H |
234 | 1 | pfleura2 | D(IP)=D(IP)-H |
235 | 1 | pfleura2 | D(IQ)=D(IQ)+H |
236 | 1 | pfleura2 | A(IP,IQ)=0. |
237 | 1 | pfleura2 | DO J=1,IP-1 |
238 | 1 | pfleura2 | G=A(J,IP) |
239 | 1 | pfleura2 | H=A(J,IQ) |
240 | 1 | pfleura2 | A(J,IP)=G-S*(H+G*TAU) |
241 | 1 | pfleura2 | A(J,IQ)=H+S*(G-H*TAU) |
242 | 1 | pfleura2 | END DO |
243 | 1 | pfleura2 | DO J=IP+1,IQ-1 |
244 | 1 | pfleura2 | G=A(IP,J) |
245 | 1 | pfleura2 | H=A(J,IQ) |
246 | 1 | pfleura2 | A(IP,J)=G-S*(H+G*TAU) |
247 | 1 | pfleura2 | A(J,IQ)=H+S*(G-H*TAU) |
248 | 1 | pfleura2 | END DO |
249 | 1 | pfleura2 | DO J=IQ+1,N |
250 | 1 | pfleura2 | G=A(IP,J) |
251 | 1 | pfleura2 | H=A(IQ,J) |
252 | 1 | pfleura2 | A(IP,J)=G-S*(H+G*TAU) |
253 | 1 | pfleura2 | A(IQ,J)=H+S*(G-H*TAU) |
254 | 1 | pfleura2 | END DO |
255 | 1 | pfleura2 | DO J=1,N |
256 | 1 | pfleura2 | G=V(J,IP) |
257 | 1 | pfleura2 | H=V(J,IQ) |
258 | 1 | pfleura2 | V(J,IP)=G-S*(H+G*TAU) |
259 | 1 | pfleura2 | V(J,IQ)=H+S*(G-H*TAU) |
260 | 1 | pfleura2 | END DO |
261 | 1 | pfleura2 | NROT=NROT+1 |
262 | 1 | pfleura2 | ENDIF |
263 | 1 | pfleura2 | END DO |
264 | 1 | pfleura2 | END DO |
265 | 1 | pfleura2 | DO IP=1,N |
266 | 1 | pfleura2 | B(IP)=B(IP)+Z(IP) |
267 | 1 | pfleura2 | D(IP)=B(IP) |
268 | 1 | pfleura2 | Z(IP)=0. |
269 | 1 | pfleura2 | END DO |
270 | 1 | pfleura2 | END DO |
271 | 1 | pfleura2 | write(6,*) max_it,' iterations should never happen' |
272 | 1 | pfleura2 | STOP |
273 | 1 | pfleura2 | 100 DEALLOCATE(B,Z) |
274 | 1 | pfleura2 | RETURN |
275 | 1 | pfleura2 | END SUBROUTINE JACOBI |
276 | 1 | pfleura2 | ! |
277 | 1 | pfleura2 | !============================================================ |
278 | 1 | pfleura2 | !c |
279 | 1 | pfleura2 | !c ++ Sort Eigenvectors in ascending eigenvalues order |
280 | 1 | pfleura2 | !c |
281 | 1 | pfleura2 | !c============================================================ |
282 | 1 | pfleura2 | !c |
283 | 1 | pfleura2 | SUBROUTINE trie(nb_niv,ene,psi,nreal) |
284 | 1 | pfleura2 | |
285 | 1 | pfleura2 | ! |
286 | 1 | pfleura2 | ! Input: |
287 | 1 | pfleura2 | ! Nb_niv : Dimension of Psi |
288 | 1 | pfleura2 | ! NReal : Actual dimensions of Psi, Ene |
289 | 1 | pfleura2 | ! Input/output: |
290 | 1 | pfleura2 | ! Psi(N,N) : Eigvenvectors, changed in output. Stored in a (Nreal,Nreal) matrix |
291 | 1 | pfleura2 | ! Ene(N) : Eigenvalues, changed in output. Stored in Ene(NReal) |
292 | 1 | pfleura2 | ! |
293 | 1 | pfleura2 | !!!!!!!!!!!!!!!! |
294 | 1 | pfleura2 | |
295 | 1 | pfleura2 | Use VarTypes |
296 | 1 | pfleura2 | IMPLICIT NONE |
297 | 1 | pfleura2 | |
298 | 2 | pfleura2 | integer(KINT) :: i, j, k, nb_niv, nreal |
299 | 1 | pfleura2 | real(KREAL) :: ene(nreal),psi(nreal,nreal) |
300 | 1 | pfleura2 | real(KREAL) :: a |
301 | 1 | pfleura2 | |
302 | 1 | pfleura2 | |
303 | 1 | pfleura2 | !!!!!!!!!!!!!!!! |
304 | 1 | pfleura2 | |
305 | 1 | pfleura2 | |
306 | 1 | pfleura2 | DO i=1,nb_niv |
307 | 1 | pfleura2 | DO j=i+1,nb_niv |
308 | 1 | pfleura2 | IF (ene(i) .GT. ene(j)) THEN |
309 | 1 | pfleura2 | ! permutation |
310 | 1 | pfleura2 | a=ene(i) |
311 | 1 | pfleura2 | ene(i)=ene(j) |
312 | 1 | pfleura2 | ene(j)=a |
313 | 1 | pfleura2 | |
314 | 1 | pfleura2 | DO k=1,nb_niv |
315 | 1 | pfleura2 | a=psi(k,i) |
316 | 1 | pfleura2 | psi(k,i)=psi(k,j) |
317 | 1 | pfleura2 | psi(k,j)=a |
318 | 1 | pfleura2 | END DO |
319 | 1 | pfleura2 | END IF |
320 | 1 | pfleura2 | END DO |
321 | 1 | pfleura2 | END DO |
322 | 1 | pfleura2 | |
323 | 1 | pfleura2 | END SUBROUTINE trie |