ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/branches/new_design/OOPSE-2.0/src/UseTheForce/DarkSide/LJ.F90
Revision: 1851
Committed: Sat Dec 4 20:09:19 2004 UTC (19 years, 7 months ago) by tim
File size: 10034 byte(s)
Log Message:
NVE is working now, get the same result as OOPSE-1.0

File Contents

# Content
1 !! Calculates Long Range forces Lennard-Jones interactions.
2 !! @author Charles F. Vardeman II
3 !! @author Matthew Meineke
4 !! @version $Id: LJ.F90,v 1.4.2.3 2004-12-04 20:09:19 tim Exp $, $Date: 2004-12-04 20:09:19 $, $Name: not supported by cvs2svn $, $Revision: 1.4.2.3 $
5
6 module lj
7 use atype_module
8 use switcheroo
9 use vector_class
10 use simulation
11 use status
12 #ifdef IS_MPI
13 use mpiSimulation
14 #endif
15 use force_globals
16
17 implicit none
18 PRIVATE
19
20 integer, parameter :: DP = selected_real_kind(15)
21
22 type, private :: LjType
23 integer :: c_ident
24 integer :: atid
25 real(kind=dp) :: sigma
26 real(kind=dp) :: epsilon
27 end type LjType
28
29 type(LjType), dimension(:), allocatable :: ParameterMap
30
31 logical, save :: haveMixingMap = .false.
32
33 type :: MixParameters
34 real(kind=DP) :: sigma
35 real(kind=DP) :: epsilon
36 real(kind=dp) :: sigma6
37 real(kind=dp) :: tp6
38 real(kind=dp) :: tp12
39 real(kind=dp) :: delta
40 end type MixParameters
41
42 type(MixParameters), dimension(:,:), allocatable :: MixingMap
43
44 real(kind=DP), save :: LJ_rcut
45 logical, save :: have_rcut = .false.
46 logical, save :: LJ_do_shift = .false.
47 logical, save :: useGeometricDistanceMixing = .false.
48
49 !! Public methods and data
50
51 public :: setCutoffLJ
52 public :: useGeometricMixing
53 public :: do_lj_pair
54 public :: newLJtype
55 public :: getSigma
56 public :: getEpsilon
57
58 contains
59
60 subroutine newLJtype(c_ident, sigma, epsilon, status)
61 integer,intent(in) :: c_ident
62 real(kind=dp),intent(in) :: sigma
63 real(kind=dp),intent(in) :: epsilon
64 integer,intent(out) :: status
65 integer :: nATypes, myATID
66 integer, pointer :: MatchList(:) => null()
67
68 status = 0
69
70 myATID = getFirstMatchingElement(atypes, "c_ident", c_ident)
71
72 if (.not.allocated(ParameterMap)) then
73
74 !call getMatchingElementList(atypes, "is_LennardJones", .true., &
75 ! nLJTypes, MatchList)
76 nAtypes = getSize(atypes)
77 if (nAtypes == 0) then
78 status = -1
79 return
80 end if
81
82 if (.not. allocated(ParameterMap)) then
83 allocate(ParameterMap(nAtypes))
84 endif
85
86 end if
87
88 if (myATID .gt. size(ParameterMap)) then
89 status = -1
90 return
91 endif
92
93 ! set the values for ParameterMap for this atom type:
94
95 ParameterMap(myATID)%c_ident = c_ident
96 ParameterMap(myATID)%atid = myATID
97 ParameterMap(myATID)%epsilon = epsilon
98 ParameterMap(myATID)%sigma = sigma
99
100 end subroutine newLJtype
101
102 function getSigma(atid) result (s)
103 integer, intent(in) :: atid
104 integer :: localError
105 real(kind=dp) :: s
106
107 if (.not.allocated(ParameterMap)) then
108 call handleError("LJ", "no ParameterMap was present before first call of getSigma!")
109 return
110 end if
111
112 s = ParameterMap(atid)%sigma
113 end function getSigma
114
115 function getEpsilon(atid) result (e)
116 integer, intent(in) :: atid
117 integer :: localError
118 real(kind=dp) :: e
119
120 if (.not.allocated(ParameterMap)) then
121 call handleError("LJ", "no ParameterMap was present before first call of getEpsilon!")
122 return
123 end if
124
125 e = ParameterMap(atid)%epsilon
126 end function getEpsilon
127
128
129 subroutine setCutoffLJ(rcut, do_shift, status)
130 logical, intent(in):: do_shift
131 integer :: status, myStatus
132 real(kind=dp) :: rcut
133
134 #define __FORTRAN90
135 #include "UseTheForce/fSwitchingFunction.h"
136
137 status = 0
138
139 LJ_rcut = rcut
140 LJ_do_shift = do_shift
141 call set_switch(LJ_SWITCH, rcut, rcut)
142 have_rcut = .true.
143
144 return
145 end subroutine setCutoffLJ
146
147 subroutine useGeometricMixing()
148 useGeometricDistanceMixing = .true.
149 haveMixingMap = .false.
150 return
151 end subroutine useGeometricMixing
152
153 subroutine createMixingMap(status)
154 integer :: nATIDs
155 integer :: status
156 integer :: i
157 integer :: j
158 real ( kind = dp ) :: Sigma_i, Sigma_j
159 real ( kind = dp ) :: Epsilon_i, Epsilon_j
160 real ( kind = dp ) :: rcut6
161
162 status = 0
163
164 nATIDs = size(ParameterMap)
165
166 if (nATIDs == 0) then
167 status = -1
168 return
169 end if
170
171 if (.not.have_rcut) then
172 status = -1
173 return
174 endif
175
176 if (.not. allocated(MixingMap)) then
177 allocate(MixingMap(nATIDs, nATIDs))
178 endif
179
180 rcut6 = LJ_rcut**6
181
182 ! This loops through all atypes, even those that don't support LJ forces.
183 do i = 1, nATIDs
184
185 Epsilon_i = ParameterMap(i)%epsilon
186 Sigma_i = ParameterMap(i)%sigma
187
188 ! do self mixing rule
189 MixingMap(i,i)%sigma = Sigma_i
190 MixingMap(i,i)%sigma6 = Sigma_i ** 6
191 MixingMap(i,i)%tp6 = (MixingMap(i,i)%sigma6)/rcut6
192 MixingMap(i,i)%tp12 = (MixingMap(i,i)%tp6) ** 2
193 MixingMap(i,i)%epsilon = Epsilon_i
194 MixingMap(i,i)%delta = -4.0_DP * MixingMap(i,i)%epsilon * &
195 (MixingMap(i,i)%tp12 - MixingMap(i,i)%tp6)
196
197 do j = i + 1, nATIDs
198
199 Epsilon_j = ParameterMap(j)%epsilon
200 Sigma_j = ParameterMap(j)%sigma
201
202 ! only the distance parameter uses different mixing policies
203 if (useGeometricDistanceMixing) then
204 ! only for OPLS as far as we can tell
205 MixingMap(i,j)%sigma = dsqrt(Sigma_i * Sigma_j)
206 else
207 ! everyone else
208 MixingMap(i,j)%sigma = 0.5_dp * (Sigma_i + Sigma_j)
209 endif
210
211 ! energy parameter is always geometric mean:
212 MixingMap(i,j)%epsilon = dsqrt(Epsilon_i * Epsilon_j)
213
214 MixingMap(i,j)%sigma6 = (MixingMap(i,j)%sigma)**6
215 MixingMap(i,j)%tp6 = MixingMap(i,j)%sigma6/rcut6
216 MixingMap(i,j)%tp12 = (MixingMap(i,j)%tp6) ** 2
217
218 MixingMap(i,j)%delta = -4.0_DP * MixingMap(i,j)%epsilon * &
219 (MixingMap(i,j)%tp12 - MixingMap(i,j)%tp6)
220
221 MixingMap(j,i)%sigma = MixingMap(i,j)%sigma
222 MixingMap(j,i)%sigma6 = MixingMap(i,j)%sigma6
223 MixingMap(j,i)%tp6 = MixingMap(i,j)%tp6
224 MixingMap(j,i)%tp12 = MixingMap(i,j)%tp12
225 MixingMap(j,i)%epsilon = MixingMap(i,j)%epsilon
226 MixingMap(j,i)%delta = MixingMap(i,j)%delta
227
228 end do
229 end do
230
231 haveMixingMap = .true.
232
233 end subroutine createMixingMap
234
235 subroutine do_lj_pair(atom1, atom2, d, rij, r2, sw, vpair, fpair, &
236 pot, f, do_pot)
237
238 integer, intent(in) :: atom1, atom2
239 real( kind = dp ), intent(in) :: rij, r2
240 real( kind = dp ) :: pot, sw, vpair
241 real( kind = dp ), dimension(3,nLocal) :: f
242 real( kind = dp ), intent(in), dimension(3) :: d
243 real( kind = dp ), intent(inout), dimension(3) :: fpair
244 logical, intent(in) :: do_pot
245
246 ! local Variables
247 real( kind = dp ) :: drdx, drdy, drdz
248 real( kind = dp ) :: fx, fy, fz
249 real( kind = dp ) :: pot_temp, dudr
250 real( kind = dp ) :: sigma6
251 real( kind = dp ) :: epsilon
252 real( kind = dp ) :: r6
253 real( kind = dp ) :: t6
254 real( kind = dp ) :: t12
255 real( kind = dp ) :: delta
256 integer :: id1, id2, localError
257
258 if (.not.haveMixingMap) then
259 localError = 0
260 call createMixingMap(localError)
261 if ( localError .ne. 0 ) then
262 call handleError("LJ", "MixingMap creation failed!")
263 return
264 end if
265 endif
266
267 ! Look up the correct parameters in the mixing matrix
268 #ifdef IS_MPI
269 sigma6 = MixingMap(atid_Row(atom1),atid_Col(atom2))%sigma6
270 epsilon = MixingMap(atid_Row(atom1),atid_Col(atom2))%epsilon
271 delta = MixingMap(atid_Row(atom1),atid_Col(atom2))%delta
272 #else
273 sigma6 = MixingMap(atid(atom1),atid(atom2))%sigma6
274 epsilon = MixingMap(atid(atom1),atid(atom2))%epsilon
275 delta = MixingMap(atid(atom1),atid(atom2))%delta
276 #endif
277
278 r6 = r2 * r2 * r2
279
280 t6 = sigma6/ r6
281 t12 = t6 * t6
282
283 pot_temp = 4.0E0_DP * epsilon * (t12 - t6)
284 if (LJ_do_shift) then
285 pot_temp = pot_temp + delta
286 endif
287
288 vpair = vpair + pot_temp
289
290 dudr = sw * 24.0E0_DP * epsilon * (t6 - 2.0E0_DP*t12) / rij
291
292 drdx = d(1) / rij
293 drdy = d(2) / rij
294 drdz = d(3) / rij
295
296 fx = dudr * drdx
297 fy = dudr * drdy
298 fz = dudr * drdz
299
300
301 #ifdef IS_MPI
302 if (do_pot) then
303 pot_Row(atom1) = pot_Row(atom1) + sw*pot_temp*0.5
304 pot_Col(atom2) = pot_Col(atom2) + sw*pot_temp*0.5
305 endif
306
307 f_Row(1,atom1) = f_Row(1,atom1) + fx
308 f_Row(2,atom1) = f_Row(2,atom1) + fy
309 f_Row(3,atom1) = f_Row(3,atom1) + fz
310
311 f_Col(1,atom2) = f_Col(1,atom2) - fx
312 f_Col(2,atom2) = f_Col(2,atom2) - fy
313 f_Col(3,atom2) = f_Col(3,atom2) - fz
314
315 #else
316 if (do_pot) pot = pot + sw*pot_temp
317
318 f(1,atom1) = f(1,atom1) + fx
319 f(2,atom1) = f(2,atom1) + fy
320 f(3,atom1) = f(3,atom1) + fz
321
322 f(1,atom2) = f(1,atom2) - fx
323 f(2,atom2) = f(2,atom2) - fy
324 f(3,atom2) = f(3,atom2) - fz
325 #endif
326
327 #ifdef IS_MPI
328 id1 = AtomRowToGlobal(atom1)
329 id2 = AtomColToGlobal(atom2)
330 #else
331 id1 = atom1
332 id2 = atom2
333 #endif
334
335 if (molMembershipList(id1) .ne. molMembershipList(id2)) then
336
337 fpair(1) = fpair(1) + fx
338 fpair(2) = fpair(2) + fy
339 fpair(3) = fpair(3) + fz
340
341 endif
342
343 return
344
345 end subroutine do_lj_pair
346
347
348 !! Calculates the mixing for sigma or epslon
349
350 end module lj
351
352 subroutine newLJtype(c_ident, sigma, epsilon, status)
353 use lj, ONLY : module_newLJtype => newLJtype
354 integer, parameter :: DP = selected_real_kind(15)
355 integer,intent(inout) :: c_ident
356 real(kind=dp),intent(inout) :: sigma
357 real(kind=dp),intent(inout) :: epsilon
358 integer,intent(inout) :: status
359
360 call module_newLJtype(c_ident, sigma, epsilon, status)
361
362 end subroutine newLJtype
363
364 subroutine useGeometricMixing()
365 use lj, ONLY: module_useGeometricMixing => useGeometricMixing
366
367 call module_useGeometricMixing()
368 return
369 end subroutine useGeometricMixing