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 2266 by chuckv, Thu Jul 28 22:12:45 2005 UTC vs.
Revision 2279 by chrisfen, Tue Aug 30 18:23:50 2005 UTC

# Line 45 | Line 45
45  
46   !! @author Charles F. Vardeman II
47   !! @author Matthew Meineke
48 < !! @version $Id: doForces.F90,v 1.24 2005-07-28 22:12:45 chuckv Exp $, $Date: 2005-07-28 22:12:45 $, $Name: not supported by cvs2svn $, $Revision: 1.24 $
48 > !! @version $Id: doForces.F90,v 1.33 2005-08-30 18:23:29 chrisfen Exp $, $Date: 2005-08-30 18:23:29 $, $Name: not supported by cvs2svn $, $Revision: 1.33 $
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  
102 <  !!!GO AWAY---------
120 <  !!!!!real(kind=dp), save :: rlist, rlistsq
102 >  integer, save :: corrMethod
103  
104    public :: init_FF
105 +  public :: setDefaultCutoffs
106    public :: do_force_loop
107 < !  public :: setRlistDF
108 <  !public :: addInteraction
109 <  !public :: setInteractionHash
110 <  !public :: getInteractionHash
111 <  public :: createInteractionMap
112 <  public :: createRcuts
107 >  public :: createInteractionHash
108 >  public :: createGtypeCutoffMap
109 >  public :: getStickyCut
110 >  public :: getStickyPowerCut
111 >  public :: getGayBerneCut
112 >  public :: getEAMCut
113 >  public :: getShapeCut
114  
115   #ifdef PROFILE
116    public :: getforcetime
# Line 134 | Line 118 | module doForces
118    real :: forceTimeInitial, forceTimeFinal
119    integer :: nLoops
120   #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
121    
122 <  type(Interaction), dimension(:,:),allocatable :: InteractionMap
123 <  
122 >  !! Variables for cutoff mapping and interaction mapping
123 >  ! Bit hash to determine pair-pair interactions.
124 >  integer, dimension(:,:), allocatable :: InteractionHash
125 >  real(kind=dp), dimension(:), allocatable :: atypeMaxCutoff
126 >  real(kind=dp), dimension(:), allocatable :: groupMaxCutoff
127 >  integer, dimension(:), allocatable :: groupToGtype
128 >  real(kind=dp), dimension(:), allocatable :: gtypeMaxCutoff
129 >  type ::gtypeCutoffs
130 >     real(kind=dp) :: rcut
131 >     real(kind=dp) :: rcutsq
132 >     real(kind=dp) :: rlistsq
133 >  end type gtypeCutoffs
134 >  type(gtypeCutoffs), dimension(:,:), allocatable :: gtypeCutoffMap
135  
136 +  integer, save :: cutoffPolicy = TRADITIONAL_CUTOFF_POLICY
137 +  real(kind=dp),save :: defaultRcut, defaultRsw, defaultRlist
138    
139   contains
140  
141 <
151 <  subroutine createInteractionMap(status)
141 >  subroutine createInteractionHash(status)
142      integer :: nAtypes
143      integer, intent(out) :: status
144      integer :: i
145      integer :: j
146 <    integer :: ihash
147 <    real(kind=dp) :: myRcut
158 < ! Test Types
146 >    integer :: iHash
147 >    !! Test Types
148      logical :: i_is_LJ
149      logical :: i_is_Elect
150      logical :: i_is_Sticky
# Line 170 | Line 159 | contains
159      logical :: j_is_GB
160      logical :: j_is_EAM
161      logical :: j_is_Shape
162 <    
163 <    status = 0
164 <    
162 >    real(kind=dp) :: myRcut
163 >
164 >    status = 0  
165 >
166      if (.not. associated(atypes)) then
167 <       call handleError("atype", "atypes was not present before call of createDefaultInteractionMap!")
167 >       call handleError("atype", "atypes was not present before call of createInteractionHash!")
168         status = -1
169         return
170      endif
# Line 186 | Line 176 | contains
176         return
177      end if
178  
179 <    if (.not. allocated(InteractionMap)) then
180 <       allocate(InteractionMap(nAtypes,nAtypes))
179 >    if (.not. allocated(InteractionHash)) then
180 >       allocate(InteractionHash(nAtypes,nAtypes))
181      endif
182 +
183 +    if (.not. allocated(atypeMaxCutoff)) then
184 +       allocate(atypeMaxCutoff(nAtypes))
185 +    endif
186          
187      do i = 1, nAtypes
188         call getElementProperty(atypes, i, "is_LennardJones", i_is_LJ)
# Line 241 | Line 235 | contains
235            if (i_is_LJ .and. j_is_Shape) iHash = ior(iHash, SHAPE_LJ)
236  
237  
238 <          InteractionMap(i,j)%InteractionHash = iHash
239 <          InteractionMap(j,i)%InteractionHash = iHash
238 >          InteractionHash(i,j) = iHash
239 >          InteractionHash(j,i) = iHash
240  
241         end do
242  
243      end do
250  end subroutine createInteractionMap
244  
245 < ! 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.
246 <  subroutine createRcuts(defaultRList,stat)
254 <    real(kind=dp), intent(in), optional :: defaultRList
255 <    integer :: iMap
256 <    integer :: map_i,map_j
257 <    real(kind=dp) :: thisRCut = 0.0_dp
258 <    real(kind=dp) :: actualCutoff = 0.0_dp
259 <    integer, intent(out) :: stat
260 <    integer :: nAtypes
261 <    integer :: myStatus
245 >    haveInteractionHash = .true.
246 >  end subroutine createInteractionHash
247  
248 <    stat = 0
264 <    if (.not. haveInteractionMap) then
248 >  subroutine createGtypeCutoffMap(stat)
249  
250 <       call createInteractionMap(myStatus)
250 >    integer, intent(out), optional :: stat
251 >    logical :: i_is_LJ
252 >    logical :: i_is_Elect
253 >    logical :: i_is_Sticky
254 >    logical :: i_is_StickyP
255 >    logical :: i_is_GB
256 >    logical :: i_is_EAM
257 >    logical :: i_is_Shape
258 >
259 >    integer :: myStatus, nAtypes,  i, j, istart, iend, jstart, jend
260 >    integer :: n_in_i
261 >    real(kind=dp):: thisSigma, bigSigma, thisRcut
262 >    real(kind=dp) :: biggestAtypeCutoff
263  
264 +    stat = 0
265 +    if (.not. haveInteractionHash) then
266 +       call createInteractionHash(myStatus)      
267         if (myStatus .ne. 0) then
268 <          write(default_error, *) 'createInteractionMap failed in doForces!'
268 >          write(default_error, *) 'createInteractionHash failed in doForces!'
269            stat = -1
270            return
271         endif
272      endif
273  
275
274      nAtypes = getSize(atypes)
275 < ! If we pass a default rcut, set all atypes to that cutoff distance
276 <    if(present(defaultRList)) then
277 <       InteractionMap(:,:)%rList = defaultRList
278 <       InteractionMap(:,:)%rListSq = defaultRList*defaultRList
279 <       haveRlist = .true.
280 <       return
281 <    end if
282 <
283 <    do map_i = 1,nAtypes
284 <       do map_j = map_i,nAtypes
287 <          iMap = InteractionMap(map_i, map_j)%InteractionHash
275 >    
276 >    do i = 1, nAtypes
277 >       if (SimHasAtype(i)) then          
278 >          call getElementProperty(atypes, i, "is_LennardJones", i_is_LJ)
279 >          call getElementProperty(atypes, i, "is_Electrostatic", i_is_Elect)
280 >          call getElementProperty(atypes, i, "is_Sticky", i_is_Sticky)
281 >          call getElementProperty(atypes, i, "is_StickyPower", i_is_StickyP)
282 >          call getElementProperty(atypes, i, "is_GayBerne", i_is_GB)
283 >          call getElementProperty(atypes, i, "is_EAM", i_is_EAM)
284 >          call getElementProperty(atypes, i, "is_Shape", i_is_Shape)
285            
286 <          if ( iand(iMap, LJ_PAIR).ne.0 ) then
287 < !            thisRCut = getLJCutOff(map_i,map_j)
288 <             if (thisRcut > actualCutoff) actualCutoff = thisRcut
286 >          if (i_is_LJ) then
287 >             thisRcut = getSigma(i) * 2.5_dp
288 >             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
289            endif
290 <          
291 <          if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
292 < !            thisRCut = getElectrostaticCutOff(map_i,map_j)
296 <             if (thisRcut > actualCutoff) actualCutoff = thisRcut
290 >          if (i_is_Elect) then
291 >             thisRcut = defaultRcut
292 >             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
293            endif
294 +          if (i_is_Sticky) then
295 +             thisRcut = getStickyCut(i)
296 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
297 +          endif
298 +          if (i_is_StickyP) then
299 +             thisRcut = getStickyPowerCut(i)
300 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
301 +          endif
302 +          if (i_is_GB) then
303 +             thisRcut = getGayBerneCut(i)
304 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
305 +          endif
306 +          if (i_is_EAM) then
307 +             thisRcut = getEAMCut(i)
308 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
309 +          endif
310 +          if (i_is_Shape) then
311 +             thisRcut = getShapeCut(i)
312 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
313 +          endif
314            
315 <          if ( iand(iMap, STICKY_PAIR).ne.0 ) then
316 < !             thisRCut = getStickyCutOff(map_i,map_j)
317 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
318 <           endif
319 <          
320 <           if ( iand(iMap, STICKYPOWER_PAIR).ne.0 ) then
321 < !              thisRCut = getStickyPowerCutOff(map_i,map_j)
322 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
323 <           endif
324 <          
325 <           if ( iand(iMap, GAYBERNE_PAIR).ne.0 ) then
326 < !              thisRCut = getGayberneCutOff(map_i,map_j)
327 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
328 <           endif
329 <          
330 <           if ( iand(iMap, GAYBERNE_LJ).ne.0 ) then
331 < !              thisRCut = getGaybrneLJCutOff(map_i,map_j)
332 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
333 <           endif
334 <          
335 <           if ( iand(iMap, EAM_PAIR).ne.0 ) then      
336 < !              thisRCut = getEAMCutOff(map_i,map_j)
337 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
338 <           endif
339 <          
340 <           if ( iand(iMap, SHAPE_PAIR).ne.0 ) then      
341 < !              thisRCut = getShapeCutOff(map_i,map_j)
342 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
343 <           endif
344 <          
345 <           if ( iand(iMap, SHAPE_LJ).ne.0 ) then      
346 < !              thisRCut = getShapeLJCutOff(map_i,map_j)
347 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
332 <           endif
333 <           InteractionMap(map_i, map_j)%rList = actualCutoff
334 <           InteractionMap(map_i, map_j)%rListSq = actualCutoff * actualCutoff
335 <        end do
336 <     end do
337 <          haveRlist = .true.
338 <  end subroutine createRcuts
315 >          if (atypeMaxCutoff(i).gt.biggestAtypeCutoff) then
316 >             biggestAtypeCutoff = atypeMaxCutoff(i)
317 >          endif
318 >       endif
319 >    enddo
320 >
321 >    istart = 1
322 > #ifdef IS_MPI
323 >    iend = nGroupsInRow
324 > #else
325 >    iend = nGroups
326 > #endif
327 >    outer: do i = istart, iend
328 >      
329 >       n_in_i = groupStartRow(i+1) - groupStartRow(i)
330 >      
331 > #ifdef IS_MPI
332 >       jstart = 1
333 >       jend = nGroupsInCol
334 > #else
335 >       jstart = i+1
336 >       jend = nGroups
337 > #endif
338 >      
339 >      
340 >      
341 >      
342 >      
343 >      
344 >    enddo outer        
345 >    
346 >     haveGtypeCutoffMap = .true.
347 >   end subroutine createGtypeCutoffMap
348  
349 +   subroutine setDefaultCutoffs(defRcut, defRsw, defRlist, cutPolicy)
350 +     real(kind=dp),intent(in) :: defRcut, defRsw, defRlist
351 +     integer, intent(in) :: cutPolicy
352  
353 < !!! THIS GOES AWAY FOR SIZE DEPENDENT CUTOFF
354 < !!$  subroutine setRlistDF( this_rlist )
355 < !!$
356 < !!$   real(kind=dp) :: this_rlist
357 < !!$
346 < !!$    rlist = this_rlist
347 < !!$    rlistsq = rlist * rlist
348 < !!$
349 < !!$    haveRlist = .true.
350 < !!$
351 < !!$  end subroutine setRlistDF
353 >     defaultRcut = defRcut
354 >     defaultRsw = defRsw
355 >     defaultRlist = defRlist
356 >     cutoffPolicy = cutPolicy
357 >   end subroutine setDefaultCutoffs
358  
359 +   subroutine setCutoffPolicy(cutPolicy)
360  
361 +     integer, intent(in) :: cutPolicy
362 +     cutoffPolicy = cutPolicy
363 +     call createGtypeCutoffMap()
364 +
365 +   end subroutine setCutoffPolicy
366 +    
367 +    
368    subroutine setSimVariables()
369      SIM_uses_DirectionalAtoms = SimUsesDirectionalAtoms()
356    SIM_uses_LennardJones = SimUsesLennardJones()
357    SIM_uses_Electrostatics = SimUsesElectrostatics()
358    SIM_uses_Charges = SimUsesCharges()
359    SIM_uses_Dipoles = SimUsesDipoles()
360    SIM_uses_Sticky = SimUsesSticky()
361    SIM_uses_StickyPower = SimUsesStickyPower()
362    SIM_uses_GayBerne = SimUsesGayBerne()
370      SIM_uses_EAM = SimUsesEAM()
364    SIM_uses_Shapes = SimUsesShapes()
365    SIM_uses_FLARB = SimUsesFLARB()
371      SIM_uses_RF = SimUsesRF()
372      SIM_requires_postpair_calc = SimRequiresPostpairCalc()
373      SIM_requires_prepair_calc = SimRequiresPrepairCalc()
# Line 380 | Line 385 | contains
385  
386      error = 0
387  
388 <    if (.not. haveInteractionMap) then
388 >    if (.not. haveInteractionHash) then      
389 >       myStatus = 0      
390 >       call createInteractionHash(myStatus)      
391 >       if (myStatus .ne. 0) then
392 >          write(default_error, *) 'createInteractionHash failed in doForces!'
393 >          error = -1
394 >          return
395 >       endif
396 >    endif
397  
398 <       myStatus = 0
399 <
400 <       call createInteractionMap(myStatus)
388 <
398 >    if (.not. haveGtypeCutoffMap) then        
399 >       myStatus = 0      
400 >       call createGtypeCutoffMap(myStatus)      
401         if (myStatus .ne. 0) then
402 <          write(default_error, *) 'createInteractionMap failed in doForces!'
402 >          write(default_error, *) 'createGtypeCutoffMap failed in doForces!'
403            error = -1
404            return
405         endif
# Line 426 | Line 438 | contains
438    end subroutine doReadyCheck
439  
440  
441 <  subroutine init_FF(use_RF_c, thisStat)
441 >  subroutine init_FF(use_RF_c, use_UW_c, use_DW_c, thisStat)
442  
443      logical, intent(in) :: use_RF_c
444 <
444 >    logical, intent(in) :: use_UW_c
445 >    logical, intent(in) :: use_DW_c
446      integer, intent(out) :: thisStat  
447      integer :: my_status, nMatches
448 +    integer :: corrMethod
449      integer, pointer :: MatchList(:) => null()
450      real(kind=dp) :: rcut, rrf, rt, dielect
451  
# Line 441 | Line 455 | contains
455      !! Fortran's version of a cast:
456      FF_uses_RF = use_RF_c
457  
458 +    !! set the electrostatic correction method
459 +    if (use_UW_c .eq. .true.) then
460 +       corrMethod = 1
461 +    elseif (use_DW_c .eq. .true.) then
462 +       corrMethod = 2
463 +    else
464 +       corrMethod = 0
465 +    endif
466 +    
467      !! init_FF is called *after* all of the atom types have been
468      !! defined in atype_module using the new_atype subroutine.
469      !!
# Line 448 | Line 471 | contains
471      !! interactions are used by the force field.    
472  
473      FF_uses_DirectionalAtoms = .false.
451    FF_uses_LennardJones = .false.
452    FF_uses_Electrostatics = .false.
453    FF_uses_Charges = .false.    
474      FF_uses_Dipoles = .false.
455    FF_uses_Sticky = .false.
456    FF_uses_StickyPower = .false.
475      FF_uses_GayBerne = .false.
476      FF_uses_EAM = .false.
459    FF_uses_Shapes = .false.
460    FF_uses_FLARB = .false.
477  
478      call getMatchingElementList(atypes, "is_Directional", .true., &
479           nMatches, MatchList)
480      if (nMatches .gt. 0) FF_uses_DirectionalAtoms = .true.
481  
466    call getMatchingElementList(atypes, "is_LennardJones", .true., &
467         nMatches, MatchList)
468    if (nMatches .gt. 0) FF_uses_LennardJones = .true.
469
470    call getMatchingElementList(atypes, "is_Electrostatic", .true., &
471         nMatches, MatchList)
472    if (nMatches .gt. 0) then
473       FF_uses_Electrostatics = .true.
474    endif
475
476    call getMatchingElementList(atypes, "is_Charge", .true., &
477         nMatches, MatchList)
478    if (nMatches .gt. 0) then
479       FF_uses_Charges = .true.  
480       FF_uses_Electrostatics = .true.
481    endif
482
482      call getMatchingElementList(atypes, "is_Dipole", .true., &
483           nMatches, MatchList)
484 <    if (nMatches .gt. 0) then
486 <       FF_uses_Dipoles = .true.
487 <       FF_uses_Electrostatics = .true.
488 <       FF_uses_DirectionalAtoms = .true.
489 <    endif
490 <
491 <    call getMatchingElementList(atypes, "is_Quadrupole", .true., &
492 <         nMatches, MatchList)
493 <    if (nMatches .gt. 0) then
494 <       FF_uses_Quadrupoles = .true.
495 <       FF_uses_Electrostatics = .true.
496 <       FF_uses_DirectionalAtoms = .true.
497 <    endif
498 <
499 <    call getMatchingElementList(atypes, "is_Sticky", .true., nMatches, &
500 <         MatchList)
501 <    if (nMatches .gt. 0) then
502 <       FF_uses_Sticky = .true.
503 <       FF_uses_DirectionalAtoms = .true.
504 <    endif
505 <
506 <    call getMatchingElementList(atypes, "is_StickyPower", .true., nMatches, &
507 <         MatchList)
508 <    if (nMatches .gt. 0) then
509 <       FF_uses_StickyPower = .true.
510 <       FF_uses_DirectionalAtoms = .true.
511 <    endif
484 >    if (nMatches .gt. 0) FF_uses_Dipoles = .true.
485      
486      call getMatchingElementList(atypes, "is_GayBerne", .true., &
487           nMatches, MatchList)
488 <    if (nMatches .gt. 0) then
516 <       FF_uses_GayBerne = .true.
517 <       FF_uses_DirectionalAtoms = .true.
518 <    endif
488 >    if (nMatches .gt. 0) FF_uses_GayBerne = .true.
489  
490      call getMatchingElementList(atypes, "is_EAM", .true., nMatches, MatchList)
491      if (nMatches .gt. 0) FF_uses_EAM = .true.
492  
523    call getMatchingElementList(atypes, "is_Shape", .true., &
524         nMatches, MatchList)
525    if (nMatches .gt. 0) then
526       FF_uses_Shapes = .true.
527       FF_uses_DirectionalAtoms = .true.
528    endif
493  
530    call getMatchingElementList(atypes, "is_FLARB", .true., &
531         nMatches, MatchList)
532    if (nMatches .gt. 0) FF_uses_FLARB = .true.
533
534    !! Assume sanity (for the sake of argument)
494      haveSaneForceField = .true.
495  
496      !! check to make sure the FF_uses_RF setting makes sense
497  
498 <    if (FF_uses_dipoles) then
498 >    if (FF_uses_Dipoles) then
499         if (FF_uses_RF) then
500            dielect = getDielect()
501            call initialize_rf(dielect)
# Line 549 | Line 508 | contains
508            return
509         endif
510      endif
552
553    !sticky module does not contain check_sticky_FF anymore
554    !if (FF_uses_sticky) then
555    !   call check_sticky_FF(my_status)
556    !   if (my_status /= 0) then
557    !      thisStat = -1
558    !      haveSaneForceField = .false.
559    !      return
560    !   end if
561    !endif
511  
512      if (FF_uses_EAM) then
513         call init_EAM_FF(my_status)
# Line 579 | Line 528 | contains
528         endif
529      endif
530  
582    if (FF_uses_GayBerne .and. FF_uses_LennardJones) then
583    endif
584
531      if (.not. haveNeighborList) then
532         !! Create neighbor lists
533         call expandNeighborList(nLocal, my_status)
# Line 645 | Line 591 | contains
591      integer :: localError
592      integer :: propPack_i, propPack_j
593      integer :: loopStart, loopEnd, loop
594 <    integer :: iMap
594 >    integer :: iHash
595      real(kind=dp) :: listSkin = 1.0  
596  
597      !! initialize local variables  
# Line 743 | Line 689 | contains
689  
690            if (update_nlist) then
691   #ifdef IS_MPI
746             me_i = atid_row(i)
692               jstart = 1
693               jend = nGroupsInCol
694   #else
750             me_i = atid(i)
695               jstart = i+1
696               jend = nGroups
697   #endif
# Line 775 | Line 719 | contains
719                    q_group(:,j), d_grp, rgrpsq)
720   #endif
721  
722 <             if (rgrpsq < InteractionMap(me_i,me_j)%rListsq) then
722 >             if (rgrpsq < InteractionHash(me_i,me_j)%rListsq) then
723                  if (update_nlist) then
724                     nlist = nlist + 1
725  
# Line 993 | Line 937 | contains
937   #else
938               me_i = atid(i)
939   #endif
940 <             iMap = InteractionMap(me_i, me_j)%InteractionHash
940 >             iHash = InteractionHash(me_i,me_j)
941              
942 <             if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
942 >             if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then
943  
944                  mu_i = getDipoleMoment(me_i)
945  
# Line 1062 | Line 1006 | contains
1006      real ( kind = dp ) :: ebalance
1007      integer :: me_i, me_j
1008  
1009 <    integer :: iMap
1009 >    integer :: iHash
1010  
1011      r = sqrt(rijsq)
1012      vpair = 0.0d0
# Line 1076 | Line 1020 | contains
1020      me_j = atid(j)
1021   #endif
1022  
1023 <    iMap = InteractionMap(me_i, me_j)%InteractionHash
1023 >    iHash = InteractionHash(me_i, me_j)
1024  
1025 <    if ( iand(iMap, LJ_PAIR).ne.0 ) then
1025 >    if ( iand(iHash, LJ_PAIR).ne.0 ) then
1026         call do_lj_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot)
1027      endif
1028  
1029 <    if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
1029 >    if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then
1030         call doElectrostaticPair(i, j, d, r, rijsq, sw, vpair, fpair, &
1031 <            pot, eFrame, f, t, do_pot)
1031 >            pot, eFrame, f, t, do_pot, corrMethod)
1032  
1033         if (FF_uses_RF .and. SIM_uses_RF) then
1034  
# Line 1095 | Line 1039 | contains
1039  
1040      endif
1041  
1042 <    if ( iand(iMap, STICKY_PAIR).ne.0 ) then
1042 >    if ( iand(iHash, STICKY_PAIR).ne.0 ) then
1043         call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1044              pot, A, f, t, do_pot)
1045      endif
1046  
1047 <    if ( iand(iMap, STICKYPOWER_PAIR).ne.0 ) then
1047 >    if ( iand(iHash, STICKYPOWER_PAIR).ne.0 ) then
1048         call do_sticky_power_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1049              pot, A, f, t, do_pot)
1050      endif
1051  
1052 <    if ( iand(iMap, GAYBERNE_PAIR).ne.0 ) then
1052 >    if ( iand(iHash, GAYBERNE_PAIR).ne.0 ) then
1053         call do_gb_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1054              pot, A, f, t, do_pot)
1055      endif
1056      
1057 <    if ( iand(iMap, GAYBERNE_LJ).ne.0 ) then
1057 >    if ( iand(iHash, GAYBERNE_LJ).ne.0 ) then
1058   !      call do_gblj_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1059   !           pot, A, f, t, do_pot)
1060      endif
1061  
1062 <    if ( iand(iMap, EAM_PAIR).ne.0 ) then      
1062 >    if ( iand(iHash, EAM_PAIR).ne.0 ) then      
1063         call do_eam_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, &
1064              do_pot)
1065      endif
1066  
1067 <    if ( iand(iMap, SHAPE_PAIR).ne.0 ) then      
1067 >    if ( iand(iHash, SHAPE_PAIR).ne.0 ) then      
1068         call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1069              pot, A, f, t, do_pot)
1070      endif
1071  
1072 <    if ( iand(iMap, SHAPE_LJ).ne.0 ) then      
1072 >    if ( iand(iHash, SHAPE_LJ).ne.0 ) then      
1073         call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1074              pot, A, f, t, do_pot)
1075      endif
# Line 1147 | Line 1091 | contains
1091      real ( kind = dp )                :: r, rc
1092      real ( kind = dp ), intent(inout) :: d(3), dc(3)
1093  
1094 <    integer :: me_i, me_j, iMap
1094 >    integer :: me_i, me_j, iHash
1095  
1096   #ifdef IS_MPI  
1097      me_i = atid_row(i)
# Line 1157 | Line 1101 | contains
1101      me_j = atid(j)  
1102   #endif
1103  
1104 <    iMap = InteractionMap(me_i, me_j)%InteractionHash
1104 >    iHash = InteractionHash(me_i, me_j)
1105  
1106 <    if ( iand(iMap, EAM_PAIR).ne.0 ) then      
1106 >    if ( iand(iHash, EAM_PAIR).ne.0 ) then      
1107              call calc_EAM_prepair_rho(i, j, d, r, rijsq )
1108      endif
1109      
# Line 1356 | Line 1300 | contains
1300  
1301    function FF_UsesDirectionalAtoms() result(doesit)
1302      logical :: doesit
1303 <    doesit = FF_uses_DirectionalAtoms .or. FF_uses_Dipoles .or. &
1360 <         FF_uses_Quadrupoles .or. FF_uses_Sticky .or. &
1361 <         FF_uses_StickyPower .or. FF_uses_GayBerne .or. FF_uses_Shapes
1303 >    doesit = FF_uses_DirectionalAtoms
1304    end function FF_UsesDirectionalAtoms
1305  
1306    function FF_RequiresPrepairCalc() result(doesit)

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines