ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/doForces.F90
Revision: 2269
Committed: Tue Aug 9 19:40:56 2005 UTC (18 years, 11 months ago) by chuckv
File size: 42998 byte(s)
Log Message:
In process of re-write for group based cutoff....

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