ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-2.0/src/UseTheForce/doForces.F90
Revision: 2317
Committed: Wed Sep 21 17:20:14 2005 UTC (18 years, 9 months ago) by chrisfen
File size: 42704 byte(s)
Log Message:
Fixed a defaultCutoff bug (HEMES!)

File Contents

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