root / src / egrad_test_2D.f90 @ 12
Historique | Voir | Annoter | Télécharger (5,43 ko)
1 | 5 | pfleura2 | SUBROUTINE egrad_test_2D(nat,e,geom,grad) |
---|---|---|---|
2 | 5 | pfleura2 | ! This program computes the energy and the gradient |
3 | 5 | pfleura2 | ! to cheat PATH we use a 3 atoms system |
4 | 5 | pfleura2 | |
5 | 12 | pfleura2 | !---------------------------------------------------------------------- |
6 | 12 | pfleura2 | ! Copyright 2003-2014 Ecole Normale Supérieure de Lyon, |
7 | 12 | pfleura2 | ! Centre National de la Recherche Scientifique, |
8 | 12 | pfleura2 | ! Université Claude Bernard Lyon 1. All rights reserved. |
9 | 12 | pfleura2 | ! |
10 | 12 | pfleura2 | ! This work is registered with the Agency for the Protection of Programs |
11 | 12 | pfleura2 | ! as IDDN.FR.001.100009.000.S.P.2014.000.30625 |
12 | 12 | pfleura2 | ! |
13 | 12 | pfleura2 | ! Authors: P. Fleurat-Lessard, P. Dayal |
14 | 12 | pfleura2 | ! Contact: optnpath@gmail.com |
15 | 12 | pfleura2 | ! |
16 | 12 | pfleura2 | ! This file is part of "Opt'n Path". |
17 | 12 | pfleura2 | ! |
18 | 12 | pfleura2 | ! "Opt'n Path" is free software: you can redistribute it and/or modify |
19 | 12 | pfleura2 | ! it under the terms of the GNU Affero General Public License as |
20 | 12 | pfleura2 | ! published by the Free Software Foundation, either version 3 of the License, |
21 | 12 | pfleura2 | ! or (at your option) any later version. |
22 | 12 | pfleura2 | ! |
23 | 12 | pfleura2 | ! "Opt'n Path" is distributed in the hope that it will be useful, |
24 | 12 | pfleura2 | ! but WITHOUT ANY WARRANTY; without even the implied warranty of |
25 | 12 | pfleura2 | ! |
26 | 12 | pfleura2 | ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the |
27 | 12 | pfleura2 | ! GNU Affero General Public License for more details. |
28 | 12 | pfleura2 | ! |
29 | 12 | pfleura2 | ! You should have received a copy of the GNU Affero General Public License |
30 | 12 | pfleura2 | ! along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>. |
31 | 12 | pfleura2 | ! |
32 | 12 | pfleura2 | ! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr, |
33 | 12 | pfleura2 | ! for commercial licensing opportunities. |
34 | 12 | pfleura2 | !---------------------------------------------------------------------- |
35 | 12 | pfleura2 | |
36 | 5 | pfleura2 | IMPLICIT NONE |
37 | 5 | pfleura2 | integer, parameter :: KINT = kind(1) |
38 | 5 | pfleura2 | integer, parameter :: KREAL = kind(1.0d0) |
39 | 5 | pfleura2 | |
40 | 5 | pfleura2 | INTEGER(KINT), INTENT(IN) :: Nat |
41 | 5 | pfleura2 | REAL(KREAL), INTENT(OUT) :: E,grad(Nat*3) |
42 | 5 | pfleura2 | REAL(KREAL), INTENT(IN) :: Geom(Nat,3) |
43 | 5 | pfleura2 | |
44 | 5 | pfleura2 | ! Bohr --> Angstr |
45 | 5 | pfleura2 | ! real(KREAL), parameter :: BOHR = 0.52917726D+00 |
46 | 5 | pfleura2 | ! |
47 | 5 | pfleura2 | |
48 | 5 | pfleura2 | ! Parameters to define the surface |
49 | 5 | pfleura2 | INTEGER(KINT), DIMENSION(6), PARAMETER :: IECOEF = (/-1,9,-45,45,-9,1/) |
50 | 5 | pfleura2 | INTEGER(KINT), DIMENSION(6), PARAMETER :: ISCOEF = (/-3,-2,-1,1,2,3/) |
51 | 5 | pfleura2 | REAL(KREAL), PARAMETER :: hh=0.01d0 |
52 | 5 | pfleura2 | INTEGER(KINT), PARAMETER :: IOTMP=99 |
53 | 5 | pfleura2 | ! Variables |
54 | 5 | pfleura2 | INTEGER(KINT) :: i, iat, jat,j |
55 | 5 | pfleura2 | REAL(KREAL), ALLOCATABLE :: Xyztmp(:,:),GradTmp(:,:) |
56 | 5 | pfleura2 | |
57 | 5 | pfleura2 | LOGICAL :: Debug |
58 | 5 | pfleura2 | LOGICAL, save :: First |
59 | 5 | pfleura2 | |
60 | 5 | pfleura2 | REAL(KREAL) :: x,y |
61 | 5 | pfleura2 | |
62 | 5 | pfleura2 | |
63 | 5 | pfleura2 | |
64 | 5 | pfleura2 | INTERFACE |
65 | 5 | pfleura2 | function valid(string) result (isValid) |
66 | 5 | pfleura2 | CHARACTER(*), intent(in) :: string |
67 | 5 | pfleura2 | logical :: isValid |
68 | 5 | pfleura2 | END function VALID |
69 | 5 | pfleura2 | |
70 | 5 | pfleura2 | |
71 | 5 | pfleura2 | function E2D(natoms,Xyz) |
72 | 5 | pfleura2 | |
73 | 5 | pfleura2 | use Path_module, only : order |
74 | 5 | pfleura2 | use Io_module, only : IOTMP |
75 | 5 | pfleura2 | |
76 | 5 | pfleura2 | IMPLICIT NONE |
77 | 5 | pfleura2 | integer, parameter :: KINT = kind(1) |
78 | 5 | pfleura2 | integer, parameter :: KREAL = kind(1.0d0) |
79 | 5 | pfleura2 | |
80 | 5 | pfleura2 | |
81 | 5 | pfleura2 | INTEGER(KINT) ,INTENT(IN) :: natoms |
82 | 5 | pfleura2 | REAL(KREAL) ,INTENT(IN) :: Xyz(natoms,3) |
83 | 5 | pfleura2 | REAL(KREAL) :: E2D |
84 | 5 | pfleura2 | END function E2D |
85 | 5 | pfleura2 | |
86 | 5 | pfleura2 | |
87 | 5 | pfleura2 | END INTERFACE |
88 | 5 | pfleura2 | |
89 | 5 | pfleura2 | debug=valid('egrad_test_2D') |
90 | 5 | pfleura2 | |
91 | 5 | pfleura2 | if (debug) WRITE(*,*) '================ Entering Egrad_test ===================' |
92 | 5 | pfleura2 | if (debug) THEN |
93 | 5 | pfleura2 | WRITE(*,*) "Cartesian Geometry" |
94 | 5 | pfleura2 | DO I=1,Nat |
95 | 5 | pfleura2 | WRITE(*,'(1X,I5,3(1X,F12.6))') I,Geom(i,1:3) |
96 | 5 | pfleura2 | END DO |
97 | 5 | pfleura2 | END IF |
98 | 5 | pfleura2 | |
99 | 5 | pfleura2 | ALLOCATE(XyZTmp(Nat,3),GradTmp(Nat,3)) |
100 | 5 | pfleura2 | |
101 | 5 | pfleura2 | if (first) THEN |
102 | 5 | pfleura2 | OPEN(IOTMP,File="tt") |
103 | 5 | pfleura2 | DO I=1, 501 |
104 | 5 | pfleura2 | DO j=1,501 |
105 | 5 | pfleura2 | x=(i-1.)/100. |
106 | 5 | pfleura2 | y=(j-1.)/100. |
107 | 5 | pfleura2 | xyztmp(2,1)=x |
108 | 5 | pfleura2 | xyztmp(3,1)=y |
109 | 5 | pfleura2 | write(IOTMP,*) x,y,E2D(nat,xyztmp) |
110 | 5 | pfleura2 | END DO |
111 | 5 | pfleura2 | ! we skip a blank line |
112 | 5 | pfleura2 | WRITe(IOTMP,*) |
113 | 5 | pfleura2 | END DO |
114 | 5 | pfleura2 | CLOSE(IOTMP) |
115 | 5 | pfleura2 | First=.FALSE. |
116 | 5 | pfleura2 | END IF |
117 | 5 | pfleura2 | |
118 | 5 | pfleura2 | e=E2D(nat,Geom) |
119 | 5 | pfleura2 | |
120 | 5 | pfleura2 | ! We now calculate the gradients using numerical derivatives |
121 | 5 | pfleura2 | Grad=0.d0 |
122 | 5 | pfleura2 | GradTmp=0.d0 |
123 | 5 | pfleura2 | do iat=1,1 |
124 | 5 | pfleura2 | do jat=2,nat |
125 | 5 | pfleura2 | xyztmp=geom |
126 | 5 | pfleura2 | do i=1,6 |
127 | 5 | pfleura2 | xyztmp(jat,iat)=geom(jat,iat)+ISCoef(i)*hh |
128 | 5 | pfleura2 | gradTmp(jat,iat)=gradTmp(jat,iat)+IECoef(i)*E2D(nat,xyztmp) |
129 | 5 | pfleura2 | end do |
130 | 5 | pfleura2 | end do |
131 | 5 | pfleura2 | end do |
132 | 5 | pfleura2 | gradTmp=gradTmp/(60.*hh) |
133 | 5 | pfleura2 | do iat=1,nat |
134 | 5 | pfleura2 | grad(3*iat-2:3*iat)=gradTmp(iat,1:3) |
135 | 5 | pfleura2 | end do |
136 | 5 | pfleura2 | |
137 | 5 | pfleura2 | if (debug) THEN |
138 | 5 | pfleura2 | WRITE(*,*) "Cartesian gradient GradTmp" |
139 | 5 | pfleura2 | DO I=1,Nat |
140 | 5 | pfleura2 | WRITE(*,'(1X,I5,3(1X,F12.6))') I,Gradtmp(i,1:3) |
141 | 5 | pfleura2 | END DO |
142 | 5 | pfleura2 | WRITE(*,*) "Cartesian gradient Grad" |
143 | 5 | pfleura2 | WRITE(*,'(50(1X,F12.6))') Grad |
144 | 5 | pfleura2 | |
145 | 5 | pfleura2 | END IF |
146 | 5 | pfleura2 | |
147 | 5 | pfleura2 | |
148 | 5 | pfleura2 | deallocate(xyztmp,gradTmp) |
149 | 5 | pfleura2 | |
150 | 5 | pfleura2 | |
151 | 5 | pfleura2 | if (debug) WRITE(*,*) '================ Exiting Egrad_test_2D ===================' |
152 | 5 | pfleura2 | |
153 | 5 | pfleura2 | ! ====================================================================== |
154 | 5 | pfleura2 | end SUBROUTINE egrad_test_2D |
155 | 5 | pfleura2 | |
156 | 5 | pfleura2 | |
157 | 5 | pfleura2 | |
158 | 5 | pfleura2 | function E2D(natoms,Xyz) |
159 | 5 | pfleura2 | |
160 | 5 | pfleura2 | use Io_module, only : IOTMP |
161 | 5 | pfleura2 | |
162 | 5 | pfleura2 | IMPLICIT NONE |
163 | 5 | pfleura2 | integer, parameter :: KINT = kind(1) |
164 | 5 | pfleura2 | integer, parameter :: KREAL = kind(1.0d0) |
165 | 5 | pfleura2 | |
166 | 5 | pfleura2 | |
167 | 5 | pfleura2 | INTEGER(KINT) ,INTENT(IN) :: natoms |
168 | 5 | pfleura2 | REAL(KREAL) ,INTENT(IN) :: Xyz(natoms,3) |
169 | 5 | pfleura2 | REAL(KREAL) :: E,x,y, E2D |
170 | 5 | pfleura2 | REAL(KREAL), save :: Data(501,501) |
171 | 5 | pfleura2 | |
172 | 5 | pfleura2 | INTEGER(KINT) :: i,j |
173 | 5 | pfleura2 | |
174 | 5 | pfleura2 | LOGICAL :: Debug |
175 | 5 | pfleura2 | LOGICAL, SAVE :: First=.TRUE. |
176 | 5 | pfleura2 | |
177 | 5 | pfleura2 | INTERFACE |
178 | 5 | pfleura2 | function valid(string) result (isValid) |
179 | 5 | pfleura2 | CHARACTER(*), intent(in) :: string |
180 | 5 | pfleura2 | logical :: isValid |
181 | 5 | pfleura2 | END function VALID |
182 | 5 | pfleura2 | |
183 | 5 | pfleura2 | END INTERFACE |
184 | 5 | pfleura2 | |
185 | 5 | pfleura2 | debug=valid('e2D') |
186 | 5 | pfleura2 | |
187 | 5 | pfleura2 | if (First) THEN |
188 | 5 | pfleura2 | ! we read the data |
189 | 5 | pfleura2 | open(IOTMP,File="CCSDT.subtr.reg") |
190 | 5 | pfleura2 | DO I=1, 501 |
191 | 5 | pfleura2 | DO j=1,501 |
192 | 5 | pfleura2 | READ(IOTMP,*) x,y,E |
193 | 5 | pfleura2 | Data(int(x*100+0.1)+1,int(y*100+0.1)+1)=E |
194 | 5 | pfleura2 | write(*,*) x,y,int(x*100+0.1)+1, int(y*100+0.1)+1,E |
195 | 5 | pfleura2 | END DO |
196 | 5 | pfleura2 | ! we skip a blank line |
197 | 5 | pfleura2 | READ(IOTMP,*) |
198 | 5 | pfleura2 | END DO |
199 | 5 | pfleura2 | CLOSE(IOTMP) |
200 | 5 | pfleura2 | First=.FALSE. |
201 | 5 | pfleura2 | END IF |
202 | 5 | pfleura2 | |
203 | 5 | pfleura2 | x=Xyz(2,1) |
204 | 5 | pfleura2 | y=Xyz(3,1) |
205 | 5 | pfleura2 | E2D=Data(int(x*100+0.1)+1,int(y*100+0.1)+1) |
206 | 5 | pfleura2 | |
207 | 5 | pfleura2 | return |
208 | 5 | pfleura2 | end function E2D |