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 295 by chuckv, Thu Mar 6 19:57:03 2003 UTC vs.
Revision 306 by chuckv, Mon Mar 10 19:26:45 2003 UTC

# Line 1 | Line 1
1 + !! do_Forces.F90
2 + !! module do_Forces
3   !! Calculates Long Range forces.
4 +
5   !! @author Charles F. Vardeman II
6   !! @author Matthew Meineke
7 < !! @version $Id: do_Forces.F90,v 1.3 2003-03-06 19:57:03 chuckv Exp $, $Date: 2003-03-06 19:57:03 $, $Name: not supported by cvs2svn $, $Revision: 1.3 $
7 > !! @version $Id: do_Forces.F90,v 1.8 2003-03-10 19:26:45 chuckv Exp $, $Date: 2003-03-10 19:26:45 $, $Name: not supported by cvs2svn $, $Revision: 1.8 $
8  
9  
10  
11   module do_Forces
12    use simulation
13    use definitions
14 <  use generic_atypes
14 >  use forceGlobals
15 >  use atype_typedefs
16    use neighborLists
17 +
18    
19    use lj_FF
20    use sticky_FF
# Line 22 | Line 27 | module do_Forces
27    implicit none
28    PRIVATE
29  
30 < !! Number of lj_atypes in lj_atype_list
26 <  integer, save :: n_atypes = 0
30 > public :: do_force_loop
31  
28 !! Global list of lj atypes in simulation
29  type (atype), pointer :: ListHead => null()
30  type (atype), pointer :: ListTail => null()
31
32
33
34
35  logical, save :: firstTime = .True.
36
37 !! Atype identity pointer lists
38 #ifdef IS_MPI
39 !! Row lj_atype pointer list
40  type (identPtrList), dimension(:), pointer :: identPtrListRow => null()
41 !! Column lj_atype pointer list
42  type (identPtrList), dimension(:), pointer :: identPtrListColumn => null()
43 #else
44  type(identPtrList ), dimension(:), pointer :: identPtrList => null()
45 #endif
46
47
48 !! Logical has lj force field module been initialized?
49  logical, save :: isFFinit = .false.
50
51 !! Use periodic boundry conditions
52  logical :: wrap = .false.
53
54 !! Potential energy global module variables
55 #ifdef IS_MPI
56  real(kind = dp), dimension(3,getNrow(plan_row)) :: qRow = 0.0_dp
57  real(kind = dp), dimension(3,getNcol(plan_col)) :: qCol = 0.0_dp
58
59  real(kind = dp), dimension(3,getNrow(plan_row)) :: muRow = 0.0_dp
60  real(kind = dp), dimension(3,getNcol(plan_col)) :: muCol = 0.0_dp
61
62  real(kind = dp), dimension(3,getNrow(plan_row)) :: u_lRow = 0.0_dp
63  real(kind = dp), dimension(3,getNcol(plan_col)) :: u_lCol = 0.0_dp
64
65  real(kind = dp), dimension(3,getNrow(plan_row)) :: ARow = 0.0_dp
66  real(kind = dp), dimension(3,getNcol(plan_col)) :: ACol = 0.0_dp
67
68  
69
70  real(kind = dp), dimension(3,getNrow(plan_row)) :: fRow = 0.0_dp
71  real(kind = dp), dimension(3,getNcol(plan_col)) :: fCol = 0.0_dp
72
73
74  real(kind = dp), dimension(3,getNrow(plan_row)) :: tRow = 0.0_dp
75  real(kind = dp), dimension(3,getNcol(plan_col)) :: tCol = 0.0_dp
76
77
78
79  real(kind = dp), dimension(getNrow(plan_row)) :: eRow = 0.0_dp
80  real(kind = dp), dimension(getNcol(plan_col)) :: eCol = 0.0_dp
81
82  real(kind = dp), dimension(getNlocal()) :: eTemp = 0.0_dp
83 #endif
84  real(kind = dp) :: pe = 0.0_dp
85  real(kind = dp), dimension(3,getNlocal()) :: fTemp = 0.0_dp
86  real(kind = dp), dimension(3,getNlocal()) :: tTemp = 0.0_dp
87  real(kind = dp), dimension(9) :: tauTemp = 0.0_dp
88
89  logical :: do_preForce  = .false.
90  logical :: do_postForce = .false.
91
92
93
94 !! Public methods and data
95  public :: new_atype
96  public :: do_forceLoop
97  public :: init_FF
98
99  
100
101
32   contains
33  
34 < !! Adds a new lj_atype to the list.
105 <  subroutine new_atype(ident,mass,epsilon,sigma, &
106 <       is_LJ,is_Sticky,is_DP,is_GB,w0,v0,dipoleMoment,status)
107 <    real( kind = dp ), intent(in) :: mass
108 <    real( kind = dp ), intent(in) :: epsilon
109 <    real( kind = dp ), intent(in) :: sigma
110 <    real( kind = dp ), intent(in) :: w0
111 <    real( kind = dp ), intent(in) :: v0
112 <    real( kind = dp ), intent(in) :: dipoleMoment
113 <
114 <    integer, intent(in) :: ident
115 <    integer, intent(out) :: status
116 <    integer, intent(in) :: is_Sticky
117 <    integer, intent(in) :: is_DP
118 <    integer, intent(in) :: is_GB
119 <    integer, intent(in) :: is_LJ
120 <
121 <
122 <    type (atype), pointer :: the_new_atype
123 <    integer :: alloc_error
124 <    integer :: atype_counter = 0
125 <    integer :: alloc_size
126 <    integer :: err_stat
127 <    status = 0
128 <
129 <
130 <
131 < ! allocate a new atype    
132 <    allocate(the_new_atype,stat=alloc_error)
133 <    if (alloc_error /= 0 ) then
134 <       status = -1
135 <       return
136 <    end if
137 <
138 < ! assign our new atype information
139 <    the_new_atype%mass        = mass
140 <    the_new_atype%epsilon     = epsilon
141 <    the_new_atype%sigma       = sigma
142 <    the_new_atype%sigma2      = sigma * sigma
143 <    the_new_atype%sigma6      = the_new_atype%sigma2 * the_new_atype%sigma2 &
144 <         * the_new_atype%sigma2
145 <    the_new_atype%w0       = w0
146 <    the_new_atype%v0       = v0
147 <    the_new_atype%dipoleMoment       = dipoleMoment
148 <
149 <    
150 < ! assume that this atype will be successfully added
151 <    the_new_atype%atype_ident = ident
152 <    the_new_atype%atype_number = n_lj_atypes + 1
153 <    
154 <    if ( is_Sticky /= 0 )    the_new_atype%is_Sticky   = .true.
155 <    if ( is_GB /= 0 )        the_new_atype%is_GB       = .true.
156 <    if ( is_LJ /= 0 )        the_new_atype%is_LJ       = .true.
157 <    if ( is_DP /= 0 )        the_new_atype%is_DP       = .true.
158 <
159 <    call add_atype(the_new_atype,ListHead,ListTail,err_stat)
160 <    if (err_stat /= 0 ) then
161 <       status = -1
162 <       return
163 <    endif
164 <
165 <    n_atypes = n_atypes + 1
166 <
167 <
168 <  end subroutine new_atype
169 <
170 <
171 <  subroutine init_FF(nComponents,ident, status)
172 < !! Number of components in ident array
173 <    integer, intent(inout) :: nComponents
174 < !! Array of identities nComponents long corresponding to
175 < !! ljatype ident.
176 <    integer, dimension(nComponents),intent(inout) :: ident
177 < !!  Result status, success = 0, error = -1
178 <    integer, intent(out) :: Status
179 <
180 <    integer :: alloc_stat
181 <
182 <    integer :: thisStat
183 <    integer :: i
184 <
185 <    integer :: myNode
186 < #ifdef IS_MPI
187 <    integer, allocatable, dimension(:) :: identRow
188 <    integer, allocatable, dimension(:) :: identCol
189 <    integer :: nrow
190 <    integer :: ncol
191 < #endif
192 <    status = 0
193 <  
194 <
195 <    
196 <
197 < !! if were're not in MPI, we just update ljatypePtrList
198 < #ifndef IS_MPI
199 <    call create_IdentPtrlst(ident,ListHead,identPtrList,thisStat)
200 <    if ( thisStat /= 0 ) then
201 <       status = -1
202 <       return
203 <    endif
204 <
205 <    
206 < ! if were're in MPI, we also have to worry about row and col lists    
207 < #else
208 <  
209 < ! We can only set up forces if mpiSimulation has been setup.
210 <    if (.not. isMPISimSet()) then
211 <       write(default_error,*) "MPI is not set"
212 <       status = -1
213 <       return
214 <    endif
215 <    nrow = getNrow(plan_row)
216 <    ncol = getNcol(plan_col)
217 <    mynode = getMyNode()
218 < !! Allocate temperary arrays to hold gather information
219 <    allocate(identRow(nrow),stat=alloc_stat)
220 <    if (alloc_stat /= 0 ) then
221 <       status = -1
222 <       return
223 <    endif
224 <
225 <    allocate(identCol(ncol),stat=alloc_stat)
226 <    if (alloc_stat /= 0 ) then
227 <       status = -1
228 <       return
229 <    endif
230 <
231 < !! Gather idents into row and column idents
232 <
233 <    call gather(ident,identRow,plan_row)
234 <    call gather(ident,identCol,plan_col)
235 <    
236 <  
237 < !! Create row and col pointer lists
238 <  
239 <    call create_IdentPtrlst(identRow,ListHead,identPtrListRow,thisStat)
240 <    if (thisStat /= 0 ) then
241 <       status = -1
242 <       return
243 <    endif
244 <  
245 <    call create_IdentPtrlst(identCol,ListHead,identPtrListColumn,thisStat)
246 <    if (thisStat /= 0 ) then
247 <       status = -1
248 <       return
249 <    endif
250 <
251 < !! free temporary ident arrays
252 <    if (allocated(identCol)) then
253 <       deallocate(identCol)
254 <    end if
255 <    if (allocated(identCol)) then
256 <       deallocate(identRow)
257 <    endif
258 <
259 < #endif
260 <    
261 <    call initForce_Modules(thisStat)
262 <    if (thisStat /= 0) then
263 <       status = -1
264 <       return
265 <    endif
266 <
267 < !! Create neighbor lists
268 <    call expandList(thisStat)
269 <    if (thisStat /= 0) then
270 <       status = -1
271 <       return
272 <    endif
273 <
274 <    isFFinit = .true.
275 <
276 <
277 <  end subroutine init_FF
278 <
279 <
280 <
281 <
282 <  subroutine initForce_Modules(thisStat)
283 <    integer, intent(out) :: thisStat
284 <    integer :: my_status
285 <    
286 <    thisStat = 0
287 <    call init_lj_FF(ListHead,my_status)
288 <    if (my_status /= 0) then
289 <       thisStat = -1
290 <       return
291 <    end if
292 <
293 <  end subroutine initForce_Modules
294 <
295 <
296 <
297 <
298 < !! FORCE routine Calculates Lennard Jones forces.
34 > !! Does force loop over i,j pairs. Calls do_pair to calculates forces.
35   !------------------------------------------------------------->
36 <  subroutine do__force_loop(q,A,mu,u_l,f,t,tau,potE,do_pot,FFerror)
36 >  subroutine do_force_loop(q,A,mu,u_l,f,t,tau,potE,do_pot,FFerror)
37   !! Position array provided by C, dimensioned by getNlocal
38      real ( kind = dp ), dimension(3,getNlocal()) :: q
39    !! Rotation Matrix for each long range particle in simulation.
# Line 350 | Line 86 | contains
86    real( kind = DP ) ::  rx_ij, ry_ij, rz_ij, rijsq
87    real( kind = DP ) ::  rlistsq, rcutsq,rlist,rcut
88  
89 <  real( kind = DP ) :: dielectric = 0.0_dp
89 >  
90  
91   ! a rig that need to be fixed.
92   #ifdef IS_MPI
# Line 393 | Line 129 | contains
129    if (isPBC()) wrap = .true.
130  
131  
396 #ifndef IS_MPI
397  nrow = natoms - 1
398  ncol = natoms
399 #else
400  nrow = getNrow(plan_row)
401  ncol = getNcol(plan_col)
402  nlocal = natoms
403  j_start = 1
404 #endif
132  
133    
134   !! See if we need to update neighbor lists
# Line 431 | Line 158 | contains
158   #endif
159  
160  
434  if (update_nlist) then
435
436     ! save current configuration, contruct neighbor list,
437     ! and calculate forces
438     call save_neighborList(q)
439    
440     neighborListSize = getNeighborListSize()
441     nlist = 0
442    
443    
444
445     do i = 1, nrow
446        point(i) = nlist + 1
161   #ifdef IS_MPI
162 <        Atype_i => identPtrListRow(i)%this
163 <        tag_i = tagRow(i)
164 < #else
165 <        Atype_i   => identPtrList(i)%this
166 <        j_start = i + 1
167 < #endif
162 >    
163 >    if (update_nlist) then
164 >      
165 >       ! save current configuration, contruct neighbor list,
166 >       ! and calculate forces
167 >       call save_neighborList(q)
168 >      
169 >       neighborListSize = getNeighborListSize()
170 >       nlist = 0
171 >      
172 >       nrow = getNrow(plan_row)
173 >       ncol = getNcol(plan_col)
174 >       nlocal = getNlocal()
175 >      
176 >       do i = 1, nrow
177 >          point(i) = nlist + 1
178 >          Atype_i => identPtrListRow(i)%this
179 >          
180 >          inner: do j = 1, ncol
181 >             Atype_j => identPtrListColumn(j)%this
182 >            
183 >             call get_interatomic_vector(i,j,qRow(:,i),qCol(:,j),&
184 >                  rxij,ryij,rzij,rijsq,r)
185 >            
186 >             ! skip the loop if the atoms are identical
187 >             if (mpi_cycle_jLoop(i,j)) cycle inner:
188 >            
189 >             if (rijsq <  rlistsq) then            
190 >                
191 >                nlist = nlist + 1
192 >                
193 >                if (nlist > neighborListSize) then
194 >                   call expandList(listerror)
195 >                   if (listerror /= 0) then
196 >                      FFerror = -1
197 >                      write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
198 >                      return
199 >                   end if
200 >                endif
201 >                
202 >                list(nlist) = j
203 >                
204 >                
205 >                if (rijsq <  rcutsq) then
206 >                   call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
207 >                endif
208 >             endif
209 >          enddo inner
210 >       enddo
211  
212 <        inner: do j = j_start, ncol
456 < ! Assign identity pointers and tags
457 < #ifdef IS_MPI
458 <           Atype_j => identPtrListColumn(j)%this
459 <          
460 <           call get_interatomic_vector(i,j,qRow(:,i),qCol(:,j),&
461 <                rxij,ryij,rzij,rijsq,r)
462 < !! For mpi, use newtons 3rd law when building neigbor list
463 < !! Also check to see the particle i != j.
464 <           if (mpi_cycle_jLoop(i,j)) cycle inner:
465 <
466 < #else          
467 <           Atype_j   => identPtrList(j)%this
468 <           call get_interatomic_vector(i,j,q(:,i),q(:,j),&
469 <                rxij,ryij,rzij,rijsq,r)
212 >       point(nrow + 1) = nlist + 1
213        
214 < #endif          
472 <          
473 <           if (rijsq <  rlistsq) then
214 >    else !! (update)
215  
216 <              nlist = nlist + 1
216 >       ! use the list to find the neighbors
217 >       do i = 1, nrow
218 >          JBEG = POINT(i)
219 >          JEND = POINT(i+1) - 1
220 >          ! check thiat molecule i has neighbors
221 >          if (jbeg .le. jend) then
222  
223 <              if (nlist > neighborListSize) then
224 <                 call expandList(listerror)
225 <                 if (listerror /= 0) then
226 <                    FFerror = -1
227 <                    write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
228 <                    return
229 <                 end if
230 <              endif
223 >             Atype_i => identPtrListRow(i)%this
224 >             do jnab = jbeg, jend
225 >                j = list(jnab)
226 >                Atype_j = identPtrListColumn(j)%this
227 >                call get_interatomic_vector(i,j,qRow(:,i),qCol(:,j),&
228 >                     rxij,ryij,rzij,rijsq,r)
229 >                
230 >                call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
231 >             enddo
232 >          endif
233 >       enddo
234 >    endif
235  
236 <              list(nlist) = j
236 > #else
237 >    
238 >    if (update_nlist) then
239 >      
240 >       ! save current configuration, contruct neighbor list,
241 >       ! and calculate forces
242 >       call save_neighborList(q)
243 >      
244 >       neighborListSize = getNeighborListSize()
245 >       nlist = 0
246 >      
247 >    
248 >       do i = 1, natoms-1
249 >          point(i) = nlist + 1
250 >          Atype_i   => identPtrList(i)%this
251  
252 +          inner: do j = i+1, natoms
253 +             Atype_j   => identPtrList(j)%this
254 +             call get_interatomic_vector(i,j,q(:,i),q(:,j),&
255 +                  rxij,ryij,rzij,rijsq,r)
256 +          
257 +             if (rijsq <  rlistsq) then
258 +
259 +                nlist = nlist + 1
260 +                
261 +                if (nlist > neighborListSize) then
262 +                   call expandList(listerror)
263 +                   if (listerror /= 0) then
264 +                      FFerror = -1
265 +                      write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
266 +                      return
267 +                   end if
268 +                endif
269 +                
270 +                list(nlist) = j
271 +
272      
273 <              if (rijsq <  rcutsq) then
274 <                 call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
275 <              endif
273 >                if (rijsq <  rcutsq) then
274 >                   call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
275 >                endif
276 >             endif
277            enddo inner
278 <     enddo
278 >       enddo
279 >      
280 >       point(natoms) = nlist + 1
281 >      
282 >    else !! (update)
283 >      
284 >       ! use the list to find the neighbors
285 >       do i = 1, nrow
286 >          JBEG = POINT(i)
287 >          JEND = POINT(i+1) - 1
288 >          ! check thiat molecule i has neighbors
289 >          if (jbeg .le. jend) then
290 >            
291 >             Atype_i => identPtrList(i)%this
292 >             do jnab = jbeg, jend
293 >                j = list(jnab)
294 >                Atype_j = identPtrList(j)%this
295 >                call get_interatomic_vector(i,j,q(:,i),q(:,j),&
296 >                     rxij,ryij,rzij,rijsq,r)
297 >                call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
298 >             enddo
299 >          endif
300 >       enddo
301 >    endif
302  
303 + #endif
304 +
305 +
306   #ifdef IS_MPI
307 <     point(nrow + 1) = nlist + 1
308 < #else
309 <     point(natoms) = nlist + 1
307 >    !! distribute all reaction field stuff (or anything for post-pair):
308 >    call scatter(rflRow,rflTemp1,plan_row3d)
309 >    call scatter(rflCol,rflTemp2,plan_col3d)
310 >    do i = 1,nlocal
311 >       rflTemp(1:3,i) = rflTemp1(1:3,i) + rflTemp2(1:3,i)
312 >    end do
313   #endif
314  
315 <  else !! (update)
315 > ! This is the post-pair loop:
316 > #ifdef IS_MPI
317  
318 <     ! use the list to find the neighbors
319 <     do i = 1, nrow
320 <        JBEG = POINT(i)
321 <        JEND = POINT(i+1) - 1
322 <        ! check thiat molecule i has neighbors
323 <        if (jbeg .le. jend) then
318 >    if (system_has_postpair_atoms) then
319 >       do i = 1, nlocal
320 >          Atype_i => identPtrListRow(i)%this
321 >          call do_postpair(i, Atype_i)
322 >       enddo
323 >    endif
324  
510 #ifdef IS_MPI
511           ljAtype_i => identPtrListRow(i)%this
325   #else
326 <           ljAtype_i => identPtrList(i)%this
326 >
327 >    if (system_has_postpair_atoms) then
328 >       do i = 1, natoms
329 >          Atype_i => identPtr(i)%this
330 >          call do_postpair(i, Atype_i)
331 >       enddo
332 >    endif
333 >
334   #endif
515           do jnab = jbeg, jend
516              j = list(jnab)
517 #ifdef IS_MPI
518              ljAtype_j = identPtrListColumn(j)%this
519              call get_interatomic_vector(i,j,qRow(:,i),qCol(:,j),&
520                   rxij,ryij,rzij,rijsq,r)
521              
522 #else
523              ljAtype_j = identPtrList(j)%this
524              call get_interatomic_vector(i,j,q(:,i),q(:,j),&
525                   rxij,ryij,rzij,rijsq,r)
526 #endif
527              call do_pair(i,j,r,rxij,ryij,rzij)
528          enddo
529       endif
530    enddo
531 endif
532
335  
336  
337 +
338 +
339   #ifdef IS_MPI
340      !!distribute forces
341  
342 <    call scatter(fRow,f,plan_row3d)
343 <    call scatter(fCol,fTemp,plan_col3d)
342 >    call scatter(fRow,fTemp1,plan_row3d)
343 >    call scatter(fCol,fTemp2,plan_col3d)
344  
345 +
346      do i = 1,nlocal
347 <       f(1:3,i) = f(1:3,i) + fTemp(1:3,i)
347 >       fTemp(1:3,i) = fTemp1(1:3,i) + fTemp2(1:3,i)
348      end do
349  
350      if (do_torque) then
351 <       call scatter(tRow,t,plan_row3d)
352 <       call scatter(tCol,tTemp,plan_col3d)
351 >       call scatter(tRow,tTemp1,plan_row3d)
352 >       call scatter(tCol,tTemp2,plan_col3d)
353      
354         do i = 1,nlocal
355 <          t(1:3,i) = t(1:3,i) + tTemp(1:3,i)
355 >          tTemp(1:3,i) = tTemp1(1:3,i) + tTemp2(1:3,i)
356         end do
357      endif
358  
# Line 571 | Line 376 | contains
376      endif
377   #else
378   ! Copy local array into return array for c
379 <    f = fTemp
380 <    t = tTemp
379 >    f = f+fTemp
380 >    t = t+tTemp
381   #endif
382  
383      potE = pe
# Line 654 | Line 459 | contains
459      real( kind = dp ) :: fx = 0.0_dp
460      real( kind = dp ) :: fy = 0.0_dp
461      real( kind = dp ) :: fz = 0.0_dp  
462 <
462 >  
463      real( kind = dp ) ::  drdx = 0.0_dp
464      real( kind = dp ) ::  drdy = 0.0_dp
465      real( kind = dp ) ::  drdz = 0.0_dp
466      
467  
468 + #ifdef IS_MPI
469  
470 +    if (Atype_i%is_LJ .and. Atype_j%is_LJ) then
471 +       call getLJForce(r,pot,dudr,ljAtype_i,ljAtype_j,fx,fy,fz)
472 +    endif
473  
474 +    if (Atype_i%is_dp .and. Atype_j%is_dp) then
475  
476 +       call dipole_dipole(i, j, atype_i, atype_j, rx_ij, ry_ij, rz_ij, r_ij, &
477 +            ulRow(:,i), ulCol(:,j), rt, rrf, pot)
478  
479 <    call getLJForce(r,pot,dudr,ljAtype_i,ljAtype_j)
479 >       if (do_reaction_field) then
480 >          call accumulate_rf(i, j, r_ij, rflRow(:,i), rflCol(:j), &
481 >               ulRow(:i), ulCol(:,j), rt, rrf)
482 >       endif
483 >
484 >    endif
485 >
486 >    if (Atype_i%is_sticky .and. Atype_j%is_sticky) then
487 >       call getstickyforce(r, pot, dudr, Atype_i, Atype_j)
488 >    endif
489 >
490 > #else
491 >
492 >    if (Atype_i%is_LJ .and. Atype_j%is_LJ) then
493 >       call getLJForce(r,pot,dudr,ljAtype_i,ljAtype_j,fx,fy,fz)
494 >    endif
495 >
496 >    if (Atype_i%is_dp .and. Atype_j%is_dp) then
497 >       call dipole_dipole(i, j, atype_i, atype_j, rx_ij, ry_ij, rz_ij, r_ij, &
498 >            ul(:,i), ul(:,j), rt, rrf, pot)
499 >
500 >       if (do_reaction_field) then
501 >          call accumulate_rf(i, j, r_ij, rfl(:,i), rfl(:j), &
502 >               ul(:,i), ul(:,j), rt, rrf)
503 >       endif
504 >
505 >    endif
506 >
507 >    if (Atype_i%is_sticky .and. Atype_j%is_sticky) then
508 >       call getstickyforce(r,pot,dudr, Atype_i, Atype_j)
509 >    endif
510 >
511 > #endif
512 >
513        
514   #ifdef IS_MPI
515                  eRow(i) = eRow(i) + pot*0.5
# Line 680 | Line 525 | contains
525                  fx = dudr * drdx
526                  fy = dudr * drdy
527                  fz = dudr * drdz
683
684
685
686
687
688
528                  
529   #ifdef IS_MPI
530                  fCol(1,j) = fCol(1,j) - fx
# Line 819 | Line 658 | contains
658  
659    end subroutine zero_module_variables
660  
661 < #ifdef IS_MPI
661 >
662   !! Function to properly build neighbor lists in MPI using newtons 3rd law.
663   !! We don't want 2 processors doing the same i j pair twice.
664   !! Also checks to see if i and j are the same particle.
665 <  function mpi_cycle_jLoop(i,j) result(do_cycle)
665 >  function checkExcludes(atom1,atom2) result(do_cycle)
666   !--------------- Arguments--------------------------
667   ! Index i
668 <    integer,intent(in) :: i
668 >    integer,intent(in) :: atom1
669   ! Index j
670 <    integer,intent(in) :: j
670 >    integer,intent(in), optional :: atom2
671   ! Result do_cycle
672      logical :: do_cycle
673   !--------------- Local variables--------------------
674      integer :: tag_i
675      integer :: tag_j
676 < !--------------- END DECLARATIONS------------------    
677 <    tag_i = tagRow(i)
676 >    integer :: i
677 > !--------------- END DECLARATIONS------------------  
678 >    do_cycle = .false.
679 >
680 > #ifdef IS_MPI
681 >    tag_i = tagRow(atom1)
682 > #else
683 >    tag_i = tag(atom1)
684 > #endif
685 >
686 > !! Check global excludes first
687 >    if (.not. present(atom2)) then
688 >       do i = 1,nGlobalExcludes
689 >          if (excludeGlobal(i) == tag_i) then
690 >             do_cycle = .true.
691 >             return
692 >          end if
693 >       end do
694 >       return !! return after checking globals
695 >    end if
696 >
697 > !! we return if j not present here.
698      tag_j = tagColumn(j)
699  
700 <    do_cycle = .false.
700 >
701  
702      if (tag_i == tag_j) then
703         do_cycle = .true.
# Line 851 | Line 710 | contains
710      else                
711         if (mod(tag_i + tag_j,2) == 1) do_cycle = .true.
712      endif
854  end function mpi_cycle_jLoop
855 #endif
713  
714 +
715 +
716 +    do i = 1, nLocalExcludes
717 +       if (tag_i = excludes(1,i) .and. excludes(2,i) < 0) then
718 +          do_cycle = .true.
719 +          return
720 +       end if
721 +    end do
722 +      
723 +
724 +  end function checkExcludes
725 +
726 +
727   end module do_Forces

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines