ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-3.0/src/UseTheForce/doForces.F90
Revision: 2286
Committed: Wed Sep 7 22:08:39 2005 UTC (18 years, 10 months ago) by gezelter
File size: 42104 byte(s)
Log Message:
bugfix on the grouptype finding algorithm

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 gezelter 1610 !! doForces.F90
43     !! module doForces
44     !! Calculates Long Range forces.
45    
46     !! @author Charles F. Vardeman II
47     !! @author Matthew Meineke
48 gezelter 2286 !! @version $Id: doForces.F90,v 1.39 2005-09-07 22:08:39 gezelter Exp $, $Date: 2005-09-07 22:08:39 $, $Name: not supported by cvs2svn $, $Revision: 1.39 $
49 gezelter 1610
50 gezelter 1930
51 gezelter 1610 module doForces
52     use force_globals
53     use simulation
54     use definitions
55     use atype_module
56     use switcheroo
57     use neighborLists
58     use lj
59 gezelter 1930 use sticky
60 gezelter 2085 use electrostatic_module
61 gezelter 1610 use reaction_field
62     use gb_pair
63 chrisfen 1636 use shapes
64 gezelter 1610 use vector_class
65     use eam
66     use status
67     #ifdef IS_MPI
68     use mpiSimulation
69     #endif
70    
71     implicit none
72     PRIVATE
73    
74     #define __FORTRAN90
75     #include "UseTheForce/fSwitchingFunction.h"
76 gezelter 2273 #include "UseTheForce/fCutoffPolicy.h"
77 gezelter 2259 #include "UseTheForce/DarkSide/fInteractionMap.h"
78 gezelter 1610
79 gezelter 2273
80 gezelter 1610 INTEGER, PARAMETER:: PREPAIR_LOOP = 1
81     INTEGER, PARAMETER:: PAIR_LOOP = 2
82    
83     logical, save :: haveNeighborList = .false.
84     logical, save :: haveSIMvariables = .false.
85     logical, save :: haveSaneForceField = .false.
86 gezelter 2270 logical, save :: haveInteractionHash = .false.
87     logical, save :: haveGtypeCutoffMap = .false.
88 gezelter 2280 logical, save :: haveRlist = .false.
89 chrisfen 2229
90 gezelter 1634 logical, save :: FF_uses_DirectionalAtoms
91 gezelter 2085 logical, save :: FF_uses_Dipoles
92 gezelter 1634 logical, save :: FF_uses_GayBerne
93     logical, save :: FF_uses_EAM
94 gezelter 1610 logical, save :: FF_uses_RF
95 gezelter 1634
96     logical, save :: SIM_uses_DirectionalAtoms
97     logical, save :: SIM_uses_EAM
98 gezelter 1610 logical, save :: SIM_uses_RF
99     logical, save :: SIM_requires_postpair_calc
100     logical, save :: SIM_requires_prepair_calc
101     logical, save :: SIM_uses_PBC
102    
103 chrisfen 2279 integer, save :: corrMethod
104    
105 gezelter 1610 public :: init_FF
106 gezelter 2273 public :: setDefaultCutoffs
107 gezelter 1610 public :: do_force_loop
108 gezelter 2270 public :: createInteractionHash
109     public :: createGtypeCutoffMap
110 chrisfen 2277 public :: getStickyCut
111     public :: getStickyPowerCut
112     public :: getGayBerneCut
113     public :: getEAMCut
114     public :: getShapeCut
115 gezelter 1610
116     #ifdef PROFILE
117     public :: getforcetime
118     real, save :: forceTime = 0
119     real :: forceTimeInitial, forceTimeFinal
120     integer :: nLoops
121     #endif
122 chuckv 2260
123 gezelter 2270 !! Variables for cutoff mapping and interaction mapping
124     ! Bit hash to determine pair-pair interactions.
125     integer, dimension(:,:), allocatable :: InteractionHash
126     real(kind=dp), dimension(:), allocatable :: atypeMaxCutoff
127 chuckv 2269 real(kind=dp), dimension(:), allocatable :: groupMaxCutoff
128 gezelter 2270 integer, dimension(:), allocatable :: groupToGtype
129 chuckv 2269 real(kind=dp), dimension(:), allocatable :: gtypeMaxCutoff
130 gezelter 2270 type ::gtypeCutoffs
131     real(kind=dp) :: rcut
132     real(kind=dp) :: rcutsq
133     real(kind=dp) :: rlistsq
134     end type gtypeCutoffs
135     type(gtypeCutoffs), dimension(:,:), allocatable :: gtypeCutoffMap
136 gezelter 2273
137     integer, save :: cutoffPolicy = TRADITIONAL_CUTOFF_POLICY
138     real(kind=dp),save :: defaultRcut, defaultRsw, defaultRlist
139 gezelter 2261
140 gezelter 1610 contains
141    
142 gezelter 2270 subroutine createInteractionHash(status)
143 chuckv 2260 integer :: nAtypes
144 chuckv 2266 integer, intent(out) :: status
145 chuckv 2260 integer :: i
146     integer :: j
147 gezelter 2270 integer :: iHash
148 tim 2267 !! Test Types
149 chuckv 2260 logical :: i_is_LJ
150     logical :: i_is_Elect
151     logical :: i_is_Sticky
152     logical :: i_is_StickyP
153     logical :: i_is_GB
154     logical :: i_is_EAM
155     logical :: i_is_Shape
156     logical :: j_is_LJ
157     logical :: j_is_Elect
158     logical :: j_is_Sticky
159     logical :: j_is_StickyP
160     logical :: j_is_GB
161     logical :: j_is_EAM
162     logical :: j_is_Shape
163 gezelter 2275 real(kind=dp) :: myRcut
164    
165 gezelter 2268 status = 0
166    
167 chuckv 2260 if (.not. associated(atypes)) then
168 gezelter 2270 call handleError("atype", "atypes was not present before call of createInteractionHash!")
169 chuckv 2260 status = -1
170     return
171     endif
172    
173     nAtypes = getSize(atypes)
174    
175     if (nAtypes == 0) then
176     status = -1
177     return
178     end if
179 chrisfen 2229
180 chuckv 2269 if (.not. allocated(InteractionHash)) then
181     allocate(InteractionHash(nAtypes,nAtypes))
182 chuckv 2260 endif
183 gezelter 2270
184     if (.not. allocated(atypeMaxCutoff)) then
185     allocate(atypeMaxCutoff(nAtypes))
186     endif
187 chuckv 2260
188     do i = 1, nAtypes
189     call getElementProperty(atypes, i, "is_LennardJones", i_is_LJ)
190     call getElementProperty(atypes, i, "is_Electrostatic", i_is_Elect)
191     call getElementProperty(atypes, i, "is_Sticky", i_is_Sticky)
192     call getElementProperty(atypes, i, "is_StickyPower", i_is_StickyP)
193     call getElementProperty(atypes, i, "is_GayBerne", i_is_GB)
194     call getElementProperty(atypes, i, "is_EAM", i_is_EAM)
195     call getElementProperty(atypes, i, "is_Shape", i_is_Shape)
196 gezelter 1610
197 chuckv 2260 do j = i, nAtypes
198 chrisfen 2229
199 chuckv 2260 iHash = 0
200     myRcut = 0.0_dp
201 gezelter 1610
202 chuckv 2260 call getElementProperty(atypes, j, "is_LennardJones", j_is_LJ)
203     call getElementProperty(atypes, j, "is_Electrostatic", j_is_Elect)
204     call getElementProperty(atypes, j, "is_Sticky", j_is_Sticky)
205     call getElementProperty(atypes, j, "is_StickyPower", j_is_StickyP)
206     call getElementProperty(atypes, j, "is_GayBerne", j_is_GB)
207     call getElementProperty(atypes, j, "is_EAM", j_is_EAM)
208     call getElementProperty(atypes, j, "is_Shape", j_is_Shape)
209 gezelter 1610
210 chuckv 2260 if (i_is_LJ .and. j_is_LJ) then
211 gezelter 2261 iHash = ior(iHash, LJ_PAIR)
212     endif
213    
214     if (i_is_Elect .and. j_is_Elect) then
215     iHash = ior(iHash, ELECTROSTATIC_PAIR)
216     endif
217    
218     if (i_is_Sticky .and. j_is_Sticky) then
219     iHash = ior(iHash, STICKY_PAIR)
220     endif
221 chuckv 2260
222 gezelter 2261 if (i_is_StickyP .and. j_is_StickyP) then
223     iHash = ior(iHash, STICKYPOWER_PAIR)
224     endif
225 chuckv 2260
226 gezelter 2261 if (i_is_EAM .and. j_is_EAM) then
227     iHash = ior(iHash, EAM_PAIR)
228 chuckv 2260 endif
229    
230     if (i_is_GB .and. j_is_GB) iHash = ior(iHash, GAYBERNE_PAIR)
231     if (i_is_GB .and. j_is_LJ) iHash = ior(iHash, GAYBERNE_LJ)
232     if (i_is_LJ .and. j_is_GB) iHash = ior(iHash, GAYBERNE_LJ)
233    
234     if (i_is_Shape .and. j_is_Shape) iHash = ior(iHash, SHAPE_PAIR)
235     if (i_is_Shape .and. j_is_LJ) iHash = ior(iHash, SHAPE_LJ)
236     if (i_is_LJ .and. j_is_Shape) iHash = ior(iHash, SHAPE_LJ)
237    
238    
239 chuckv 2269 InteractionHash(i,j) = iHash
240     InteractionHash(j,i) = iHash
241 chuckv 2260
242     end do
243    
244     end do
245 tim 2267
246 gezelter 2270 haveInteractionHash = .true.
247     end subroutine createInteractionHash
248 chuckv 2260
249 gezelter 2275 subroutine createGtypeCutoffMap(stat)
250 gezelter 2268
251 gezelter 2275 integer, intent(out), optional :: stat
252 gezelter 2273 logical :: i_is_LJ
253     logical :: i_is_Elect
254     logical :: i_is_Sticky
255     logical :: i_is_StickyP
256     logical :: i_is_GB
257     logical :: i_is_EAM
258     logical :: i_is_Shape
259 gezelter 2286 logical :: GtypeFound
260 chuckv 2260
261 gezelter 2275 integer :: myStatus, nAtypes, i, j, istart, iend, jstart, jend
262 gezelter 2280 integer :: n_in_i, me_i, ia, g, atom1, nGroupTypes
263     real(kind=dp):: thisSigma, bigSigma, thisRcut, tol, skin
264 gezelter 2275 real(kind=dp) :: biggestAtypeCutoff
265 gezelter 2270
266 chuckv 2266 stat = 0
267 gezelter 2270 if (.not. haveInteractionHash) then
268     call createInteractionHash(myStatus)
269 chuckv 2266 if (myStatus .ne. 0) then
270 gezelter 2270 write(default_error, *) 'createInteractionHash failed in doForces!'
271 chuckv 2266 stat = -1
272     return
273     endif
274     endif
275    
276 chuckv 2262 nAtypes = getSize(atypes)
277 gezelter 2274
278 gezelter 2270 do i = 1, nAtypes
279 gezelter 2281 if (SimHasAtype(i)) then
280 gezelter 2274 call getElementProperty(atypes, i, "is_LennardJones", i_is_LJ)
281     call getElementProperty(atypes, i, "is_Electrostatic", i_is_Elect)
282     call getElementProperty(atypes, i, "is_Sticky", i_is_Sticky)
283     call getElementProperty(atypes, i, "is_StickyPower", i_is_StickyP)
284     call getElementProperty(atypes, i, "is_GayBerne", i_is_GB)
285     call getElementProperty(atypes, i, "is_EAM", i_is_EAM)
286     call getElementProperty(atypes, i, "is_Shape", i_is_Shape)
287    
288 gezelter 2281 atypeMaxCutoff(i) = 0.0_dp
289 gezelter 2274 if (i_is_LJ) then
290     thisRcut = getSigma(i) * 2.5_dp
291     if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
292     endif
293     if (i_is_Elect) then
294     thisRcut = defaultRcut
295     if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
296     endif
297     if (i_is_Sticky) then
298     thisRcut = getStickyCut(i)
299     if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
300     endif
301 gezelter 2275 if (i_is_StickyP) then
302 gezelter 2274 thisRcut = getStickyPowerCut(i)
303     if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
304     endif
305 gezelter 2275 if (i_is_GB) then
306 gezelter 2274 thisRcut = getGayBerneCut(i)
307     if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
308     endif
309     if (i_is_EAM) then
310     thisRcut = getEAMCut(i)
311     if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
312     endif
313     if (i_is_Shape) then
314     thisRcut = getShapeCut(i)
315     if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
316     endif
317    
318     if (atypeMaxCutoff(i).gt.biggestAtypeCutoff) then
319     biggestAtypeCutoff = atypeMaxCutoff(i)
320     endif
321 gezelter 2273 endif
322 gezelter 2274 enddo
323 gezelter 2280
324     nGroupTypes = 0
325    
326 gezelter 2274 istart = 1
327     #ifdef IS_MPI
328     iend = nGroupsInRow
329     #else
330     iend = nGroups
331     #endif
332 gezelter 2281
333 gezelter 2280 !! allocate the groupToGtype and gtypeMaxCutoff here.
334 chuckv 2282 if(.not.allocated(groupToGtype)) then
335     allocate(groupToGtype(iend))
336     allocate(groupMaxCutoff(iend))
337     allocate(gtypeMaxCutoff(iend))
338     endif
339 gezelter 2281 !! first we do a single loop over the cutoff groups to find the
340     !! largest cutoff for any atypes present in this group. We also
341     !! create gtypes at this point.
342    
343 gezelter 2280 tol = 1.0d-6
344    
345     do i = istart, iend
346 gezelter 2274 n_in_i = groupStartRow(i+1) - groupStartRow(i)
347 gezelter 2280 groupMaxCutoff(i) = 0.0_dp
348     do ia = groupStartRow(i), groupStartRow(i+1)-1
349     atom1 = groupListRow(ia)
350 gezelter 2274 #ifdef IS_MPI
351 gezelter 2280 me_i = atid_row(atom1)
352 gezelter 2274 #else
353 gezelter 2280 me_i = atid(atom1)
354     #endif
355     if (atypeMaxCutoff(me_i).gt.groupMaxCutoff(i)) then
356     groupMaxCutoff(i)=atypeMaxCutoff(me_i)
357 gezelter 2286 endif
358 gezelter 2280 enddo
359 gezelter 2286
360 gezelter 2280 if (nGroupTypes.eq.0) then
361     nGroupTypes = nGroupTypes + 1
362     gtypeMaxCutoff(nGroupTypes) = groupMaxCutoff(i)
363     groupToGtype(i) = nGroupTypes
364     else
365 gezelter 2286 GtypeFound = .false.
366 gezelter 2280 do g = 1, nGroupTypes
367 gezelter 2286 if ( abs(groupMaxCutoff(i) - gtypeMaxCutoff(g)).lt.tol) then
368 gezelter 2280 groupToGtype(i) = g
369 gezelter 2286 GtypeFound = .true.
370 gezelter 2280 endif
371     enddo
372 gezelter 2286 if (.not.GtypeFound) then
373     nGroupTypes = nGroupTypes + 1
374     gtypeMaxCutoff(nGroupTypes) = groupMaxCutoff(i)
375     groupToGtype(i) = nGroupTypes
376     endif
377 gezelter 2280 endif
378 gezelter 2286 enddo
379    
380 gezelter 2280 !! allocate the gtypeCutoffMap here.
381 chuckv 2282 allocate(gtypeCutoffMap(nGroupTypes,nGroupTypes))
382 gezelter 2280 !! then we do a double loop over all the group TYPES to find the cutoff
383     !! map between groups of two types
384    
385     do i = 1, nGroupTypes
386     do j = 1, nGroupTypes
387 gezelter 2275
388 gezelter 2280 select case(cutoffPolicy)
389 gezelter 2281 case(TRADITIONAL_CUTOFF_POLICY)
390     thisRcut = maxval(gtypeMaxCutoff)
391     case(MIX_CUTOFF_POLICY)
392     thisRcut = 0.5_dp * (gtypeMaxCutoff(i) + gtypeMaxCutoff(j))
393     case(MAX_CUTOFF_POLICY)
394     thisRcut = max(gtypeMaxCutoff(i), gtypeMaxCutoff(j))
395     case default
396     call handleError("createGtypeCutoffMap", "Unknown Cutoff Policy")
397     return
398     end select
399     gtypeCutoffMap(i,j)%rcut = thisRcut
400     gtypeCutoffMap(i,j)%rcutsq = thisRcut*thisRcut
401     skin = defaultRlist - defaultRcut
402     gtypeCutoffMap(i,j)%rlistsq = (thisRcut + skin)**2
403 gezelter 2284
404 gezelter 2280 enddo
405     enddo
406 gezelter 2275
407 gezelter 2280 haveGtypeCutoffMap = .true.
408 chuckv 2282
409 gezelter 2281 end subroutine createGtypeCutoffMap
410    
411     subroutine setDefaultCutoffs(defRcut, defRsw, defRlist, cutPolicy)
412     real(kind=dp),intent(in) :: defRcut, defRsw, defRlist
413     integer, intent(in) :: cutPolicy
414    
415     defaultRcut = defRcut
416     defaultRsw = defRsw
417     defaultRlist = defRlist
418     cutoffPolicy = cutPolicy
419     end subroutine setDefaultCutoffs
420    
421     subroutine setCutoffPolicy(cutPolicy)
422 chrisfen 2277
423 gezelter 2273 integer, intent(in) :: cutPolicy
424     cutoffPolicy = cutPolicy
425     call createGtypeCutoffMap()
426    
427 gezelter 2275 end subroutine setCutoffPolicy
428 gezelter 2273
429    
430 gezelter 1610 subroutine setSimVariables()
431 gezelter 1634 SIM_uses_DirectionalAtoms = SimUsesDirectionalAtoms()
432     SIM_uses_EAM = SimUsesEAM()
433 gezelter 1610 SIM_uses_RF = SimUsesRF()
434     SIM_requires_postpair_calc = SimRequiresPostpairCalc()
435     SIM_requires_prepair_calc = SimRequiresPrepairCalc()
436     SIM_uses_PBC = SimUsesPBC()
437    
438     haveSIMvariables = .true.
439    
440     return
441     end subroutine setSimVariables
442    
443     subroutine doReadyCheck(error)
444     integer, intent(out) :: error
445    
446     integer :: myStatus
447    
448     error = 0
449 chrisfen 2229
450 gezelter 2270 if (.not. haveInteractionHash) then
451 gezelter 2268 myStatus = 0
452 gezelter 2270 call createInteractionHash(myStatus)
453 gezelter 1610 if (myStatus .ne. 0) then
454 gezelter 2270 write(default_error, *) 'createInteractionHash failed in doForces!'
455 gezelter 1610 error = -1
456     return
457     endif
458     endif
459    
460 gezelter 2270 if (.not. haveGtypeCutoffMap) then
461     myStatus = 0
462     call createGtypeCutoffMap(myStatus)
463     if (myStatus .ne. 0) then
464     write(default_error, *) 'createGtypeCutoffMap failed in doForces!'
465     error = -1
466     return
467     endif
468     endif
469    
470 gezelter 1610 if (.not. haveSIMvariables) then
471     call setSimVariables()
472     endif
473    
474 chuckv 2282 ! if (.not. haveRlist) then
475     ! write(default_error, *) 'rList has not been set in doForces!'
476     ! error = -1
477     ! return
478     ! endif
479 gezelter 1610
480     if (.not. haveNeighborList) then
481     write(default_error, *) 'neighbor list has not been initialized in doForces!'
482     error = -1
483     return
484     end if
485    
486     if (.not. haveSaneForceField) then
487     write(default_error, *) 'Force Field is not sane in doForces!'
488     error = -1
489     return
490     end if
491    
492     #ifdef IS_MPI
493     if (.not. isMPISimSet()) then
494     write(default_error,*) "ERROR: mpiSimulation has not been initialized!"
495     error = -1
496     return
497     endif
498     #endif
499     return
500     end subroutine doReadyCheck
501    
502 chrisfen 2229
503 gezelter 2280 subroutine init_FF(use_RF, use_UW, use_DW, thisStat)
504 gezelter 1610
505 gezelter 2280 logical, intent(in) :: use_RF
506     logical, intent(in) :: use_UW
507     logical, intent(in) :: use_DW
508 gezelter 1610 integer, intent(out) :: thisStat
509     integer :: my_status, nMatches
510 chrisfen 2279 integer :: corrMethod
511 gezelter 1610 integer, pointer :: MatchList(:) => null()
512     real(kind=dp) :: rcut, rrf, rt, dielect
513    
514     !! assume things are copacetic, unless they aren't
515     thisStat = 0
516    
517     !! Fortran's version of a cast:
518 gezelter 2280 FF_uses_RF = use_RF
519 chrisfen 2229
520 chrisfen 2279 !! set the electrostatic correction method
521 gezelter 2280 if (use_UW) then
522 chrisfen 2279 corrMethod = 1
523 gezelter 2280 elseif (use_DW) then
524 chrisfen 2279 corrMethod = 2
525     else
526     corrMethod = 0
527     endif
528    
529 gezelter 1610 !! init_FF is called *after* all of the atom types have been
530     !! defined in atype_module using the new_atype subroutine.
531     !!
532     !! this will scan through the known atypes and figure out what
533     !! interactions are used by the force field.
534 chrisfen 2229
535 gezelter 1634 FF_uses_DirectionalAtoms = .false.
536     FF_uses_Dipoles = .false.
537     FF_uses_GayBerne = .false.
538 gezelter 1610 FF_uses_EAM = .false.
539 chrisfen 2229
540 gezelter 1634 call getMatchingElementList(atypes, "is_Directional", .true., &
541     nMatches, MatchList)
542     if (nMatches .gt. 0) FF_uses_DirectionalAtoms = .true.
543    
544     call getMatchingElementList(atypes, "is_Dipole", .true., &
545     nMatches, MatchList)
546 gezelter 2270 if (nMatches .gt. 0) FF_uses_Dipoles = .true.
547 chrisfen 2220
548 gezelter 1634 call getMatchingElementList(atypes, "is_GayBerne", .true., &
549     nMatches, MatchList)
550 gezelter 2270 if (nMatches .gt. 0) FF_uses_GayBerne = .true.
551 chrisfen 2229
552 gezelter 1610 call getMatchingElementList(atypes, "is_EAM", .true., nMatches, MatchList)
553     if (nMatches .gt. 0) FF_uses_EAM = .true.
554 chrisfen 2229
555 gezelter 1634
556 gezelter 1610 haveSaneForceField = .true.
557 chrisfen 2229
558 gezelter 1610 !! check to make sure the FF_uses_RF setting makes sense
559 chrisfen 2229
560 gezelter 2270 if (FF_uses_Dipoles) then
561 gezelter 1610 if (FF_uses_RF) then
562     dielect = getDielect()
563     call initialize_rf(dielect)
564     endif
565     else
566     if (FF_uses_RF) then
567     write(default_error,*) 'Using Reaction Field with no dipoles? Huh?'
568     thisStat = -1
569     haveSaneForceField = .false.
570     return
571     endif
572 chrisfen 2229 endif
573 gezelter 1610
574     if (FF_uses_EAM) then
575 chrisfen 2229 call init_EAM_FF(my_status)
576 gezelter 1610 if (my_status /= 0) then
577     write(default_error, *) "init_EAM_FF returned a bad status"
578     thisStat = -1
579     haveSaneForceField = .false.
580     return
581     end if
582     endif
583    
584 gezelter 1634 if (FF_uses_GayBerne) then
585 gezelter 1610 call check_gb_pair_FF(my_status)
586     if (my_status .ne. 0) then
587     thisStat = -1
588     haveSaneForceField = .false.
589     return
590     endif
591     endif
592    
593     if (.not. haveNeighborList) then
594     !! Create neighbor lists
595     call expandNeighborList(nLocal, my_status)
596     if (my_Status /= 0) then
597     write(default_error,*) "SimSetup: ExpandNeighborList returned error."
598     thisStat = -1
599     return
600     endif
601     haveNeighborList = .true.
602 chrisfen 2229 endif
603    
604 gezelter 1610 end subroutine init_FF
605    
606 chrisfen 2229
607 gezelter 1610 !! Does force loop over i,j pairs. Calls do_pair to calculates forces.
608     !------------------------------------------------------------->
609 gezelter 1930 subroutine do_force_loop(q, q_group, A, eFrame, f, t, tau, pot, &
610 gezelter 1610 do_pot_c, do_stress_c, error)
611     !! Position array provided by C, dimensioned by getNlocal
612     real ( kind = dp ), dimension(3, nLocal) :: q
613     !! molecular center-of-mass position array
614     real ( kind = dp ), dimension(3, nGroups) :: q_group
615     !! Rotation Matrix for each long range particle in simulation.
616     real( kind = dp), dimension(9, nLocal) :: A
617     !! Unit vectors for dipoles (lab frame)
618 gezelter 1930 real( kind = dp ), dimension(9,nLocal) :: eFrame
619 gezelter 1610 !! Force array provided by C, dimensioned by getNlocal
620     real ( kind = dp ), dimension(3,nLocal) :: f
621     !! Torsion array provided by C, dimensioned by getNlocal
622     real( kind = dp ), dimension(3,nLocal) :: t
623    
624     !! Stress Tensor
625     real( kind = dp), dimension(9) :: tau
626     real ( kind = dp ) :: pot
627     logical ( kind = 2) :: do_pot_c, do_stress_c
628     logical :: do_pot
629     logical :: do_stress
630     logical :: in_switching_region
631     #ifdef IS_MPI
632     real( kind = DP ) :: pot_local
633     integer :: nAtomsInRow
634     integer :: nAtomsInCol
635     integer :: nprocs
636     integer :: nGroupsInRow
637     integer :: nGroupsInCol
638     #endif
639     integer :: natoms
640     logical :: update_nlist
641     integer :: i, j, jstart, jend, jnab
642     integer :: istart, iend
643     integer :: ia, jb, atom1, atom2
644     integer :: nlist
645     real( kind = DP ) :: ratmsq, rgrpsq, rgrp, vpair, vij
646     real( kind = DP ) :: sw, dswdr, swderiv, mf
647     real(kind=dp),dimension(3) :: d_atm, d_grp, fpair, fij
648     real(kind=dp) :: rfpot, mu_i, virial
649     integer :: me_i, me_j, n_in_i, n_in_j
650     logical :: is_dp_i
651     integer :: neighborListSize
652     integer :: listerror, error
653     integer :: localError
654     integer :: propPack_i, propPack_j
655     integer :: loopStart, loopEnd, loop
656 gezelter 2270 integer :: iHash
657 gezelter 1610 real(kind=dp) :: listSkin = 1.0
658 chrisfen 2229
659 gezelter 1610 !! initialize local variables
660 chrisfen 2229
661 gezelter 1610 #ifdef IS_MPI
662     pot_local = 0.0_dp
663     nAtomsInRow = getNatomsInRow(plan_atom_row)
664     nAtomsInCol = getNatomsInCol(plan_atom_col)
665     nGroupsInRow = getNgroupsInRow(plan_group_row)
666     nGroupsInCol = getNgroupsInCol(plan_group_col)
667     #else
668     natoms = nlocal
669     #endif
670 chrisfen 2229
671 gezelter 1610 call doReadyCheck(localError)
672     if ( localError .ne. 0 ) then
673     call handleError("do_force_loop", "Not Initialized")
674     error = -1
675     return
676     end if
677     call zero_work_arrays()
678 chrisfen 2229
679 gezelter 1610 do_pot = do_pot_c
680     do_stress = do_stress_c
681 chrisfen 2229
682 gezelter 1610 ! Gather all information needed by all force loops:
683 chrisfen 2229
684 gezelter 1610 #ifdef IS_MPI
685 chrisfen 2229
686 gezelter 1610 call gather(q, q_Row, plan_atom_row_3d)
687     call gather(q, q_Col, plan_atom_col_3d)
688    
689     call gather(q_group, q_group_Row, plan_group_row_3d)
690     call gather(q_group, q_group_Col, plan_group_col_3d)
691 chrisfen 2229
692 gezelter 1634 if (FF_UsesDirectionalAtoms() .and. SIM_uses_DirectionalAtoms) then
693 gezelter 1930 call gather(eFrame, eFrame_Row, plan_atom_row_rotation)
694     call gather(eFrame, eFrame_Col, plan_atom_col_rotation)
695 chrisfen 2229
696 gezelter 1610 call gather(A, A_Row, plan_atom_row_rotation)
697     call gather(A, A_Col, plan_atom_col_rotation)
698     endif
699 chrisfen 2229
700 gezelter 1610 #endif
701 chrisfen 2229
702 gezelter 1610 !! Begin force loop timing:
703     #ifdef PROFILE
704     call cpu_time(forceTimeInitial)
705     nloops = nloops + 1
706     #endif
707 chrisfen 2229
708 gezelter 1610 loopEnd = PAIR_LOOP
709     if (FF_RequiresPrepairCalc() .and. SIM_requires_prepair_calc) then
710     loopStart = PREPAIR_LOOP
711     else
712     loopStart = PAIR_LOOP
713     endif
714    
715     do loop = loopStart, loopEnd
716    
717     ! See if we need to update neighbor lists
718     ! (but only on the first time through):
719     if (loop .eq. loopStart) then
720     #ifdef IS_MPI
721     call checkNeighborList(nGroupsInRow, q_group_row, listSkin, &
722 chrisfen 2229 update_nlist)
723 gezelter 1610 #else
724     call checkNeighborList(nGroups, q_group, listSkin, &
725 chrisfen 2229 update_nlist)
726 gezelter 1610 #endif
727     endif
728 chrisfen 2229
729 gezelter 1610 if (update_nlist) then
730     !! save current configuration and construct neighbor list
731     #ifdef IS_MPI
732     call saveNeighborList(nGroupsInRow, q_group_row)
733     #else
734     call saveNeighborList(nGroups, q_group)
735     #endif
736     neighborListSize = size(list)
737     nlist = 0
738     endif
739 chrisfen 2229
740 gezelter 1610 istart = 1
741     #ifdef IS_MPI
742     iend = nGroupsInRow
743     #else
744     iend = nGroups - 1
745     #endif
746     outer: do i = istart, iend
747    
748     if (update_nlist) point(i) = nlist + 1
749 chrisfen 2229
750 gezelter 1610 n_in_i = groupStartRow(i+1) - groupStartRow(i)
751 chrisfen 2229
752 gezelter 1610 if (update_nlist) then
753     #ifdef IS_MPI
754     jstart = 1
755     jend = nGroupsInCol
756     #else
757     jstart = i+1
758     jend = nGroups
759     #endif
760     else
761     jstart = point(i)
762     jend = point(i+1) - 1
763     ! make sure group i has neighbors
764     if (jstart .gt. jend) cycle outer
765     endif
766 chrisfen 2229
767 gezelter 1610 do jnab = jstart, jend
768     if (update_nlist) then
769     j = jnab
770     else
771     j = list(jnab)
772     endif
773    
774     #ifdef IS_MPI
775 chuckv 2266 me_j = atid_col(j)
776 gezelter 1610 call get_interatomic_vector(q_group_Row(:,i), &
777     q_group_Col(:,j), d_grp, rgrpsq)
778     #else
779 chuckv 2266 me_j = atid(j)
780 gezelter 1610 call get_interatomic_vector(q_group(:,i), &
781     q_group(:,j), d_grp, rgrpsq)
782     #endif
783    
784 gezelter 2280 if (rgrpsq < gtypeCutoffMap(groupToGtype(i),groupToGtype(j))%rListsq) then
785 gezelter 1610 if (update_nlist) then
786     nlist = nlist + 1
787 chrisfen 2229
788 gezelter 1610 if (nlist > neighborListSize) then
789     #ifdef IS_MPI
790     call expandNeighborList(nGroupsInRow, listerror)
791     #else
792     call expandNeighborList(nGroups, listerror)
793     #endif
794     if (listerror /= 0) then
795     error = -1
796     write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
797     return
798     end if
799     neighborListSize = size(list)
800     endif
801 chrisfen 2229
802 gezelter 1610 list(nlist) = j
803     endif
804 chrisfen 2229
805 gezelter 1610 if (loop .eq. PAIR_LOOP) then
806     vij = 0.0d0
807     fij(1:3) = 0.0d0
808     endif
809 chrisfen 2229
810 gezelter 1610 call get_switch(rgrpsq, sw, dswdr, rgrp, group_switch, &
811     in_switching_region)
812 chrisfen 2229
813 gezelter 1610 n_in_j = groupStartCol(j+1) - groupStartCol(j)
814 chrisfen 2229
815 gezelter 1610 do ia = groupStartRow(i), groupStartRow(i+1)-1
816 chrisfen 2229
817 gezelter 1610 atom1 = groupListRow(ia)
818 chrisfen 2229
819 gezelter 1610 inner: do jb = groupStartCol(j), groupStartCol(j+1)-1
820 chrisfen 2229
821 gezelter 1610 atom2 = groupListCol(jb)
822 chrisfen 2229
823 gezelter 1610 if (skipThisPair(atom1, atom2)) cycle inner
824    
825     if ((n_in_i .eq. 1).and.(n_in_j .eq. 1)) then
826     d_atm(1:3) = d_grp(1:3)
827     ratmsq = rgrpsq
828     else
829     #ifdef IS_MPI
830     call get_interatomic_vector(q_Row(:,atom1), &
831     q_Col(:,atom2), d_atm, ratmsq)
832     #else
833     call get_interatomic_vector(q(:,atom1), &
834     q(:,atom2), d_atm, ratmsq)
835     #endif
836     endif
837    
838     if (loop .eq. PREPAIR_LOOP) then
839     #ifdef IS_MPI
840     call do_prepair(atom1, atom2, ratmsq, d_atm, sw, &
841     rgrpsq, d_grp, do_pot, do_stress, &
842 gezelter 1930 eFrame, A, f, t, pot_local)
843 gezelter 1610 #else
844     call do_prepair(atom1, atom2, ratmsq, d_atm, sw, &
845     rgrpsq, d_grp, do_pot, do_stress, &
846 gezelter 1930 eFrame, A, f, t, pot)
847 gezelter 1610 #endif
848     else
849     #ifdef IS_MPI
850     call do_pair(atom1, atom2, ratmsq, d_atm, sw, &
851     do_pot, &
852 gezelter 1930 eFrame, A, f, t, pot_local, vpair, fpair)
853 gezelter 1610 #else
854     call do_pair(atom1, atom2, ratmsq, d_atm, sw, &
855     do_pot, &
856 gezelter 1930 eFrame, A, f, t, pot, vpair, fpair)
857 gezelter 1610 #endif
858    
859     vij = vij + vpair
860     fij(1:3) = fij(1:3) + fpair(1:3)
861     endif
862     enddo inner
863     enddo
864 chrisfen 2229
865 gezelter 1610 if (loop .eq. PAIR_LOOP) then
866     if (in_switching_region) then
867     swderiv = vij*dswdr/rgrp
868     fij(1) = fij(1) + swderiv*d_grp(1)
869     fij(2) = fij(2) + swderiv*d_grp(2)
870     fij(3) = fij(3) + swderiv*d_grp(3)
871 chrisfen 2229
872 gezelter 1610 do ia=groupStartRow(i), groupStartRow(i+1)-1
873     atom1=groupListRow(ia)
874     mf = mfactRow(atom1)
875     #ifdef IS_MPI
876     f_Row(1,atom1) = f_Row(1,atom1) + swderiv*d_grp(1)*mf
877     f_Row(2,atom1) = f_Row(2,atom1) + swderiv*d_grp(2)*mf
878     f_Row(3,atom1) = f_Row(3,atom1) + swderiv*d_grp(3)*mf
879     #else
880     f(1,atom1) = f(1,atom1) + swderiv*d_grp(1)*mf
881     f(2,atom1) = f(2,atom1) + swderiv*d_grp(2)*mf
882     f(3,atom1) = f(3,atom1) + swderiv*d_grp(3)*mf
883     #endif
884     enddo
885 chrisfen 2229
886 gezelter 1610 do jb=groupStartCol(j), groupStartCol(j+1)-1
887     atom2=groupListCol(jb)
888     mf = mfactCol(atom2)
889     #ifdef IS_MPI
890     f_Col(1,atom2) = f_Col(1,atom2) - swderiv*d_grp(1)*mf
891     f_Col(2,atom2) = f_Col(2,atom2) - swderiv*d_grp(2)*mf
892     f_Col(3,atom2) = f_Col(3,atom2) - swderiv*d_grp(3)*mf
893     #else
894     f(1,atom2) = f(1,atom2) - swderiv*d_grp(1)*mf
895     f(2,atom2) = f(2,atom2) - swderiv*d_grp(2)*mf
896     f(3,atom2) = f(3,atom2) - swderiv*d_grp(3)*mf
897     #endif
898     enddo
899     endif
900 chrisfen 2229
901 gezelter 1610 if (do_stress) call add_stress_tensor(d_grp, fij)
902     endif
903     end if
904     enddo
905     enddo outer
906 chrisfen 2229
907 gezelter 1610 if (update_nlist) then
908     #ifdef IS_MPI
909     point(nGroupsInRow + 1) = nlist + 1
910     #else
911     point(nGroups) = nlist + 1
912     #endif
913     if (loop .eq. PREPAIR_LOOP) then
914     ! we just did the neighbor list update on the first
915     ! pass, so we don't need to do it
916     ! again on the second pass
917     update_nlist = .false.
918     endif
919     endif
920 chrisfen 2229
921 gezelter 1610 if (loop .eq. PREPAIR_LOOP) then
922     call do_preforce(nlocal, pot)
923     endif
924 chrisfen 2229
925 gezelter 1610 enddo
926 chrisfen 2229
927 gezelter 1610 !! Do timing
928     #ifdef PROFILE
929     call cpu_time(forceTimeFinal)
930     forceTime = forceTime + forceTimeFinal - forceTimeInitial
931     #endif
932 chrisfen 2229
933 gezelter 1610 #ifdef IS_MPI
934     !!distribute forces
935 chrisfen 2229
936 gezelter 1610 f_temp = 0.0_dp
937     call scatter(f_Row,f_temp,plan_atom_row_3d)
938     do i = 1,nlocal
939     f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
940     end do
941 chrisfen 2229
942 gezelter 1610 f_temp = 0.0_dp
943     call scatter(f_Col,f_temp,plan_atom_col_3d)
944     do i = 1,nlocal
945     f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
946     end do
947 chrisfen 2229
948 gezelter 1634 if (FF_UsesDirectionalAtoms() .and. SIM_uses_DirectionalAtoms) then
949 gezelter 1610 t_temp = 0.0_dp
950     call scatter(t_Row,t_temp,plan_atom_row_3d)
951     do i = 1,nlocal
952     t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
953     end do
954     t_temp = 0.0_dp
955     call scatter(t_Col,t_temp,plan_atom_col_3d)
956 chrisfen 2229
957 gezelter 1610 do i = 1,nlocal
958     t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
959     end do
960     endif
961 chrisfen 2229
962 gezelter 1610 if (do_pot) then
963     ! scatter/gather pot_row into the members of my column
964     call scatter(pot_Row, pot_Temp, plan_atom_row)
965 chrisfen 2229
966 gezelter 1610 ! scatter/gather pot_local into all other procs
967     ! add resultant to get total pot
968     do i = 1, nlocal
969     pot_local = pot_local + pot_Temp(i)
970     enddo
971 chrisfen 2229
972 gezelter 1610 pot_Temp = 0.0_DP
973 chrisfen 2229
974 gezelter 1610 call scatter(pot_Col, pot_Temp, plan_atom_col)
975     do i = 1, nlocal
976     pot_local = pot_local + pot_Temp(i)
977     enddo
978 chrisfen 2229
979 gezelter 1610 endif
980     #endif
981 chrisfen 2229
982 gezelter 1610 if (FF_RequiresPostpairCalc() .and. SIM_requires_postpair_calc) then
983 chrisfen 2229
984 gezelter 1610 if (FF_uses_RF .and. SIM_uses_RF) then
985 chrisfen 2229
986 gezelter 1610 #ifdef IS_MPI
987     call scatter(rf_Row,rf,plan_atom_row_3d)
988     call scatter(rf_Col,rf_Temp,plan_atom_col_3d)
989     do i = 1,nlocal
990     rf(1:3,i) = rf(1:3,i) + rf_Temp(1:3,i)
991     end do
992     #endif
993 chrisfen 2229
994 gezelter 1610 do i = 1, nLocal
995 chrisfen 2229
996 gezelter 1610 rfpot = 0.0_DP
997     #ifdef IS_MPI
998     me_i = atid_row(i)
999     #else
1000     me_i = atid(i)
1001     #endif
1002 gezelter 2270 iHash = InteractionHash(me_i,me_j)
1003 gezelter 2261
1004 gezelter 2270 if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then
1005 chrisfen 2229
1006 gezelter 1634 mu_i = getDipoleMoment(me_i)
1007 chrisfen 2229
1008 gezelter 1610 !! The reaction field needs to include a self contribution
1009     !! to the field:
1010 gezelter 1930 call accumulate_self_rf(i, mu_i, eFrame)
1011 gezelter 1610 !! Get the reaction field contribution to the
1012     !! potential and torques:
1013 gezelter 1930 call reaction_field_final(i, mu_i, eFrame, rfpot, t, do_pot)
1014 gezelter 1610 #ifdef IS_MPI
1015     pot_local = pot_local + rfpot
1016     #else
1017     pot = pot + rfpot
1018 chrisfen 2229
1019 gezelter 1610 #endif
1020 chrisfen 2229 endif
1021 gezelter 1610 enddo
1022     endif
1023     endif
1024 chrisfen 2229
1025    
1026 gezelter 1610 #ifdef IS_MPI
1027 chrisfen 2229
1028 gezelter 1610 if (do_pot) then
1029     pot = pot + pot_local
1030     !! we assume the c code will do the allreduce to get the total potential
1031     !! we could do it right here if we needed to...
1032     endif
1033 chrisfen 2229
1034 gezelter 1610 if (do_stress) then
1035     call mpi_allreduce(tau_Temp, tau, 9,mpi_double_precision,mpi_sum, &
1036     mpi_comm_world,mpi_err)
1037     call mpi_allreduce(virial_Temp, virial,1,mpi_double_precision,mpi_sum, &
1038     mpi_comm_world,mpi_err)
1039     endif
1040 chrisfen 2229
1041 gezelter 1610 #else
1042 chrisfen 2229
1043 gezelter 1610 if (do_stress) then
1044     tau = tau_Temp
1045     virial = virial_Temp
1046     endif
1047 chrisfen 2229
1048 gezelter 1610 #endif
1049 chrisfen 2229
1050 gezelter 1610 end subroutine do_force_loop
1051 chrisfen 2229
1052 gezelter 1610 subroutine do_pair(i, j, rijsq, d, sw, do_pot, &
1053 gezelter 1930 eFrame, A, f, t, pot, vpair, fpair)
1054 gezelter 1610
1055     real( kind = dp ) :: pot, vpair, sw
1056     real( kind = dp ), dimension(3) :: fpair
1057     real( kind = dp ), dimension(nLocal) :: mfact
1058 gezelter 1930 real( kind = dp ), dimension(9,nLocal) :: eFrame
1059 gezelter 1610 real( kind = dp ), dimension(9,nLocal) :: A
1060     real( kind = dp ), dimension(3,nLocal) :: f
1061     real( kind = dp ), dimension(3,nLocal) :: t
1062    
1063     logical, intent(inout) :: do_pot
1064     integer, intent(in) :: i, j
1065     real ( kind = dp ), intent(inout) :: rijsq
1066     real ( kind = dp ) :: r
1067     real ( kind = dp ), intent(inout) :: d(3)
1068 chrisfen 2231 real ( kind = dp ) :: ebalance
1069 gezelter 1610 integer :: me_i, me_j
1070    
1071 gezelter 2270 integer :: iHash
1072 gezelter 2259
1073 gezelter 1610 r = sqrt(rijsq)
1074     vpair = 0.0d0
1075     fpair(1:3) = 0.0d0
1076    
1077     #ifdef IS_MPI
1078     me_i = atid_row(i)
1079     me_j = atid_col(j)
1080     #else
1081     me_i = atid(i)
1082     me_j = atid(j)
1083     #endif
1084 gezelter 1706
1085 gezelter 2270 iHash = InteractionHash(me_i, me_j)
1086 chrisfen 2229
1087 gezelter 2270 if ( iand(iHash, LJ_PAIR).ne.0 ) then
1088 gezelter 2259 call do_lj_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot)
1089 gezelter 1610 endif
1090 chrisfen 2229
1091 gezelter 2270 if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then
1092 gezelter 2259 call doElectrostaticPair(i, j, d, r, rijsq, sw, vpair, fpair, &
1093 chrisfen 2279 pot, eFrame, f, t, do_pot, corrMethod)
1094 chrisfen 2229
1095 gezelter 2261 if (FF_uses_RF .and. SIM_uses_RF) then
1096    
1097     ! CHECK ME (RF needs to know about all electrostatic types)
1098     call accumulate_rf(i, j, r, eFrame, sw)
1099     call rf_correct_forces(i, j, d, r, eFrame, sw, f, fpair)
1100 gezelter 1610 endif
1101 gezelter 2261
1102 gezelter 1610 endif
1103    
1104 gezelter 2270 if ( iand(iHash, STICKY_PAIR).ne.0 ) then
1105 gezelter 2259 call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1106     pot, A, f, t, do_pot)
1107     endif
1108 gezelter 2085
1109 gezelter 2270 if ( iand(iHash, STICKYPOWER_PAIR).ne.0 ) then
1110 gezelter 2259 call do_sticky_power_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1111     pot, A, f, t, do_pot)
1112 gezelter 1610 endif
1113    
1114 gezelter 2270 if ( iand(iHash, GAYBERNE_PAIR).ne.0 ) then
1115 gezelter 2259 call do_gb_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1116     pot, A, f, t, do_pot)
1117 chrisfen 2229 endif
1118    
1119 gezelter 2270 if ( iand(iHash, GAYBERNE_LJ).ne.0 ) then
1120 chuckv 2262 ! call do_gblj_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1121     ! pot, A, f, t, do_pot)
1122 gezelter 2259 endif
1123 kdaily 2226
1124 gezelter 2270 if ( iand(iHash, EAM_PAIR).ne.0 ) then
1125 gezelter 2259 call do_eam_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, &
1126     do_pot)
1127 gezelter 1610 endif
1128 chrisfen 2229
1129 gezelter 2270 if ( iand(iHash, SHAPE_PAIR).ne.0 ) then
1130 gezelter 2259 call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1131     pot, A, f, t, do_pot)
1132 gezelter 1610 endif
1133 gezelter 1634
1134 gezelter 2270 if ( iand(iHash, SHAPE_LJ).ne.0 ) then
1135 gezelter 2259 call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1136     pot, A, f, t, do_pot)
1137 gezelter 1634 endif
1138 gezelter 2259
1139 gezelter 1610 end subroutine do_pair
1140    
1141     subroutine do_prepair(i, j, rijsq, d, sw, rcijsq, dc, &
1142 gezelter 1930 do_pot, do_stress, eFrame, A, f, t, pot)
1143 gezelter 1610
1144 chrisfen 2229 real( kind = dp ) :: pot, sw
1145     real( kind = dp ), dimension(9,nLocal) :: eFrame
1146     real (kind=dp), dimension(9,nLocal) :: A
1147     real (kind=dp), dimension(3,nLocal) :: f
1148     real (kind=dp), dimension(3,nLocal) :: t
1149 gezelter 1610
1150 chrisfen 2229 logical, intent(inout) :: do_pot, do_stress
1151     integer, intent(in) :: i, j
1152     real ( kind = dp ), intent(inout) :: rijsq, rcijsq
1153     real ( kind = dp ) :: r, rc
1154     real ( kind = dp ), intent(inout) :: d(3), dc(3)
1155    
1156 gezelter 2270 integer :: me_i, me_j, iHash
1157 chrisfen 2229
1158 gezelter 1610 #ifdef IS_MPI
1159 chrisfen 2229 me_i = atid_row(i)
1160     me_j = atid_col(j)
1161 gezelter 1610 #else
1162 chrisfen 2229 me_i = atid(i)
1163     me_j = atid(j)
1164 gezelter 1610 #endif
1165 chrisfen 2229
1166 gezelter 2270 iHash = InteractionHash(me_i, me_j)
1167 chrisfen 2229
1168 gezelter 2270 if ( iand(iHash, EAM_PAIR).ne.0 ) then
1169 chrisfen 2229 call calc_EAM_prepair_rho(i, j, d, r, rijsq )
1170     endif
1171 gezelter 2259
1172 chrisfen 2229 end subroutine do_prepair
1173    
1174    
1175     subroutine do_preforce(nlocal,pot)
1176     integer :: nlocal
1177     real( kind = dp ) :: pot
1178    
1179     if (FF_uses_EAM .and. SIM_uses_EAM) then
1180     call calc_EAM_preforce_Frho(nlocal,pot)
1181     endif
1182    
1183    
1184     end subroutine do_preforce
1185    
1186    
1187     subroutine get_interatomic_vector(q_i, q_j, d, r_sq)
1188    
1189     real (kind = dp), dimension(3) :: q_i
1190     real (kind = dp), dimension(3) :: q_j
1191     real ( kind = dp ), intent(out) :: r_sq
1192     real( kind = dp ) :: d(3), scaled(3)
1193     integer i
1194    
1195     d(1:3) = q_j(1:3) - q_i(1:3)
1196    
1197     ! Wrap back into periodic box if necessary
1198     if ( SIM_uses_PBC ) then
1199    
1200     if( .not.boxIsOrthorhombic ) then
1201     ! calc the scaled coordinates.
1202    
1203     scaled = matmul(HmatInv, d)
1204    
1205     ! wrap the scaled coordinates
1206    
1207     scaled = scaled - anint(scaled)
1208    
1209    
1210     ! calc the wrapped real coordinates from the wrapped scaled
1211     ! coordinates
1212    
1213     d = matmul(Hmat,scaled)
1214    
1215     else
1216     ! calc the scaled coordinates.
1217    
1218     do i = 1, 3
1219     scaled(i) = d(i) * HmatInv(i,i)
1220    
1221     ! wrap the scaled coordinates
1222    
1223     scaled(i) = scaled(i) - anint(scaled(i))
1224    
1225     ! calc the wrapped real coordinates from the wrapped scaled
1226     ! coordinates
1227    
1228     d(i) = scaled(i)*Hmat(i,i)
1229     enddo
1230     endif
1231    
1232     endif
1233    
1234     r_sq = dot_product(d,d)
1235    
1236     end subroutine get_interatomic_vector
1237    
1238     subroutine zero_work_arrays()
1239    
1240 gezelter 1610 #ifdef IS_MPI
1241    
1242 chrisfen 2229 q_Row = 0.0_dp
1243     q_Col = 0.0_dp
1244    
1245     q_group_Row = 0.0_dp
1246     q_group_Col = 0.0_dp
1247    
1248     eFrame_Row = 0.0_dp
1249     eFrame_Col = 0.0_dp
1250    
1251     A_Row = 0.0_dp
1252     A_Col = 0.0_dp
1253    
1254     f_Row = 0.0_dp
1255     f_Col = 0.0_dp
1256     f_Temp = 0.0_dp
1257    
1258     t_Row = 0.0_dp
1259     t_Col = 0.0_dp
1260     t_Temp = 0.0_dp
1261    
1262     pot_Row = 0.0_dp
1263     pot_Col = 0.0_dp
1264     pot_Temp = 0.0_dp
1265    
1266     rf_Row = 0.0_dp
1267     rf_Col = 0.0_dp
1268     rf_Temp = 0.0_dp
1269    
1270 gezelter 1610 #endif
1271 chrisfen 2229
1272     if (FF_uses_EAM .and. SIM_uses_EAM) then
1273     call clean_EAM()
1274     endif
1275    
1276     rf = 0.0_dp
1277     tau_Temp = 0.0_dp
1278     virial_Temp = 0.0_dp
1279     end subroutine zero_work_arrays
1280    
1281     function skipThisPair(atom1, atom2) result(skip_it)
1282     integer, intent(in) :: atom1
1283     integer, intent(in), optional :: atom2
1284     logical :: skip_it
1285     integer :: unique_id_1, unique_id_2
1286     integer :: me_i,me_j
1287     integer :: i
1288    
1289     skip_it = .false.
1290    
1291     !! there are a number of reasons to skip a pair or a particle
1292     !! mostly we do this to exclude atoms who are involved in short
1293     !! range interactions (bonds, bends, torsions), but we also need
1294     !! to exclude some overcounted interactions that result from
1295     !! the parallel decomposition
1296    
1297 gezelter 1610 #ifdef IS_MPI
1298 chrisfen 2229 !! in MPI, we have to look up the unique IDs for each atom
1299     unique_id_1 = AtomRowToGlobal(atom1)
1300 gezelter 1610 #else
1301 chrisfen 2229 !! in the normal loop, the atom numbers are unique
1302     unique_id_1 = atom1
1303 gezelter 1610 #endif
1304 chrisfen 2229
1305     !! We were called with only one atom, so just check the global exclude
1306     !! list for this atom
1307     if (.not. present(atom2)) then
1308     do i = 1, nExcludes_global
1309     if (excludesGlobal(i) == unique_id_1) then
1310     skip_it = .true.
1311     return
1312     end if
1313     end do
1314     return
1315     end if
1316    
1317 gezelter 1610 #ifdef IS_MPI
1318 chrisfen 2229 unique_id_2 = AtomColToGlobal(atom2)
1319 gezelter 1610 #else
1320 chrisfen 2229 unique_id_2 = atom2
1321 gezelter 1610 #endif
1322 chrisfen 2229
1323 gezelter 1610 #ifdef IS_MPI
1324 chrisfen 2229 !! this situation should only arise in MPI simulations
1325     if (unique_id_1 == unique_id_2) then
1326     skip_it = .true.
1327     return
1328     end if
1329    
1330     !! this prevents us from doing the pair on multiple processors
1331     if (unique_id_1 < unique_id_2) then
1332     if (mod(unique_id_1 + unique_id_2,2) == 0) then
1333     skip_it = .true.
1334     return
1335     endif
1336     else
1337     if (mod(unique_id_1 + unique_id_2,2) == 1) then
1338     skip_it = .true.
1339     return
1340     endif
1341     endif
1342 gezelter 1610 #endif
1343 chrisfen 2229
1344     !! the rest of these situations can happen in all simulations:
1345     do i = 1, nExcludes_global
1346     if ((excludesGlobal(i) == unique_id_1) .or. &
1347     (excludesGlobal(i) == unique_id_2)) then
1348     skip_it = .true.
1349     return
1350     endif
1351     enddo
1352    
1353     do i = 1, nSkipsForAtom(atom1)
1354     if (skipsForAtom(atom1, i) .eq. unique_id_2) then
1355     skip_it = .true.
1356     return
1357     endif
1358     end do
1359    
1360     return
1361     end function skipThisPair
1362    
1363     function FF_UsesDirectionalAtoms() result(doesit)
1364     logical :: doesit
1365 gezelter 2270 doesit = FF_uses_DirectionalAtoms
1366 chrisfen 2229 end function FF_UsesDirectionalAtoms
1367    
1368     function FF_RequiresPrepairCalc() result(doesit)
1369     logical :: doesit
1370     doesit = FF_uses_EAM
1371     end function FF_RequiresPrepairCalc
1372    
1373     function FF_RequiresPostpairCalc() result(doesit)
1374     logical :: doesit
1375     doesit = FF_uses_RF
1376     end function FF_RequiresPostpairCalc
1377    
1378 gezelter 1610 #ifdef PROFILE
1379 chrisfen 2229 function getforcetime() result(totalforcetime)
1380     real(kind=dp) :: totalforcetime
1381     totalforcetime = forcetime
1382     end function getforcetime
1383 gezelter 1610 #endif
1384    
1385 chrisfen 2229 !! This cleans componets of force arrays belonging only to fortran
1386    
1387     subroutine add_stress_tensor(dpair, fpair)
1388    
1389     real( kind = dp ), dimension(3), intent(in) :: dpair, fpair
1390    
1391     ! because the d vector is the rj - ri vector, and
1392     ! because fx, fy, fz are the force on atom i, we need a
1393     ! negative sign here:
1394    
1395     tau_Temp(1) = tau_Temp(1) - dpair(1) * fpair(1)
1396     tau_Temp(2) = tau_Temp(2) - dpair(1) * fpair(2)
1397     tau_Temp(3) = tau_Temp(3) - dpair(1) * fpair(3)
1398     tau_Temp(4) = tau_Temp(4) - dpair(2) * fpair(1)
1399     tau_Temp(5) = tau_Temp(5) - dpair(2) * fpair(2)
1400     tau_Temp(6) = tau_Temp(6) - dpair(2) * fpair(3)
1401     tau_Temp(7) = tau_Temp(7) - dpair(3) * fpair(1)
1402     tau_Temp(8) = tau_Temp(8) - dpair(3) * fpair(2)
1403     tau_Temp(9) = tau_Temp(9) - dpair(3) * fpair(3)
1404    
1405     virial_Temp = virial_Temp + &
1406     (tau_Temp(1) + tau_Temp(5) + tau_Temp(9))
1407    
1408     end subroutine add_stress_tensor
1409    
1410 gezelter 1610 end module doForces