ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/OpenMD/trunk/src/UseTheForce/doForces.F90
Revision: 938
Committed: Mon Apr 17 21:49:12 2006 UTC (19 years ago) by gezelter
File size: 50583 byte(s)
Log Message:
Many performance improvements

File Contents

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