ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/DarkSide/LJ.F90
Revision: 1754
Committed: Thu Nov 18 15:57:16 2004 UTC (19 years, 7 months ago) by chrisfen
File size: 9873 byte(s)
Log Message:
Fixed a mixing list bug that slowed down the force loop

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