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 2286 by gezelter, Wed Sep 7 22:08:39 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.39 2005-09-07 22:08:39 gezelter Exp $, $Date: 2005-09-07 22:08:39 $, $Name: not supported by cvs2svn $, $Revision: 1.39 $
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, 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 <    status = 0
165 <    
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 186 | 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 241 | 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
250  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,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
246 >    haveInteractionHash = .true.
247 >  end subroutine createInteractionHash
248  
249 <    stat = 0
264 <    if (.not. haveInteractionMap) then
249 >  subroutine createGtypeCutoffMap(stat)
250  
251 <       call createInteractionMap(myStatus)
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 >    logical :: GtypeFound
260  
261 +    integer :: myStatus, nAtypes,  i, j, istart, iend, jstart, jend
262 +    integer :: n_in_i, me_i, ia, g, atom1, nGroupTypes
263 +    real(kind=dp):: thisSigma, bigSigma, thisRcut, tol, skin
264 +    real(kind=dp) :: biggestAtypeCutoff
265 +
266 +    stat = 0
267 +    if (.not. haveInteractionHash) then
268 +       call createInteractionHash(myStatus)      
269         if (myStatus .ne. 0) then
270 <          write(default_error, *) 'createInteractionMap failed in doForces!'
270 >          write(default_error, *) 'createInteractionHash failed in doForces!'
271            stat = -1
272            return
273         endif
274      endif
275  
275
276      nAtypes = getSize(atypes)
277 < ! If we pass a default rcut, set all atypes to that cutoff distance
278 <    if(present(defaultRList)) then
279 <       InteractionMap(:,:)%rList = defaultRList
280 <       InteractionMap(:,:)%rListSq = defaultRList*defaultRList
281 <       haveRlist = .true.
282 <       return
283 <    end if
284 <
285 <    do map_i = 1,nAtypes
286 <       do map_j = map_i,nAtypes
287 <          iMap = InteractionMap(map_i, map_j)%InteractionHash
277 >    
278 >    do i = 1, nAtypes
279 >       if (SimHasAtype(i)) then    
280 >          call getElementProperty(atypes, i, "is_LennardJones", i_is_LJ)
281 >          call getElementProperty(atypes, i, "is_Electrostatic", i_is_Elect)
282 >          call getElementProperty(atypes, i, "is_Sticky", i_is_Sticky)
283 >          call getElementProperty(atypes, i, "is_StickyPower", i_is_StickyP)
284 >          call getElementProperty(atypes, i, "is_GayBerne", i_is_GB)
285 >          call getElementProperty(atypes, i, "is_EAM", i_is_EAM)
286 >          call getElementProperty(atypes, i, "is_Shape", i_is_Shape)
287            
288 <          if ( iand(iMap, LJ_PAIR).ne.0 ) then
289 < !            thisRCut = getLJCutOff(map_i,map_j)
290 <             if (thisRcut > actualCutoff) actualCutoff = thisRcut
288 >          atypeMaxCutoff(i) = 0.0_dp
289 >          if (i_is_LJ) then
290 >             thisRcut = getSigma(i) * 2.5_dp
291 >             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
292            endif
293 <          
294 <          if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
295 < !            thisRCut = getElectrostaticCutOff(map_i,map_j)
296 <             if (thisRcut > actualCutoff) actualCutoff = thisRcut
293 >          if (i_is_Elect) then
294 >             thisRcut = defaultRcut
295 >             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
296            endif
297 +          if (i_is_Sticky) then
298 +             thisRcut = getStickyCut(i)
299 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
300 +          endif
301 +          if (i_is_StickyP) then
302 +             thisRcut = getStickyPowerCut(i)
303 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
304 +          endif
305 +          if (i_is_GB) then
306 +             thisRcut = getGayBerneCut(i)
307 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
308 +          endif
309 +          if (i_is_EAM) then
310 +             thisRcut = getEAMCut(i)
311 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
312 +          endif
313 +          if (i_is_Shape) then
314 +             thisRcut = getShapeCut(i)
315 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
316 +          endif
317            
318 <          if ( iand(iMap, STICKY_PAIR).ne.0 ) then
319 < !             thisRCut = getStickyCutOff(map_i,map_j)
320 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
321 <           endif
322 <          
323 <           if ( iand(iMap, STICKYPOWER_PAIR).ne.0 ) then
324 < !              thisRCut = getStickyPowerCutOff(map_i,map_j)
325 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
326 <           endif
327 <          
328 <           if ( iand(iMap, GAYBERNE_PAIR).ne.0 ) then
329 < !              thisRCut = getGayberneCutOff(map_i,map_j)
330 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
331 <           endif
332 <          
333 <           if ( iand(iMap, GAYBERNE_LJ).ne.0 ) then
334 < !              thisRCut = getGaybrneLJCutOff(map_i,map_j)
335 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
336 <           endif
337 <          
338 <           if ( iand(iMap, EAM_PAIR).ne.0 ) then      
339 < !              thisRCut = getEAMCutOff(map_i,map_j)
340 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
341 <           endif
342 <          
343 <           if ( iand(iMap, SHAPE_PAIR).ne.0 ) then      
344 < !              thisRCut = getShapeCutOff(map_i,map_j)
345 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
346 <           endif
347 <          
348 <           if ( iand(iMap, SHAPE_LJ).ne.0 ) then      
349 < !              thisRCut = getShapeLJCutOff(map_i,map_j)
350 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
351 <           endif
352 <           InteractionMap(map_i, map_j)%rList = actualCutoff
353 <           InteractionMap(map_i, map_j)%rListSq = actualCutoff * actualCutoff
354 <        end do
355 <     end do
356 <          haveRlist = .true.
357 <  end subroutine createRcuts
358 <
340 <
341 < !!! THIS GOES AWAY FOR SIZE DEPENDENT CUTOFF
342 < !!$  subroutine setRlistDF( this_rlist )
343 < !!$
344 < !!$   real(kind=dp) :: this_rlist
345 < !!$
346 < !!$    rlist = this_rlist
347 < !!$    rlistsq = rlist * rlist
348 < !!$
349 < !!$    haveRlist = .true.
350 < !!$
351 < !!$  end subroutine setRlistDF
318 >          if (atypeMaxCutoff(i).gt.biggestAtypeCutoff) then
319 >             biggestAtypeCutoff = atypeMaxCutoff(i)
320 >          endif
321 >       endif
322 >    enddo
323 >  
324 >    nGroupTypes = 0
325 >    
326 >    istart = 1
327 > #ifdef IS_MPI
328 >    iend = nGroupsInRow
329 > #else
330 >    iend = nGroups
331 > #endif
332 >    
333 >    !! allocate the groupToGtype and gtypeMaxCutoff here.
334 >    if(.not.allocated(groupToGtype)) then
335 >       allocate(groupToGtype(iend))
336 >       allocate(groupMaxCutoff(iend))
337 >       allocate(gtypeMaxCutoff(iend))
338 >    endif
339 >    !! first we do a single loop over the cutoff groups to find the
340 >    !! largest cutoff for any atypes present in this group.  We also
341 >    !! create gtypes at this point.
342 >    
343 >    tol = 1.0d-6
344 >    
345 >    do i = istart, iend      
346 >       n_in_i = groupStartRow(i+1) - groupStartRow(i)
347 >       groupMaxCutoff(i) = 0.0_dp
348 >       do ia = groupStartRow(i), groupStartRow(i+1)-1
349 >          atom1 = groupListRow(ia)
350 > #ifdef IS_MPI
351 >          me_i = atid_row(atom1)
352 > #else
353 >          me_i = atid(atom1)
354 > #endif          
355 >          if (atypeMaxCutoff(me_i).gt.groupMaxCutoff(i)) then
356 >             groupMaxCutoff(i)=atypeMaxCutoff(me_i)
357 >          endif          
358 >       enddo
359  
360 +       if (nGroupTypes.eq.0) then
361 +          nGroupTypes = nGroupTypes + 1
362 +          gtypeMaxCutoff(nGroupTypes) = groupMaxCutoff(i)
363 +          groupToGtype(i) = nGroupTypes
364 +       else
365 +          GtypeFound = .false.
366 +          do g = 1, nGroupTypes
367 +             if ( abs(groupMaxCutoff(i) - gtypeMaxCutoff(g)).lt.tol) then
368 +                groupToGtype(i) = g
369 +                GtypeFound = .true.
370 +             endif
371 +          enddo
372 +          if (.not.GtypeFound) then            
373 +             nGroupTypes = nGroupTypes + 1
374 +             gtypeMaxCutoff(nGroupTypes) = groupMaxCutoff(i)
375 +             groupToGtype(i) = nGroupTypes
376 +          endif
377 +       endif
378 +    enddo    
379  
380 +    !! allocate the gtypeCutoffMap here.
381 +    allocate(gtypeCutoffMap(nGroupTypes,nGroupTypes))
382 +    !! then we do a double loop over all the group TYPES to find the cutoff
383 +    !! map between groups of two types
384 +    
385 +    do i = 1, nGroupTypes
386 +       do j = 1, nGroupTypes
387 +      
388 +          select case(cutoffPolicy)
389 +          case(TRADITIONAL_CUTOFF_POLICY)
390 +             thisRcut = maxval(gtypeMaxCutoff)
391 +          case(MIX_CUTOFF_POLICY)
392 +             thisRcut = 0.5_dp * (gtypeMaxCutoff(i) + gtypeMaxCutoff(j))
393 +          case(MAX_CUTOFF_POLICY)
394 +             thisRcut = max(gtypeMaxCutoff(i), gtypeMaxCutoff(j))
395 +          case default
396 +             call handleError("createGtypeCutoffMap", "Unknown Cutoff Policy")
397 +             return
398 +          end select
399 +          gtypeCutoffMap(i,j)%rcut = thisRcut
400 +          gtypeCutoffMap(i,j)%rcutsq = thisRcut*thisRcut
401 +          skin = defaultRlist - defaultRcut
402 +          gtypeCutoffMap(i,j)%rlistsq = (thisRcut + skin)**2
403 +
404 +       enddo
405 +    enddo
406 +    
407 +    haveGtypeCutoffMap = .true.
408 +    
409 +  end subroutine createGtypeCutoffMap
410 +  
411 +  subroutine setDefaultCutoffs(defRcut, defRsw, defRlist, cutPolicy)
412 +    real(kind=dp),intent(in) :: defRcut, defRsw, defRlist
413 +    integer, intent(in) :: cutPolicy
414 +    
415 +    defaultRcut = defRcut
416 +    defaultRsw = defRsw
417 +    defaultRlist = defRlist
418 +    cutoffPolicy = cutPolicy
419 +  end subroutine setDefaultCutoffs
420 +  
421 +  subroutine setCutoffPolicy(cutPolicy)
422 +
423 +     integer, intent(in) :: cutPolicy
424 +     cutoffPolicy = cutPolicy
425 +     call createGtypeCutoffMap()
426 +
427 +   end subroutine setCutoffPolicy
428 +    
429 +    
430    subroutine setSimVariables()
431      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()
432      SIM_uses_EAM = SimUsesEAM()
364    SIM_uses_Shapes = SimUsesShapes()
365    SIM_uses_FLARB = SimUsesFLARB()
433      SIM_uses_RF = SimUsesRF()
434      SIM_requires_postpair_calc = SimRequiresPostpairCalc()
435      SIM_requires_prepair_calc = SimRequiresPrepairCalc()
# Line 380 | Line 447 | contains
447  
448      error = 0
449  
450 <    if (.not. haveInteractionMap) then
450 >    if (.not. haveInteractionHash) then      
451 >       myStatus = 0      
452 >       call createInteractionHash(myStatus)      
453 >       if (myStatus .ne. 0) then
454 >          write(default_error, *) 'createInteractionHash failed in doForces!'
455 >          error = -1
456 >          return
457 >       endif
458 >    endif
459  
460 <       myStatus = 0
461 <
462 <       call createInteractionMap(myStatus)
388 <
460 >    if (.not. haveGtypeCutoffMap) then        
461 >       myStatus = 0      
462 >       call createGtypeCutoffMap(myStatus)      
463         if (myStatus .ne. 0) then
464 <          write(default_error, *) 'createInteractionMap failed in doForces!'
464 >          write(default_error, *) 'createGtypeCutoffMap failed in doForces!'
465            error = -1
466            return
467         endif
# Line 397 | Line 471 | contains
471         call setSimVariables()
472      endif
473  
474 <    if (.not. haveRlist) then
475 <       write(default_error, *) 'rList has not been set in doForces!'
476 <       error = -1
477 <       return
478 <    endif
474 >  !  if (.not. haveRlist) then
475 >  !     write(default_error, *) 'rList has not been set in doForces!'
476 >  !     error = -1
477 >  !     return
478 >  !  endif
479  
480      if (.not. haveNeighborList) then
481         write(default_error, *) 'neighbor list has not been initialized in doForces!'
# Line 426 | Line 500 | contains
500    end subroutine doReadyCheck
501  
502  
503 <  subroutine init_FF(use_RF_c, thisStat)
503 >  subroutine init_FF(use_RF, use_UW, use_DW, thisStat)
504  
505 <    logical, intent(in) :: use_RF_c
506 <
505 >    logical, intent(in) :: use_RF
506 >    logical, intent(in) :: use_UW
507 >    logical, intent(in) :: use_DW
508      integer, intent(out) :: thisStat  
509      integer :: my_status, nMatches
510 +    integer :: corrMethod
511      integer, pointer :: MatchList(:) => null()
512      real(kind=dp) :: rcut, rrf, rt, dielect
513  
# Line 439 | Line 515 | contains
515      thisStat = 0
516  
517      !! Fortran's version of a cast:
518 <    FF_uses_RF = use_RF_c
518 >    FF_uses_RF = use_RF
519  
520 +    !! set the electrostatic correction method
521 +    if (use_UW) then
522 +       corrMethod = 1
523 +    elseif (use_DW) then
524 +       corrMethod = 2
525 +    else
526 +       corrMethod = 0
527 +    endif
528 +    
529      !! init_FF is called *after* all of the atom types have been
530      !! defined in atype_module using the new_atype subroutine.
531      !!
# Line 448 | Line 533 | contains
533      !! interactions are used by the force field.    
534  
535      FF_uses_DirectionalAtoms = .false.
451    FF_uses_LennardJones = .false.
452    FF_uses_Electrostatics = .false.
453    FF_uses_Charges = .false.    
536      FF_uses_Dipoles = .false.
455    FF_uses_Sticky = .false.
456    FF_uses_StickyPower = .false.
537      FF_uses_GayBerne = .false.
538      FF_uses_EAM = .false.
459    FF_uses_Shapes = .false.
460    FF_uses_FLARB = .false.
539  
540      call getMatchingElementList(atypes, "is_Directional", .true., &
541           nMatches, MatchList)
542      if (nMatches .gt. 0) FF_uses_DirectionalAtoms = .true.
543  
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
544      call getMatchingElementList(atypes, "is_Dipole", .true., &
545           nMatches, MatchList)
546 <    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
546 >    if (nMatches .gt. 0) FF_uses_Dipoles = .true.
547      
548      call getMatchingElementList(atypes, "is_GayBerne", .true., &
549           nMatches, MatchList)
550 <    if (nMatches .gt. 0) then
516 <       FF_uses_GayBerne = .true.
517 <       FF_uses_DirectionalAtoms = .true.
518 <    endif
550 >    if (nMatches .gt. 0) FF_uses_GayBerne = .true.
551  
552      call getMatchingElementList(atypes, "is_EAM", .true., nMatches, MatchList)
553      if (nMatches .gt. 0) FF_uses_EAM = .true.
554  
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
555  
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)
556      haveSaneForceField = .true.
557  
558      !! check to make sure the FF_uses_RF setting makes sense
559  
560 <    if (FF_uses_dipoles) then
560 >    if (FF_uses_Dipoles) then
561         if (FF_uses_RF) then
562            dielect = getDielect()
563            call initialize_rf(dielect)
# Line 550 | Line 571 | contains
571         endif
572      endif
573  
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
562
574      if (FF_uses_EAM) then
575         call init_EAM_FF(my_status)
576         if (my_status /= 0) then
# Line 579 | Line 590 | contains
590         endif
591      endif
592  
582    if (FF_uses_GayBerne .and. FF_uses_LennardJones) then
583    endif
584
593      if (.not. haveNeighborList) then
594         !! Create neighbor lists
595         call expandNeighborList(nLocal, my_status)
# Line 645 | Line 653 | contains
653      integer :: localError
654      integer :: propPack_i, propPack_j
655      integer :: loopStart, loopEnd, loop
656 <    integer :: iMap
656 >    integer :: iHash
657      real(kind=dp) :: listSkin = 1.0  
658  
659      !! initialize local variables  
# Line 743 | Line 751 | contains
751  
752            if (update_nlist) then
753   #ifdef IS_MPI
746             me_i = atid_row(i)
754               jstart = 1
755               jend = nGroupsInCol
756   #else
750             me_i = atid(i)
757               jstart = i+1
758               jend = nGroups
759   #endif
# Line 775 | Line 781 | contains
781                    q_group(:,j), d_grp, rgrpsq)
782   #endif
783  
784 <             if (rgrpsq < InteractionMap(me_i,me_j)%rListsq) then
784 >             if (rgrpsq < gtypeCutoffMap(groupToGtype(i),groupToGtype(j))%rListsq) then
785                  if (update_nlist) then
786                     nlist = nlist + 1
787  
# Line 993 | Line 999 | contains
999   #else
1000               me_i = atid(i)
1001   #endif
1002 <             iMap = InteractionMap(me_i, me_j)%InteractionHash
1002 >             iHash = InteractionHash(me_i,me_j)
1003              
1004 <             if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
1004 >             if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then
1005  
1006                  mu_i = getDipoleMoment(me_i)
1007  
# Line 1062 | Line 1068 | contains
1068      real ( kind = dp ) :: ebalance
1069      integer :: me_i, me_j
1070  
1071 <    integer :: iMap
1071 >    integer :: iHash
1072  
1073      r = sqrt(rijsq)
1074      vpair = 0.0d0
# Line 1076 | Line 1082 | contains
1082      me_j = atid(j)
1083   #endif
1084  
1085 <    iMap = InteractionMap(me_i, me_j)%InteractionHash
1085 >    iHash = InteractionHash(me_i, me_j)
1086  
1087 <    if ( iand(iMap, LJ_PAIR).ne.0 ) then
1087 >    if ( iand(iHash, LJ_PAIR).ne.0 ) then
1088         call do_lj_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot)
1089      endif
1090  
1091 <    if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
1091 >    if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then
1092         call doElectrostaticPair(i, j, d, r, rijsq, sw, vpair, fpair, &
1093 <            pot, eFrame, f, t, do_pot)
1093 >            pot, eFrame, f, t, do_pot, corrMethod)
1094  
1095         if (FF_uses_RF .and. SIM_uses_RF) then
1096  
# Line 1095 | Line 1101 | contains
1101  
1102      endif
1103  
1104 <    if ( iand(iMap, STICKY_PAIR).ne.0 ) then
1104 >    if ( iand(iHash, STICKY_PAIR).ne.0 ) then
1105         call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1106              pot, A, f, t, do_pot)
1107      endif
1108  
1109 <    if ( iand(iMap, STICKYPOWER_PAIR).ne.0 ) then
1109 >    if ( iand(iHash, STICKYPOWER_PAIR).ne.0 ) then
1110         call do_sticky_power_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1111              pot, A, f, t, do_pot)
1112      endif
1113  
1114 <    if ( iand(iMap, GAYBERNE_PAIR).ne.0 ) then
1114 >    if ( iand(iHash, GAYBERNE_PAIR).ne.0 ) then
1115         call do_gb_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1116              pot, A, f, t, do_pot)
1117      endif
1118      
1119 <    if ( iand(iMap, GAYBERNE_LJ).ne.0 ) then
1119 >    if ( iand(iHash, GAYBERNE_LJ).ne.0 ) then
1120   !      call do_gblj_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1121   !           pot, A, f, t, do_pot)
1122      endif
1123  
1124 <    if ( iand(iMap, EAM_PAIR).ne.0 ) then      
1124 >    if ( iand(iHash, EAM_PAIR).ne.0 ) then      
1125         call do_eam_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, &
1126              do_pot)
1127      endif
1128  
1129 <    if ( iand(iMap, SHAPE_PAIR).ne.0 ) then      
1129 >    if ( iand(iHash, SHAPE_PAIR).ne.0 ) then      
1130         call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1131              pot, A, f, t, do_pot)
1132      endif
1133  
1134 <    if ( iand(iMap, SHAPE_LJ).ne.0 ) then      
1134 >    if ( iand(iHash, SHAPE_LJ).ne.0 ) then      
1135         call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1136              pot, A, f, t, do_pot)
1137      endif
# Line 1147 | Line 1153 | contains
1153      real ( kind = dp )                :: r, rc
1154      real ( kind = dp ), intent(inout) :: d(3), dc(3)
1155  
1156 <    integer :: me_i, me_j, iMap
1156 >    integer :: me_i, me_j, iHash
1157  
1158   #ifdef IS_MPI  
1159      me_i = atid_row(i)
# Line 1157 | Line 1163 | contains
1163      me_j = atid(j)  
1164   #endif
1165  
1166 <    iMap = InteractionMap(me_i, me_j)%InteractionHash
1166 >    iHash = InteractionHash(me_i, me_j)
1167  
1168 <    if ( iand(iMap, EAM_PAIR).ne.0 ) then      
1168 >    if ( iand(iHash, EAM_PAIR).ne.0 ) then      
1169              call calc_EAM_prepair_rho(i, j, d, r, rijsq )
1170      endif
1171      
# Line 1356 | Line 1362 | contains
1362  
1363    function FF_UsesDirectionalAtoms() result(doesit)
1364      logical :: doesit
1365 <    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
1365 >    doesit = FF_uses_DirectionalAtoms
1366    end function FF_UsesDirectionalAtoms
1367  
1368    function FF_RequiresPrepairCalc() result(doesit)

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines