ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/OpenMD/branches/development/src/UseTheForce/doForces.F90
Revision: 576
Committed: Fri Aug 26 16:36:16 2005 UTC (19 years, 8 months ago) by gezelter
Original Path: trunk/src/UseTheForce/doForces.F90
File size: 39197 byte(s)
Log Message:
fixing some of the problems in the interactionHash and gtypeCutoff routines

File Contents

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