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 2262 by chuckv, Sun Jul 3 20:53:43 2005 UTC vs.
Revision 2277 by chrisfen, Fri Aug 26 21:30:41 2005 UTC

# Line 45 | Line 45
45  
46   !! @author Charles F. Vardeman II
47   !! @author Matthew Meineke
48 < !! @version $Id: doForces.F90,v 1.23 2005-07-03 20:53:43 chuckv Exp $, $Date: 2005-07-03 20:53:43 $, $Name: not supported by cvs2svn $, $Revision: 1.23 $
48 > !! @version $Id: doForces.F90,v 1.32 2005-08-26 21:30:30 chrisfen Exp $, $Date: 2005-08-26 21:30:30 $, $Name: not supported by cvs2svn $, $Revision: 1.32 $
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
107 <  !public :: setInteractionHash
108 <  !public :: getInteractionHash
109 <  public :: createInteractionMap
110 <  public :: createRcuts
105 >  public :: createInteractionHash
106 >  public :: createGtypeCutoffMap
107 >  public :: getStickyCut
108 >  public :: getStickyPowerCut
109 >  public :: getGayBerneCut
110 >  public :: getEAMCut
111 >  public :: getShapeCut
112  
113   #ifdef PROFILE
114    public :: getforcetime
# Line 134 | Line 116 | module doForces
116    real :: forceTimeInitial, forceTimeFinal
117    integer :: nLoops
118   #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
119    
120 <  type(Interaction), dimension(:,:),allocatable :: InteractionMap
121 <  
120 >  !! Variables for cutoff mapping and interaction mapping
121 >  ! Bit hash to determine pair-pair interactions.
122 >  integer, dimension(:,:), allocatable :: InteractionHash
123 >  real(kind=dp), dimension(:), allocatable :: atypeMaxCutoff
124 >  real(kind=dp), dimension(:), allocatable :: groupMaxCutoff
125 >  integer, dimension(:), allocatable :: groupToGtype
126 >  real(kind=dp), dimension(:), allocatable :: gtypeMaxCutoff
127 >  type ::gtypeCutoffs
128 >     real(kind=dp) :: rcut
129 >     real(kind=dp) :: rcutsq
130 >     real(kind=dp) :: rlistsq
131 >  end type gtypeCutoffs
132 >  type(gtypeCutoffs), dimension(:,:), allocatable :: gtypeCutoffMap
133  
134 +  integer, save :: cutoffPolicy = TRADITIONAL_CUTOFF_POLICY
135 +  real(kind=dp),save :: defaultRcut, defaultRsw, defaultRlist
136    
137   contains
138  
139 <
151 <  subroutine createInteractionMap(status)
139 >  subroutine createInteractionHash(status)
140      integer :: nAtypes
141 <    integer :: status
141 >    integer, intent(out) :: status
142      integer :: i
143      integer :: j
144 <    integer :: ihash
145 <    real(kind=dp) :: myRcut
158 < ! Test Types
144 >    integer :: iHash
145 >    !! Test Types
146      logical :: i_is_LJ
147      logical :: i_is_Elect
148      logical :: i_is_Sticky
# Line 170 | Line 157 | contains
157      logical :: j_is_GB
158      logical :: j_is_EAM
159      logical :: j_is_Shape
160 <    
161 <    
160 >    real(kind=dp) :: myRcut
161 >
162 >    status = 0  
163 >
164      if (.not. associated(atypes)) then
165 <       call handleError("atype", "atypes was not present before call of createDefaultInteractionMap!")
165 >       call handleError("atype", "atypes was not present before call of createInteractionHash!")
166         status = -1
167         return
168      endif
# Line 185 | Line 174 | contains
174         return
175      end if
176  
177 <    if (.not. allocated(InteractionMap)) then
178 <       allocate(InteractionMap(nAtypes,nAtypes))
177 >    if (.not. allocated(InteractionHash)) then
178 >       allocate(InteractionHash(nAtypes,nAtypes))
179      endif
180 +
181 +    if (.not. allocated(atypeMaxCutoff)) then
182 +       allocate(atypeMaxCutoff(nAtypes))
183 +    endif
184          
185      do i = 1, nAtypes
186         call getElementProperty(atypes, i, "is_LennardJones", i_is_LJ)
# Line 240 | Line 233 | contains
233            if (i_is_LJ .and. j_is_Shape) iHash = ior(iHash, SHAPE_LJ)
234  
235  
236 <          InteractionMap(i,j)%InteractionHash = iHash
237 <          InteractionMap(j,i)%InteractionHash = iHash
236 >          InteractionHash(i,j) = iHash
237 >          InteractionHash(j,i) = iHash
238  
239         end do
240  
241      end do
249  end subroutine createInteractionMap
242  
243 < ! 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.
244 <  subroutine createRcuts(defaultRList)
253 <    real(kind=dp), intent(in), optional :: defaultRList
254 <    integer :: iMap
255 <    integer :: map_i,map_j
256 <    real(kind=dp) :: thisRCut = 0.0_dp
257 <    real(kind=dp) :: actualCutoff = 0.0_dp
258 <    integer :: nAtypes
243 >    haveInteractionHash = .true.
244 >  end subroutine createInteractionHash
245  
246 <    if(.not. allocated(InteractionMap)) return
246 >  subroutine createGtypeCutoffMap(stat)
247 >
248 >    integer, intent(out), optional :: stat
249 >    logical :: i_is_LJ
250 >    logical :: i_is_Elect
251 >    logical :: i_is_Sticky
252 >    logical :: i_is_StickyP
253 >    logical :: i_is_GB
254 >    logical :: i_is_EAM
255 >    logical :: i_is_Shape
256  
257 <    nAtypes = getSize(atypes)
258 < ! If we pass a default rcut, set all atypes to that cutoff distance
259 <    if(present(defaultRList)) then
260 <       InteractionMap(:,:)%rList = defaultRList
266 <       InteractionMap(:,:)%rListSq = defaultRList*defaultRList
267 <       haveRlist = .true.
268 <       return
269 <    end if
257 >    integer :: myStatus, nAtypes,  i, j, istart, iend, jstart, jend
258 >    integer :: n_in_i
259 >    real(kind=dp):: thisSigma, bigSigma, thisRcut
260 >    real(kind=dp) :: biggestAtypeCutoff
261  
262 <    do map_i = 1,nAtypes
263 <       do map_j = map_i,nAtypes
264 <          iMap = InteractionMap(map_i, map_j)%InteractionHash
262 >    stat = 0
263 >    if (.not. haveInteractionHash) then
264 >       call createInteractionHash(myStatus)      
265 >       if (myStatus .ne. 0) then
266 >          write(default_error, *) 'createInteractionHash failed in doForces!'
267 >          stat = -1
268 >          return
269 >       endif
270 >    endif
271 >
272 >    nAtypes = getSize(atypes)
273 >    
274 >    do i = 1, nAtypes
275 >       if (SimHasAtype(i)) then          
276 >          call getElementProperty(atypes, i, "is_LennardJones", i_is_LJ)
277 >          call getElementProperty(atypes, i, "is_Electrostatic", i_is_Elect)
278 >          call getElementProperty(atypes, i, "is_Sticky", i_is_Sticky)
279 >          call getElementProperty(atypes, i, "is_StickyPower", i_is_StickyP)
280 >          call getElementProperty(atypes, i, "is_GayBerne", i_is_GB)
281 >          call getElementProperty(atypes, i, "is_EAM", i_is_EAM)
282 >          call getElementProperty(atypes, i, "is_Shape", i_is_Shape)
283            
284 <          if ( iand(iMap, LJ_PAIR).ne.0 ) then
285 < !            thisRCut = getLJCutOff(map_i,map_j)
286 <             if (thisRcut > actualCutoff) actualCutoff = thisRcut
284 >          if (i_is_LJ) then
285 >             thisRcut = getSigma(i) * 2.5_dp
286 >             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
287            endif
288 <          
289 <          if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
290 < !            thisRCut = getElectrostaticCutOff(map_i,map_j)
282 <             if (thisRcut > actualCutoff) actualCutoff = thisRcut
288 >          if (i_is_Elect) then
289 >             thisRcut = defaultRcut
290 >             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
291            endif
292 <          
293 <          if ( iand(iMap, STICKY_PAIR).ne.0 ) then
294 < !             thisRCut = getStickyCutOff(map_i,map_j)
295 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
296 <           endif
297 <          
298 <           if ( iand(iMap, STICKYPOWER_PAIR).ne.0 ) then
299 < !              thisRCut = getStickyPowerCutOff(map_i,map_j)
300 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
301 <           endif
302 <          
303 <           if ( iand(iMap, GAYBERNE_PAIR).ne.0 ) then
304 < !              thisRCut = getGayberneCutOff(map_i,map_j)
305 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
306 <           endif
307 <          
308 <           if ( iand(iMap, GAYBERNE_LJ).ne.0 ) then
309 < !              thisRCut = getGaybrneLJCutOff(map_i,map_j)
310 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
311 <           endif
312 <          
313 <           if ( iand(iMap, EAM_PAIR).ne.0 ) then      
314 < !              thisRCut = getEAMCutOff(map_i,map_j)
315 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
316 <           endif
317 <          
310 <           if ( iand(iMap, SHAPE_PAIR).ne.0 ) then      
311 < !              thisRCut = getShapeCutOff(map_i,map_j)
312 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
313 <           endif
314 <          
315 <           if ( iand(iMap, SHAPE_LJ).ne.0 ) then      
316 < !              thisRCut = getShapeLJCutOff(map_i,map_j)
317 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
318 <           endif
319 <           InteractionMap(map_i, map_j)%rList = actualCutoff
320 <           InteractionMap(map_i, map_j)%rListSq = actualCutoff * actualCutoff
321 <        end do
322 <     end do
323 <          haveRlist = .true.
324 <  end subroutine createRcuts
325 <
326 <
327 < !!! THIS GOES AWAY FOR SIZE DEPENDENT CUTOFF
328 < !!$  subroutine setRlistDF( this_rlist )
329 < !!$
330 < !!$   real(kind=dp) :: this_rlist
331 < !!$
332 < !!$    rlist = this_rlist
333 < !!$    rlistsq = rlist * rlist
334 < !!$
335 < !!$    haveRlist = .true.
336 < !!$
337 < !!$  end subroutine setRlistDF
292 >          if (i_is_Sticky) then
293 >             thisRcut = getStickyCut(i)
294 >             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
295 >          endif
296 >          if (i_is_StickyP) then
297 >             thisRcut = getStickyPowerCut(i)
298 >             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
299 >          endif
300 >          if (i_is_GB) then
301 >             thisRcut = getGayBerneCut(i)
302 >             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
303 >          endif
304 >          if (i_is_EAM) then
305 >             thisRcut = getEAMCut(i)
306 >             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
307 >          endif
308 >          if (i_is_Shape) then
309 >             thisRcut = getShapeCut(i)
310 >             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
311 >          endif
312 >          
313 >          if (atypeMaxCutoff(i).gt.biggestAtypeCutoff) then
314 >             biggestAtypeCutoff = atypeMaxCutoff(i)
315 >          endif
316 >       endif
317 >    enddo
318  
319 +    istart = 1
320 + #ifdef IS_MPI
321 +    iend = nGroupsInRow
322 + #else
323 +    iend = nGroups
324 + #endif
325 +    outer: do i = istart, iend
326 +      
327 +       n_in_i = groupStartRow(i+1) - groupStartRow(i)
328 +      
329 + #ifdef IS_MPI
330 +       jstart = 1
331 +       jend = nGroupsInCol
332 + #else
333 +       jstart = i+1
334 +       jend = nGroups
335 + #endif
336 +      
337 +      
338 +      
339 +      
340 +      
341 +      
342 +    enddo outer        
343 +    
344 +     haveGtypeCutoffMap = .true.
345 +   end subroutine createGtypeCutoffMap
346  
347 +   subroutine setDefaultCutoffs(defRcut, defRsw, defRlist, cutPolicy)
348 +     real(kind=dp),intent(in) :: defRcut, defRsw, defRlist
349 +     integer, intent(in) :: cutPolicy
350 +
351 +     defaultRcut = defRcut
352 +     defaultRsw = defRsw
353 +     defaultRlist = defRlist
354 +     cutoffPolicy = cutPolicy
355 +   end subroutine setDefaultCutoffs
356 +
357 +   subroutine setCutoffPolicy(cutPolicy)
358 +
359 +     integer, intent(in) :: cutPolicy
360 +     cutoffPolicy = cutPolicy
361 +     call createGtypeCutoffMap()
362 +
363 +   end subroutine setCutoffPolicy
364 +    
365 +    
366    subroutine setSimVariables()
367      SIM_uses_DirectionalAtoms = SimUsesDirectionalAtoms()
342    SIM_uses_LennardJones = SimUsesLennardJones()
343    SIM_uses_Electrostatics = SimUsesElectrostatics()
344    SIM_uses_Charges = SimUsesCharges()
345    SIM_uses_Dipoles = SimUsesDipoles()
346    SIM_uses_Sticky = SimUsesSticky()
347    SIM_uses_StickyPower = SimUsesStickyPower()
348    SIM_uses_GayBerne = SimUsesGayBerne()
368      SIM_uses_EAM = SimUsesEAM()
350    SIM_uses_Shapes = SimUsesShapes()
351    SIM_uses_FLARB = SimUsesFLARB()
369      SIM_uses_RF = SimUsesRF()
370      SIM_requires_postpair_calc = SimRequiresPostpairCalc()
371      SIM_requires_prepair_calc = SimRequiresPrepairCalc()
# Line 366 | Line 383 | contains
383  
384      error = 0
385  
386 <    if (.not. haveInteractionMap) then
386 >    if (.not. haveInteractionHash) then      
387 >       myStatus = 0      
388 >       call createInteractionHash(myStatus)      
389 >       if (myStatus .ne. 0) then
390 >          write(default_error, *) 'createInteractionHash failed in doForces!'
391 >          error = -1
392 >          return
393 >       endif
394 >    endif
395  
396 <       myStatus = 0
397 <
398 <       call createInteractionMap(myStatus)
374 <
396 >    if (.not. haveGtypeCutoffMap) then        
397 >       myStatus = 0      
398 >       call createGtypeCutoffMap(myStatus)      
399         if (myStatus .ne. 0) then
400 <          write(default_error, *) 'createInteractionMap failed in doForces!'
400 >          write(default_error, *) 'createGtypeCutoffMap failed in doForces!'
401            error = -1
402            return
403         endif
# Line 434 | Line 458 | contains
458      !! interactions are used by the force field.    
459  
460      FF_uses_DirectionalAtoms = .false.
437    FF_uses_LennardJones = .false.
438    FF_uses_Electrostatics = .false.
439    FF_uses_Charges = .false.    
461      FF_uses_Dipoles = .false.
441    FF_uses_Sticky = .false.
442    FF_uses_StickyPower = .false.
462      FF_uses_GayBerne = .false.
463      FF_uses_EAM = .false.
445    FF_uses_Shapes = .false.
446    FF_uses_FLARB = .false.
464  
465      call getMatchingElementList(atypes, "is_Directional", .true., &
466           nMatches, MatchList)
467      if (nMatches .gt. 0) FF_uses_DirectionalAtoms = .true.
451
452    call getMatchingElementList(atypes, "is_LennardJones", .true., &
453         nMatches, MatchList)
454    if (nMatches .gt. 0) FF_uses_LennardJones = .true.
455
456    call getMatchingElementList(atypes, "is_Electrostatic", .true., &
457         nMatches, MatchList)
458    if (nMatches .gt. 0) then
459       FF_uses_Electrostatics = .true.
460    endif
461
462    call getMatchingElementList(atypes, "is_Charge", .true., &
463         nMatches, MatchList)
464    if (nMatches .gt. 0) then
465       FF_uses_Charges = .true.  
466       FF_uses_Electrostatics = .true.
467    endif
468  
469      call getMatchingElementList(atypes, "is_Dipole", .true., &
470           nMatches, MatchList)
471 <    if (nMatches .gt. 0) then
472 <       FF_uses_Dipoles = .true.
473 <       FF_uses_Electrostatics = .true.
474 <       FF_uses_DirectionalAtoms = .true.
475 <    endif
476 <
477 <    call getMatchingElementList(atypes, "is_Quadrupole", .true., &
478 <         nMatches, MatchList)
479 <    if (nMatches .gt. 0) then
480 <       FF_uses_Quadrupoles = .true.
481 <       FF_uses_Electrostatics = .true.
482 <       FF_uses_DirectionalAtoms = .true.
483 <    endif
484 <
485 <    call getMatchingElementList(atypes, "is_Sticky", .true., nMatches, &
486 <         MatchList)
487 <    if (nMatches .gt. 0) then
488 <       FF_uses_Sticky = .true.
489 <       FF_uses_DirectionalAtoms = .true.
490 <    endif
491 <
492 <    call getMatchingElementList(atypes, "is_StickyPower", .true., nMatches, &
493 <         MatchList)
494 <    if (nMatches .gt. 0) then
495 <       FF_uses_StickyPower = .true.
496 <       FF_uses_DirectionalAtoms = .true.
497 <    endif
471 >    if (nMatches .gt. 0) FF_uses_Dipoles = .true.
472      
473      call getMatchingElementList(atypes, "is_GayBerne", .true., &
474           nMatches, MatchList)
475 <    if (nMatches .gt. 0) then
502 <       FF_uses_GayBerne = .true.
503 <       FF_uses_DirectionalAtoms = .true.
504 <    endif
475 >    if (nMatches .gt. 0) FF_uses_GayBerne = .true.
476  
477      call getMatchingElementList(atypes, "is_EAM", .true., nMatches, MatchList)
478      if (nMatches .gt. 0) FF_uses_EAM = .true.
479  
509    call getMatchingElementList(atypes, "is_Shape", .true., &
510         nMatches, MatchList)
511    if (nMatches .gt. 0) then
512       FF_uses_Shapes = .true.
513       FF_uses_DirectionalAtoms = .true.
514    endif
480  
516    call getMatchingElementList(atypes, "is_FLARB", .true., &
517         nMatches, MatchList)
518    if (nMatches .gt. 0) FF_uses_FLARB = .true.
519
520    !! Assume sanity (for the sake of argument)
481      haveSaneForceField = .true.
482  
483      !! check to make sure the FF_uses_RF setting makes sense
484  
485 <    if (FF_uses_dipoles) then
485 >    if (FF_uses_Dipoles) then
486         if (FF_uses_RF) then
487            dielect = getDielect()
488            call initialize_rf(dielect)
# Line 535 | Line 495 | contains
495            return
496         endif
497      endif
538
539    !sticky module does not contain check_sticky_FF anymore
540    !if (FF_uses_sticky) then
541    !   call check_sticky_FF(my_status)
542    !   if (my_status /= 0) then
543    !      thisStat = -1
544    !      haveSaneForceField = .false.
545    !      return
546    !   end if
547    !endif
498  
499      if (FF_uses_EAM) then
500         call init_EAM_FF(my_status)
# Line 565 | Line 515 | contains
515         endif
516      endif
517  
568    if (FF_uses_GayBerne .and. FF_uses_LennardJones) then
569    endif
570
518      if (.not. haveNeighborList) then
519         !! Create neighbor lists
520         call expandNeighborList(nLocal, my_status)
# Line 631 | Line 578 | contains
578      integer :: localError
579      integer :: propPack_i, propPack_j
580      integer :: loopStart, loopEnd, loop
581 <    integer :: iMap
581 >    integer :: iHash
582      real(kind=dp) :: listSkin = 1.0  
583  
584      !! initialize local variables  
# Line 750 | Line 697 | contains
697               endif
698  
699   #ifdef IS_MPI
700 +             me_j = atid_col(j)
701               call get_interatomic_vector(q_group_Row(:,i), &
702                    q_group_Col(:,j), d_grp, rgrpsq)
703   #else
704 +             me_j = atid(j)
705               call get_interatomic_vector(q_group(:,i), &
706                    q_group(:,j), d_grp, rgrpsq)
707   #endif
708  
709 <             if (rgrpsq < InteractionMap(me_i,me_j)%rListsq) then
709 >             if (rgrpsq < InteractionHash(me_i,me_j)%rListsq) then
710                  if (update_nlist) then
711                     nlist = nlist + 1
712  
# Line 975 | Line 924 | contains
924   #else
925               me_i = atid(i)
926   #endif
927 <             iMap = InteractionMap(me_i, me_j)%InteractionHash
927 >             iHash = InteractionHash(me_i,me_j)
928              
929 <             if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
929 >             if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then
930  
931                  mu_i = getDipoleMoment(me_i)
932  
# Line 1044 | Line 993 | contains
993      real ( kind = dp ) :: ebalance
994      integer :: me_i, me_j
995  
996 <    integer :: iMap
996 >    integer :: iHash
997  
998      r = sqrt(rijsq)
999      vpair = 0.0d0
# Line 1058 | Line 1007 | contains
1007      me_j = atid(j)
1008   #endif
1009  
1010 <    iMap = InteractionMap(me_i, me_j)%InteractionHash
1010 >    iHash = InteractionHash(me_i, me_j)
1011  
1012 <    if ( iand(iMap, LJ_PAIR).ne.0 ) then
1012 >    if ( iand(iHash, LJ_PAIR).ne.0 ) then
1013         call do_lj_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot)
1014      endif
1015  
1016 <    if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
1016 >    if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then
1017         call doElectrostaticPair(i, j, d, r, rijsq, sw, vpair, fpair, &
1018              pot, eFrame, f, t, do_pot)
1019  
# Line 1077 | Line 1026 | contains
1026  
1027      endif
1028  
1029 <    if ( iand(iMap, STICKY_PAIR).ne.0 ) then
1029 >    if ( iand(iHash, STICKY_PAIR).ne.0 ) then
1030         call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1031              pot, A, f, t, do_pot)
1032      endif
1033  
1034 <    if ( iand(iMap, STICKYPOWER_PAIR).ne.0 ) then
1034 >    if ( iand(iHash, STICKYPOWER_PAIR).ne.0 ) then
1035         call do_sticky_power_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1036              pot, A, f, t, do_pot)
1037      endif
1038  
1039 <    if ( iand(iMap, GAYBERNE_PAIR).ne.0 ) then
1039 >    if ( iand(iHash, GAYBERNE_PAIR).ne.0 ) then
1040         call do_gb_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1041              pot, A, f, t, do_pot)
1042      endif
1043      
1044 <    if ( iand(iMap, GAYBERNE_LJ).ne.0 ) then
1044 >    if ( iand(iHash, GAYBERNE_LJ).ne.0 ) then
1045   !      call do_gblj_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1046   !           pot, A, f, t, do_pot)
1047      endif
1048  
1049 <    if ( iand(iMap, EAM_PAIR).ne.0 ) then      
1049 >    if ( iand(iHash, EAM_PAIR).ne.0 ) then      
1050         call do_eam_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, &
1051              do_pot)
1052      endif
1053  
1054 <    if ( iand(iMap, SHAPE_PAIR).ne.0 ) then      
1054 >    if ( iand(iHash, SHAPE_PAIR).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
1058  
1059 <    if ( iand(iMap, SHAPE_LJ).ne.0 ) then      
1059 >    if ( iand(iHash, SHAPE_LJ).ne.0 ) then      
1060         call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1061              pot, A, f, t, do_pot)
1062      endif
# Line 1129 | Line 1078 | contains
1078      real ( kind = dp )                :: r, rc
1079      real ( kind = dp ), intent(inout) :: d(3), dc(3)
1080  
1081 <    integer :: me_i, me_j, iMap
1081 >    integer :: me_i, me_j, iHash
1082  
1083   #ifdef IS_MPI  
1084      me_i = atid_row(i)
# Line 1139 | Line 1088 | contains
1088      me_j = atid(j)  
1089   #endif
1090  
1091 <    iMap = InteractionMap(me_i, me_j)%InteractionHash
1091 >    iHash = InteractionHash(me_i, me_j)
1092  
1093 <    if ( iand(iMap, EAM_PAIR).ne.0 ) then      
1093 >    if ( iand(iHash, EAM_PAIR).ne.0 ) then      
1094              call calc_EAM_prepair_rho(i, j, d, r, rijsq )
1095      endif
1096      
# Line 1338 | Line 1287 | contains
1287  
1288    function FF_UsesDirectionalAtoms() result(doesit)
1289      logical :: doesit
1290 <    doesit = FF_uses_DirectionalAtoms .or. FF_uses_Dipoles .or. &
1342 <         FF_uses_Quadrupoles .or. FF_uses_Sticky .or. &
1343 <         FF_uses_StickyPower .or. FF_uses_GayBerne .or. FF_uses_Shapes
1290 >    doesit = FF_uses_DirectionalAtoms
1291    end function FF_UsesDirectionalAtoms
1292  
1293    function FF_RequiresPrepairCalc() result(doesit)

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines