ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/OpenMD/branches/development/src/UseTheForce/doForces.F90
Revision: 607
Committed: Fri Sep 16 20:37:05 2005 UTC (19 years, 7 months ago) by chrisfen
Original Path: trunk/src/UseTheForce/doForces.F90
File size: 42100 byte(s)
Log Message:
fixing some summation method issues

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