ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/OpenMD/trunk/src/UseTheForce/doForces.F90
Revision: 712
Committed: Wed Nov 2 21:01:21 2005 UTC (19 years, 6 months ago) by chrisfen
File size: 47050 byte(s)
Log Message:
removed some test code

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