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 293 by mmeineke, Thu Mar 6 16:07:57 2003 UTC vs.
Revision 317 by gezelter, Tue Mar 11 23:13:06 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.2 2003-03-06 16:07:55 mmeineke Exp $, $Date: 2003-03-06 16:07:55 $, $Name: not supported by cvs2svn $, $Revision: 1.2 $
7 > !! @version $Id: do_Forces.F90,v 1.11 2003-03-11 23:13:06 gezelter Exp $, $Date: 2003-03-11 23:13:06 $, $Name: not supported by cvs2svn $, $Revision: 1.11 $
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  
32 < !! Global list of lj atypes in simulation
29 <  type (atype), pointer :: ListHead => null()
30 <  type (atype), pointer :: ListTail => null()
32 > contains
33  
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)
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.
40 +    real( kind = dp), dimension(9,getNlocal()) :: A
41 +    
42 +    !! Magnitude dipole moment
43 +    real( kind = dp ), dimension(3,getNlocal()) :: mu
44 +    !! Unit vectors for dipoles (lab frame)
45 +    real( kind = dp ), dimension(3,getNlocal()) :: u_l
46 +    !! Force array provided by C, dimensioned by getNlocal
47 +    real ( kind = dp ), dimension(3,getNlocal()) :: f
48 +    !! Torsion array provided by C, dimensioned by getNlocal
49 +    real( kind = dp ), dimension(3,getNlocal()) :: t
50 +    
51 +    !! Stress Tensor
52 +    real( kind = dp), dimension(9) :: tau
53 +    
54 +    real ( kind = dp ) :: potE
55 +    logical ( kind = 2) :: do_pot
56 +    integer :: FFerror
57  
58 < !! LJ mixing array  
59 < !  type (lj_atype), dimension(:,:), pointer :: ljMixed => null()
58 > #ifdef IS_MPI
59 >    real( kind = DP ) :: pot_local
60 > #endif
61 >    
62 >    real( kind = DP )   :: pe
63 >    logical             :: update_nlist
64 >    
65  
66 +    integer ::  i, j, jbeg, jend, jnab, idim, jdim, idim2, jdim2, dim, dim2
67 +    integer :: nlist
68 +    integer :: j_start
69 +    
70 +    real( kind = DP ) ::  r_ij, pot, ftmp, dudr, d2, drdx1, kt1, kt2, kt3, ktmp
71 +    
72 +    real( kind = DP ) ::  rx_ij, ry_ij, rz_ij, rijsq
73 +    real( kind = DP ) ::  rlistsq, rcutsq, rlist, rcut
74  
75 <  logical, save :: firstTime = .True.
38 <
39 < !! Atype identity pointer lists
75 >    ! a rig that need to be fixed.
76   #ifdef IS_MPI
77 < !! Row lj_atype pointer list
78 <  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()
77 >    real( kind = dp ) :: pe_local
78 >    integer :: nlocal
79   #endif
80 +    integer :: nrow
81 +    integer :: ncol
82 +    integer :: natoms
83 +    integer :: neighborListSize
84 +    integer :: listerror
85 +    !! should we calculate the stress tensor
86 +    logical  :: do_stress = .false.
87 +    FFerror = 0
88  
89 <
90 < !! Logical has lj force field module been initialized?
91 <  logical, save :: isFFinit = .false.
92 <
53 <
54 < !! Public methods and data
55 <  public :: new_atype
56 <  public :: do_forceLoop
57 <  public :: getLjPot
58 <  public :: init_FF
59 <
60 <  
61 <
62 <
63 < contains
64 <
65 < !! 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
89 >    ! Make sure we are properly initialized.
90 >    if (.not. isFFInit) then
91 >       write(default_error,*) "ERROR: lj_FF has not been properly initialized"
92 >       FFerror = -1
93         return
94 <    end if
94 >    endif
95 > #ifdef IS_MPI
96 >    if (.not. isMPISimSet()) then
97 >       write(default_error,*) "ERROR: mpiSimulation has not been properly initialized"
98 >       FFerror = -1
99 >       return
100 >    endif
101 > #endif
102 >    
103 >    !! initialize local variables  
104 >    natoms = getNlocal()
105 >    call getRcut(rcut,rcut2=rcutsq)
106 >    call getRlist(rlist,rlistsq)
107 >    
108 >    !! See if we need to update neighbor lists
109 >    call check(q, update_nlist)
110 >    
111 >    !--------------WARNING...........................
112 >    ! Zero variables, NOTE:::: Forces are zeroed in C
113 >    ! Zeroing them here could delete previously computed
114 >    ! Forces.
115 >    !------------------------------------------------
116 >    call zero_module_variables()
117  
118 < ! assign our new atype information
119 <    the_new_atype%mass        = mass
120 <    the_new_atype%epsilon     = epsilon
121 <    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 <
118 >    ! communicate MPI positions
119 > #ifdef IS_MPI    
120 >    call gather(q,q_Row,plan_row3d)
121 >    call gather(q,q_Col,plan_col3d)
122      
123 < ! assume that this atype will be successfully added
124 <    the_new_atype%atype_ident = ident
113 <    the_new_atype%atype_number = n_lj_atypes + 1
123 >    call gather(u_l,u_l_Row,plan_row3d)
124 >    call gather(u_l,u_l_Col,plan_col3d)
125      
126 <    if ( is_Sticky /= 0 )    the_new_atype%is_Sticky   = .true.
127 <    if ( is_GB /= 0 )        the_new_atype%is_GB       = .true.
128 <    if ( is_LJ /= 0 )        the_new_atype%is_LJ       = .true.
118 <    if ( is_DP /= 0 )        the_new_atype%is_DP       = .true.
126 >    call gather(A,A_Row,plan_row_rotation)
127 >    call gather(A,A_Col,plan_col_rotation)
128 > #endif
129  
120    call add_atype(the_new_atype,ListHead,ListTail,err_stat)
121    if (err_stat /= 0 ) then
122       status = -1
123       return
124    endif
130  
131 <    n_atypes = n_atypes + 1
131 > #ifdef IS_MPI
132 >    
133 >    if (update_nlist) then
134 >      
135 >       ! save current configuration, contruct neighbor list,
136 >       ! and calculate forces
137 >       call save_neighborList(q)
138 >      
139 >       neighborListSize = getNeighborListSize()
140 >       nlist = 0
141 >      
142 >       nrow = getNrow(plan_row)
143 >       ncol = getNcol(plan_col)
144 >       nlocal = getNlocal()
145 >      
146 >       do i = 1, nrow
147 >          point(i) = nlist + 1
148 >          
149 >          inner: do j = 1, ncol
150 >            
151 >             if (check_exclude(i,j)) cycle inner:
152  
153 +             call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
154 +            
155 +             if (rijsq <  rlistsq) then            
156 +                
157 +                nlist = nlist + 1
158 +                
159 +                if (nlist > neighborListSize) then
160 +                   call expandList(listerror)
161 +                   if (listerror /= 0) then
162 +                      FFerror = -1
163 +                      write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
164 +                      return
165 +                   end if
166 +                endif
167 +                
168 +                list(nlist) = j
169 +                                
170 +                if (rijsq <  rcutsq) then
171 +                   call do_pair(i, j, rijsq, d)
172 +                endif
173 +             endif
174 +          enddo inner
175 +       enddo
176  
177 <  end subroutine new_atype
177 >       point(nrow + 1) = nlist + 1
178 >      
179 >    else !! (update)
180  
181 +       ! use the list to find the neighbors
182 +       do i = 1, nrow
183 +          JBEG = POINT(i)
184 +          JEND = POINT(i+1) - 1
185 +          ! check thiat molecule i has neighbors
186 +          if (jbeg .le. jend) then
187 +            
188 +             do jnab = jbeg, jend
189 +                j = list(jnab)
190  
191 <  subroutine init_FF(nComponents,ident, status)
192 < !! 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
191 >                call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
192 >                call do_pair(i, j, rijsq, d)
193  
194 <    integer :: alloc_stat
194 >             enddo
195 >          endif
196 >       enddo
197 >    endif
198  
199 <    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 <
199 > #else
200      
201 +    if (update_nlist) then
202 +      
203 +       ! save current configuration, contruct neighbor list,
204 +       ! and calculate forces
205 +       call save_neighborList(q)
206 +      
207 +       neighborListSize = getNeighborListSize()
208 +       nlist = 0
209 +          
210 +       do i = 1, natoms-1
211 +          point(i) = nlist + 1
212  
213 < !! 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
213 >          inner: do j = i+1, natoms
214  
215 +             if (check_exclude(i,j)) cycle inner:
216 +
217 +             call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
218 +          
219 +             if (rijsq <  rlistsq) then
220 +                
221 +                nlist = nlist + 1
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
231 +                
232 +                list(nlist) = j
233 +                    
234 +                if (rijsq <  rcutsq) then
235 +                   call do_pair(i, j, rijsq, d)
236 +                endif
237 +             endif
238 +          enddo inner
239 +       enddo
240 +      
241 +       point(natoms) = nlist + 1
242 +      
243 +    else !! (update)
244 +      
245 +       ! use the list to find the neighbors
246 +       do i = 1, nrow
247 +          JBEG = POINT(i)
248 +          JEND = POINT(i+1) - 1
249 +          ! check thiat molecule i has neighbors
250 +          if (jbeg .le. jend) then
251 +            
252 +             do jnab = jbeg, jend
253 +                j = list(jnab)
254 +
255 +                call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
256 +                call do_pair(i, j, rijsq, d)
257 +
258 +             enddo
259 +          endif
260 +       enddo
261 +    endif
262      
263 < ! if were're in MPI, we also have to worry about row and col lists    
263 > #endif
264 >    
265 >    
266 > #ifdef IS_MPI
267 >    !! distribute all reaction field stuff (or anything for post-pair):
268 >    call scatter(rflRow,rflTemp1,plan_row3d)
269 >    call scatter(rflCol,rflTemp2,plan_col3d)
270 >    do i = 1,nlocal
271 >       rflTemp(1:3,i) = rflTemp1(1:3,i) + rflTemp2(1:3,i)
272 >    end do
273 > #endif
274 >    
275 > ! This is the post-pair loop:
276 > #ifdef IS_MPI
277 >    
278 >    if (system_has_postpair_atoms) then
279 >       do i = 1, nlocal
280 >          Atype_i => identPtrListRow(i)%this
281 >          call do_postpair(i, Atype_i)
282 >       enddo
283 >    endif
284 >    
285   #else
286 <  
287 < ! We can only set up forces if mpiSimulation has been setup.
288 <    if (.not. isMPISimSet()) then
289 <       write(default_error,*) "MPI is not set"
290 <       status = -1
291 <       return
286 >    
287 >    if (system_has_postpair_atoms) then
288 >       do i = 1, natoms
289 >          Atype_i => identPtr(i)%this
290 >          call do_postpair(i, Atype_i)
291 >       enddo
292      endif
293 <    nrow = getNrow(plan_row)
294 <    ncol = getNcol(plan_col)
295 <    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
293 >    
294 > #endif
295 >    
296  
297 <    allocate(identCol(ncol),stat=alloc_stat)
298 <    if (alloc_stat /= 0 ) then
188 <       status = -1
189 <       return
190 <    endif
297 > #ifdef IS_MPI
298 >    !!distribute forces
299  
300 < !! Gather idents into row and column idents
301 <
302 <    call gather(ident,identRow,plan_row)
303 <    call gather(ident,identCol,plan_col)
300 >    call scatter(f_Row,f,plan_row3d)
301 >    call scatter(f_Col,f_temp,plan_col3d)
302 >    do i = 1,nlocal
303 >       f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
304 >    end do
305 >
306 >    if (doTorque()) then
307 >       call scatter(t_Row,t,plan_row3d)
308 >       call scatter(t_Col,t_temp,plan_col3d)
309      
310 <  
311 < !! Create row and col pointer lists
312 <  
200 <    call create_IdentPtrlst(identRow,ListHead,identPtrListRow,thisStat)
201 <    if (thisStat /= 0 ) then
202 <       status = -1
203 <       return
310 >       do i = 1,nlocal
311 >          t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
312 >       end do
313      endif
314 <  
315 <    call create_IdentPtrlst(identCol,ListHead,identPtrListColumn,thisStat)
316 <    if (thisStat /= 0 ) then
317 <       status = -1
318 <       return
314 >    
315 >    if (do_pot) then
316 >       ! scatter/gather pot_row into the members of my column
317 >       call scatter(pot_Row, pot_Temp, plan_row)
318 >      
319 >       ! scatter/gather pot_local into all other procs
320 >       ! add resultant to get total pot
321 >       do i = 1, nlocal
322 >          pot_local = pot_local + pot_Temp(i)
323 >       enddo
324 >
325 >       pot_Temp = 0.0_DP
326 >
327 >       call scatter(pot_Col, pot_Temp, plan_col)
328 >       do i = 1, nlocal
329 >          pot_local = pot_local + pot_Temp(i)
330 >       enddo
331 >      
332 >       pot = pot_local
333      endif
334  
335 < !! free temporary ident arrays
336 <    if (allocated(identCol)) then
337 <       deallocate(identCol)
338 <    end if
339 <    if (allocated(identCol)) then
217 <       deallocate(identRow)
335 >    if (doStress()) then
336 >       mpi_allreduce(tau, tau_Temp,9,mpi_double_precision,mpi_sum, &
337 >            mpi_comm_world,mpi_err)
338 >       mpi_allreduce(virial, virial_Temp,1,mpi_double_precision,mpi_sum, &
339 >            mpi_comm_world,mpi_err)
340      endif
341  
342   #endif
221    
222    call initForce_Modules(thisStat)
223    if (thisStat /= 0) then
224       status = -1
225       return
226    endif
343  
344 < !! Create neighbor lists
345 <    call expandList(thisStat)
346 <    if (thisStat /= 0) then
231 <       status = -1
232 <       return
344 >    if (doStress()) then
345 >       tau = tau_Temp
346 >       virial = virial_Temp
347      endif
348  
349 <    isFFinit = .true.
349 >  end subroutine do_force_loop
350  
351  
352 <  end subroutine init_FF
352 > !! Calculate any pre-force loop components and update nlist if necessary.
353 >  subroutine do_preForce(updateNlist)
354 >    logical, intent(inout) :: updateNlist
355  
356  
357  
358 +  end subroutine do_preForce
359  
360 <  subroutine initForce_Modules(thisStat)
361 <    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
360 > !! Calculate any post force loop components, i.e. reaction field, etc.
361 >  subroutine do_postForce()
362  
254  end subroutine initForce_Modules
363  
364  
365 +  end subroutine do_postForce
366  
367 +  subroutine do_pair(i, j, rijsq, d)
368  
369 < !! FORCE routine Calculates Lennard Jones forces.
370 < !------------------------------------------------------------->
371 <  subroutine do__force_loop(q,A,mu,u_l,f,t,tau,potE,do_pot,FFerror)
372 < !! Position array provided by C, dimensioned by getNlocal
263 <    real ( kind = dp ), dimension(3,getNlocal()) :: q
264 <  !! Rotation Matrix for each long range particle in simulation.
265 <    real( kind = dp), dimension(9,getNlocal()) :: A
369 >    integer, intent(in) :: i, j
370 >    real ( kind = dp ), intent(in)    :: rijsq
371 >    real ( kind = dp )                :: r
372 >    real ( kind = dp ), intent(inout) :: d(3)
373  
374 <  !! Magnitude dipole moment
268 <    real( kind = dp ), dimension(3,getNlocal()) :: mu
269 <  !! Unit vectors for dipoles (lab frame)
270 <    real( kind = dp ), dimension(3,getNlocal()) :: u_l
271 < !! Force array provided by C, dimensioned by getNlocal
272 <    real ( kind = dp ), dimension(3,getNlocal()) :: f
273 < !! Torsion array provided by C, dimensioned by getNlocal
274 <    real( kind = dp ), dimension(3,getNlocal()) :: t
275 <
276 < !! Stress Tensor
277 <    real( kind = dp), dimension(9) :: tau
278 <    real( kind = dp), dimension(9) :: tauTemp
279 <    real ( kind = dp ) :: potE
280 <    logical ( kind = 2) :: do_pot
281 <    integer :: FFerror
282 <
374 >    r = sqrt(rijsq)
375      
376 <    type(atype), pointer :: Atype_i
377 <    type(atype), pointer :: Atype_j
376 >    logical :: is_LJ_i, is_LJ_j
377 >    logical :: is_DP_i, is_DP_j
378 >    logical :: is_Sticky_i, is_Sticky_j
379 >    integer :: me_i, me_j
380  
381 + #ifdef IS_MPI
382  
383 +    me_i = atid_row(i)
384 +    me_j = atid_col(j)
385  
386 + #else
387  
388 <  
388 >    me_i = atid(i)
389 >    me_j = atid(j)
390  
391 < #ifdef IS_MPI
293 <  real( kind = DP ) :: pot_local
391 > #endif
392  
393 < !! Local arrays needed for MPI
394 <  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
393 >    call getElementProperty(atypes, me_i, "is_LJ", is_LJ_i)
394 >    call getElementProperty(atypes, me_j, "is_LJ", is_LJ_j)
395  
396 <  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
396 >    if ( is_LJ_i .and. is_LJ_j ) call do_lj_pair(i, j, d, r, pot, f)
397  
398 <  real(kind = dp), dimension(3,getNrow(plan_row)) :: u_lRow = 0.0_dp
399 <  real(kind = dp), dimension(3,getNcol(plan_col)) :: u_lCol = 0.0_dp
398 >    call getElementProperty(atypes, me_i, "is_DP", is_DP_i)
399 >    call getElementProperty(atypes, me_j, "is_DP", is_DP_j)
400  
401 <  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
401 >    if ( is_DP_i .and. is_DP_j ) then
402  
403 <  
403 >       call do_dipole_pair(i, j, d, r, pot, u_l, f, t)
404  
405 <  real(kind = dp), dimension(3,getNrow(plan_row)) :: fRow = 0.0_dp
406 <  real(kind = dp), dimension(3,getNcol(plan_col)) :: fCol = 0.0_dp
407 <  real(kind = dp), dimension(3,getNlocal()) :: fMPITemp = 0.0_dp
405 >       if (do_reaction_field) then
406 >          call accumulate_rf(i, j, r_ij)
407 >       endif
408  
409 <  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
409 >    endif
410  
411 +    call getElementProperty(atypes, me_i, "is_Sticky", is_Sticky_i)
412 +    call getElementProperty(atypes, me_j, "is_Sticky", is_Sticky_j)
413  
414 <  real(kind = dp), dimension(getNrow(plan_row)) :: eRow = 0.0_dp
415 <  real(kind = dp), dimension(getNcol(plan_col)) :: eCol = 0.0_dp
414 >    if ( is_Sticky_i .and. is_Sticky_j ) then
415 >       call do_sticky_pair(i, j, d, r, pot, u_l, f, t)
416 >    endif
417  
418 <  real(kind = dp), dimension(getNlocal()) :: eTemp = 0.0_dp
418 >      
419 >  end subroutine do_pair
420  
324 #endif
421  
422 +  subroutine get_interatomic_vector(q_i, q_j, d, r_sq)
423 +    
424 +    real (kind = dp), dimension(3) :: q_i
425 +    real (kind = dp), dimension(3) :: q_j
426 +    real ( kind = dp ), intent(out) :: r_sq
427 +    real( kind = dp ) :: d(3)
428  
429 +    d(1:3) = q_i(1:3) - q_j(1:3)
430 +    
431 +    ! Wrap back into periodic box if necessary
432 +    if ( isPBC() ) then
433 +       d(1:3) = d(1:3) - thisSim%box(1:3) * sign(1.0_dp,thisSim%box(1:3)) * &
434 +            int(abs(d(1:3)/thisSim%box(1:3) + 0.5_dp)
435 +    endif
436 +    
437 +    r_sq = dot_product(d,d)
438 +        
439 +  end subroutine get_interatomic_vector
440 +  
441 +  subroutine zero_module_variables()
442  
328  real( kind = DP )   :: pe
329  logical             :: update_nlist
330
331
332  integer ::  i, j, jbeg, jend, jnab, idim, jdim, idim2, jdim2, dim, dim2
333  integer :: nlist
334  integer :: j_start
335  integer :: tag_i,tag_j
336  real( kind = DP ) ::  r, pot, ftmp, dudr, d2, drdx1, kt1, kt2, kt3, ktmp
337  real( kind = dp ) :: fx,fy,fz
338  real( kind = DP ) ::  drdx, drdy, drdz
339  real( kind = DP ) ::  rxi, ryi, rzi, rxij, ryij, rzij, rijsq
340  real( kind = DP ) ::  rlistsq, rcutsq,rlist,rcut
341
342  real( kind = DP ) :: dielectric = 0.0_dp
343
344 ! a rig that need to be fixed.
345 #ifdef IS_MPI
346  logical :: newtons_thrd = .true.
347  real( kind = dp ) :: pe_local
348  integer :: nlocal
349 #endif
350  integer :: nrow
351  integer :: ncol
352  integer :: natoms
353  integer :: neighborListSize
354  integer :: listerror
355 !! should we calculate the stress tensor
356  logical  :: do_stress = .false.
357
358
359  FFerror = 0
360
361 ! Make sure we are properly initialized.
362  if (.not. isFFInit) then
363     write(default_error,*) "ERROR: lj_FF has not been properly initialized"
364     FFerror = -1
365     return
366  endif
367 #ifdef IS_MPI
368    if (.not. isMPISimSet()) then
369     write(default_error,*) "ERROR: mpiSimulation has not been properly initialized"
370     FFerror = -1
371     return
372  endif
373 #endif
374
375 !! initialize local variables  
376  natoms = getNlocal()
377  call getRcut(rcut,rcut2=rcutsq)
378  call getRlist(rlist,rlistsq)
379 !! Find ensemble
380  if (isEnsemble("NPT")) do_stress = .true.
381
443   #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
444  
445 +    pe = 0.0E0_DP
446 +    tauTemp = 0.0_dp
447 +    fTemp = 0.0_dp
448 +    tTemp = 0.0_dp
449 + #else
450 +    qRow = 0.0_dp
451 +    qCol = 0.0_dp
452 +    
453 +    muRow = 0.0_dp
454 +    muCol = 0.0_dp
455 +    
456 +    u_lRow = 0.0_dp
457 +    u_lCol = 0.0_dp
458 +    
459 +    ARow = 0.0_dp
460 +    ACol = 0.0_dp
461 +    
462 +    fRow = 0.0_dp
463 +    fCol = 0.0_dp
464 +    
465    
466 < !! See if we need to update neighbor lists
467 <  call check(q,update_nlist)
395 < !  if (firstTime) then
396 < !     update_nlist = .true.
397 < !     firstTime = .false.
398 < !  endif
399 <
400 < !--------------WARNING...........................
401 < ! Zero variables, NOTE:::: Forces are zeroed in C
402 < ! Zeroing them here could delete previously computed
403 < ! Forces.
404 < !------------------------------------------------
405 < #ifndef IS_MPI
406 < !  nloops = nloops + 1
407 <  pe = 0.0E0_DP
466 >    tRow = 0.0_dp
467 >    tCol = 0.0_dp
468  
469 < #else
410 <    fRow = 0.0E0_DP
411 <    fCol = 0.0E0_DP
469 >  
470  
471 <    pe_local = 0.0E0_DP
472 <
473 <    eRow = 0.0E0_DP
416 <    eCol = 0.0E0_DP
417 <    eTemp = 0.0E0_DP
471 >    eRow = 0.0_dp
472 >    eCol = 0.0_dp
473 >    eTemp = 0.0_dp
474   #endif
475  
476 < ! communicate MPI positions
421 < #ifdef IS_MPI    
422 <    call gather(q,qRow,plan_row3d)
423 <    call gather(q,qCol,plan_col3d)
476 >  end subroutine zero_module_variables
477  
425    call gather(mu,muRow,plan_row3d)
426    call gather(mu,muCol,plan_col3d)
478  
479 <    call gather(u_l,u_lRow,plan_row3d)
480 <    call gather(u_l,u_lCol,plan_col3d)
479 > !! Function to properly build neighbor lists in MPI using newtons 3rd law.
480 > !! We don't want 2 processors doing the same i j pair twice.
481 > !! Also checks to see if i and j are the same particle.
482 >  function checkExcludes(atom1,atom2) result(do_cycle)
483 > !--------------- Arguments--------------------------
484 > ! Index i
485 >    integer,intent(in) :: atom1
486 > ! Index j
487 >    integer,intent(in), optional :: atom2
488 > ! Result do_cycle
489 >    logical :: do_cycle
490 > !--------------- Local variables--------------------
491 >    integer :: tag_i
492 >    integer :: tag_j
493 >    integer :: i
494 > !--------------- END DECLARATIONS------------------  
495 >    do_cycle = .false.
496  
431    call gather(A,ARow,plan_row_rotation)
432    call gather(A,ACol,plan_col_rotation)
433
434 #endif
435
436
437  if (update_nlist) then
438
439     ! save current configuration, contruct neighbor list,
440     ! and calculate forces
441     call save_neighborList(q)
442    
443     neighborListSize = getNeighborListSize()
444     nlist = 0
445    
446    
447
448     do i = 1, nrow
449        point(i) = nlist + 1
497   #ifdef IS_MPI
498 <        ljAtype_i => identPtrListRow(i)%this
452 <        tag_i = tagRow(i)
453 <        rxi = qRow(1,i)
454 <        ryi = qRow(2,i)
455 <        rzi = qRow(3,i)
498 >    tag_i = tagRow(atom1)
499   #else
500 <        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)
500 >    tag_i = tag(atom1)
501   #endif
502  
503 <        inner: do j = j_start, ncol
504 < #ifdef IS_MPI
505 < ! Assign identity pointers and tags
506 <           ljAtype_j => identPtrListColumn(j)%this
507 <           tag_j = tagColumn(j)
508 <           if (newtons_thrd) then
509 <              if (tag_i <= tag_j) then
510 <                 if (mod(tag_i + tag_j,2) == 0) cycle inner
511 <              else                
512 <                 if (mod(tag_i + tag_j,2) == 1) cycle inner
474 <              endif
475 <           endif
476 <
477 <           rxij = wrap(rxi - qCol(1,j), 1)
478 <           ryij = wrap(ryi - qCol(2,j), 2)
479 <           rzij = wrap(rzi - qCol(3,j), 3)
480 < #else          
481 <           ljAtype_j   => identPtrList(j)%this
482 <           rxij = wrap(rxi - q(1,j), 1)
483 <           ryij = wrap(ryi - q(2,j), 2)
484 <           rzij = wrap(rzi - q(3,j), 3)
485 <      
486 < #endif          
487 <           rijsq = rxij*rxij + ryij*ryij + rzij*rzij
503 > !! Check global excludes first
504 >    if (.not. present(atom2)) then
505 >       do i = 1,nGlobalExcludes
506 >          if (excludeGlobal(i) == tag_i) then
507 >             do_cycle = .true.
508 >             return
509 >          end if
510 >       end do
511 >       return !! return after checking globals
512 >    end if
513  
514 < #ifdef IS_MPI
515 <             if (rijsq <=  rlistsq .AND. &
491 <                  tag_j /= tag_i) then
492 < #else
493 <          
494 <             if (rijsq <  rlistsq) then
495 < #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
514 > !! we return if j not present here.
515 >    tag_j = tagColumn(j)
516  
508    
509              if (rijsq <  rcutsq) then
510                
511                 r = dsqrt(rijsq)
512      
513                 call getLJPot(r,pot,dudr,ljAtype_i,ljAtype_j)
514      
515 #ifdef IS_MPI
516                eRow(i) = eRow(i) + pot*0.5
517                eCol(i) = eCol(i) + pot*0.5
518 #else
519                    pe = pe + pot
520 #endif                
521            
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
545 #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
561
562 #ifdef IS_MPI
563     point(nrow + 1) = nlist + 1
564 #else
565     point(natoms) = nlist + 1
566 #endif
567
568  else
569
570     ! use the list to find the neighbors
571     do i = 1, nrow
572        JBEG = POINT(i)
573        JEND = POINT(i+1) - 1
574        ! check thiat molecule i has neighbors
575        if (jbeg .le. jend) then
576 #ifdef IS_MPI
577           ljAtype_i => identPtrListRow(i)%this
578           rxi = qRow(1,i)
579           ryi = qRow(2,i)
580           rzi = qRow(3,i)
581 #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
603
604                 r = dsqrt(rijsq)
605                
606                 call getLJPot(r,pot,dudr,ljAtype_i,ljAtype_j)
607 #ifdef IS_MPI
608                eRow(i) = eRow(i) + pot*0.5
609                eCol(i) = eCol(i) + pot*0.5
610 #else
611                pe = pe + pot
612 #endif                
613  
614                drdx = -rxij / r
615                drdy = -ryij / r
616                drdz = -rzij / r
617                
618                fx = dudr * drdx
619                fy = dudr * drdy
620                fz = dudr * drdz
621                
622 #ifdef IS_MPI
623                fCol(1,j) = fCol(1,j) - fx
624                fCol(2,j) = fCol(2,j) - fy
625                fCol(3,j) = fCol(3,j) - fz
626                
627                fRow(1,j) = fRow(1,j) + fx
628                fRow(2,j) = fRow(2,j) + fy
629                fRow(3,j) = fRow(3,j) + fz
630 #else
631                f(1,j) = f(1,j) - fx
632                f(2,j) = f(2,j) - fy
633                f(3,j) = f(3,j) - fz
634                f(1,i) = f(1,i) + fx
635                f(2,i) = f(2,i) + fy
636                f(3,i) = f(3,i) + fz
637 #endif
638                
639                if (do_stress) then
640                   tauTemp(1) = tauTemp(1) + fx * rxij
641                   tauTemp(2) = tauTemp(2) + fx * ryij
642                   tauTemp(3) = tauTemp(3) + fx * rzij
643                   tauTemp(4) = tauTemp(4) + fy * rxij
644                   tauTemp(5) = tauTemp(5) + fy * ryij
645                   tauTemp(6) = tauTemp(6) + fy * rzij
646                   tauTemp(7) = tauTemp(7) + fz * rxij
647                   tauTemp(8) = tauTemp(8) + fz * ryij
648                   tauTemp(9) = tauTemp(9) + fz * rzij
649                endif
650                
651                
652             endif
653          enddo
654       endif
655    enddo
656 endif
517  
518  
519 +    if (tag_i == tag_j) then
520 +       do_cycle = .true.
521 +       return
522 +    end if
523  
524 < #ifdef IS_MPI
525 <    !!distribute forces
524 >    if (tag_i < tag_j) then
525 >       if (mod(tag_i + tag_j,2) == 0) do_cycle = .true.
526 >       return
527 >    else                
528 >       if (mod(tag_i + tag_j,2) == 1) do_cycle = .true.
529 >    endif
530  
663    call scatter(fRow,f,plan_row3d)
664    call scatter(fCol,fMPITemp,plan_col3d)
531  
666    do i = 1,nlocal
667       f(1:3,i) = f(1:3,i) + fMPITemp(1:3,i)
668    end do
532  
533 <
534 <    call scatter(tRow,t,plan_row3d)
535 <    call scatter(tCol,tMPITemp,plan_col3d)
536 <    
537 <    do i = 1,nlocal
675 <       t(1:3,i) = t(1:3,i) + tMPITemp(1:3,i)
533 >    do i = 1, nLocalExcludes
534 >       if (tag_i = excludes(1,i) .and. excludes(2,i) < 0) then
535 >          do_cycle = .true.
536 >          return
537 >       end if
538      end do
677
678
679    if (do_pot) then
680       ! scatter/gather pot_row into the members of my column
681       call scatter(eRow,eTemp,plan_row)
539        
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
540  
541 < #endif
541 >  end function checkExcludes
542  
700    potE = pe
543  
702
703    if (do_stress) then
704 #ifdef IS_MPI
705       mpi_allreduce = (tau,tauTemp,9,mpi_double_precision,mpi_sum, &
706            mpi_comm_world,mpi_err)
707 #else
708       tau = tauTemp
709 #endif      
710    endif
711
712
713  end subroutine do_force_loop
714
715
716
544   end module do_Forces

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines