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 306 by chuckv, Mon Mar 10 19:26:45 2003 UTC vs.
Revision 325 by gezelter, Wed Mar 12 19:10:54 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.8 2003-03-10 19:26:45 chuckv Exp $, $Date: 2003-03-10 19:26:45 $, $Name: not supported by cvs2svn $, $Revision: 1.8 $
7 > !! @version $Id: do_Forces.F90,v 1.13 2003-03-12 19:10:54 gezelter Exp $, $Date: 2003-03-12 19:10:54 $, $Name: not supported by cvs2svn $, $Revision: 1.13 $
8  
9  
10  
# Line 13 | Line 13 | module do_Forces
13    use definitions
14    use forceGlobals
15    use atype_typedefs
16 <  use neighborLists
17 <
18 <  
16 >  use neighborLists  
17    use lj_FF
18    use sticky_FF
19 <  use dp_FF
19 >  use dipole_dipole
20    use gb_FF
21  
22   #ifdef IS_MPI
# Line 27 | Line 25 | public :: do_force_loop
25    implicit none
26    PRIVATE
27  
28 < public :: do_force_loop
28 >  public :: do_force_loop
29  
30 +  logical :: do_pot
31 +  logical :: do_stress
32 +
33   contains
34  
35 < !! Does force loop over i,j pairs. Calls do_pair to calculates forces.
36 < !------------------------------------------------------------->
37 <  subroutine do_force_loop(q,A,mu,u_l,f,t,tau,potE,do_pot,FFerror)
38 < !! Position array provided by C, dimensioned by getNlocal
35 >  !! Does force loop over i,j pairs. Calls do_pair to calculates forces.
36 >  !------------------------------------------------------------->
37 >  subroutine do_force_loop(q, A, u_l, f, t, tau, pot, do_pot_c, do_stress_c, &
38 >       FFerror)
39 >    !! Position array provided by C, dimensioned by getNlocal
40      real ( kind = dp ), dimension(3,getNlocal()) :: q
41 <  !! Rotation Matrix for each long range particle in simulation.
42 <    real( kind = dp), dimension(9,getNlocal()) :: A
43 <
42 <  !! Magnitude dipole moment
43 <    real( kind = dp ), dimension(3,getNlocal()) :: mu
44 <  !! Unit vectors for dipoles (lab frame)
41 >    !! Rotation Matrix for each long range particle in simulation.
42 >    real( kind = dp), dimension(9,getNlocal()) :: A    
43 >    !! Unit vectors for dipoles (lab frame)
44      real( kind = dp ), dimension(3,getNlocal()) :: u_l
45 < !! Force array provided by C, dimensioned by getNlocal
45 >    !! Force array provided by C, dimensioned by getNlocal
46      real ( kind = dp ), dimension(3,getNlocal()) :: f
47 < !! Torsion array provided by C, dimensioned by getNlocal
48 <    real( kind = dp ), dimension(3,getNlocal()) :: t
49 <
50 < !! Stress Tensor
51 <    real( kind = dp), dimension(9) :: tau
52 <
54 <    real ( kind = dp ) :: potE
55 <    logical ( kind = 2) :: do_pot
47 >    !! Torsion array provided by C, dimensioned by getNlocal
48 >    real( kind = dp ), dimension(3,getNlocal()) :: t    
49 >    !! Stress Tensor
50 >    real( kind = dp), dimension(9) :: tau  
51 >    real ( kind = dp ) :: pot
52 >    logical ( kind = 2) :: do_pot_c, do_stress_c
53      integer :: FFerror
54  
55 + #ifdef IS_MPI
56 +    real( kind = DP ) :: pot_local
57 + #endif
58      
59 <    type(atype), pointer :: Atype_i
60 <    type(atype), pointer :: Atype_j
59 >    logical :: update_nlist  
60 >    integer :: i, j, jbeg, jend, jnab
61 >    integer :: nlist
62 >    real( kind = DP ) ::  rijsq, rlistsq, rcutsq, rlist, rcut
63  
62
63
64
65  
66
64   #ifdef IS_MPI
65 <  real( kind = DP ) :: pot_local
69 <
70 < !! Local arrays needed for MPI
71 <
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
65 >    integer :: nlocal
66   #endif
67 <  integer :: nrow
68 <  integer :: ncol
69 <  integer :: natoms
70 <  integer :: neighborListSize
71 <  integer :: listerror
72 < !! should we calculate the stress tensor
102 <  logical  :: do_stress = .false.
67 >    integer :: nrow
68 >    integer :: ncol
69 >    integer :: natoms
70 >    integer :: neighborListSize
71 >    integer :: listerror
72 >    FFerror = 0
73  
74 +    do_pot = do_pot_c
75 +    do_stress = do_stress_c
76  
77 <  FFerror = 0
78 <
79 < ! Make sure we are properly initialized.
80 <  if (.not. isFFInit) then
81 <     write(default_error,*) "ERROR: lj_FF has not been properly initialized"
82 <     FFerror = -1
111 <     return
112 <  endif
77 >    ! Make sure we are properly initialized.
78 >    if (.not. isFFInit) then
79 >       write(default_error,*) "ERROR: lj_FF has not been properly initialized"
80 >       FFerror = -1
81 >       return
82 >    endif
83   #ifdef IS_MPI
84      if (.not. isMPISimSet()) then
85 <     write(default_error,*) "ERROR: mpiSimulation has not been properly initialized"
86 <     FFerror = -1
87 <     return
88 <  endif
85 >       write(default_error,*) "ERROR: mpiSimulation has not been properly initialized"
86 >       FFerror = -1
87 >       return
88 >    endif
89   #endif
90 <
91 < !! initialize local variables  
92 <  natoms = getNlocal()
93 <  call getRcut(rcut,rcut2=rcutsq)
94 <  call getRlist(rlist,rlistsq)
95 <
96 < !! Find ensemble
97 <  if (isEnsemble("NPT")) do_stress = .true.
98 < !! set to wrap
99 <  if (isPBC()) wrap = .true.
100 <
101 <
102 <
103 <  
104 < !! 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
146 < #ifdef IS_MPI    
147 <    call gather(q,qRow,plan_row3d)
148 <    call gather(q,qCol,plan_col3d)
149 <
150 <    call gather(mu,muRow,plan_row3d)
151 <    call gather(mu,muCol,plan_col3d)
152 <
153 <    call gather(u_l,u_lRow,plan_row3d)
154 <    call gather(u_l,u_lCol,plan_col3d)
90 >    
91 >    !! initialize local variables  
92 >    natoms = getNlocal()
93 >    call getRcut(rcut,rcut2=rcutsq)
94 >    call getRlist(rlist,rlistsq)
95 >    
96 >    !! See if we need to update neighbor lists
97 >    call checkNeighborList(natoms, q, rcut, rlist, update_nlist)
98 >    
99 >    !--------------WARNING...........................
100 >    ! Zero variables, NOTE:::: Forces are zeroed in C
101 >    ! Zeroing them here could delete previously computed
102 >    ! Forces.
103 >    !------------------------------------------------
104 >    call zero_module_variables()
105  
106 <    call gather(A,ARow,plan_row_rotation)
107 <    call gather(A,ACol,plan_col_rotation)
106 >    ! communicate MPI positions
107 > #ifdef IS_MPI    
108 >    call gather(q,q_Row,plan_row3d)
109 >    call gather(q,q_Col,plan_col3d)
110 >    
111 >    call gather(u_l,u_l_Row,plan_row3d)
112 >    call gather(u_l,u_l_Col,plan_col3d)
113 >    
114 >    call gather(A,A_Row,plan_row_rotation)
115 >    call gather(A,A_Col,plan_col_rotation)
116   #endif
117  
118  
# Line 175 | Line 133 | contains
133        
134         do i = 1, nrow
135            point(i) = nlist + 1
178          Atype_i => identPtrListRow(i)%this
136            
137            inner: do j = 1, ncol
181             Atype_j => identPtrListColumn(j)%this
138              
139 <             call get_interatomic_vector(i,j,qRow(:,i),qCol(:,j),&
140 <                  rxij,ryij,rzij,rijsq,r)
141 <            
142 <             ! skip the loop if the atoms are identical
187 <             if (mpi_cycle_jLoop(i,j)) cycle inner:
188 <            
139 >             if (check_exclude(i,j)) cycle inner:
140 >
141 >             call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
142 >            
143               if (rijsq <  rlistsq) then            
144                  
145                  nlist = nlist + 1
146                  
147                  if (nlist > neighborListSize) then
148 <                   call expandList(listerror)
148 >                   call expandNeighborList(nlocal, listerror)
149                     if (listerror /= 0) then
150                        FFerror = -1
151                        write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
# Line 200 | Line 154 | contains
154                  endif
155                  
156                  list(nlist) = j
157 <                
204 <                
157 >                                
158                  if (rijsq <  rcutsq) then
159 <                   call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
159 >                   call do_pair(i, j, rijsq, d)
160                  endif
161               endif
162            enddo inner
# Line 219 | Line 172 | contains
172            JEND = POINT(i+1) - 1
173            ! check thiat molecule i has neighbors
174            if (jbeg .le. jend) then
175 <
223 <             Atype_i => identPtrListRow(i)%this
175 >            
176               do jnab = jbeg, jend
177                  j = list(jnab)
178 <                Atype_j = identPtrListColumn(j)%this
179 <                call get_interatomic_vector(i,j,qRow(:,i),qCol(:,j),&
180 <                     rxij,ryij,rzij,rijsq,r)
181 <                
230 <                call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
178 >
179 >                call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
180 >                call do_pair(i, j, rijsq, d)
181 >
182               enddo
183            endif
184         enddo
# Line 243 | Line 194 | contains
194        
195         neighborListSize = getNeighborListSize()
196         nlist = 0
197 <      
247 <    
197 >          
198         do i = 1, natoms-1
199            point(i) = nlist + 1
250          Atype_i   => identPtrList(i)%this
200  
201            inner: do j = i+1, natoms
202 <             Atype_j   => identPtrList(j)%this
203 <             call get_interatomic_vector(i,j,q(:,i),q(:,j),&
204 <                  rxij,ryij,rzij,rijsq,r)
202 >
203 >             if (check_exclude(i,j)) cycle inner:
204 >
205 >             call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
206            
207               if (rijsq <  rlistsq) then
208 <
208 >                
209                  nlist = nlist + 1
210                  
211                  if (nlist > neighborListSize) then
212 <                   call expandList(listerror)
212 >                   call expandList(natoms, listerror)
213                     if (listerror /= 0) then
214                        FFerror = -1
215                        write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
# Line 268 | Line 218 | contains
218                  endif
219                  
220                  list(nlist) = j
221 <
272 <    
221 >                    
222                  if (rijsq <  rcutsq) then
223 <                   call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
223 >                   call do_pair(i, j, rijsq, d)
224                  endif
225               endif
226            enddo inner
# Line 288 | Line 237 | contains
237            ! check thiat molecule i has neighbors
238            if (jbeg .le. jend) then
239              
291             Atype_i => identPtrList(i)%this
240               do jnab = jbeg, jend
241                  j = list(jnab)
242 <                Atype_j = identPtrList(j)%this
243 <                call get_interatomic_vector(i,j,q(:,i),q(:,j),&
244 <                     rxij,ryij,rzij,rijsq,r)
245 <                call do_pair(Atype_i,Atype_j,i,j,r,rxij,ryij,rzij)
242 >
243 >                call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
244 >                call do_pair(i, j, rijsq, d)
245 >
246               enddo
247            endif
248         enddo
249      endif
250 <
250 >    
251   #endif
252 <
253 <
252 >    
253 >    
254   #ifdef IS_MPI
255      !! distribute all reaction field stuff (or anything for post-pair):
256      call scatter(rflRow,rflTemp1,plan_row3d)
# Line 311 | Line 259 | contains
259         rflTemp(1:3,i) = rflTemp1(1:3,i) + rflTemp2(1:3,i)
260      end do
261   #endif
262 <
262 >    
263   ! This is the post-pair loop:
264   #ifdef IS_MPI
265 <
265 >    
266      if (system_has_postpair_atoms) then
267         do i = 1, nlocal
268            Atype_i => identPtrListRow(i)%this
269            call do_postpair(i, Atype_i)
270         enddo
271      endif
272 <
272 >    
273   #else
274 <
274 >    
275      if (system_has_postpair_atoms) then
276         do i = 1, natoms
277            Atype_i => identPtr(i)%this
278            call do_postpair(i, Atype_i)
279         enddo
280      endif
281 <
281 >    
282   #endif
283 +    
284  
336
337
338
285   #ifdef IS_MPI
286      !!distribute forces
287  
288 <    call scatter(fRow,fTemp1,plan_row3d)
289 <    call scatter(fCol,fTemp2,plan_col3d)
344 <
345 <
288 >    call scatter(f_Row,f,plan_row3d)
289 >    call scatter(f_Col,f_temp,plan_col3d)
290      do i = 1,nlocal
291 <       fTemp(1:3,i) = fTemp1(1:3,i) + fTemp2(1:3,i)
291 >       f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
292      end do
293  
294 <    if (do_torque) then
295 <       call scatter(tRow,tTemp1,plan_row3d)
296 <       call scatter(tCol,tTemp2,plan_col3d)
294 >    if (doTorque()) then
295 >       call scatter(t_Row,t,plan_row3d)
296 >       call scatter(t_Col,t_temp,plan_col3d)
297      
298         do i = 1,nlocal
299 <          tTemp(1:3,i) = tTemp1(1:3,i) + tTemp2(1:3,i)
299 >          t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
300         end do
301      endif
302 <
302 >    
303      if (do_pot) then
304         ! scatter/gather pot_row into the members of my column
305 <       call scatter(eRow,eTemp,plan_row)
305 >       call scatter(pot_Row, pot_Temp, plan_row)
306        
307         ! scatter/gather pot_local into all other procs
308         ! add resultant to get total pot
309         do i = 1, nlocal
310 <          pe_local = pe_local + eTemp(i)
310 >          pot_local = pot_local + pot_Temp(i)
311         enddo
312  
313 <       eTemp = 0.0E0_DP
314 <       call scatter(eCol,eTemp,plan_col)
313 >       pot_Temp = 0.0_DP
314 >
315 >       call scatter(pot_Col, pot_Temp, plan_col)
316         do i = 1, nlocal
317 <          pe_local = pe_local + eTemp(i)
317 >          pot_local = pot_local + pot_Temp(i)
318         enddo
319        
320 <       pe = pe_local
320 >       pot = pot_local
321      endif
377 #else
378 ! Copy local array into return array for c
379    f = f+fTemp
380    t = t+tTemp
381 #endif
322  
323 <    potE = pe
323 >    if (doStress()) then
324 >       mpi_allreduce(tau, tau_Temp,9,mpi_double_precision,mpi_sum, &
325 >            mpi_comm_world,mpi_err)
326 >       mpi_allreduce(virial, virial_Temp,1,mpi_double_precision,mpi_sum, &
327 >            mpi_comm_world,mpi_err)
328 >    endif
329  
330 + #endif
331  
332 <    if (do_stress) then
333 < #ifdef IS_MPI
334 <       mpi_allreduce = (tau,tauTemp,9,mpi_double_precision,mpi_sum, &
389 <            mpi_comm_world,mpi_err)
390 < #else
391 <       tau = tauTemp
392 < #endif      
332 >    if (doStress()) then
333 >       tau = tau_Temp
334 >       virial = virial_Temp
335      endif
336  
337    end subroutine do_force_loop
338  
339  
398
399
400
401
402
403
404
405
340   !! Calculate any pre-force loop components and update nlist if necessary.
341    subroutine do_preForce(updateNlist)
342      logical, intent(inout) :: updateNlist
# Line 411 | Line 345 | contains
345  
346    end subroutine do_preForce
347  
414
415
416
417
418
419
420
421
422
423
424
425
348   !! Calculate any post force loop components, i.e. reaction field, etc.
349    subroutine do_postForce()
350  
# Line 430 | Line 352 | contains
352  
353    end subroutine do_postForce
354  
355 +  subroutine do_pair(i, j, rijsq, d)
356  
357 +    integer, intent(in) :: i, j
358 +    real ( kind = dp ), intent(in)    :: rijsq
359 +    real ( kind = dp )                :: r
360 +    real ( kind = dp ), intent(inout) :: d(3)
361  
362 <
436 <
437 <
438 <
439 <
440 <
441 <
442 <
443 <
444 <
445 <
446 <
447 <
448 <
449 <  subroutine do_pair(atype_i,atype_j,i,j,r_ij,rx_ij,ry_ij,rz_ij)
450 <    type (atype ), pointer, intent(inout) :: atype_i
451 <    type (atype ), pointer, intent(inout) :: atype_j
452 <    integer :: i
453 <    integer :: j
454 <    real ( kind = dp ), intent(inout) :: rx_ij
455 <    real ( kind = dp ), intent(inout) :: ry_ij
456 <    real ( kind = dp ), intent(inout) :: rz_ij
457 <
458 <
459 <    real( kind = dp ) :: fx = 0.0_dp
460 <    real( kind = dp ) :: fy = 0.0_dp
461 <    real( kind = dp ) :: fz = 0.0_dp  
462 <  
463 <    real( kind = dp ) ::  drdx = 0.0_dp
464 <    real( kind = dp ) ::  drdy = 0.0_dp
465 <    real( kind = dp ) ::  drdz = 0.0_dp
362 >    r = sqrt(rijsq)
363      
364 +    logical :: is_LJ_i, is_LJ_j
365 +    logical :: is_DP_i, is_DP_j
366 +    logical :: is_Sticky_i, is_Sticky_j
367 +    integer :: me_i, me_j
368  
369   #ifdef IS_MPI
370  
371 <    if (Atype_i%is_LJ .and. Atype_j%is_LJ) then
372 <       call getLJForce(r,pot,dudr,ljAtype_i,ljAtype_j,fx,fy,fz)
472 <    endif
371 >    me_i = atid_row(i)
372 >    me_j = atid_col(j)
373  
374 <    if (Atype_i%is_dp .and. Atype_j%is_dp) then
374 > #else
375  
376 <       call dipole_dipole(i, j, atype_i, atype_j, rx_ij, ry_ij, rz_ij, r_ij, &
377 <            ulRow(:,i), ulCol(:,j), rt, rrf, pot)
376 >    me_i = atid(i)
377 >    me_j = atid(j)
378  
379 <       if (do_reaction_field) then
480 <          call accumulate_rf(i, j, r_ij, rflRow(:,i), rflCol(:j), &
481 <               ulRow(:i), ulCol(:,j), rt, rrf)
482 <       endif
379 > #endif
380  
381 <    endif
381 >    call getElementProperty(atypes, me_i, "is_LJ", is_LJ_i)
382 >    call getElementProperty(atypes, me_j, "is_LJ", is_LJ_j)
383  
384 <    if (Atype_i%is_sticky .and. Atype_j%is_sticky) then
385 <       call getstickyforce(r, pot, dudr, Atype_i, Atype_j)
488 <    endif
384 >    if ( is_LJ_i .and. is_LJ_j ) &
385 >         call do_lj_pair(i, j, d, r, rijsq, pot, f, do_pot, do_stress)
386  
387 < #else
387 >    call getElementProperty(atypes, me_i, "is_DP", is_DP_i)
388 >    call getElementProperty(atypes, me_j, "is_DP", is_DP_j)
389  
390 <    if (Atype_i%is_LJ .and. Atype_j%is_LJ) then
493 <       call getLJForce(r,pot,dudr,ljAtype_i,ljAtype_j,fx,fy,fz)
494 <    endif
390 >    if ( is_DP_i .and. is_DP_j ) then
391  
392 <    if (Atype_i%is_dp .and. Atype_j%is_dp) then
497 <       call dipole_dipole(i, j, atype_i, atype_j, rx_ij, ry_ij, rz_ij, r_ij, &
498 <            ul(:,i), ul(:,j), rt, rrf, pot)
392 >       call do_dipole_pair(i, j, d, r, pot, u_l, f, t, do_pot, do_stress)
393  
394         if (do_reaction_field) then
395 <          call accumulate_rf(i, j, r_ij, rfl(:,i), rfl(:j), &
502 <               ul(:,i), ul(:,j), rt, rrf)
395 >          call accumulate_rf(i, j, r)
396         endif
397  
398      endif
399  
400 <    if (Atype_i%is_sticky .and. Atype_j%is_sticky) then
401 <       call getstickyforce(r,pot,dudr, Atype_i, Atype_j)
400 >    call getElementProperty(atypes, me_i, "is_Sticky", is_Sticky_i)
401 >    call getElementProperty(atypes, me_j, "is_Sticky", is_Sticky_j)
402 >
403 >    if ( is_Sticky_i .and. is_Sticky_j ) then
404 >       call do_sticky_pair(i, j, d, r, rijsq, A, pot, f, t, do_pot, do_stress)
405      endif
406  
407 < #endif
512 <
513 <      
514 < #ifdef IS_MPI
515 <                eRow(i) = eRow(i) + pot*0.5
516 <                eCol(i) = eCol(i) + pot*0.5
517 < #else
518 <                    pe = pe + pot
519 < #endif                
520 <            
521 <                drdx = -rxij / r
522 <                drdy = -ryij / r
523 <                drdz = -rzij / r
524 <                
525 <                fx = dudr * drdx
526 <                fy = dudr * drdy
527 <                fz = dudr * drdz
528 <                
529 < #ifdef IS_MPI
530 <                fCol(1,j) = fCol(1,j) - fx
531 <                fCol(2,j) = fCol(2,j) - fy
532 <                fCol(3,j) = fCol(3,j) - fz
533 <                
534 <                fRow(1,j) = fRow(1,j) + fx
535 <                fRow(2,j) = fRow(2,j) + fy
536 <                fRow(3,j) = fRow(3,j) + fz
537 < #else
538 <                fTemp(1,j) = fTemp(1,j) - fx
539 <                fTemp(2,j) = fTemp(2,j) - fy
540 <                fTemp(3,j) = fTemp(3,j) - fz
541 <                fTemp(1,i) = fTemp(1,i) + fx
542 <                fTemp(2,i) = fTemp(2,i) + fy
543 <                fTemp(3,i) = fTemp(3,i) + fz
544 < #endif
545 <                
546 <                if (do_stress) then
547 <                   tauTemp(1) = tauTemp(1) + fx * rxij
548 <                   tauTemp(2) = tauTemp(2) + fx * ryij
549 <                   tauTemp(3) = tauTemp(3) + fx * rzij
550 <                   tauTemp(4) = tauTemp(4) + fy * rxij
551 <                   tauTemp(5) = tauTemp(5) + fy * ryij
552 <                   tauTemp(6) = tauTemp(6) + fy * rzij
553 <                   tauTemp(7) = tauTemp(7) + fz * rxij
554 <                   tauTemp(8) = tauTemp(8) + fz * ryij
555 <                   tauTemp(9) = tauTemp(9) + fz * rzij
556 <                endif
557 <
558 <
559 <
407 >      
408    end subroutine do_pair
409  
410  
411 <
412 <
565 <
566 <
567 <
568 <
569 <
570 <
571 <
572 <
573 <
574 <
575 <
576 <
577 <  subroutine get_interatomic_vector(q_i,q_j,rx_ij,ry_ij,rz_ij,r_sq,r_ij)
578 < !---------------- Arguments-------------------------------
579 <   !! index i
580 <
581 <    !! Position array
411 >  subroutine get_interatomic_vector(q_i, q_j, d, r_sq)
412 >    
413      real (kind = dp), dimension(3) :: q_i
414      real (kind = dp), dimension(3) :: q_j
584    !! x component of vector between i and j
585    real ( kind = dp ), intent(out)  :: rx_ij
586    !! y component of vector between i and j
587    real ( kind = dp ), intent(out)  :: ry_ij
588    !! z component of vector between i and j
589    real ( kind = dp ), intent(out)  :: rz_ij
590    !! magnitude of r squared
415      real ( kind = dp ), intent(out) :: r_sq
592    !! magnitude of vector r between atoms i and j.
593    real ( kind = dp ), intent(out) :: r_ij
594    !! wrap into periodic box.
595    logical, intent(in) :: wrap
596
597 !--------------- Local Variables---------------------------
598    !! Distance between i and j
416      real( kind = dp ) :: d(3)
600 !---------------- END DECLARATIONS-------------------------
417  
602
603 ! Find distance between i and j
418      d(1:3) = q_i(1:3) - q_j(1:3)
419 <
420 < ! Wrap back into periodic box if necessary
421 <    if ( wrap ) then
419 >    
420 >    ! Wrap back into periodic box if necessary
421 >    if ( isPBC() ) then
422         d(1:3) = d(1:3) - thisSim%box(1:3) * sign(1.0_dp,thisSim%box(1:3)) * &
423              int(abs(d(1:3)/thisSim%box(1:3) + 0.5_dp)
424 <    end if
424 >    endif
425      
612 !   Find Magnitude of the vector
426      r_sq = dot_product(d,d)
427 <    r_ij = sqrt(r_sq)
615 <
616 < !   Set each component for force calculation
617 <    rx_ij = d(1)
618 <    ry_ij = d(2)
619 <    rz_ij = d(3)
620 <
621 <
427 >        
428    end subroutine get_interatomic_vector
429 +  
430 +  subroutine zero_work_arrays()
431 +    
432 + #ifdef IS_MPI
433  
434 <  subroutine zero_module_variables()
435 <
626 < #ifndef IS_MPI
627 <
628 <    pe = 0.0E0_DP
629 <    tauTemp = 0.0_dp
630 <    fTemp = 0.0_dp
631 <    tTemp = 0.0_dp
632 < #else
633 <    qRow = 0.0_dp
634 <    qCol = 0.0_dp
434 >    q_Row = 0.0_dp
435 >    q_Col = 0.0_dp  
436      
437 <    muRow = 0.0_dp
438 <    muCol = 0.0_dp
437 >    u_l_Row = 0.0_dp
438 >    u_l_Col = 0.0_dp
439      
440 <    u_lRow = 0.0_dp
441 <    u_lCol = 0.0_dp
440 >    A_Row = 0.0_dp
441 >    A_Col = 0.0_dp
442      
443 <    ARow = 0.0_dp
444 <    ACol = 0.0_dp
445 <    
446 <    fRow = 0.0_dp
447 <    fCol = 0.0_dp
448 <    
449 <  
649 <    tRow = 0.0_dp
650 <    tCol = 0.0_dp
443 >    f_Row = 0.0_dp
444 >    f_Col = 0.0_dp
445 >    f_Temp = 0.0_dp
446 >      
447 >    t_Row = 0.0_dp
448 >    t_Col = 0.0_dp
449 >    t_Temp = 0.0_dp
450  
451 <  
451 >    pot_Row = 0.0_dp
452 >    pot_Col = 0.0_dp
453 >    pot_Temp = 0.0_dp
454  
654    eRow = 0.0_dp
655    eCol = 0.0_dp
656    eTemp = 0.0_dp
455   #endif
456  
457 <  end subroutine zero_module_variables
457 >    tau_Temp = 0.0_dp
458 >    virial_Temp = 0.0_dp
459 >    
460 >  end subroutine zero_work_arrays
461 >  
462  
661
463   !! Function to properly build neighbor lists in MPI using newtons 3rd law.
464   !! We don't want 2 processors doing the same i j pair twice.
465   !! Also checks to see if i and j are the same particle.

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines