ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/OpenMD/branches/heatflux/src/UseTheForce/doForces.F90
Revision: 1680
Committed: Mon Feb 27 20:59:02 2012 UTC (13 years, 5 months ago) by chuckv
File size: 69764 byte(s)
Log Message:
Bug fixes for v_j not being set correctly and accumulation error.

File Contents

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

Properties

Name Value
svn:keywords Author Id Revision Date