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

Comparing trunk/OOPSE-2.0/src/UseTheForce/doForces.F90 (file contents):
Revision 2267 by tim, Fri Jul 29 17:34:06 2005 UTC vs.
Revision 2275 by gezelter, Fri Aug 26 16:36:16 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.31 2005-08-26 16:36:16 gezelter Exp $, $Date: 2005-08-26 16:36:16 $, $Name: not supported by cvs2svn $, $Revision: 1.31 $
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 170 | Line 152 | contains
152      logical :: j_is_GB
153      logical :: j_is_EAM
154      logical :: j_is_Shape
155 <    
156 <    status = 0
157 <    
155 >    real(kind=dp) :: myRcut
156 >
157 >    status = 0  
158 >
159      if (.not. associated(atypes)) then
160 <       call handleError("atype", "atypes was not present before call of createDefaultInteractionMap!")
160 >       call handleError("atype", "atypes was not present before call of createInteractionHash!")
161         status = -1
162         return
163      endif
# Line 186 | Line 169 | contains
169         return
170      end if
171  
172 <    if (.not. allocated(InteractionMap)) then
173 <       allocate(InteractionMap(nAtypes,nAtypes))
172 >    if (.not. allocated(InteractionHash)) then
173 >       allocate(InteractionHash(nAtypes,nAtypes))
174      endif
175 +
176 +    if (.not. allocated(atypeMaxCutoff)) then
177 +       allocate(atypeMaxCutoff(nAtypes))
178 +    endif
179          
180      do i = 1, nAtypes
181         call getElementProperty(atypes, i, "is_LennardJones", i_is_LJ)
# Line 241 | Line 228 | contains
228            if (i_is_LJ .and. j_is_Shape) iHash = ior(iHash, SHAPE_LJ)
229  
230  
231 <          InteractionMap(i,j)%InteractionHash = iHash
232 <          InteractionMap(j,i)%InteractionHash = iHash
231 >          InteractionHash(i,j) = iHash
232 >          InteractionHash(j,i) = iHash
233  
234         end do
235  
236      end do
237  
238 <    haveInteractionMap = .true.
239 <  end subroutine createInteractionMap
238 >    haveInteractionHash = .true.
239 >  end subroutine createInteractionHash
240  
241 < ! 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
241 >  subroutine createGtypeCutoffMap(stat)
242  
243 <    stat = 0
244 <    if (.not. haveInteractionMap) then
243 >    integer, intent(out), optional :: stat
244 >    logical :: i_is_LJ
245 >    logical :: i_is_Elect
246 >    logical :: i_is_Sticky
247 >    logical :: i_is_StickyP
248 >    logical :: i_is_GB
249 >    logical :: i_is_EAM
250 >    logical :: i_is_Shape
251  
252 <       call createInteractionMap(myStatus)
252 >    integer :: myStatus, nAtypes,  i, j, istart, iend, jstart, jend
253 >    integer :: n_in_i
254 >    real(kind=dp):: thisSigma, bigSigma, thisRcut
255 >    real(kind=dp) :: biggestAtypeCutoff
256  
257 +    stat = 0
258 +    if (.not. haveInteractionHash) then
259 +       call createInteractionHash(myStatus)      
260         if (myStatus .ne. 0) then
261 <          write(default_error, *) 'createInteractionMap failed in doForces!'
261 >          write(default_error, *) 'createInteractionHash failed in doForces!'
262            stat = -1
263            return
264         endif
265      endif
266  
277
267      nAtypes = getSize(atypes)
268 <    !! If we pass a default rcut, set all atypes to that cutoff distance
269 <    if(present(defaultRList)) then
270 <       InteractionMap(:,:)%rList = defaultRList
271 <       InteractionMap(:,:)%rListSq = defaultRList*defaultRList
272 <       haveRlist = .true.
273 <       return
274 <    end if
275 <
276 <    do map_i = 1,nAtypes
277 <       do map_j = map_i,nAtypes
289 <          iMap = InteractionMap(map_i, map_j)%InteractionHash
268 >    
269 >    do i = 1, nAtypes
270 >       if (SimHasAtype(i)) then          
271 >          call getElementProperty(atypes, i, "is_LennardJones", i_is_LJ)
272 >          call getElementProperty(atypes, i, "is_Electrostatic", i_is_Elect)
273 >          call getElementProperty(atypes, i, "is_Sticky", i_is_Sticky)
274 >          call getElementProperty(atypes, i, "is_StickyPower", i_is_StickyP)
275 >          call getElementProperty(atypes, i, "is_GayBerne", i_is_GB)
276 >          call getElementProperty(atypes, i, "is_EAM", i_is_EAM)
277 >          call getElementProperty(atypes, i, "is_Shape", i_is_Shape)
278            
279 <          if ( iand(iMap, LJ_PAIR).ne.0 ) then
280 <             ! thisRCut = getLJCutOff(map_i,map_j)
281 <             if (thisRcut > actualCutoff) actualCutoff = thisRcut
279 >          if (i_is_LJ) then
280 >             thisRcut = getSigma(i) * 2.5_dp
281 >             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
282            endif
283 <          
284 <          if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
285 <             ! thisRCut = getElectrostaticCutOff(map_i,map_j)
298 <             if (thisRcut > actualCutoff) actualCutoff = thisRcut
283 >          if (i_is_Elect) then
284 >             thisRcut = defaultRcut
285 >             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
286            endif
287 +          if (i_is_Sticky) then
288 +             thisRcut = getStickyCut(i)
289 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
290 +          endif
291 +          if (i_is_StickyP) then
292 +             thisRcut = getStickyPowerCut(i)
293 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
294 +          endif
295 +          if (i_is_GB) then
296 +             thisRcut = getGayBerneCut(i)
297 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
298 +          endif
299 +          if (i_is_EAM) then
300 +             thisRcut = getEAMCut(i)
301 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
302 +          endif
303 +          if (i_is_Shape) then
304 +             thisRcut = getShapeCut(i)
305 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
306 +          endif
307            
308 <          if ( iand(iMap, STICKY_PAIR).ne.0 ) then
309 <             ! thisRCut = getStickyCutOff(map_i,map_j)
310 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
311 <           endif
312 <          
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
308 >          if (atypeMaxCutoff(i).gt.biggestAtypeCutoff) then
309 >             biggestAtypeCutoff = atypeMaxCutoff(i)
310 >          endif
311 >       endif
312 >    enddo
313  
314 +    istart = 1
315 + #ifdef IS_MPI
316 +    iend = nGroupsInRow
317 + #else
318 +    iend = nGroups
319 + #endif
320 +    outer: do i = istart, iend
321 +      
322 +       n_in_i = groupStartRow(i+1) - groupStartRow(i)
323 +      
324 + #ifdef IS_MPI
325 +       jstart = 1
326 +       jend = nGroupsInCol
327 + #else
328 +       jstart = i+1
329 +       jend = nGroups
330 + #endif
331 +      
332 +      
333 +      
334 +      
335 +      
336 +      
337 +    enddo outer        
338 +    
339 +     haveGtypeCutoffMap = .true.
340 +   end subroutine createGtypeCutoffMap
341 +
342 +   subroutine setDefaultCutoffs(defRcut, defRsw, defRlist, cutPolicy)
343 +     real(kind=dp),intent(in) :: defRcut, defRsw, defRlist
344 +     integer, intent(in) :: cutPolicy
345  
346 < !!! THIS GOES AWAY FOR SIZE DEPENDENT CUTOFF
347 < !!$  subroutine setRlistDF( this_rlist )
348 < !!$
349 < !!$   real(kind=dp) :: this_rlist
350 < !!$
348 < !!$    rlist = this_rlist
349 < !!$    rlistsq = rlist * rlist
350 < !!$
351 < !!$    haveRlist = .true.
352 < !!$
353 < !!$  end subroutine setRlistDF
346 >     defaultRcut = defRcut
347 >     defaultRsw = defRsw
348 >     defaultRlist = defRlist
349 >     cutoffPolicy = cutPolicy
350 >   end subroutine setDefaultCutoffs
351  
352 +   subroutine setCutoffPolicy(cutPolicy)
353  
354 +     integer, intent(in) :: cutPolicy
355 +     cutoffPolicy = cutPolicy
356 +     call createGtypeCutoffMap()
357 +
358 +   end subroutine setCutoffPolicy
359 +    
360 +    
361    subroutine setSimVariables()
362      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()
363      SIM_uses_EAM = SimUsesEAM()
366    SIM_uses_Shapes = SimUsesShapes()
367    SIM_uses_FLARB = SimUsesFLARB()
364      SIM_uses_RF = SimUsesRF()
365      SIM_requires_postpair_calc = SimRequiresPostpairCalc()
366      SIM_requires_prepair_calc = SimRequiresPrepairCalc()
# Line 382 | Line 378 | contains
378  
379      error = 0
380  
381 <    if (.not. haveInteractionMap) then
381 >    if (.not. haveInteractionHash) then      
382 >       myStatus = 0      
383 >       call createInteractionHash(myStatus)      
384 >       if (myStatus .ne. 0) then
385 >          write(default_error, *) 'createInteractionHash failed in doForces!'
386 >          error = -1
387 >          return
388 >       endif
389 >    endif
390  
391 <       myStatus = 0
392 <
393 <       call createInteractionMap(myStatus)
390 <
391 >    if (.not. haveGtypeCutoffMap) then        
392 >       myStatus = 0      
393 >       call createGtypeCutoffMap(myStatus)      
394         if (myStatus .ne. 0) then
395 <          write(default_error, *) 'createInteractionMap failed in doForces!'
395 >          write(default_error, *) 'createGtypeCutoffMap failed in doForces!'
396            error = -1
397            return
398         endif
# Line 450 | Line 453 | contains
453      !! interactions are used by the force field.    
454  
455      FF_uses_DirectionalAtoms = .false.
453    FF_uses_LennardJones = .false.
454    FF_uses_Electrostatics = .false.
455    FF_uses_Charges = .false.    
456      FF_uses_Dipoles = .false.
457    FF_uses_Sticky = .false.
458    FF_uses_StickyPower = .false.
457      FF_uses_GayBerne = .false.
458      FF_uses_EAM = .false.
461    FF_uses_Shapes = .false.
462    FF_uses_FLARB = .false.
459  
460      call getMatchingElementList(atypes, "is_Directional", .true., &
461           nMatches, MatchList)
462      if (nMatches .gt. 0) FF_uses_DirectionalAtoms = .true.
463  
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
464      call getMatchingElementList(atypes, "is_Dipole", .true., &
465           nMatches, MatchList)
466 <    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
466 >    if (nMatches .gt. 0) FF_uses_Dipoles = .true.
467      
468      call getMatchingElementList(atypes, "is_GayBerne", .true., &
469           nMatches, MatchList)
470 <    if (nMatches .gt. 0) then
518 <       FF_uses_GayBerne = .true.
519 <       FF_uses_DirectionalAtoms = .true.
520 <    endif
470 >    if (nMatches .gt. 0) FF_uses_GayBerne = .true.
471  
472      call getMatchingElementList(atypes, "is_EAM", .true., nMatches, MatchList)
473      if (nMatches .gt. 0) FF_uses_EAM = .true.
474  
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
475  
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)
476      haveSaneForceField = .true.
477  
478      !! check to make sure the FF_uses_RF setting makes sense
479  
480 <    if (FF_uses_dipoles) then
480 >    if (FF_uses_Dipoles) then
481         if (FF_uses_RF) then
482            dielect = getDielect()
483            call initialize_rf(dielect)
# Line 552 | Line 491 | contains
491         endif
492      endif
493  
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
494      if (FF_uses_EAM) then
495         call init_EAM_FF(my_status)
496         if (my_status /= 0) then
# Line 579 | Line 508 | contains
508            haveSaneForceField = .false.
509            return
510         endif
582    endif
583
584    if (FF_uses_GayBerne .and. FF_uses_LennardJones) then
511      endif
512  
513      if (.not. haveNeighborList) then
# Line 647 | Line 573 | contains
573      integer :: localError
574      integer :: propPack_i, propPack_j
575      integer :: loopStart, loopEnd, loop
576 <    integer :: iMap
576 >    integer :: iHash
577      real(kind=dp) :: listSkin = 1.0  
578  
579      !! initialize local variables  
# Line 739 | Line 665 | contains
665   #endif
666         outer: do i = istart, iend
667  
742 #ifdef IS_MPI
743             me_i = atid_row(i)
744 #else
745             me_i = atid(i)
746 #endif
747
668            if (update_nlist) point(i) = nlist + 1
669  
670            n_in_i = groupStartRow(i+1) - groupStartRow(i)
# Line 781 | Line 701 | contains
701                    q_group(:,j), d_grp, rgrpsq)
702   #endif
703  
704 <             if (rgrpsq < InteractionMap(me_i,me_j)%rListsq) then
704 >             if (rgrpsq < InteractionHash(me_i,me_j)%rListsq) then
705                  if (update_nlist) then
706                     nlist = nlist + 1
707  
# Line 999 | Line 919 | contains
919   #else
920               me_i = atid(i)
921   #endif
922 <             iMap = InteractionMap(me_i, me_j)%InteractionHash
922 >             iHash = InteractionHash(me_i,me_j)
923              
924 <             if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
924 >             if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then
925  
926                  mu_i = getDipoleMoment(me_i)
927  
# Line 1068 | Line 988 | contains
988      real ( kind = dp ) :: ebalance
989      integer :: me_i, me_j
990  
991 <    integer :: iMap
991 >    integer :: iHash
992  
993      r = sqrt(rijsq)
994      vpair = 0.0d0
# Line 1082 | Line 1002 | contains
1002      me_j = atid(j)
1003   #endif
1004  
1005 <    iMap = InteractionMap(me_i, me_j)%InteractionHash
1005 >    iHash = InteractionHash(me_i, me_j)
1006  
1007 <    if ( iand(iMap, LJ_PAIR).ne.0 ) then
1007 >    if ( iand(iHash, LJ_PAIR).ne.0 ) then
1008         call do_lj_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot)
1009      endif
1010  
1011 <    if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
1011 >    if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then
1012         call doElectrostaticPair(i, j, d, r, rijsq, sw, vpair, fpair, &
1013              pot, eFrame, f, t, do_pot)
1014  
# Line 1101 | Line 1021 | contains
1021  
1022      endif
1023  
1024 <    if ( iand(iMap, STICKY_PAIR).ne.0 ) then
1024 >    if ( iand(iHash, STICKY_PAIR).ne.0 ) then
1025         call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1026              pot, A, f, t, do_pot)
1027      endif
1028  
1029 <    if ( iand(iMap, STICKYPOWER_PAIR).ne.0 ) then
1029 >    if ( iand(iHash, STICKYPOWER_PAIR).ne.0 ) then
1030         call do_sticky_power_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1031              pot, A, f, t, do_pot)
1032      endif
1033  
1034 <    if ( iand(iMap, GAYBERNE_PAIR).ne.0 ) then
1034 >    if ( iand(iHash, GAYBERNE_PAIR).ne.0 ) then
1035         call do_gb_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1036              pot, A, f, t, do_pot)
1037      endif
1038      
1039 <    if ( iand(iMap, GAYBERNE_LJ).ne.0 ) then
1039 >    if ( iand(iHash, GAYBERNE_LJ).ne.0 ) then
1040   !      call do_gblj_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1041   !           pot, A, f, t, do_pot)
1042      endif
1043  
1044 <    if ( iand(iMap, EAM_PAIR).ne.0 ) then      
1044 >    if ( iand(iHash, EAM_PAIR).ne.0 ) then      
1045         call do_eam_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, &
1046              do_pot)
1047      endif
1048  
1049 <    if ( iand(iMap, SHAPE_PAIR).ne.0 ) then      
1049 >    if ( iand(iHash, SHAPE_PAIR).ne.0 ) then      
1050         call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1051              pot, A, f, t, do_pot)
1052      endif
1053  
1054 <    if ( iand(iMap, SHAPE_LJ).ne.0 ) then      
1054 >    if ( iand(iHash, SHAPE_LJ).ne.0 ) then      
1055         call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1056              pot, A, f, t, do_pot)
1057      endif
# Line 1153 | Line 1073 | contains
1073      real ( kind = dp )                :: r, rc
1074      real ( kind = dp ), intent(inout) :: d(3), dc(3)
1075  
1076 <    integer :: me_i, me_j, iMap
1076 >    integer :: me_i, me_j, iHash
1077  
1078   #ifdef IS_MPI  
1079      me_i = atid_row(i)
# Line 1163 | Line 1083 | contains
1083      me_j = atid(j)  
1084   #endif
1085  
1086 <    iMap = InteractionMap(me_i, me_j)%InteractionHash
1086 >    iHash = InteractionHash(me_i, me_j)
1087  
1088 <    if ( iand(iMap, EAM_PAIR).ne.0 ) then      
1088 >    if ( iand(iHash, EAM_PAIR).ne.0 ) then      
1089              call calc_EAM_prepair_rho(i, j, d, r, rijsq )
1090      endif
1091      
# Line 1362 | Line 1282 | contains
1282  
1283    function FF_UsesDirectionalAtoms() result(doesit)
1284      logical :: doesit
1285 <    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
1285 >    doesit = FF_uses_DirectionalAtoms
1286    end function FF_UsesDirectionalAtoms
1287  
1288    function FF_RequiresPrepairCalc() result(doesit)

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines