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 2267 by tim, Fri Jul 29 17:34:06 2005 UTC vs.
Revision 2273 by gezelter, Thu Aug 11 21:04:03 2005 UTC

# Line 45 | Line 45
45  
46   !! @author Charles F. Vardeman II
47   !! @author Matthew Meineke
48 < !! @version $Id: doForces.F90,v 1.25 2005-07-29 17:34:06 tim Exp $, $Date: 2005-07-29 17:34:06 $, $Name: not supported by cvs2svn $, $Revision: 1.25 $
48 > !! @version $Id: doForces.F90,v 1.29 2005-08-11 21:04:03 gezelter Exp $, $Date: 2005-08-11 21:04:03 $, $Name: not supported by cvs2svn $, $Revision: 1.29 $
49  
50  
51   module doForces
# Line 73 | Line 73 | module doForces
73  
74   #define __FORTRAN90
75   #include "UseTheForce/fSwitchingFunction.h"
76 + #include "UseTheForce/fCutoffPolicy.h"
77   #include "UseTheForce/DarkSide/fInteractionMap.h"
78  
79 +
80    INTEGER, PARAMETER:: PREPAIR_LOOP = 1
81    INTEGER, PARAMETER:: PAIR_LOOP    = 2
82  
81  logical, save :: haveRlist = .false.
83    logical, save :: haveNeighborList = .false.
84    logical, save :: haveSIMvariables = .false.
85    logical, save :: haveSaneForceField = .false.
86 <  logical, save :: haveInteractionMap = .false.
86 >  logical, save :: haveInteractionHash = .false.
87 >  logical, save :: haveGtypeCutoffMap = .false.
88  
89    logical, save :: FF_uses_DirectionalAtoms
88  logical, save :: FF_uses_LennardJones
89  logical, save :: FF_uses_Electrostatics
90  logical, save :: FF_uses_Charges
90    logical, save :: FF_uses_Dipoles
92  logical, save :: FF_uses_Quadrupoles
93  logical, save :: FF_uses_Sticky
94  logical, save :: FF_uses_StickyPower
91    logical, save :: FF_uses_GayBerne
92    logical, save :: FF_uses_EAM
97  logical, save :: FF_uses_Shapes
98  logical, save :: FF_uses_FLARB
93    logical, save :: FF_uses_RF
94  
95    logical, save :: SIM_uses_DirectionalAtoms
102  logical, save :: SIM_uses_LennardJones
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
96    logical, save :: SIM_uses_EAM
111  logical, save :: SIM_uses_Shapes
112  logical, save :: SIM_uses_FLARB
97    logical, save :: SIM_uses_RF
98    logical, save :: SIM_requires_postpair_calc
99    logical, save :: SIM_requires_prepair_calc
100    logical, save :: SIM_uses_PBC
117  logical, save :: SIM_uses_molecular_cutoffs
101  
119  !!!GO AWAY---------
120  !!!!!real(kind=dp), save :: rlist, rlistsq
121
102    public :: init_FF
103 +  public :: setDefaultCutoffs
104    public :: do_force_loop
105 < !  public :: setRlistDF
106 <  !public :: addInteraction
126 <  !public :: setInteractionHash
127 <  !public :: getInteractionHash
128 <  public :: createInteractionMap
129 <  public :: createRcuts
105 >  public :: createInteractionHash
106 >  public :: createGtypeCutoffMap
107  
108   #ifdef PROFILE
109    public :: getforcetime
# Line 134 | Line 111 | module doForces
111    real :: forceTimeInitial, forceTimeFinal
112    integer :: nLoops
113   #endif
137
138  type, public :: Interaction
139     integer :: InteractionHash
140     real(kind=dp) :: rList = 0.0_dp
141     real(kind=dp) :: rListSq = 0.0_dp
142  end type Interaction
114    
115 <  type(Interaction), dimension(:,:),allocatable :: InteractionMap
116 <  
115 >  !! Variables for cutoff mapping and interaction mapping
116 >  ! Bit hash to determine pair-pair interactions.
117 >  integer, dimension(:,:), allocatable :: InteractionHash
118 >  real(kind=dp), dimension(:), allocatable :: atypeMaxCutoff
119 >  real(kind=dp), dimension(:), allocatable :: groupMaxCutoff
120 >  integer, dimension(:), allocatable :: groupToGtype
121 >  real(kind=dp), dimension(:), allocatable :: gtypeMaxCutoff
122 >  type ::gtypeCutoffs
123 >     real(kind=dp) :: rcut
124 >     real(kind=dp) :: rcutsq
125 >     real(kind=dp) :: rlistsq
126 >  end type gtypeCutoffs
127 >  type(gtypeCutoffs), dimension(:,:), allocatable :: gtypeCutoffMap
128  
129 +  integer, save :: cutoffPolicy = TRADITIONAL_CUTOFF_POLICY
130 +  real(kind=dp),save :: defaultRcut, defaultRsw, defaultRlist
131    
132   contains
133  
134 <
151 <  subroutine createInteractionMap(status)
134 >  subroutine createInteractionHash(status)
135      integer :: nAtypes
136      integer, intent(out) :: status
137      integer :: i
138      integer :: j
139 <    integer :: ihash
157 <    real(kind=dp) :: myRcut
139 >    integer :: iHash
140      !! Test Types
141      logical :: i_is_LJ
142      logical :: i_is_Elect
# Line 171 | Line 153 | contains
153      logical :: j_is_EAM
154      logical :: j_is_Shape
155      
156 <    status = 0
157 <    
156 >    status = 0  
157 >
158      if (.not. associated(atypes)) then
159 <       call handleError("atype", "atypes was not present before call of createDefaultInteractionMap!")
159 >       call handleError("atype", "atypes was not present before call of createInteractionHash!")
160         status = -1
161         return
162      endif
# Line 186 | Line 168 | contains
168         return
169      end if
170  
171 <    if (.not. allocated(InteractionMap)) then
172 <       allocate(InteractionMap(nAtypes,nAtypes))
171 >    if (.not. allocated(InteractionHash)) then
172 >       allocate(InteractionHash(nAtypes,nAtypes))
173      endif
174 +
175 +    if (.not. allocated(atypeMaxCutoff)) then
176 +       allocate(atypeMaxCutoff(nAtypes))
177 +    endif
178          
179      do i = 1, nAtypes
180         call getElementProperty(atypes, i, "is_LennardJones", i_is_LJ)
# Line 241 | Line 227 | contains
227            if (i_is_LJ .and. j_is_Shape) iHash = ior(iHash, SHAPE_LJ)
228  
229  
230 <          InteractionMap(i,j)%InteractionHash = iHash
231 <          InteractionMap(j,i)%InteractionHash = iHash
230 >          InteractionHash(i,j) = iHash
231 >          InteractionHash(j,i) = iHash
232  
233         end do
234  
235      end do
236  
237 <    haveInteractionMap = .true.
238 <  end subroutine createInteractionMap
253 <
254 < ! Query each potential and return the cutoff for that potential. We build the neighbor list based on the largest cutoff value for that atype. Each potential can decide whether to calculate the force for that atype based upon it's own cutoff.
255 <  subroutine createRcuts(defaultRList,stat)
256 <    real(kind=dp), intent(in), optional :: defaultRList
257 <    integer :: iMap
258 <    integer :: map_i,map_j
259 <    real(kind=dp) :: thisRCut = 0.0_dp
260 <    real(kind=dp) :: actualCutoff = 0.0_dp
261 <    integer, intent(out) :: stat
262 <    integer :: nAtypes
263 <    integer :: myStatus
237 >    haveInteractionHash = .true.
238 >  end subroutine createInteractionHash
239  
240 <    stat = 0
266 <    if (.not. haveInteractionMap) then
240 >  subroutine createGtypeCutoffMap()
241  
242 <       call createInteractionMap(myStatus)
242 >    logical :: i_is_LJ
243 >    logical :: i_is_Elect
244 >    logical :: i_is_Sticky
245 >    logical :: i_is_StickyP
246 >    logical :: i_is_GB
247 >    logical :: i_is_EAM
248 >    logical :: i_is_Shape
249  
250 +    integer :: myStatus, nAtypes
251 +
252 +    stat = 0
253 +    if (.not. haveInteractionHash) then
254 +       call createInteractionHash(myStatus)      
255         if (myStatus .ne. 0) then
256 <          write(default_error, *) 'createInteractionMap failed in doForces!'
256 >          write(default_error, *) 'createInteractionHash failed in doForces!'
257            stat = -1
258            return
259         endif
260      endif
261  
277
262      nAtypes = getSize(atypes)
279    !! If we pass a default rcut, set all atypes to that cutoff distance
280    if(present(defaultRList)) then
281       InteractionMap(:,:)%rList = defaultRList
282       InteractionMap(:,:)%rListSq = defaultRList*defaultRList
283       haveRlist = .true.
284       return
285    end if
263  
264 <    do map_i = 1,nAtypes
265 <       do map_j = map_i,nAtypes
266 <          iMap = InteractionMap(map_i, map_j)%InteractionHash
267 <          
268 <          if ( iand(iMap, LJ_PAIR).ne.0 ) then
269 <             ! thisRCut = getLJCutOff(map_i,map_j)
270 <             if (thisRcut > actualCutoff) actualCutoff = thisRcut
271 <          endif
272 <          
273 <          if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
274 <             ! thisRCut = getElectrostaticCutOff(map_i,map_j)
275 <             if (thisRcut > actualCutoff) actualCutoff = thisRcut
276 <          endif
277 <          
278 <          if ( iand(iMap, STICKY_PAIR).ne.0 ) then
279 <             ! thisRCut = getStickyCutOff(map_i,map_j)
303 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
304 <           endif
305 <          
306 <           if ( iand(iMap, STICKYPOWER_PAIR).ne.0 ) then
307 <              ! thisRCut = getStickyPowerCutOff(map_i,map_j)
308 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
309 <           endif
310 <          
311 <           if ( iand(iMap, GAYBERNE_PAIR).ne.0 ) then
312 <              ! thisRCut = getGayberneCutOff(map_i,map_j)
313 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
314 <           endif
315 <          
316 <           if ( iand(iMap, GAYBERNE_LJ).ne.0 ) then
317 < !              thisRCut = getGaybrneLJCutOff(map_i,map_j)
318 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
319 <           endif
320 <          
321 <           if ( iand(iMap, EAM_PAIR).ne.0 ) then      
322 < !              thisRCut = getEAMCutOff(map_i,map_j)
323 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
324 <           endif
325 <          
326 <           if ( iand(iMap, SHAPE_PAIR).ne.0 ) then      
327 < !              thisRCut = getShapeCutOff(map_i,map_j)
328 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
329 <           endif
330 <          
331 <           if ( iand(iMap, SHAPE_LJ).ne.0 ) then      
332 < !              thisRCut = getShapeLJCutOff(map_i,map_j)
333 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
334 <           endif
335 <           InteractionMap(map_i, map_j)%rList = actualCutoff
336 <           InteractionMap(map_i, map_j)%rListSq = actualCutoff * actualCutoff
337 <        end do
338 <     end do
339 <     haveRlist = .true.
340 <  end subroutine createRcuts
341 <
342 <
343 < !!! THIS GOES AWAY FOR SIZE DEPENDENT CUTOFF
344 < !!$  subroutine setRlistDF( this_rlist )
345 < !!$
346 < !!$   real(kind=dp) :: this_rlist
347 < !!$
348 < !!$    rlist = this_rlist
349 < !!$    rlistsq = rlist * rlist
350 < !!$
351 < !!$    haveRlist = .true.
352 < !!$
353 < !!$  end subroutine setRlistDF
264 >    do i = 1, nAtypes
265 >       call getElementProperty(atypes, i, "is_LennardJones", i_is_LJ)
266 >       call getElementProperty(atypes, i, "is_Electrostatic", i_is_Elect)
267 >       call getElementProperty(atypes, i, "is_Sticky", i_is_Sticky)
268 >       call getElementProperty(atypes, i, "is_StickyPower", i_is_StickyP)
269 >       call getElementProperty(atypes, i, "is_GayBerne", i_is_GB)
270 >       call getElementProperty(atypes, i, "is_EAM", i_is_EAM)
271 >       call getElementProperty(atypes, i, "is_Shape", i_is_Shape)
272 >      
273 >       if (i_is_LJ) then
274 >          thisCut = getSigma(i) * DEFAULT_SIGMA_MULTIPLIER
275 >          if (thisCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisCut
276 >       endif
277 >       if (i_is_Elect) then
278 >          thisCut =
279 >    
280  
281  
282 +
283 +     haveGtypeCutoffMap = .true.
284 +   end subroutine createGtypeCutoffMap
285 +
286 +   subroutine setDefaultCutoffs(defRcut, defRsw, defRlist, cutPolicy)
287 +     real(kind=dp),intent(in) :: defRcut, defRsw, defRlist
288 +     integer, intent(in) :: cutPolicy
289 +
290 +     defaultRcut = defRcut
291 +     defaultRsw = defRsw
292 +     defaultRlist = defRlist
293 +     cutoffPolicy = cutPolicy
294 +   end subroutine setDefaultCutoffs
295 +
296 +   subroutine setCutoffPolicy(cutPolicy)
297 +
298 +     integer, intent(in) :: cutPolicy
299 +     cutoffPolicy = cutPolicy
300 +     call createGtypeCutoffMap()
301 +
302 +   end subroutine setDefaultCutoffs
303 +    
304 +    
305    subroutine setSimVariables()
306      SIM_uses_DirectionalAtoms = SimUsesDirectionalAtoms()
358    SIM_uses_LennardJones = SimUsesLennardJones()
359    SIM_uses_Electrostatics = SimUsesElectrostatics()
360    SIM_uses_Charges = SimUsesCharges()
361    SIM_uses_Dipoles = SimUsesDipoles()
362    SIM_uses_Sticky = SimUsesSticky()
363    SIM_uses_StickyPower = SimUsesStickyPower()
364    SIM_uses_GayBerne = SimUsesGayBerne()
307      SIM_uses_EAM = SimUsesEAM()
366    SIM_uses_Shapes = SimUsesShapes()
367    SIM_uses_FLARB = SimUsesFLARB()
308      SIM_uses_RF = SimUsesRF()
309      SIM_requires_postpair_calc = SimRequiresPostpairCalc()
310      SIM_requires_prepair_calc = SimRequiresPrepairCalc()
# Line 382 | Line 322 | contains
322  
323      error = 0
324  
325 <    if (.not. haveInteractionMap) then
325 >    if (.not. haveInteractionHash) then      
326 >       myStatus = 0      
327 >       call createInteractionHash(myStatus)      
328 >       if (myStatus .ne. 0) then
329 >          write(default_error, *) 'createInteractionHash failed in doForces!'
330 >          error = -1
331 >          return
332 >       endif
333 >    endif
334  
335 <       myStatus = 0
336 <
337 <       call createInteractionMap(myStatus)
390 <
335 >    if (.not. haveGtypeCutoffMap) then        
336 >       myStatus = 0      
337 >       call createGtypeCutoffMap(myStatus)      
338         if (myStatus .ne. 0) then
339 <          write(default_error, *) 'createInteractionMap failed in doForces!'
339 >          write(default_error, *) 'createGtypeCutoffMap failed in doForces!'
340            error = -1
341            return
342         endif
# Line 450 | Line 397 | contains
397      !! interactions are used by the force field.    
398  
399      FF_uses_DirectionalAtoms = .false.
453    FF_uses_LennardJones = .false.
454    FF_uses_Electrostatics = .false.
455    FF_uses_Charges = .false.    
400      FF_uses_Dipoles = .false.
457    FF_uses_Sticky = .false.
458    FF_uses_StickyPower = .false.
401      FF_uses_GayBerne = .false.
402      FF_uses_EAM = .false.
461    FF_uses_Shapes = .false.
462    FF_uses_FLARB = .false.
403  
404      call getMatchingElementList(atypes, "is_Directional", .true., &
405           nMatches, MatchList)
406      if (nMatches .gt. 0) FF_uses_DirectionalAtoms = .true.
407  
468    call getMatchingElementList(atypes, "is_LennardJones", .true., &
469         nMatches, MatchList)
470    if (nMatches .gt. 0) FF_uses_LennardJones = .true.
471
472    call getMatchingElementList(atypes, "is_Electrostatic", .true., &
473         nMatches, MatchList)
474    if (nMatches .gt. 0) then
475       FF_uses_Electrostatics = .true.
476    endif
477
478    call getMatchingElementList(atypes, "is_Charge", .true., &
479         nMatches, MatchList)
480    if (nMatches .gt. 0) then
481       FF_uses_Charges = .true.  
482       FF_uses_Electrostatics = .true.
483    endif
484
408      call getMatchingElementList(atypes, "is_Dipole", .true., &
409           nMatches, MatchList)
410 <    if (nMatches .gt. 0) then
488 <       FF_uses_Dipoles = .true.
489 <       FF_uses_Electrostatics = .true.
490 <       FF_uses_DirectionalAtoms = .true.
491 <    endif
492 <
493 <    call getMatchingElementList(atypes, "is_Quadrupole", .true., &
494 <         nMatches, MatchList)
495 <    if (nMatches .gt. 0) then
496 <       FF_uses_Quadrupoles = .true.
497 <       FF_uses_Electrostatics = .true.
498 <       FF_uses_DirectionalAtoms = .true.
499 <    endif
500 <
501 <    call getMatchingElementList(atypes, "is_Sticky", .true., nMatches, &
502 <         MatchList)
503 <    if (nMatches .gt. 0) then
504 <       FF_uses_Sticky = .true.
505 <       FF_uses_DirectionalAtoms = .true.
506 <    endif
507 <
508 <    call getMatchingElementList(atypes, "is_StickyPower", .true., nMatches, &
509 <         MatchList)
510 <    if (nMatches .gt. 0) then
511 <       FF_uses_StickyPower = .true.
512 <       FF_uses_DirectionalAtoms = .true.
513 <    endif
410 >    if (nMatches .gt. 0) FF_uses_Dipoles = .true.
411      
412      call getMatchingElementList(atypes, "is_GayBerne", .true., &
413           nMatches, MatchList)
414 <    if (nMatches .gt. 0) then
518 <       FF_uses_GayBerne = .true.
519 <       FF_uses_DirectionalAtoms = .true.
520 <    endif
414 >    if (nMatches .gt. 0) FF_uses_GayBerne = .true.
415  
416      call getMatchingElementList(atypes, "is_EAM", .true., nMatches, MatchList)
417      if (nMatches .gt. 0) FF_uses_EAM = .true.
418  
525    call getMatchingElementList(atypes, "is_Shape", .true., &
526         nMatches, MatchList)
527    if (nMatches .gt. 0) then
528       FF_uses_Shapes = .true.
529       FF_uses_DirectionalAtoms = .true.
530    endif
419  
532    call getMatchingElementList(atypes, "is_FLARB", .true., &
533         nMatches, MatchList)
534    if (nMatches .gt. 0) FF_uses_FLARB = .true.
535
536    !! Assume sanity (for the sake of argument)
420      haveSaneForceField = .true.
421  
422      !! check to make sure the FF_uses_RF setting makes sense
423  
424 <    if (FF_uses_dipoles) then
424 >    if (FF_uses_Dipoles) then
425         if (FF_uses_RF) then
426            dielect = getDielect()
427            call initialize_rf(dielect)
# Line 552 | Line 435 | contains
435         endif
436      endif
437  
555    !sticky module does not contain check_sticky_FF anymore
556    !if (FF_uses_sticky) then
557    !   call check_sticky_FF(my_status)
558    !   if (my_status /= 0) then
559    !      thisStat = -1
560    !      haveSaneForceField = .false.
561    !      return
562    !   end if
563    !endif
564
438      if (FF_uses_EAM) then
439         call init_EAM_FF(my_status)
440         if (my_status /= 0) then
# Line 579 | Line 452 | contains
452            haveSaneForceField = .false.
453            return
454         endif
582    endif
583
584    if (FF_uses_GayBerne .and. FF_uses_LennardJones) then
455      endif
456  
457      if (.not. haveNeighborList) then
# Line 647 | Line 517 | contains
517      integer :: localError
518      integer :: propPack_i, propPack_j
519      integer :: loopStart, loopEnd, loop
520 <    integer :: iMap
520 >    integer :: iHash
521      real(kind=dp) :: listSkin = 1.0  
522  
523      !! initialize local variables  
# Line 781 | Line 651 | contains
651                    q_group(:,j), d_grp, rgrpsq)
652   #endif
653  
654 <             if (rgrpsq < InteractionMap(me_i,me_j)%rListsq) then
654 >             if (rgrpsq < InteractionHash(me_i,me_j)%rListsq) then
655                  if (update_nlist) then
656                     nlist = nlist + 1
657  
# Line 999 | Line 869 | contains
869   #else
870               me_i = atid(i)
871   #endif
872 <             iMap = InteractionMap(me_i, me_j)%InteractionHash
872 >             iHash = InteractionHash(me_i,me_j)
873              
874 <             if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
874 >             if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then
875  
876                  mu_i = getDipoleMoment(me_i)
877  
# Line 1068 | Line 938 | contains
938      real ( kind = dp ) :: ebalance
939      integer :: me_i, me_j
940  
941 <    integer :: iMap
941 >    integer :: iHash
942  
943      r = sqrt(rijsq)
944      vpair = 0.0d0
# Line 1082 | Line 952 | contains
952      me_j = atid(j)
953   #endif
954  
955 <    iMap = InteractionMap(me_i, me_j)%InteractionHash
955 >    iHash = InteractionHash(me_i, me_j)
956  
957 <    if ( iand(iMap, LJ_PAIR).ne.0 ) then
957 >    if ( iand(iHash, LJ_PAIR).ne.0 ) then
958         call do_lj_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot)
959      endif
960  
961 <    if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
961 >    if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then
962         call doElectrostaticPair(i, j, d, r, rijsq, sw, vpair, fpair, &
963              pot, eFrame, f, t, do_pot)
964  
# Line 1101 | Line 971 | contains
971  
972      endif
973  
974 <    if ( iand(iMap, STICKY_PAIR).ne.0 ) then
974 >    if ( iand(iHash, STICKY_PAIR).ne.0 ) then
975         call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
976              pot, A, f, t, do_pot)
977      endif
978  
979 <    if ( iand(iMap, STICKYPOWER_PAIR).ne.0 ) then
979 >    if ( iand(iHash, STICKYPOWER_PAIR).ne.0 ) then
980         call do_sticky_power_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
981              pot, A, f, t, do_pot)
982      endif
983  
984 <    if ( iand(iMap, GAYBERNE_PAIR).ne.0 ) then
984 >    if ( iand(iHash, GAYBERNE_PAIR).ne.0 ) then
985         call do_gb_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
986              pot, A, f, t, do_pot)
987      endif
988      
989 <    if ( iand(iMap, GAYBERNE_LJ).ne.0 ) then
989 >    if ( iand(iHash, GAYBERNE_LJ).ne.0 ) then
990   !      call do_gblj_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
991   !           pot, A, f, t, do_pot)
992      endif
993  
994 <    if ( iand(iMap, EAM_PAIR).ne.0 ) then      
994 >    if ( iand(iHash, EAM_PAIR).ne.0 ) then      
995         call do_eam_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, &
996              do_pot)
997      endif
998  
999 <    if ( iand(iMap, SHAPE_PAIR).ne.0 ) then      
999 >    if ( iand(iHash, SHAPE_PAIR).ne.0 ) then      
1000         call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1001              pot, A, f, t, do_pot)
1002      endif
1003  
1004 <    if ( iand(iMap, SHAPE_LJ).ne.0 ) then      
1004 >    if ( iand(iHash, SHAPE_LJ).ne.0 ) then      
1005         call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1006              pot, A, f, t, do_pot)
1007      endif
# Line 1153 | Line 1023 | contains
1023      real ( kind = dp )                :: r, rc
1024      real ( kind = dp ), intent(inout) :: d(3), dc(3)
1025  
1026 <    integer :: me_i, me_j, iMap
1026 >    integer :: me_i, me_j, iHash
1027  
1028   #ifdef IS_MPI  
1029      me_i = atid_row(i)
# Line 1163 | Line 1033 | contains
1033      me_j = atid(j)  
1034   #endif
1035  
1036 <    iMap = InteractionMap(me_i, me_j)%InteractionHash
1036 >    iHash = InteractionHash(me_i, me_j)
1037  
1038 <    if ( iand(iMap, EAM_PAIR).ne.0 ) then      
1038 >    if ( iand(iHash, EAM_PAIR).ne.0 ) then      
1039              call calc_EAM_prepair_rho(i, j, d, r, rijsq )
1040      endif
1041      
# Line 1362 | Line 1232 | contains
1232  
1233    function FF_UsesDirectionalAtoms() result(doesit)
1234      logical :: doesit
1235 <    doesit = FF_uses_DirectionalAtoms .or. FF_uses_Dipoles .or. &
1366 <         FF_uses_Quadrupoles .or. FF_uses_Sticky .or. &
1367 <         FF_uses_StickyPower .or. FF_uses_GayBerne .or. FF_uses_Shapes
1235 >    doesit = FF_uses_DirectionalAtoms
1236    end function FF_UsesDirectionalAtoms
1237  
1238    function FF_RequiresPrepairCalc() result(doesit)

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines