ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-2.0/src/UseTheForce/doForces.F90
Revision: 2295
Committed: Thu Sep 15 00:13:15 2005 UTC (18 years, 9 months ago) by chrisfen
File size: 42669 byte(s)
Log Message:
some changes to activate the coulombicCorrection selector

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