ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/DarkSide/LJ.F90
Revision: 2086
Committed: Tue Mar 8 21:06:12 2005 UTC (19 years, 6 months ago) by gezelter
File size: 13096 byte(s)
Log Message:
electrostatic unification project
fixed an uninitialized variable in Lennard Jones mixing map

File Contents

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