ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE_old/src/mdtools/libmdCode/do_Forces.F90
(Generate patch)

Comparing trunk/OOPSE_old/src/mdtools/libmdCode/do_Forces.F90 (file contents):
Revision 325 by gezelter, Wed Mar 12 19:10:54 2003 UTC vs.
Revision 334 by gezelter, Thu Mar 13 17:45:54 2003 UTC

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

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines