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 312 by gezelter, Tue Mar 11 17:46:18 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.10 2003-03-11 17:46:18 gezelter Exp $, $Date: 2003-03-11 17:46:18 $, $Name: not supported by cvs2svn $, $Revision: 1.10 $
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
19 >  use lj
20    use sticky_FF
21 <  use dp_FF
21 >  use dipole_dipole
22    use gb_FF
23  
24   #ifdef IS_MPI
# 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 417 | Line 144 | contains
144  
145   ! communicate MPI positions
146   #ifdef IS_MPI    
147 <    call gather(q,qRow,plan_row3d)
148 <    call gather(q,qCol,plan_col3d)
147 >    call gather(q,q_Row,plan_row3d)
148 >    call gather(q,q_Col,plan_col3d)
149  
150 <    call gather(mu,muRow,plan_row3d)
151 <    call gather(mu,muCol,plan_col3d)
150 >    call gather(u_l,u_l_Row,plan_row3d)
151 >    call gather(u_l,u_l_Col,plan_col3d)
152  
153 <    call gather(u_l,u_lRow,plan_row3d)
154 <    call gather(u_l,u_lCol,plan_col3d)
428 <
429 <    call gather(A,ARow,plan_row_rotation)
430 <    call gather(A,ACol,plan_col_rotation)
153 >    call gather(A,A_Row,plan_row_rotation)
154 >    call gather(A,A_Col,plan_col_rotation)
155   #endif
156  
157  
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
158   #ifdef IS_MPI
448        Atype_i => identPtrListRow(i)%this
449        tag_i = tagRow(i)
450 #else
451        Atype_i   => identPtrList(i)%this
452        j_start = i + 1
453 #endif
454
455        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)
470      
471 #endif          
472          
473           if (rijsq <  rlistsq) then
474
475              nlist = nlist + 1
476
477              if (nlist > neighborListSize) then
478                 call expandList(listerror)
479                 if (listerror /= 0) then
480                    FFerror = -1
481                    write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
482                    return
483                 end if
484              endif
485
486              list(nlist) = j
487
159      
160 <              if (rijsq <  rcutsq) then
161 <                 call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
162 <              endif
163 <          enddo inner
164 <     enddo
165 <
166 < #ifdef IS_MPI
167 <     point(nrow + 1) = nlist + 1
160 >    if (update_nlist) then
161 >      
162 >       ! save current configuration, contruct neighbor list,
163 >       ! and calculate forces
164 >       call save_neighborList(q)
165 >      
166 >       neighborListSize = getNeighborListSize()
167 >       nlist = 0
168 >      
169 >       nrow = getNrow(plan_row)
170 >       ncol = getNcol(plan_col)
171 >       nlocal = getNlocal()
172 >      
173 >       do i = 1, nrow
174 >          point(i) = nlist + 1
175 >          Atype_i => identPtrListRow(i)%this
176 >          
177 >          inner: do j = 1, ncol
178 >             Atype_j => identPtrListColumn(j)%this
179 >            
180 >             call get_interatomic_vector(i,j,q_Row(:,i),q_Col(:,j),&
181 >                  rxij,ryij,rzij,rijsq,r)
182 >            
183 >             ! skip the loop if the atoms are identical
184 >             if (mpi_cycle_jLoop(i,j)) cycle inner:
185 >            
186 >             if (rijsq <  rlistsq) then            
187 >                
188 >                nlist = nlist + 1
189 >                
190 >                if (nlist > neighborListSize) then
191 >                   call expandList(listerror)
192 >                   if (listerror /= 0) then
193 >                      FFerror = -1
194 >                      write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
195 >                      return
196 >                   end if
197 >                endif
198 >                
199 >                list(nlist) = j
200 >                
201 >                
202 >                if (rijsq <  rcutsq) then
203 >                   call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
204 >                endif
205 >             endif
206 >          enddo inner
207 >       enddo
208 >
209 >       point(nrow + 1) = nlist + 1
210 >      
211 >    else !! (update)
212 >
213 >       ! use the list to find the neighbors
214 >       do i = 1, nrow
215 >          JBEG = POINT(i)
216 >          JEND = POINT(i+1) - 1
217 >          ! check thiat molecule i has neighbors
218 >          if (jbeg .le. jend) then
219 >
220 >             Atype_i => identPtrListRow(i)%this
221 >             do jnab = jbeg, jend
222 >                j = list(jnab)
223 >                Atype_j = identPtrListColumn(j)%this
224 >                call get_interatomic_vector(i,j,q_Row(:,i),q_Col(:,j),&
225 >                     rxij,ryij,rzij,rijsq,r)
226 >                
227 >                call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
228 >             enddo
229 >          endif
230 >       enddo
231 >    endif
232 >
233   #else
234 <     point(natoms) = nlist + 1
235 < #endif
234 >    
235 >    if (update_nlist) then
236 >      
237 >       ! save current configuration, contruct neighbor list,
238 >       ! and calculate forces
239 >       call save_neighborList(q)
240 >      
241 >       neighborListSize = getNeighborListSize()
242 >       nlist = 0
243 >      
244 >    
245 >       do i = 1, natoms-1
246 >          point(i) = nlist + 1
247 >          Atype_i   => identPtrList(i)%this
248  
249 <  else !! (update)
249 >          inner: do j = i+1, natoms
250 >             Atype_j   => identPtrList(j)%this
251 >             call get_interatomic_vector(i,j,q(:,i),q(:,j),&
252 >                  rxij,ryij,rzij,rijsq,r)
253 >          
254 >             if (rijsq <  rlistsq) then
255  
256 <     ! use the list to find the neighbors
257 <     do i = 1, nrow
258 <        JBEG = POINT(i)
259 <        JEND = POINT(i+1) - 1
260 <        ! check thiat molecule i has neighbors
261 <        if (jbeg .le. jend) then
256 >                nlist = nlist + 1
257 >                
258 >                if (nlist > neighborListSize) then
259 >                   call expandList(listerror)
260 >                   if (listerror /= 0) then
261 >                      FFerror = -1
262 >                      write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
263 >                      return
264 >                   end if
265 >                endif
266 >                
267 >                list(nlist) = j
268  
269 +    
270 +                if (rijsq <  rcutsq) then
271 +                   call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
272 +                endif
273 +             endif
274 +          enddo inner
275 +       enddo
276 +      
277 +       point(natoms) = nlist + 1
278 +      
279 +    else !! (update)
280 +      
281 +       ! use the list to find the neighbors
282 +       do i = 1, nrow
283 +          JBEG = POINT(i)
284 +          JEND = POINT(i+1) - 1
285 +          ! check thiat molecule i has neighbors
286 +          if (jbeg .le. jend) then
287 +            
288 +             Atype_i => identPtrList(i)%this
289 +             do jnab = jbeg, jend
290 +                j = list(jnab)
291 +                Atype_j = identPtrList(j)%this
292 +                call get_interatomic_vector(i,j,q(:,i),q(:,j),&
293 +                     rxij,ryij,rzij,rijsq,r)
294 +                call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
295 +             enddo
296 +          endif
297 +       enddo
298 +    endif
299 +
300 + #endif
301 +
302 +
303   #ifdef IS_MPI
304 <           ljAtype_i => identPtrListRow(i)%this
305 < #else
306 <           ljAtype_i => identPtrList(i)%this
304 >    !! distribute all reaction field stuff (or anything for post-pair):
305 >    call scatter(rflRow,rflTemp1,plan_row3d)
306 >    call scatter(rflCol,rflTemp2,plan_col3d)
307 >    do i = 1,nlocal
308 >       rflTemp(1:3,i) = rflTemp1(1:3,i) + rflTemp2(1:3,i)
309 >    end do
310   #endif
311 <           do jnab = jbeg, jend
312 <              j = list(jnab)
311 >
312 > ! This is the post-pair loop:
313   #ifdef IS_MPI
314 <              ljAtype_j = identPtrListColumn(j)%this
315 <              call get_interatomic_vector(i,j,qRow(:,i),qCol(:,j),&
316 <                   rxij,ryij,rzij,rijsq,r)
317 <              
314 >
315 >    if (system_has_postpair_atoms) then
316 >       do i = 1, nlocal
317 >          Atype_i => identPtrListRow(i)%this
318 >          call do_postpair(i, Atype_i)
319 >       enddo
320 >    endif
321 >
322   #else
323 <              ljAtype_j = identPtrList(j)%this
324 <              call get_interatomic_vector(i,j,q(:,i),q(:,j),&
325 <                   rxij,ryij,rzij,rijsq,r)
323 >
324 >    if (system_has_postpair_atoms) then
325 >       do i = 1, natoms
326 >          Atype_i => identPtr(i)%this
327 >          call do_postpair(i, Atype_i)
328 >       enddo
329 >    endif
330 >
331   #endif
527              call do_pair(i,j,r,rxij,ryij,rzij)
528          enddo
529       endif
530    enddo
531 endif
532
332  
333  
334   #ifdef IS_MPI
335      !!distribute forces
336  
337 <    call scatter(fRow,f,plan_row3d)
338 <    call scatter(fCol,fTemp,plan_col3d)
540 <
337 >    call scatter(f_Row,f,plan_row3d)
338 >    call scatter(f_Col,f_temp,plan_col3d)
339      do i = 1,nlocal
340 <       f(1:3,i) = f(1:3,i) + fTemp(1:3,i)
340 >       f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
341      end do
342  
343 <    if (do_torque) then
344 <       call scatter(tRow,t,plan_row3d)
345 <       call scatter(tCol,tTemp,plan_col3d)
343 >    if (doTorque()) then
344 >       call scatter(t_Row,t,plan_row3d)
345 >       call scatter(t_Col,t_temp,plan_col3d)
346      
347         do i = 1,nlocal
348 <          t(1:3,i) = t(1:3,i) + tTemp(1:3,i)
348 >          t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
349         end do
350      endif
351 <
351 >    
352      if (do_pot) then
353         ! scatter/gather pot_row into the members of my column
354 <       call scatter(eRow,eTemp,plan_row)
354 >       call scatter(pot_Row, pot_Temp, plan_row)
355        
356         ! scatter/gather pot_local into all other procs
357         ! add resultant to get total pot
358         do i = 1, nlocal
359 <          pe_local = pe_local + eTemp(i)
359 >          pot_local = pot_local + pot_Temp(i)
360         enddo
361  
362 <       eTemp = 0.0E0_DP
363 <       call scatter(eCol,eTemp,plan_col)
362 >       pot_Temp = 0.0_DP
363 >
364 >       call scatter(pot_Col, pot_Temp, plan_col)
365         do i = 1, nlocal
366 <          pe_local = pe_local + eTemp(i)
366 >          pot_local = pot_local + pot_Temp(i)
367         enddo
368        
369 <       pe = pe_local
369 >       pot = pot_local
370      endif
572 #else
573 ! Copy local array into return array for c
574    f = fTemp
575    t = tTemp
576 #endif
371  
372 <    potE = pe
372 >    if (doStress()) then
373 >       mpi_allreduce(tau, tau_Temp,9,mpi_double_precision,mpi_sum, &
374 >            mpi_comm_world,mpi_err)
375 >       mpi_allreduce(virial, virial_Temp,1,mpi_double_precision,mpi_sum, &
376 >            mpi_comm_world,mpi_err)
377 >    endif
378  
379 + #endif
380  
381 <    if (do_stress) then
382 < #ifdef IS_MPI
383 <       mpi_allreduce = (tau,tauTemp,9,mpi_double_precision,mpi_sum, &
584 <            mpi_comm_world,mpi_err)
585 < #else
586 <       tau = tauTemp
587 < #endif      
381 >    if (doStress()) then
382 >       tau = tau_Temp
383 >       virial = virial_Temp
384      endif
385  
386    end subroutine do_force_loop
387  
388  
593
594
595
596
597
598
599
600
389   !! Calculate any pre-force loop components and update nlist if necessary.
390    subroutine do_preForce(updateNlist)
391      logical, intent(inout) :: updateNlist
# Line 654 | Line 442 | contains
442      real( kind = dp ) :: fx = 0.0_dp
443      real( kind = dp ) :: fy = 0.0_dp
444      real( kind = dp ) :: fz = 0.0_dp  
445 <
445 >  
446      real( kind = dp ) ::  drdx = 0.0_dp
447      real( kind = dp ) ::  drdy = 0.0_dp
448      real( kind = dp ) ::  drdz = 0.0_dp
449      
450  
451 + #ifdef IS_MPI
452  
453 +    if (Atype_i%is_LJ .and. Atype_j%is_LJ) then
454 +       call do_lj_pair(i, j, atype_i, atype_j, rx_ij, ry_ij, rz_ij, r_ij, &
455 +            pot, f)
456 +    endif
457  
458 +    if (Atype_i%is_dp .and. Atype_j%is_dp) then
459  
460 +       call do_dipole_pair(i, j, atype_i, atype_j, rx_ij, ry_ij, rz_ij, r_ij, &
461 +            pot, u_l, f, t)
462  
463 <    call getLJForce(r,pot,dudr,ljAtype_i,ljAtype_j)
464 <      
465 < #ifdef IS_MPI
466 <                eRow(i) = eRow(i) + pot*0.5
467 <                eCol(i) = eCol(i) + pot*0.5
463 >       if (do_reaction_field) then
464 >          call accumulate_rf(i, j, r_ij, rt, rrf)
465 >       endif
466 >
467 >    endif
468 >
469 >    if (Atype_i%is_sticky .and. Atype_j%is_sticky) then
470 >       call getstickyforce(r, pot, dudr, Atype_i, Atype_j)
471 >    endif
472 >
473   #else
673                    pe = pe + pot
674 #endif                
675            
676                drdx = -rxij / r
677                drdy = -ryij / r
678                drdz = -rzij / r
679                
680                fx = dudr * drdx
681                fy = dudr * drdy
682                fz = dudr * drdz
474  
475 +    if (Atype_i%is_LJ .and. Atype_j%is_LJ) then
476 +       call do_lj_pair(i, j, atype_i, atype_j, rx_ij, ry_ij, rz_ij, r_ij, &
477 +            pot, f)
478 +    endif
479  
480 +    if (Atype_i%is_dp .and. Atype_j%is_dp) then
481 +       call do_dipole_pair(i, j, atype_i, atype_j, rx_ij, ry_ij, rz_ij, r_ij, &
482 +            pot, u_l, f, t)
483  
484 +       if (do_reaction_field) then
485 +          call accumulate_rf(i, j, r_ij, rt, rrf)
486 +       endif
487  
488 +    endif
489 +
490 +    if (Atype_i%is_sticky .and. Atype_j%is_sticky) then
491 +       call getstickyforce(r,pot,dudr, Atype_i, Atype_j)
492 +    endif
493  
688
689                
690 #ifdef IS_MPI
691                fCol(1,j) = fCol(1,j) - fx
692                fCol(2,j) = fCol(2,j) - fy
693                fCol(3,j) = fCol(3,j) - fz
694                
695                fRow(1,j) = fRow(1,j) + fx
696                fRow(2,j) = fRow(2,j) + fy
697                fRow(3,j) = fRow(3,j) + fz
698 #else
699                fTemp(1,j) = fTemp(1,j) - fx
700                fTemp(2,j) = fTemp(2,j) - fy
701                fTemp(3,j) = fTemp(3,j) - fz
702                fTemp(1,i) = fTemp(1,i) + fx
703                fTemp(2,i) = fTemp(2,i) + fy
704                fTemp(3,i) = fTemp(3,i) + fz
494   #endif
706                
707                if (do_stress) then
708                   tauTemp(1) = tauTemp(1) + fx * rxij
709                   tauTemp(2) = tauTemp(2) + fx * ryij
710                   tauTemp(3) = tauTemp(3) + fx * rzij
711                   tauTemp(4) = tauTemp(4) + fy * rxij
712                   tauTemp(5) = tauTemp(5) + fy * ryij
713                   tauTemp(6) = tauTemp(6) + fy * rzij
714                   tauTemp(7) = tauTemp(7) + fz * rxij
715                   tauTemp(8) = tauTemp(8) + fz * ryij
716                   tauTemp(9) = tauTemp(9) + fz * rzij
717                endif
495  
496 <
720 <
496 >      
497    end subroutine do_pair
498  
499  
# Line 819 | Line 595 | contains
595  
596    end subroutine zero_module_variables
597  
598 < #ifdef IS_MPI
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 mpi_cycle_jLoop(i,j) result(do_cycle)
602 >  function checkExcludes(atom1,atom2) result(do_cycle)
603   !--------------- Arguments--------------------------
604   ! Index i
605 <    integer,intent(in) :: i
605 >    integer,intent(in) :: atom1
606   ! Index j
607 <    integer,intent(in) :: j
607 >    integer,intent(in), optional :: atom2
608   ! Result do_cycle
609      logical :: do_cycle
610   !--------------- Local variables--------------------
611      integer :: tag_i
612      integer :: tag_j
613 < !--------------- END DECLARATIONS------------------    
614 <    tag_i = tagRow(i)
613 >    integer :: i
614 > !--------------- END DECLARATIONS------------------  
615 >    do_cycle = .false.
616 >
617 > #ifdef IS_MPI
618 >    tag_i = tagRow(atom1)
619 > #else
620 >    tag_i = tag(atom1)
621 > #endif
622 >
623 > !! Check global excludes first
624 >    if (.not. present(atom2)) then
625 >       do i = 1,nGlobalExcludes
626 >          if (excludeGlobal(i) == tag_i) then
627 >             do_cycle = .true.
628 >             return
629 >          end if
630 >       end do
631 >       return !! return after checking globals
632 >    end if
633 >
634 > !! we return if j not present here.
635      tag_j = tagColumn(j)
636  
637 <    do_cycle = .false.
637 >
638  
639      if (tag_i == tag_j) then
640         do_cycle = .true.
# Line 851 | Line 647 | contains
647      else                
648         if (mod(tag_i + tag_j,2) == 1) do_cycle = .true.
649      endif
854  end function mpi_cycle_jLoop
855 #endif
650  
651 +
652 +
653 +    do i = 1, nLocalExcludes
654 +       if (tag_i = excludes(1,i) .and. excludes(2,i) < 0) then
655 +          do_cycle = .true.
656 +          return
657 +       end if
658 +    end do
659 +      
660 +
661 +  end function checkExcludes
662 +
663 +
664   end module do_Forces

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines