ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE/libmdtools/do_Forces.F90
(Generate patch)

Comparing trunk/OOPSE/libmdtools/do_Forces.F90 (file contents):
Revision 887 by mmeineke, Fri Dec 19 17:25:00 2003 UTC vs.
Revision 1206 by tim, Thu May 27 19:51:18 2004 UTC

# Line 4 | Line 4
4  
5   !! @author Charles F. Vardeman II
6   !! @author Matthew Meineke
7 < !! @version $Id: do_Forces.F90,v 1.39 2003-12-19 17:25:00 mmeineke Exp $, $Date: 2003-12-19 17:25:00 $, $Name: not supported by cvs2svn $, $Revision: 1.39 $
7 > !! @version $Id: do_Forces.F90,v 1.65 2004-05-27 19:51:18 tim Exp $, $Date: 2004-05-27 19:51:18 $, $Name: not supported by cvs2svn $, $Revision: 1.65 $
8  
9   module do_Forces
10    use force_globals
11    use simulation
12    use definitions
13    use atype_module
14 +  use switcheroo
15    use neighborLists  
16    use lj
17    use sticky_pair
18    use dipole_dipole
19 +  use charge_charge
20    use reaction_field
21    use gb_pair
22    use vector_class
# Line 29 | Line 31 | module do_Forces
31  
32   #define __FORTRAN90
33   #include "fForceField.h"
34 + #include "fSwitchingFunction.h"
35  
36 <  logical, save :: do_forces_initialized = .false., haveRlist = .false.
36 >  INTEGER, PARAMETER:: PREPAIR_LOOP = 1
37 >  INTEGER, PARAMETER:: PAIR_LOOP    = 2
38 >
39 >  logical, save :: haveRlist = .false.
40 >  logical, save :: haveNeighborList = .false.
41    logical, save :: havePolicies = .false.
42 +  logical, save :: haveSIMvariables = .false.
43 +  logical, save :: havePropertyMap = .false.
44 +  logical, save :: haveSaneForceField = .false.
45    logical, save :: FF_uses_LJ
46    logical, save :: FF_uses_sticky
47 +  logical, save :: FF_uses_charges
48    logical, save :: FF_uses_dipoles
49    logical, save :: FF_uses_RF
50    logical, save :: FF_uses_GB
51    logical, save :: FF_uses_EAM
52 +  logical, save :: SIM_uses_LJ
53 +  logical, save :: SIM_uses_sticky
54 +  logical, save :: SIM_uses_charges
55 +  logical, save :: SIM_uses_dipoles
56 +  logical, save :: SIM_uses_RF
57 +  logical, save :: SIM_uses_GB
58 +  logical, save :: SIM_uses_EAM
59 +  logical, save :: SIM_requires_postpair_calc
60 +  logical, save :: SIM_requires_prepair_calc
61 +  logical, save :: SIM_uses_directional_atoms
62 +  logical, save :: SIM_uses_PBC
63 +  logical, save :: SIM_uses_molecular_cutoffs
64  
65    real(kind=dp), save :: rlist, rlistsq
66  
# Line 49 | Line 72 | module do_Forces
72    public :: getforcetime
73    real, save :: forceTime = 0
74    real :: forceTimeInitial, forceTimeFinal
75 +  integer :: nLoops
76   #endif
77  
78 +  type :: Properties
79 +     logical :: is_lj     = .false.
80 +     logical :: is_sticky = .false.
81 +     logical :: is_dp     = .false.
82 +     logical :: is_gb     = .false.
83 +     logical :: is_eam    = .false.
84 +     logical :: is_charge = .false.
85 +     real(kind=DP) :: charge = 0.0_DP
86 +     real(kind=DP) :: dipole_moment = 0.0_DP
87 +  end type Properties
88 +
89 +  type(Properties), dimension(:),allocatable :: PropertyMap
90 +
91   contains
92  
93    subroutine setRlistDF( this_rlist )
# Line 61 | Line 98 | contains
98      rlistsq = rlist * rlist
99      
100      haveRlist = .true.
64    if( havePolicies ) do_forces_initialized = .true.
101  
102    end subroutine setRlistDF    
103 +
104 +  subroutine createPropertyMap(status)
105 +    integer :: nAtypes
106 +    integer :: status
107 +    integer :: i
108 +    logical :: thisProperty
109 +    real (kind=DP) :: thisDPproperty
110 +
111 +    status = 0
112 +
113 +    nAtypes = getSize(atypes)
114 +
115 +    if (nAtypes == 0) then
116 +       status = -1
117 +       return
118 +    end if
119 +        
120 +    if (.not. allocated(PropertyMap)) then
121 +       allocate(PropertyMap(nAtypes))
122 +    endif
123 +
124 +    do i = 1, nAtypes
125 +       call getElementProperty(atypes, i, "is_LJ", thisProperty)
126 +       PropertyMap(i)%is_LJ = thisProperty
127 +
128 +       call getElementProperty(atypes, i, "is_Charge", thisProperty)
129 +       PropertyMap(i)%is_Charge = thisProperty
130 +      
131 +       if (thisProperty) then
132 +          call getElementProperty(atypes, i, "charge", thisDPproperty)
133 +          PropertyMap(i)%charge = thisDPproperty
134 +       endif
135 +
136 +       call getElementProperty(atypes, i, "is_DP", thisProperty)
137 +       PropertyMap(i)%is_DP = thisProperty
138 +
139 +       if (thisProperty) then
140 +          call getElementProperty(atypes, i, "dipole_moment", thisDPproperty)
141 +          PropertyMap(i)%dipole_moment = thisDPproperty
142 +       endif
143 +
144 +       call getElementProperty(atypes, i, "is_Sticky", thisProperty)
145 +       PropertyMap(i)%is_Sticky = thisProperty
146 +       call getElementProperty(atypes, i, "is_GB", thisProperty)
147 +       PropertyMap(i)%is_GB = thisProperty
148 +       call getElementProperty(atypes, i, "is_EAM", thisProperty)
149 +       PropertyMap(i)%is_EAM = thisProperty
150 +    end do
151 +
152 +    havePropertyMap = .true.
153 +
154 +  end subroutine createPropertyMap
155 +
156 +  subroutine setSimVariables()
157 +    SIM_uses_LJ = SimUsesLJ()
158 +    SIM_uses_sticky = SimUsesSticky()
159 +    SIM_uses_charges = SimUsesCharges()
160 +    SIM_uses_dipoles = SimUsesDipoles()
161 +    SIM_uses_RF = SimUsesRF()
162 +    SIM_uses_GB = SimUsesGB()
163 +    SIM_uses_EAM = SimUsesEAM()
164 +    SIM_requires_postpair_calc = SimRequiresPostpairCalc()
165 +    SIM_requires_prepair_calc = SimRequiresPrepairCalc()
166 +    SIM_uses_directional_atoms = SimUsesDirectionalAtoms()
167 +    SIM_uses_PBC = SimUsesPBC()
168 +    !SIM_uses_molecular_cutoffs = SimUsesMolecularCutoffs()
169 +
170 +    haveSIMvariables = .true.
171  
172 +    return
173 +  end subroutine setSimVariables
174 +
175 +  subroutine doReadyCheck(error)
176 +    integer, intent(out) :: error
177 +
178 +    integer :: myStatus
179 +
180 +    error = 0
181 +    
182 +    if (.not. havePropertyMap) then
183 +
184 +       myStatus = 0
185 +
186 +       call createPropertyMap(myStatus)
187 +
188 +       if (myStatus .ne. 0) then
189 +          write(default_error, *) 'createPropertyMap failed in do_Forces!'
190 +          error = -1
191 +          return
192 +       endif
193 +    endif
194 +
195 +    if (.not. haveSIMvariables) then
196 +       call setSimVariables()
197 +    endif
198 +
199 +    if (.not. haveRlist) then
200 +       write(default_error, *) 'rList has not been set in do_Forces!'
201 +       error = -1
202 +       return
203 +    endif
204 +
205 +    if (SIM_uses_LJ .and. FF_uses_LJ) then
206 +       if (.not. havePolicies) then
207 +          write(default_error, *) 'LJ mixing Policies have not been set in do_Forces!'
208 +          error = -1
209 +          return
210 +       endif
211 +    endif
212 +
213 +    if (.not. haveNeighborList) then
214 +       write(default_error, *) 'neighbor list has not been initialized in do_Forces!'
215 +       error = -1
216 +       return
217 +    end if
218 +
219 +    if (.not. haveSaneForceField) then
220 +       write(default_error, *) 'Force Field is not sane in do_Forces!'
221 +       error = -1
222 +       return
223 +    end if
224 +
225 + #ifdef IS_MPI
226 +    if (.not. isMPISimSet()) then
227 +       write(default_error,*) "ERROR: mpiSimulation has not been initialized!"
228 +       error = -1
229 +       return
230 +    endif
231 + #endif
232 +    return
233 +  end subroutine doReadyCheck
234 +    
235 +
236    subroutine init_FF(LJMIXPOLICY, use_RF_c, thisStat)
237  
238      integer, intent(in) :: LJMIXPOLICY
# Line 89 | Line 257 | contains
257    
258      FF_uses_LJ = .false.
259      FF_uses_sticky = .false.
260 +    FF_uses_charges = .false.
261      FF_uses_dipoles = .false.
262      FF_uses_GB = .false.
263      FF_uses_EAM = .false.
264      
265      call getMatchingElementList(atypes, "is_LJ", .true., nMatches, MatchList)
266      if (nMatches .gt. 0) FF_uses_LJ = .true.
267 <    
267 >
268 >    call getMatchingElementList(atypes, "is_Charge", .true., nMatches, MatchList)
269 >    if (nMatches .gt. 0) FF_uses_charges = .true.  
270 >
271      call getMatchingElementList(atypes, "is_DP", .true., nMatches, MatchList)
272      if (nMatches .gt. 0) FF_uses_dipoles = .true.
273      
# Line 109 | Line 281 | contains
281      call getMatchingElementList(atypes, "is_EAM", .true., nMatches, MatchList)
282      if (nMatches .gt. 0) FF_uses_EAM = .true.
283      
284 +    !! Assume sanity (for the sake of argument)
285 +    haveSaneForceField = .true.
286 +
287      !! check to make sure the FF_uses_RF setting makes sense
288      
289      if (FF_uses_dipoles) then
# Line 120 | Line 295 | contains
295         if (FF_uses_RF) then          
296            write(default_error,*) 'Using Reaction Field with no dipoles?  Huh?'
297            thisStat = -1
298 +          haveSaneForceField = .false.
299            return
300         endif
301      endif
# Line 134 | Line 310 | contains
310         case default
311            write(default_error,*) 'unknown LJ Mixing Policy!'
312            thisStat = -1
313 +          haveSaneForceField = .false.
314            return            
315         end select
316         if (my_status /= 0) then
317            thisStat = -1
318 +          haveSaneForceField = .false.
319            return
320         end if
321 +       havePolicies = .true.
322      endif
323  
324      if (FF_uses_sticky) then
325         call check_sticky_FF(my_status)
326         if (my_status /= 0) then
327            thisStat = -1
328 +          haveSaneForceField = .false.
329            return
330         end if
331      endif
# Line 154 | Line 334 | contains
334      if (FF_uses_EAM) then
335           call init_EAM_FF(my_status)
336         if (my_status /= 0) then
337 <          write(*,*) "init_EAM_FF returned a bad status"
337 >          write(default_error, *) "init_EAM_FF returned a bad status"
338            thisStat = -1
339 +          haveSaneForceField = .false.
340            return
341         end if
342      endif
343  
163
164    
344      if (FF_uses_GB) then
345         call check_gb_pair_FF(my_status)
346         if (my_status .ne. 0) then
347            thisStat = -1
348 +          haveSaneForceField = .false.
349            return
350         endif
351      endif
352  
353      if (FF_uses_GB .and. FF_uses_LJ) then
354      endif
355 <    if (.not. do_forces_initialized) then
355 >    if (.not. haveNeighborList) then
356         !! Create neighbor lists
357 <       call expandNeighborList(getNlocal(), my_status)
357 >       call expandNeighborList(nLocal, my_status)
358         if (my_Status /= 0) then
359            write(default_error,*) "SimSetup: ExpandNeighborList returned error."
360            thisStat = -1
361            return
362         endif
363 +       haveNeighborList = .true.
364      endif
184    
365  
366 <    havePolicies = .true.
367 <    if( haveRlist ) do_forces_initialized = .true.
188 <
366 >    
367 >    
368    end subroutine init_FF
369    
370  
371    !! Does force loop over i,j pairs. Calls do_pair to calculates forces.
372    !------------------------------------------------------------->
373 <  subroutine do_force_loop(q, A, u_l, f, t, tau, pot, do_pot_c, do_stress_c, &
374 <       error)
373 >  subroutine do_force_loop(q, q_group, A, u_l, f, t, tau, pot, &
374 >       do_pot_c, do_stress_c, error)
375      !! Position array provided by C, dimensioned by getNlocal
376 <    real ( kind = dp ), dimension(3,getNlocal()) :: q
377 <    !! Rotation Matrix for each long range particle in simulation.
378 <    real( kind = dp), dimension(9,getNlocal()) :: A    
379 <    !! Unit vectors for dipoles (lab frame)
380 <    real( kind = dp ), dimension(3,getNlocal()) :: u_l
376 >    real ( kind = dp ), dimension(3, nLocal) :: q
377 >    !! molecular center-of-mass position array
378 >    real ( kind = dp ), dimension(3, nGroups) :: q_group
379 >    !! Rotation Matrix for each long range particle in simulation.
380 >    real( kind = dp), dimension(9, nLocal) :: A    
381 >    !! Unit vectors for dipoles (lab frame)
382 >    real( kind = dp ), dimension(3,nLocal) :: u_l
383      !! Force array provided by C, dimensioned by getNlocal
384 <    real ( kind = dp ), dimension(3,getNlocal()) :: f
384 >    real ( kind = dp ), dimension(3,nLocal) :: f
385      !! Torsion array provided by C, dimensioned by getNlocal
386 <    real( kind = dp ), dimension(3,getNlocal()) :: t    
386 >    real( kind = dp ), dimension(3,nLocal) :: t    
387 >
388      !! Stress Tensor
389      real( kind = dp), dimension(9) :: tau  
390      real ( kind = dp ) :: pot
391      logical ( kind = 2) :: do_pot_c, do_stress_c
392      logical :: do_pot
393      logical :: do_stress
394 +    logical :: in_switching_region
395   #ifdef IS_MPI
396      real( kind = DP ) :: pot_local
397 <    integer :: nrow
398 <    integer :: ncol
397 >    integer :: nAtomsInRow
398 >    integer :: nAtomsInCol
399      integer :: nprocs
400 +    integer :: nGroupsInRow
401 +    integer :: nGroupsInCol
402   #endif
218    integer :: nlocal
403      integer :: natoms    
404      logical :: update_nlist  
405 <    integer :: i, j, jbeg, jend, jnab
405 >    integer :: i, j, jstart, jend, jnab
406 >    integer :: istart, iend
407 >    integer :: ia, jb, atom1, atom2
408      integer :: nlist
409 <    real( kind = DP ) ::  rijsq
410 <    real(kind=dp),dimension(3) :: d
409 >    real( kind = DP ) :: ratmsq, rgrpsq, rgrp, vpair, vij
410 >    real( kind = DP ) :: sw, dswdr, swderiv, mf
411 >    real(kind=dp),dimension(3) :: d_atm, d_grp, fpair, fij
412      real(kind=dp) :: rfpot, mu_i, virial
413 <    integer :: me_i
413 >    integer :: me_i, me_j, n_in_i, n_in_j
414      logical :: is_dp_i
415      integer :: neighborListSize
416      integer :: listerror, error
417      integer :: localError
418 +    integer :: propPack_i, propPack_j
419 +    integer :: loopStart, loopEnd, loop
420  
421      real(kind=dp) :: listSkin = 1.0  
422 <
422 >    
423      !! initialize local variables  
424 <
424 >    
425   #ifdef IS_MPI
426      pot_local = 0.0_dp
427 <    nlocal = getNlocal()
428 <    nrow   = getNrow(plan_row)
429 <    ncol   = getNcol(plan_col)
427 >    nAtomsInRow   = getNatomsInRow(plan_atom_row)
428 >    nAtomsInCol   = getNatomsInCol(plan_atom_col)
429 >    nGroupsInRow  = getNgroupsInRow(plan_group_row)
430 >    nGroupsInCol  = getNgroupsInCol(plan_group_col)
431   #else
242    nlocal = getNlocal()
432      natoms = nlocal
433   #endif
434 <
435 <    call check_initialization(localError)
434 >    
435 >    call doReadyCheck(localError)
436      if ( localError .ne. 0 ) then
437 <       call handleError("do_force_loop","Not Initialized")
437 >       call handleError("do_force_loop", "Not Initialized")
438         error = -1
439         return
440      end if
441      call zero_work_arrays()
442 <
442 >        
443      do_pot = do_pot_c
444      do_stress = do_stress_c
445 <
257 <
445 >    
446      ! Gather all information needed by all force loops:
447      
448   #ifdef IS_MPI    
449 +    
450 +    call gather(q, q_Row, plan_atom_row_3d)
451 +    call gather(q, q_Col, plan_atom_col_3d)
452  
453 <    call gather(q,q_Row,plan_row3d)
454 <    call gather(q,q_Col,plan_col3d)
453 >    call gather(q_group, q_group_Row, plan_group_row_3d)
454 >    call gather(q_group, q_group_Col, plan_group_col_3d)
455          
456 <    if (FF_UsesDirectionalAtoms() .and. SimUsesDirectionalAtoms()) then
457 <       call gather(u_l,u_l_Row,plan_row3d)
458 <       call gather(u_l,u_l_Col,plan_col3d)
456 >    if (FF_UsesDirectionalAtoms() .and. SIM_uses_directional_atoms) then
457 >       call gather(u_l, u_l_Row, plan_atom_row_3d)
458 >       call gather(u_l, u_l_Col, plan_atom_col_3d)
459        
460 <       call gather(A,A_Row,plan_row_rotation)
461 <       call gather(A,A_Col,plan_col_rotation)
460 >       call gather(A, A_Row, plan_atom_row_rotation)
461 >       call gather(A, A_Col, plan_atom_col_rotation)
462      endif
463      
464   #endif
465 <
466 < !! Begin force loop timing:
465 >    
466 >    !! Begin force loop timing:
467   #ifdef PROFILE
468      call cpu_time(forceTimeInitial)
469      nloops = nloops + 1
470   #endif
280  
281    if (FF_RequiresPrepairCalc() .and. SimRequiresPrepairCalc()) then
282       !! See if we need to update neighbor lists
283       call checkNeighborList(nlocal, q, listSkin, update_nlist)  
284       !! if_mpi_gather_stuff_for_prepair
285       !! do_prepair_loop_if_needed
286       !! if_mpi_scatter_stuff_from_prepair
287       !! if_mpi_gather_stuff_from_prepair_to_main_loop
288    
289 !--------------------PREFORCE LOOP----------->>>>>>>>>>>>>>>>>>>>>>>>>>>
290 #ifdef IS_MPI
471      
472 <    if (update_nlist) then
473 <      
474 <       !! save current configuration, construct neighbor list,
475 <       !! and calculate forces
476 <       call saveNeighborList(nlocal, q)
477 <      
298 <       neighborListSize = size(list)
299 <       nlist = 0      
300 <      
301 <       do i = 1, nrow
302 <          point(i) = nlist + 1
303 <          
304 <          prepair_inner: do j = 1, ncol
305 <            
306 <             if (skipThisPair(i,j)) cycle prepair_inner
307 <            
308 <             call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
309 <            
310 <             if (rijsq < rlistsq) then            
311 <                
312 <                nlist = nlist + 1
313 <                
314 <                if (nlist > neighborListSize) then
315 <                   call expandNeighborList(nlocal, listerror)
316 <                   if (listerror /= 0) then
317 <                      error = -1
318 <                      write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
319 <                      return
320 <                   end if
321 <                   neighborListSize = size(list)
322 <                endif
323 <                
324 <                list(nlist) = j
325 <                call do_prepair(i, j, rijsq, d, do_pot, do_stress, u_l, A, f, t, pot_local)                      
326 <             endif
327 <          enddo prepair_inner
328 <       enddo
472 >    loopEnd = PAIR_LOOP
473 >    if (FF_RequiresPrepairCalc() .and. SIM_requires_prepair_calc) then
474 >       loopStart = PREPAIR_LOOP
475 >    else
476 >       loopStart = PAIR_LOOP
477 >    endif
478  
479 <       point(nrow + 1) = nlist + 1
331 <      
332 <    else  !! (of update_check)
479 >    do loop = loopStart, loopEnd
480  
481 <       ! use the list to find the neighbors
482 <       do i = 1, nrow
483 <          JBEG = POINT(i)
484 <          JEND = POINT(i+1) - 1
485 <          ! check thiat molecule i has neighbors
486 <          if (jbeg .le. jend) then
487 <            
488 <             do jnab = jbeg, jend
489 <                j = list(jnab)
490 <
344 <                call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
345 <                call do_prepair(i, j, rijsq, d, do_pot, do_stress, &
346 <                     u_l, A, f, t, pot_local)
347 <
348 <             enddo
349 <          endif
350 <       enddo
351 <    endif
352 <    
481 >       ! See if we need to update neighbor lists
482 >       ! (but only on the first time through):
483 >       if (loop .eq. loopStart) then
484 >          call checkNeighborList(nGroups, q_group, listSkin, update_nlist)
485 >       endif
486 >      
487 >       if (update_nlist) then
488 >          !! save current configuration and construct neighbor list
489 > #ifdef IS_MPI
490 >          call saveNeighborList(nGroupsInRow, q_group)
491   #else
492 <    
493 <    if (update_nlist) then
492 >          call saveNeighborList(nGroups, q_group)
493 > #endif        
494 >          neighborListSize = size(list)
495 >          nlist = 0
496 >       endif
497        
498 <       ! save current configuration, contruct neighbor list,
499 <       ! and calculate forces
500 <       call saveNeighborList(natoms, q)
501 <      
502 <       neighborListSize = size(list)
503 <  
504 <       nlist = 0
364 <
365 <       do i = 1, natoms-1
366 <          point(i) = nlist + 1
498 >       istart = 1
499 > #ifdef IS_MPI
500 >       iend = nGroupsInRow
501 > #else
502 >       iend = nGroups - 1
503 > #endif
504 >       outer: do i = istart, iend
505            
506 <          prepair_inner: do j = i+1, natoms
507 <            
508 <             if (skipThisPair(i,j))  cycle prepair_inner
509 <                          
510 <             call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
373 <          
374 <
375 <             if (rijsq < rlistsq) then
376 <
377 <          
378 <                nlist = nlist + 1
379 <              
380 <                if (nlist > neighborListSize) then
381 <                   call expandNeighborList(natoms, listerror)
382 <                   if (listerror /= 0) then
383 <                      error = -1
384 <                      write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
385 <                      return
386 <                   end if
387 <                   neighborListSize = size(list)
388 <                endif
389 <                
390 <                list(nlist) = j
391 <                
392 <                call do_prepair(i, j, rijsq, d, do_pot, do_stress, &
393 <                        u_l, A, f, t, pot)
394 <                
395 <             endif
396 <          enddo prepair_inner
397 <       enddo
398 <      
399 <       point(natoms) = nlist + 1
400 <      
401 <    else !! (update)
402 <  
403 <       ! use the list to find the neighbors
404 <       do i = 1, natoms-1
405 <          JBEG = POINT(i)
406 <          JEND = POINT(i+1) - 1
407 <          ! check thiat molecule i has neighbors
408 <          if (jbeg .le. jend) then
409 <            
410 <             do jnab = jbeg, jend
411 <                j = list(jnab)
412 <
413 <                call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
414 <                call do_prepair(i, j, rijsq, d, do_pot, do_stress, &
415 <                     u_l, A, f, t, pot)
416 <
417 <             enddo
418 <          endif
419 <       enddo
420 <    endif    
421 < #endif
422 <    !! Do rest of preforce calculations
423 <    !! do necessary preforce calculations  
424 <    call do_preforce(nlocal,pot)
425 <   ! we have already updated the neighbor list set it to false...
426 <   update_nlist = .false.
427 <    else
428 <       !! See if we need to update neighbor lists for non pre-pair
429 <       call checkNeighborList(nlocal, q, listSkin, update_nlist)  
430 <    endif
431 <
432 <
433 <
434 <
435 <
436 < !---------------------------------MAIN Pair LOOP->>>>>>>>>>>>>>>>>>>>>>>>>>>>
437 <
438 <
439 <
440 <
441 <  
506 >          if (update_nlist) point(i) = nlist + 1
507 >          
508 >          n_in_i = groupStartRow(i+1) - groupStartRow(i)
509 >          
510 >          if (update_nlist) then
511   #ifdef IS_MPI
512 <    
513 <    if (update_nlist) then
514 <       !! save current configuration, construct neighbor list,
515 <       !! and calculate forces
516 <       call saveNeighborList(nlocal, q)
517 <      
518 <       neighborListSize = size(list)
519 <       nlist = 0      
520 <      
521 <       do i = 1, nrow
522 <          point(i) = nlist + 1
512 >             jstart = 1
513 >             jend = nGroupsInCol
514 > #else
515 >             jstart = i+1
516 >             jend = nGroups
517 > #endif
518 >          else            
519 >             jstart = point(i)
520 >             jend = point(i+1) - 1
521 >             ! make sure group i has neighbors
522 >             if (jstart .gt. jend) cycle outer
523 >          endif
524            
525 <          inner: do j = 1, ncol
526 <            
527 <             if (skipThisPair(i,j)) cycle inner
528 <            
529 <             call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
460 <            
461 <             if (rijsq < rlistsq) then            
462 <                
463 <                nlist = nlist + 1
464 <                
465 <                if (nlist > neighborListSize) then
466 <                   call expandNeighborList(nlocal, listerror)
467 <                   if (listerror /= 0) then
468 <                      error = -1
469 <                      write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
470 <                      return
471 <                   end if
472 <                   neighborListSize = size(list)
473 <                endif
474 <                
475 <                list(nlist) = j
476 <                                
477 <                call do_pair(i, j, rijsq, d, do_pot, do_stress, &
478 <                     u_l, A, f, t, pot_local)
479 <                
525 >          do jnab = jstart, jend
526 >             if (update_nlist) then
527 >                j = jnab
528 >             else
529 >                j = list(jnab)
530               endif
481          enddo inner
482       enddo
531  
532 <       point(nrow + 1) = nlist + 1
533 <      
534 <    else  !! (of update_check)
487 <
488 <       ! use the list to find the neighbors
489 <       do i = 1, nrow
490 <          JBEG = POINT(i)
491 <          JEND = POINT(i+1) - 1
492 <          ! check thiat molecule i has neighbors
493 <          if (jbeg .le. jend) then
494 <            
495 <             do jnab = jbeg, jend
496 <                j = list(jnab)
497 <
498 <                call get_interatomic_vector(q_Row(:,i), q_Col(:,j), d, rijsq)
499 <                call do_pair(i, j, rijsq, d, do_pot, do_stress, &
500 <                     u_l, A, f, t, pot_local)
501 <
502 <             enddo
503 <          endif
504 <       enddo
505 <    endif
506 <    
532 > #ifdef IS_MPI
533 >             call get_interatomic_vector(q_group_Row(:,i), &
534 >                  q_group_Col(:,j), d_grp, rgrpsq)
535   #else
536 <    
537 <    if (update_nlist) then
536 >             call get_interatomic_vector(q_group(:,i), &
537 >                  q_group(:,j), d_grp, rgrpsq)
538 > #endif
539  
540 <       ! save current configuration, contruct neighbor list,
541 <       ! and calculate forces
542 <       call saveNeighborList(natoms, q)
543 <      
544 <       neighborListSize = size(list)
545 <  
546 <       nlist = 0
547 <      
548 <       do i = 1, natoms-1
549 <          point(i) = nlist + 1
550 <          
551 <          inner: do j = i+1, natoms
552 <            
553 <             if (skipThisPair(i,j))  cycle inner
554 <                          
555 <             call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
556 <          
557 <
558 <             if (rijsq < rlistsq) then
540 >             if (rgrpsq < rlistsq) then
541 >                if (update_nlist) then
542 >                   nlist = nlist + 1
543 >                  
544 >                   if (nlist > neighborListSize) then
545 > #ifdef IS_MPI                
546 >                      call expandNeighborList(nGroupsInRow, listerror)
547 > #else
548 >                      call expandNeighborList(nGroups, listerror)
549 > #endif
550 >                      if (listerror /= 0) then
551 >                         error = -1
552 >                         write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
553 >                         return
554 >                      end if
555 >                      neighborListSize = size(list)
556 >                   endif
557 >                  
558 >                   list(nlist) = j
559 >                endif
560                  
561 <                nlist = nlist + 1
562 <              
563 <                if (nlist > neighborListSize) then
534 <                   call expandNeighborList(natoms, listerror)
535 <                   if (listerror /= 0) then
536 <                      error = -1
537 <                      write(DEFAULT_ERROR,*) "ERROR: nlist > list size and max allocations exceeded."
538 <                      return
539 <                   end if
540 <                   neighborListSize = size(list)
561 >                if (loop .eq. PAIR_LOOP) then
562 >                   vij = 0.0d0
563 >                   fij(1:3) = 0.0d0
564                  endif
565                  
566 <                list(nlist) = j
566 >                call get_switch(rgrpsq, sw, dswdr, rgrp, group_switch, &
567 >                     in_switching_region)
568                  
569 <                call do_pair(i, j, rijsq, d, do_pot, do_stress, &
546 <                        u_l, A, f, t, pot)
569 >                n_in_j = groupStartCol(j+1) - groupStartCol(j)
570                  
571 <             endif
572 <          enddo inner
573 <       enddo
571 >                do ia = groupStartRow(i), groupStartRow(i+1)-1
572 >                  
573 >                   atom1 = groupListRow(ia)
574 >                  
575 >                   inner: do jb = groupStartCol(j), groupStartCol(j+1)-1
576 >                      
577 >                      atom2 = groupListCol(jb)
578 >                      
579 >                      if (skipThisPair(atom1, atom2)) cycle inner
580 >                      
581 >                      if ((n_in_i .eq. 1).and.(n_in_j .eq. 1)) then
582 >                         d_atm(1:3) = d_grp(1:3)
583 >                         ratmsq = rgrpsq
584 >                      else
585 > #ifdef IS_MPI
586 >                         call get_interatomic_vector(q_Row(:,atom1), &
587 >                              q_Col(:,atom2), d_atm, ratmsq)
588 > #else
589 >                         call get_interatomic_vector(q(:,atom1), &
590 >                              q(:,atom2), d_atm, ratmsq)
591 > #endif
592 >                      endif
593 >                      if (loop .eq. PREPAIR_LOOP) then
594 > #ifdef IS_MPI                      
595 >                         call do_prepair(atom1, atom2, ratmsq, d_atm, sw, &
596 >                              rgrpsq, d_grp, do_pot, do_stress, &
597 >                              u_l, A, f, t, pot_local)
598 > #else
599 >                         call do_prepair(atom1, atom2, ratmsq, d_atm, sw, &
600 >                              rgrpsq, d_grp, do_pot, do_stress, &
601 >                              u_l, A, f, t, pot)
602 > #endif                                              
603 >                      else
604 > #ifdef IS_MPI                      
605 >                         call do_pair(atom1, atom2, ratmsq, d_atm, sw, &
606 >                              do_pot, &
607 >                              u_l, A, f, t, pot_local, vpair, fpair)
608 > #else
609 >                         call do_pair(atom1, atom2, ratmsq, d_atm, sw, &
610 >                              do_pot,  &
611 >                              u_l, A, f, t, pot, vpair, fpair)
612 > #endif
613 >                         vij = vij + vpair
614 >                         fij(1:3) = fij(1:3) + fpair(1:3)
615 >                      endif
616 >                   enddo inner
617 >                enddo
618 >                
619 >                if (loop .eq. PAIR_LOOP) then
620 >                   if (in_switching_region) then
621 >                      swderiv = vij*dswdr/rgrp
622 >                      fij(1) = fij(1) + swderiv*d_grp(1)
623 >                      fij(2) = fij(2) + swderiv*d_grp(2)
624 >                      fij(3) = fij(3) + swderiv*d_grp(3)
625 >                      
626 >                      do ia=groupStartRow(i), groupStartRow(i+1)-1
627 >                         atom1=groupListRow(ia)
628 >                         mf = mfactRow(atom1)
629 > #ifdef IS_MPI
630 >                         f_Row(1,atom1) = f_Row(1,atom1) + swderiv*d_grp(1)*mf
631 >                         f_Row(2,atom1) = f_Row(2,atom1) + swderiv*d_grp(2)*mf
632 >                         f_Row(3,atom1) = f_Row(3,atom1) + swderiv*d_grp(3)*mf
633 > #else
634 >                         f(1,atom1) = f(1,atom1) + swderiv*d_grp(1)*mf
635 >                         f(2,atom1) = f(2,atom1) + swderiv*d_grp(2)*mf
636 >                         f(3,atom1) = f(3,atom1) + swderiv*d_grp(3)*mf
637 > #endif
638 >                      enddo
639 >                      
640 >                      do jb=groupStartCol(j), groupStartCol(j+1)-1
641 >                         atom2=groupListCol(jb)
642 >                         mf = mfactCol(atom2)
643 > #ifdef IS_MPI
644 >                         f_Col(1,atom2) = f_Col(1,atom2) - swderiv*d_grp(1)*mf
645 >                         f_Col(2,atom2) = f_Col(2,atom2) - swderiv*d_grp(2)*mf
646 >                         f_Col(3,atom2) = f_Col(3,atom2) - swderiv*d_grp(3)*mf
647 > #else
648 >                         f(1,atom2) = f(1,atom2) - swderiv*d_grp(1)*mf
649 >                         f(2,atom2) = f(2,atom2) - swderiv*d_grp(2)*mf
650 >                         f(3,atom2) = f(3,atom2) - swderiv*d_grp(3)*mf
651 > #endif
652 >                      enddo
653 >                   endif
654 >                  
655 >                   if (do_stress) call add_stress_tensor(d_grp, fij)
656 >                endif
657 >             end if
658 >          enddo
659 >       enddo outer
660        
661 <       point(natoms) = nlist + 1
662 <      
663 <    else !! (update)
664 <      
665 <       ! use the list to find the neighbors
666 <       do i = 1, natoms-1
667 <          JBEG = POINT(i)
668 <          JEND = POINT(i+1) - 1
669 <          ! check thiat molecule i has neighbors
670 <          if (jbeg .le. jend) then
671 <            
563 <             do jnab = jbeg, jend
564 <                j = list(jnab)
565 <
566 <                call get_interatomic_vector(q(:,i), q(:,j), d, rijsq)
567 <                call do_pair(i, j, rijsq, d, do_pot, do_stress, &
568 <                     u_l, A, f, t, pot)
569 <
570 <             enddo
661 >       if (update_nlist) then
662 > #ifdef IS_MPI
663 >          point(nGroupsInRow + 1) = nlist + 1
664 > #else
665 >          point(nGroups) = nlist + 1
666 > #endif
667 >          if (loop .eq. PREPAIR_LOOP) then
668 >             ! we just did the neighbor list update on the first
669 >             ! pass, so we don't need to do it
670 >             ! again on the second pass
671 >             update_nlist = .false.                              
672            endif
673 <       enddo
674 <    endif
673 >       endif
674 >            
675 >       if (loop .eq. PREPAIR_LOOP) then
676 >          call do_preforce(nlocal, pot)
677 >       endif
678 >      
679 >    enddo
680      
681 < #endif
576 <    
577 <    ! phew, done with main loop.
578 <
579 < !! Do timing
681 >    !! Do timing
682   #ifdef PROFILE
683      call cpu_time(forceTimeFinal)
684      forceTime = forceTime + forceTimeFinal - forceTimeInitial
685 < #endif
686 <
585 <
685 > #endif    
686 >    
687   #ifdef IS_MPI
688      !!distribute forces
689 <  
689 >    
690      f_temp = 0.0_dp
691 <    call scatter(f_Row,f_temp,plan_row3d)
691 >    call scatter(f_Row,f_temp,plan_atom_row_3d)
692      do i = 1,nlocal
693         f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
694      end do
695 <
695 >    
696      f_temp = 0.0_dp
697 <    call scatter(f_Col,f_temp,plan_col3d)
697 >    call scatter(f_Col,f_temp,plan_atom_col_3d)
698      do i = 1,nlocal
699         f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
700      end do
701      
702 <    if (FF_UsesDirectionalAtoms() .and. SimUsesDirectionalAtoms()) then
702 >    if (FF_UsesDirectionalAtoms() .and. SIM_uses_directional_atoms) then
703         t_temp = 0.0_dp
704 <       call scatter(t_Row,t_temp,plan_row3d)
704 >       call scatter(t_Row,t_temp,plan_atom_row_3d)
705         do i = 1,nlocal
706            t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
707         end do
708         t_temp = 0.0_dp
709 <       call scatter(t_Col,t_temp,plan_col3d)
709 >       call scatter(t_Col,t_temp,plan_atom_col_3d)
710        
711         do i = 1,nlocal
712            t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
# Line 614 | Line 715 | contains
715      
716      if (do_pot) then
717         ! scatter/gather pot_row into the members of my column
718 <       call scatter(pot_Row, pot_Temp, plan_row)
719 <
718 >       call scatter(pot_Row, pot_Temp, plan_atom_row)
719 >      
720         ! scatter/gather pot_local into all other procs
721         ! add resultant to get total pot
722         do i = 1, nlocal
# Line 623 | Line 724 | contains
724         enddo
725        
726         pot_Temp = 0.0_DP
727 <
728 <       call scatter(pot_Col, pot_Temp, plan_col)
727 >      
728 >       call scatter(pot_Col, pot_Temp, plan_atom_col)
729         do i = 1, nlocal
730            pot_local = pot_local + pot_Temp(i)
731         enddo
732 <
733 <    endif    
732 >      
733 >    endif
734   #endif
735 <
736 <    if (FF_RequiresPostpairCalc() .and. SimRequiresPostpairCalc()) then
735 >    
736 >    if (FF_RequiresPostpairCalc() .and. SIM_requires_postpair_calc) then
737        
738 <       if (FF_uses_RF .and. SimUsesRF()) then
738 >       if (FF_uses_RF .and. SIM_uses_RF) then
739            
740   #ifdef IS_MPI
741 <          call scatter(rf_Row,rf,plan_row3d)
742 <          call scatter(rf_Col,rf_Temp,plan_col3d)
741 >          call scatter(rf_Row,rf,plan_atom_row_3d)
742 >          call scatter(rf_Col,rf_Temp,plan_atom_col_3d)
743            do i = 1,nlocal
744               rf(1:3,i) = rf(1:3,i) + rf_Temp(1:3,i)
745            end do
746   #endif
747            
748 <          do i = 1, getNlocal()
749 <
748 >          do i = 1, nLocal
749 >            
750               rfpot = 0.0_DP
751   #ifdef IS_MPI
752               me_i = atid_row(i)
753   #else
754               me_i = atid(i)
755   #endif
756 <             call getElementProperty(atypes, me_i, "is_DP", is_DP_i)      
757 <             if ( is_DP_i ) then
758 <                call getElementProperty(atypes, me_i, "dipole_moment", mu_i)
756 >            
757 >             if (PropertyMap(me_i)%is_DP) then
758 >                
759 >                mu_i = PropertyMap(me_i)%dipole_moment
760 >                
761                  !! The reaction field needs to include a self contribution
762                  !! to the field:
763 <                call accumulate_self_rf(i, mu_i, u_l)            
763 >                call accumulate_self_rf(i, mu_i, u_l)
764                  !! Get the reaction field contribution to the
765                  !! potential and torques:
766                  call reaction_field_final(i, mu_i, u_l, rfpot, t, do_pot)
# Line 671 | Line 774 | contains
774            enddo
775         endif
776      endif
777 <
778 <
777 >    
778 >    
779   #ifdef IS_MPI
780 <
780 >    
781      if (do_pot) then
782         pot = pot + pot_local
783         !! we assume the c code will do the allreduce to get the total potential
784         !! we could do it right here if we needed to...
785      endif
786 <
786 >    
787      if (do_stress) then
788 <      call mpi_allreduce(tau_Temp, tau, 9,mpi_double_precision,mpi_sum, &
788 >       call mpi_allreduce(tau_Temp, tau, 9,mpi_double_precision,mpi_sum, &
789              mpi_comm_world,mpi_err)
790         call mpi_allreduce(virial_Temp, virial,1,mpi_double_precision,mpi_sum, &
791              mpi_comm_world,mpi_err)
792      endif
793 <
793 >    
794   #else
795 <
795 >    
796      if (do_stress) then
797         tau = tau_Temp
798         virial = virial_Temp
799      endif
800      
801   #endif
802 <    
700 <    
701 <    
802 >      
803    end subroutine do_force_loop
804 +  
805 +  subroutine do_pair(i, j, rijsq, d, sw, do_pot, &
806 +       u_l, A, f, t, pot, vpair, fpair)
807  
808 <  subroutine do_pair(i, j, rijsq, d, do_pot, do_stress, u_l, A, f, t, pot)
808 >    real( kind = dp ) :: pot, vpair, sw
809 >    real( kind = dp ), dimension(3) :: fpair
810 >    real( kind = dp ), dimension(nLocal)   :: mfact
811 >    real( kind = dp ), dimension(3,nLocal) :: u_l
812 >    real( kind = dp ), dimension(9,nLocal) :: A
813 >    real( kind = dp ), dimension(3,nLocal) :: f
814 >    real( kind = dp ), dimension(3,nLocal) :: t
815  
816 <    real( kind = dp ) :: pot
707 <    real( kind = dp ), dimension(3,getNlocal()) :: u_l
708 <    real (kind=dp), dimension(9,getNlocal()) :: A
709 <    real (kind=dp), dimension(3,getNlocal()) :: f
710 <    real (kind=dp), dimension(3,getNlocal()) :: t
711 <
712 <    logical, intent(inout) :: do_pot, do_stress
816 >    logical, intent(inout) :: do_pot
817      integer, intent(in) :: i, j
818 <    real ( kind = dp ), intent(inout)    :: rijsq
818 >    real ( kind = dp ), intent(inout) :: rijsq
819      real ( kind = dp )                :: r
820      real ( kind = dp ), intent(inout) :: d(3)
717    logical :: is_LJ_i, is_LJ_j
718    logical :: is_DP_i, is_DP_j
719    logical :: is_GB_i, is_GB_j
720    logical :: is_EAM_i,is_EAM_j
721    logical :: is_Sticky_i, is_Sticky_j
821      integer :: me_i, me_j
822  
823      r = sqrt(rijsq)
824 +    vpair = 0.0d0
825 +    fpair(1:3) = 0.0d0
826  
827   #ifdef IS_MPI
828 <    if (tagRow(i) .eq. tagColumn(j)) then
829 <       write(0,*) 'do_pair is doing', i , j, tagRow(i), tagColumn(j)
828 >    if (AtomRowToGlobal(i) .eq. AtomColToGlobal(j)) then
829 >       write(0,*) 'do_pair is doing', i , j, AtomRowToGlobal(i), AtomColToGlobal(j)
830      endif
730
831      me_i = atid_row(i)
832      me_j = atid_col(j)
733
833   #else
735
834      me_i = atid(i)
835      me_j = atid(j)
738
836   #endif
837 +    
838 +    if (FF_uses_LJ .and. SIM_uses_LJ) then
839 +      
840 +       if ( PropertyMap(me_i)%is_LJ .and. PropertyMap(me_j)%is_LJ ) then
841 +          !write(*,*) 'calling lj with'
842 +          !write(*,*) i, j, r, rijsq
843 +          !write(*,'(3es12.3)') d(1), d(2), d(3)
844 +          !write(*,'(3es12.3)') sw, vpair, pot
845 +          !write(*,*)
846  
847 <    if (FF_uses_LJ .and. SimUsesLJ()) then
848 <       call getElementProperty(atypes, me_i, "is_LJ", is_LJ_i)
849 <       call getElementProperty(atypes, me_j, "is_LJ", is_LJ_j)
744 <
745 <       if ( is_LJ_i .and. is_LJ_j ) &
746 <            call do_lj_pair(i, j, d, r, rijsq, pot, f, do_pot, do_stress)
847 >          call do_lj_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot)
848 >       endif
849 >      
850      endif
851 <
852 <    if (FF_uses_dipoles .and. SimUsesDipoles()) then
750 <       call getElementProperty(atypes, me_i, "is_DP", is_DP_i)
751 <       call getElementProperty(atypes, me_j, "is_DP", is_DP_j)
851 >    
852 >    if (FF_uses_charges .and. SIM_uses_charges) then
853        
854 <       if ( is_DP_i .and. is_DP_j ) then
855 <          call do_dipole_pair(i, j, d, r, rijsq, pot, u_l, f, t, &
755 <               do_pot, do_stress)
756 <          if (FF_uses_RF .and. SimUsesRF()) then
757 <             call accumulate_rf(i, j, r, u_l)
758 <             call rf_correct_forces(i, j, d, r, u_l, f, do_stress)
759 <          endif
760 <          
854 >       if (PropertyMap(me_i)%is_Charge .and. PropertyMap(me_j)%is_Charge) then
855 >          call do_charge_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot)
856         endif
857 +      
858      endif
859 +    
860 +    if (FF_uses_dipoles .and. SIM_uses_dipoles) then
861 +      
862 +       if ( PropertyMap(me_i)%is_DP .and. PropertyMap(me_j)%is_DP) then
863 +          call do_dipole_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, u_l, f, t, &
864 +               do_pot)
865 +          if (FF_uses_RF .and. SIM_uses_RF) then
866 +             call accumulate_rf(i, j, r, u_l, sw)
867 +             call rf_correct_forces(i, j, d, r, u_l, sw, f, fpair)
868 +          endif          
869 +       endif
870  
871 <    if (FF_uses_Sticky .and. SimUsesSticky()) then
871 >    endif
872  
873 <       call getElementProperty(atypes, me_i, "is_Sticky", is_Sticky_i)
767 <       call getElementProperty(atypes, me_j, "is_Sticky", is_Sticky_j)
873 >    if (FF_uses_Sticky .and. SIM_uses_sticky) then
874  
875 <       if ( is_Sticky_i .and. is_Sticky_j ) then
876 <          call do_sticky_pair(i, j, d, r, rijsq, A, pot, f, t, &
877 <               do_pot, do_stress)
875 >       if ( PropertyMap(me_i)%is_Sticky .and. PropertyMap(me_j)%is_Sticky) then
876 >          call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, A, f, t, &
877 >               do_pot)
878         endif
879 +
880      endif
881  
882  
883 <    if (FF_uses_GB .and. SimUsesGB()) then
883 >    if (FF_uses_GB .and. SIM_uses_GB) then
884 >      
885 >       if ( PropertyMap(me_i)%is_GB .and. PropertyMap(me_j)%is_GB) then
886 >          call do_gb_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, u_l, f, t, &
887 >               do_pot)
888 >       endif
889  
890 <
779 <       call getElementProperty(atypes, me_i, "is_GB", is_GB_i)
780 <       call getElementProperty(atypes, me_j, "is_GB", is_GB_j)
890 >    endif
891        
892 <       if ( is_GB_i .and. is_GB_j ) then
893 <          call do_gb_pair(i, j, d, r, rijsq, u_l, pot, f, t, &
894 <               do_pot, do_stress)          
892 >    if (FF_uses_EAM .and. SIM_uses_EAM) then
893 >      
894 >       if ( PropertyMap(me_i)%is_EAM .and. PropertyMap(me_j)%is_EAM) then
895 >          call do_eam_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, &
896 >               do_pot)
897         endif
898 +      
899      endif
900 <    
788 <
789 <  
790 <   if (FF_uses_EAM .and. SimUsesEAM()) then
791 <      call getElementProperty(atypes, me_i, "is_EAM", is_EAM_i)
792 <      call getElementProperty(atypes, me_j, "is_EAM", is_EAM_j)
793 <      
794 <      if ( is_EAM_i .and. is_EAM_j ) &
795 <           call do_eam_pair(i, j, d, r, rijsq, pot, f, do_pot, do_stress)
796 <   endif
797 <
798 <
799 <
800 <
900 >    
901    end subroutine do_pair
902  
903 +  subroutine do_prepair(i, j, rijsq, d, sw, rcijsq, dc, &
904 +       do_pot, do_stress, u_l, A, f, t, pot)
905  
906 <
907 <  subroutine do_prepair(i, j, rijsq, d, do_pot, do_stress, u_l, A, f, t, pot)
908 <   real( kind = dp ) :: pot
909 <   real( kind = dp ), dimension(3,getNlocal()) :: u_l
910 <   real (kind=dp), dimension(9,getNlocal()) :: A
809 <   real (kind=dp), dimension(3,getNlocal()) :: f
810 <   real (kind=dp), dimension(3,getNlocal()) :: t
906 >   real( kind = dp ) :: pot, sw
907 >   real( kind = dp ), dimension(3,nLocal) :: u_l
908 >   real (kind=dp), dimension(9,nLocal) :: A
909 >   real (kind=dp), dimension(3,nLocal) :: f
910 >   real (kind=dp), dimension(3,nLocal) :: t
911    
912     logical, intent(inout) :: do_pot, do_stress
913     integer, intent(in) :: i, j
914 <   real ( kind = dp ), intent(inout)    :: rijsq
915 <   real ( kind = dp )                :: r
916 <   real ( kind = dp ), intent(inout) :: d(3)
914 >   real ( kind = dp ), intent(inout)    :: rijsq, rcijsq
915 >   real ( kind = dp )                :: r, rc
916 >   real ( kind = dp ), intent(inout) :: d(3), dc(3)
917    
918     logical :: is_EAM_i, is_EAM_j
919    
920     integer :: me_i, me_j
921    
922 <   r = sqrt(rijsq)
922 >
923 >    r = sqrt(rijsq)
924 >    if (SIM_uses_molecular_cutoffs) then
925 >       rc = sqrt(rcijsq)
926 >    else
927 >       rc = r
928 >    endif
929    
930  
931   #ifdef IS_MPI
932 <   if (tagRow(i) .eq. tagColumn(j)) then
933 <      write(0,*) 'do_pair is doing', i , j, tagRow(i), tagColumn(j)
932 >   if (AtomRowToGlobal(i) .eq. AtomColToGlobal(j)) then
933 >      write(0,*) 'do_prepair is doing', i , j, AtomRowToGlobal(i), AtomColToGlobal(j)
934     endif
935    
936     me_i = atid_row(i)
# Line 836 | Line 942 | contains
942     me_j = atid(j)
943    
944   #endif
945 <    
946 <   if (FF_uses_EAM .and. SimUsesEAM()) then
841 <      call getElementProperty(atypes, me_i, "is_EAM", is_EAM_i)
842 <      call getElementProperty(atypes, me_j, "is_EAM", is_EAM_j)
945 >  
946 >   if (FF_uses_EAM .and. SIM_uses_EAM) then
947        
948 <      if ( is_EAM_i .and. is_EAM_j ) &
948 >      if (PropertyMap(me_i)%is_EAM .and. PropertyMap(me_j)%is_EAM) &
949             call calc_EAM_prepair_rho(i, j, d, r, rijsq )
950 +      
951     endif
952 <
952 >  
953   end subroutine do_prepair
849
850
851
852
853  subroutine do_preforce(nlocal,pot)
854    integer :: nlocal
855    real( kind = dp ) :: pot
856
857    if (FF_uses_EAM .and. SimUsesEAM()) then
858       call calc_EAM_preforce_Frho(nlocal,pot)
859    endif
860
861
862  end subroutine do_preforce
863  
864  
865  subroutine get_interatomic_vector(q_i, q_j, d, r_sq)
866    
867    real (kind = dp), dimension(3) :: q_i
868    real (kind = dp), dimension(3) :: q_j
869    real ( kind = dp ), intent(out) :: r_sq
870    real( kind = dp ) :: d(3), scaled(3)
871    integer i
872
873    d(1:3) = q_j(1:3) - q_i(1:3)
874
875    ! Wrap back into periodic box if necessary
876    if ( SimUsesPBC() ) then
877      
878       if( .not.boxIsOrthorhombic ) then
879          ! calc the scaled coordinates.
880          
881          scaled = matmul(HmatInv, d)
882          
883          ! wrap the scaled coordinates
884
885          scaled = scaled  - anint(scaled)
886          
887
888          ! calc the wrapped real coordinates from the wrapped scaled
889          ! coordinates
890
891          d = matmul(Hmat,scaled)
892
893       else
894          ! calc the scaled coordinates.
895          
896          do i = 1, 3
897             scaled(i) = d(i) * HmatInv(i,i)
898            
899             ! wrap the scaled coordinates
900            
901             scaled(i) = scaled(i) - anint(scaled(i))
902            
903             ! calc the wrapped real coordinates from the wrapped scaled
904             ! coordinates
905
906             d(i) = scaled(i)*Hmat(i,i)
907          enddo
908       endif
909      
910    endif
911    
912    r_sq = dot_product(d,d)
913    
914  end subroutine get_interatomic_vector
915  
916  subroutine check_initialization(error)
917    integer, intent(out) :: error
918    
919    error = 0
920    ! Make sure we are properly initialized.
921    if (.not. do_forces_initialized) then
922       write(*,*) "Forces not initialized"
923       error = -1
924       return
925    endif
926
927 #ifdef IS_MPI
928    if (.not. isMPISimSet()) then
929       write(default_error,*) "ERROR: mpiSimulation has not been initialized!"
930       error = -1
931       return
932    endif
933 #endif
934    
935    return
936  end subroutine check_initialization
937
938  
939  subroutine zero_work_arrays()
940    
941 #ifdef IS_MPI
942
943    q_Row = 0.0_dp
944    q_Col = 0.0_dp  
945    
946    u_l_Row = 0.0_dp
947    u_l_Col = 0.0_dp
948    
949    A_Row = 0.0_dp
950    A_Col = 0.0_dp
951    
952    f_Row = 0.0_dp
953    f_Col = 0.0_dp
954    f_Temp = 0.0_dp
955      
956    t_Row = 0.0_dp
957    t_Col = 0.0_dp
958    t_Temp = 0.0_dp
954  
955 <    pot_Row = 0.0_dp
956 <    pot_Col = 0.0_dp
957 <    pot_Temp = 0.0_dp
958 <
959 <    rf_Row = 0.0_dp
960 <    rf_Col = 0.0_dp
961 <    rf_Temp = 0.0_dp
955 >
956 > subroutine do_preforce(nlocal,pot)
957 >   integer :: nlocal
958 >   real( kind = dp ) :: pot
959 >  
960 >   if (FF_uses_EAM .and. SIM_uses_EAM) then
961 >      call calc_EAM_preforce_Frho(nlocal,pot)
962 >   endif
963 >  
964 >  
965 > end subroutine do_preforce
966 >
967 >
968 > subroutine get_interatomic_vector(q_i, q_j, d, r_sq)
969 >  
970 >   real (kind = dp), dimension(3) :: q_i
971 >   real (kind = dp), dimension(3) :: q_j
972 >   real ( kind = dp ), intent(out) :: r_sq
973 >   real( kind = dp ) :: d(3), scaled(3)
974 >   integer i
975 >  
976 >   d(1:3) = q_j(1:3) - q_i(1:3)
977 >  
978 >   ! Wrap back into periodic box if necessary
979 >   if ( SIM_uses_PBC ) then
980 >      
981 >      if( .not.boxIsOrthorhombic ) then
982 >         ! calc the scaled coordinates.
983 >        
984 >         scaled = matmul(HmatInv, d)
985 >        
986 >         ! wrap the scaled coordinates
987 >        
988 >         scaled = scaled  - anint(scaled)
989 >        
990 >        
991 >         ! calc the wrapped real coordinates from the wrapped scaled
992 >         ! coordinates
993 >        
994 >         d = matmul(Hmat,scaled)
995 >        
996 >      else
997 >         ! calc the scaled coordinates.
998 >        
999 >         do i = 1, 3
1000 >            scaled(i) = d(i) * HmatInv(i,i)
1001 >            
1002 >            ! wrap the scaled coordinates
1003 >            
1004 >            scaled(i) = scaled(i) - anint(scaled(i))
1005 >            
1006 >            ! calc the wrapped real coordinates from the wrapped scaled
1007 >            ! coordinates
1008 >            
1009 >            d(i) = scaled(i)*Hmat(i,i)
1010 >         enddo
1011 >      endif
1012 >      
1013 >   endif
1014 >  
1015 >   r_sq = dot_product(d,d)
1016 >  
1017 > end subroutine get_interatomic_vector
1018 >
1019 > subroutine zero_work_arrays()
1020 >  
1021 > #ifdef IS_MPI
1022 >  
1023 >   q_Row = 0.0_dp
1024 >   q_Col = 0.0_dp
1025  
1026 +   q_group_Row = 0.0_dp
1027 +   q_group_Col = 0.0_dp  
1028 +  
1029 +   u_l_Row = 0.0_dp
1030 +   u_l_Col = 0.0_dp
1031 +  
1032 +   A_Row = 0.0_dp
1033 +   A_Col = 0.0_dp
1034 +  
1035 +   f_Row = 0.0_dp
1036 +   f_Col = 0.0_dp
1037 +   f_Temp = 0.0_dp
1038 +  
1039 +   t_Row = 0.0_dp
1040 +   t_Col = 0.0_dp
1041 +   t_Temp = 0.0_dp
1042 +  
1043 +   pot_Row = 0.0_dp
1044 +   pot_Col = 0.0_dp
1045 +   pot_Temp = 0.0_dp
1046 +  
1047 +   rf_Row = 0.0_dp
1048 +   rf_Col = 0.0_dp
1049 +   rf_Temp = 0.0_dp
1050 +  
1051   #endif
969
1052  
1053 <    if (FF_uses_EAM .and. SimUsesEAM()) then
1054 <       call clean_EAM()
1055 <    endif
1056 <
1057 <
1058 <
1059 <
1060 <
1061 <    rf = 0.0_dp
1062 <    tau_Temp = 0.0_dp
1063 <    virial_Temp = 0.0_dp
1064 <  end subroutine zero_work_arrays
1065 <  
1066 <  function skipThisPair(atom1, atom2) result(skip_it)
1067 <    integer, intent(in) :: atom1
1068 <    integer, intent(in), optional :: atom2
1069 <    logical :: skip_it
1070 <    integer :: unique_id_1, unique_id_2
1071 <    integer :: me_i,me_j
1072 <    integer :: i
1073 <
1074 <    skip_it = .false.
1075 <    
1076 <    !! there are a number of reasons to skip a pair or a particle
1077 <    !! mostly we do this to exclude atoms who are involved in short
996 <    !! range interactions (bonds, bends, torsions), but we also need
997 <    !! to exclude some overcounted interactions that result from
998 <    !! the parallel decomposition
999 <    
1053 >   if (FF_uses_EAM .and. SIM_uses_EAM) then
1054 >      call clean_EAM()
1055 >   endif
1056 >  
1057 >   rf = 0.0_dp
1058 >   tau_Temp = 0.0_dp
1059 >   virial_Temp = 0.0_dp
1060 > end subroutine zero_work_arrays
1061 >
1062 > function skipThisPair(atom1, atom2) result(skip_it)
1063 >   integer, intent(in) :: atom1
1064 >   integer, intent(in), optional :: atom2
1065 >   logical :: skip_it
1066 >   integer :: unique_id_1, unique_id_2
1067 >   integer :: me_i,me_j
1068 >   integer :: i
1069 >  
1070 >   skip_it = .false.
1071 >  
1072 >   !! there are a number of reasons to skip a pair or a particle
1073 >   !! mostly we do this to exclude atoms who are involved in short
1074 >   !! range interactions (bonds, bends, torsions), but we also need
1075 >   !! to exclude some overcounted interactions that result from
1076 >   !! the parallel decomposition
1077 >  
1078   #ifdef IS_MPI
1079 <    !! in MPI, we have to look up the unique IDs for each atom
1080 <    unique_id_1 = tagRow(atom1)
1079 >   !! in MPI, we have to look up the unique IDs for each atom
1080 >   unique_id_1 = AtomRowToGlobal(atom1)
1081   #else
1082 <    !! in the normal loop, the atom numbers are unique
1083 <    unique_id_1 = atom1
1082 >   !! in the normal loop, the atom numbers are unique
1083 >   unique_id_1 = atom1
1084   #endif
1085 <
1086 <    !! We were called with only one atom, so just check the global exclude
1087 <    !! list for this atom
1088 <    if (.not. present(atom2)) then
1089 <       do i = 1, nExcludes_global
1090 <          if (excludesGlobal(i) == unique_id_1) then
1091 <             skip_it = .true.
1092 <             return
1093 <          end if
1094 <       end do
1095 <       return
1096 <    end if
1097 <    
1085 >  
1086 >   !! We were called with only one atom, so just check the global exclude
1087 >   !! list for this atom
1088 >   if (.not. present(atom2)) then
1089 >      do i = 1, nExcludes_global
1090 >         if (excludesGlobal(i) == unique_id_1) then
1091 >            skip_it = .true.
1092 >            return
1093 >         end if
1094 >      end do
1095 >      return
1096 >   end if
1097 >  
1098   #ifdef IS_MPI
1099 <    unique_id_2 = tagColumn(atom2)
1099 >   unique_id_2 = AtomColToGlobal(atom2)
1100   #else
1101 <    unique_id_2 = atom2
1101 >   unique_id_2 = atom2
1102   #endif
1103 <
1103 >  
1104   #ifdef IS_MPI
1105 <    !! this situation should only arise in MPI simulations
1106 <    if (unique_id_1 == unique_id_2) then
1107 <       skip_it = .true.
1108 <       return
1109 <    end if
1110 <    
1111 <    !! this prevents us from doing the pair on multiple processors
1112 <    if (unique_id_1 < unique_id_2) then
1113 <       if (mod(unique_id_1 + unique_id_2,2) == 0) then
1114 <          skip_it = .true.
1115 <          return
1116 <       endif
1117 <    else                
1118 <       if (mod(unique_id_1 + unique_id_2,2) == 1) then
1119 <          skip_it = .true.
1120 <          return
1121 <       endif
1122 <    endif
1105 >   !! this situation should only arise in MPI simulations
1106 >   if (unique_id_1 == unique_id_2) then
1107 >      skip_it = .true.
1108 >      return
1109 >   end if
1110 >  
1111 >   !! this prevents us from doing the pair on multiple processors
1112 >   if (unique_id_1 < unique_id_2) then
1113 >      if (mod(unique_id_1 + unique_id_2,2) == 0) then
1114 >         skip_it = .true.
1115 >         return
1116 >      endif
1117 >   else                
1118 >      if (mod(unique_id_1 + unique_id_2,2) == 1) then
1119 >         skip_it = .true.
1120 >         return
1121 >      endif
1122 >   endif
1123   #endif
1124 +  
1125 +   !! the rest of these situations can happen in all simulations:
1126 +   do i = 1, nExcludes_global      
1127 +      if ((excludesGlobal(i) == unique_id_1) .or. &
1128 +           (excludesGlobal(i) == unique_id_2)) then
1129 +         skip_it = .true.
1130 +         return
1131 +      endif
1132 +   enddo
1133 +  
1134 +   do i = 1, nSkipsForAtom(atom1)
1135 +      if (skipsForAtom(atom1, i) .eq. unique_id_2) then
1136 +         skip_it = .true.
1137 +         return
1138 +      endif
1139 +   end do
1140 +  
1141 +   return
1142 + end function skipThisPair
1143  
1144 <    !! the rest of these situations can happen in all simulations:
1145 <    do i = 1, nExcludes_global      
1146 <       if ((excludesGlobal(i) == unique_id_1) .or. &
1147 <            (excludesGlobal(i) == unique_id_2)) then
1148 <          skip_it = .true.
1149 <          return
1150 <       endif
1151 <    enddo
1152 <
1153 <    do i = 1, nExcludes_local
1154 <       if (excludesLocal(1,i) == unique_id_1) then
1155 <          if (excludesLocal(2,i) == unique_id_2) then
1156 <             skip_it = .true.
1157 <             return
1158 <          endif
1159 <       else
1063 <          if (excludesLocal(1,i) == unique_id_2) then
1064 <             if (excludesLocal(2,i) == unique_id_1) then
1065 <                skip_it = .true.
1066 <                return
1067 <             endif
1068 <          endif
1069 <       endif
1070 <    end do
1071 <    
1072 <    return
1073 <  end function skipThisPair
1074 <
1075 <  function FF_UsesDirectionalAtoms() result(doesit)
1076 <    logical :: doesit
1077 <    doesit = FF_uses_dipoles .or. FF_uses_sticky .or. &
1078 <         FF_uses_GB .or. FF_uses_RF
1079 <  end function FF_UsesDirectionalAtoms
1080 <  
1081 <  function FF_RequiresPrepairCalc() result(doesit)
1082 <    logical :: doesit
1083 <    doesit = FF_uses_EAM
1084 <  end function FF_RequiresPrepairCalc
1085 <  
1086 <  function FF_RequiresPostpairCalc() result(doesit)
1087 <    logical :: doesit
1088 <    doesit = FF_uses_RF
1089 <  end function FF_RequiresPostpairCalc
1090 <  
1144 > function FF_UsesDirectionalAtoms() result(doesit)
1145 >   logical :: doesit
1146 >   doesit = FF_uses_dipoles .or. FF_uses_sticky .or. &
1147 >        FF_uses_GB .or. FF_uses_RF
1148 > end function FF_UsesDirectionalAtoms
1149 >
1150 > function FF_RequiresPrepairCalc() result(doesit)
1151 >   logical :: doesit
1152 >   doesit = FF_uses_EAM
1153 > end function FF_RequiresPrepairCalc
1154 >
1155 > function FF_RequiresPostpairCalc() result(doesit)
1156 >   logical :: doesit
1157 >   doesit = FF_uses_RF
1158 > end function FF_RequiresPostpairCalc
1159 >
1160   #ifdef PROFILE
1161 <  function getforcetime() return(totalforcetime)
1162 <    real(kind=dp) :: totalforcetime
1163 <    totalforcetime = forcetime
1164 <  end function getforcetime
1161 > function getforcetime() result(totalforcetime)
1162 >   real(kind=dp) :: totalforcetime
1163 >   totalforcetime = forcetime
1164 > end function getforcetime
1165   #endif
1166 +
1167 + !! This cleans componets of force arrays belonging only to fortran
1168  
1169 < !! This cleans componets of force arrays belonging only to fortran
1170 <
1169 > subroutine add_stress_tensor(dpair, fpair)
1170 >  
1171 >   real( kind = dp ), dimension(3), intent(in) :: dpair, fpair
1172 >  
1173 >   ! because the d vector is the rj - ri vector, and
1174 >   ! because fx, fy, fz are the force on atom i, we need a
1175 >   ! negative sign here:  
1176 >  
1177 >   tau_Temp(1) = tau_Temp(1) - dpair(1) * fpair(1)
1178 >   tau_Temp(2) = tau_Temp(2) - dpair(1) * fpair(2)
1179 >   tau_Temp(3) = tau_Temp(3) - dpair(1) * fpair(3)
1180 >   tau_Temp(4) = tau_Temp(4) - dpair(2) * fpair(1)
1181 >   tau_Temp(5) = tau_Temp(5) - dpair(2) * fpair(2)
1182 >   tau_Temp(6) = tau_Temp(6) - dpair(2) * fpair(3)
1183 >   tau_Temp(7) = tau_Temp(7) - dpair(3) * fpair(1)
1184 >   tau_Temp(8) = tau_Temp(8) - dpair(3) * fpair(2)
1185 >   tau_Temp(9) = tau_Temp(9) - dpair(3) * fpair(3)
1186 >  
1187 >   !write(*,'(6es12.3)')  fpair(1:3), tau_Temp(1), tau_Temp(5), tau_temp(9)
1188 >   virial_Temp = virial_Temp + &
1189 >        (tau_Temp(1) + tau_Temp(5) + tau_Temp(9))
1190 >  
1191 > end subroutine add_stress_tensor
1192 >
1193   end module do_Forces
1194 +

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines