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 292 by chuckv, Thu Mar 6 14:52:44 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.1 2003-03-06 14:52:44 chuckv Exp $, $Date: 2003-03-06 14:52:44 $, $Name: not supported by cvs2svn $, $Revision: 1.1 $
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 !! LJ mixing array  
34 !  type (lj_atype), dimension(:,:), pointer :: ljMixed => null()
35
36
37  logical, save :: firstTime = .True.
38
39 !! Atype identity pointer lists
40 #ifdef IS_MPI
41 !! Row lj_atype pointer list
42  type (identPtrList), dimension(:), pointer :: identPtrListRow => null()
43 !! Column lj_atype pointer list
44  type (identPtrList), dimension(:), pointer :: identPtrListColumn => null()
45 #else
46  type(identPtrList ), dimension(:), pointer :: identPtrList => null()
47 #endif
48
49
50 !! Logical has lj force field module been initialized?
51  logical, save :: isFFinit = .false.
52
53
54 !! Public methods and data
55  public :: new_atype
56  public :: do_lj_ff
57  public :: getLjPot
58  public :: init_FF
59
60  
61
62
32   contains
33  
34 < !! Adds a new lj_atype to the list.
66 <  subroutine new_atype(ident,mass,epsilon,sigma, &
67 <       is_LJ,is_Sticky,is_DP,is_GB,w0,v0,dipoleMoment,status)
68 <    real( kind = dp ), intent(in) :: mass
69 <    real( kind = dp ), intent(in) :: epsilon
70 <    real( kind = dp ), intent(in) :: sigma
71 <    real( kind = dp ), intent(in) :: w0
72 <    real( kind = dp ), intent(in) :: v0
73 <    real( kind = dp ), intent(in) :: dipoleMoment
74 <
75 <    integer, intent(in) :: ident
76 <    integer, intent(out) :: status
77 <    integer, intent(in) :: is_Sticky
78 <    integer, intent(in) :: is_DP
79 <    integer, intent(in) :: is_GB
80 <    integer, intent(in) :: is_LJ
81 <
82 <
83 <    type (atype), pointer :: the_new_atype
84 <    integer :: alloc_error
85 <    integer :: atype_counter = 0
86 <    integer :: alloc_size
87 <    integer :: err_stat
88 <    status = 0
89 <
90 <
91 <
92 < ! allocate a new atype    
93 <    allocate(the_new_atype,stat=alloc_error)
94 <    if (alloc_error /= 0 ) then
95 <       status = -1
96 <       return
97 <    end if
98 <
99 < ! assign our new atype information
100 <    the_new_atype%mass        = mass
101 <    the_new_atype%epsilon     = epsilon
102 <    the_new_atype%sigma       = sigma
103 <    the_new_atype%sigma2      = sigma * sigma
104 <    the_new_atype%sigma6      = the_new_atype%sigma2 * the_new_atype%sigma2 &
105 <         * the_new_atype%sigma2
106 <    the_new_atype%w0       = w0
107 <    the_new_atype%v0       = v0
108 <    the_new_atype%dipoleMoment       = dipoleMoment
109 <
110 <    
111 < ! assume that this atype will be successfully added
112 <    the_new_atype%atype_ident = ident
113 <    the_new_atype%atype_number = n_lj_atypes + 1
114 <    
115 <    if ( is_Sticky /= 0 )    the_new_atype%is_Sticky   = .true.
116 <    if ( is_GB /= 0 )        the_new_atype%is_GB       = .true.
117 <    if ( is_LJ /= 0 )        the_new_atype%is_LJ       = .true.
118 <    if ( is_DP /= 0 )        the_new_atype%is_DP       = .true.
119 <
120 <    call add_atype(the_new_atype,ListHead,ListTail,err_stat)
121 <    if (err_stat /= 0 ) then
122 <       status = -1
123 <       return
124 <    endif
125 <
126 <    n_atypes = n_atypes + 1
127 <
128 <
129 <  end subroutine new_atype
130 <
131 <
132 <  subroutine init_FF(nComponents,ident, status)
133 < !! Number of components in ident array
134 <    integer, intent(inout) :: nComponents
135 < !! Array of identities nComponents long corresponding to
136 < !! ljatype ident.
137 <    integer, dimension(nComponents),intent(inout) :: ident
138 < !!  Result status, success = 0, error = -1
139 <    integer, intent(out) :: Status
140 <
141 <    integer :: alloc_stat
142 <
143 <    integer :: thisStat
144 <    integer :: i
145 <
146 <    integer :: myNode
147 < #ifdef IS_MPI
148 <    integer, allocatable, dimension(:) :: identRow
149 <    integer, allocatable, dimension(:) :: identCol
150 <    integer :: nrow
151 <    integer :: ncol
152 < #endif
153 <    status = 0
154 <  
155 <
156 <    
157 <
158 < !! if were're not in MPI, we just update ljatypePtrList
159 < #ifndef IS_MPI
160 <    call create_IdentPtrlst(ident,ListHead,identPtrList,thisStat)
161 <    if ( thisStat /= 0 ) then
162 <       status = -1
163 <       return
164 <    endif
165 <
166 <    
167 < ! if were're in MPI, we also have to worry about row and col lists    
168 < #else
169 <  
170 < ! We can only set up forces if mpiSimulation has been setup.
171 <    if (.not. isMPISimSet()) then
172 <       write(default_error,*) "MPI is not set"
173 <       status = -1
174 <       return
175 <    endif
176 <    nrow = getNrow(plan_row)
177 <    ncol = getNcol(plan_col)
178 <    mynode = getMyNode()
179 < !! Allocate temperary arrays to hold gather information
180 <    allocate(identRow(nrow),stat=alloc_stat)
181 <    if (alloc_stat /= 0 ) then
182 <       status = -1
183 <       return
184 <    endif
185 <
186 <    allocate(identCol(ncol),stat=alloc_stat)
187 <    if (alloc_stat /= 0 ) then
188 <       status = -1
189 <       return
190 <    endif
191 <
192 < !! Gather idents into row and column idents
193 <
194 <    call gather(ident,identRow,plan_row)
195 <    call gather(ident,identCol,plan_col)
196 <    
197 <  
198 < !! Create row and col pointer lists
199 <  
200 <    call create_IdentPtrlst(identRow,ListHead,identPtrListRow,thisStat)
201 <    if (thisStat /= 0 ) then
202 <       status = -1
203 <       return
204 <    endif
205 <  
206 <    call create_IdentPtrlst(identCol,ListHead,identPtrListColumn,thisStat)
207 <    if (thisStat /= 0 ) then
208 <       status = -1
209 <       return
210 <    endif
211 <
212 < !! free temporary ident arrays
213 <    if (allocated(identCol)) then
214 <       deallocate(identCol)
215 <    end if
216 <    if (allocated(identCol)) then
217 <       deallocate(identRow)
218 <    endif
219 <
220 < #endif
221 <    
222 <    call initForce_Modules(thisStat)
223 <    if (thisStat /= 0) then
224 <       status = -1
225 <       return
226 <    endif
227 <
228 < !! Create neighbor lists
229 <    call expandList(thisStat)
230 <    if (thisStat /= 0) then
231 <       status = -1
232 <       return
233 <    endif
234 <
235 <    isFFinit = .true.
236 <
237 <
238 <  end subroutine init_FF
239 <
240 <
241 <
242 <
243 <  subroutine initForce_Modules(thisStat)
244 <    integer, intent(out) :: thisStat
245 <    integer :: my_status
246 <    
247 <    thisStat = 0
248 <    call init_lj_FF(ListHead,my_status)
249 <    if (my_status /= 0) then
250 <       thisStat = -1
251 <       return
252 <    end if
253 <
254 <  end subroutine initForce_Modules
255 <
256 <
257 <
258 <
259 < !! 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 275 | Line 50 | contains
50  
51   !! Stress Tensor
52      real( kind = dp), dimension(9) :: tau
53 <    real( kind = dp), dimension(9) :: tauTemp
53 >
54      real ( kind = dp ) :: potE
55      logical ( kind = 2) :: do_pot
56      integer :: FFerror
# Line 293 | Line 68 | contains
68    real( kind = DP ) :: pot_local
69  
70   !! Local arrays needed for MPI
296  real(kind = dp), dimension(3,getNrow(plan_row)) :: qRow = 0.0_dp
297  real(kind = dp), dimension(3,getNcol(plan_col)) :: qCol = 0.0_dp
71  
299  real(kind = dp), dimension(3,getNrow(plan_row)) :: muRow = 0.0_dp
300  real(kind = dp), dimension(3,getNcol(plan_col)) :: muCol = 0.0_dp
301
302  real(kind = dp), dimension(3,getNrow(plan_row)) :: u_lRow = 0.0_dp
303  real(kind = dp), dimension(3,getNcol(plan_col)) :: u_lCol = 0.0_dp
304
305  real(kind = dp), dimension(3,getNrow(plan_row)) :: ARow = 0.0_dp
306  real(kind = dp), dimension(3,getNcol(plan_col)) :: ACol = 0.0_dp
307
308  
309
310  real(kind = dp), dimension(3,getNrow(plan_row)) :: fRow = 0.0_dp
311  real(kind = dp), dimension(3,getNcol(plan_col)) :: fCol = 0.0_dp
312  real(kind = dp), dimension(3,getNlocal()) :: fMPITemp = 0.0_dp
313
314  real(kind = dp), dimension(3,getNrow(plan_row)) :: tRow = 0.0_dp
315  real(kind = dp), dimension(3,getNcol(plan_col)) :: tCol = 0.0_dp
316  real(kind = dp), dimension(3,getNlocal()) :: tMPITemp = 0.0_dp
317
318
319  real(kind = dp), dimension(getNrow(plan_row)) :: eRow = 0.0_dp
320  real(kind = dp), dimension(getNcol(plan_col)) :: eCol = 0.0_dp
321
322  real(kind = dp), dimension(getNlocal()) :: eTemp = 0.0_dp
323
72   #endif
73  
74  
# Line 332 | Line 80 | contains
80    integer ::  i, j, jbeg, jend, jnab, idim, jdim, idim2, jdim2, dim, dim2
81    integer :: nlist
82    integer :: j_start
83 <  integer :: tag_i,tag_j
84 <  real( kind = DP ) ::  r, pot, ftmp, dudr, d2, drdx1, kt1, kt2, kt3, ktmp
85 <  real( kind = dp ) :: fx,fy,fz
86 <  real( kind = DP ) ::  drdx, drdy, drdz
339 <  real( kind = DP ) ::  rxi, ryi, rzi, rxij, ryij, rzij, rijsq
83 >
84 >  real( kind = DP ) ::  r_ij, pot, ftmp, dudr, d2, drdx1, kt1, kt2, kt3, ktmp
85 >
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
346  logical :: newtons_thrd = .true.
93    real( kind = dp ) :: pe_local
94    integer :: nlocal
95   #endif
# Line 376 | Line 122 | contains
122    natoms = getNlocal()
123    call getRcut(rcut,rcut2=rcutsq)
124    call getRlist(rlist,rlistsq)
125 +
126   !! Find ensemble
127    if (isEnsemble("NPT")) do_stress = .true.
128 + !! set to wrap
129 +  if (isPBC()) wrap = .true.
130  
382 #ifndef IS_MPI
383  nrow = natoms - 1
384  ncol = natoms
385 #else
386  nrow = getNrow(plan_row)
387  ncol = getNcol(plan_col)
388  nlocal = natoms
389  j_start = 1
390 #endif
131  
132 +
133    
134   !! See if we need to update neighbor lists
135    call check(q,update_nlist)
395 !  if (firstTime) then
396 !     update_nlist = .true.
397 !     firstTime = .false.
398 !  endif
136  
137   !--------------WARNING...........................
138   ! Zero variables, NOTE:::: Forces are zeroed in C
139   ! Zeroing them here could delete previously computed
140   ! Forces.
141   !------------------------------------------------
142 < #ifndef IS_MPI
406 < !  nloops = nloops + 1
407 <  pe = 0.0E0_DP
408 <
409 < #else
410 <    fRow = 0.0E0_DP
411 <    fCol = 0.0E0_DP
142 >  call zero_module_variables()
143  
413    pe_local = 0.0E0_DP
144  
415    eRow = 0.0E0_DP
416    eCol = 0.0E0_DP
417    eTemp = 0.0E0_DP
418 #endif
419
145   ! communicate MPI positions
146   #ifdef IS_MPI    
147      call gather(q,qRow,plan_row3d)
# Line 430 | Line 155 | contains
155  
156      call gather(A,ARow,plan_row_rotation)
157      call gather(A,ACol,plan_col_rotation)
433
158   #endif
159  
160  
161 <  if (update_nlist) then
161 > #ifdef IS_MPI
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 <     ! save current configuration, contruct neighbor list,
213 <     ! and calculate forces
214 <     call save_neighborList(q)
215 <    
216 <     neighborListSize = getNeighborListSize()
217 <     nlist = 0
218 <    
212 >       point(nrow + 1) = nlist + 1
213 >      
214 >    else !! (update)
215 >
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 >             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 > #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 <     do i = 1, nrow
253 <        point(i) = nlist + 1
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
276 >             endif
277 >          enddo inner
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 <        ljAtype_i => identPtrListRow(i)%this
308 <        tag_i = tagRow(i)
309 <        rxi = qRow(1,i)
310 <        ryi = qRow(2,i)
311 <        rzi = qRow(3,i)
312 < #else
457 <        ljAtype_i   => identPtrList(i)%this
458 <        j_start = i + 1
459 <        rxi = q(1,i)
460 <        ryi = q(2,i)
461 <        rzi = q(3,i)
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 <        inner: do j = j_start, ncol
315 > ! This is the post-pair loop:
316   #ifdef IS_MPI
466 ! Assign identity pointers and tags
467           ljAtype_j => identPtrListColumn(j)%this
468           tag_j = tagColumn(j)
469           if (newtons_thrd) then
470              if (tag_i <= tag_j) then
471                 if (mod(tag_i + tag_j,2) == 0) cycle inner
472              else                
473                 if (mod(tag_i + tag_j,2) == 1) cycle inner
474              endif
475           endif
317  
318 <           rxij = wrap(rxi - qCol(1,j), 1)
319 <           ryij = wrap(ryi - qCol(2,j), 2)
320 <           rzij = wrap(rzi - qCol(3,j), 3)
321 < #else          
322 <           ljAtype_j   => identPtrList(j)%this
323 <           rxij = wrap(rxi - q(1,j), 1)
324 <           ryij = wrap(ryi - q(2,j), 2)
325 <           rzij = wrap(rzi - q(3,j), 3)
485 <      
486 < #endif          
487 <           rijsq = rxij*rxij + ryij*ryij + rzij*rzij
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 >
325 > #else
326  
327 < #ifdef IS_MPI
328 <             if (rijsq <=  rlistsq .AND. &
329 <                  tag_j /= tag_i) then
330 < #else
331 <          
332 <             if (rijsq <  rlistsq) then
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
496            
497              nlist = nlist + 1
498              if (nlist > neighborListSize) then
499                 call expandList(listerror)
500                 if (listerror /= 0) then
501                    FFerror = -1
502                    write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
503                    return
504                 end if
505              endif
506              list(nlist) = j
335  
336 +
337 +
338 +
339 + #ifdef IS_MPI
340 +    !!distribute forces
341 +
342 +    call scatter(fRow,fTemp1,plan_row3d)
343 +    call scatter(fCol,fTemp2,plan_col3d)
344 +
345 +
346 +    do i = 1,nlocal
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,tTemp1,plan_row3d)
352 +       call scatter(tCol,tTemp2,plan_col3d)
353      
354 <              if (rijsq <  rcutsq) then
355 <                
356 <                 r = dsqrt(rijsq)
354 >       do i = 1,nlocal
355 >          tTemp(1:3,i) = tTemp1(1:3,i) + tTemp2(1:3,i)
356 >       end do
357 >    endif
358 >
359 >    if (do_pot) then
360 >       ! scatter/gather pot_row into the members of my column
361 >       call scatter(eRow,eTemp,plan_row)
362        
363 <                 call getLJPot(r,pot,dudr,ljAtype_i,ljAtype_j)
363 >       ! scatter/gather pot_local into all other procs
364 >       ! add resultant to get total pot
365 >       do i = 1, nlocal
366 >          pe_local = pe_local + eTemp(i)
367 >       enddo
368 >
369 >       eTemp = 0.0E0_DP
370 >       call scatter(eCol,eTemp,plan_col)
371 >       do i = 1, nlocal
372 >          pe_local = pe_local + eTemp(i)
373 >       enddo
374        
375 < #ifdef IS_MPI
376 <                eRow(i) = eRow(i) + pot*0.5
517 <                eCol(i) = eCol(i) + pot*0.5
375 >       pe = pe_local
376 >    endif
377   #else
378 <                    pe = pe + pot
379 < #endif                
380 <            
522 <                drdx = -rxij / r
523 <                drdy = -ryij / r
524 <                drdz = -rzij / r
525 <                
526 <                fx = dudr * drdx
527 <                fy = dudr * drdy
528 <                fz = dudr * drdz
529 <                
530 < #ifdef IS_MPI
531 <                fCol(1,j) = fCol(1,j) - fx
532 <                fCol(2,j) = fCol(2,j) - fy
533 <                fCol(3,j) = fCol(3,j) - fz
534 <                
535 <                fRow(1,j) = fRow(1,j) + fx
536 <                fRow(2,j) = fRow(2,j) + fy
537 <                fRow(3,j) = fRow(3,j) + fz
538 < #else
539 <                f(1,j) = f(1,j) - fx
540 <                f(2,j) = f(2,j) - fy
541 <                f(3,j) = f(3,j) - fz
542 <                f(1,i) = f(1,i) + fx
543 <                f(2,i) = f(2,i) + fy
544 <                f(3,i) = f(3,i) + fz
378 > ! Copy local array into return array for c
379 >    f = f+fTemp
380 >    t = t+tTemp
381   #endif
546                
547                if (do_stress) then
548                   tauTemp(1) = tauTemp(1) + fx * rxij
549                   tauTemp(2) = tauTemp(2) + fx * ryij
550                   tauTemp(3) = tauTemp(3) + fx * rzij
551                   tauTemp(4) = tauTemp(4) + fy * rxij
552                   tauTemp(5) = tauTemp(5) + fy * ryij
553                   tauTemp(6) = tauTemp(6) + fy * rzij
554                   tauTemp(7) = tauTemp(7) + fz * rxij
555                   tauTemp(8) = tauTemp(8) + fz * ryij
556                   tauTemp(9) = tauTemp(9) + fz * rzij
557                endif
558             endif
559          enddo inner
560     enddo
382  
383 +    potE = pe
384 +
385 +
386 +    if (do_stress) then
387   #ifdef IS_MPI
388 <     point(nrow + 1) = nlist + 1
388 >       mpi_allreduce = (tau,tauTemp,9,mpi_double_precision,mpi_sum, &
389 >            mpi_comm_world,mpi_err)
390   #else
391 <     point(natoms) = nlist + 1
392 < #endif
391 >       tau = tauTemp
392 > #endif      
393 >    endif
394  
395 <  else
395 >  end subroutine do_force_loop
396  
397 <     ! use the list to find the neighbors
398 <     do i = 1, nrow
399 <        JBEG = POINT(i)
400 <        JEND = POINT(i+1) - 1
401 <        ! check thiat molecule i has neighbors
402 <        if (jbeg .le. jend) then
397 >
398 >
399 >
400 >
401 >
402 >
403 >
404 >
405 >
406 > !! Calculate any pre-force loop components and update nlist if necessary.
407 >  subroutine do_preForce(updateNlist)
408 >    logical, intent(inout) :: updateNlist
409 >
410 >
411 >
412 >  end subroutine do_preForce
413 >
414 >
415 >
416 >
417 >
418 >
419 >
420 >
421 >
422 >
423 >
424 >
425 >
426 > !! Calculate any post force loop components, i.e. reaction field, etc.
427 >  subroutine do_postForce()
428 >
429 >
430 >
431 >  end subroutine do_postForce
432 >
433 >
434 >
435 >
436 >
437 >
438 >
439 >
440 >
441 >
442 >
443 >
444 >
445 >
446 >
447 >
448 >
449 >  subroutine do_pair(atype_i,atype_j,i,j,r_ij,rx_ij,ry_ij,rz_ij)
450 >    type (atype ), pointer, intent(inout) :: atype_i
451 >    type (atype ), pointer, intent(inout) :: atype_j
452 >    integer :: i
453 >    integer :: j
454 >    real ( kind = dp ), intent(inout) :: rx_ij
455 >    real ( kind = dp ), intent(inout) :: ry_ij
456 >    real ( kind = dp ), intent(inout) :: rz_ij
457 >
458 >
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 >  
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 <           ljAtype_i => identPtrListRow(i)%this
470 <           rxi = qRow(1,i)
471 <           ryi = qRow(2,i)
472 <           rzi = qRow(3,i)
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 >       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
582           ljAtype_i   => identPtrList(i)%this
583           rxi = q(1,i)
584           ryi = q(2,i)
585           rzi = q(3,i)
586 #endif
587           do jnab = jbeg, jend
588              j = list(jnab)
589 #ifdef IS_MPI
590              ljAtype_j = identPtrListColumn(j)%this
591              rxij = wrap(rxi - qCol(1,j), 1)
592              ryij = wrap(ryi - qCol(2,j), 2)
593              rzij = wrap(rzi - qCol(3,j), 3)
594 #else
595              ljAtype_j = identPtrList(j)%this
596              rxij = wrap(rxi - q(1,j), 1)
597              ryij = wrap(ryi - q(2,j), 2)
598              rzij = wrap(rzi - q(3,j), 3)
599 #endif
600              rijsq = rxij*rxij + ryij*ryij + rzij*rzij
601              
602              if (rijsq <  rcutsq) then
491  
492 <                 r = dsqrt(rijsq)
493 <                
494 <                 call getLJPot(r,pot,dudr,ljAtype_i,ljAtype_j)
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
516                  eCol(i) = eCol(i) + pot*0.5
517   #else
518 <                pe = pe + pot
518 >                    pe = pe + pot
519   #endif                
520 <  
520 >            
521                  drdx = -rxij / r
522                  drdy = -ryij / r
523                  drdz = -rzij / r
# Line 628 | Line 535 | contains
535                  fRow(2,j) = fRow(2,j) + fy
536                  fRow(3,j) = fRow(3,j) + fz
537   #else
538 <                f(1,j) = f(1,j) - fx
539 <                f(2,j) = f(2,j) - fy
540 <                f(3,j) = f(3,j) - fz
541 <                f(1,i) = f(1,i) + fx
542 <                f(2,i) = f(2,i) + fy
543 <                f(3,i) = f(3,i) + fz
538 >                fTemp(1,j) = fTemp(1,j) - fx
539 >                fTemp(2,j) = fTemp(2,j) - fy
540 >                fTemp(3,j) = fTemp(3,j) - fz
541 >                fTemp(1,i) = fTemp(1,i) + fx
542 >                fTemp(2,i) = fTemp(2,i) + fy
543 >                fTemp(3,i) = fTemp(3,i) + fz
544   #endif
545                  
546                  if (do_stress) then
# Line 647 | Line 554 | contains
554                     tauTemp(8) = tauTemp(8) + fz * ryij
555                     tauTemp(9) = tauTemp(9) + fz * rzij
556                  endif
650                
651                
652             endif
653          enddo
654       endif
655    enddo
656 endif
657
557  
558  
660 #ifdef IS_MPI
661    !!distribute forces
559  
560 <    call scatter(fRow,f,plan_row3d)
664 <    call scatter(fCol,fMPITemp,plan_col3d)
560 >  end subroutine do_pair
561  
666    do i = 1,nlocal
667       f(1:3,i) = f(1:3,i) + fMPITemp(1:3,i)
668    end do
562  
563  
564 <    call scatter(tRow,t,plan_row3d)
565 <    call scatter(tCol,tMPITemp,plan_col3d)
564 >
565 >
566 >
567 >
568 >
569 >
570 >
571 >
572 >
573 >
574 >
575 >
576 >
577 >  subroutine get_interatomic_vector(q_i,q_j,rx_ij,ry_ij,rz_ij,r_sq,r_ij)
578 > !---------------- Arguments-------------------------------
579 >   !! index i
580 >
581 >    !! Position array
582 >    real (kind = dp), dimension(3) :: q_i
583 >    real (kind = dp), dimension(3) :: q_j
584 >    !! x component of vector between i and j
585 >    real ( kind = dp ), intent(out)  :: rx_ij
586 >    !! y component of vector between i and j
587 >    real ( kind = dp ), intent(out)  :: ry_ij
588 >    !! z component of vector between i and j
589 >    real ( kind = dp ), intent(out)  :: rz_ij
590 >    !! magnitude of r squared
591 >    real ( kind = dp ), intent(out) :: r_sq
592 >    !! magnitude of vector r between atoms i and j.
593 >    real ( kind = dp ), intent(out) :: r_ij
594 >    !! wrap into periodic box.
595 >    logical, intent(in) :: wrap
596 >
597 > !--------------- Local Variables---------------------------
598 >    !! Distance between i and j
599 >    real( kind = dp ) :: d(3)
600 > !---------------- END DECLARATIONS-------------------------
601 >
602 >
603 > ! Find distance between i and j
604 >    d(1:3) = q_i(1:3) - q_j(1:3)
605 >
606 > ! Wrap back into periodic box if necessary
607 >    if ( wrap ) then
608 >       d(1:3) = d(1:3) - thisSim%box(1:3) * sign(1.0_dp,thisSim%box(1:3)) * &
609 >            int(abs(d(1:3)/thisSim%box(1:3) + 0.5_dp)
610 >    end if
611      
612 <    do i = 1,nlocal
613 <       t(1:3,i) = t(1:3,i) + tMPITemp(1:3,i)
614 <    end do
612 > !   Find Magnitude of the vector
613 >    r_sq = dot_product(d,d)
614 >    r_ij = sqrt(r_sq)
615  
616 + !   Set each component for force calculation
617 +    rx_ij = d(1)
618 +    ry_ij = d(2)
619 +    rz_ij = d(3)
620  
679    if (do_pot) then
680       ! scatter/gather pot_row into the members of my column
681       call scatter(eRow,eTemp,plan_row)
682      
683       ! scatter/gather pot_local into all other procs
684       ! add resultant to get total pot
685       do i = 1, nlocal
686          pe_local = pe_local + eTemp(i)
687       enddo
688       if (newtons_thrd) then
689          eTemp = 0.0E0_DP
690          call scatter(eCol,eTemp,plan_col)
691          do i = 1, nlocal
692             pe_local = pe_local + eTemp(i)
693          enddo
694       endif
695       pe = pe_local
696    endif
621  
622 +  end subroutine get_interatomic_vector
623 +
624 +  subroutine zero_module_variables()
625 +
626 + #ifndef IS_MPI
627 +
628 +    pe = 0.0E0_DP
629 +    tauTemp = 0.0_dp
630 +    fTemp = 0.0_dp
631 +    tTemp = 0.0_dp
632 + #else
633 +    qRow = 0.0_dp
634 +    qCol = 0.0_dp
635 +    
636 +    muRow = 0.0_dp
637 +    muCol = 0.0_dp
638 +    
639 +    u_lRow = 0.0_dp
640 +    u_lCol = 0.0_dp
641 +    
642 +    ARow = 0.0_dp
643 +    ACol = 0.0_dp
644 +    
645 +    fRow = 0.0_dp
646 +    fCol = 0.0_dp
647 +    
648 +  
649 +    tRow = 0.0_dp
650 +    tCol = 0.0_dp
651 +
652 +  
653 +
654 +    eRow = 0.0_dp
655 +    eCol = 0.0_dp
656 +    eTemp = 0.0_dp
657   #endif
658  
659 <    potE = pe
659 >  end subroutine zero_module_variables
660  
661  
662 <    if (do_stress) then
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 checkExcludes(atom1,atom2) result(do_cycle)
666 > !--------------- Arguments--------------------------
667 > ! Index i
668 >    integer,intent(in) :: atom1
669 > ! Index 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 >    integer :: i
677 > !--------------- END DECLARATIONS------------------  
678 >    do_cycle = .false.
679 >
680   #ifdef IS_MPI
681 <       mpi_allreduce = (tau,tauTemp,9,mpi_double_precision,mpi_sum, &
706 <            mpi_comm_world,mpi_err)
681 >    tag_i = tagRow(atom1)
682   #else
683 <       tau = tauTemp
684 < #endif      
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 >
701 >
702 >    if (tag_i == tag_j) then
703 >       do_cycle = .true.
704 >       return
705 >    end if
706 >
707 >    if (tag_i < tag_j) then
708 >       if (mod(tag_i + tag_j,2) == 0) do_cycle = .true.
709 >       return
710 >    else                
711 >       if (mod(tag_i + tag_j,2) == 1) do_cycle = .true.
712      endif
713  
714  
713  end subroutine do_force_loop
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