ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/doForces.F90
Revision: 2540
Committed: Mon Jan 9 22:22:35 2006 UTC (18 years, 6 months ago) by chuckv
File size: 49875 byte(s)
Log Message:
Fixed SC bug with SIM_uses_SC

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