ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/doForces.F90
Revision: 3177
Committed: Tue Jul 17 21:55:57 2007 UTC (17 years ago) by gezelter
File size: 58568 byte(s)
Log Message:
adding MetalNonMetal interactions

File Contents

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