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