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