root / src / egrad_test.f90 @ 12
Historique | Voir | Annoter | Télécharger (7,31 ko)
1 | 1 | pfleura2 | SUBROUTINE egrad_test(nat,e,geom,grad) |
---|---|---|---|
2 | 1 | pfleura2 | ! This program reads cartesian coordinates from the file Ext.in |
3 | 1 | pfleura2 | ! and print the energy (in au) and gradient (in au/Ang) in the file Ext.out |
4 | 1 | pfleura2 | ! format D25.15 |
5 | 1 | pfleura2 | |
6 | 12 | pfleura2 | !---------------------------------------------------------------------- |
7 | 12 | pfleura2 | ! Copyright 2003-2014 Ecole Normale Supérieure de Lyon, |
8 | 12 | pfleura2 | ! Centre National de la Recherche Scientifique, |
9 | 12 | pfleura2 | ! Université Claude Bernard Lyon 1. All rights reserved. |
10 | 12 | pfleura2 | ! |
11 | 12 | pfleura2 | ! This work is registered with the Agency for the Protection of Programs |
12 | 12 | pfleura2 | ! as IDDN.FR.001.100009.000.S.P.2014.000.30625 |
13 | 12 | pfleura2 | ! |
14 | 12 | pfleura2 | ! Authors: P. Fleurat-Lessard, P. Dayal |
15 | 12 | pfleura2 | ! Contact: optnpath@gmail.com |
16 | 12 | pfleura2 | ! |
17 | 12 | pfleura2 | ! This file is part of "Opt'n Path". |
18 | 12 | pfleura2 | ! |
19 | 12 | pfleura2 | ! "Opt'n Path" is free software: you can redistribute it and/or modify |
20 | 12 | pfleura2 | ! it under the terms of the GNU Affero General Public License as |
21 | 12 | pfleura2 | ! published by the Free Software Foundation, either version 3 of the License, |
22 | 12 | pfleura2 | ! or (at your option) any later version. |
23 | 12 | pfleura2 | ! |
24 | 12 | pfleura2 | ! "Opt'n Path" is distributed in the hope that it will be useful, |
25 | 12 | pfleura2 | ! but WITHOUT ANY WARRANTY; without even the implied warranty of |
26 | 12 | pfleura2 | ! |
27 | 12 | pfleura2 | ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the |
28 | 12 | pfleura2 | ! GNU Affero General Public License for more details. |
29 | 12 | pfleura2 | ! |
30 | 12 | pfleura2 | ! You should have received a copy of the GNU Affero General Public License |
31 | 12 | pfleura2 | ! along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>. |
32 | 12 | pfleura2 | ! |
33 | 12 | pfleura2 | ! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr, |
34 | 12 | pfleura2 | ! for commercial licensing opportunities. |
35 | 12 | pfleura2 | !---------------------------------------------------------------------- |
36 | 12 | pfleura2 | |
37 | 1 | pfleura2 | IMPLICIT NONE |
38 | 1 | pfleura2 | integer, parameter :: KINT = kind(1) |
39 | 1 | pfleura2 | integer, parameter :: KREAL = kind(1.0d0) |
40 | 1 | pfleura2 | |
41 | 1 | pfleura2 | INTEGER(KINT), INTENT(IN) :: Nat |
42 | 1 | pfleura2 | REAL(KREAL), INTENT(OUT) :: E,grad(Nat*3) |
43 | 1 | pfleura2 | REAL(KREAL), INTENT(IN) :: Geom(Nat,3) |
44 | 1 | pfleura2 | |
45 | 1 | pfleura2 | ! Bohr --> Angstr |
46 | 2 | pfleura2 | ! real(KREAL), parameter :: BOHR = 0.52917726D+00 |
47 | 1 | pfleura2 | ! |
48 | 2 | pfleura2 | |
49 | 1 | pfleura2 | ! Parameters to define the surface |
50 | 1 | pfleura2 | INTEGER(KINT), DIMENSION(6), PARAMETER :: IECOEF = (/-1,9,-45,45,-9,1/) |
51 | 1 | pfleura2 | INTEGER(KINT), DIMENSION(6), PARAMETER :: ISCOEF = (/-3,-2,-1,1,2,3/) |
52 | 1 | pfleura2 | REAL(KREAL), PARAMETER :: hh=0.001d0 |
53 | 1 | pfleura2 | |
54 | 1 | pfleura2 | ! Variables |
55 | 2 | pfleura2 | INTEGER(KINT) :: i, iat, jat |
56 | 1 | pfleura2 | REAL(KREAL), ALLOCATABLE :: Xyztmp(:,:),GradTmp(:,:) |
57 | 1 | pfleura2 | |
58 | 1 | pfleura2 | LOGICAL :: Debug |
59 | 1 | pfleura2 | |
60 | 1 | pfleura2 | REAL(KREAL), external :: Exyz |
61 | 1 | pfleura2 | |
62 | 1 | pfleura2 | |
63 | 1 | pfleura2 | INTERFACE |
64 | 1 | pfleura2 | function valid(string) result (isValid) |
65 | 1 | pfleura2 | CHARACTER(*), intent(in) :: string |
66 | 1 | pfleura2 | logical :: isValid |
67 | 1 | pfleura2 | END function VALID |
68 | 1 | pfleura2 | |
69 | 1 | pfleura2 | END INTERFACE |
70 | 1 | pfleura2 | |
71 | 1 | pfleura2 | debug=valid('egrad_test') |
72 | 1 | pfleura2 | |
73 | 1 | pfleura2 | if (debug) WRITE(*,*) '================ Entering Egrad_test ===================' |
74 | 1 | pfleura2 | if (debug) THEN |
75 | 1 | pfleura2 | WRITE(*,*) "Cartesian Geometry" |
76 | 1 | pfleura2 | DO I=1,Nat |
77 | 1 | pfleura2 | WRITE(*,'(1X,I5,3(1X,F12.6))') I,Geom(i,1:3) |
78 | 1 | pfleura2 | END DO |
79 | 1 | pfleura2 | END IF |
80 | 1 | pfleura2 | |
81 | 1 | pfleura2 | ALLOCATE(XyZTmp(Nat,3),GradTmp(Nat,3)) |
82 | 1 | pfleura2 | |
83 | 1 | pfleura2 | e=Exyz(nat,Geom) |
84 | 1 | pfleura2 | |
85 | 1 | pfleura2 | ! We now calculate the gradients using numerical derivatives |
86 | 1 | pfleura2 | Grad=0.d0 |
87 | 1 | pfleura2 | GradTmp=0.d0 |
88 | 1 | pfleura2 | do iat=1,3 |
89 | 1 | pfleura2 | do jat=1,nat |
90 | 1 | pfleura2 | xyztmp=geom |
91 | 1 | pfleura2 | do i=1,6 |
92 | 1 | pfleura2 | xyztmp(jat,iat)=geom(jat,iat)+ISCoef(i)*hh |
93 | 1 | pfleura2 | gradTmp(jat,iat)=gradTmp(jat,iat)+IECoef(i)*Exyz(nat,xyztmp) |
94 | 1 | pfleura2 | end do |
95 | 1 | pfleura2 | end do |
96 | 1 | pfleura2 | end do |
97 | 1 | pfleura2 | gradTmp=gradTmp/(60.*hh) |
98 | 1 | pfleura2 | do iat=1,nat |
99 | 1 | pfleura2 | grad(3*iat-2:3*iat)=gradTmp(iat,1:3) |
100 | 1 | pfleura2 | end do |
101 | 1 | pfleura2 | |
102 | 1 | pfleura2 | if (debug) THEN |
103 | 1 | pfleura2 | WRITE(*,*) "Cartesian gradient GradTmp" |
104 | 1 | pfleura2 | DO I=1,Nat |
105 | 1 | pfleura2 | WRITE(*,'(1X,I5,3(1X,F12.6))') I,Gradtmp(i,1:3) |
106 | 1 | pfleura2 | END DO |
107 | 1 | pfleura2 | WRITE(*,*) "Cartesian gradient Grad" |
108 | 1 | pfleura2 | WRITE(*,'(50(1X,F12.6))') Grad |
109 | 1 | pfleura2 | |
110 | 1 | pfleura2 | END IF |
111 | 1 | pfleura2 | |
112 | 1 | pfleura2 | |
113 | 1 | pfleura2 | deallocate(xyztmp,gradTmp) |
114 | 1 | pfleura2 | |
115 | 1 | pfleura2 | |
116 | 1 | pfleura2 | if (debug) WRITE(*,*) '================ Exiting Egrad_test ===================' |
117 | 1 | pfleura2 | |
118 | 1 | pfleura2 | ! ====================================================================== |
119 | 1 | pfleura2 | end |
120 | 1 | pfleura2 | |
121 | 1 | pfleura2 | |
122 | 1 | pfleura2 | |
123 | 1 | pfleura2 | function Exyz(natoms,Xyz) |
124 | 1 | pfleura2 | |
125 | 1 | pfleura2 | use Path_module, only : order |
126 | 1 | pfleura2 | |
127 | 1 | pfleura2 | IMPLICIT NONE |
128 | 1 | pfleura2 | integer, parameter :: KINT = kind(1) |
129 | 1 | pfleura2 | integer, parameter :: KREAL = kind(1.0d0) |
130 | 1 | pfleura2 | |
131 | 1 | pfleura2 | |
132 | 1 | pfleura2 | INTEGER(KINT) ,INTENT(IN) :: natoms |
133 | 1 | pfleura2 | REAL(KREAL) ,INTENT(IN) :: Xyz(natoms,3) |
134 | 1 | pfleura2 | REAL(KREAL) :: Exyz |
135 | 1 | pfleura2 | |
136 | 1 | pfleura2 | INTEGER(KINT) :: i |
137 | 1 | pfleura2 | REAL(KREAL) :: dCH,dNH,dCN |
138 | 1 | pfleura2 | |
139 | 2 | pfleura2 | ! real(KREAL) :: autoA,autoeV |
140 | 2 | pfleura2 | real(KREAL) :: autoeV |
141 | 2 | pfleura2 | ! parameter (autoA=0.52917715d0) |
142 | 1 | pfleura2 | parameter (autoeV=27.21183d0) |
143 | 1 | pfleura2 | |
144 | 1 | pfleura2 | |
145 | 1 | pfleura2 | |
146 | 2 | pfleura2 | real(KREAL) :: r1, r2, r3 |
147 | 1 | pfleura2 | |
148 | 1 | pfleura2 | real(KREAL) :: Z1,Z12,V1 |
149 | 1 | pfleura2 | real(KREAL) :: Z2,Z22,V2 |
150 | 1 | pfleura2 | real(KREAL) :: Z3,Z32,V3 |
151 | 1 | pfleura2 | |
152 | 1 | pfleura2 | real(KREAL) :: S1,S2,S3,S12,S22,S32,POLY |
153 | 1 | pfleura2 | real(KREAL) :: E1,E2,E3,HY1,HY2,HY3,SWITCH,V123 |
154 | 1 | pfleura2 | |
155 | 1 | pfleura2 | LOGICAL :: Debug |
156 | 1 | pfleura2 | LOGICAL, SAVE :: First=.TRUE. |
157 | 1 | pfleura2 | |
158 | 1 | pfleura2 | INTERFACE |
159 | 1 | pfleura2 | function valid(string) result (isValid) |
160 | 1 | pfleura2 | CHARACTER(*), intent(in) :: string |
161 | 1 | pfleura2 | logical :: isValid |
162 | 1 | pfleura2 | END function VALID |
163 | 1 | pfleura2 | |
164 | 1 | pfleura2 | END INTERFACE |
165 | 1 | pfleura2 | |
166 | 1 | pfleura2 | debug=valid('exyz') |
167 | 1 | pfleura2 | |
168 | 1 | pfleura2 | |
169 | 1 | pfleura2 | |
170 | 1 | pfleura2 | dCN=0. |
171 | 1 | pfleura2 | dCH=0. |
172 | 1 | pfleura2 | dNH=0. |
173 | 1 | pfleura2 | do i=1,3 |
174 | 1 | pfleura2 | dCN=dCN+(xyz(Order(3),i)-xyz(order(2),i))**2 |
175 | 1 | pfleura2 | dCH=dCH+(xyz(order(1),i)-xyz(order(2),i))**2 |
176 | 1 | pfleura2 | dNH=dNH+(xyz(order(1),i)-xyz(order(3),i))**2 |
177 | 1 | pfleura2 | end do |
178 | 1 | pfleura2 | R1=sqrt(dCH) |
179 | 1 | pfleura2 | R2=sqrt(dCN) |
180 | 1 | pfleura2 | R3=sqrt(dNH) |
181 | 1 | pfleura2 | |
182 | 1 | pfleura2 | IF (debug.AND.First) THEN |
183 | 1 | pfleura2 | WRITE(*,*) "Exyz in Test, dCH,dCN,dNH:",R1,R2,R3 |
184 | 1 | pfleura2 | END IF |
185 | 1 | pfleura2 | |
186 | 1 | pfleura2 | ! R1=R1*autoA |
187 | 1 | pfleura2 | ! R2=R2*autoA |
188 | 1 | pfleura2 | ! R3=R3*autoA |
189 | 1 | pfleura2 | |
190 | 1 | pfleura2 | !.....CH |
191 | 1 | pfleura2 | Z1=R1-1.0823 |
192 | 1 | pfleura2 | Z12=Z1*Z1 |
193 | 1 | pfleura2 | V1=-2.8521*(1.0+5.5297*Z1+8.7166*Z12+5.3082*Z1*Z12)*dexp(-5.5297*Z1) |
194 | 1 | pfleura2 | !.....CN |
195 | 1 | pfleura2 | Z2=R2-1.1718 |
196 | 1 | pfleura2 | Z22=Z2*Z2 |
197 | 1 | pfleura2 | V2=-7.9282*(1.0+5.2448*Z2+7.3416*Z22+4.9785*Z2*Z22)*dexp(-5.2448*Z2) |
198 | 1 | pfleura2 | !.....NH |
199 | 1 | pfleura2 | Z3=R3-1.0370 |
200 | 1 | pfleura2 | Z32=Z3*Z3 |
201 | 1 | pfleura2 | V3=-3.9938*(1.0+3.0704*Z3)*dexp(-3.0704*Z3) |
202 | 1 | pfleura2 | |
203 | 1 | pfleura2 | ! write(6,*) v1,v2,v3 |
204 | 1 | pfleura2 | |
205 | 1 | pfleura2 | !.....THREE BODY TERMS |
206 | 1 | pfleura2 | Z1=R1-1.9607 |
207 | 1 | pfleura2 | Z2=R2-2.2794 |
208 | 1 | pfleura2 | Z3=R3-1.8687 |
209 | 1 | pfleura2 | S1=0.4436*Z1+0.6091*Z2+0.6575*Z3 |
210 | 1 | pfleura2 | S2=-.8941*Z1+0.2498*Z2+0.3718*Z3 |
211 | 1 | pfleura2 | S3=0.0622*Z1-0.7527*Z2+0.6554*Z3 |
212 | 1 | pfleura2 | |
213 | 1 | pfleura2 | S12=S1*S1 |
214 | 1 | pfleura2 | S22=S2*S2 |
215 | 1 | pfleura2 | S32=S3*S3 |
216 | 1 | pfleura2 | POLY=-3.0578*(1.0+1.9076*S1-0.5008*S2-0.0149*S3+0.6695*S12 & |
217 | 1 | pfleura2 | -1.3535*S22-1.0501*S32+0.2698*S1*S2-1.1120*S1*S3 & |
218 | 1 | pfleura2 | +1.9310*S2*S3-0.0877*S1*S12+0.0044*S2*S22+0.0700 & |
219 | 1 | pfleura2 | *S3*S32+0.0898*S12*S2-1.0186*S1*S22-0.0911*S12 & |
220 | 1 | pfleura2 | *S3+0.0017*S1*S32+0.4567*S22*S3-0.8840*S2*S32 & |
221 | 1 | pfleura2 | +0.3333*S1*S2*S3-0.0367*S12*S12+0.4821*S22*S22 & |
222 | 1 | pfleura2 | +0.2564*S32*S32-0.0017*S12*S1*S2-0.2278*S12*S22 & |
223 | 1 | pfleura2 | -0.1287*S1*S2*S22+0.1759*S1*S12*S3-0.0399*S12*S32 & |
224 | 1 | pfleura2 | -0.1447*S1*S3*S32-0.3147*S2*S22*S3+0.1233*S22*S32 & |
225 | 1 | pfleura2 | +0.3161*S2*S3*S32+0.0919*S12*S2*S3-0.0954*S1*S22*S3 & |
226 | 1 | pfleura2 | +0.1778*S1*S2*S32-0.1892*S22*S22*S2) |
227 | 1 | pfleura2 | |
228 | 1 | pfleura2 | |
229 | 1 | pfleura2 | E1=dexp(3.9742*Z1/2.) |
230 | 1 | pfleura2 | E2=dexp(4.3688*Z2/2.) |
231 | 1 | pfleura2 | E3=dexp(1.5176*Z3/2.) |
232 | 1 | pfleura2 | HY1=(E1-1.0/E1)/(E1+1.0/E1) |
233 | 1 | pfleura2 | HY2=(E2-1.0/E2)/(E2+1.0/E2) |
234 | 1 | pfleura2 | HY3=(E3-1.0/E3)/(E3+1.0/E3) |
235 | 1 | pfleura2 | SWITCH=(1.0-HY1)*(1.0-HY2)*(1.0-HY3) |
236 | 1 | pfleura2 | V123=SWITCH*POLY |
237 | 1 | pfleura2 | |
238 | 1 | pfleura2 | ! write(6,*) v123,V1+V2+V3+V123 |
239 | 1 | pfleura2 | |
240 | 1 | pfleura2 | Exyz=(V1+V2+V3+V123)/autoeV |
241 | 1 | pfleura2 | |
242 | 1 | pfleura2 | First=.FALSE. |
243 | 1 | pfleura2 | |
244 | 1 | pfleura2 | return |
245 | 1 | pfleura2 | end function Exyz |
246 | 1 | pfleura2 | |
247 | 1 | pfleura2 | function Exyz2(natoms,Xyz) |
248 | 1 | pfleura2 | |
249 | 1 | pfleura2 | IMPLICIT NONE |
250 | 1 | pfleura2 | integer, parameter :: KINT = kind(1) |
251 | 1 | pfleura2 | integer, parameter :: KREAL = kind(1.0d0) |
252 | 1 | pfleura2 | |
253 | 1 | pfleura2 | |
254 | 1 | pfleura2 | INTEGER(KINT) ,INTENT(IN) :: natoms |
255 | 1 | pfleura2 | REAL(KREAL) ,INTENT(IN) :: Xyz(natoms,3) |
256 | 1 | pfleura2 | REAL(KREAL) :: Exyz |
257 | 1 | pfleura2 | |
258 | 2 | pfleura2 | INTEGER(KINT) :: iat, jat |
259 | 1 | pfleura2 | REAL(KREAL) :: Exyz2 |
260 | 1 | pfleura2 | |
261 | 2 | pfleura2 | ! real(KREAL) :: autoA,autoeV |
262 | 2 | pfleura2 | ! parameter (autoA=0.52917715d0) |
263 | 2 | pfleura2 | ! parameter (autoeV=27.21183d0) |
264 | 1 | pfleura2 | |
265 | 1 | pfleura2 | |
266 | 1 | pfleura2 | |
267 | 1 | pfleura2 | |
268 | 1 | pfleura2 | |
269 | 1 | pfleura2 | |
270 | 1 | pfleura2 | Exyz=0. |
271 | 1 | pfleura2 | do jat=1,natoms |
272 | 1 | pfleura2 | do iat=1,3 |
273 | 1 | pfleura2 | Exyz=Exyz+(3*iat-3+jat)*xyz(jat,iat)**2 |
274 | 1 | pfleura2 | end do |
275 | 1 | pfleura2 | end do |
276 | 1 | pfleura2 | |
277 | 1 | pfleura2 | Exyz2=Exyz |
278 | 1 | pfleura2 | |
279 | 1 | pfleura2 | return |
280 | 1 | pfleura2 | end function Exyz2 |