ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/doForces.F90
Revision: 2281
Committed: Thu Sep 1 22:56:20 2005 UTC (18 years, 10 months ago) by gezelter
File size: 41743 byte(s)
Log Message:
initialized atomTypeMaxCutoff(i) to zero

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