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 2280 by gezelter, Thu Sep 1 20:17:55 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.34 2005-09-01 20:17:55 gezelter Exp $, $Date: 2005-09-01 20:17:55 $, $Name: not supported by cvs2svn $, $Revision: 1.34 $
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 >  logical, save :: haveRlist = .false.
89  
90    logical, save :: FF_uses_DirectionalAtoms
88  logical, save :: FF_uses_LennardJones
89  logical, save :: FF_uses_Electrostatics
90  logical, save :: FF_uses_Charges
91    logical, save :: FF_uses_Dipoles
92  logical, save :: FF_uses_Quadrupoles
93  logical, save :: FF_uses_Sticky
94  logical, save :: FF_uses_StickyPower
92    logical, save :: FF_uses_GayBerne
93    logical, save :: FF_uses_EAM
97  logical, save :: FF_uses_Shapes
98  logical, save :: FF_uses_FLARB
94    logical, save :: FF_uses_RF
95  
96    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
97    logical, save :: SIM_uses_EAM
111  logical, save :: SIM_uses_Shapes
112  logical, save :: SIM_uses_FLARB
98    logical, save :: SIM_uses_RF
99    logical, save :: SIM_requires_postpair_calc
100    logical, save :: SIM_requires_prepair_calc
101    logical, save :: SIM_uses_PBC
117  logical, save :: SIM_uses_molecular_cutoffs
102  
103 <  !!!GO AWAY---------
120 <  !!!!!real(kind=dp), save :: rlist, rlistsq
103 >  integer, save :: corrMethod
104  
105    public :: init_FF
106 +  public :: setDefaultCutoffs
107    public :: do_force_loop
108 < !  public :: setRlistDF
109 <  !public :: addInteraction
110 <  !public :: setInteractionHash
111 <  !public :: getInteractionHash
112 <  public :: createInteractionMap
113 <  public :: createRcuts
108 >  public :: createInteractionHash
109 >  public :: createGtypeCutoffMap
110 >  public :: getStickyCut
111 >  public :: getStickyPowerCut
112 >  public :: getGayBerneCut
113 >  public :: getEAMCut
114 >  public :: getShapeCut
115  
116   #ifdef PROFILE
117    public :: getforcetime
# Line 134 | Line 119 | module doForces
119    real :: forceTimeInitial, forceTimeFinal
120    integer :: nLoops
121   #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
122    
123 <  type(Interaction), dimension(:,:),allocatable :: InteractionMap
124 <  
123 >  !! Variables for cutoff mapping and interaction mapping
124 >  ! Bit hash to determine pair-pair interactions.
125 >  integer, dimension(:,:), allocatable :: InteractionHash
126 >  real(kind=dp), dimension(:), allocatable :: atypeMaxCutoff
127 >  real(kind=dp), dimension(:), allocatable :: groupMaxCutoff
128 >  integer, dimension(:), allocatable :: groupToGtype
129 >  real(kind=dp), dimension(:), allocatable :: gtypeMaxCutoff
130 >  type ::gtypeCutoffs
131 >     real(kind=dp) :: rcut
132 >     real(kind=dp) :: rcutsq
133 >     real(kind=dp) :: rlistsq
134 >  end type gtypeCutoffs
135 >  type(gtypeCutoffs), dimension(:,:), allocatable :: gtypeCutoffMap
136  
137 +  integer, save :: cutoffPolicy = TRADITIONAL_CUTOFF_POLICY
138 +  real(kind=dp),save :: defaultRcut, defaultRsw, defaultRlist
139    
140   contains
141  
142 <
151 <  subroutine createInteractionMap(status)
142 >  subroutine createInteractionHash(status)
143      integer :: nAtypes
144 <    integer :: status
144 >    integer, intent(out) :: status
145      integer :: i
146      integer :: j
147 <    integer :: ihash
148 <    real(kind=dp) :: myRcut
158 < ! Test Types
147 >    integer :: iHash
148 >    !! Test Types
149      logical :: i_is_LJ
150      logical :: i_is_Elect
151      logical :: i_is_Sticky
# Line 170 | Line 160 | contains
160      logical :: j_is_GB
161      logical :: j_is_EAM
162      logical :: j_is_Shape
163 <    
164 <    
163 >    real(kind=dp) :: myRcut
164 >
165 >    status = 0  
166 >
167      if (.not. associated(atypes)) then
168 <       call handleError("atype", "atypes was not present before call of createDefaultInteractionMap!")
168 >       call handleError("atype", "atypes was not present before call of createInteractionHash!")
169         status = -1
170         return
171      endif
# Line 185 | Line 177 | contains
177         return
178      end if
179  
180 <    if (.not. allocated(InteractionMap)) then
181 <       allocate(InteractionMap(nAtypes,nAtypes))
180 >    if (.not. allocated(InteractionHash)) then
181 >       allocate(InteractionHash(nAtypes,nAtypes))
182      endif
183 +
184 +    if (.not. allocated(atypeMaxCutoff)) then
185 +       allocate(atypeMaxCutoff(nAtypes))
186 +    endif
187          
188      do i = 1, nAtypes
189         call getElementProperty(atypes, i, "is_LennardJones", i_is_LJ)
# Line 240 | Line 236 | contains
236            if (i_is_LJ .and. j_is_Shape) iHash = ior(iHash, SHAPE_LJ)
237  
238  
239 <          InteractionMap(i,j)%InteractionHash = iHash
240 <          InteractionMap(j,i)%InteractionHash = iHash
239 >          InteractionHash(i,j) = iHash
240 >          InteractionHash(j,i) = iHash
241  
242         end do
243  
244      end do
249  end subroutine createInteractionMap
245  
246 < ! 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.
247 <  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
246 >    haveInteractionHash = .true.
247 >  end subroutine createInteractionHash
248  
249 <    if(.not. allocated(InteractionMap)) return
249 >  subroutine createGtypeCutoffMap(stat)
250  
251 <    nAtypes = getSize(atypes)
252 < ! If we pass a default rcut, set all atypes to that cutoff distance
253 <    if(present(defaultRList)) then
254 <       InteractionMap(:,:)%rList = defaultRList
255 <       InteractionMap(:,:)%rListSq = defaultRList*defaultRList
256 <       haveRlist = .true.
257 <       return
258 <    end if
251 >    integer, intent(out), optional :: stat
252 >    logical :: i_is_LJ
253 >    logical :: i_is_Elect
254 >    logical :: i_is_Sticky
255 >    logical :: i_is_StickyP
256 >    logical :: i_is_GB
257 >    logical :: i_is_EAM
258 >    logical :: i_is_Shape
259  
260 <    do map_i = 1,nAtypes
261 <       do map_j = map_i,nAtypes
262 <          iMap = InteractionMap(map_i, map_j)%InteractionHash
263 <          
264 <          if ( iand(iMap, LJ_PAIR).ne.0 ) then
265 < !            thisRCut = getLJCutOff(map_i,map_j)
266 <             if (thisRcut > actualCutoff) actualCutoff = thisRcut
267 <          endif
260 >    integer :: myStatus, nAtypes,  i, j, istart, iend, jstart, jend
261 >    integer :: n_in_i, me_i, ia, g, atom1, nGroupTypes
262 >    real(kind=dp):: thisSigma, bigSigma, thisRcut, tol, skin
263 >    real(kind=dp) :: biggestAtypeCutoff
264 >
265 >    stat = 0
266 >    if (.not. haveInteractionHash) then
267 >       call createInteractionHash(myStatus)      
268 >       if (myStatus .ne. 0) then
269 >          write(default_error, *) 'createInteractionHash failed in doForces!'
270 >          stat = -1
271 >          return
272 >       endif
273 >    endif
274 >
275 >    nAtypes = getSize(atypes)
276 >    
277 >    do i = 1, nAtypes
278 >       if (SimHasAtype(i)) then          
279 >          call getElementProperty(atypes, i, "is_LennardJones", i_is_LJ)
280 >          call getElementProperty(atypes, i, "is_Electrostatic", i_is_Elect)
281 >          call getElementProperty(atypes, i, "is_Sticky", i_is_Sticky)
282 >          call getElementProperty(atypes, i, "is_StickyPower", i_is_StickyP)
283 >          call getElementProperty(atypes, i, "is_GayBerne", i_is_GB)
284 >          call getElementProperty(atypes, i, "is_EAM", i_is_EAM)
285 >          call getElementProperty(atypes, i, "is_Shape", i_is_Shape)
286            
287 <          if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
288 < !            thisRCut = getElectrostaticCutOff(map_i,map_j)
289 <             if (thisRcut > actualCutoff) actualCutoff = thisRcut
287 >          if (i_is_LJ) then
288 >             thisRcut = getSigma(i) * 2.5_dp
289 >             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
290            endif
291 +          if (i_is_Elect) then
292 +             thisRcut = defaultRcut
293 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
294 +          endif
295 +          if (i_is_Sticky) then
296 +             thisRcut = getStickyCut(i)
297 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
298 +          endif
299 +          if (i_is_StickyP) then
300 +             thisRcut = getStickyPowerCut(i)
301 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
302 +          endif
303 +          if (i_is_GB) then
304 +             thisRcut = getGayBerneCut(i)
305 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
306 +          endif
307 +          if (i_is_EAM) then
308 +             thisRcut = getEAMCut(i)
309 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
310 +          endif
311 +          if (i_is_Shape) then
312 +             thisRcut = getShapeCut(i)
313 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
314 +          endif
315            
316 <          if ( iand(iMap, STICKY_PAIR).ne.0 ) then
317 < !             thisRCut = getStickyCutOff(map_i,map_j)
318 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
319 <           endif
320 <          
321 <           if ( iand(iMap, STICKYPOWER_PAIR).ne.0 ) then
322 < !              thisRCut = getStickyPowerCutOff(map_i,map_j)
323 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
324 <           endif
325 <          
326 <           if ( iand(iMap, GAYBERNE_PAIR).ne.0 ) then
327 < !              thisRCut = getGayberneCutOff(map_i,map_j)
328 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
329 <           endif
299 <          
300 <           if ( iand(iMap, GAYBERNE_LJ).ne.0 ) then
301 < !              thisRCut = getGaybrneLJCutOff(map_i,map_j)
302 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
303 <           endif
304 <          
305 <           if ( iand(iMap, EAM_PAIR).ne.0 ) then      
306 < !              thisRCut = getEAMCutOff(map_i,map_j)
307 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
308 <           endif
309 <          
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
316 >          if (atypeMaxCutoff(i).gt.biggestAtypeCutoff) then
317 >             biggestAtypeCutoff = atypeMaxCutoff(i)
318 >          endif
319 >       endif
320 >    enddo
321 >  
322 >    nGroupTypes = 0
323 >    
324 >    istart = 1
325 > #ifdef IS_MPI
326 >    iend = nGroupsInRow
327 > #else
328 >    iend = nGroups
329 > #endif
330  
331 <
332 < !!! THIS GOES AWAY FOR SIZE DEPENDENT CUTOFF
333 < !!$  subroutine setRlistDF( this_rlist )
334 < !!$
335 < !!$   real(kind=dp) :: this_rlist
336 < !!$
337 < !!$    rlist = this_rlist
338 < !!$    rlistsq = rlist * rlist
339 < !!$
340 < !!$    haveRlist = .true.
341 < !!$
342 < !!$  end subroutine setRlistDF
331 >    !! allocate the groupToGtype and gtypeMaxCutoff here.
332 >    
333 >    !! first we do a single loop over the cutoff groups to find the largest cutoff for any atypes
334 >    !! present in this group.   We also create gtypes at this point.
335 >    tol = 1.0d-6
336 >    
337 >    do i = istart, iend      
338 >       n_in_i = groupStartRow(i+1) - groupStartRow(i)
339 >       groupMaxCutoff(i) = 0.0_dp
340 >       do ia = groupStartRow(i), groupStartRow(i+1)-1
341 >          atom1 = groupListRow(ia)
342 > #ifdef IS_MPI
343 >          me_i = atid_row(atom1)
344 > #else
345 >          me_i = atid(atom1)
346 > #endif          
347 >          if (atypeMaxCutoff(me_i).gt.groupMaxCutoff(i)) then
348 >             groupMaxCutoff(i)=atypeMaxCutoff(me_i)
349 >          endif
350 >       enddo
351 >       if (nGroupTypes.eq.0) then
352 >          nGroupTypes = nGroupTypes + 1
353 >          gtypeMaxCutoff(nGroupTypes) = groupMaxCutoff(i)
354 >          groupToGtype(i) = nGroupTypes
355 >       else
356 >          do g = 1, nGroupTypes
357 >             if ( abs(groupMaxCutoff(i) - gtypeMaxCutoff(g)).gt.tol) then
358 >                nGroupTypes = nGroupTypes + 1
359 >                gtypeMaxCutoff(nGroupTypes) = groupMaxCutoff(i)
360 >                groupToGtype(i) = nGroupTypes
361 >             else
362 >                groupToGtype(i) = g
363 >             endif
364 >          enddo
365 >       endif
366 >    enddo
367 >    
368 >    !! allocate the gtypeCutoffMap here.
369  
370 +    !! then we do a double loop over all the group TYPES to find the cutoff
371 +    !! map between groups of two types
372 +    
373 +    do i = 1, nGroupTypes
374 +       do j = 1, nGroupTypes
375 +      
376 +          select case(cutoffPolicy)
377 +             case(TRADITIONAL_CUTOFF_POLICY)
378 +                thisRcut = maxval(gtypeMaxCutoff)
379 +             case(MIX_CUTOFF_POLICY)
380 +                thisRcut = 0.5_dp * (gtypeMaxCutoff(i) + gtypeMaxCutoff(j))
381 +             case(MAX_CUTOFF_POLICY)
382 +                thisRcut = max(gtypeMaxCutoff(i), gtypeMaxCutoff(j))
383 +             case default
384 +                call handleError("createGtypeCutoffMap", "Unknown Cutoff Policy")
385 +                return
386 +          end select      
387 +         gtypeCutoffMap(i,j)%rcut = thisRcut
388 +         gtypeCutoffMap(i,j)%rcutsq = thisRcut*thisRcut
389 +         skin = defaultRlist - defaultRcut
390 +         gtypeCutoffMap(i,j)%rlistsq = (thisRcut + skin)**2
391 +       enddo
392 +    enddo
393 +    
394 +    haveGtypeCutoffMap = .true.
395 +   end subroutine createGtypeCutoffMap
396  
397 +   subroutine setDefaultCutoffs(defRcut, defRsw, defRlist, cutPolicy)
398 +     real(kind=dp),intent(in) :: defRcut, defRsw, defRlist
399 +     integer, intent(in) :: cutPolicy
400 +
401 +     defaultRcut = defRcut
402 +     defaultRsw = defRsw
403 +     defaultRlist = defRlist
404 +     cutoffPolicy = cutPolicy
405 +   end subroutine setDefaultCutoffs
406 +
407 +   subroutine setCutoffPolicy(cutPolicy)
408 +
409 +     integer, intent(in) :: cutPolicy
410 +     cutoffPolicy = cutPolicy
411 +     call createGtypeCutoffMap()
412 +
413 +   end subroutine setCutoffPolicy
414 +    
415 +    
416    subroutine setSimVariables()
417      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()
418      SIM_uses_EAM = SimUsesEAM()
350    SIM_uses_Shapes = SimUsesShapes()
351    SIM_uses_FLARB = SimUsesFLARB()
419      SIM_uses_RF = SimUsesRF()
420      SIM_requires_postpair_calc = SimRequiresPostpairCalc()
421      SIM_requires_prepair_calc = SimRequiresPrepairCalc()
# Line 366 | Line 433 | contains
433  
434      error = 0
435  
436 <    if (.not. haveInteractionMap) then
436 >    if (.not. haveInteractionHash) then      
437 >       myStatus = 0      
438 >       call createInteractionHash(myStatus)      
439 >       if (myStatus .ne. 0) then
440 >          write(default_error, *) 'createInteractionHash failed in doForces!'
441 >          error = -1
442 >          return
443 >       endif
444 >    endif
445  
446 <       myStatus = 0
447 <
448 <       call createInteractionMap(myStatus)
374 <
446 >    if (.not. haveGtypeCutoffMap) then        
447 >       myStatus = 0      
448 >       call createGtypeCutoffMap(myStatus)      
449         if (myStatus .ne. 0) then
450 <          write(default_error, *) 'createInteractionMap failed in doForces!'
450 >          write(default_error, *) 'createGtypeCutoffMap failed in doForces!'
451            error = -1
452            return
453         endif
# Line 412 | Line 486 | contains
486    end subroutine doReadyCheck
487  
488  
489 <  subroutine init_FF(use_RF_c, thisStat)
489 >  subroutine init_FF(use_RF, use_UW, use_DW, thisStat)
490  
491 <    logical, intent(in) :: use_RF_c
492 <
491 >    logical, intent(in) :: use_RF
492 >    logical, intent(in) :: use_UW
493 >    logical, intent(in) :: use_DW
494      integer, intent(out) :: thisStat  
495      integer :: my_status, nMatches
496 +    integer :: corrMethod
497      integer, pointer :: MatchList(:) => null()
498      real(kind=dp) :: rcut, rrf, rt, dielect
499  
# Line 425 | Line 501 | contains
501      thisStat = 0
502  
503      !! Fortran's version of a cast:
504 <    FF_uses_RF = use_RF_c
504 >    FF_uses_RF = use_RF
505  
506 +    !! set the electrostatic correction method
507 +    if (use_UW) then
508 +       corrMethod = 1
509 +    elseif (use_DW) then
510 +       corrMethod = 2
511 +    else
512 +       corrMethod = 0
513 +    endif
514 +    
515      !! init_FF is called *after* all of the atom types have been
516      !! defined in atype_module using the new_atype subroutine.
517      !!
# Line 434 | Line 519 | contains
519      !! interactions are used by the force field.    
520  
521      FF_uses_DirectionalAtoms = .false.
437    FF_uses_LennardJones = .false.
438    FF_uses_Electrostatics = .false.
439    FF_uses_Charges = .false.    
522      FF_uses_Dipoles = .false.
441    FF_uses_Sticky = .false.
442    FF_uses_StickyPower = .false.
523      FF_uses_GayBerne = .false.
524      FF_uses_EAM = .false.
445    FF_uses_Shapes = .false.
446    FF_uses_FLARB = .false.
525  
526      call getMatchingElementList(atypes, "is_Directional", .true., &
527           nMatches, MatchList)
528      if (nMatches .gt. 0) FF_uses_DirectionalAtoms = .true.
529  
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
530      call getMatchingElementList(atypes, "is_Dipole", .true., &
531           nMatches, MatchList)
532 <    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
532 >    if (nMatches .gt. 0) FF_uses_Dipoles = .true.
533      
534      call getMatchingElementList(atypes, "is_GayBerne", .true., &
535           nMatches, MatchList)
536 <    if (nMatches .gt. 0) then
502 <       FF_uses_GayBerne = .true.
503 <       FF_uses_DirectionalAtoms = .true.
504 <    endif
536 >    if (nMatches .gt. 0) FF_uses_GayBerne = .true.
537  
538      call getMatchingElementList(atypes, "is_EAM", .true., nMatches, MatchList)
539      if (nMatches .gt. 0) FF_uses_EAM = .true.
540  
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
541  
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)
542      haveSaneForceField = .true.
543  
544      !! check to make sure the FF_uses_RF setting makes sense
545  
546 <    if (FF_uses_dipoles) then
546 >    if (FF_uses_Dipoles) then
547         if (FF_uses_RF) then
548            dielect = getDielect()
549            call initialize_rf(dielect)
# Line 535 | Line 556 | contains
556            return
557         endif
558      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
559  
560      if (FF_uses_EAM) then
561         call init_EAM_FF(my_status)
# Line 565 | Line 576 | contains
576         endif
577      endif
578  
568    if (FF_uses_GayBerne .and. FF_uses_LennardJones) then
569    endif
570
579      if (.not. haveNeighborList) then
580         !! Create neighbor lists
581         call expandNeighborList(nLocal, my_status)
# Line 631 | Line 639 | contains
639      integer :: localError
640      integer :: propPack_i, propPack_j
641      integer :: loopStart, loopEnd, loop
642 <    integer :: iMap
642 >    integer :: iHash
643      real(kind=dp) :: listSkin = 1.0  
644  
645      !! initialize local variables  
# Line 750 | Line 758 | contains
758               endif
759  
760   #ifdef IS_MPI
761 +             me_j = atid_col(j)
762               call get_interatomic_vector(q_group_Row(:,i), &
763                    q_group_Col(:,j), d_grp, rgrpsq)
764   #else
765 +             me_j = atid(j)
766               call get_interatomic_vector(q_group(:,i), &
767                    q_group(:,j), d_grp, rgrpsq)
768   #endif
769  
770 <             if (rgrpsq < InteractionMap(me_i,me_j)%rListsq) then
770 >             if (rgrpsq < gtypeCutoffMap(groupToGtype(i),groupToGtype(j))%rListsq) then
771                  if (update_nlist) then
772                     nlist = nlist + 1
773  
# Line 975 | Line 985 | contains
985   #else
986               me_i = atid(i)
987   #endif
988 <             iMap = InteractionMap(me_i, me_j)%InteractionHash
988 >             iHash = InteractionHash(me_i,me_j)
989              
990 <             if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
990 >             if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then
991  
992                  mu_i = getDipoleMoment(me_i)
993  
# Line 1044 | Line 1054 | contains
1054      real ( kind = dp ) :: ebalance
1055      integer :: me_i, me_j
1056  
1057 <    integer :: iMap
1057 >    integer :: iHash
1058  
1059      r = sqrt(rijsq)
1060      vpair = 0.0d0
# Line 1058 | Line 1068 | contains
1068      me_j = atid(j)
1069   #endif
1070  
1071 <    iMap = InteractionMap(me_i, me_j)%InteractionHash
1071 >    iHash = InteractionHash(me_i, me_j)
1072  
1073 <    if ( iand(iMap, LJ_PAIR).ne.0 ) then
1073 >    if ( iand(iHash, LJ_PAIR).ne.0 ) then
1074         call do_lj_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot)
1075      endif
1076  
1077 <    if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
1077 >    if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then
1078         call doElectrostaticPair(i, j, d, r, rijsq, sw, vpair, fpair, &
1079 <            pot, eFrame, f, t, do_pot)
1079 >            pot, eFrame, f, t, do_pot, corrMethod)
1080  
1081         if (FF_uses_RF .and. SIM_uses_RF) then
1082  
# Line 1077 | Line 1087 | contains
1087  
1088      endif
1089  
1090 <    if ( iand(iMap, STICKY_PAIR).ne.0 ) then
1090 >    if ( iand(iHash, STICKY_PAIR).ne.0 ) then
1091         call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1092              pot, A, f, t, do_pot)
1093      endif
1094  
1095 <    if ( iand(iMap, STICKYPOWER_PAIR).ne.0 ) then
1095 >    if ( iand(iHash, STICKYPOWER_PAIR).ne.0 ) then
1096         call do_sticky_power_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1097              pot, A, f, t, do_pot)
1098      endif
1099  
1100 <    if ( iand(iMap, GAYBERNE_PAIR).ne.0 ) then
1100 >    if ( iand(iHash, GAYBERNE_PAIR).ne.0 ) then
1101         call do_gb_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1102              pot, A, f, t, do_pot)
1103      endif
1104      
1105 <    if ( iand(iMap, GAYBERNE_LJ).ne.0 ) then
1105 >    if ( iand(iHash, GAYBERNE_LJ).ne.0 ) then
1106   !      call do_gblj_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1107   !           pot, A, f, t, do_pot)
1108      endif
1109  
1110 <    if ( iand(iMap, EAM_PAIR).ne.0 ) then      
1110 >    if ( iand(iHash, EAM_PAIR).ne.0 ) then      
1111         call do_eam_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, &
1112              do_pot)
1113      endif
1114  
1115 <    if ( iand(iMap, SHAPE_PAIR).ne.0 ) then      
1115 >    if ( iand(iHash, SHAPE_PAIR).ne.0 ) then      
1116         call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1117              pot, A, f, t, do_pot)
1118      endif
1119  
1120 <    if ( iand(iMap, SHAPE_LJ).ne.0 ) then      
1120 >    if ( iand(iHash, SHAPE_LJ).ne.0 ) then      
1121         call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1122              pot, A, f, t, do_pot)
1123      endif
# Line 1129 | Line 1139 | contains
1139      real ( kind = dp )                :: r, rc
1140      real ( kind = dp ), intent(inout) :: d(3), dc(3)
1141  
1142 <    integer :: me_i, me_j, iMap
1142 >    integer :: me_i, me_j, iHash
1143  
1144   #ifdef IS_MPI  
1145      me_i = atid_row(i)
# Line 1139 | Line 1149 | contains
1149      me_j = atid(j)  
1150   #endif
1151  
1152 <    iMap = InteractionMap(me_i, me_j)%InteractionHash
1152 >    iHash = InteractionHash(me_i, me_j)
1153  
1154 <    if ( iand(iMap, EAM_PAIR).ne.0 ) then      
1154 >    if ( iand(iHash, EAM_PAIR).ne.0 ) then      
1155              call calc_EAM_prepair_rho(i, j, d, r, rijsq )
1156      endif
1157      
# Line 1338 | Line 1348 | contains
1348  
1349    function FF_UsesDirectionalAtoms() result(doesit)
1350      logical :: doesit
1351 <    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
1351 >    doesit = FF_uses_DirectionalAtoms
1352    end function FF_UsesDirectionalAtoms
1353  
1354    function FF_RequiresPrepairCalc() result(doesit)

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines