ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/doForces.F90
(Generate patch)

Comparing trunk/OOPSE-4/src/UseTheForce/doForces.F90 (file contents):
Revision 1930 by gezelter, Wed Jan 12 22:41:40 2005 UTC vs.
Revision 2260 by chuckv, Mon Jun 27 22:21:37 2005 UTC

# Line 45 | Line 45
45  
46   !! @author Charles F. Vardeman II
47   !! @author Matthew Meineke
48 < !! @version $Id: doForces.F90,v 1.9 2005-01-12 22:40:37 gezelter Exp $, $Date: 2005-01-12 22:40:37 $, $Name: not supported by cvs2svn $, $Revision: 1.9 $
48 > !! @version $Id: doForces.F90,v 1.21 2005-06-27 22:21:37 chuckv Exp $, $Date: 2005-06-27 22:21:37 $, $Name: not supported by cvs2svn $, $Revision: 1.21 $
49  
50  
51   module doForces
# Line 57 | Line 57 | module doForces
57    use neighborLists  
58    use lj
59    use sticky
60 <  use dipole_dipole
61 <  use charge_charge
60 >  use electrostatic_module
61    use reaction_field
62    use gb_pair
63    use shapes
# Line 74 | Line 73 | module doForces
73  
74   #define __FORTRAN90
75   #include "UseTheForce/fSwitchingFunction.h"
76 + #include "UseTheForce/DarkSide/fInteractionMap.h"
77  
78    INTEGER, PARAMETER:: PREPAIR_LOOP = 1
79    INTEGER, PARAMETER:: PAIR_LOOP    = 2
# Line 83 | Line 83 | module doForces
83    logical, save :: haveSIMvariables = .false.
84    logical, save :: havePropertyMap = .false.
85    logical, save :: haveSaneForceField = .false.
86 <  
86 >
87    logical, save :: FF_uses_DirectionalAtoms
88    logical, save :: FF_uses_LennardJones
89 <  logical, save :: FF_uses_Electrostatic
90 <  logical, save :: FF_uses_charges
91 <  logical, save :: FF_uses_dipoles
92 <  logical, save :: FF_uses_sticky
89 >  logical, save :: FF_uses_Electrostatics
90 >  logical, save :: FF_uses_Charges
91 >  logical, save :: FF_uses_Dipoles
92 >  logical, save :: FF_uses_Quadrupoles
93 >  logical, save :: FF_uses_Sticky
94 >  logical, save :: FF_uses_StickyPower
95    logical, save :: FF_uses_GayBerne
96    logical, save :: FF_uses_EAM
97    logical, save :: FF_uses_Shapes
# Line 101 | Line 103 | module doForces
103    logical, save :: SIM_uses_Electrostatics
104    logical, save :: SIM_uses_Charges
105    logical, save :: SIM_uses_Dipoles
106 +  logical, save :: SIM_uses_Quadrupoles
107    logical, save :: SIM_uses_Sticky
108 +  logical, save :: SIM_uses_StickyPower
109    logical, save :: SIM_uses_GayBerne
110    logical, save :: SIM_uses_EAM
111    logical, save :: SIM_uses_Shapes
# Line 112 | Line 116 | module doForces
116    logical, save :: SIM_uses_PBC
117    logical, save :: SIM_uses_molecular_cutoffs
118  
119 <  real(kind=dp), save :: rlist, rlistsq
119 >  !!!GO AWAY---------
120 >  !!!!!real(kind=dp), save :: rlist, rlistsq
121  
122    public :: init_FF
123    public :: do_force_loop
124 <  public :: setRlistDF
124 > !  public :: setRlistDF
125  
126   #ifdef PROFILE
127    public :: getforcetime
# Line 131 | Line 136 | module doForces
136       logical :: is_Electrostatic = .false.
137       logical :: is_Charge        = .false.
138       logical :: is_Dipole        = .false.
139 +     logical :: is_Quadrupole    = .false.
140       logical :: is_Sticky        = .false.
141 +     logical :: is_StickyPower   = .false.
142       logical :: is_GayBerne      = .false.
143       logical :: is_EAM           = .false.
144       logical :: is_Shape         = .false.
# Line 140 | Line 147 | contains
147  
148    type(Properties), dimension(:),allocatable :: PropertyMap
149  
150 +
151 +  
152 +  type, public :: Interaction
153 +     integer :: InteractionHash
154 +     real(kind=dp) :: rCut
155 +  end type Interaction
156 +  
157 +  type(Interaction), public, dimension(:,:), allocatable :: InteractionMap
158 +  
159 +  !public :: addInteraction
160 +  !public :: setInteractionHash
161 +  !public :: getInteractionHash
162 +  public :: createInteractionMap
163 +
164   contains
165  
166 <  subroutine setRlistDF( this_rlist )
166 >
167 >  subroutine createInteractionMap(status)
168 >    integer :: nAtypes
169 >    integer :: status
170 >    integer :: i
171 >    integer :: j
172 >    integer :: ihash
173 >    real(kind=dp) :: myRcut
174 > ! Test Types
175 >    logical :: i_is_LJ
176 >    logical :: i_is_Elect
177 >    logical :: i_is_Sticky
178 >    logical :: i_is_StickyP
179 >    logical :: i_is_GB
180 >    logical :: i_is_EAM
181 >    logical :: i_is_Shape
182 >    logical :: j_is_LJ
183 >    logical :: j_is_Elect
184 >    logical :: j_is_Sticky
185 >    logical :: j_is_StickyP
186 >    logical :: j_is_GB
187 >    logical :: j_is_EAM
188 >    logical :: j_is_Shape
189      
147    real(kind=dp) :: this_rlist
148
149    rlist = this_rlist
150    rlistsq = rlist * rlist
190      
191 <    haveRlist = .true.
191 >    if (.not. associated(atypes)) then
192 >       call handleError("atype", "atypes was not present before call of createDefaultInteractionMap!")
193 >       status = -1
194 >       return
195 >    endif
196 >    
197 >    nAtypes = getSize(atypes)
198 >    
199 >    if (nAtypes == 0) then
200 >       status = -1
201 >       return
202 >    end if
203  
204 <  end subroutine setRlistDF    
204 >    if (.not. allocated(InteractionMap)) then
205 >       allocate(InteractionMap(nAtypes,nAtypes))
206 >    endif
207 >        
208 >    do i = 1, nAtypes
209 >       call getElementProperty(atypes, i, "is_LennardJones", i_is_LJ)
210 >       call getElementProperty(atypes, i, "is_Electrostatic", i_is_Elect)
211 >       call getElementProperty(atypes, i, "is_Sticky", i_is_Sticky)
212 >       call getElementProperty(atypes, i, "is_StickyPower", i_is_StickyP)
213 >       call getElementProperty(atypes, i, "is_GayBerne", i_is_GB)
214 >       call getElementProperty(atypes, i, "is_EAM", i_is_EAM)
215 >       call getElementProperty(atypes, i, "is_Shape", i_is_Shape)
216 >
217 >       do j = i, nAtypes
218 >
219 >          iHash = 0
220 >          myRcut = 0.0_dp
221 >
222 >          call getElementProperty(atypes, j, "is_LennardJones", j_is_LJ)
223 >          call getElementProperty(atypes, j, "is_Electrostatic", j_is_Elect)
224 >          call getElementProperty(atypes, j, "is_Sticky", j_is_Sticky)
225 >          call getElementProperty(atypes, j, "is_StickyPower", j_is_StickyP)
226 >          call getElementProperty(atypes, j, "is_GayBerne", j_is_GB)
227 >          call getElementProperty(atypes, j, "is_EAM", j_is_EAM)
228 >          call getElementProperty(atypes, j, "is_Shape", j_is_Shape)
229 >
230 >          if (i_is_LJ .and. j_is_LJ) then
231 >             iHash = ior(iHash, LJ_PAIR)
232 >            
233 >
234 >
235 >          endif
236 >
237 >
238 >
239 >          if (i_is_Elect .and. j_is_Elect) iHash = ior(iHash, ELECTROSTATIC_PAIR)
240 >          if (i_is_Sticky .and. j_is_Sticky) iHash = ior(iHash, STICKY_PAIR)
241 >          if (i_is_StickyP .and. j_is_StickyP) iHash = ior(iHash, STICKYPOWER_PAIR)
242 >
243 >          if (i_is_EAM .and. j_is_EAM) iHash = ior(iHash, EAM_PAIR)
244 >
245 >          if (i_is_GB .and. j_is_GB) iHash = ior(iHash, GAYBERNE_PAIR)
246 >          if (i_is_GB .and. j_is_LJ) iHash = ior(iHash, GAYBERNE_LJ)
247 >          if (i_is_LJ .and. j_is_GB) iHash = ior(iHash, GAYBERNE_LJ)
248 >
249 >          if (i_is_Shape .and. j_is_Shape) iHash = ior(iHash, SHAPE_PAIR)
250 >          if (i_is_Shape .and. j_is_LJ) iHash = ior(iHash, SHAPE_LJ)
251 >          if (i_is_LJ .and. j_is_Shape) iHash = ior(iHash, SHAPE_LJ)
252 >
253 >
254 >          InteractionMap(i,j)%InteractionHash = iHash
255 >          InteractionMap(j,i)%InteractionHash = iHash
256 >
257 >       end do
258 >
259 >    end do
260 >  end subroutine createInteractionMap
261 >
262 >
263 >
264 > !!! THIS GOES AWAY FOR SIZE DEPENDENT CUTOFF
265 > !!$  subroutine setRlistDF( this_rlist )
266 > !!$
267 > !!$   real(kind=dp) :: this_rlist
268 > !!$
269 > !!$    rlist = this_rlist
270 > !!$    rlistsq = rlist * rlist
271 > !!$
272 > !!$    haveRlist = .true.
273 > !!$
274 > !!$  end subroutine setRlistDF
275  
276    subroutine createPropertyMap(status)
277      integer :: nAtypes
# Line 168 | Line 288 | contains
288         status = -1
289         return
290      end if
291 <        
291 >
292      if (.not. allocated(PropertyMap)) then
293         allocate(PropertyMap(nAtypes))
294      endif
# Line 179 | Line 299 | contains
299  
300         call getElementProperty(atypes, i, "is_LennardJones", thisProperty)
301         PropertyMap(i)%is_LennardJones = thisProperty
302 <      
302 >
303         call getElementProperty(atypes, i, "is_Electrostatic", thisProperty)
304         PropertyMap(i)%is_Electrostatic = thisProperty
305  
306         call getElementProperty(atypes, i, "is_Charge", thisProperty)
307         PropertyMap(i)%is_Charge = thisProperty
308 <      
308 >
309         call getElementProperty(atypes, i, "is_Dipole", thisProperty)
310         PropertyMap(i)%is_Dipole = thisProperty
311  
312 +       call getElementProperty(atypes, i, "is_Quadrupole", thisProperty)
313 +       PropertyMap(i)%is_Quadrupole = thisProperty
314 +
315         call getElementProperty(atypes, i, "is_Sticky", thisProperty)
316         PropertyMap(i)%is_Sticky = thisProperty
317 +      
318 +       call getElementProperty(atypes, i, "is_StickyPower", thisProperty)
319 +       PropertyMap(i)%is_StickyPower = thisProperty
320  
321         call getElementProperty(atypes, i, "is_GayBerne", thisProperty)
322         PropertyMap(i)%is_GayBerne = thisProperty
# Line 216 | Line 342 | contains
342      SIM_uses_Charges = SimUsesCharges()
343      SIM_uses_Dipoles = SimUsesDipoles()
344      SIM_uses_Sticky = SimUsesSticky()
345 +    SIM_uses_StickyPower = SimUsesStickyPower()
346      SIM_uses_GayBerne = SimUsesGayBerne()
347      SIM_uses_EAM = SimUsesEAM()
348      SIM_uses_Shapes = SimUsesShapes()
# Line 236 | Line 363 | contains
363      integer :: myStatus
364  
365      error = 0
366 <    
366 >
367      if (.not. havePropertyMap) then
368  
369         myStatus = 0
# Line 281 | Line 408 | contains
408   #endif
409      return
410    end subroutine doReadyCheck
284    
411  
412 +
413    subroutine init_FF(use_RF_c, thisStat)
414  
415      logical, intent(in) :: use_RF_c
# Line 297 | Line 424 | contains
424  
425      !! Fortran's version of a cast:
426      FF_uses_RF = use_RF_c
427 <    
427 >
428      !! init_FF is called *after* all of the atom types have been
429      !! defined in atype_module using the new_atype subroutine.
430      !!
431      !! this will scan through the known atypes and figure out what
432      !! interactions are used by the force field.    
433 <  
433 >
434      FF_uses_DirectionalAtoms = .false.
435      FF_uses_LennardJones = .false.
436 <    FF_uses_Electrostatic = .false.
436 >    FF_uses_Electrostatics = .false.
437      FF_uses_Charges = .false.    
438      FF_uses_Dipoles = .false.
439      FF_uses_Sticky = .false.
440 +    FF_uses_StickyPower = .false.
441      FF_uses_GayBerne = .false.
442      FF_uses_EAM = .false.
443      FF_uses_Shapes = .false.
444      FF_uses_FLARB = .false.
445 <    
445 >
446      call getMatchingElementList(atypes, "is_Directional", .true., &
447           nMatches, MatchList)
448      if (nMatches .gt. 0) FF_uses_DirectionalAtoms = .true.
# Line 322 | Line 450 | contains
450      call getMatchingElementList(atypes, "is_LennardJones", .true., &
451           nMatches, MatchList)
452      if (nMatches .gt. 0) FF_uses_LennardJones = .true.
453 <    
453 >
454      call getMatchingElementList(atypes, "is_Electrostatic", .true., &
455           nMatches, MatchList)
456      if (nMatches .gt. 0) then
457 <       FF_uses_Electrostatic = .true.
457 >       FF_uses_Electrostatics = .true.
458      endif
459  
460      call getMatchingElementList(atypes, "is_Charge", .true., &
461           nMatches, MatchList)
462      if (nMatches .gt. 0) then
463 <       FF_uses_charges = .true.  
464 <       FF_uses_electrostatic = .true.
463 >       FF_uses_Charges = .true.  
464 >       FF_uses_Electrostatics = .true.
465      endif
466 <    
466 >
467      call getMatchingElementList(atypes, "is_Dipole", .true., &
468           nMatches, MatchList)
469      if (nMatches .gt. 0) then
470 <       FF_uses_dipoles = .true.
471 <       FF_uses_electrostatic = .true.
470 >       FF_uses_Dipoles = .true.
471 >       FF_uses_Electrostatics = .true.
472         FF_uses_DirectionalAtoms = .true.
473      endif
474 <    
474 >
475 >    call getMatchingElementList(atypes, "is_Quadrupole", .true., &
476 >         nMatches, MatchList)
477 >    if (nMatches .gt. 0) then
478 >       FF_uses_Quadrupoles = .true.
479 >       FF_uses_Electrostatics = .true.
480 >       FF_uses_DirectionalAtoms = .true.
481 >    endif
482 >
483      call getMatchingElementList(atypes, "is_Sticky", .true., nMatches, &
484           MatchList)
485      if (nMatches .gt. 0) then
486         FF_uses_Sticky = .true.
487         FF_uses_DirectionalAtoms = .true.
488      endif
489 +
490 +    call getMatchingElementList(atypes, "is_StickyPower", .true., nMatches, &
491 +         MatchList)
492 +    if (nMatches .gt. 0) then
493 +       FF_uses_StickyPower = .true.
494 +       FF_uses_DirectionalAtoms = .true.
495 +    endif
496      
497      call getMatchingElementList(atypes, "is_GayBerne", .true., &
498           nMatches, MatchList)
# Line 357 | Line 500 | contains
500         FF_uses_GayBerne = .true.
501         FF_uses_DirectionalAtoms = .true.
502      endif
503 <    
503 >
504      call getMatchingElementList(atypes, "is_EAM", .true., nMatches, MatchList)
505      if (nMatches .gt. 0) FF_uses_EAM = .true.
506 <    
506 >
507      call getMatchingElementList(atypes, "is_Shape", .true., &
508           nMatches, MatchList)
509      if (nMatches .gt. 0) then
# Line 374 | Line 517 | contains
517  
518      !! Assume sanity (for the sake of argument)
519      haveSaneForceField = .true.
520 <    
520 >
521      !! check to make sure the FF_uses_RF setting makes sense
522 <    
522 >
523      if (FF_uses_dipoles) then
524         if (FF_uses_RF) then
525            dielect = getDielect()
# Line 389 | Line 532 | contains
532            haveSaneForceField = .false.
533            return
534         endif
535 <    endif
535 >    endif
536  
537      !sticky module does not contain check_sticky_FF anymore
538      !if (FF_uses_sticky) then
# Line 402 | Line 545 | contains
545      !endif
546  
547      if (FF_uses_EAM) then
548 <         call init_EAM_FF(my_status)
548 >       call init_EAM_FF(my_status)
549         if (my_status /= 0) then
550            write(default_error, *) "init_EAM_FF returned a bad status"
551            thisStat = -1
# Line 422 | Line 565 | contains
565  
566      if (FF_uses_GayBerne .and. FF_uses_LennardJones) then
567      endif
568 <    
568 >
569      if (.not. haveNeighborList) then
570         !! Create neighbor lists
571         call expandNeighborList(nLocal, my_status)
# Line 432 | Line 575 | contains
575            return
576         endif
577         haveNeighborList = .true.
578 <    endif    
579 <    
578 >    endif
579 >
580    end subroutine init_FF
438  
581  
582 +
583    !! Does force loop over i,j pairs. Calls do_pair to calculates forces.
584    !------------------------------------------------------------->
585    subroutine do_force_loop(q, q_group, A, eFrame, f, t, tau, pot, &
# Line 488 | Line 631 | contains
631      integer :: loopStart, loopEnd, loop
632  
633      real(kind=dp) :: listSkin = 1.0  
634 <    
634 >
635      !! initialize local variables  
636 <    
636 >
637   #ifdef IS_MPI
638      pot_local = 0.0_dp
639      nAtomsInRow   = getNatomsInRow(plan_atom_row)
# Line 500 | Line 643 | contains
643   #else
644      natoms = nlocal
645   #endif
646 <    
646 >
647      call doReadyCheck(localError)
648      if ( localError .ne. 0 ) then
649         call handleError("do_force_loop", "Not Initialized")
# Line 508 | Line 651 | contains
651         return
652      end if
653      call zero_work_arrays()
654 <        
654 >
655      do_pot = do_pot_c
656      do_stress = do_stress_c
657 <    
657 >
658      ! Gather all information needed by all force loops:
659 <    
659 >
660   #ifdef IS_MPI    
661 <    
661 >
662      call gather(q, q_Row, plan_atom_row_3d)
663      call gather(q, q_Col, plan_atom_col_3d)
664  
665      call gather(q_group, q_group_Row, plan_group_row_3d)
666      call gather(q_group, q_group_Col, plan_group_col_3d)
667 <        
667 >
668      if (FF_UsesDirectionalAtoms() .and. SIM_uses_DirectionalAtoms) then
669         call gather(eFrame, eFrame_Row, plan_atom_row_rotation)
670         call gather(eFrame, eFrame_Col, plan_atom_col_rotation)
671 <      
671 >
672         call gather(A, A_Row, plan_atom_row_rotation)
673         call gather(A, A_Col, plan_atom_col_rotation)
674      endif
675 <    
675 >
676   #endif
677 <    
677 >
678      !! Begin force loop timing:
679   #ifdef PROFILE
680      call cpu_time(forceTimeInitial)
681      nloops = nloops + 1
682   #endif
683 <    
683 >
684      loopEnd = PAIR_LOOP
685      if (FF_RequiresPrepairCalc() .and. SIM_requires_prepair_calc) then
686         loopStart = PREPAIR_LOOP
# Line 552 | Line 695 | contains
695         if (loop .eq. loopStart) then
696   #ifdef IS_MPI
697            call checkNeighborList(nGroupsInRow, q_group_row, listSkin, &
698 <             update_nlist)
698 >               update_nlist)
699   #else
700            call checkNeighborList(nGroups, q_group, listSkin, &
701 <             update_nlist)
701 >               update_nlist)
702   #endif
703         endif
704 <      
704 >
705         if (update_nlist) then
706            !! save current configuration and construct neighbor list
707   #ifdef IS_MPI
# Line 569 | Line 712 | contains
712            neighborListSize = size(list)
713            nlist = 0
714         endif
715 <      
715 >
716         istart = 1
717   #ifdef IS_MPI
718         iend = nGroupsInRow
# Line 579 | Line 722 | contains
722         outer: do i = istart, iend
723  
724            if (update_nlist) point(i) = nlist + 1
725 <          
725 >
726            n_in_i = groupStartRow(i+1) - groupStartRow(i)
727 <          
727 >
728            if (update_nlist) then
729   #ifdef IS_MPI
730               jstart = 1
# Line 596 | Line 739 | contains
739               ! make sure group i has neighbors
740               if (jstart .gt. jend) cycle outer
741            endif
742 <          
742 >
743            do jnab = jstart, jend
744               if (update_nlist) then
745                  j = jnab
# Line 615 | Line 758 | contains
758               if (rgrpsq < rlistsq) then
759                  if (update_nlist) then
760                     nlist = nlist + 1
761 <                  
761 >
762                     if (nlist > neighborListSize) then
763   #ifdef IS_MPI                
764                        call expandNeighborList(nGroupsInRow, listerror)
# Line 629 | Line 772 | contains
772                        end if
773                        neighborListSize = size(list)
774                     endif
775 <                  
775 >
776                     list(nlist) = j
777                  endif
778 <                
778 >
779                  if (loop .eq. PAIR_LOOP) then
780                     vij = 0.0d0
781                     fij(1:3) = 0.0d0
782                  endif
783 <                
783 >
784                  call get_switch(rgrpsq, sw, dswdr, rgrp, group_switch, &
785                       in_switching_region)
786 <                
786 >
787                  n_in_j = groupStartCol(j+1) - groupStartCol(j)
788 <                
788 >
789                  do ia = groupStartRow(i), groupStartRow(i+1)-1
790 <                  
790 >
791                     atom1 = groupListRow(ia)
792 <                  
792 >
793                     inner: do jb = groupStartCol(j), groupStartCol(j+1)-1
794 <                      
794 >
795                        atom2 = groupListCol(jb)
796 <                      
796 >
797                        if (skipThisPair(atom1, atom2)) cycle inner
798  
799                        if ((n_in_i .eq. 1).and.(n_in_j .eq. 1)) then
# Line 692 | Line 835 | contains
835                        endif
836                     enddo inner
837                  enddo
838 <                
838 >
839                  if (loop .eq. PAIR_LOOP) then
840                     if (in_switching_region) then
841                        swderiv = vij*dswdr/rgrp
842                        fij(1) = fij(1) + swderiv*d_grp(1)
843                        fij(2) = fij(2) + swderiv*d_grp(2)
844                        fij(3) = fij(3) + swderiv*d_grp(3)
845 <                      
845 >
846                        do ia=groupStartRow(i), groupStartRow(i+1)-1
847                           atom1=groupListRow(ia)
848                           mf = mfactRow(atom1)
# Line 713 | Line 856 | contains
856                           f(3,atom1) = f(3,atom1) + swderiv*d_grp(3)*mf
857   #endif
858                        enddo
859 <                      
859 >
860                        do jb=groupStartCol(j), groupStartCol(j+1)-1
861                           atom2=groupListCol(jb)
862                           mf = mfactCol(atom2)
# Line 728 | Line 871 | contains
871   #endif
872                        enddo
873                     endif
874 <                  
874 >
875                     if (do_stress) call add_stress_tensor(d_grp, fij)
876                  endif
877               end if
878            enddo
879         enddo outer
880 <      
880 >
881         if (update_nlist) then
882   #ifdef IS_MPI
883            point(nGroupsInRow + 1) = nlist + 1
# Line 748 | Line 891 | contains
891               update_nlist = .false.                              
892            endif
893         endif
894 <            
894 >
895         if (loop .eq. PREPAIR_LOOP) then
896            call do_preforce(nlocal, pot)
897         endif
898 <      
898 >
899      enddo
900 <    
900 >
901      !! Do timing
902   #ifdef PROFILE
903      call cpu_time(forceTimeFinal)
904      forceTime = forceTime + forceTimeFinal - forceTimeInitial
905   #endif    
906 <    
906 >
907   #ifdef IS_MPI
908      !!distribute forces
909 <    
909 >
910      f_temp = 0.0_dp
911      call scatter(f_Row,f_temp,plan_atom_row_3d)
912      do i = 1,nlocal
913         f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
914      end do
915 <    
915 >
916      f_temp = 0.0_dp
917      call scatter(f_Col,f_temp,plan_atom_col_3d)
918      do i = 1,nlocal
919         f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
920      end do
921 <    
921 >
922      if (FF_UsesDirectionalAtoms() .and. SIM_uses_DirectionalAtoms) then
923         t_temp = 0.0_dp
924         call scatter(t_Row,t_temp,plan_atom_row_3d)
# Line 784 | Line 927 | contains
927         end do
928         t_temp = 0.0_dp
929         call scatter(t_Col,t_temp,plan_atom_col_3d)
930 <      
930 >
931         do i = 1,nlocal
932            t(1:3,i) = t(1:3,i) + t_temp(1:3,i)
933         end do
934      endif
935 <    
935 >
936      if (do_pot) then
937         ! scatter/gather pot_row into the members of my column
938         call scatter(pot_Row, pot_Temp, plan_atom_row)
939 <      
939 >
940         ! scatter/gather pot_local into all other procs
941         ! add resultant to get total pot
942         do i = 1, nlocal
943            pot_local = pot_local + pot_Temp(i)
944         enddo
945 <      
945 >
946         pot_Temp = 0.0_DP
947 <      
947 >
948         call scatter(pot_Col, pot_Temp, plan_atom_col)
949         do i = 1, nlocal
950            pot_local = pot_local + pot_Temp(i)
951         enddo
952 <      
952 >
953      endif
954   #endif
955 <    
955 >
956      if (FF_RequiresPostpairCalc() .and. SIM_requires_postpair_calc) then
957 <      
957 >
958         if (FF_uses_RF .and. SIM_uses_RF) then
959 <          
959 >
960   #ifdef IS_MPI
961            call scatter(rf_Row,rf,plan_atom_row_3d)
962            call scatter(rf_Col,rf_Temp,plan_atom_col_3d)
# Line 821 | Line 964 | contains
964               rf(1:3,i) = rf(1:3,i) + rf_Temp(1:3,i)
965            end do
966   #endif
967 <          
967 >
968            do i = 1, nLocal
969 <            
969 >
970               rfpot = 0.0_DP
971   #ifdef IS_MPI
972               me_i = atid_row(i)
973   #else
974               me_i = atid(i)
975   #endif
976 <            
976 >
977               if (PropertyMap(me_i)%is_Dipole) then
978 <                
978 >
979                  mu_i = getDipoleMoment(me_i)
980 <                
980 >
981                  !! The reaction field needs to include a self contribution
982                  !! to the field:
983                  call accumulate_self_rf(i, mu_i, eFrame)
# Line 845 | Line 988 | contains
988                  pot_local = pot_local + rfpot
989   #else
990                  pot = pot + rfpot
991 <      
991 >
992   #endif
993 <             endif            
993 >             endif
994            enddo
995         endif
996      endif
997 <    
998 <    
997 >
998 >
999   #ifdef IS_MPI
1000 <    
1000 >
1001      if (do_pot) then
1002         pot = pot + pot_local
1003         !! we assume the c code will do the allreduce to get the total potential
1004         !! we could do it right here if we needed to...
1005      endif
1006 <    
1006 >
1007      if (do_stress) then
1008         call mpi_allreduce(tau_Temp, tau, 9,mpi_double_precision,mpi_sum, &
1009              mpi_comm_world,mpi_err)
1010         call mpi_allreduce(virial_Temp, virial,1,mpi_double_precision,mpi_sum, &
1011              mpi_comm_world,mpi_err)
1012      endif
1013 <    
1013 >
1014   #else
1015 <    
1015 >
1016      if (do_stress) then
1017         tau = tau_Temp
1018         virial = virial_Temp
1019      endif
1020 <    
1020 >
1021   #endif
1022 <      
1022 >
1023    end subroutine do_force_loop
1024 <  
1024 >
1025    subroutine do_pair(i, j, rijsq, d, sw, do_pot, &
1026         eFrame, A, f, t, pot, vpair, fpair)
1027  
# Line 895 | Line 1038 | contains
1038      real ( kind = dp ), intent(inout) :: rijsq
1039      real ( kind = dp )                :: r
1040      real ( kind = dp ), intent(inout) :: d(3)
1041 +    real ( kind = dp ) :: ebalance
1042      integer :: me_i, me_j
1043  
1044 +    integer :: iMap
1045 +
1046      r = sqrt(rijsq)
1047      vpair = 0.0d0
1048      fpair(1:3) = 0.0d0
# Line 909 | Line 1055 | contains
1055      me_j = atid(j)
1056   #endif
1057  
1058 < !    write(*,*) i, j, me_i, me_j
1059 <    
1060 <    if (FF_uses_LennardJones .and. SIM_uses_LennardJones) then
1061 <      
916 <       if ( PropertyMap(me_i)%is_LennardJones .and. &
917 <            PropertyMap(me_j)%is_LennardJones ) then
918 <          call do_lj_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot)
919 <       endif
920 <      
1058 >    iMap = InteractionMap(me_i, me_j)%InteractionHash
1059 >
1060 >    if ( iand(iMap, LJ_PAIR).ne.0 ) then
1061 >       call do_lj_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot)
1062      endif
1063 <    
1064 <    if (FF_uses_charges .and. SIM_uses_charges) then
1065 <      
1066 <       if (PropertyMap(me_i)%is_Charge .and. PropertyMap(me_j)%is_Charge) then
1067 <          call do_charge_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1068 <               pot, f, do_pot)
1069 <       endif
1070 <      
1071 <    endif
1072 <    
1073 <    if (FF_uses_dipoles .and. SIM_uses_dipoles) then
1074 <      
934 <       if ( PropertyMap(me_i)%is_Dipole .and. PropertyMap(me_j)%is_Dipole) then
935 <          call do_dipole_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
936 <               pot, eFrame, f, t, do_pot)
937 <          if (FF_uses_RF .and. SIM_uses_RF) then
938 <             call accumulate_rf(i, j, r, eFrame, sw)
939 <             call rf_correct_forces(i, j, d, r, eFrame, sw, f, fpair)
1063 >
1064 >    if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
1065 >       call doElectrostaticPair(i, j, d, r, rijsq, sw, vpair, fpair, &
1066 >            pot, eFrame, f, t, do_pot)
1067 >
1068 >       if (FF_uses_dipoles .and. SIM_uses_dipoles) then                
1069 >          if ( PropertyMap(me_i)%is_Dipole .and. &
1070 >               PropertyMap(me_j)%is_Dipole) then
1071 >             if (FF_uses_RF .and. SIM_uses_RF) then
1072 >                call accumulate_rf(i, j, r, eFrame, sw)
1073 >                call rf_correct_forces(i, j, d, r, eFrame, sw, f, fpair)
1074 >             endif
1075            endif
1076         endif
1077 +    endif
1078  
1079 +    if ( iand(iMap, STICKY_PAIR).ne.0 ) then
1080 +       call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1081 +            pot, A, f, t, do_pot)
1082      endif
1083  
1084 <    if (FF_uses_Sticky .and. SIM_uses_sticky) then
1085 <
1086 <       if ( PropertyMap(me_i)%is_Sticky .and. PropertyMap(me_j)%is_Sticky) then
948 <          call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
949 <               pot, A, f, t, do_pot)
950 <       endif
951 <      
1084 >    if ( iand(iMap, STICKYPOWER_PAIR).ne.0 ) then
1085 >       call do_sticky_power_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1086 >            pot, A, f, t, do_pot)
1087      endif
1088  
1089 <
1090 <    if (FF_uses_GayBerne .and. SIM_uses_GayBerne) then
1091 <      
957 <       if ( PropertyMap(me_i)%is_GayBerne .and. &
958 <            PropertyMap(me_j)%is_GayBerne) then
959 <          call do_gb_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
960 <               pot, A, f, t, do_pot)
961 <       endif
962 <      
1089 >    if ( iand(iMap, GAYBERNE_PAIR).ne.0 ) then
1090 >       call do_gb_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1091 >            pot, A, f, t, do_pot)
1092      endif
1093      
1094 <    if (FF_uses_EAM .and. SIM_uses_EAM) then
1095 <      
1096 <       if ( PropertyMap(me_i)%is_EAM .and. PropertyMap(me_j)%is_EAM) then
968 <          call do_eam_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, &
969 <               do_pot)
970 <       endif
971 <      
1094 >    if ( iand(iMap, GAYBERNE_LJ).ne.0 ) then
1095 >       call do_gblj_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1096 >            pot, A, f, t, do_pot)
1097      endif
1098  
1099 +    if ( iand(iMap, EAM_PAIR).ne.0 ) then      
1100 +       call do_eam_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, &
1101 +            do_pot)
1102 +    endif
1103  
1104 < !    write(*,*) PropertyMap(me_i)%is_Shape,PropertyMap(me_j)%is_Shape
1104 >    if ( iand(iMap, SHAPE_PAIR).ne.0 ) then      
1105 >       call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1106 >            pot, A, f, t, do_pot)
1107 >    endif
1108  
1109 <    if (FF_uses_Shapes .and. SIM_uses_Shapes) then
1110 <       if ( PropertyMap(me_i)%is_Shape .and. &
1111 <            PropertyMap(me_j)%is_Shape ) then
980 <          call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
981 <               pot, A, f, t, do_pot)
982 <       endif
983 <      
1109 >    if ( iand(iMap, SHAPE_LJ).ne.0 ) then      
1110 >       call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1111 >            pot, A, f, t, do_pot)
1112      endif
1113      
1114    end subroutine do_pair
# Line 988 | Line 1116 | contains
1116    subroutine do_prepair(i, j, rijsq, d, sw, rcijsq, dc, &
1117         do_pot, do_stress, eFrame, A, f, t, pot)
1118  
1119 <   real( kind = dp ) :: pot, sw
1120 <   real( kind = dp ), dimension(9,nLocal) :: eFrame
1121 <   real (kind=dp), dimension(9,nLocal) :: A
1122 <   real (kind=dp), dimension(3,nLocal) :: f
1123 <   real (kind=dp), dimension(3,nLocal) :: t
996 <  
997 <   logical, intent(inout) :: do_pot, do_stress
998 <   integer, intent(in) :: i, j
999 <   real ( kind = dp ), intent(inout)    :: rijsq, rcijsq
1000 <   real ( kind = dp )                :: r, rc
1001 <   real ( kind = dp ), intent(inout) :: d(3), dc(3)
1002 <  
1003 <   logical :: is_EAM_i, is_EAM_j
1004 <  
1005 <   integer :: me_i, me_j
1006 <  
1119 >    real( kind = dp ) :: pot, sw
1120 >    real( kind = dp ), dimension(9,nLocal) :: eFrame
1121 >    real (kind=dp), dimension(9,nLocal) :: A
1122 >    real (kind=dp), dimension(3,nLocal) :: f
1123 >    real (kind=dp), dimension(3,nLocal) :: t
1124  
1125 <    r = sqrt(rijsq)
1126 <    if (SIM_uses_molecular_cutoffs) then
1127 <       rc = sqrt(rcijsq)
1128 <    else
1129 <       rc = r
1013 <    endif
1014 <  
1125 >    logical, intent(inout) :: do_pot, do_stress
1126 >    integer, intent(in) :: i, j
1127 >    real ( kind = dp ), intent(inout)    :: rijsq, rcijsq
1128 >    real ( kind = dp )                :: r, rc
1129 >    real ( kind = dp ), intent(inout) :: d(3), dc(3)
1130  
1131 +    integer :: me_i, me_j, iMap
1132 +
1133   #ifdef IS_MPI  
1134 <   me_i = atid_row(i)
1135 <   me_j = atid_col(j)  
1134 >    me_i = atid_row(i)
1135 >    me_j = atid_col(j)  
1136   #else  
1137 <   me_i = atid(i)
1138 <   me_j = atid(j)  
1137 >    me_i = atid(i)
1138 >    me_j = atid(j)  
1139   #endif
1140 <  
1141 <   if (FF_uses_EAM .and. SIM_uses_EAM) then
1142 <      
1143 <      if (PropertyMap(me_i)%is_EAM .and. PropertyMap(me_j)%is_EAM) &
1144 <           call calc_EAM_prepair_rho(i, j, d, r, rijsq )
1145 <      
1146 <   endif
1147 <  
1148 < end subroutine do_prepair
1149 <
1150 <
1151 < subroutine do_preforce(nlocal,pot)
1152 <   integer :: nlocal
1153 <   real( kind = dp ) :: pot
1154 <  
1155 <   if (FF_uses_EAM .and. SIM_uses_EAM) then
1156 <      call calc_EAM_preforce_Frho(nlocal,pot)
1157 <   endif
1158 <  
1159 <  
1160 < end subroutine do_preforce
1161 <
1162 <
1163 < subroutine get_interatomic_vector(q_i, q_j, d, r_sq)
1164 <  
1165 <   real (kind = dp), dimension(3) :: q_i
1166 <   real (kind = dp), dimension(3) :: q_j
1167 <   real ( kind = dp ), intent(out) :: r_sq
1168 <   real( kind = dp ) :: d(3), scaled(3)
1169 <   integer i
1170 <  
1171 <   d(1:3) = q_j(1:3) - q_i(1:3)
1172 <  
1173 <   ! Wrap back into periodic box if necessary
1174 <   if ( SIM_uses_PBC ) then
1175 <      
1176 <      if( .not.boxIsOrthorhombic ) then
1177 <         ! calc the scaled coordinates.
1178 <        
1179 <         scaled = matmul(HmatInv, d)
1180 <        
1181 <         ! wrap the scaled coordinates
1182 <        
1183 <         scaled = scaled  - anint(scaled)
1184 <        
1185 <        
1186 <         ! calc the wrapped real coordinates from the wrapped scaled
1187 <         ! coordinates
1188 <        
1189 <         d = matmul(Hmat,scaled)
1190 <        
1191 <      else
1192 <         ! calc the scaled coordinates.
1193 <        
1194 <         do i = 1, 3
1195 <            scaled(i) = d(i) * HmatInv(i,i)
1196 <            
1197 <            ! wrap the scaled coordinates
1198 <            
1199 <            scaled(i) = scaled(i) - anint(scaled(i))
1200 <            
1201 <            ! calc the wrapped real coordinates from the wrapped scaled
1202 <            ! coordinates
1203 <            
1204 <            d(i) = scaled(i)*Hmat(i,i)
1205 <         enddo
1206 <      endif
1207 <      
1208 <   endif
1209 <  
1210 <   r_sq = dot_product(d,d)
1211 <  
1212 < end subroutine get_interatomic_vector
1213 <
1214 < subroutine zero_work_arrays()
1098 <  
1140 >
1141 >    iMap = InteractionMap(me_i, me_j)%InteractionHash
1142 >
1143 >    if ( iand(iMap, EAM_PAIR).ne.0 ) then      
1144 >            call calc_EAM_prepair_rho(i, j, d, r, rijsq )
1145 >    endif
1146 >    
1147 >  end subroutine do_prepair
1148 >
1149 >
1150 >  subroutine do_preforce(nlocal,pot)
1151 >    integer :: nlocal
1152 >    real( kind = dp ) :: pot
1153 >
1154 >    if (FF_uses_EAM .and. SIM_uses_EAM) then
1155 >       call calc_EAM_preforce_Frho(nlocal,pot)
1156 >    endif
1157 >
1158 >
1159 >  end subroutine do_preforce
1160 >
1161 >
1162 >  subroutine get_interatomic_vector(q_i, q_j, d, r_sq)
1163 >
1164 >    real (kind = dp), dimension(3) :: q_i
1165 >    real (kind = dp), dimension(3) :: q_j
1166 >    real ( kind = dp ), intent(out) :: r_sq
1167 >    real( kind = dp ) :: d(3), scaled(3)
1168 >    integer i
1169 >
1170 >    d(1:3) = q_j(1:3) - q_i(1:3)
1171 >
1172 >    ! Wrap back into periodic box if necessary
1173 >    if ( SIM_uses_PBC ) then
1174 >
1175 >       if( .not.boxIsOrthorhombic ) then
1176 >          ! calc the scaled coordinates.
1177 >
1178 >          scaled = matmul(HmatInv, d)
1179 >
1180 >          ! wrap the scaled coordinates
1181 >
1182 >          scaled = scaled  - anint(scaled)
1183 >
1184 >
1185 >          ! calc the wrapped real coordinates from the wrapped scaled
1186 >          ! coordinates
1187 >
1188 >          d = matmul(Hmat,scaled)
1189 >
1190 >       else
1191 >          ! calc the scaled coordinates.
1192 >
1193 >          do i = 1, 3
1194 >             scaled(i) = d(i) * HmatInv(i,i)
1195 >
1196 >             ! wrap the scaled coordinates
1197 >
1198 >             scaled(i) = scaled(i) - anint(scaled(i))
1199 >
1200 >             ! calc the wrapped real coordinates from the wrapped scaled
1201 >             ! coordinates
1202 >
1203 >             d(i) = scaled(i)*Hmat(i,i)
1204 >          enddo
1205 >       endif
1206 >
1207 >    endif
1208 >
1209 >    r_sq = dot_product(d,d)
1210 >
1211 >  end subroutine get_interatomic_vector
1212 >
1213 >  subroutine zero_work_arrays()
1214 >
1215   #ifdef IS_MPI
1100  
1101   q_Row = 0.0_dp
1102   q_Col = 0.0_dp
1216  
1217 <   q_group_Row = 0.0_dp
1218 <   q_group_Col = 0.0_dp  
1219 <  
1220 <   eFrame_Row = 0.0_dp
1221 <   eFrame_Col = 0.0_dp
1222 <  
1223 <   A_Row = 0.0_dp
1224 <   A_Col = 0.0_dp
1225 <  
1226 <   f_Row = 0.0_dp
1227 <   f_Col = 0.0_dp
1228 <   f_Temp = 0.0_dp
1229 <  
1230 <   t_Row = 0.0_dp
1231 <   t_Col = 0.0_dp
1232 <   t_Temp = 0.0_dp
1233 <  
1234 <   pot_Row = 0.0_dp
1235 <   pot_Col = 0.0_dp
1236 <   pot_Temp = 0.0_dp
1237 <  
1238 <   rf_Row = 0.0_dp
1239 <   rf_Col = 0.0_dp
1240 <   rf_Temp = 0.0_dp
1241 <  
1217 >    q_Row = 0.0_dp
1218 >    q_Col = 0.0_dp
1219 >
1220 >    q_group_Row = 0.0_dp
1221 >    q_group_Col = 0.0_dp  
1222 >
1223 >    eFrame_Row = 0.0_dp
1224 >    eFrame_Col = 0.0_dp
1225 >
1226 >    A_Row = 0.0_dp
1227 >    A_Col = 0.0_dp
1228 >
1229 >    f_Row = 0.0_dp
1230 >    f_Col = 0.0_dp
1231 >    f_Temp = 0.0_dp
1232 >
1233 >    t_Row = 0.0_dp
1234 >    t_Col = 0.0_dp
1235 >    t_Temp = 0.0_dp
1236 >
1237 >    pot_Row = 0.0_dp
1238 >    pot_Col = 0.0_dp
1239 >    pot_Temp = 0.0_dp
1240 >
1241 >    rf_Row = 0.0_dp
1242 >    rf_Col = 0.0_dp
1243 >    rf_Temp = 0.0_dp
1244 >
1245   #endif
1246 <
1247 <   if (FF_uses_EAM .and. SIM_uses_EAM) then
1248 <      call clean_EAM()
1249 <   endif
1250 <  
1251 <   rf = 0.0_dp
1252 <   tau_Temp = 0.0_dp
1253 <   virial_Temp = 0.0_dp
1254 < end subroutine zero_work_arrays
1255 <
1256 < function skipThisPair(atom1, atom2) result(skip_it)
1257 <   integer, intent(in) :: atom1
1258 <   integer, intent(in), optional :: atom2
1259 <   logical :: skip_it
1260 <   integer :: unique_id_1, unique_id_2
1261 <   integer :: me_i,me_j
1262 <   integer :: i
1263 <  
1264 <   skip_it = .false.
1265 <  
1266 <   !! there are a number of reasons to skip a pair or a particle
1267 <   !! mostly we do this to exclude atoms who are involved in short
1268 <   !! range interactions (bonds, bends, torsions), but we also need
1269 <   !! to exclude some overcounted interactions that result from
1270 <   !! the parallel decomposition
1271 <  
1246 >
1247 >    if (FF_uses_EAM .and. SIM_uses_EAM) then
1248 >       call clean_EAM()
1249 >    endif
1250 >
1251 >    rf = 0.0_dp
1252 >    tau_Temp = 0.0_dp
1253 >    virial_Temp = 0.0_dp
1254 >  end subroutine zero_work_arrays
1255 >
1256 >  function skipThisPair(atom1, atom2) result(skip_it)
1257 >    integer, intent(in) :: atom1
1258 >    integer, intent(in), optional :: atom2
1259 >    logical :: skip_it
1260 >    integer :: unique_id_1, unique_id_2
1261 >    integer :: me_i,me_j
1262 >    integer :: i
1263 >
1264 >    skip_it = .false.
1265 >
1266 >    !! there are a number of reasons to skip a pair or a particle
1267 >    !! mostly we do this to exclude atoms who are involved in short
1268 >    !! range interactions (bonds, bends, torsions), but we also need
1269 >    !! to exclude some overcounted interactions that result from
1270 >    !! the parallel decomposition
1271 >
1272   #ifdef IS_MPI
1273 <   !! in MPI, we have to look up the unique IDs for each atom
1274 <   unique_id_1 = AtomRowToGlobal(atom1)
1273 >    !! in MPI, we have to look up the unique IDs for each atom
1274 >    unique_id_1 = AtomRowToGlobal(atom1)
1275   #else
1276 <   !! in the normal loop, the atom numbers are unique
1277 <   unique_id_1 = atom1
1276 >    !! in the normal loop, the atom numbers are unique
1277 >    unique_id_1 = atom1
1278   #endif
1279 <  
1280 <   !! We were called with only one atom, so just check the global exclude
1281 <   !! list for this atom
1282 <   if (.not. present(atom2)) then
1283 <      do i = 1, nExcludes_global
1284 <         if (excludesGlobal(i) == unique_id_1) then
1285 <            skip_it = .true.
1286 <            return
1287 <         end if
1288 <      end do
1289 <      return
1290 <   end if
1291 <  
1279 >
1280 >    !! We were called with only one atom, so just check the global exclude
1281 >    !! list for this atom
1282 >    if (.not. present(atom2)) then
1283 >       do i = 1, nExcludes_global
1284 >          if (excludesGlobal(i) == unique_id_1) then
1285 >             skip_it = .true.
1286 >             return
1287 >          end if
1288 >       end do
1289 >       return
1290 >    end if
1291 >
1292   #ifdef IS_MPI
1293 <   unique_id_2 = AtomColToGlobal(atom2)
1293 >    unique_id_2 = AtomColToGlobal(atom2)
1294   #else
1295 <   unique_id_2 = atom2
1295 >    unique_id_2 = atom2
1296   #endif
1297 <  
1297 >
1298   #ifdef IS_MPI
1299 <   !! this situation should only arise in MPI simulations
1300 <   if (unique_id_1 == unique_id_2) then
1301 <      skip_it = .true.
1302 <      return
1303 <   end if
1304 <  
1305 <   !! this prevents us from doing the pair on multiple processors
1306 <   if (unique_id_1 < unique_id_2) then
1307 <      if (mod(unique_id_1 + unique_id_2,2) == 0) then
1308 <         skip_it = .true.
1309 <         return
1310 <      endif
1311 <   else                
1312 <      if (mod(unique_id_1 + unique_id_2,2) == 1) then
1313 <         skip_it = .true.
1314 <         return
1315 <      endif
1316 <   endif
1299 >    !! this situation should only arise in MPI simulations
1300 >    if (unique_id_1 == unique_id_2) then
1301 >       skip_it = .true.
1302 >       return
1303 >    end if
1304 >
1305 >    !! this prevents us from doing the pair on multiple processors
1306 >    if (unique_id_1 < unique_id_2) then
1307 >       if (mod(unique_id_1 + unique_id_2,2) == 0) then
1308 >          skip_it = .true.
1309 >          return
1310 >       endif
1311 >    else                
1312 >       if (mod(unique_id_1 + unique_id_2,2) == 1) then
1313 >          skip_it = .true.
1314 >          return
1315 >       endif
1316 >    endif
1317   #endif
1318 <  
1319 <   !! the rest of these situations can happen in all simulations:
1320 <   do i = 1, nExcludes_global      
1321 <      if ((excludesGlobal(i) == unique_id_1) .or. &
1322 <           (excludesGlobal(i) == unique_id_2)) then
1323 <         skip_it = .true.
1324 <         return
1325 <      endif
1326 <   enddo
1327 <  
1328 <   do i = 1, nSkipsForAtom(atom1)
1329 <      if (skipsForAtom(atom1, i) .eq. unique_id_2) then
1330 <         skip_it = .true.
1331 <         return
1332 <      endif
1333 <   end do
1334 <  
1335 <   return
1336 < end function skipThisPair
1337 <
1338 < function FF_UsesDirectionalAtoms() result(doesit)
1339 <   logical :: doesit
1340 <   doesit = FF_uses_DirectionalAtoms .or. FF_uses_Dipoles .or. &
1341 <        FF_uses_Sticky .or. FF_uses_GayBerne .or. FF_uses_Shapes
1342 < end function FF_UsesDirectionalAtoms
1343 <
1344 < function FF_RequiresPrepairCalc() result(doesit)
1345 <   logical :: doesit
1346 <   doesit = FF_uses_EAM
1347 < end function FF_RequiresPrepairCalc
1348 <
1349 < function FF_RequiresPostpairCalc() result(doesit)
1350 <   logical :: doesit
1351 <   doesit = FF_uses_RF
1352 < end function FF_RequiresPostpairCalc
1353 <
1318 >
1319 >    !! the rest of these situations can happen in all simulations:
1320 >    do i = 1, nExcludes_global      
1321 >       if ((excludesGlobal(i) == unique_id_1) .or. &
1322 >            (excludesGlobal(i) == unique_id_2)) then
1323 >          skip_it = .true.
1324 >          return
1325 >       endif
1326 >    enddo
1327 >
1328 >    do i = 1, nSkipsForAtom(atom1)
1329 >       if (skipsForAtom(atom1, i) .eq. unique_id_2) then
1330 >          skip_it = .true.
1331 >          return
1332 >       endif
1333 >    end do
1334 >
1335 >    return
1336 >  end function skipThisPair
1337 >
1338 >  function FF_UsesDirectionalAtoms() result(doesit)
1339 >    logical :: doesit
1340 >    doesit = FF_uses_DirectionalAtoms .or. FF_uses_Dipoles .or. &
1341 >         FF_uses_Quadrupoles .or. FF_uses_Sticky .or. &
1342 >         FF_uses_StickyPower .or. FF_uses_GayBerne .or. FF_uses_Shapes
1343 >  end function FF_UsesDirectionalAtoms
1344 >
1345 >  function FF_RequiresPrepairCalc() result(doesit)
1346 >    logical :: doesit
1347 >    doesit = FF_uses_EAM
1348 >  end function FF_RequiresPrepairCalc
1349 >
1350 >  function FF_RequiresPostpairCalc() result(doesit)
1351 >    logical :: doesit
1352 >    doesit = FF_uses_RF
1353 >  end function FF_RequiresPostpairCalc
1354 >
1355   #ifdef PROFILE
1356 < function getforcetime() result(totalforcetime)
1357 <   real(kind=dp) :: totalforcetime
1358 <   totalforcetime = forcetime
1359 < end function getforcetime
1356 >  function getforcetime() result(totalforcetime)
1357 >    real(kind=dp) :: totalforcetime
1358 >    totalforcetime = forcetime
1359 >  end function getforcetime
1360   #endif
1244
1245 !! This cleans componets of force arrays belonging only to fortran
1361  
1362 < subroutine add_stress_tensor(dpair, fpair)
1248 <  
1249 <   real( kind = dp ), dimension(3), intent(in) :: dpair, fpair
1250 <  
1251 <   ! because the d vector is the rj - ri vector, and
1252 <   ! because fx, fy, fz are the force on atom i, we need a
1253 <   ! negative sign here:  
1254 <  
1255 <   tau_Temp(1) = tau_Temp(1) - dpair(1) * fpair(1)
1256 <   tau_Temp(2) = tau_Temp(2) - dpair(1) * fpair(2)
1257 <   tau_Temp(3) = tau_Temp(3) - dpair(1) * fpair(3)
1258 <   tau_Temp(4) = tau_Temp(4) - dpair(2) * fpair(1)
1259 <   tau_Temp(5) = tau_Temp(5) - dpair(2) * fpair(2)
1260 <   tau_Temp(6) = tau_Temp(6) - dpair(2) * fpair(3)
1261 <   tau_Temp(7) = tau_Temp(7) - dpair(3) * fpair(1)
1262 <   tau_Temp(8) = tau_Temp(8) - dpair(3) * fpair(2)
1263 <   tau_Temp(9) = tau_Temp(9) - dpair(3) * fpair(3)
1264 <  
1265 <   virial_Temp = virial_Temp + &
1266 <        (tau_Temp(1) + tau_Temp(5) + tau_Temp(9))
1267 <  
1268 < end subroutine add_stress_tensor
1269 <
1270 < end module doForces
1362 >  !! This cleans componets of force arrays belonging only to fortran
1363  
1364 < !! Interfaces for C programs to module....
1364 >  subroutine add_stress_tensor(dpair, fpair)
1365  
1366 < subroutine initFortranFF(use_RF_c, thisStat)
1275 <    use doForces, ONLY: init_FF
1276 <    logical, intent(in) :: use_RF_c
1366 >    real( kind = dp ), dimension(3), intent(in) :: dpair, fpair
1367  
1368 <    integer, intent(out) :: thisStat  
1369 <    call init_FF(use_RF_c, thisStat)
1368 >    ! because the d vector is the rj - ri vector, and
1369 >    ! because fx, fy, fz are the force on atom i, we need a
1370 >    ! negative sign here:  
1371  
1372 < end subroutine initFortranFF
1372 >    tau_Temp(1) = tau_Temp(1) - dpair(1) * fpair(1)
1373 >    tau_Temp(2) = tau_Temp(2) - dpair(1) * fpair(2)
1374 >    tau_Temp(3) = tau_Temp(3) - dpair(1) * fpair(3)
1375 >    tau_Temp(4) = tau_Temp(4) - dpair(2) * fpair(1)
1376 >    tau_Temp(5) = tau_Temp(5) - dpair(2) * fpair(2)
1377 >    tau_Temp(6) = tau_Temp(6) - dpair(2) * fpair(3)
1378 >    tau_Temp(7) = tau_Temp(7) - dpair(3) * fpair(1)
1379 >    tau_Temp(8) = tau_Temp(8) - dpair(3) * fpair(2)
1380 >    tau_Temp(9) = tau_Temp(9) - dpair(3) * fpair(3)
1381  
1382 <  subroutine doForceloop(q, q_group, A, eFrame, f, t, tau, pot, &
1383 <       do_pot_c, do_stress_c, error)
1285 <      
1286 <       use definitions, ONLY: dp
1287 <       use simulation
1288 <       use doForces, ONLY: do_force_loop
1289 <    !! Position array provided by C, dimensioned by getNlocal
1290 <    real ( kind = dp ), dimension(3, nLocal) :: q
1291 <    !! molecular center-of-mass position array
1292 <    real ( kind = dp ), dimension(3, nGroups) :: q_group
1293 <    !! Rotation Matrix for each long range particle in simulation.
1294 <    real( kind = dp), dimension(9, nLocal) :: A    
1295 <    !! Unit vectors for dipoles (lab frame)
1296 <    real( kind = dp ), dimension(9,nLocal) :: eFrame
1297 <    !! Force array provided by C, dimensioned by getNlocal
1298 <    real ( kind = dp ), dimension(3,nLocal) :: f
1299 <    !! Torsion array provided by C, dimensioned by getNlocal
1300 <    real( kind = dp ), dimension(3,nLocal) :: t    
1382 >    virial_Temp = virial_Temp + &
1383 >         (tau_Temp(1) + tau_Temp(5) + tau_Temp(9))
1384  
1385 <    !! Stress Tensor
1386 <    real( kind = dp), dimension(9) :: tau  
1387 <    real ( kind = dp ) :: pot
1305 <    logical ( kind = 2) :: do_pot_c, do_stress_c
1306 <    integer :: error
1307 <    
1308 <    call do_force_loop(q, q_group, A, eFrame, f, t, tau, pot, &
1309 <       do_pot_c, do_stress_c, error)
1310 <      
1311 < end subroutine doForceloop
1385 >  end subroutine add_stress_tensor
1386 >
1387 > end module doForces

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines