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 309 by gezelter, Mon Mar 10 23:19:23 2003 UTC vs.
Revision 329 by gezelter, Wed Mar 12 22:27:59 2003 UTC

# Line 4 | Line 4
4  
5   !! @author Charles F. Vardeman II
6   !! @author Matthew Meineke
7 < !! @version $Id: do_Forces.F90,v 1.9 2003-03-10 23:19:23 gezelter Exp $, $Date: 2003-03-10 23:19:23 $, $Name: not supported by cvs2svn $, $Revision: 1.9 $
7 > !! @version $Id: do_Forces.F90,v 1.15 2003-03-12 22:27:59 gezelter Exp $, $Date: 2003-03-12 22:27:59 $, $Name: not supported by cvs2svn $, $Revision: 1.15 $
8  
9  
10  
11   module do_Forces
12    use simulation
13    use definitions
14 <  use forceGlobals
15 <  use atype_typedefs
16 <  use neighborLists
17 <
18 <  
19 <  use lj
14 >  use atype_module
15 >  use neighborLists  
16 >  use lj_FF
17    use sticky_FF
18    use dipole_dipole
19    use gb_FF
# Line 27 | Line 24 | public :: do_force_loop
24    implicit none
25    PRIVATE
26  
27 < public :: do_force_loop
27 >  logical, save :: do_forces_initialized = .false.
28 >  logical, save :: FF_uses_LJ
29 >  logical, save :: FF_uses_sticky
30 >  logical, save :: FF_uses_dipoles
31 >  logical, save :: FF_uses_RF
32 >  logical, save :: FF_uses_GB
33 >  logical, save :: FF_uses_EAM
34  
32 contains
35  
36 < !! Does force loop over i,j pairs. Calls do_pair to calculates forces.
37 < !------------------------------------------------------------->
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
36 >  public :: init_FF
37 >  public :: do_forces
38  
39 <  !! 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
39 > contains
40  
41 < !! Stress Tensor
42 <    real( kind = dp), dimension(9) :: tau
41 >  subroutine init_FF(thisStat)
42 >  
43 >    integer, intent(out) :: my_status
44 >    integer :: thisStat = 0
45  
46 <    real ( kind = dp ) :: potE
55 <    logical ( kind = 2) :: do_pot
56 <    integer :: FFerror
46 >    ! be a smarter subroutine.
47  
48      
49 <    type(atype), pointer :: Atype_i
50 <    type(atype), pointer :: Atype_j
49 >    call init_lj_FF(my_status)
50 >    if (my_status /= 0) then
51 >       thisStat = -1
52 >       return
53 >    end if
54 >    
55 >    call check_sticky_FF(my_status)
56 >    if (my_status /= 0) then
57 >       thisStat = -1
58 >       return
59 >    end if
60 >    
61 >    do_forces_initialized = .true.    
62 >    
63 >  end subroutine init_FF
64  
65  
66  
67 <
68 <  
69 <
67 >  !! Does force loop over i,j pairs. Calls do_pair to calculates forces.
68 >  !------------------------------------------------------------->
69 >  subroutine do_force_loop(q, A, u_l, f, t, tau, pot, do_pot_c, do_stress_c, &
70 >       error)
71 >    !! Position array provided by C, dimensioned by getNlocal
72 >    real ( kind = dp ), dimension(3,getNlocal()) :: q
73 >    !! Rotation Matrix for each long range particle in simulation.
74 >    real( kind = dp), dimension(9,getNlocal()) :: A    
75 >    !! Unit vectors for dipoles (lab frame)
76 >    real( kind = dp ), dimension(3,getNlocal()) :: u_l
77 >    !! Force array provided by C, dimensioned by getNlocal
78 >    real ( kind = dp ), dimension(3,getNlocal()) :: f
79 >    !! Torsion array provided by C, dimensioned by getNlocal
80 >    real( kind = dp ), dimension(3,getNlocal()) :: t    
81 >    !! Stress Tensor
82 >    real( kind = dp), dimension(9) :: tau  
83 >    real ( kind = dp ) :: pot
84 >    logical ( kind = 2) :: do_pot_c, do_stress_c
85 >    logical :: do_pot
86 >    logical :: do_stress
87   #ifdef IS_MPI
88 <  real( kind = DP ) :: pot_local
89 <
90 < !! Local arrays needed for MPI
91 <
72 < #endif
73 <
74 <
75 <
76 <  real( kind = DP )   :: pe
77 <  logical             :: update_nlist
78 <
79 <
80 <  integer ::  i, j, jbeg, jend, jnab, idim, jdim, idim2, jdim2, dim, dim2
81 <  integer :: nlist
82 <  integer :: j_start
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 <  
90 <
91 < ! a rig that need to be fixed.
92 < #ifdef IS_MPI
93 <  real( kind = dp ) :: pe_local
94 <  integer :: nlocal
88 >    real( kind = DP ) :: pot_local
89 >    integer :: nlocal
90 >    integer :: nrow
91 >    integer :: ncol
92   #endif
93 <  integer :: nrow
94 <  integer :: ncol
95 <  integer :: natoms
96 <  integer :: neighborListSize
97 <  integer :: listerror
98 < !! should we calculate the stress tensor
99 <  logical  :: do_stress = .false.
93 >    integer :: natoms    
94 >    logical :: update_nlist  
95 >    integer :: i, j, jbeg, jend, jnab
96 >    integer :: nlist
97 >    real( kind = DP ) ::  rijsq, rlistsq, rcutsq, rlist, rcut
98 >    integer :: neighborListSize
99 >    integer :: listerror
100  
101 +    !! initialize local variables  
102  
105  FFerror = 0
106
107 ! Make sure we are properly initialized.
108  if (.not. isFFInit) then
109     write(default_error,*) "ERROR: lj_FF has not been properly initialized"
110     FFerror = -1
111     return
112  endif
103   #ifdef IS_MPI
104 <    if (.not. isMPISimSet()) then
105 <     write(default_error,*) "ERROR: mpiSimulation has not been properly initialized"
106 <     FFerror = -1
107 <     return
108 <  endif
104 >    nlocal = getNlocal()
105 >    nrow   = getNrow(plan_row)
106 >    ncol   = getNcol(plan_col)
107 > #else
108 >    nlocal = getNlocal()
109 >    natoms = nlocal
110   #endif
111  
112 < !! initialize local variables  
113 <  natoms = getNlocal()
114 <  call getRcut(rcut,rcut2=rcutsq)
115 <  call getRlist(rlist,rlistsq)
112 >    call getRcut(rcut,rcut2=rcutsq)
113 >    call getRlist(rlist,rlistsq)
114 >    
115 >    call check_initialization()
116 >    call zero_work_arrays()
117  
118 < !! Find ensemble
119 <  if (isEnsemble("NPT")) do_stress = .true.
128 < !! set to wrap
129 <  if (isPBC()) wrap = .true.
118 >    do_pot = do_pot_c
119 >    do_stress = do_stress_c
120  
121 <
122 <
133 <  
134 < !! See if we need to update neighbor lists
135 <  call check(q,update_nlist)
136 <
137 < !--------------WARNING...........................
138 < ! Zero variables, NOTE:::: Forces are zeroed in C
139 < ! Zeroing them here could delete previously computed
140 < ! Forces.
141 < !------------------------------------------------
142 <  call zero_module_variables()
143 <
144 <
145 < ! communicate MPI positions
121 >    ! Gather all information needed by all force loops:
122 >    
123   #ifdef IS_MPI    
124 +
125      call gather(q,q_Row,plan_row3d)
126      call gather(q,q_Col,plan_col3d)
127 <
128 <    call gather(u_l,u_l_Row,plan_row3d)
129 <    call gather(u_l,u_l_Col,plan_col3d)
130 <
131 <    call gather(A,A_Row,plan_row_rotation)
132 <    call gather(A,A_Col,plan_col_rotation)
127 >        
128 >    if (FF_UsesDirectionalAtoms() .and. SimUsesDirectionalAtoms()) then
129 >       call gather(u_l,u_l_Row,plan_row3d)
130 >       call gather(u_l,u_l_Col,plan_col3d)
131 >      
132 >       call gather(A,A_Row,plan_row_rotation)
133 >       call gather(A,A_Col,plan_col_rotation)
134 >    endif
135 >    
136   #endif
137 <
138 <
137 >    
138 >    if (FF_RequiresPrepairCalc() .and. SimRequiresPrepairCalc()) then
139 >       !! See if we need to update neighbor lists
140 >       call checkNeighborList(nlocal, q, rcut, rlist, update_nlist)  
141 >       !! if_mpi_gather_stuff_for_prepair
142 >       !! do_prepair_loop_if_needed
143 >       !! if_mpi_scatter_stuff_from_prepair
144 >       !! if_mpi_gather_stuff_from_prepair_to_main_loop
145 >    else
146 >       !! See if we need to update neighbor lists
147 >       call checkNeighborList(nlocal, q, rcut, rlist, update_nlist)  
148 >    endif
149 >    
150   #ifdef IS_MPI
151      
152      if (update_nlist) then
153        
154 <       ! save current configuration, contruct neighbor list,
155 <       ! and calculate forces
154 >       !! save current configuration, construct neighbor list,
155 >       !! and calculate forces
156         call save_neighborList(q)
157        
158         neighborListSize = getNeighborListSize()
159 <       nlist = 0
159 >       nlist = 0      
160        
169       nrow = getNrow(plan_row)
170       ncol = getNcol(plan_col)
171       nlocal = getNlocal()
172      
161         do i = 1, nrow
162            point(i) = nlist + 1
175          Atype_i => identPtrListRow(i)%this
163            
164            inner: do j = 1, ncol
178             Atype_j => identPtrListColumn(j)%this
165              
166 <             call get_interatomic_vector(i,j,q_Row(:,i),q_Col(:,j),&
181 <                  rxij,ryij,rzij,rijsq,r)
166 >             if (check_exclude(i,j)) cycle inner:
167              
168 <             ! skip the loop if the atoms are identical
169 <             if (mpi_cycle_jLoop(i,j)) cycle inner:
185 <            
168 >             call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
169 >            
170               if (rijsq <  rlistsq) then            
171                  
172                  nlist = nlist + 1
173                  
174                  if (nlist > neighborListSize) then
175 <                   call expandList(listerror)
175 >                   call expandNeighborList(nlocal, listerror)
176                     if (listerror /= 0) then
177 <                      FFerror = -1
177 >                      error = -1
178                        write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
179                        return
180                     end if
181                  endif
182                  
183                  list(nlist) = j
184 <                
201 <                
184 >                                
185                  if (rijsq <  rcutsq) then
186 <                   call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
186 >                   call do_pair(i, j, rijsq, d, do_pot, do_stress)
187                  endif
188               endif
189            enddo inner
# Line 208 | Line 191 | contains
191  
192         point(nrow + 1) = nlist + 1
193        
194 <    else !! (update)
194 >    else  !! (of update_check)
195  
196         ! use the list to find the neighbors
197         do i = 1, nrow
# Line 216 | Line 199 | contains
199            JEND = POINT(i+1) - 1
200            ! check thiat molecule i has neighbors
201            if (jbeg .le. jend) then
202 <
220 <             Atype_i => identPtrListRow(i)%this
202 >            
203               do jnab = jbeg, jend
204                  j = list(jnab)
205 <                Atype_j = identPtrListColumn(j)%this
206 <                call get_interatomic_vector(i,j,q_Row(:,i),q_Col(:,j),&
207 <                     rxij,ryij,rzij,rijsq,r)
208 <                
227 <                call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
205 >
206 >                call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
207 >                call do_pair(i, j, rijsq, d, do_pot, do_stress)
208 >
209               enddo
210            endif
211         enddo
212      endif
213 <
213 >    
214   #else
215      
216      if (update_nlist) then
# Line 241 | Line 222 | contains
222         neighborListSize = getNeighborListSize()
223         nlist = 0
224        
244    
225         do i = 1, natoms-1
226            point(i) = nlist + 1
227 <          Atype_i   => identPtrList(i)%this
248 <
227 >          
228            inner: do j = i+1, natoms
229 <             Atype_j   => identPtrList(j)%this
230 <             call get_interatomic_vector(i,j,q(:,i),q(:,j),&
231 <                  rxij,ryij,rzij,rijsq,r)
229 >            
230 >             if (check_exclude(i,j)) cycle inner:
231 >            
232 >             call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
233            
234               if (rijsq <  rlistsq) then
235 <
235 >                
236                  nlist = nlist + 1
237                  
238                  if (nlist > neighborListSize) then
239 <                   call expandList(listerror)
239 >                   call expandList(natoms, listerror)
240                     if (listerror /= 0) then
241 <                      FFerror = -1
241 >                      error = -1
242                        write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
243                        return
244                     end if
245                  endif
246                  
247                  list(nlist) = j
248 <
269 <    
248 >                
249                  if (rijsq <  rcutsq) then
250 <                   call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
250 >                   call do_pair(i, j, rijsq, d, do_pot, do_stress)
251                  endif
252               endif
253            enddo inner
# Line 285 | Line 264 | contains
264            ! check thiat molecule i has neighbors
265            if (jbeg .le. jend) then
266              
288             Atype_i => identPtrList(i)%this
267               do jnab = jbeg, jend
268                  j = list(jnab)
269 <                Atype_j = identPtrList(j)%this
270 <                call get_interatomic_vector(i,j,q(:,i),q(:,j),&
271 <                     rxij,ryij,rzij,rijsq,r)
272 <                call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
269 >
270 >                call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
271 >                call do_pair(i, j, rijsq, d, do_pot, do_stress)
272 >
273               enddo
274            endif
275         enddo
276      endif
277 <
277 >    
278   #endif
279 <
280 <
279 >    
280 >    ! phew, done with main loop.
281 >    
282   #ifdef IS_MPI
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
312 ! This is the post-pair loop:
313 #ifdef IS_MPI
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
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
332
333
334 #ifdef IS_MPI
283      !!distribute forces
284 <
284 >    
285      call scatter(f_Row,f,plan_row3d)
286      call scatter(f_Col,f_temp,plan_col3d)
287      do i = 1,nlocal
288         f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
289      end do
290 <
291 <    if (doTorque()) then
290 >    
291 >    if (FF_UsesDirectionalAtoms() .and. SimUsesDirectionalAtoms()) then
292         call scatter(t_Row,t,plan_row3d)
293         call scatter(t_Col,t_temp,plan_col3d)
294 <    
294 >      
295         do i = 1,nlocal
296            t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
297         end do
# Line 366 | Line 314 | contains
314            pot_local = pot_local + pot_Temp(i)
315         enddo
316        
317 +    endif
318 +    
319 +    if (FF_RequiresPostpairCalc() .and. SimRequiresPostpairCalc()) then
320 +      
321 +       if (FF_uses_RF .and. SimUsesRF()) then
322 +          
323 + #ifdef IS_MPI
324 +          call scatter(rf_Row,rf,plan_row3d)
325 +          call scatter(rf_Col,rf_Temp,plan_col3d)
326 +          do i = 1,nlocal
327 +             rf(1:3,i) = rf(1:3,i) + rf_Temp(1:3,i)
328 +          end do
329 + #endif
330 +          
331 +          do i = 1, getNlocal()
332 +
333 + #ifdef IS_MPI
334 +             me_i = atid_row(i)
335 + #else
336 +             me_i = atid(i)
337 + #endif
338 +             call getElementProperty(atypes, me_i, "is_DP", is_DP_i)      
339 +             if ( is_DP_i ) then
340 +                call getElementProperty(atypes, me_i, "dipole_moment", mu_i)
341 +                !! The reaction field needs to include a self contribution
342 +                !! to the field:
343 +                call accumulate_self_rf(i, mu_i, u_l)            
344 +                !! Get the reaction field contribution to the
345 +                !! potential and torques:
346 +                call reaction_field(i, mu_i, u_l, rfpot, t, do_pot)
347 + #ifdef IS_MPI
348 +                pot_local = pot_local + rfpot
349 + #else
350 +                pot = pot + rfpot
351 + #endif
352 +             endif            
353 +          enddo
354 +       endif
355 +    endif
356 +
357 +
358 + #ifdef IS_MPI
359 +
360 +    if (do_pot) then
361         pot = pot_local
362 +       !! we assume the c code will do the allreduce to get the total potential
363 +       !! we could do it right here if we needed to...
364      endif
365  
366 <    if (doStress()) then
366 >    if (do_stress) then
367         mpi_allreduce(tau, tau_Temp,9,mpi_double_precision,mpi_sum, &
368              mpi_comm_world,mpi_err)
369         mpi_allreduce(virial, virial_Temp,1,mpi_double_precision,mpi_sum, &
370              mpi_comm_world,mpi_err)
371      endif
372  
373 < #endif
373 > #else
374  
375 <    if (doStress()) then
375 >    if (do_stress) then
376         tau = tau_Temp
377         virial = virial_Temp
378      endif
379  
380 + #endif
381 +    
382    end subroutine do_force_loop
383  
384  
# Line 394 | Line 390 | contains
390  
391    end subroutine do_preForce
392  
397
398
399
400
401
402
403
404
405
406
407
408
393   !! Calculate any post force loop components, i.e. reaction field, etc.
394    subroutine do_postForce()
395  
# Line 413 | Line 397 | contains
397  
398    end subroutine do_postForce
399  
400 +  subroutine do_pair(i, j, rijsq, d, do_pot, do_stress)
401  
402 +    logical, intent(inout) :: do_pot, do_stress
403 +    integer, intent(in) :: i, j
404 +    real ( kind = dp ), intent(in)    :: rijsq
405 +    real ( kind = dp )                :: r
406 +    real ( kind = dp ), intent(inout) :: d(3)
407  
408 <
419 <
420 <
421 <
422 <
423 <
424 <
425 <
426 <
427 <
428 <
429 <
430 <
431 <
432 <  subroutine do_pair(atype_i,atype_j,i,j,r_ij,rx_ij,ry_ij,rz_ij)
433 <    type (atype ), pointer, intent(inout) :: atype_i
434 <    type (atype ), pointer, intent(inout) :: atype_j
435 <    integer :: i
436 <    integer :: j
437 <    real ( kind = dp ), intent(inout) :: rx_ij
438 <    real ( kind = dp ), intent(inout) :: ry_ij
439 <    real ( kind = dp ), intent(inout) :: rz_ij
440 <
441 <
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 <  
446 <    real( kind = dp ) ::  drdx = 0.0_dp
447 <    real( kind = dp ) ::  drdy = 0.0_dp
448 <    real( kind = dp ) ::  drdz = 0.0_dp
408 >    r = sqrt(rijsq)
409      
410 +    logical :: is_LJ_i, is_LJ_j
411 +    logical :: is_DP_i, is_DP_j
412 +    logical :: is_Sticky_i, is_Sticky_j
413 +    integer :: me_i, me_j
414  
415   #ifdef IS_MPI
416  
417 <    if (Atype_i%is_LJ .and. Atype_j%is_LJ) then
418 <       call do_lj_pair(i, j, atype_i, atype_j, rx_ij, ry_ij, rz_ij, r_ij, &
455 <            pot, f)
456 <    endif
417 >    me_i = atid_row(i)
418 >    me_j = atid_col(j)
419  
420 <    if (Atype_i%is_dp .and. Atype_j%is_dp) then
420 > #else
421  
422 <       call do_dipole_pair(i, j, atype_i, atype_j, rx_ij, ry_ij, rz_ij, r_ij, &
423 <            rt, rrf, pot, u_l, f, t)
422 >    me_i = atid(i)
423 >    me_j = atid(j)
424  
425 <       if (do_reaction_field) then
464 <          call accumulate_rf(i, j, r_ij, rt, rrf)
465 <       endif
425 > #endif
426  
467    endif
427  
428 <    if (Atype_i%is_sticky .and. Atype_j%is_sticky) then
429 <       call getstickyforce(r, pot, dudr, Atype_i, Atype_j)
428 >    if (FF_uses_LJ .and. SimUsesLJ()) then
429 >       call getElementProperty(atypes, me_i, "is_LJ", is_LJ_i)
430 >       call getElementProperty(atypes, me_j, "is_LJ", is_LJ_j)
431 >      
432 >       if ( is_LJ_i .and. is_LJ_j ) &
433 >            call do_lj_pair(i, j, d, r, rijsq, pot, f, do_pot, do_stress)
434      endif
435 +      
436  
437 < #else
438 <
439 <    if (Atype_i%is_LJ .and. Atype_j%is_LJ) then
440 <       call do_lj_pair(i, j, atype_i, atype_j, rx_ij, ry_ij, rz_ij, r_ij, &
441 <            pot, f)
437 >    if (FF_uses_DP .and. SimUsesDP()) then
438 >       call getElementProperty(atypes, me_i, "is_DP", is_DP_i)
439 >       call getElementProperty(atypes, me_j, "is_DP", is_DP_j)
440 >      
441 >       if ( is_DP_i .and. is_DP_j ) then
442 >          
443 >          call do_dipole_pair(i, j, d, r, pot, u_l, f, t, do_pot, do_stress)
444 >          
445 >          if (FF_uses_RF .and. SimUsesRF()) then
446 >            
447 >             call accumulate_rf(i, j, r, u_l)
448 >             call rf_correct_forces(i, j, d, r, u_l, f, do_stress)
449 >            
450 >          endif
451 >          
452 >       endif
453      endif
454  
455 <    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 <            rt, rrf, pot, u_l, f, t)
455 >    if (FF_uses_Sticky .and. SimUsesSticky()) then
456  
457 <       if (do_reaction_field) then
458 <          call accumulate_rf(i, j, r_ij, rt, rrf)
457 >       call getElementProperty(atypes, me_i, "is_Sticky", is_Sticky_i)
458 >       call getElementProperty(atypes, me_j, "is_Sticky", is_Sticky_j)
459 >      
460 >       if ( is_Sticky_i .and. is_Sticky_j ) then
461 >          call do_sticky_pair(i, j, d, r, rijsq, A, pot, f, t, &
462 >               do_pot, do_stress)
463         endif
487
464      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
494 #endif
495
465        
466    end subroutine do_pair
498
499
500
467  
468  
469 <
470 <
505 <
506 <
507 <
508 <
509 <
510 <
511 <
512 <
513 <
514 <  subroutine get_interatomic_vector(q_i,q_j,rx_ij,ry_ij,rz_ij,r_sq,r_ij)
515 < !---------------- Arguments-------------------------------
516 <   !! index i
517 <
518 <    !! Position array
469 >  subroutine get_interatomic_vector(q_i, q_j, d, r_sq)
470 >    
471      real (kind = dp), dimension(3) :: q_i
472      real (kind = dp), dimension(3) :: q_j
521    !! x component of vector between i and j
522    real ( kind = dp ), intent(out)  :: rx_ij
523    !! y component of vector between i and j
524    real ( kind = dp ), intent(out)  :: ry_ij
525    !! z component of vector between i and j
526    real ( kind = dp ), intent(out)  :: rz_ij
527    !! magnitude of r squared
473      real ( kind = dp ), intent(out) :: r_sq
529    !! magnitude of vector r between atoms i and j.
530    real ( kind = dp ), intent(out) :: r_ij
531    !! wrap into periodic box.
532    logical, intent(in) :: wrap
533
534 !--------------- Local Variables---------------------------
535    !! Distance between i and j
474      real( kind = dp ) :: d(3)
537 !---------------- END DECLARATIONS-------------------------
475  
539
540 ! Find distance between i and j
476      d(1:3) = q_i(1:3) - q_j(1:3)
477 <
478 < ! Wrap back into periodic box if necessary
479 <    if ( wrap ) then
477 >    
478 >    ! Wrap back into periodic box if necessary
479 >    if ( isPBC() ) then
480         d(1:3) = d(1:3) - thisSim%box(1:3) * sign(1.0_dp,thisSim%box(1:3)) * &
481              int(abs(d(1:3)/thisSim%box(1:3) + 0.5_dp)
482 <    end if
482 >    endif
483      
549 !   Find Magnitude of the vector
484      r_sq = dot_product(d,d)
485 <    r_ij = sqrt(r_sq)
485 >        
486 >  end subroutine get_interatomic_vector
487  
488 < !   Set each component for force calculation
489 <    rx_ij = d(1)
555 <    ry_ij = d(2)
556 <    rz_ij = d(3)
488 >  subroutine check_initialization(error)
489 >    integer, intent(out) :: error
490  
491 +    error = 0
492 +    ! Make sure we are properly initialized.
493 +    if (.not. do_Forces_initialized) then
494 +       write(default_error,*) "ERROR: do_Forces has not been initialized!"
495 +       error = -1
496 +       return
497 +    endif
498 + #ifdef IS_MPI
499 +    if (.not. isMPISimSet()) then
500 +       write(default_error,*) "ERROR: mpiSimulation has not been initialized!"
501 +       error = -1
502 +       return
503 +    endif
504 + #endif
505  
506 <  end subroutine get_interatomic_vector
506 >    return
507 >  end subroutine check_initialization
508  
509 <  subroutine zero_module_variables()
509 >  
510 >  subroutine zero_work_arrays()
511 >    
512 > #ifdef IS_MPI
513  
514 < #ifndef IS_MPI
515 <
565 <    pe = 0.0E0_DP
566 <    tauTemp = 0.0_dp
567 <    fTemp = 0.0_dp
568 <    tTemp = 0.0_dp
569 < #else
570 <    qRow = 0.0_dp
571 <    qCol = 0.0_dp
514 >    q_Row = 0.0_dp
515 >    q_Col = 0.0_dp  
516      
517 <    muRow = 0.0_dp
518 <    muCol = 0.0_dp
517 >    u_l_Row = 0.0_dp
518 >    u_l_Col = 0.0_dp
519      
520 <    u_lRow = 0.0_dp
521 <    u_lCol = 0.0_dp
520 >    A_Row = 0.0_dp
521 >    A_Col = 0.0_dp
522      
523 <    ARow = 0.0_dp
524 <    ACol = 0.0_dp
525 <    
526 <    fRow = 0.0_dp
527 <    fCol = 0.0_dp
528 <    
529 <  
586 <    tRow = 0.0_dp
587 <    tCol = 0.0_dp
523 >    f_Row = 0.0_dp
524 >    f_Col = 0.0_dp
525 >    f_Temp = 0.0_dp
526 >      
527 >    t_Row = 0.0_dp
528 >    t_Col = 0.0_dp
529 >    t_Temp = 0.0_dp
530  
531 <  
531 >    pot_Row = 0.0_dp
532 >    pot_Col = 0.0_dp
533 >    pot_Temp = 0.0_dp
534  
591    eRow = 0.0_dp
592    eCol = 0.0_dp
593    eTemp = 0.0_dp
535   #endif
536  
537 <  end subroutine zero_module_variables
537 >    tau_Temp = 0.0_dp
538 >    virial_Temp = 0.0_dp
539 >    
540 >  end subroutine zero_work_arrays
541 >  
542  
598
543   !! Function to properly build neighbor lists in MPI using newtons 3rd law.
544   !! We don't want 2 processors doing the same i j pair twice.
545   !! Also checks to see if i and j are the same particle.
# Line 660 | Line 604 | contains
604  
605    end function checkExcludes
606  
607 <
607 >  function FF_UsesDirectionalAtoms() result(doesit)
608 >    logical :: doesit
609 >    doesit = FF_uses_dipoles .or. FF_uses_sticky .or. &
610 >         FF_uses_GB .or. FF_uses_RF
611 >  end function FF_UsesDirectionalAtoms
612 >  
613 >  function FF_RequiresPrepairCalc() result(doesit)
614 >    logical :: doesit
615 >    doesit = FF_uses_EAM
616 >  end function FF_RequiresPrepairCalc
617 >  
618 >  function FF_RequiresPostpairCalc() result(doesit)
619 >    logical :: doesit
620 >    doesit = FF_uses_RF
621 >  end function FF_RequiresPostpairCalc
622 >  
623   end module do_Forces

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines