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

Comparing trunk/OOPSE-3.0/src/UseTheForce/doForces.F90 (file contents):
Revision 2267 by tim, Fri Jul 29 17:34:06 2005 UTC vs.
Revision 2274 by gezelter, Wed Aug 17 15:26:42 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.30 2005-08-17 15:26:37 gezelter Exp $, $Date: 2005-08-17 15:26:37 $, $Name: not supported by cvs2svn $, $Revision: 1.30 $
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
237 >    haveInteractionHash = .true.
238 >  end subroutine createInteractionHash
239  
240 < ! 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
240 >  subroutine createGtypeCutoffMap()
241  
242 <    stat = 0
243 <    if (.not. haveInteractionMap) then
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 <       call createInteractionMap(myStatus)
250 >    integer :: myStatus, nAtypes
251 >    real(kind=dp):: thisSigma, bigSigma
252  
253 +    stat = 0
254 +    if (.not. haveInteractionHash) then
255 +       call createInteractionHash(myStatus)      
256         if (myStatus .ne. 0) then
257 <          write(default_error, *) 'createInteractionMap failed in doForces!'
257 >          write(default_error, *) 'createInteractionHash failed in doForces!'
258            stat = -1
259            return
260         endif
261      endif
262  
277
263      nAtypes = getSize(atypes)
264 <    !! If we pass a default rcut, set all atypes to that cutoff distance
265 <    if(present(defaultRList)) then
266 <       InteractionMap(:,:)%rList = defaultRList
267 <       InteractionMap(:,:)%rListSq = defaultRList*defaultRList
268 <       haveRlist = .true.
269 <       return
270 <    end if
271 <
272 <    do map_i = 1,nAtypes
273 <       do map_j = map_i,nAtypes
289 <          iMap = InteractionMap(map_i, map_j)%InteractionHash
264 >    
265 >    do i = 1, nAtypes
266 >       if (SimHasAtype(i)) then          
267 >          call getElementProperty(atypes, i, "is_LennardJones", i_is_LJ)
268 >          call getElementProperty(atypes, i, "is_Electrostatic", i_is_Elect)
269 >          call getElementProperty(atypes, i, "is_Sticky", i_is_Sticky)
270 >          call getElementProperty(atypes, i, "is_StickyPower", i_is_StickyP)
271 >          call getElementProperty(atypes, i, "is_GayBerne", i_is_GB)
272 >          call getElementProperty(atypes, i, "is_EAM", i_is_EAM)
273 >          call getElementProperty(atypes, i, "is_Shape", i_is_Shape)
274            
275 <          if ( iand(iMap, LJ_PAIR).ne.0 ) then
276 <             ! thisRCut = getLJCutOff(map_i,map_j)
277 <             if (thisRcut > actualCutoff) actualCutoff = thisRcut
275 >          if (i_is_LJ) then
276 >             thisRcut = getSigma(i) * 2.5_dp
277 >             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
278            endif
279 <          
280 <          if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
281 <             ! thisRCut = getElectrostaticCutOff(map_i,map_j)
298 <             if (thisRcut > actualCutoff) actualCutoff = thisRcut
279 >          if (i_is_Elect) then
280 >             thisRcut = defaultRcut
281 >             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
282            endif
283 +          if (i_is_Sticky) then
284 +             thisRcut = getStickyCut(i)
285 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
286 +          endif
287 +          if (i_is_StickyPower) then
288 +             thisRcut = getStickyPowerCut(i)
289 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
290 +          endif
291 +          if (i_is_GayBerne) then
292 +             thisRcut = getGayBerneCut(i)
293 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
294 +          endif
295 +          if (i_is_EAM) then
296 +             thisRcut = getEAMCut(i)
297 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
298 +          endif
299 +          if (i_is_Shape) then
300 +             thisRcut = getShapeCut(i)
301 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
302 +          endif
303            
304 <          if ( iand(iMap, STICKY_PAIR).ne.0 ) then
305 <             ! thisRCut = getStickyCutOff(map_i,map_j)
306 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
307 <           endif
308 <          
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
304 >          if (atypeMaxCutoff(i).gt.biggestAtypeCutoff) then
305 >             biggestAtypeCutoff = atypeMaxCutoff(i)
306 >          endif
307 >       endif
308 >    enddo
309  
310 +    istart = 1
311 + #ifdef IS_MPI
312 +    iend = nGroupsInRow
313 + #else
314 +    iend = nGroups
315 + #endif
316 +    outer: do i = istart, iend
317  
318 < !!! 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
318 >       n_in_i = groupStartRow(i+1) - groupStartRow(i)
319  
320 + #ifdef IS_MPI
321 +             jstart = 1
322 +             jend = nGroupsInCol
323 + #else
324 +             jstart = i+1
325 +             jend = nGroups
326 + #endif
327  
328 +
329 +
330 +            
331 +
332 +
333 +
334 +     haveGtypeCutoffMap = .true.
335 +   end subroutine createGtypeCutoffMap
336 +
337 +   subroutine setDefaultCutoffs(defRcut, defRsw, defRlist, cutPolicy)
338 +     real(kind=dp),intent(in) :: defRcut, defRsw, defRlist
339 +     integer, intent(in) :: cutPolicy
340 +
341 +     defaultRcut = defRcut
342 +     defaultRsw = defRsw
343 +     defaultRlist = defRlist
344 +     cutoffPolicy = cutPolicy
345 +   end subroutine setDefaultCutoffs
346 +
347 +   subroutine setCutoffPolicy(cutPolicy)
348 +
349 +     integer, intent(in) :: cutPolicy
350 +     cutoffPolicy = cutPolicy
351 +     call createGtypeCutoffMap()
352 +
353 +   end subroutine setDefaultCutoffs
354 +    
355 +    
356    subroutine setSimVariables()
357      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()
358      SIM_uses_EAM = SimUsesEAM()
366    SIM_uses_Shapes = SimUsesShapes()
367    SIM_uses_FLARB = SimUsesFLARB()
359      SIM_uses_RF = SimUsesRF()
360      SIM_requires_postpair_calc = SimRequiresPostpairCalc()
361      SIM_requires_prepair_calc = SimRequiresPrepairCalc()
# Line 382 | Line 373 | contains
373  
374      error = 0
375  
376 <    if (.not. haveInteractionMap) then
376 >    if (.not. haveInteractionHash) then      
377 >       myStatus = 0      
378 >       call createInteractionHash(myStatus)      
379 >       if (myStatus .ne. 0) then
380 >          write(default_error, *) 'createInteractionHash failed in doForces!'
381 >          error = -1
382 >          return
383 >       endif
384 >    endif
385  
386 <       myStatus = 0
387 <
388 <       call createInteractionMap(myStatus)
390 <
386 >    if (.not. haveGtypeCutoffMap) then        
387 >       myStatus = 0      
388 >       call createGtypeCutoffMap(myStatus)      
389         if (myStatus .ne. 0) then
390 <          write(default_error, *) 'createInteractionMap failed in doForces!'
390 >          write(default_error, *) 'createGtypeCutoffMap failed in doForces!'
391            error = -1
392            return
393         endif
# Line 450 | Line 448 | contains
448      !! interactions are used by the force field.    
449  
450      FF_uses_DirectionalAtoms = .false.
453    FF_uses_LennardJones = .false.
454    FF_uses_Electrostatics = .false.
455    FF_uses_Charges = .false.    
451      FF_uses_Dipoles = .false.
457    FF_uses_Sticky = .false.
458    FF_uses_StickyPower = .false.
452      FF_uses_GayBerne = .false.
453      FF_uses_EAM = .false.
461    FF_uses_Shapes = .false.
462    FF_uses_FLARB = .false.
454  
455      call getMatchingElementList(atypes, "is_Directional", .true., &
456           nMatches, MatchList)
457      if (nMatches .gt. 0) FF_uses_DirectionalAtoms = .true.
458  
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
459      call getMatchingElementList(atypes, "is_Dipole", .true., &
460           nMatches, MatchList)
461 <    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
461 >    if (nMatches .gt. 0) FF_uses_Dipoles = .true.
462      
463      call getMatchingElementList(atypes, "is_GayBerne", .true., &
464           nMatches, MatchList)
465 <    if (nMatches .gt. 0) then
518 <       FF_uses_GayBerne = .true.
519 <       FF_uses_DirectionalAtoms = .true.
520 <    endif
465 >    if (nMatches .gt. 0) FF_uses_GayBerne = .true.
466  
467      call getMatchingElementList(atypes, "is_EAM", .true., nMatches, MatchList)
468      if (nMatches .gt. 0) FF_uses_EAM = .true.
469  
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
470  
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)
471      haveSaneForceField = .true.
472  
473      !! check to make sure the FF_uses_RF setting makes sense
474  
475 <    if (FF_uses_dipoles) then
475 >    if (FF_uses_Dipoles) then
476         if (FF_uses_RF) then
477            dielect = getDielect()
478            call initialize_rf(dielect)
# Line 552 | Line 486 | contains
486         endif
487      endif
488  
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
489      if (FF_uses_EAM) then
490         call init_EAM_FF(my_status)
491         if (my_status /= 0) then
# Line 581 | Line 505 | contains
505         endif
506      endif
507  
584    if (FF_uses_GayBerne .and. FF_uses_LennardJones) then
585    endif
586
508      if (.not. haveNeighborList) then
509         !! Create neighbor lists
510         call expandNeighborList(nLocal, my_status)
# Line 647 | Line 568 | contains
568      integer :: localError
569      integer :: propPack_i, propPack_j
570      integer :: loopStart, loopEnd, loop
571 <    integer :: iMap
571 >    integer :: iHash
572      real(kind=dp) :: listSkin = 1.0  
573  
574      !! initialize local variables  
# Line 739 | Line 660 | contains
660   #endif
661         outer: do i = istart, iend
662  
742 #ifdef IS_MPI
743             me_i = atid_row(i)
744 #else
745             me_i = atid(i)
746 #endif
747
663            if (update_nlist) point(i) = nlist + 1
664  
665            n_in_i = groupStartRow(i+1) - groupStartRow(i)
# Line 781 | Line 696 | contains
696                    q_group(:,j), d_grp, rgrpsq)
697   #endif
698  
699 <             if (rgrpsq < InteractionMap(me_i,me_j)%rListsq) then
699 >             if (rgrpsq < InteractionHash(me_i,me_j)%rListsq) then
700                  if (update_nlist) then
701                     nlist = nlist + 1
702  
# Line 999 | Line 914 | contains
914   #else
915               me_i = atid(i)
916   #endif
917 <             iMap = InteractionMap(me_i, me_j)%InteractionHash
917 >             iHash = InteractionHash(me_i,me_j)
918              
919 <             if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
919 >             if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then
920  
921                  mu_i = getDipoleMoment(me_i)
922  
# Line 1068 | Line 983 | contains
983      real ( kind = dp ) :: ebalance
984      integer :: me_i, me_j
985  
986 <    integer :: iMap
986 >    integer :: iHash
987  
988      r = sqrt(rijsq)
989      vpair = 0.0d0
# Line 1082 | Line 997 | contains
997      me_j = atid(j)
998   #endif
999  
1000 <    iMap = InteractionMap(me_i, me_j)%InteractionHash
1000 >    iHash = InteractionHash(me_i, me_j)
1001  
1002 <    if ( iand(iMap, LJ_PAIR).ne.0 ) then
1002 >    if ( iand(iHash, LJ_PAIR).ne.0 ) then
1003         call do_lj_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot)
1004      endif
1005  
1006 <    if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
1006 >    if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then
1007         call doElectrostaticPair(i, j, d, r, rijsq, sw, vpair, fpair, &
1008              pot, eFrame, f, t, do_pot)
1009  
# Line 1101 | Line 1016 | contains
1016  
1017      endif
1018  
1019 <    if ( iand(iMap, STICKY_PAIR).ne.0 ) then
1019 >    if ( iand(iHash, STICKY_PAIR).ne.0 ) then
1020         call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1021              pot, A, f, t, do_pot)
1022      endif
1023  
1024 <    if ( iand(iMap, STICKYPOWER_PAIR).ne.0 ) then
1024 >    if ( iand(iHash, STICKYPOWER_PAIR).ne.0 ) then
1025         call do_sticky_power_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1026              pot, A, f, t, do_pot)
1027      endif
1028  
1029 <    if ( iand(iMap, GAYBERNE_PAIR).ne.0 ) then
1029 >    if ( iand(iHash, GAYBERNE_PAIR).ne.0 ) then
1030         call do_gb_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1031              pot, A, f, t, do_pot)
1032      endif
1033      
1034 <    if ( iand(iMap, GAYBERNE_LJ).ne.0 ) then
1034 >    if ( iand(iHash, GAYBERNE_LJ).ne.0 ) then
1035   !      call do_gblj_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1036   !           pot, A, f, t, do_pot)
1037      endif
1038  
1039 <    if ( iand(iMap, EAM_PAIR).ne.0 ) then      
1039 >    if ( iand(iHash, EAM_PAIR).ne.0 ) then      
1040         call do_eam_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, &
1041              do_pot)
1042      endif
1043  
1044 <    if ( iand(iMap, SHAPE_PAIR).ne.0 ) then      
1044 >    if ( iand(iHash, SHAPE_PAIR).ne.0 ) then      
1045         call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1046              pot, A, f, t, do_pot)
1047      endif
1048  
1049 <    if ( iand(iMap, SHAPE_LJ).ne.0 ) then      
1049 >    if ( iand(iHash, SHAPE_LJ).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
# Line 1153 | Line 1068 | contains
1068      real ( kind = dp )                :: r, rc
1069      real ( kind = dp ), intent(inout) :: d(3), dc(3)
1070  
1071 <    integer :: me_i, me_j, iMap
1071 >    integer :: me_i, me_j, iHash
1072  
1073   #ifdef IS_MPI  
1074      me_i = atid_row(i)
# Line 1163 | Line 1078 | contains
1078      me_j = atid(j)  
1079   #endif
1080  
1081 <    iMap = InteractionMap(me_i, me_j)%InteractionHash
1081 >    iHash = InteractionHash(me_i, me_j)
1082  
1083 <    if ( iand(iMap, EAM_PAIR).ne.0 ) then      
1083 >    if ( iand(iHash, EAM_PAIR).ne.0 ) then      
1084              call calc_EAM_prepair_rho(i, j, d, r, rijsq )
1085      endif
1086      
# Line 1362 | Line 1277 | contains
1277  
1278    function FF_UsesDirectionalAtoms() result(doesit)
1279      logical :: doesit
1280 <    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
1280 >    doesit = FF_uses_DirectionalAtoms
1281    end function FF_UsesDirectionalAtoms
1282  
1283    function FF_RequiresPrepairCalc() result(doesit)

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines