ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/OpenMD/trunk/src/UseTheForce/DarkSide/LJ.F90
Revision: 942
Committed: Fri Apr 21 19:32:07 2006 UTC (19 years, 3 months ago) by chrisfen
File size: 12732 byte(s)
Log Message:
Removed sqrt splines and shape stuff (doesn't work, so why was it in there?).  Changed some of the water samples to use shifted_force.  Probably should set the defaults to use the damped version now that we sped it up.

File Contents

# User Rev Content
1 gezelter 246 !!
2     !! Copyright (c) 2005 The University of Notre Dame. All Rights Reserved.
3     !!
4     !! The University of Notre Dame grants you ("Licensee") a
5     !! non-exclusive, royalty free, license to use, modify and
6     !! redistribute this software in source and binary code form, provided
7     !! that the following conditions are met:
8     !!
9     !! 1. Acknowledgement of the program authors must be made in any
10     !! publication of scientific results based in part on use of the
11     !! program. An acceptable form of acknowledgement is citation of
12     !! the article in which the program was described (Matthew
13     !! A. Meineke, Charles F. Vardeman II, Teng Lin, Christopher
14     !! J. Fennell and J. Daniel Gezelter, "OOPSE: An Object-Oriented
15     !! Parallel Simulation Engine for Molecular Dynamics,"
16     !! J. Comput. Chem. 26, pp. 252-271 (2005))
17     !!
18     !! 2. Redistributions of source code must retain the above copyright
19     !! notice, this list of conditions and the following disclaimer.
20     !!
21     !! 3. Redistributions in binary form must reproduce the above copyright
22     !! notice, this list of conditions and the following disclaimer in the
23     !! documentation and/or other materials provided with the
24     !! distribution.
25     !!
26     !! This software is provided "AS IS," without a warranty of any
27     !! kind. All express or implied conditions, representations and
28     !! warranties, including any implied warranty of merchantability,
29     !! fitness for a particular purpose or non-infringement, are hereby
30     !! excluded. The University of Notre Dame and its licensors shall not
31     !! be liable for any damages suffered by licensee as a result of
32     !! using, modifying or distributing the software or its
33     !! derivatives. In no event will the University of Notre Dame or its
34     !! licensors be liable for any lost revenue, profit or data, or for
35     !! direct, indirect, special, consequential, incidental or punitive
36     !! damages, however caused and regardless of the theory of liability,
37     !! arising out of the use of or inability to use software, even if the
38     !! University of Notre Dame has been advised of the possibility of
39     !! such damages.
40     !!
41    
42    
43 gezelter 115 !! Calculates Long Range forces Lennard-Jones interactions.
44     !! @author Charles F. Vardeman II
45     !! @author Matthew Meineke
46 chrisfen 942 !! @version $Id: LJ.F90,v 1.23 2006-04-21 19:32:07 chrisfen Exp $, $Date: 2006-04-21 19:32:07 $, $Name: not supported by cvs2svn $, $Revision: 1.23 $
47 gezelter 115
48 gezelter 246
49 gezelter 115 module lj
50     use atype_module
51     use vector_class
52     use simulation
53 gezelter 135 use status
54 chuckv 798 use fForceOptions
55 gezelter 115 #ifdef IS_MPI
56     use mpiSimulation
57     #endif
58     use force_globals
59    
60     implicit none
61     PRIVATE
62 chuckv 656 #define __FORTRAN90
63     #include "UseTheForce/DarkSide/fInteractionMap.h"
64 gezelter 507
65 chuckv 131 integer, parameter :: DP = selected_real_kind(15)
66 gezelter 507
67 gezelter 572 logical, save :: useGeometricDistanceMixing = .false.
68     logical, save :: haveMixingMap = .false.
69    
70     real(kind=DP), save :: defaultCutoff = 0.0_DP
71     logical, save :: defaultShift = .false.
72     logical, save :: haveDefaultCutoff = .false.
73    
74     type, private :: LJtype
75     integer :: atid
76 gezelter 135 real(kind=dp) :: sigma
77     real(kind=dp) :: epsilon
78 gezelter 572 logical :: isSoftCore = .false.
79     end type LJtype
80 gezelter 507
81 gezelter 572 type, private :: LJList
82 chuckv 620 integer :: Nljtypes = 0
83 gezelter 572 integer :: currentLJtype = 0
84     type(LJtype), pointer :: LJtypes(:) => null()
85     integer, pointer :: atidToLJtype(:) => null()
86     end type LJList
87 gezelter 507
88 gezelter 572 type(LJList), save :: LJMap
89 gezelter 507
90 gezelter 135 type :: MixParameters
91     real(kind=DP) :: sigma
92     real(kind=DP) :: epsilon
93 gezelter 938 real(kind=dp) :: sigmai
94 gezelter 572 real(kind=dp) :: rCut
95     logical :: rCutWasSet = .false.
96     logical :: shiftedPot
97     logical :: isSoftCore = .false.
98 gezelter 135 end type MixParameters
99 gezelter 507
100 gezelter 135 type(MixParameters), dimension(:,:), allocatable :: MixingMap
101 gezelter 507
102 gezelter 572 public :: newLJtype
103     public :: setLJDefaultCutoff
104     public :: getSigma
105     public :: getEpsilon
106 gezelter 135 public :: do_lj_pair
107 gezelter 572 public :: destroyLJtypes
108 gezelter 507
109 gezelter 115 contains
110    
111 gezelter 572 subroutine newLJtype(c_ident, sigma, epsilon, isSoftCore, status)
112 gezelter 246 integer,intent(in) :: c_ident
113 gezelter 135 real(kind=dp),intent(in) :: sigma
114     real(kind=dp),intent(in) :: epsilon
115 gezelter 572 integer, intent(in) :: isSoftCore
116 chuckv 131 integer,intent(out) :: status
117 gezelter 572 integer :: nLJTypes, ntypes, myATID
118 gezelter 246 integer, pointer :: MatchList(:) => null()
119 gezelter 572 integer :: current
120 gezelter 135
121 chuckv 131 status = 0
122 gezelter 572 ! check to see if this is the first time into this routine...
123     if (.not.associated(LJMap%LJtypes)) then
124 gezelter 507
125 gezelter 572 call getMatchingElementList(atypes, "is_LennardJones", .true., &
126     nLJTypes, MatchList)
127    
128     LJMap%nLJtypes = nLJTypes
129    
130     allocate(LJMap%LJtypes(nLJTypes))
131    
132     ntypes = getSize(atypes)
133    
134     allocate(LJMap%atidToLJtype(ntypes))
135     end if
136    
137     LJMap%currentLJtype = LJMap%currentLJtype + 1
138     current = LJMap%currentLJtype
139    
140 gezelter 246 myATID = getFirstMatchingElement(atypes, "c_ident", c_ident)
141 gezelter 572 LJMap%atidToLJtype(myATID) = current
142     LJMap%LJtypes(current)%atid = myATID
143     LJMap%LJtypes(current)%sigma = sigma
144     LJMap%LJtypes(current)%epsilon = epsilon
145     if (isSoftCore .eq. 1) then
146     LJMap%LJtypes(current)%isSoftCore = .true.
147     else
148     LJMap%LJtypes(current)%isSoftCore = .false.
149     endif
150     end subroutine newLJtype
151 chuckv 131
152 gezelter 572 subroutine setLJDefaultCutoff(thisRcut, shiftedPot)
153     real(kind=dp), intent(in) :: thisRcut
154     logical, intent(in) :: shiftedPot
155     defaultCutoff = thisRcut
156     defaultShift = shiftedPot
157     haveDefaultCutoff = .true.
158 chrisfen 942 !we only want to build LJ Mixing map if LJ is being used.
159 chuckv 620 if(LJMap%nLJTypes /= 0) then
160     call createMixingMap()
161     end if
162 gezelter 938
163 gezelter 572 end subroutine setLJDefaultCutoff
164 gezelter 507
165 gezelter 140 function getSigma(atid) result (s)
166     integer, intent(in) :: atid
167 gezelter 572 integer :: ljt1
168 gezelter 140 real(kind=dp) :: s
169 gezelter 507
170 gezelter 572 if (LJMap%currentLJtype == 0) then
171     call handleError("LJ", "No members in LJMap")
172 gezelter 140 return
173     end if
174 gezelter 507
175 gezelter 572 ljt1 = LJMap%atidToLJtype(atid)
176     s = LJMap%LJtypes(ljt1)%sigma
177    
178 gezelter 140 end function getSigma
179    
180     function getEpsilon(atid) result (e)
181     integer, intent(in) :: atid
182 gezelter 572 integer :: ljt1
183 gezelter 140 real(kind=dp) :: e
184 gezelter 507
185 gezelter 572 if (LJMap%currentLJtype == 0) then
186     call handleError("LJ", "No members in LJMap")
187 gezelter 140 return
188     end if
189 gezelter 507
190 gezelter 572 ljt1 = LJMap%atidToLJtype(atid)
191     e = LJMap%LJtypes(ljt1)%epsilon
192    
193 gezelter 140 end function getEpsilon
194    
195 gezelter 572 subroutine createMixingMap()
196     integer :: nLJtypes, i, j
197     real ( kind = dp ) :: s1, s2, e1, e2
198     real ( kind = dp ) :: rcut6, tp6, tp12
199 gezelter 590 logical :: isSoftCore1, isSoftCore2, doShift
200 gezelter 135
201 gezelter 572 if (LJMap%currentLJtype == 0) then
202     call handleError("LJ", "No members in LJMap")
203 gezelter 402 return
204 gezelter 572 end if
205 gezelter 507
206 gezelter 572 nLJtypes = LJMap%nLJtypes
207 gezelter 507
208 gezelter 402 if (.not. allocated(MixingMap)) then
209 gezelter 572 allocate(MixingMap(nLJtypes, nLJtypes))
210 gezelter 402 endif
211    
212 chuckv 798 useGeometricDistanceMixing = usesGeometricDistanceMixing()
213 gezelter 572 do i = 1, nLJtypes
214 gezelter 507
215 gezelter 572 s1 = LJMap%LJtypes(i)%sigma
216     e1 = LJMap%LJtypes(i)%epsilon
217     isSoftCore1 = LJMap%LJtypes(i)%isSoftCore
218 gezelter 507
219 gezelter 572 do j = i, nLJtypes
220    
221     s2 = LJMap%LJtypes(j)%sigma
222     e2 = LJMap%LJtypes(j)%epsilon
223     isSoftCore2 = LJMap%LJtypes(j)%isSoftCore
224    
225     MixingMap(i,j)%isSoftCore = isSoftCore1 .or. isSoftCore2
226 gezelter 507
227 gezelter 572 ! only the distance parameter uses different mixing policies
228     if (useGeometricDistanceMixing) then
229     MixingMap(i,j)%sigma = dsqrt(s1 * s2)
230     else
231     MixingMap(i,j)%sigma = 0.5_dp * (s1 + s2)
232     endif
233    
234     MixingMap(i,j)%epsilon = dsqrt(e1 * e2)
235 gezelter 507
236 gezelter 938 MixingMap(i,j)%sigmai = 1.0_DP / (MixingMap(i,j)%sigma)
237 gezelter 507
238 gezelter 762 if (haveDefaultCutoff) then
239     MixingMap(i,j)%shiftedPot = defaultShift
240 gezelter 572 else
241 gezelter 762 MixingMap(i,j)%shiftedPot = defaultShift
242     endif
243 gezelter 507
244 gezelter 590 if (i.ne.j) then
245     MixingMap(j,i)%sigma = MixingMap(i,j)%sigma
246     MixingMap(j,i)%epsilon = MixingMap(i,j)%epsilon
247 gezelter 938 MixingMap(j,i)%sigmai = MixingMap(i,j)%sigmai
248 gezelter 590 MixingMap(j,i)%rCut = MixingMap(i,j)%rCut
249     MixingMap(j,i)%rCutWasSet = MixingMap(i,j)%rCutWasSet
250     MixingMap(j,i)%shiftedPot = MixingMap(i,j)%shiftedPot
251     MixingMap(j,i)%isSoftCore = MixingMap(i,j)%isSoftCore
252     endif
253    
254 gezelter 572 enddo
255     enddo
256    
257 chrisfen 217 haveMixingMap = .true.
258 gezelter 572
259 gezelter 135 end subroutine createMixingMap
260 chrisfen 942
261 gezelter 762 subroutine do_lj_pair(atom1, atom2, d, rij, r2, rcut, sw, vpair, fpair, &
262 gezelter 115 pot, f, do_pot)
263 gezelter 762
264 gezelter 115 integer, intent(in) :: atom1, atom2
265 gezelter 572 integer :: atid1, atid2, ljt1, ljt2
266 gezelter 762 real( kind = dp ), intent(in) :: rij, r2, rcut
267 gezelter 115 real( kind = dp ) :: pot, sw, vpair
268     real( kind = dp ), dimension(3,nLocal) :: f
269     real( kind = dp ), intent(in), dimension(3) :: d
270     real( kind = dp ), intent(inout), dimension(3) :: fpair
271     logical, intent(in) :: do_pot
272    
273     ! local Variables
274     real( kind = dp ) :: drdx, drdy, drdz
275     real( kind = dp ) :: fx, fy, fz
276 gezelter 938 real( kind = dp ) :: myPot, myPotC, myDeriv, myDerivC, ros, rcos
277 gezelter 115 real( kind = dp ) :: pot_temp, dudr
278 gezelter 938 real( kind = dp ) :: sigmai
279 gezelter 115 real( kind = dp ) :: epsilon
280 gezelter 572 logical :: isSoftCore, shiftedPot
281 gezelter 135 integer :: id1, id2, localError
282 gezelter 115
283 gezelter 135 if (.not.haveMixingMap) then
284 gezelter 572 call createMixingMap()
285 gezelter 135 endif
286    
287 gezelter 115 ! Look up the correct parameters in the mixing matrix
288     #ifdef IS_MPI
289 gezelter 572 atid1 = atid_Row(atom1)
290     atid2 = atid_Col(atom2)
291 gezelter 115 #else
292 gezelter 572 atid1 = atid(atom1)
293     atid2 = atid(atom2)
294 gezelter 115 #endif
295    
296 gezelter 572 ljt1 = LJMap%atidToLJtype(atid1)
297     ljt2 = LJMap%atidToLJtype(atid2)
298    
299 gezelter 938 sigmai = MixingMap(ljt1,ljt2)%sigmai
300 gezelter 572 epsilon = MixingMap(ljt1,ljt2)%epsilon
301     isSoftCore = MixingMap(ljt1,ljt2)%isSoftCore
302     shiftedPot = MixingMap(ljt1,ljt2)%shiftedPot
303    
304 gezelter 938 ros = rij * sigmai
305     myPotC = 0.0_DP
306 gezelter 507
307 gezelter 938 if (isSoftCore) then
308 tim 378
309 gezelter 938 call getSoftFunc(ros, myPot, myDeriv)
310    
311 gezelter 572 if (shiftedPot) then
312 gezelter 938 rcos = rcut * sigmai
313     call getSoftFunc(rcos, myPotC, myDerivC)
314 gezelter 572 endif
315 gezelter 938
316 tim 378 else
317 gezelter 938
318     call getLJfunc(ros, myPot, myDeriv)
319    
320 gezelter 572 if (shiftedPot) then
321 gezelter 938 rcos = rcut * sigmai
322     call getLJfunc(rcos, myPotC, myDerivC)
323 gezelter 507 endif
324 gezelter 572
325 gezelter 115 endif
326 gezelter 507
327 gezelter 938 !write(*,*) rij, ros, rcos, myPot, myDeriv, myPotC
328    
329     pot_temp = epsilon * (myPot - myPotC)
330     vpair = vpair + pot_temp
331     dudr = sw * epsilon * myDeriv * sigmai
332    
333 gezelter 115 drdx = d(1) / rij
334     drdy = d(2) / rij
335     drdz = d(3) / rij
336 gezelter 507
337 gezelter 115 fx = dudr * drdx
338     fy = dudr * drdy
339     fz = dudr * drdz
340 gezelter 507
341 gezelter 115 #ifdef IS_MPI
342     if (do_pot) then
343 gezelter 662 pot_Row(VDW_POT,atom1) = pot_Row(VDW_POT,atom1) + sw*pot_temp*0.5
344     pot_Col(VDW_POT,atom2) = pot_Col(VDW_POT,atom2) + sw*pot_temp*0.5
345 gezelter 115 endif
346 gezelter 507
347 gezelter 115 f_Row(1,atom1) = f_Row(1,atom1) + fx
348     f_Row(2,atom1) = f_Row(2,atom1) + fy
349     f_Row(3,atom1) = f_Row(3,atom1) + fz
350 gezelter 507
351 gezelter 115 f_Col(1,atom2) = f_Col(1,atom2) - fx
352     f_Col(2,atom2) = f_Col(2,atom2) - fy
353     f_Col(3,atom2) = f_Col(3,atom2) - fz
354 gezelter 507
355 gezelter 115 #else
356     if (do_pot) pot = pot + sw*pot_temp
357    
358     f(1,atom1) = f(1,atom1) + fx
359     f(2,atom1) = f(2,atom1) + fy
360     f(3,atom1) = f(3,atom1) + fz
361 gezelter 507
362 gezelter 115 f(1,atom2) = f(1,atom2) - fx
363     f(2,atom2) = f(2,atom2) - fy
364     f(3,atom2) = f(3,atom2) - fz
365     #endif
366 gezelter 507
367 gezelter 115 #ifdef IS_MPI
368     id1 = AtomRowToGlobal(atom1)
369     id2 = AtomColToGlobal(atom2)
370     #else
371     id1 = atom1
372     id2 = atom2
373     #endif
374    
375     if (molMembershipList(id1) .ne. molMembershipList(id2)) then
376 gezelter 507
377 gezelter 115 fpair(1) = fpair(1) + fx
378     fpair(2) = fpair(2) + fy
379     fpair(3) = fpair(3) + fz
380    
381     endif
382    
383     return
384 gezelter 507
385 gezelter 115 end subroutine do_lj_pair
386 gezelter 507
387 chuckv 492 subroutine destroyLJTypes()
388 gezelter 572
389     LJMap%nLJtypes = 0
390     LJMap%currentLJtype = 0
391    
392     if (associated(LJMap%LJtypes)) then
393     deallocate(LJMap%LJtypes)
394     LJMap%LJtypes => null()
395     end if
396    
397     if (associated(LJMap%atidToLJtype)) then
398     deallocate(LJMap%atidToLJtype)
399     LJMap%atidToLJtype => null()
400     end if
401    
402 chuckv 492 haveMixingMap = .false.
403 gezelter 938
404 chuckv 492 end subroutine destroyLJTypes
405    
406 gezelter 938 subroutine getLJfunc(r, myPot, myDeriv)
407    
408     real(kind=dp), intent(in) :: r
409     real(kind=dp), intent(inout) :: myPot, myDeriv
410     real(kind=dp) :: ri, ri2, ri6, ri7, ri12, ri13
411     real(kind=dp) :: a, b, c, d, dx
412     integer :: j
413    
414 chrisfen 942 ri = 1.0_DP / r
415     ri2 = ri*ri
416     ri6 = ri2*ri2*ri2
417     ri7 = ri6*ri
418     ri12 = ri6*ri6
419     ri13 = ri12*ri
420    
421     myPot = 4.0_DP * (ri12 - ri6)
422     myDeriv = 24.0_DP * (ri7 - 2.0_DP * ri13)
423    
424 gezelter 938 return
425     end subroutine getLJfunc
426    
427     subroutine getSoftFunc(r, myPot, myDeriv)
428    
429     real(kind=dp), intent(in) :: r
430     real(kind=dp), intent(inout) :: myPot, myDeriv
431     real(kind=dp) :: ri, ri2, ri6, ri7
432     real(kind=dp) :: a, b, c, d, dx
433     integer :: j
434    
435 chrisfen 942 ri = 1.0_DP / r
436     ri2 = ri*ri
437     ri6 = ri2*ri2*ri2
438     ri7 = ri6*ri
439     myPot = 4.0_DP * (ri6)
440     myDeriv = - 24.0_DP * ri7
441    
442 gezelter 938 return
443     end subroutine getSoftFunc
444    
445 gezelter 115 end module lj