ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE/libmdtools/do_Forces.F90
Revision: 1144
Committed: Sat May 1 18:52:38 2004 UTC (20 years, 2 months ago) by tim
File size: 38415 byte(s)
Log Message:
C++ pass groupList to fortran

File Contents

# User Rev Content
1 mmeineke 377 !! do_Forces.F90
2     !! module do_Forces
3     !! Calculates Long Range forces.
4    
5     !! @author Charles F. Vardeman II
6     !! @author Matthew Meineke
7 tim 1144 !! @version $Id: do_Forces.F90,v 1.53 2004-05-01 18:52:38 tim Exp $, $Date: 2004-05-01 18:52:38 $, $Name: not supported by cvs2svn $, $Revision: 1.53 $
8 mmeineke 377
9     module do_Forces
10     use force_globals
11     use simulation
12     use definitions
13     use atype_module
14     use neighborLists
15     use lj
16     use sticky_pair
17     use dipole_dipole
18 gezelter 941 use charge_charge
19 mmeineke 377 use reaction_field
20     use gb_pair
21 mmeineke 626 use vector_class
22 chuckv 650 use eam
23 chuckv 657 use status
24 mmeineke 377 #ifdef IS_MPI
25     use mpiSimulation
26     #endif
27    
28     implicit none
29     PRIVATE
30    
31     #define __FORTRAN90
32     #include "fForceField.h"
33    
34 chuckv 900 logical, save :: haveRlist = .false.
35     logical, save :: haveNeighborList = .false.
36 mmeineke 626 logical, save :: havePolicies = .false.
37 chuckv 900 logical, save :: haveSIMvariables = .false.
38     logical, save :: havePropertyMap = .false.
39     logical, save :: haveSaneForceField = .false.
40 mmeineke 377 logical, save :: FF_uses_LJ
41     logical, save :: FF_uses_sticky
42 gezelter 941 logical, save :: FF_uses_charges
43 mmeineke 377 logical, save :: FF_uses_dipoles
44     logical, save :: FF_uses_RF
45     logical, save :: FF_uses_GB
46     logical, save :: FF_uses_EAM
47 chuckv 900 logical, save :: SIM_uses_LJ
48     logical, save :: SIM_uses_sticky
49 gezelter 941 logical, save :: SIM_uses_charges
50 chuckv 900 logical, save :: SIM_uses_dipoles
51     logical, save :: SIM_uses_RF
52     logical, save :: SIM_uses_GB
53     logical, save :: SIM_uses_EAM
54     logical, save :: SIM_requires_postpair_calc
55     logical, save :: SIM_requires_prepair_calc
56     logical, save :: SIM_uses_directional_atoms
57     logical, save :: SIM_uses_PBC
58 gezelter 1138 logical, save :: SIM_uses_molecular_cutoffs
59 mmeineke 377
60 mmeineke 626 real(kind=dp), save :: rlist, rlistsq
61    
62 mmeineke 377 public :: init_FF
63     public :: do_force_loop
64 mmeineke 626 public :: setRlistDF
65 mmeineke 377
66 chuckv 900
67 chuckv 694 #ifdef PROFILE
68 chuckv 883 public :: getforcetime
69     real, save :: forceTime = 0
70     real :: forceTimeInitial, forceTimeFinal
71 mmeineke 891 integer :: nLoops
72 chuckv 694 #endif
73    
74 chuckv 900 type :: Properties
75     logical :: is_lj = .false.
76     logical :: is_sticky = .false.
77     logical :: is_dp = .false.
78     logical :: is_gb = .false.
79     logical :: is_eam = .false.
80 gezelter 941 logical :: is_charge = .false.
81     real(kind=DP) :: charge = 0.0_DP
82 chuckv 900 real(kind=DP) :: dipole_moment = 0.0_DP
83     end type Properties
84 chuckv 895
85 chuckv 900 type(Properties), dimension(:),allocatable :: PropertyMap
86    
87 mmeineke 377 contains
88    
89 mmeineke 626 subroutine setRlistDF( this_rlist )
90    
91     real(kind=dp) :: this_rlist
92    
93     rlist = this_rlist
94     rlistsq = rlist * rlist
95    
96     haveRlist = .true.
97    
98     end subroutine setRlistDF
99    
100 chuckv 900 subroutine createPropertyMap(status)
101     integer :: nAtypes
102     integer :: status
103     integer :: i
104     logical :: thisProperty
105     real (kind=DP) :: thisDPproperty
106    
107     status = 0
108    
109     nAtypes = getSize(atypes)
110    
111     if (nAtypes == 0) then
112     status = -1
113     return
114     end if
115    
116     if (.not. allocated(PropertyMap)) then
117     allocate(PropertyMap(nAtypes))
118     endif
119    
120     do i = 1, nAtypes
121     call getElementProperty(atypes, i, "is_LJ", thisProperty)
122     PropertyMap(i)%is_LJ = thisProperty
123 gezelter 941
124     call getElementProperty(atypes, i, "is_Charge", thisProperty)
125     PropertyMap(i)%is_Charge = thisProperty
126    
127     if (thisProperty) then
128     call getElementProperty(atypes, i, "charge", thisDPproperty)
129     PropertyMap(i)%charge = thisDPproperty
130     endif
131    
132 chuckv 900 call getElementProperty(atypes, i, "is_DP", thisProperty)
133     PropertyMap(i)%is_DP = thisProperty
134    
135     if (thisProperty) then
136     call getElementProperty(atypes, i, "dipole_moment", thisDPproperty)
137     PropertyMap(i)%dipole_moment = thisDPproperty
138     endif
139    
140     call getElementProperty(atypes, i, "is_Sticky", thisProperty)
141     PropertyMap(i)%is_Sticky = thisProperty
142     call getElementProperty(atypes, i, "is_GB", thisProperty)
143     PropertyMap(i)%is_GB = thisProperty
144     call getElementProperty(atypes, i, "is_EAM", thisProperty)
145     PropertyMap(i)%is_EAM = thisProperty
146     end do
147    
148     havePropertyMap = .true.
149    
150     end subroutine createPropertyMap
151    
152     subroutine setSimVariables()
153     SIM_uses_LJ = SimUsesLJ()
154     SIM_uses_sticky = SimUsesSticky()
155 gezelter 941 SIM_uses_charges = SimUsesCharges()
156 chuckv 900 SIM_uses_dipoles = SimUsesDipoles()
157     SIM_uses_RF = SimUsesRF()
158     SIM_uses_GB = SimUsesGB()
159     SIM_uses_EAM = SimUsesEAM()
160     SIM_requires_postpair_calc = SimRequiresPostpairCalc()
161     SIM_requires_prepair_calc = SimRequiresPrepairCalc()
162     SIM_uses_directional_atoms = SimUsesDirectionalAtoms()
163     SIM_uses_PBC = SimUsesPBC()
164 tim 1144 !SIM_uses_molecular_cutoffs = SimUsesMolecularCutoffs()
165 chuckv 900
166     haveSIMvariables = .true.
167    
168     return
169     end subroutine setSimVariables
170    
171     subroutine doReadyCheck(error)
172     integer, intent(out) :: error
173    
174     integer :: myStatus
175    
176     error = 0
177    
178     if (.not. havePropertyMap) then
179    
180     myStatus = 0
181    
182     call createPropertyMap(myStatus)
183    
184     if (myStatus .ne. 0) then
185     write(default_error, *) 'createPropertyMap failed in do_Forces!'
186     error = -1
187     return
188     endif
189     endif
190    
191     if (.not. haveSIMvariables) then
192     call setSimVariables()
193     endif
194    
195     if (.not. haveRlist) then
196     write(default_error, *) 'rList has not been set in do_Forces!'
197     error = -1
198     return
199     endif
200    
201     if (SIM_uses_LJ .and. FF_uses_LJ) then
202     if (.not. havePolicies) then
203     write(default_error, *) 'LJ mixing Policies have not been set in do_Forces!'
204     error = -1
205     return
206     endif
207     endif
208    
209     if (.not. haveNeighborList) then
210     write(default_error, *) 'neighbor list has not been initialized in do_Forces!'
211     error = -1
212     return
213     end if
214    
215     if (.not. haveSaneForceField) then
216     write(default_error, *) 'Force Field is not sane in do_Forces!'
217     error = -1
218     return
219     end if
220    
221     #ifdef IS_MPI
222     if (.not. isMPISimSet()) then
223     write(default_error,*) "ERROR: mpiSimulation has not been initialized!"
224     error = -1
225     return
226     endif
227     #endif
228     return
229     end subroutine doReadyCheck
230    
231    
232 mmeineke 377 subroutine init_FF(LJMIXPOLICY, use_RF_c, thisStat)
233    
234     integer, intent(in) :: LJMIXPOLICY
235     logical, intent(in) :: use_RF_c
236    
237     integer, intent(out) :: thisStat
238     integer :: my_status, nMatches
239     integer, pointer :: MatchList(:) => null()
240     real(kind=dp) :: rcut, rrf, rt, dielect
241    
242     !! assume things are copacetic, unless they aren't
243     thisStat = 0
244    
245     !! Fortran's version of a cast:
246     FF_uses_RF = use_RF_c
247    
248     !! init_FF is called *after* all of the atom types have been
249     !! defined in atype_module using the new_atype subroutine.
250     !!
251     !! this will scan through the known atypes and figure out what
252     !! interactions are used by the force field.
253    
254     FF_uses_LJ = .false.
255     FF_uses_sticky = .false.
256 gezelter 941 FF_uses_charges = .false.
257 mmeineke 377 FF_uses_dipoles = .false.
258     FF_uses_GB = .false.
259     FF_uses_EAM = .false.
260    
261     call getMatchingElementList(atypes, "is_LJ", .true., nMatches, MatchList)
262     if (nMatches .gt. 0) FF_uses_LJ = .true.
263 gezelter 941
264     call getMatchingElementList(atypes, "is_Charge", .true., nMatches, MatchList)
265 tim 1113 if (nMatches .gt. 0) FF_uses_charges = .true.
266    
267 mmeineke 377 call getMatchingElementList(atypes, "is_DP", .true., nMatches, MatchList)
268     if (nMatches .gt. 0) FF_uses_dipoles = .true.
269    
270     call getMatchingElementList(atypes, "is_Sticky", .true., nMatches, &
271     MatchList)
272     if (nMatches .gt. 0) FF_uses_Sticky = .true.
273    
274     call getMatchingElementList(atypes, "is_GB", .true., nMatches, MatchList)
275     if (nMatches .gt. 0) FF_uses_GB = .true.
276    
277     call getMatchingElementList(atypes, "is_EAM", .true., nMatches, MatchList)
278     if (nMatches .gt. 0) FF_uses_EAM = .true.
279    
280 chuckv 900 !! Assume sanity (for the sake of argument)
281     haveSaneForceField = .true.
282 tim 1132 !!
283     if (FF_uses_charges) then
284     dielect = getDielect()
285     call initialize_charge(dielect)
286     endif
287 chuckv 900
288 tim 1132
289 mmeineke 377 !! check to make sure the FF_uses_RF setting makes sense
290    
291     if (FF_uses_dipoles) then
292     if (FF_uses_RF) then
293     dielect = getDielect()
294 mmeineke 626 call initialize_rf(dielect)
295 mmeineke 377 endif
296     else
297     if (FF_uses_RF) then
298     write(default_error,*) 'Using Reaction Field with no dipoles? Huh?'
299     thisStat = -1
300 chuckv 900 haveSaneForceField = .false.
301 mmeineke 377 return
302     endif
303 mmeineke 626 endif
304 mmeineke 377
305     if (FF_uses_LJ) then
306    
307     select case (LJMIXPOLICY)
308 gezelter 834 case (LB_MIXING_RULE)
309     call init_lj_FF(LB_MIXING_RULE, my_status)
310     case (EXPLICIT_MIXING_RULE)
311     call init_lj_FF(EXPLICIT_MIXING_RULE, my_status)
312 mmeineke 377 case default
313     write(default_error,*) 'unknown LJ Mixing Policy!'
314     thisStat = -1
315 chuckv 900 haveSaneForceField = .false.
316 mmeineke 377 return
317     end select
318     if (my_status /= 0) then
319     thisStat = -1
320 chuckv 900 haveSaneForceField = .false.
321 mmeineke 377 return
322     end if
323 chuckv 900 havePolicies = .true.
324 mmeineke 377 endif
325    
326     if (FF_uses_sticky) then
327     call check_sticky_FF(my_status)
328     if (my_status /= 0) then
329     thisStat = -1
330 chuckv 900 haveSaneForceField = .false.
331 mmeineke 377 return
332     end if
333     endif
334 chuckv 657
335    
336     if (FF_uses_EAM) then
337 chuckv 801 call init_EAM_FF(my_status)
338 chuckv 657 if (my_status /= 0) then
339 chuckv 900 write(default_error, *) "init_EAM_FF returned a bad status"
340 chuckv 657 thisStat = -1
341 chuckv 900 haveSaneForceField = .false.
342 chuckv 657 return
343     end if
344     endif
345    
346 mmeineke 377 if (FF_uses_GB) then
347     call check_gb_pair_FF(my_status)
348     if (my_status .ne. 0) then
349     thisStat = -1
350 chuckv 900 haveSaneForceField = .false.
351 mmeineke 377 return
352     endif
353     endif
354    
355     if (FF_uses_GB .and. FF_uses_LJ) then
356     endif
357 chuckv 900 if (.not. haveNeighborList) then
358 chuckv 480 !! Create neighbor lists
359 chuckv 898 call expandNeighborList(nLocal, my_status)
360 chuckv 480 if (my_Status /= 0) then
361     write(default_error,*) "SimSetup: ExpandNeighborList returned error."
362     thisStat = -1
363     return
364     endif
365 chuckv 900 haveNeighborList = .true.
366 chuckv 480 endif
367 chuckv 657
368 mmeineke 377 end subroutine init_FF
369    
370    
371     !! Does force loop over i,j pairs. Calls do_pair to calculates forces.
372     !------------------------------------------------------------->
373 tim 1144 subroutine do_force_loop(q, qcom, A, u_l, f, t, tau, pot, &
374 gezelter 1138 do_pot_c, do_stress_c, error)
375 mmeineke 377 !! Position array provided by C, dimensioned by getNlocal
376 chuckv 898 real ( kind = dp ), dimension(3,nLocal) :: q
377 gezelter 1138 !! molecular center-of-mass position array
378     real ( kind = dp ), dimension(3,nLocal) :: qcom
379 mmeineke 377 !! Rotation Matrix for each long range particle in simulation.
380 chuckv 898 real( kind = dp), dimension(9,nLocal) :: A
381 mmeineke 377 !! Unit vectors for dipoles (lab frame)
382 chuckv 898 real( kind = dp ), dimension(3,nLocal) :: u_l
383 mmeineke 377 !! Force array provided by C, dimensioned by getNlocal
384 chuckv 898 real ( kind = dp ), dimension(3,nLocal) :: f
385 mmeineke 377 !! Torsion array provided by C, dimensioned by getNlocal
386 chuckv 898 real( kind = dp ), dimension(3,nLocal) :: t
387 chuckv 895
388 mmeineke 377 !! Stress Tensor
389     real( kind = dp), dimension(9) :: tau
390     real ( kind = dp ) :: pot
391     logical ( kind = 2) :: do_pot_c, do_stress_c
392     logical :: do_pot
393     logical :: do_stress
394 chuckv 439 #ifdef IS_MPI
395 chuckv 441 real( kind = DP ) :: pot_local
396 mmeineke 377 integer :: nrow
397     integer :: ncol
398 chuckv 694 integer :: nprocs
399 mmeineke 377 #endif
400     integer :: natoms
401     logical :: update_nlist
402     integer :: i, j, jbeg, jend, jnab
403     integer :: nlist
404 gezelter 1138 real( kind = DP ) :: rijsq, rcijsq
405     real(kind=dp),dimension(3) :: d, dc
406 mmeineke 377 real(kind=dp) :: rfpot, mu_i, virial
407 chuckv 897 integer :: me_i, me_j
408 mmeineke 377 logical :: is_dp_i
409     integer :: neighborListSize
410     integer :: listerror, error
411     integer :: localError
412 chuckv 897 integer :: propPack_i, propPack_j
413 mmeineke 626
414 gezelter 845 real(kind=dp) :: listSkin = 1.0
415 gezelter 1138
416 mmeineke 377 !! initialize local variables
417 gezelter 1138
418 mmeineke 377 #ifdef IS_MPI
419 chuckv 441 pot_local = 0.0_dp
420 mmeineke 377 nrow = getNrow(plan_row)
421     ncol = getNcol(plan_col)
422     #else
423     natoms = nlocal
424     #endif
425 gezelter 1138
426 chuckv 900 call doReadyCheck(localError)
427 mmeineke 377 if ( localError .ne. 0 ) then
428 chuckv 900 call handleError("do_force_loop", "Not Initialized")
429 mmeineke 377 error = -1
430     return
431     end if
432     call zero_work_arrays()
433 gezelter 1138
434 mmeineke 377 do_pot = do_pot_c
435     do_stress = do_stress_c
436 gezelter 1138
437 mmeineke 377 ! Gather all information needed by all force loops:
438    
439     #ifdef IS_MPI
440 gezelter 1138
441 mmeineke 377 call gather(q,q_Row,plan_row3d)
442     call gather(q,q_Col,plan_col3d)
443 gezelter 1138
444     if (SIM_uses_molecular_cutoffs) then
445     call gather(qcom,qcom_Row,plan_row3d)
446     call gather(qcom,qcom_Col,plan_col3d)
447     endif
448    
449 chuckv 900 if (FF_UsesDirectionalAtoms() .and. SIM_uses_directional_atoms) then
450 mmeineke 377 call gather(u_l,u_l_Row,plan_row3d)
451     call gather(u_l,u_l_Col,plan_col3d)
452    
453     call gather(A,A_Row,plan_row_rotation)
454     call gather(A,A_Col,plan_col_rotation)
455     endif
456    
457     #endif
458 gezelter 1138
459     !! Begin force loop timing:
460 chuckv 694 #ifdef PROFILE
461     call cpu_time(forceTimeInitial)
462     nloops = nloops + 1
463     #endif
464 gezelter 1138
465 chuckv 900 if (FF_RequiresPrepairCalc() .and. SIM_requires_prepair_calc) then
466 mmeineke 377 !! See if we need to update neighbor lists
467 gezelter 1138 if (SIM_uses_molecular_cutoffs) then
468     call checkNeighborList(nlocal, qcom, listSkin, update_nlist)
469     else
470     call checkNeighborList(nlocal, q, listSkin, update_nlist)
471     endif
472 mmeineke 377 !! if_mpi_gather_stuff_for_prepair
473     !! do_prepair_loop_if_needed
474     !! if_mpi_scatter_stuff_from_prepair
475     !! if_mpi_gather_stuff_from_prepair_to_main_loop
476 gezelter 1138
477     !--------------------PREFORCE LOOP----------->>>>>>>>>>>>>>>>>>>>>>>>>>>
478 chuckv 648 #ifdef IS_MPI
479    
480 gezelter 1138 if (update_nlist) then
481 chuckv 648
482 gezelter 1138 !! save current configuration, construct neighbor list,
483     !! and calculate forces
484     if (SIM_uses_molecular_cutoffs) then
485     call saveNeighborList(nlocal, qcom)
486     else
487     call saveNeighborList(nlocal, q)
488     endif
489    
490     neighborListSize = size(list)
491     nlist = 0
492    
493     do i = 1, nrow
494     point(i) = nlist + 1
495 chuckv 648
496 gezelter 1138 prepair_inner: do j = 1, ncol
497 chuckv 648
498 gezelter 1138 if (skipThisPair(i,j)) cycle prepair_inner
499 chuckv 648
500 gezelter 1138 if (SIM_uses_molecular_cutoffs) then
501     call get_interatomic_vector(qcom_Row(:,i), qcom_Col(:,j), &
502     dc, rcijsq)
503     else
504     call get_interatomic_vector(q_Row(:,i), q_Col(:,j), &
505     dc, rcijsq)
506 chuckv 648 endif
507    
508 gezelter 1138 if (rcijsq < rlistsq) then
509    
510     nlist = nlist + 1
511    
512     if (nlist > neighborListSize) then
513     call expandNeighborList(nlocal, listerror)
514     if (listerror /= 0) then
515     error = -1
516     write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
517     return
518     end if
519     neighborListSize = size(list)
520     endif
521    
522     list(nlist) = j
523    
524     if (SIM_uses_molecular_cutoffs) then
525     ! since the simulation distances were in molecular COMs:
526     call get_interatomic_vector(q_Row(:,i), q_Col(:,j), &
527     d, rijsq)
528     else
529     d(1:3) = dc(1:3)
530     rijsq = rcijsq
531     endif
532    
533     call do_prepair(i, j, rijsq, d, rcijsq, dc, &
534     do_pot, do_stress, u_l, A, f, t, pot_local)
535     endif
536     enddo prepair_inner
537     enddo
538    
539     point(nrow + 1) = nlist + 1
540    
541     else !! (of update_check)
542    
543     ! use the list to find the neighbors
544     do i = 1, nrow
545     JBEG = POINT(i)
546     JEND = POINT(i+1) - 1
547     ! check thiat molecule i has neighbors
548     if (jbeg .le. jend) then
549    
550     do jnab = jbeg, jend
551     j = list(jnab)
552    
553     call get_interatomic_vector(q_Row(:,i), q_Col(:,j), &
554     d, rijsq)
555     if (SIM_uses_molecular_cutoffs) then
556     call get_interatomic_vector(qcom_Row(:,i),qcom_Col(:,j),&
557     dc, rcijsq)
558     else
559     dc(1:3) = d(1:3)
560     rcijsq = rijsq
561     endif
562    
563     call do_prepair(i, j, rijsq, d, rcijsq, dc, &
564     do_pot, do_stress, u_l, A, f, t, pot_local)
565    
566     enddo
567 chuckv 648 endif
568 gezelter 1138 enddo
569     endif
570 chuckv 648
571     #else
572    
573 gezelter 1138 if (update_nlist) then
574 chuckv 648
575 gezelter 1138 ! save current configuration, contruct neighbor list,
576     ! and calculate forces
577     call saveNeighborList(natoms, q)
578    
579     neighborListSize = size(list)
580    
581     nlist = 0
582    
583     do i = 1, natoms-1
584     point(i) = nlist + 1
585 chuckv 648
586 gezelter 1138 prepair_inner: do j = i+1, natoms
587    
588     if (skipThisPair(i,j)) cycle prepair_inner
589    
590     if (SIM_uses_molecular_cutoffs) then
591     call get_interatomic_vector(qcom(:,i), qcom(:,j), &
592     dc, rcijsq)
593     else
594     call get_interatomic_vector(q(:,i), q(:,j), dc, rcijsq)
595 chuckv 648 endif
596    
597 gezelter 1138 if (rcijsq < rlistsq) then
598    
599     nlist = nlist + 1
600    
601     if (nlist > neighborListSize) then
602     call expandNeighborList(natoms, listerror)
603     if (listerror /= 0) then
604     error = -1
605     write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
606     return
607     end if
608     neighborListSize = size(list)
609     endif
610    
611     list(nlist) = j
612    
613    
614     if (SIM_uses_molecular_cutoffs) then
615     ! since the simulation distances were in molecular COMs:
616     call get_interatomic_vector(q(:,i), q(:,j), &
617     d, rijsq)
618     else
619     dc(1:3) = d(1:3)
620     rcijsq = rijsq
621     endif
622    
623     call do_prepair(i, j, rijsq, d, rcijsq, dc, &
624     do_pot, do_stress, u_l, A, f, t, pot)
625    
626     endif
627     enddo prepair_inner
628     enddo
629    
630     point(natoms) = nlist + 1
631    
632     else !! (update)
633    
634     ! use the list to find the neighbors
635     do i = 1, natoms-1
636     JBEG = POINT(i)
637     JEND = POINT(i+1) - 1
638     ! check thiat molecule i has neighbors
639     if (jbeg .le. jend) then
640 chuckv 648
641 gezelter 1138 do jnab = jbeg, jend
642     j = list(jnab)
643    
644     call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
645     if (SIM_uses_molecular_cutoffs) then
646     call get_interatomic_vector(qcom(:,i), qcom(:,j), &
647     dc, rcijsq)
648     else
649     dc(1:3) = d(1:3)
650     rcijsq = rijsq
651     endif
652    
653     call do_prepair(i, j, rijsq, d, rcijsq, dc, &
654     do_pot, do_stress, u_l, A, f, t, pot)
655    
656     enddo
657 chuckv 648 endif
658 gezelter 1138 enddo
659     endif
660 chuckv 648 #endif
661 gezelter 1138 !! Do rest of preforce calculations
662     !! do necessary preforce calculations
663     call do_preforce(nlocal,pot)
664     ! we have already updated the neighbor list set it to false...
665     update_nlist = .false.
666 mmeineke 377 else
667 chuckv 648 !! See if we need to update neighbor lists for non pre-pair
668 mmeineke 626 call checkNeighborList(nlocal, q, listSkin, update_nlist)
669 mmeineke 377 endif
670 gezelter 1138
671     !---------------------------------MAIN Pair LOOP->>>>>>>>>>>>>
672    
673 mmeineke 377 #ifdef IS_MPI
674    
675     if (update_nlist) then
676     !! save current configuration, construct neighbor list,
677     !! and calculate forces
678 mmeineke 459 call saveNeighborList(nlocal, q)
679 mmeineke 377
680     neighborListSize = size(list)
681     nlist = 0
682    
683     do i = 1, nrow
684 gezelter 1138
685 mmeineke 377 point(i) = nlist + 1
686    
687     inner: do j = 1, ncol
688    
689     if (skipThisPair(i,j)) cycle inner
690    
691 gezelter 1138 if (SIM_uses_molecular_cutoffs) then
692     call get_interatomic_vector(qcom_Row(:,i), qcom_Col(:,j), &
693     dc, rcijsq)
694     else
695     call get_interatomic_vector(q_Row(:,i), q_Col(:,j), &
696     dc, rcijsq)
697     endif
698 mmeineke 377
699 gezelter 1138 if (rcijsq < rlistsq) then
700 mmeineke 377
701     nlist = nlist + 1
702    
703     if (nlist > neighborListSize) then
704     call expandNeighborList(nlocal, listerror)
705     if (listerror /= 0) then
706     error = -1
707     write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
708     return
709     end if
710     neighborListSize = size(list)
711     endif
712    
713     list(nlist) = j
714 mmeineke 626
715 gezelter 1138 if (SIM_uses_molecular_cutoffs) then
716     call get_interatomic_vector(q_Row(:,i), q_Col(:,j), &
717     d, rijsq)
718     else
719     d(1:3) = dc(1:3)
720     rijsq = rcijsq
721     endif
722    
723     call do_pair(i, j, rijsq, d, rcijsq, dc, mfact, &
724     do_pot, do_stress, u_l, A, f, t, pot_local)
725    
726 mmeineke 377 endif
727     enddo inner
728     enddo
729 gezelter 1138
730 mmeineke 377 point(nrow + 1) = nlist + 1
731    
732     else !! (of update_check)
733 gezelter 1138
734 mmeineke 377 ! use the list to find the neighbors
735     do i = 1, nrow
736     JBEG = POINT(i)
737     JEND = POINT(i+1) - 1
738     ! check thiat molecule i has neighbors
739     if (jbeg .le. jend) then
740    
741     do jnab = jbeg, jend
742     j = list(jnab)
743 gezelter 1138
744 mmeineke 377 call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
745 gezelter 1138 if (SIM_uses_molecular_cutoffs) then
746     call get_interatomic_vector(qcom_Row(:,i), qcom_Col(:,j), &
747     dc, rcijsq)
748     else
749     dc(1:3) = d(1:3)
750     rcijsq = rijsq
751     endif
752    
753     call do_pair(i, j, rijsq, d, rcijsq, dc, mfact, &
754     do_pot, do_stress, u_l, A, f, t, pot_local)
755    
756 mmeineke 377 enddo
757     endif
758     enddo
759     endif
760    
761     #else
762    
763     if (update_nlist) then
764 gezelter 1138
765 mmeineke 377 ! save current configuration, contruct neighbor list,
766     ! and calculate forces
767 mmeineke 459 call saveNeighborList(natoms, q)
768 mmeineke 377
769     neighborListSize = size(list)
770 gezelter 1138
771 mmeineke 377 nlist = 0
772    
773     do i = 1, natoms-1
774     point(i) = nlist + 1
775    
776     inner: do j = i+1, natoms
777    
778 chuckv 388 if (skipThisPair(i,j)) cycle inner
779 gezelter 1138
780     if (SIM_uses_molecular_cutoffs) then
781     call get_interatomic_vector(qcom(:,i), qcom(:,j), &
782     dc, rcijsq)
783     else
784     call get_interatomic_vector(q(:,i), q(:,j), &
785     dc, rcijsq)
786     endif
787    
788     if (rcijsq < rlistsq) then
789 mmeineke 377
790     nlist = nlist + 1
791 gezelter 1138
792 mmeineke 377 if (nlist > neighborListSize) then
793     call expandNeighborList(natoms, listerror)
794     if (listerror /= 0) then
795     error = -1
796     write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
797     return
798     end if
799     neighborListSize = size(list)
800     endif
801    
802     list(nlist) = j
803    
804 gezelter 1138 if (SIM_uses_molecular_cutoffs) then
805     call get_interatomic_vector(q(:,i), q(:,j), &
806     d, rijsq)
807     else
808     d(1:3) = dc(1:3)
809     rijsq = rcijsq
810     endif
811 mmeineke 626
812 gezelter 1138 call do_pair(i, j, rijsq, d, rcijsq, dc, mfact, &
813     do_pot, do_stress, u_l, A, f, t, pot)
814    
815 mmeineke 377 endif
816     enddo inner
817     enddo
818    
819     point(natoms) = nlist + 1
820    
821     else !! (update)
822    
823     ! use the list to find the neighbors
824     do i = 1, natoms-1
825     JBEG = POINT(i)
826     JEND = POINT(i+1) - 1
827     ! check thiat molecule i has neighbors
828     if (jbeg .le. jend) then
829    
830     do jnab = jbeg, jend
831     j = list(jnab)
832    
833 gezelter 1138
834 mmeineke 377 call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
835 gezelter 1138 if (SIM_uses_molecular_cutoffs) then
836     call get_interatomic_vector(qcom(:,i), qcom(:,j), &
837     dc, rcijsq)
838     else
839     dc(1:3) = d(1:3)
840     rcijsq = rijsq
841     endif
842    
843     call do_pair(i, j, rijsq, d, rcijsq, dc, mfact, &
844     do_pot, do_stress, u_l, A, f, t, pot)
845    
846 mmeineke 377 enddo
847     endif
848     enddo
849     endif
850    
851     #endif
852    
853     ! phew, done with main loop.
854 gezelter 1138
855     !! Do timing
856 chuckv 694 #ifdef PROFILE
857     call cpu_time(forceTimeFinal)
858     forceTime = forceTime + forceTimeFinal - forceTimeInitial
859     #endif
860 gezelter 1138
861    
862 mmeineke 377 #ifdef IS_MPI
863     !!distribute forces
864 gezelter 1138
865 chuckv 438 f_temp = 0.0_dp
866     call scatter(f_Row,f_temp,plan_row3d)
867     do i = 1,nlocal
868     f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
869     end do
870 gezelter 1138
871 chuckv 438 f_temp = 0.0_dp
872 mmeineke 377 call scatter(f_Col,f_temp,plan_col3d)
873     do i = 1,nlocal
874     f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
875     end do
876    
877 chuckv 900 if (FF_UsesDirectionalAtoms() .and. SIM_uses_directional_atoms) then
878 chuckv 438 t_temp = 0.0_dp
879     call scatter(t_Row,t_temp,plan_row3d)
880     do i = 1,nlocal
881     t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
882     end do
883     t_temp = 0.0_dp
884 mmeineke 377 call scatter(t_Col,t_temp,plan_col3d)
885    
886     do i = 1,nlocal
887     t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
888     end do
889     endif
890    
891     if (do_pot) then
892     ! scatter/gather pot_row into the members of my column
893     call scatter(pot_Row, pot_Temp, plan_row)
894 gezelter 1138
895 mmeineke 377 ! scatter/gather pot_local into all other procs
896     ! add resultant to get total pot
897     do i = 1, nlocal
898     pot_local = pot_local + pot_Temp(i)
899     enddo
900 chuckv 439
901     pot_Temp = 0.0_DP
902 gezelter 1138
903 mmeineke 377 call scatter(pot_Col, pot_Temp, plan_col)
904     do i = 1, nlocal
905     pot_local = pot_local + pot_Temp(i)
906     enddo
907 chuckv 439
908 gezelter 1138 endif
909 mmeineke 377 #endif
910 gezelter 1138
911 chuckv 900 if (FF_RequiresPostpairCalc() .and. SIM_requires_postpair_calc) then
912 mmeineke 377
913 chuckv 900 if (FF_uses_RF .and. SIM_uses_RF) then
914 gezelter 1138
915 mmeineke 377 #ifdef IS_MPI
916     call scatter(rf_Row,rf,plan_row3d)
917     call scatter(rf_Col,rf_Temp,plan_col3d)
918     do i = 1,nlocal
919     rf(1:3,i) = rf(1:3,i) + rf_Temp(1:3,i)
920     end do
921     #endif
922    
923 chuckv 898 do i = 1, nLocal
924 gezelter 1138
925 mmeineke 377 rfpot = 0.0_DP
926     #ifdef IS_MPI
927     me_i = atid_row(i)
928     #else
929     me_i = atid(i)
930     #endif
931 gezelter 1138
932 chuckv 900 if (PropertyMap(me_i)%is_DP) then
933 gezelter 1138
934 chuckv 900 mu_i = PropertyMap(me_i)%dipole_moment
935 gezelter 1138
936 mmeineke 377 !! The reaction field needs to include a self contribution
937     !! to the field:
938 chuckv 900 call accumulate_self_rf(i, mu_i, u_l)
939 mmeineke 377 !! Get the reaction field contribution to the
940     !! potential and torques:
941     call reaction_field_final(i, mu_i, u_l, rfpot, t, do_pot)
942     #ifdef IS_MPI
943     pot_local = pot_local + rfpot
944     #else
945     pot = pot + rfpot
946    
947     #endif
948     endif
949     enddo
950     endif
951     endif
952 gezelter 1138
953    
954 mmeineke 377 #ifdef IS_MPI
955 gezelter 1138
956 mmeineke 377 if (do_pot) then
957 chuckv 441 pot = pot + pot_local
958 mmeineke 377 !! we assume the c code will do the allreduce to get the total potential
959     !! we could do it right here if we needed to...
960     endif
961 gezelter 1138
962 mmeineke 377 if (do_stress) then
963 gezelter 1138 call mpi_allreduce(tau_Temp, tau, 9,mpi_double_precision,mpi_sum, &
964 mmeineke 377 mpi_comm_world,mpi_err)
965 chuckv 470 call mpi_allreduce(virial_Temp, virial,1,mpi_double_precision,mpi_sum, &
966 mmeineke 377 mpi_comm_world,mpi_err)
967     endif
968 gezelter 1138
969 mmeineke 377 #else
970 gezelter 1138
971 mmeineke 377 if (do_stress) then
972     tau = tau_Temp
973     virial = virial_Temp
974     endif
975 mmeineke 887
976 mmeineke 377 #endif
977 mmeineke 887
978    
979 mmeineke 377 end subroutine do_force_loop
980 gezelter 1138
981     subroutine do_pair(i, j, rijsq, d, rcijsq, dc, mfact, do_pot, do_stress, &
982     u_l, A, f, t, pot)
983 mmeineke 377
984     real( kind = dp ) :: pot
985 gezelter 1138 real( kind = dp ), dimension(nLocal) :: mfact
986 chuckv 898 real( kind = dp ), dimension(3,nLocal) :: u_l
987 gezelter 1138 real( kind = dp ), dimension(9,nLocal) :: A
988     real( kind = dp ), dimension(3,nLocal) :: f
989     real( kind = dp ), dimension(3,nLocal) :: t
990 mmeineke 377
991     logical, intent(inout) :: do_pot, do_stress
992     integer, intent(in) :: i, j
993 gezelter 1138 real ( kind = dp ), intent(inout) :: rijsq, rcijsq
994     real ( kind = dp ) :: r, rc
995     real ( kind = dp ), intent(inout) :: d(3), dc(3)
996 mmeineke 377 integer :: me_i, me_j
997 gezelter 946
998 mmeineke 377 r = sqrt(rijsq)
999 gezelter 1138 if (SIM_uses_molecular_cutoffs) then
1000     rc = sqrt(rcijsq)
1001     else
1002     rc = r
1003     endif
1004 mmeineke 377
1005 gezelter 1138
1006 mmeineke 377 #ifdef IS_MPI
1007 gezelter 490 if (tagRow(i) .eq. tagColumn(j)) then
1008     write(0,*) 'do_pair is doing', i , j, tagRow(i), tagColumn(j)
1009     endif
1010 mmeineke 377 me_i = atid_row(i)
1011     me_j = atid_col(j)
1012     #else
1013     me_i = atid(i)
1014     me_j = atid(j)
1015     #endif
1016 chuckv 894
1017 chuckv 900 if (FF_uses_LJ .and. SIM_uses_LJ) then
1018 gezelter 946
1019     if ( PropertyMap(me_i)%is_LJ .and. PropertyMap(me_j)%is_LJ ) then
1020     call do_lj_pair(i, j, d, r, rijsq, pot, f, do_pot, do_stress)
1021     endif
1022    
1023 mmeineke 377 endif
1024 gezelter 946
1025     if (FF_uses_charges .and. SIM_uses_charges) then
1026    
1027     if (PropertyMap(me_i)%is_Charge .and. PropertyMap(me_j)%is_Charge) then
1028 gezelter 1138 call do_charge_pair(i, j, d, r, rijsq, dc, rc, rcijsq, mfact, &
1029     pot, f, do_pot, do_stress, SIM_uses_molecular_cutoffs)
1030 gezelter 946 endif
1031    
1032     endif
1033    
1034 chuckv 900 if (FF_uses_dipoles .and. SIM_uses_dipoles) then
1035 mmeineke 377
1036 chuckv 900 if ( PropertyMap(me_i)%is_DP .and. PropertyMap(me_j)%is_DP) then
1037 gezelter 462 call do_dipole_pair(i, j, d, r, rijsq, pot, u_l, f, t, &
1038 mmeineke 377 do_pot, do_stress)
1039 chuckv 900 if (FF_uses_RF .and. SIM_uses_RF) then
1040 mmeineke 377 call accumulate_rf(i, j, r, u_l)
1041     call rf_correct_forces(i, j, d, r, u_l, f, do_stress)
1042 gezelter 946 endif
1043 mmeineke 377 endif
1044 gezelter 946
1045 mmeineke 377 endif
1046    
1047 chuckv 900 if (FF_uses_Sticky .and. SIM_uses_sticky) then
1048 mmeineke 377
1049 chuckv 900 if ( PropertyMap(me_i)%is_Sticky .and. PropertyMap(me_j)%is_Sticky) then
1050 mmeineke 377 call do_sticky_pair(i, j, d, r, rijsq, A, pot, f, t, &
1051     do_pot, do_stress)
1052     endif
1053 gezelter 946
1054 mmeineke 377 endif
1055    
1056    
1057 chuckv 900 if (FF_uses_GB .and. SIM_uses_GB) then
1058 mmeineke 377
1059 chuckv 900 if ( PropertyMap(me_i)%is_GB .and. PropertyMap(me_j)%is_GB) then
1060 mmeineke 377 call do_gb_pair(i, j, d, r, rijsq, u_l, pot, f, t, &
1061     do_pot, do_stress)
1062     endif
1063 chuckv 894
1064 mmeineke 377 endif
1065 gezelter 946
1066     if (FF_uses_EAM .and. SIM_uses_EAM) then
1067    
1068     if ( PropertyMap(me_i)%is_EAM .and. PropertyMap(me_j)%is_EAM) then
1069     call do_eam_pair(i, j, d, r, rijsq, pot, f, do_pot, do_stress)
1070     endif
1071    
1072     endif
1073 mmeineke 597
1074 mmeineke 377 end subroutine do_pair
1075    
1076    
1077 chuckv 631
1078 gezelter 1138 subroutine do_prepair(i, j, rijsq, d, rcijsq, dc, &
1079     do_pot, do_stress, u_l, A, f, t, pot)
1080 chuckv 631 real( kind = dp ) :: pot
1081 chuckv 898 real( kind = dp ), dimension(3,nLocal) :: u_l
1082     real (kind=dp), dimension(9,nLocal) :: A
1083     real (kind=dp), dimension(3,nLocal) :: f
1084     real (kind=dp), dimension(3,nLocal) :: t
1085 chuckv 631
1086     logical, intent(inout) :: do_pot, do_stress
1087     integer, intent(in) :: i, j
1088 gezelter 1138 real ( kind = dp ), intent(inout) :: rijsq, rcijsq
1089     real ( kind = dp ) :: r, rc
1090     real ( kind = dp ), intent(inout) :: d(3), dc(3)
1091 chuckv 631
1092     logical :: is_EAM_i, is_EAM_j
1093    
1094     integer :: me_i, me_j
1095    
1096 gezelter 1138
1097     r = sqrt(rijsq)
1098     if (SIM_uses_molecular_cutoffs) then
1099     rc = sqrt(rcijsq)
1100     else
1101     rc = r
1102     endif
1103 chuckv 631
1104 chuckv 669
1105 chuckv 631 #ifdef IS_MPI
1106     if (tagRow(i) .eq. tagColumn(j)) then
1107     write(0,*) 'do_pair is doing', i , j, tagRow(i), tagColumn(j)
1108     endif
1109    
1110     me_i = atid_row(i)
1111     me_j = atid_col(j)
1112    
1113     #else
1114    
1115     me_i = atid(i)
1116     me_j = atid(j)
1117    
1118     #endif
1119 chuckv 673
1120 chuckv 900 if (FF_uses_EAM .and. SIM_uses_EAM) then
1121    
1122     if (PropertyMap(me_i)%is_EAM .and. PropertyMap(me_j)%is_EAM) &
1123 chuckv 648 call calc_EAM_prepair_rho(i, j, d, r, rijsq )
1124 chuckv 900
1125 chuckv 631 endif
1126 chuckv 900
1127 chuckv 673 end subroutine do_prepair
1128 chuckv 648
1129    
1130    
1131 chuckv 673
1132 gezelter 1138 subroutine do_preforce(nlocal,pot)
1133     integer :: nlocal
1134     real( kind = dp ) :: pot
1135    
1136     if (FF_uses_EAM .and. SIM_uses_EAM) then
1137     call calc_EAM_preforce_Frho(nlocal,pot)
1138     endif
1139    
1140    
1141     end subroutine do_preforce
1142    
1143    
1144     subroutine get_interatomic_vector(q_i, q_j, d, r_sq)
1145    
1146     real (kind = dp), dimension(3) :: q_i
1147     real (kind = dp), dimension(3) :: q_j
1148     real ( kind = dp ), intent(out) :: r_sq
1149     real( kind = dp ) :: d(3), scaled(3)
1150     integer i
1151    
1152     d(1:3) = q_j(1:3) - q_i(1:3)
1153    
1154     ! Wrap back into periodic box if necessary
1155     if ( SIM_uses_PBC ) then
1156 mmeineke 377
1157 gezelter 1138 if( .not.boxIsOrthorhombic ) then
1158     ! calc the scaled coordinates.
1159    
1160     scaled = matmul(HmatInv, d)
1161    
1162     ! wrap the scaled coordinates
1163    
1164     scaled = scaled - anint(scaled)
1165    
1166    
1167     ! calc the wrapped real coordinates from the wrapped scaled
1168     ! coordinates
1169    
1170     d = matmul(Hmat,scaled)
1171    
1172     else
1173     ! calc the scaled coordinates.
1174    
1175     do i = 1, 3
1176     scaled(i) = d(i) * HmatInv(i,i)
1177    
1178     ! wrap the scaled coordinates
1179    
1180     scaled(i) = scaled(i) - anint(scaled(i))
1181    
1182     ! calc the wrapped real coordinates from the wrapped scaled
1183     ! coordinates
1184    
1185     d(i) = scaled(i)*Hmat(i,i)
1186     enddo
1187     endif
1188    
1189     endif
1190    
1191     r_sq = dot_product(d,d)
1192    
1193     end subroutine get_interatomic_vector
1194 mmeineke 377
1195 gezelter 1138 subroutine zero_work_arrays()
1196    
1197     #ifdef IS_MPI
1198    
1199     q_Row = 0.0_dp
1200     q_Col = 0.0_dp
1201 mmeineke 377
1202 gezelter 1138 qcom_Row = 0.0_dp
1203     qcom_Col = 0.0_dp
1204    
1205     u_l_Row = 0.0_dp
1206     u_l_Col = 0.0_dp
1207    
1208     A_Row = 0.0_dp
1209     A_Col = 0.0_dp
1210    
1211     f_Row = 0.0_dp
1212     f_Col = 0.0_dp
1213     f_Temp = 0.0_dp
1214    
1215     t_Row = 0.0_dp
1216     t_Col = 0.0_dp
1217     t_Temp = 0.0_dp
1218    
1219     pot_Row = 0.0_dp
1220     pot_Col = 0.0_dp
1221     pot_Temp = 0.0_dp
1222    
1223     rf_Row = 0.0_dp
1224     rf_Col = 0.0_dp
1225     rf_Temp = 0.0_dp
1226    
1227 mmeineke 377 #endif
1228 chuckv 673
1229 gezelter 1138 if (FF_uses_EAM .and. SIM_uses_EAM) then
1230     call clean_EAM()
1231     endif
1232    
1233     rf = 0.0_dp
1234     tau_Temp = 0.0_dp
1235     virial_Temp = 0.0_dp
1236     end subroutine zero_work_arrays
1237    
1238     function skipThisPair(atom1, atom2) result(skip_it)
1239     integer, intent(in) :: atom1
1240     integer, intent(in), optional :: atom2
1241     logical :: skip_it
1242     integer :: unique_id_1, unique_id_2
1243     integer :: me_i,me_j
1244     integer :: i
1245    
1246     skip_it = .false.
1247    
1248     !! there are a number of reasons to skip a pair or a particle
1249     !! mostly we do this to exclude atoms who are involved in short
1250     !! range interactions (bonds, bends, torsions), but we also need
1251     !! to exclude some overcounted interactions that result from
1252     !! the parallel decomposition
1253    
1254 mmeineke 377 #ifdef IS_MPI
1255 gezelter 1138 !! in MPI, we have to look up the unique IDs for each atom
1256     unique_id_1 = tagRow(atom1)
1257 mmeineke 377 #else
1258 gezelter 1138 !! in the normal loop, the atom numbers are unique
1259     unique_id_1 = atom1
1260 mmeineke 377 #endif
1261 gezelter 1138
1262     !! We were called with only one atom, so just check the global exclude
1263     !! list for this atom
1264     if (.not. present(atom2)) then
1265     do i = 1, nExcludes_global
1266     if (excludesGlobal(i) == unique_id_1) then
1267     skip_it = .true.
1268     return
1269     end if
1270     end do
1271     return
1272     end if
1273    
1274 mmeineke 377 #ifdef IS_MPI
1275 gezelter 1138 unique_id_2 = tagColumn(atom2)
1276 mmeineke 377 #else
1277 gezelter 1138 unique_id_2 = atom2
1278 mmeineke 377 #endif
1279 gezelter 1138
1280 mmeineke 377 #ifdef IS_MPI
1281 gezelter 1138 !! this situation should only arise in MPI simulations
1282     if (unique_id_1 == unique_id_2) then
1283     skip_it = .true.
1284     return
1285     end if
1286    
1287     !! this prevents us from doing the pair on multiple processors
1288     if (unique_id_1 < unique_id_2) then
1289     if (mod(unique_id_1 + unique_id_2,2) == 0) then
1290     skip_it = .true.
1291     return
1292     endif
1293     else
1294     if (mod(unique_id_1 + unique_id_2,2) == 1) then
1295     skip_it = .true.
1296     return
1297     endif
1298     endif
1299 mmeineke 377 #endif
1300 gezelter 1138
1301     !! the rest of these situations can happen in all simulations:
1302     do i = 1, nExcludes_global
1303     if ((excludesGlobal(i) == unique_id_1) .or. &
1304     (excludesGlobal(i) == unique_id_2)) then
1305     skip_it = .true.
1306     return
1307     endif
1308     enddo
1309    
1310     do i = 1, nExcludes_local
1311     if (excludesLocal(1,i) == unique_id_1) then
1312     if (excludesLocal(2,i) == unique_id_2) then
1313     skip_it = .true.
1314     return
1315     endif
1316     else
1317     if (excludesLocal(1,i) == unique_id_2) then
1318     if (excludesLocal(2,i) == unique_id_1) then
1319     skip_it = .true.
1320     return
1321     endif
1322     endif
1323     endif
1324     end do
1325    
1326     return
1327     end function skipThisPair
1328 chuckv 441
1329 gezelter 1138 function FF_UsesDirectionalAtoms() result(doesit)
1330     logical :: doesit
1331     doesit = FF_uses_dipoles .or. FF_uses_sticky .or. &
1332     FF_uses_GB .or. FF_uses_RF
1333     end function FF_UsesDirectionalAtoms
1334    
1335     function FF_RequiresPrepairCalc() result(doesit)
1336     logical :: doesit
1337     doesit = FF_uses_EAM
1338     end function FF_RequiresPrepairCalc
1339    
1340     function FF_RequiresPostpairCalc() result(doesit)
1341     logical :: doesit
1342     doesit = FF_uses_RF
1343     end function FF_RequiresPostpairCalc
1344    
1345 chuckv 883 #ifdef PROFILE
1346 gezelter 1138 function getforcetime() result(totalforcetime)
1347     real(kind=dp) :: totalforcetime
1348     totalforcetime = forcetime
1349     end function getforcetime
1350 chuckv 883 #endif
1351 gezelter 1138
1352     !! This cleans componets of force arrays belonging only to fortran
1353    
1354 mmeineke 377 end module do_Forces