ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE_old/src/mdtools/libmdCode/do_Forces.F90
Revision: 356
Committed: Mon Mar 17 20:42:57 2003 UTC (21 years, 5 months ago) by gezelter
File size: 19711 byte(s)
Log Message:
fortran-side fixes to play nice with C

File Contents

# User Rev Content
1 chuckv 306 !! do_Forces.F90
2     !! module do_Forces
3 chuckv 292 !! Calculates Long Range forces.
4 chuckv 306
5 chuckv 292 !! @author Charles F. Vardeman II
6     !! @author Matthew Meineke
7 gezelter 356 !! @version $Id: do_Forces.F90,v 1.21 2003-03-17 20:42:57 gezelter Exp $, $Date: 2003-03-17 20:42:57 $, $Name: not supported by cvs2svn $, $Revision: 1.21 $
8 chuckv 292
9     module do_Forces
10     use simulation
11     use definitions
12 gezelter 328 use atype_module
13 gezelter 325 use neighborLists
14 gezelter 330 use lj
15     use sticky_pair
16 gezelter 309 use dipole_dipole
17 gezelter 332 use reaction_field
18 chuckv 292 #ifdef IS_MPI
19     use mpiSimulation
20     #endif
21 gezelter 356
22 chuckv 292 implicit none
23     PRIVATE
24    
25 gezelter 356 #define __FORTRAN90
26     #include "fForceField.h"
27    
28     type (ffstruct), public :: thisFF
29    
30 gezelter 329 logical, save :: do_forces_initialized = .false.
31     logical, save :: FF_uses_LJ
32     logical, save :: FF_uses_sticky
33     logical, save :: FF_uses_dipoles
34     logical, save :: FF_uses_RF
35     logical, save :: FF_uses_GB
36     logical, save :: FF_uses_EAM
37 chuckv 292
38 gezelter 329 public :: init_FF
39 gezelter 330 public :: do_force_loop
40 gezelter 329
41 chuckv 292 contains
42    
43 gezelter 356 subroutine init_FF(setThisFF, thisStat)
44    
45     type (ffstruct) :: setThisFF
46    
47 chuckv 331 integer, intent(out) :: thisStat
48 gezelter 332 integer :: my_status, nMatches
49     integer, pointer :: MatchList(:)
50 gezelter 329
51 gezelter 332 !! assume things are copacetic, unless they aren't
52 chuckv 331 thisStat = 0
53 gezelter 356
54     thisFF = setThisFF
55    
56     !! Fortran's version of a cast:
57     FF_uses_RF = thisFF%use_RF
58 gezelter 332
59     !! init_FF is called *after* all of the atom types have been
60     !! defined in atype_module using the new_atype subroutine.
61     !!
62     !! this will scan through the known atypes and figure out what
63     !! interactions are used by the force field.
64    
65     FF_uses_LJ = .false.
66     FF_uses_sticky = .false.
67     FF_uses_dipoles = .false.
68     FF_uses_GB = .false.
69     FF_uses_EAM = .false.
70    
71     call getMatchingElementList(atypes, "is_LJ", .true., nMatches, MatchList)
72     deallocate(MatchList)
73     if (nMatches .gt. 0) FF_uses_LJ = .true.
74    
75     call getMatchingElementList(atypes, "is_DP", .true., nMatches, MatchList)
76     deallocate(MatchList)
77     if (nMatches .gt. 0) FF_uses_dipoles = .true.
78    
79     call getMatchingElementList(atypes, "is_Sticky", .true., nMatches, &
80     MatchList)
81     deallocate(MatchList)
82     if (nMatches .gt. 0) FF_uses_Sticky = .true.
83    
84     call getMatchingElementList(atypes, "is_GB", .true., nMatches, MatchList)
85     deallocate(MatchList)
86     if (nMatches .gt. 0) FF_uses_GB = .true.
87    
88     call getMatchingElementList(atypes, "is_EAM", .true., nMatches, MatchList)
89     deallocate(MatchList)
90     if (nMatches .gt. 0) FF_uses_EAM = .true.
91    
92 gezelter 356 !! check to make sure the FF_uses_RF setting makes sense
93    
94     if (FF_uses_RF) then
95 gezelter 332 if (FF_uses_dipoles) then
96     call initialize_rf()
97     else
98     write(default_error,*) 'Using Reaction Field with no dipoles? Huh?'
99     thisStat = -1
100     return
101     endif
102     endif
103 gezelter 356
104     if (FF_uses_LJ) then
105    
106     select case (thisFF%LJ_Mixing_Policy)
107     case (thisFF%LB_MIXING_RULE)
108     call init_lj_FF('LB', my_status)
109     case (thiFF%EXPLICIT_MIXING_RULE)
110     call init_lj_FF('Explicity, my_status)
111     case default
112     write(default_error,*) 'unknown LJ Mixing Policy!'
113     thisStat = -1
114     return
115     end select
116     if (my_status /= 0) then
117     thisStat = -1
118     return
119     end if
120     endif
121    
122     if (FF_uses_sticky) then
123     call check_sticky_FF(my_status)
124     if (my_status /= 0) then
125     thisStat = -1
126     return
127     end if
128     endif
129    
130 gezelter 332
131 gezelter 329 do_forces_initialized = .true.
132    
133     end subroutine init_FF
134    
135    
136    
137 gezelter 317 !! Does force loop over i,j pairs. Calls do_pair to calculates forces.
138 gezelter 356 a!------------------------------------------------------------->
139 gezelter 325 subroutine do_force_loop(q, A, u_l, f, t, tau, pot, do_pot_c, do_stress_c, &
140 gezelter 329 error)
141 gezelter 317 !! Position array provided by C, dimensioned by getNlocal
142 chuckv 292 real ( kind = dp ), dimension(3,getNlocal()) :: q
143 gezelter 317 !! Rotation Matrix for each long range particle in simulation.
144 gezelter 325 real( kind = dp), dimension(9,getNlocal()) :: A
145 gezelter 317 !! Unit vectors for dipoles (lab frame)
146 chuckv 292 real( kind = dp ), dimension(3,getNlocal()) :: u_l
147 gezelter 317 !! Force array provided by C, dimensioned by getNlocal
148 chuckv 292 real ( kind = dp ), dimension(3,getNlocal()) :: f
149 gezelter 317 !! Torsion array provided by C, dimensioned by getNlocal
150 gezelter 325 real( kind = dp ), dimension(3,getNlocal()) :: t
151 gezelter 317 !! Stress Tensor
152 gezelter 325 real( kind = dp), dimension(9) :: tau
153     real ( kind = dp ) :: pot
154     logical ( kind = 2) :: do_pot_c, do_stress_c
155 gezelter 329 logical :: do_pot
156     logical :: do_stress
157 gezelter 317 #ifdef IS_MPI
158     real( kind = DP ) :: pot_local
159 gezelter 329 integer :: nrow
160     integer :: ncol
161 gezelter 317 #endif
162 gezelter 330 integer :: nlocal
163 gezelter 329 integer :: natoms
164 gezelter 325 logical :: update_nlist
165     integer :: i, j, jbeg, jend, jnab
166 gezelter 317 integer :: nlist
167 gezelter 325 real( kind = DP ) :: rijsq, rlistsq, rcutsq, rlist, rcut
168 gezelter 330 real(kind=dp),dimension(3) :: d
169     real(kind=dp) :: rfpot, mu_i, virial
170     integer :: me_i
171     logical :: is_dp_i
172 gezelter 317 integer :: neighborListSize
173 gezelter 330 integer :: listerror, error
174 chuckv 331 integer :: localError
175 chuckv 292
176 gezelter 329 !! initialize local variables
177 gezelter 325
178 chuckv 292 #ifdef IS_MPI
179 gezelter 329 nlocal = getNlocal()
180     nrow = getNrow(plan_row)
181     ncol = getNcol(plan_col)
182     #else
183     nlocal = getNlocal()
184     natoms = nlocal
185 chuckv 292 #endif
186 gezelter 329
187 chuckv 331 call getRcut(rcut,rc2=rcutsq)
188 gezelter 317 call getRlist(rlist,rlistsq)
189    
190 chuckv 331 call check_initialization(localError)
191     if ( localError .ne. 0 ) then
192     error = -1
193     return
194     end if
195 gezelter 329 call zero_work_arrays()
196    
197     do_pot = do_pot_c
198     do_stress = do_stress_c
199    
200     ! Gather all information needed by all force loops:
201 gezelter 317
202 gezelter 329 #ifdef IS_MPI
203 chuckv 292
204 gezelter 309 call gather(q,q_Row,plan_row3d)
205     call gather(q,q_Col,plan_col3d)
206 gezelter 329
207     if (FF_UsesDirectionalAtoms() .and. SimUsesDirectionalAtoms()) then
208     call gather(u_l,u_l_Row,plan_row3d)
209     call gather(u_l,u_l_Col,plan_col3d)
210    
211     call gather(A,A_Row,plan_row_rotation)
212     call gather(A,A_Col,plan_col_rotation)
213     endif
214 gezelter 317
215 gezelter 329 #endif
216 gezelter 317
217 gezelter 329 if (FF_RequiresPrepairCalc() .and. SimRequiresPrepairCalc()) then
218     !! See if we need to update neighbor lists
219     call checkNeighborList(nlocal, q, rcut, rlist, update_nlist)
220     !! if_mpi_gather_stuff_for_prepair
221     !! do_prepair_loop_if_needed
222     !! if_mpi_scatter_stuff_from_prepair
223     !! if_mpi_gather_stuff_from_prepair_to_main_loop
224     else
225     !! See if we need to update neighbor lists
226     call checkNeighborList(nlocal, q, rcut, rlist, update_nlist)
227     endif
228    
229 gezelter 297 #ifdef IS_MPI
230 chuckv 292
231 gezelter 297 if (update_nlist) then
232    
233 gezelter 329 !! save current configuration, construct neighbor list,
234     !! and calculate forces
235 gezelter 334 call saveNeighborList(q)
236 gezelter 297
237     neighborListSize = getNeighborListSize()
238 gezelter 329 nlist = 0
239 gezelter 297
240     do i = 1, nrow
241     point(i) = nlist + 1
242    
243     inner: do j = 1, ncol
244    
245 gezelter 334 if (skipThisPair(i,j)) cycle inner
246 gezelter 329
247 gezelter 317 call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
248 gezelter 330
249 gezelter 297 if (rijsq < rlistsq) then
250    
251     nlist = nlist + 1
252    
253     if (nlist > neighborListSize) then
254 gezelter 325 call expandNeighborList(nlocal, listerror)
255 gezelter 297 if (listerror /= 0) then
256 gezelter 329 error = -1
257 gezelter 297 write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
258     return
259     end if
260     endif
261    
262     list(nlist) = j
263 gezelter 317
264 gezelter 297 if (rijsq < rcutsq) then
265 gezelter 356 call do_pair(i, j, rijsq, d, do_pot, do_stress, &
266     u_l, A, f, t)
267 gezelter 297 endif
268     endif
269     enddo inner
270     enddo
271 chuckv 292
272 gezelter 297 point(nrow + 1) = nlist + 1
273    
274 gezelter 329 else !! (of update_check)
275 chuckv 292
276 gezelter 297 ! use the list to find the neighbors
277     do i = 1, nrow
278     JBEG = POINT(i)
279     JEND = POINT(i+1) - 1
280     ! check thiat molecule i has neighbors
281     if (jbeg .le. jend) then
282 gezelter 317
283 gezelter 297 do jnab = jbeg, jend
284     j = list(jnab)
285 gezelter 317
286     call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
287 gezelter 356 call do_pair(i, j, rijsq, d, do_pot, do_stress, &
288     u_l, A, f, t)
289 gezelter 317
290 gezelter 297 enddo
291     endif
292     enddo
293     endif
294 gezelter 329
295 gezelter 297 #else
296    
297     if (update_nlist) then
298 chuckv 292
299 gezelter 297 ! save current configuration, contruct neighbor list,
300     ! and calculate forces
301 gezelter 334 call saveNeighborList(q)
302 gezelter 297
303     neighborListSize = getNeighborListSize()
304     nlist = 0
305 gezelter 329
306 gezelter 297 do i = 1, natoms-1
307     point(i) = nlist + 1
308 gezelter 329
309 gezelter 297 inner: do j = i+1, natoms
310 gezelter 329
311 gezelter 334 if (skipThisPair(i,j)) cycle inner
312 gezelter 329
313 gezelter 317 call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
314 chuckv 295
315 gezelter 297 if (rijsq < rlistsq) then
316 gezelter 317
317 gezelter 297 nlist = nlist + 1
318    
319     if (nlist > neighborListSize) then
320 gezelter 325 call expandList(natoms, listerror)
321 gezelter 297 if (listerror /= 0) then
322 gezelter 329 error = -1
323 gezelter 297 write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
324     return
325     end if
326     endif
327    
328     list(nlist) = j
329 gezelter 329
330 gezelter 297 if (rijsq < rcutsq) then
331 gezelter 356 call do_pair(i, j, rijsq, d, do_pot, do_stress, &
332     u_l, A, f, t)
333 gezelter 297 endif
334     endif
335 chuckv 292 enddo inner
336 gezelter 297 enddo
337    
338     point(natoms) = nlist + 1
339    
340     else !! (update)
341    
342     ! use the list to find the neighbors
343 gezelter 330 do i = 1, natoms-1
344 gezelter 297 JBEG = POINT(i)
345     JEND = POINT(i+1) - 1
346     ! check thiat molecule i has neighbors
347     if (jbeg .le. jend) then
348    
349     do jnab = jbeg, jend
350     j = list(jnab)
351 gezelter 317
352     call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
353 gezelter 356 call do_pair(i, j, rijsq, d, do_pot, do_stress, &
354     u_l, A, f, t)
355 gezelter 317
356 gezelter 297 enddo
357     endif
358     enddo
359     endif
360 gezelter 317
361 gezelter 297 #endif
362 gezelter 317
363 gezelter 329 ! phew, done with main loop.
364 gezelter 317
365 chuckv 292 #ifdef IS_MPI
366 gezelter 329 !!distribute forces
367 gezelter 317
368 gezelter 309 call scatter(f_Row,f,plan_row3d)
369     call scatter(f_Col,f_temp,plan_col3d)
370 chuckv 295 do i = 1,nlocal
371 gezelter 309 f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
372 chuckv 295 end do
373 gezelter 329
374     if (FF_UsesDirectionalAtoms() .and. SimUsesDirectionalAtoms()) then
375 gezelter 309 call scatter(t_Row,t,plan_row3d)
376     call scatter(t_Col,t_temp,plan_col3d)
377 gezelter 329
378 chuckv 295 do i = 1,nlocal
379 gezelter 309 t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
380 chuckv 295 end do
381     endif
382 gezelter 309
383 chuckv 295 if (do_pot) then
384     ! scatter/gather pot_row into the members of my column
385 gezelter 309 call scatter(pot_Row, pot_Temp, plan_row)
386 chuckv 295
387     ! scatter/gather pot_local into all other procs
388     ! add resultant to get total pot
389     do i = 1, nlocal
390 gezelter 309 pot_local = pot_local + pot_Temp(i)
391 chuckv 295 enddo
392    
393 gezelter 309 pot_Temp = 0.0_DP
394    
395     call scatter(pot_Col, pot_Temp, plan_col)
396 chuckv 295 do i = 1, nlocal
397 gezelter 309 pot_local = pot_local + pot_Temp(i)
398 chuckv 295 enddo
399    
400 gezelter 330 endif
401     #endif
402    
403 gezelter 329 if (FF_RequiresPostpairCalc() .and. SimRequiresPostpairCalc()) then
404    
405     if (FF_uses_RF .and. SimUsesRF()) then
406    
407     #ifdef IS_MPI
408     call scatter(rf_Row,rf,plan_row3d)
409     call scatter(rf_Col,rf_Temp,plan_col3d)
410     do i = 1,nlocal
411     rf(1:3,i) = rf(1:3,i) + rf_Temp(1:3,i)
412     end do
413     #endif
414    
415     do i = 1, getNlocal()
416    
417 gezelter 330 rfpot = 0.0_DP
418 gezelter 329 #ifdef IS_MPI
419     me_i = atid_row(i)
420     #else
421     me_i = atid(i)
422     #endif
423     call getElementProperty(atypes, me_i, "is_DP", is_DP_i)
424     if ( is_DP_i ) then
425     call getElementProperty(atypes, me_i, "dipole_moment", mu_i)
426     !! The reaction field needs to include a self contribution
427     !! to the field:
428     call accumulate_self_rf(i, mu_i, u_l)
429     !! Get the reaction field contribution to the
430     !! potential and torques:
431 gezelter 330 call reaction_field_final(i, mu_i, u_l, rfpot, t, do_pot)
432 gezelter 329 #ifdef IS_MPI
433     pot_local = pot_local + rfpot
434     #else
435     pot = pot + rfpot
436     #endif
437     endif
438     enddo
439     endif
440     endif
441    
442    
443     #ifdef IS_MPI
444    
445     if (do_pot) then
446 gezelter 309 pot = pot_local
447 gezelter 329 !! we assume the c code will do the allreduce to get the total potential
448     !! we could do it right here if we needed to...
449 chuckv 295 endif
450    
451 gezelter 329 if (do_stress) then
452 gezelter 330 call mpi_allreduce(tau, tau_Temp,9,mpi_double_precision,mpi_sum, &
453 gezelter 309 mpi_comm_world,mpi_err)
454 gezelter 330 call mpi_allreduce(virial, virial_Temp,1,mpi_double_precision,mpi_sum, &
455 gezelter 309 mpi_comm_world,mpi_err)
456     endif
457 chuckv 295
458 gezelter 329 #else
459 chuckv 295
460 gezelter 329 if (do_stress) then
461 gezelter 309 tau = tau_Temp
462     virial = virial_Temp
463 chuckv 295 endif
464    
465 gezelter 329 #endif
466    
467 chuckv 295 end subroutine do_force_loop
468    
469 gezelter 356 subroutine do_pair(i, j, rijsq, d, do_pot, do_stress, u_l, A, f, t)
470 chuckv 295
471 gezelter 330 real( kind = dp ) :: pot
472     real( kind = dp ), dimension(3,getNlocal()) :: u_l
473     real (kind=dp), dimension(9,getNlocal()) :: A
474     real (kind=dp), dimension(3,getNlocal()) :: f
475     real (kind=dp), dimension(3,getNlocal()) :: t
476    
477 gezelter 329 logical, intent(inout) :: do_pot, do_stress
478 gezelter 317 integer, intent(in) :: i, j
479 chuckv 331 real ( kind = dp ), intent(inout) :: rijsq
480 gezelter 317 real ( kind = dp ) :: r
481     real ( kind = dp ), intent(inout) :: d(3)
482     logical :: is_LJ_i, is_LJ_j
483     logical :: is_DP_i, is_DP_j
484     logical :: is_Sticky_i, is_Sticky_j
485     integer :: me_i, me_j
486 chuckv 295
487 gezelter 330 r = sqrt(rijsq)
488    
489 gezelter 302 #ifdef IS_MPI
490    
491 gezelter 317 me_i = atid_row(i)
492     me_j = atid_col(j)
493 chuckv 295
494 gezelter 317 #else
495 chuckv 295
496 gezelter 317 me_i = atid(i)
497     me_j = atid(j)
498 gezelter 302
499 gezelter 317 #endif
500 gezelter 302
501 gezelter 329 if (FF_uses_LJ .and. SimUsesLJ()) then
502     call getElementProperty(atypes, me_i, "is_LJ", is_LJ_i)
503     call getElementProperty(atypes, me_j, "is_LJ", is_LJ_j)
504    
505     if ( is_LJ_i .and. is_LJ_j ) &
506     call do_lj_pair(i, j, d, r, rijsq, pot, f, do_pot, do_stress)
507     endif
508    
509 gezelter 330 if (FF_uses_dipoles .and. SimUsesDipoles()) then
510 gezelter 329 call getElementProperty(atypes, me_i, "is_DP", is_DP_i)
511     call getElementProperty(atypes, me_j, "is_DP", is_DP_j)
512    
513     if ( is_DP_i .and. is_DP_j ) then
514    
515     call do_dipole_pair(i, j, d, r, pot, u_l, f, t, do_pot, do_stress)
516    
517     if (FF_uses_RF .and. SimUsesRF()) then
518    
519     call accumulate_rf(i, j, r, u_l)
520     call rf_correct_forces(i, j, d, r, u_l, f, do_stress)
521    
522     endif
523    
524 gezelter 297 endif
525     endif
526    
527 gezelter 329 if (FF_uses_Sticky .and. SimUsesSticky()) then
528 gezelter 317
529 gezelter 329 call getElementProperty(atypes, me_i, "is_Sticky", is_Sticky_i)
530     call getElementProperty(atypes, me_j, "is_Sticky", is_Sticky_j)
531    
532     if ( is_Sticky_i .and. is_Sticky_j ) then
533     call do_sticky_pair(i, j, d, r, rijsq, A, pot, f, t, &
534     do_pot, do_stress)
535     endif
536 gezelter 297 endif
537 gezelter 309
538 chuckv 295 end subroutine do_pair
539 chuckv 292
540    
541 gezelter 317 subroutine get_interatomic_vector(q_i, q_j, d, r_sq)
542    
543 chuckv 295 real (kind = dp), dimension(3) :: q_i
544     real (kind = dp), dimension(3) :: q_j
545     real ( kind = dp ), intent(out) :: r_sq
546     real( kind = dp ) :: d(3)
547    
548     d(1:3) = q_i(1:3) - q_j(1:3)
549 gezelter 317
550     ! Wrap back into periodic box if necessary
551 gezelter 330 if ( SimUsesPBC() ) then
552     d(1:3) = d(1:3) - box(1:3) * sign(1.0_dp,box(1:3)) * &
553     int(abs(d(1:3)/box(1:3) + 0.5_dp))
554 gezelter 317 endif
555 chuckv 292
556 chuckv 295 r_sq = dot_product(d,d)
557 gezelter 317
558 chuckv 295 end subroutine get_interatomic_vector
559 gezelter 329
560     subroutine check_initialization(error)
561     integer, intent(out) :: error
562 gezelter 332
563 gezelter 329 error = 0
564     ! Make sure we are properly initialized.
565 gezelter 332 if (.not. do_forces_initialized) then
566 gezelter 329 write(default_error,*) "ERROR: do_Forces has not been initialized!"
567     error = -1
568     return
569     endif
570 gezelter 332
571 gezelter 329 #ifdef IS_MPI
572     if (.not. isMPISimSet()) then
573     write(default_error,*) "ERROR: mpiSimulation has not been initialized!"
574     error = -1
575     return
576     endif
577     #endif
578 gezelter 332
579 gezelter 329 return
580     end subroutine check_initialization
581    
582 gezelter 317
583 gezelter 325 subroutine zero_work_arrays()
584    
585     #ifdef IS_MPI
586 chuckv 292
587 gezelter 325 q_Row = 0.0_dp
588     q_Col = 0.0_dp
589 chuckv 295
590 gezelter 325 u_l_Row = 0.0_dp
591     u_l_Col = 0.0_dp
592 chuckv 295
593 gezelter 325 A_Row = 0.0_dp
594     A_Col = 0.0_dp
595 chuckv 295
596 gezelter 325 f_Row = 0.0_dp
597     f_Col = 0.0_dp
598     f_Temp = 0.0_dp
599    
600     t_Row = 0.0_dp
601     t_Col = 0.0_dp
602     t_Temp = 0.0_dp
603 chuckv 295
604 gezelter 325 pot_Row = 0.0_dp
605     pot_Col = 0.0_dp
606     pot_Temp = 0.0_dp
607 chuckv 292
608 gezelter 332 rf_Row = 0.0_dp
609     rf_Col = 0.0_dp
610     rf_Temp = 0.0_dp
611    
612 chuckv 295 #endif
613 chuckv 292
614 gezelter 332 rf = 0.0_dp
615 gezelter 325 tau_Temp = 0.0_dp
616     virial_Temp = 0.0_dp
617    
618     end subroutine zero_work_arrays
619    
620 gezelter 334 function skipThisPair(atom1, atom2) result(skip_it)
621 gezelter 332
622 gezelter 334 integer, intent(in) :: atom1
623     integer, intent(in), optional :: atom2
624     logical :: skip_it
625 gezelter 332 integer :: unique_id_1, unique_id_2
626 gezelter 334 integer :: i
627 gezelter 332
628 gezelter 334 skip_it = .false.
629    
630     !! there are a number of reasons to skip a pair or a particle
631     !! mostly we do this to exclude atoms who are involved in short
632     !! range interactions (bonds, bends, torsions), but we also need
633     !! to exclude some overcounted interactions that result from
634     !! the parallel decomposition
635 gezelter 330
636 chuckv 306 #ifdef IS_MPI
637 gezelter 334 !! in MPI, we have to look up the unique IDs for each atom
638 gezelter 332 unique_id_1 = tagRow(atom1)
639 chuckv 306 #else
640 gezelter 334 !! in the normal loop, the atom numbers are unique
641     unique_id_1 = atom1
642 chuckv 306 #endif
643 gezelter 330
644 gezelter 334 !! We were called with only one atom, so just check the global exclude
645     !! list for this atom
646 chuckv 306 if (.not. present(atom2)) then
647 gezelter 330 do i = 1, nExcludes_global
648 gezelter 332 if (excludesGlobal(i) == unique_id_1) then
649 gezelter 334 skip_it = .true.
650 chuckv 306 return
651     end if
652     end do
653 gezelter 334 return
654 chuckv 306 end if
655 gezelter 330
656 gezelter 332 #ifdef IS_MPI
657     unique_id_2 = tagColumn(atom2)
658     #else
659 gezelter 334 unique_id_2 = atom2
660 gezelter 332 #endif
661    
662 gezelter 334 #ifdef IS_MPI
663     !! this situation should only arise in MPI simulations
664 gezelter 332 if (unique_id_1 == unique_id_2) then
665 gezelter 334 skip_it = .true.
666 chuckv 295 return
667     end if
668 gezelter 330
669 gezelter 334 !! this prevents us from doing the pair on multiple processors
670 gezelter 332 if (unique_id_1 < unique_id_2) then
671 gezelter 334 if (mod(unique_id_1 + unique_id_2,2) == 0) skip_it = .true.
672 chuckv 295 return
673     else
674 gezelter 334 if (mod(unique_id_1 + unique_id_2,2) == 1) skip_it = .true.
675 chuckv 295 endif
676 gezelter 334 #endif
677    
678     !! the rest of these situations can happen in all simulations:
679     do i = 1, nExcludes_global
680     if ((excludesGlobal(i) == unique_id_1) .or. &
681     (excludesGlobal(i) == unique_id_2)) then
682     skip_it = .true.
683     return
684     endif
685     enddo
686 gezelter 332
687 gezelter 330 do i = 1, nExcludes_local
688 gezelter 334 if (excludesLocal(1,i) == unique_id_1) then
689     if (excludesLocal(2,i) == unique_id_2) then
690     skip_it = .true.
691     return
692     endif
693     else
694     if (excludesLocal(1,i) == unique_id_2) then
695     if (excludesLocal(2,i) == unique_id_1) then
696     skip_it = .true.
697     return
698     endif
699     endif
700     endif
701 chuckv 306 end do
702 gezelter 330
703 gezelter 334 return
704     end function skipThisPair
705 chuckv 306
706 gezelter 329 function FF_UsesDirectionalAtoms() result(doesit)
707     logical :: doesit
708     doesit = FF_uses_dipoles .or. FF_uses_sticky .or. &
709     FF_uses_GB .or. FF_uses_RF
710     end function FF_UsesDirectionalAtoms
711    
712     function FF_RequiresPrepairCalc() result(doesit)
713     logical :: doesit
714     doesit = FF_uses_EAM
715     end function FF_RequiresPrepairCalc
716    
717     function FF_RequiresPostpairCalc() result(doesit)
718     logical :: doesit
719     doesit = FF_uses_RF
720     end function FF_RequiresPostpairCalc
721    
722 chuckv 292 end module do_Forces