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 297 by gezelter, Thu Mar 6 22:08:29 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.4 2003-03-06 22:08:29 gezelter Exp $, $Date: 2003-03-06 22:08:29 $, $Name: not supported by cvs2svn $, $Revision: 1.4 $
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  
28 !! Global list of lj atypes in simulation
29  type (atype), pointer :: ListHead => null()
30  type (atype), pointer :: ListTail => null()
31
32
33
34
35  logical, save :: firstTime = .True.
36
37 !! Atype identity pointer lists
38 #ifdef IS_MPI
39 !! Row lj_atype pointer list
40  type (identPtrList), dimension(:), pointer :: identPtrListRow => null()
41 !! Column lj_atype pointer list
42  type (identPtrList), dimension(:), pointer :: identPtrListColumn => null()
43 #else
44  type(identPtrList ), dimension(:), pointer :: identPtrList => null()
45 #endif
46
47
48 !! Logical has lj force field module been initialized?
49  logical, save :: isFFinit = .false.
50
51 !! Use periodic boundry conditions
52  logical :: wrap = .false.
53
54 !! Potential energy global module variables
55 #ifdef IS_MPI
56  real(kind = dp), dimension(3,getNrow(plan_row)) :: qRow = 0.0_dp
57  real(kind = dp), dimension(3,getNcol(plan_col)) :: qCol = 0.0_dp
58
59  real(kind = dp), dimension(3,getNrow(plan_row)) :: muRow = 0.0_dp
60  real(kind = dp), dimension(3,getNcol(plan_col)) :: muCol = 0.0_dp
61
62  real(kind = dp), dimension(3,getNrow(plan_row)) :: u_lRow = 0.0_dp
63  real(kind = dp), dimension(3,getNcol(plan_col)) :: u_lCol = 0.0_dp
64
65  real(kind = dp), dimension(9,getNrow(plan_row)) :: ARow = 0.0_dp
66  real(kind = dp), dimension(9,getNcol(plan_col)) :: ACol = 0.0_dp  
67
68  real(kind = dp), dimension(3,getNrow(plan_row)) :: fRow = 0.0_dp
69  real(kind = dp), dimension(3,getNcol(plan_col)) :: fCol = 0.0_dp
70  real(kind = dp), dimension(3,getNlocal()) :: fTemp1 = 0.0_dp
71  real(kind = dp), dimension(3,getNlocal()) :: tTemp1 = 0.0_dp
72  real(kind = dp), dimension(3,getNlocal()) :: fTemp2 = 0.0_dp
73  real(kind = dp), dimension(3,getNlocal()) :: tTemp2 = 0.0_dp
74  real(kind = dp), dimension(3,getNlocal()) :: fTemp = 0.0_dp
75  real(kind = dp), dimension(3,getNlocal()) :: tTemp = 0.0_dp
76
77  real(kind = dp), dimension(3,getNrow(plan_row)) :: tRow = 0.0_dp
78  real(kind = dp), dimension(3,getNcol(plan_col)) :: tCol = 0.0_dp
79
80  real(kind = dp), dimension(3,getNrow(plan_row)) :: rflRow = 0.0_dp
81  real(kind = dp), dimension(3,getNcol(plan_col)) :: rflCol = 0.0_dp
82  real(kind = dp), dimension(3,getNlocal()) :: rflTemp = 0.0_dp
83
84  real(kind = dp), dimension(getNrow(plan_row)) :: eRow = 0.0_dp
85  real(kind = dp), dimension(getNcol(plan_col)) :: eCol = 0.0_dp
86
87  real(kind = dp), dimension(getNlocal()) :: eTemp = 0.0_dp
88 #endif
89  real(kind = dp) :: pe = 0.0_dp
90  real(kind = dp), dimension(3,natoms) :: fTemp = 0.0_dp
91  real(kind = dp), dimension(3,natoms) :: tTemp = 0.0_dp
92  real(kind = dp), dimension(3,natoms) :: rflTemp = 0.0_dp
93  real(kind = dp), dimension(9) :: tauTemp = 0.0_dp
94
95  logical :: do_preForce  = .false.
96  logical :: do_postForce = .false.
97
98
99
100 !! Public methods and data
101  public :: new_atype
102  public :: do_forceLoop
103  public :: init_FF
104
105  
106
107
32   contains
33  
34 < !! Adds a new lj_atype to the list.
35 <  subroutine new_atype(ident,mass,epsilon,sigma, &
36 <       is_LJ,is_Sticky,is_DP,is_GB,w0,v0,dipoleMoment,status)
37 <    real( kind = dp ), intent(in) :: mass
38 <    real( kind = dp ), intent(in) :: epsilon
39 <    real( kind = dp ), intent(in) :: sigma
40 <    real( kind = dp ), intent(in) :: w0
117 <    real( kind = dp ), intent(in) :: v0
118 <    real( kind = dp ), intent(in) :: dipoleMoment
119 <
120 <    integer, intent(in) :: ident
121 <    integer, intent(out) :: status
122 <    integer, intent(in) :: is_Sticky
123 <    integer, intent(in) :: is_DP
124 <    integer, intent(in) :: is_GB
125 <    integer, intent(in) :: is_LJ
126 <
127 <
128 <    type (atype), pointer :: the_new_atype
129 <    integer :: alloc_error
130 <    integer :: atype_counter = 0
131 <    integer :: alloc_size
132 <    integer :: err_stat
133 <    status = 0
134 <
135 <
136 <
137 < ! allocate a new atype    
138 <    allocate(the_new_atype,stat=alloc_error)
139 <    if (alloc_error /= 0 ) then
140 <       status = -1
141 <       return
142 <    end if
143 <
144 < ! assign our new atype information
145 <    the_new_atype%mass        = mass
146 <    the_new_atype%epsilon     = epsilon
147 <    the_new_atype%sigma       = sigma
148 <    the_new_atype%sigma2      = sigma * sigma
149 <    the_new_atype%sigma6      = the_new_atype%sigma2 * the_new_atype%sigma2 &
150 <         * the_new_atype%sigma2
151 <    the_new_atype%w0       = w0
152 <    the_new_atype%v0       = v0
153 <    the_new_atype%dipoleMoment       = dipoleMoment
154 <
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 < ! assume that this atype will be successfully added
43 <    the_new_atype%atype_ident = ident
44 <    the_new_atype%atype_number = n_lj_atypes + 1
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 <    if ( is_Sticky /= 0 )    the_new_atype%is_Sticky   = .true.
52 <    if ( is_GB /= 0 )        the_new_atype%is_GB       = .true.
53 <    if ( is_LJ /= 0 )        the_new_atype%is_LJ       = .true.
54 <    if ( is_DP /= 0 )        the_new_atype%is_DP       = .true.
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  
165    call add_atype(the_new_atype,ListHead,ListTail,err_stat)
166    if (err_stat /= 0 ) then
167       status = -1
168       return
169    endif
170
171    n_atypes = n_atypes + 1
172
173
174  end subroutine new_atype
175
176
177  subroutine init_FF(nComponents,ident, status)
178 !! Number of components in ident array
179    integer, intent(inout) :: nComponents
180 !! Array of identities nComponents long corresponding to
181 !! ljatype ident.
182    integer, dimension(nComponents),intent(inout) :: ident
183 !!  Result status, success = 0, error = -1
184    integer, intent(out) :: Status
185
186    integer :: alloc_stat
187
188    integer :: thisStat
189    integer :: i
190
191    integer :: myNode
58   #ifdef IS_MPI
59 <    integer, allocatable, dimension(:) :: identRow
194 <    integer, allocatable, dimension(:) :: identCol
195 <    integer :: nrow
196 <    integer :: ncol
59 >    real( kind = DP ) :: pot_local
60   #endif
198    status = 0
199  
200
61      
62 +    real( kind = DP )   :: pe
63 +    logical             :: update_nlist
64 +    
65  
66 < !! if were're not in MPI, we just update ljatypePtrList
67 < #ifndef IS_MPI
68 <    call create_IdentPtrlst(ident,ListHead,identPtrList,thisStat)
206 <    if ( thisStat /= 0 ) then
207 <       status = -1
208 <       return
209 <    endif
210 <
66 >    integer ::  i, j, jbeg, jend, jnab, idim, jdim, idim2, jdim2, dim, dim2
67 >    integer :: nlist
68 >    integer :: j_start
69      
70 < ! if were're in MPI, we also have to worry about row and col lists    
71 < #else
72 <  
73 < ! We can only set up forces if mpiSimulation has been setup.
216 <    if (.not. isMPISimSet()) then
217 <       write(default_error,*) "MPI is not set"
218 <       status = -1
219 <       return
220 <    endif
221 <    nrow = getNrow(plan_row)
222 <    ncol = getNcol(plan_col)
223 <    mynode = getMyNode()
224 < !! Allocate temperary arrays to hold gather information
225 <    allocate(identRow(nrow),stat=alloc_stat)
226 <    if (alloc_stat /= 0 ) then
227 <       status = -1
228 <       return
229 <    endif
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 <    allocate(identCol(ncol),stat=alloc_stat)
76 <    if (alloc_stat /= 0 ) then
77 <       status = -1
78 <       return
79 <    endif
75 >    ! a rig that need to be fixed.
76 > #ifdef IS_MPI
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 < !! Gather idents into row and column idents
90 <
91 <    call gather(ident,identRow,plan_row)
92 <    call gather(ident,identCol,plan_col)
241 <    
242 <  
243 < !! Create row and col pointer lists
244 <  
245 <    call create_IdentPtrlst(identRow,ListHead,identPtrListRow,thisStat)
246 <    if (thisStat /= 0 ) then
247 <       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      endif
95 <  
96 <    call create_IdentPtrlst(identCol,ListHead,identPtrListColumn,thisStat)
97 <    if (thisStat /= 0 ) then
98 <       status = -1
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
256
257 !! free temporary ident arrays
258    if (allocated(identCol)) then
259       deallocate(identCol)
260    end if
261    if (allocated(identCol)) then
262       deallocate(identRow)
263    endif
264
101   #endif
102      
103 <    call initForce_Modules(thisStat)
104 <    if (thisStat /= 0) then
105 <       status = -1
106 <       return
271 <    endif
272 <
273 < !! Create neighbor lists
274 <    call expandList(thisStat)
275 <    if (thisStat /= 0) then
276 <       status = -1
277 <       return
278 <    endif
279 <
280 <    isFFinit = .true.
281 <
282 <
283 <  end subroutine init_FF
284 <
285 <
286 <
287 <
288 <  subroutine initForce_Modules(thisStat)
289 <    integer, intent(out) :: thisStat
290 <    integer :: my_status
103 >    !! initialize local variables  
104 >    natoms = getNlocal()
105 >    call getRcut(rcut,rcut2=rcutsq)
106 >    call getRlist(rlist,rlistsq)
107      
108 <    thisStat = 0
109 <    call init_lj_FF(ListHead,my_status)
294 <    if (my_status /= 0) then
295 <       thisStat = -1
296 <       return
297 <    end if
298 <
299 <  end subroutine initForce_Modules
300 <
301 <
302 <
303 <
304 < !! FORCE routine Calculates Lennard Jones forces.
305 < !------------------------------------------------------------->
306 <  subroutine do_force_loop(q,A,mu,u_l,f,t,tau,potE,do_pot,FFerror)
307 < !! Position array provided by C, dimensioned by getNlocal
308 <    real ( kind = dp ), dimension(3,getNlocal()) :: q
309 <  !! Rotation Matrix for each long range particle in simulation.
310 <    real( kind = dp), dimension(9,getNlocal()) :: A
311 <
312 <  !! Magnitude dipole moment
313 <    real( kind = dp ), dimension(3,getNlocal()) :: mu
314 <  !! Unit vectors for dipoles (lab frame)
315 <    real( kind = dp ), dimension(3,getNlocal()) :: u_l
316 < !! Force array provided by C, dimensioned by getNlocal
317 <    real ( kind = dp ), dimension(3,getNlocal()) :: f
318 < !! Torsion array provided by C, dimensioned by getNlocal
319 <    real( kind = dp ), dimension(3,getNlocal()) :: t
320 <
321 < !! Stress Tensor
322 <    real( kind = dp), dimension(9) :: tau
323 <
324 <    real ( kind = dp ) :: potE
325 <    logical ( kind = 2) :: do_pot
326 <    integer :: FFerror
327 <
108 >    !! See if we need to update neighbor lists
109 >    call check(q, update_nlist)
110      
111 <    type(atype), pointer :: Atype_i
112 <    type(atype), pointer :: Atype_j
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 <
333 <
334 <
335 <  
336 <
337 < #ifdef IS_MPI
338 <  real( kind = DP ) :: pot_local
339 <
340 < !! Local arrays needed for MPI
341 <
342 < #endif
343 <
344 <
345 <
346 <  real( kind = DP )   :: pe
347 <  logical             :: update_nlist
348 <
349 <
350 <  integer ::  i, j, jbeg, jend, jnab, idim, jdim, idim2, jdim2, dim, dim2
351 <  integer :: nlist
352 <  integer :: j_start
353 <
354 <  real( kind = DP ) ::  r_ij, pot, ftmp, dudr, d2, drdx1, kt1, kt2, kt3, ktmp
355 <
356 <  real( kind = DP ) ::  rx_ij, ry_ij, rz_ij, rijsq
357 <  real( kind = DP ) ::  rlistsq, rcutsq,rlist,rcut
358 <
359 <  real( kind = DP ) :: dielectric = 0.0_dp
360 <
361 < ! a rig that need to be fixed.
362 < #ifdef IS_MPI
363 <  real( kind = dp ) :: pe_local
364 <  integer :: nlocal
365 < #endif
366 <  integer :: nrow
367 <  integer :: ncol
368 <  integer :: natoms
369 <  integer :: neighborListSize
370 <  integer :: listerror
371 < !! should we calculate the stress tensor
372 <  logical  :: do_stress = .false.
373 <
374 <
375 <  FFerror = 0
376 <
377 < ! Make sure we are properly initialized.
378 <  if (.not. isFFInit) then
379 <     write(default_error,*) "ERROR: lj_FF has not been properly initialized"
380 <     FFerror = -1
381 <     return
382 <  endif
383 < #ifdef IS_MPI
384 <    if (.not. isMPISimSet()) then
385 <     write(default_error,*) "ERROR: mpiSimulation has not been properly initialized"
386 <     FFerror = -1
387 <     return
388 <  endif
389 < #endif
390 <
391 < !! initialize local variables  
392 <  natoms = getNlocal()
393 <  call getRcut(rcut,rcut2=rcutsq)
394 <  call getRlist(rlist,rlistsq)
395 <
396 < !! Find ensemble
397 <  if (isEnsemble("NPT")) do_stress = .true.
398 < !! set to wrap
399 <  if (isPBC()) wrap = .true.
400 <
401 <
402 <
403 <  
404 < !! See if we need to update neighbor lists
405 <  call check(q,update_nlist)
406 <
407 < !--------------WARNING...........................
408 < ! Zero variables, NOTE:::: Forces are zeroed in C
409 < ! Zeroing them here could delete previously computed
410 < ! Forces.
411 < !------------------------------------------------
412 <  call zero_module_variables()
413 <
414 <
415 < ! communicate MPI positions
118 >    ! communicate MPI positions
119   #ifdef IS_MPI    
120 <    call gather(q,qRow,plan_row3d)
121 <    call gather(q,qCol,plan_col3d)
122 <
123 <    call gather(mu,muRow,plan_row3d)
124 <    call gather(mu,muCol,plan_col3d)
125 <
126 <    call gather(u_l,u_lRow,plan_row3d)
127 <    call gather(u_l,u_lCol,plan_col3d)
425 <
426 <    call gather(A,ARow,plan_row_rotation)
427 <    call gather(A,ACol,plan_col_rotation)
120 >    call gather(q,q_Row,plan_row3d)
121 >    call gather(q,q_Col,plan_col3d)
122 >    
123 >    call gather(u_l,u_l_Row,plan_row3d)
124 >    call gather(u_l,u_l_Col,plan_col3d)
125 >    
126 >    call gather(A,A_Row,plan_row_rotation)
127 >    call gather(A,A_Col,plan_col_rotation)
128   #endif
129  
130  
# Line 445 | Line 145 | contains
145        
146         do i = 1, nrow
147            point(i) = nlist + 1
448          Atype_i => identPtrListRow(i)%this
148            
149            inner: do j = 1, ncol
451             Atype_j => identPtrListColumn(j)%this
150              
151 <             call get_interatomic_vector(i,j,qRow(:,i),qCol(:,j),&
152 <                  rxij,ryij,rzij,rijsq,r)
153 <            
154 <             ! skip the loop if the atoms are identical
457 <             if (mpi_cycle_jLoop(i,j)) cycle inner:
458 <            
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
# Line 470 | Line 166 | contains
166                  endif
167                  
168                  list(nlist) = j
169 <                
474 <                
169 >                                
170                  if (rijsq <  rcutsq) then
171 <                   call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
171 >                   call do_pair(i, j, rijsq, d)
172                  endif
173               endif
174            enddo inner
# Line 489 | Line 184 | contains
184            JEND = POINT(i+1) - 1
185            ! check thiat molecule i has neighbors
186            if (jbeg .le. jend) then
187 <
493 <             Atype_i => identPtrListRow(i)%this
187 >            
188               do jnab = jbeg, jend
189                  j = list(jnab)
190 <                Atype_j = identPtrListColumn(j)%this
191 <                call get_interatomic_vector(i,j,qRow(:,i),qCol(:,j),&
192 <                     rxij,ryij,rzij,rijsq,r)
193 <                
500 <                call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
190 >
191 >                call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
192 >                call do_pair(i, j, rijsq, d)
193 >
194               enddo
195            endif
196         enddo
# Line 513 | Line 206 | contains
206        
207         neighborListSize = getNeighborListSize()
208         nlist = 0
209 <      
517 <    
209 >          
210         do i = 1, natoms-1
211            point(i) = nlist + 1
520          Atype_i   => identPtrList(i)%this
212  
213            inner: do j = i+1, natoms
214 <             Atype_j   => identPtrList(j)%this
215 <             call get_interatomic_vector(i,j,q(:,i),q(:,j),&
216 <                  rxij,ryij,rzij,rijsq,r)
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 <
220 >                
221                  nlist = nlist + 1
222                  
223                  if (nlist > neighborListSize) then
# Line 538 | Line 230 | contains
230                  endif
231                  
232                  list(nlist) = j
233 <
542 <    
233 >                    
234                  if (rijsq <  rcutsq) then
235 <                   call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
235 >                   call do_pair(i, j, rijsq, d)
236                  endif
237               endif
238            enddo inner
# Line 558 | Line 249 | contains
249            ! check thiat molecule i has neighbors
250            if (jbeg .le. jend) then
251              
561             Atype_i => identPtrList(i)%this
252               do jnab = jbeg, jend
253                  j = list(jnab)
254 <                Atype_j = identPtrList(j)%this
255 <                call get_interatomic_vector(i,j,q(:,i),q(:,j),&
256 <                     rxij,ryij,rzij,rijsq,r)
257 <                call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
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 <
262 >    
263   #endif
264 <
265 <
264 >    
265 >    
266   #ifdef IS_MPI
267      !! distribute all reaction field stuff (or anything for post-pair):
268      call scatter(rflRow,rflTemp1,plan_row3d)
# Line 581 | Line 271 | contains
271         rflTemp(1:3,i) = rflTemp1(1:3,i) + rflTemp2(1:3,i)
272      end do
273   #endif
274 <
274 >    
275   ! This is the post-pair loop:
276   #ifdef IS_MPI
277 <
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 <
284 >    
285   #else
286 <
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 <
293 >    
294   #endif
295 +    
296  
606
607
608
297   #ifdef IS_MPI
298      !!distribute forces
299  
300 <    call scatter(fRow,fTemp1,plan_row3d)
301 <    call scatter(fCol,fTemp2,plan_col3d)
614 <
615 <
300 >    call scatter(f_Row,f,plan_row3d)
301 >    call scatter(f_Col,f_temp,plan_col3d)
302      do i = 1,nlocal
303 <       fTemp(1:3,i) = fTemp1(1:3,i) + fTemp2(1:3,i)
303 >       f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
304      end do
305  
306 <    if (do_torque) then
307 <       call scatter(tRow,tTemp1,plan_row3d)
308 <       call scatter(tCol,tTemp2,plan_col3d)
306 >    if (doTorque()) then
307 >       call scatter(t_Row,t,plan_row3d)
308 >       call scatter(t_Col,t_temp,plan_col3d)
309      
310         do i = 1,nlocal
311 <          tTemp(1:3,i) = tTemp1(1:3,i) + tTemp2(1:3,i)
311 >          t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
312         end do
313      endif
314 <
314 >    
315      if (do_pot) then
316         ! scatter/gather pot_row into the members of my column
317 <       call scatter(eRow,eTemp,plan_row)
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 <          pe_local = pe_local + eTemp(i)
322 >          pot_local = pot_local + pot_Temp(i)
323         enddo
324  
325 <       eTemp = 0.0E0_DP
326 <       call scatter(eCol,eTemp,plan_col)
325 >       pot_Temp = 0.0_DP
326 >
327 >       call scatter(pot_Col, pot_Temp, plan_col)
328         do i = 1, nlocal
329 <          pe_local = pe_local + eTemp(i)
329 >          pot_local = pot_local + pot_Temp(i)
330         enddo
331        
332 <       pe = pe_local
332 >       pot = pot_local
333      endif
647 #else
648 ! Copy local array into return array for c
649    f = f+fTemp
650    t = t+tTemp
651 #endif
334  
335 <    potE = pe
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
343  
344 <    if (do_stress) then
345 < #ifdef IS_MPI
346 <       mpi_allreduce = (tau,tauTemp,9,mpi_double_precision,mpi_sum, &
659 <            mpi_comm_world,mpi_err)
660 < #else
661 <       tau = tauTemp
662 < #endif      
344 >    if (doStress()) then
345 >       tau = tau_Temp
346 >       virial = virial_Temp
347      endif
348  
349    end subroutine do_force_loop
350  
351  
668
669
670
671
672
673
674
675
352   !! Calculate any pre-force loop components and update nlist if necessary.
353    subroutine do_preForce(updateNlist)
354      logical, intent(inout) :: updateNlist
# Line 681 | Line 357 | contains
357  
358    end subroutine do_preForce
359  
684
685
686
687
688
689
690
691
692
693
694
695
360   !! Calculate any post force loop components, i.e. reaction field, etc.
361    subroutine do_postForce()
362  
# Line 700 | Line 364 | contains
364  
365    end subroutine do_postForce
366  
367 +  subroutine do_pair(i, j, rijsq, d)
368  
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 +    r = sqrt(rijsq)
375 +    
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 +    me_i = atid(i)
389 +    me_j = atid(j)
390  
391 + #endif
392  
393 +    call getElementProperty(atypes, me_i, "is_LJ", is_LJ_i)
394 +    call getElementProperty(atypes, me_j, "is_LJ", is_LJ_j)
395  
396 +    if ( is_LJ_i .and. is_LJ_j ) call do_lj_pair(i, j, d, r, pot, f)
397  
398 +    call getElementProperty(atypes, me_i, "is_DP", is_DP_i)
399 +    call getElementProperty(atypes, me_j, "is_DP", is_DP_j)
400  
401 +    if ( is_DP_i .and. is_DP_j ) then
402  
403 <
716 <
717 <
718 <
719 <  subroutine do_pair(atype_i,atype_j,i,j,r_ij,rx_ij,ry_ij,rz_ij)
720 <    type (atype ), pointer, intent(inout) :: atype_i
721 <    type (atype ), pointer, intent(inout) :: atype_j
722 <    integer :: i
723 <    integer :: j
724 <    real ( kind = dp ), intent(inout) :: rx_ij
725 <    real ( kind = dp ), intent(inout) :: ry_ij
726 <    real ( kind = dp ), intent(inout) :: rz_ij
727 <
728 <
729 <    real( kind = dp ) :: fx = 0.0_dp
730 <    real( kind = dp ) :: fy = 0.0_dp
731 <    real( kind = dp ) :: fz = 0.0_dp  
732 <  
733 <    real( kind = dp ) ::  drdx = 0.0_dp
734 <    real( kind = dp ) ::  drdy = 0.0_dp
735 <    real( kind = dp ) ::  drdz = 0.0_dp
736 <    
403 >       call do_dipole_pair(i, j, d, r, pot, u_l, f, t)
404  
738    if (Atype_i%is_LJ .and. Atype_j%is_LJ) then
739       call getLJForce(r,pot,dudr,ljAtype_i,ljAtype_j,fx,fy,fz)
740    endif
741
742    if (Atype_i%is_dp .and. Atype_j%is_dp) then
743
744 #ifdef IS_MPI
745       call dipole_dipole(i, j, atype_i, atype_j, rx_ij, ry_ij, rz_ij, r_ij, &
746            ulRow(:,i), ulCol(:,j), rt, rrf, pot)
747 #else
748       call dipole_dipole(i, j, atype_i, atype_j, rx_ij, ry_ij, rz_ij, r_ij, &
749            ul(:,i), ul(:,j), rt, rrf, pot)
750 #endif
751
405         if (do_reaction_field) then
406 < #ifdef IS_MPI
754 <          call accumulate_rf(i, j, r_ij, rflRow(:,i), rflCol(:j), &
755 <               ulRow(:i), ulCol(:,j), rt, rrf)
756 < #else
757 <          call accumulate_rf(i, j, r_ij, rfl(:,i), rfl(:j), &
758 <               ul(:,i), ul(:,j), rt, rrf)
759 < #endif
406 >          call accumulate_rf(i, j, r_ij)
407         endif
408  
762
409      endif
410  
411 <    if (Atype_i%is_sticky .and. Atype_j%is_sticky) then
412 <       call getstickyforce(r,pot,dudr,ljAtype_i,ljAtype_j)
411 >    call getElementProperty(atypes, me_i, "is_Sticky", is_Sticky_i)
412 >    call getElementProperty(atypes, me_j, "is_Sticky", is_Sticky_j)
413 >
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 <      
770 < #ifdef IS_MPI
771 <                eRow(i) = eRow(i) + pot*0.5
772 <                eCol(i) = eCol(i) + pot*0.5
773 < #else
774 <                    pe = pe + pot
775 < #endif                
776 <            
777 <                drdx = -rxij / r
778 <                drdy = -ryij / r
779 <                drdz = -rzij / r
780 <                
781 <                fx = dudr * drdx
782 <                fy = dudr * drdy
783 <                fz = dudr * drdz
784 <
785 <
786 <
787 <
788 <
789 <
790 <                
791 < #ifdef IS_MPI
792 <                fCol(1,j) = fCol(1,j) - fx
793 <                fCol(2,j) = fCol(2,j) - fy
794 <                fCol(3,j) = fCol(3,j) - fz
795 <                
796 <                fRow(1,j) = fRow(1,j) + fx
797 <                fRow(2,j) = fRow(2,j) + fy
798 <                fRow(3,j) = fRow(3,j) + fz
799 < #else
800 <                fTemp(1,j) = fTemp(1,j) - fx
801 <                fTemp(2,j) = fTemp(2,j) - fy
802 <                fTemp(3,j) = fTemp(3,j) - fz
803 <                fTemp(1,i) = fTemp(1,i) + fx
804 <                fTemp(2,i) = fTemp(2,i) + fy
805 <                fTemp(3,i) = fTemp(3,i) + fz
806 < #endif
807 <                
808 <                if (do_stress) then
809 <                   tauTemp(1) = tauTemp(1) + fx * rxij
810 <                   tauTemp(2) = tauTemp(2) + fx * ryij
811 <                   tauTemp(3) = tauTemp(3) + fx * rzij
812 <                   tauTemp(4) = tauTemp(4) + fy * rxij
813 <                   tauTemp(5) = tauTemp(5) + fy * ryij
814 <                   tauTemp(6) = tauTemp(6) + fy * rzij
815 <                   tauTemp(7) = tauTemp(7) + fz * rxij
816 <                   tauTemp(8) = tauTemp(8) + fz * ryij
817 <                   tauTemp(9) = tauTemp(9) + fz * rzij
818 <                endif
819 <
820 <
821 <
418 >      
419    end subroutine do_pair
420  
421  
422 <
423 <
827 <
828 <
829 <
830 <
831 <
832 <
833 <
834 <
835 <
836 <
837 <
838 <
839 <  subroutine get_interatomic_vector(q_i,q_j,rx_ij,ry_ij,rz_ij,r_sq,r_ij)
840 < !---------------- Arguments-------------------------------
841 <   !! index i
842 <
843 <    !! Position array
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
846    !! x component of vector between i and j
847    real ( kind = dp ), intent(out)  :: rx_ij
848    !! y component of vector between i and j
849    real ( kind = dp ), intent(out)  :: ry_ij
850    !! z component of vector between i and j
851    real ( kind = dp ), intent(out)  :: rz_ij
852    !! magnitude of r squared
426      real ( kind = dp ), intent(out) :: r_sq
854    !! magnitude of vector r between atoms i and j.
855    real ( kind = dp ), intent(out) :: r_ij
856    !! wrap into periodic box.
857    logical, intent(in) :: wrap
858
859 !--------------- Local Variables---------------------------
860    !! Distance between i and j
427      real( kind = dp ) :: d(3)
862 !---------------- END DECLARATIONS-------------------------
428  
864
865 ! Find distance between i and j
429      d(1:3) = q_i(1:3) - q_j(1:3)
430 <
431 < ! Wrap back into periodic box if necessary
432 <    if ( wrap ) then
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 <    end if
435 >    endif
436      
874 !   Find Magnitude of the vector
437      r_sq = dot_product(d,d)
438 <    r_ij = sqrt(r_sq)
877 <
878 < !   Set each component for force calculation
879 <    rx_ij = d(1)
880 <    ry_ij = d(2)
881 <    rz_ij = d(3)
882 <
883 <
438 >        
439    end subroutine get_interatomic_vector
440 <
440 >  
441    subroutine zero_module_variables()
442  
443   #ifndef IS_MPI
# Line 920 | Line 475 | contains
475  
476    end subroutine zero_module_variables
477  
478 < #ifdef IS_MPI
478 >
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 mpi_cycle_jLoop(i,j) result(do_cycle)
482 >  function checkExcludes(atom1,atom2) result(do_cycle)
483   !--------------- Arguments--------------------------
484   ! Index i
485 <    integer,intent(in) :: i
485 >    integer,intent(in) :: atom1
486   ! Index j
487 <    integer,intent(in) :: 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 < !--------------- END DECLARATIONS------------------    
494 <    tag_i = tagRow(i)
493 >    integer :: i
494 > !--------------- END DECLARATIONS------------------  
495 >    do_cycle = .false.
496 >
497 > #ifdef IS_MPI
498 >    tag_i = tagRow(atom1)
499 > #else
500 >    tag_i = tag(atom1)
501 > #endif
502 >
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 > !! we return if j not present here.
515      tag_j = tagColumn(j)
516  
517 <    do_cycle = .false.
517 >
518  
519      if (tag_i == tag_j) then
520         do_cycle = .true.
# Line 952 | Line 527 | contains
527      else                
528         if (mod(tag_i + tag_j,2) == 1) do_cycle = .true.
529      endif
955  end function mpi_cycle_jLoop
956 #endif
530  
531 +
532 +
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
539 +      
540 +
541 +  end function checkExcludes
542 +
543 +
544   end module do_Forces

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines