ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/OpenMD/trunk/src/UseTheForce/doForces.F90
Revision: 561
Committed: Mon Jun 27 22:21:37 2005 UTC (19 years, 10 months ago) by chuckv
File size: 40921 byte(s)
Log Message:
More breaking and destruction of force code. Does not build at this point...

File Contents

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