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 2267 by tim, Fri Jul 29 17:34:06 2005 UTC vs.
Revision 2309 by chrisfen, Sun Sep 18 20:45:38 2005 UTC

# Line 45 | Line 45
45  
46   !! @author Charles F. Vardeman II
47   !! @author Matthew Meineke
48 < !! @version $Id: doForces.F90,v 1.25 2005-07-29 17:34:06 tim Exp $, $Date: 2005-07-29 17:34:06 $, $Name: not supported by cvs2svn $, $Revision: 1.25 $
48 > !! @version $Id: doForces.F90,v 1.46 2005-09-18 20:45:38 chrisfen Exp $, $Date: 2005-09-18 20:45:38 $, $Name: not supported by cvs2svn $, $Revision: 1.46 $
49  
50  
51   module doForces
# Line 58 | Line 58 | module doForces
58    use lj
59    use sticky
60    use electrostatic_module
61 <  use reaction_field
61 >  use reaction_field_module
62    use gb_pair
63    use shapes
64    use vector_class
# 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
99  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
113  logical, save :: SIM_uses_RF
97    logical, save :: SIM_requires_postpair_calc
98    logical, save :: SIM_requires_prepair_calc
99    logical, save :: SIM_uses_PBC
117  logical, save :: SIM_uses_molecular_cutoffs
100  
101 <  !!!GO AWAY---------
120 <  !!!!!real(kind=dp), save :: rlist, rlistsq
101 >  integer, save :: electrostaticSummationMethod
102  
103    public :: init_FF
104 +  public :: setDefaultCutoffs
105    public :: do_force_loop
106 < !  public :: setRlistDF
107 <  !public :: addInteraction
108 <  !public :: setInteractionHash
109 <  !public :: getInteractionHash
110 <  public :: createInteractionMap
111 <  public :: createRcuts
106 >  public :: createInteractionHash
107 >  public :: createGtypeCutoffMap
108 >  public :: getStickyCut
109 >  public :: getStickyPowerCut
110 >  public :: getGayBerneCut
111 >  public :: getEAMCut
112 >  public :: getShapeCut
113  
114   #ifdef PROFILE
115    public :: getforcetime
# Line 134 | Line 117 | module doForces
117    real :: forceTimeInitial, forceTimeFinal
118    integer :: nLoops
119   #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
120    
121 <  type(Interaction), dimension(:,:),allocatable :: InteractionMap
122 <  
121 >  !! Variables for cutoff mapping and interaction mapping
122 >  ! Bit hash to determine pair-pair interactions.
123 >  integer, dimension(:,:), allocatable :: InteractionHash
124 >  real(kind=dp), dimension(:), allocatable :: atypeMaxCutoff
125 >  real(kind=dp), dimension(:), allocatable :: groupMaxCutoff
126 >  integer, dimension(:), allocatable :: groupToGtype
127 >  real(kind=dp), dimension(:), allocatable :: gtypeMaxCutoff
128 >  type ::gtypeCutoffs
129 >     real(kind=dp) :: rcut
130 >     real(kind=dp) :: rcutsq
131 >     real(kind=dp) :: rlistsq
132 >  end type gtypeCutoffs
133 >  type(gtypeCutoffs), dimension(:,:), allocatable :: gtypeCutoffMap
134  
135 +  integer, save :: cutoffPolicy = TRADITIONAL_CUTOFF_POLICY
136 +  real(kind=dp),save :: defaultRcut, defaultRsw, defaultRlist
137    
138   contains
139  
140 <
151 <  subroutine createInteractionMap(status)
140 >  subroutine createInteractionHash(status)
141      integer :: nAtypes
142      integer, intent(out) :: status
143      integer :: i
144      integer :: j
145 <    integer :: ihash
157 <    real(kind=dp) :: myRcut
145 >    integer :: iHash
146      !! Test Types
147      logical :: i_is_LJ
148      logical :: i_is_Elect
# Line 170 | Line 158 | contains
158      logical :: j_is_GB
159      logical :: j_is_EAM
160      logical :: j_is_Shape
161 <    
162 <    status = 0
163 <    
161 >    real(kind=dp) :: myRcut
162 >
163 >    status = 0  
164 >
165      if (.not. associated(atypes)) then
166 <       call handleError("atype", "atypes was not present before call of createDefaultInteractionMap!")
166 >       call handleError("atype", "atypes was not present before call of createInteractionHash!")
167         status = -1
168         return
169      endif
# Line 186 | Line 175 | contains
175         return
176      end if
177  
178 <    if (.not. allocated(InteractionMap)) then
179 <       allocate(InteractionMap(nAtypes,nAtypes))
178 >    if (.not. allocated(InteractionHash)) then
179 >       allocate(InteractionHash(nAtypes,nAtypes))
180      endif
181 +
182 +    if (.not. allocated(atypeMaxCutoff)) then
183 +       allocate(atypeMaxCutoff(nAtypes))
184 +    endif
185          
186      do i = 1, nAtypes
187         call getElementProperty(atypes, i, "is_LennardJones", i_is_LJ)
# Line 241 | Line 234 | contains
234            if (i_is_LJ .and. j_is_Shape) iHash = ior(iHash, SHAPE_LJ)
235  
236  
237 <          InteractionMap(i,j)%InteractionHash = iHash
238 <          InteractionMap(j,i)%InteractionHash = iHash
237 >          InteractionHash(i,j) = iHash
238 >          InteractionHash(j,i) = iHash
239  
240         end do
241  
242      end do
243  
244 <    haveInteractionMap = .true.
245 <  end subroutine createInteractionMap
244 >    haveInteractionHash = .true.
245 >  end subroutine createInteractionHash
246  
247 < ! Query each potential and return the cutoff for that potential. We build the neighbor list based on the largest cutoff value for that atype. Each potential can decide whether to calculate the force for that atype based upon it's own cutoff.
255 <  subroutine createRcuts(defaultRList,stat)
256 <    real(kind=dp), intent(in), optional :: defaultRList
257 <    integer :: iMap
258 <    integer :: map_i,map_j
259 <    real(kind=dp) :: thisRCut = 0.0_dp
260 <    real(kind=dp) :: actualCutoff = 0.0_dp
261 <    integer, intent(out) :: stat
262 <    integer :: nAtypes
263 <    integer :: myStatus
247 >  subroutine createGtypeCutoffMap(stat)
248  
249 <    stat = 0
250 <    if (.not. haveInteractionMap) then
249 >    integer, intent(out), optional :: stat
250 >    logical :: i_is_LJ
251 >    logical :: i_is_Elect
252 >    logical :: i_is_Sticky
253 >    logical :: i_is_StickyP
254 >    logical :: i_is_GB
255 >    logical :: i_is_EAM
256 >    logical :: i_is_Shape
257 >    logical :: GtypeFound
258  
259 <       call createInteractionMap(myStatus)
259 >    integer :: myStatus, nAtypes,  i, j, istart, iend, jstart, jend
260 >    integer :: n_in_i, me_i, ia, g, atom1, nGroupTypes
261 >    integer :: nGroupsInRow
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, *) 'createInteractionMap failed in doForces!'
269 >          write(default_error, *) 'createInteractionHash failed in doForces!'
270            stat = -1
271            return
272         endif
273      endif
274 <
275 <
274 > #ifdef IS_MPI
275 >    nGroupsInRow = getNgroupsInRow(plan_group_row)
276 > #endif
277      nAtypes = getSize(atypes)
278 <    !! If we pass a default rcut, set all atypes to that cutoff distance
279 <    if(present(defaultRList)) then
280 <       InteractionMap(:,:)%rList = defaultRList
281 <       InteractionMap(:,:)%rListSq = defaultRList*defaultRList
282 <       haveRlist = .true.
283 <       return
284 <    end if
285 <
286 <    do map_i = 1,nAtypes
287 <       do map_j = map_i,nAtypes
288 <          iMap = InteractionMap(map_i, map_j)%InteractionHash
278 > ! Set all of the initial cutoffs to zero.
279 >    atypeMaxCutoff = 0.0_dp
280 >    do i = 1, nAtypes
281 >       if (SimHasAtype(i)) then    
282 >          call getElementProperty(atypes, i, "is_LennardJones", i_is_LJ)
283 >          call getElementProperty(atypes, i, "is_Electrostatic", i_is_Elect)
284 >          call getElementProperty(atypes, i, "is_Sticky", i_is_Sticky)
285 >          call getElementProperty(atypes, i, "is_StickyPower", i_is_StickyP)
286 >          call getElementProperty(atypes, i, "is_GayBerne", i_is_GB)
287 >          call getElementProperty(atypes, i, "is_EAM", i_is_EAM)
288 >          call getElementProperty(atypes, i, "is_Shape", i_is_Shape)
289            
290 <          if ( iand(iMap, LJ_PAIR).ne.0 ) then
291 <             ! thisRCut = getLJCutOff(map_i,map_j)
292 <             if (thisRcut > actualCutoff) actualCutoff = thisRcut
290 >
291 >          if (i_is_LJ) then
292 >             thisRcut = getSigma(i) * 2.5_dp
293 >             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
294            endif
295 <          
296 <          if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
297 <             ! thisRCut = getElectrostaticCutOff(map_i,map_j)
298 <             if (thisRcut > actualCutoff) actualCutoff = thisRcut
295 >          if (i_is_Elect) then
296 >             thisRcut = defaultRcut
297 >             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
298            endif
299 +          if (i_is_Sticky) then
300 +             thisRcut = getStickyCut(i)
301 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
302 +          endif
303 +          if (i_is_StickyP) then
304 +             thisRcut = getStickyPowerCut(i)
305 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
306 +          endif
307 +          if (i_is_GB) then
308 +             thisRcut = getGayBerneCut(i)
309 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
310 +          endif
311 +          if (i_is_EAM) then
312 +             thisRcut = getEAMCut(i)
313 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
314 +          endif
315 +          if (i_is_Shape) then
316 +             thisRcut = getShapeCut(i)
317 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
318 +          endif
319            
320 <          if ( iand(iMap, STICKY_PAIR).ne.0 ) then
321 <             ! thisRCut = getStickyCutOff(map_i,map_j)
322 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
323 <           endif
324 <          
325 <           if ( iand(iMap, STICKYPOWER_PAIR).ne.0 ) then
326 <              ! thisRCut = getStickyPowerCutOff(map_i,map_j)
327 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
328 <           endif
329 <          
330 <           if ( iand(iMap, GAYBERNE_PAIR).ne.0 ) then
331 <              ! thisRCut = getGayberneCutOff(map_i,map_j)
332 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
333 <           endif
334 <          
335 <           if ( iand(iMap, GAYBERNE_LJ).ne.0 ) then
336 < !              thisRCut = getGaybrneLJCutOff(map_i,map_j)
337 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
338 <           endif
339 <          
340 <           if ( iand(iMap, EAM_PAIR).ne.0 ) then      
341 < !              thisRCut = getEAMCutOff(map_i,map_j)
342 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
343 <           endif
344 <          
345 <           if ( iand(iMap, SHAPE_PAIR).ne.0 ) then      
346 < !              thisRCut = getShapeCutOff(map_i,map_j)
347 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
348 <           endif
349 <          
350 <           if ( iand(iMap, SHAPE_LJ).ne.0 ) then      
351 < !              thisRCut = getShapeLJCutOff(map_i,map_j)
352 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
353 <           endif
354 <           InteractionMap(map_i, map_j)%rList = actualCutoff
355 <           InteractionMap(map_i, map_j)%rListSq = actualCutoff * actualCutoff
356 <        end do
357 <     end do
358 <     haveRlist = .true.
359 <  end subroutine createRcuts
360 <
361 <
362 < !!! THIS GOES AWAY FOR SIZE DEPENDENT CUTOFF
344 < !!$  subroutine setRlistDF( this_rlist )
345 < !!$
346 < !!$   real(kind=dp) :: this_rlist
347 < !!$
348 < !!$    rlist = this_rlist
349 < !!$    rlistsq = rlist * rlist
350 < !!$
351 < !!$    haveRlist = .true.
352 < !!$
353 < !!$  end subroutine setRlistDF
320 >          if (atypeMaxCutoff(i).gt.biggestAtypeCutoff) then
321 >             biggestAtypeCutoff = atypeMaxCutoff(i)
322 >          endif
323 >       endif
324 >    enddo
325 >  
326 >    nGroupTypes = 0
327 >    
328 >    istart = 1
329 > #ifdef IS_MPI
330 >    iend = nGroupsInRow
331 > #else
332 >    iend = nGroups
333 > #endif
334 >    
335 >    !! allocate the groupToGtype and gtypeMaxCutoff here.
336 >    if(.not.allocated(groupToGtype)) then
337 >       allocate(groupToGtype(iend))
338 >       allocate(groupMaxCutoff(iend))
339 >       allocate(gtypeMaxCutoff(iend))
340 >       groupMaxCutoff = 0.0_dp
341 >       gtypeMaxCutoff = 0.0_dp
342 >    endif
343 >    !! first we do a single loop over the cutoff groups to find the
344 >    !! largest cutoff for any atypes present in this group.  We also
345 >    !! create gtypes at this point.
346 >    
347 >    tol = 1.0d-6
348 >    
349 >    do i = istart, iend      
350 >       n_in_i = groupStartRow(i+1) - groupStartRow(i)
351 >       groupMaxCutoff(i) = 0.0_dp
352 >       do ia = groupStartRow(i), groupStartRow(i+1)-1
353 >          atom1 = groupListRow(ia)
354 > #ifdef IS_MPI
355 >          me_i = atid_row(atom1)
356 > #else
357 >          me_i = atid(atom1)
358 > #endif          
359 >          if (atypeMaxCutoff(me_i).gt.groupMaxCutoff(i)) then
360 >             groupMaxCutoff(i)=atypeMaxCutoff(me_i)
361 >          endif          
362 >       enddo
363  
364 +       if (nGroupTypes.eq.0) then
365 +          nGroupTypes = nGroupTypes + 1
366 +          gtypeMaxCutoff(nGroupTypes) = groupMaxCutoff(i)
367 +          groupToGtype(i) = nGroupTypes
368 +       else
369 +          GtypeFound = .false.
370 +          do g = 1, nGroupTypes
371 +             if ( abs(groupMaxCutoff(i) - gtypeMaxCutoff(g)).lt.tol) then
372 +                groupToGtype(i) = g
373 +                GtypeFound = .true.
374 +             endif
375 +          enddo
376 +          if (.not.GtypeFound) then            
377 +             nGroupTypes = nGroupTypes + 1
378 +             gtypeMaxCutoff(nGroupTypes) = groupMaxCutoff(i)
379 +             groupToGtype(i) = nGroupTypes
380 +          endif
381 +       endif
382 +    enddo    
383  
384 +    !! allocate the gtypeCutoffMap here.
385 +    allocate(gtypeCutoffMap(nGroupTypes,nGroupTypes))
386 +    !! then we do a double loop over all the group TYPES to find the cutoff
387 +    !! map between groups of two types
388 +    
389 +    do i = 1, nGroupTypes
390 +       do j = 1, nGroupTypes
391 +      
392 +          select case(cutoffPolicy)
393 +          case(TRADITIONAL_CUTOFF_POLICY)
394 +             thisRcut = maxval(gtypeMaxCutoff)
395 +          case(MIX_CUTOFF_POLICY)
396 +             thisRcut = 0.5_dp * (gtypeMaxCutoff(i) + gtypeMaxCutoff(j))
397 +          case(MAX_CUTOFF_POLICY)
398 +             thisRcut = max(gtypeMaxCutoff(i), gtypeMaxCutoff(j))
399 +          case default
400 +             call handleError("createGtypeCutoffMap", "Unknown Cutoff Policy")
401 +             return
402 +          end select
403 +          gtypeCutoffMap(i,j)%rcut = thisRcut
404 +          gtypeCutoffMap(i,j)%rcutsq = thisRcut*thisRcut
405 +          skin = defaultRlist - defaultRcut
406 +          gtypeCutoffMap(i,j)%rlistsq = (thisRcut + skin)**2
407 +
408 +       enddo
409 +    enddo
410 +    
411 +    haveGtypeCutoffMap = .true.
412 +   end subroutine createGtypeCutoffMap
413 +
414 +   subroutine setDefaultCutoffs(defRcut, defRsw, defRlist, cutPolicy)
415 +     real(kind=dp),intent(in) :: defRcut, defRsw, defRlist
416 +     integer, intent(in) :: cutPolicy
417 +
418 +     defaultRcut = defRcut
419 +     defaultRsw = defRsw
420 +     defaultRlist = defRlist
421 +     cutoffPolicy = cutPolicy
422 +   end subroutine setDefaultCutoffs
423 +
424 +   subroutine setCutoffPolicy(cutPolicy)
425 +
426 +     integer, intent(in) :: cutPolicy
427 +     cutoffPolicy = cutPolicy
428 +     call createGtypeCutoffMap()
429 +   end subroutine setCutoffPolicy
430 +    
431 +    
432    subroutine setSimVariables()
433      SIM_uses_DirectionalAtoms = SimUsesDirectionalAtoms()
358    SIM_uses_LennardJones = SimUsesLennardJones()
359    SIM_uses_Electrostatics = SimUsesElectrostatics()
360    SIM_uses_Charges = SimUsesCharges()
361    SIM_uses_Dipoles = SimUsesDipoles()
362    SIM_uses_Sticky = SimUsesSticky()
363    SIM_uses_StickyPower = SimUsesStickyPower()
364    SIM_uses_GayBerne = SimUsesGayBerne()
434      SIM_uses_EAM = SimUsesEAM()
366    SIM_uses_Shapes = SimUsesShapes()
367    SIM_uses_FLARB = SimUsesFLARB()
368    SIM_uses_RF = SimUsesRF()
435      SIM_requires_postpair_calc = SimRequiresPostpairCalc()
436      SIM_requires_prepair_calc = SimRequiresPrepairCalc()
437      SIM_uses_PBC = SimUsesPBC()
# Line 382 | Line 448 | contains
448  
449      error = 0
450  
451 <    if (.not. haveInteractionMap) then
451 >    if (.not. haveInteractionHash) then      
452 >       myStatus = 0      
453 >       call createInteractionHash(myStatus)      
454 >       if (myStatus .ne. 0) then
455 >          write(default_error, *) 'createInteractionHash failed in doForces!'
456 >          error = -1
457 >          return
458 >       endif
459 >    endif
460  
461 <       myStatus = 0
462 <
463 <       call createInteractionMap(myStatus)
390 <
461 >    if (.not. haveGtypeCutoffMap) then        
462 >       myStatus = 0      
463 >       call createGtypeCutoffMap(myStatus)      
464         if (myStatus .ne. 0) then
465 <          write(default_error, *) 'createInteractionMap failed in doForces!'
465 >          write(default_error, *) 'createGtypeCutoffMap failed in doForces!'
466            error = -1
467            return
468         endif
# Line 399 | Line 472 | contains
472         call setSimVariables()
473      endif
474  
475 <    if (.not. haveRlist) then
476 <       write(default_error, *) 'rList has not been set in doForces!'
477 <       error = -1
478 <       return
479 <    endif
475 >  !  if (.not. haveRlist) then
476 >  !     write(default_error, *) 'rList has not been set in doForces!'
477 >  !     error = -1
478 >  !     return
479 >  !  endif
480  
481      if (.not. haveNeighborList) then
482         write(default_error, *) 'neighbor list has not been initialized in doForces!'
# Line 428 | Line 501 | contains
501    end subroutine doReadyCheck
502  
503  
504 <  subroutine init_FF(use_RF_c, thisStat)
504 >  subroutine init_FF(thisESM, thisStat)
505  
506 <    logical, intent(in) :: use_RF_c
507 <
506 >    integer, intent(in) :: thisESM
507 >    real(kind=dp), intent(in) :: dampingAlpha
508      integer, intent(out) :: thisStat  
509      integer :: my_status, nMatches
510      integer, pointer :: MatchList(:) => null()
# Line 440 | Line 513 | contains
513      !! assume things are copacetic, unless they aren't
514      thisStat = 0
515  
516 <    !! Fortran's version of a cast:
444 <    FF_uses_RF = use_RF_c
516 >    electrostaticSummationMethod = thisESM
517  
518      !! init_FF is called *after* all of the atom types have been
519      !! defined in atype_module using the new_atype subroutine.
# Line 450 | Line 522 | contains
522      !! interactions are used by the force field.    
523  
524      FF_uses_DirectionalAtoms = .false.
453    FF_uses_LennardJones = .false.
454    FF_uses_Electrostatics = .false.
455    FF_uses_Charges = .false.    
525      FF_uses_Dipoles = .false.
457    FF_uses_Sticky = .false.
458    FF_uses_StickyPower = .false.
526      FF_uses_GayBerne = .false.
527      FF_uses_EAM = .false.
461    FF_uses_Shapes = .false.
462    FF_uses_FLARB = .false.
528  
529      call getMatchingElementList(atypes, "is_Directional", .true., &
530           nMatches, MatchList)
531      if (nMatches .gt. 0) FF_uses_DirectionalAtoms = .true.
467
468    call getMatchingElementList(atypes, "is_LennardJones", .true., &
469         nMatches, MatchList)
470    if (nMatches .gt. 0) FF_uses_LennardJones = .true.
471
472    call getMatchingElementList(atypes, "is_Electrostatic", .true., &
473         nMatches, MatchList)
474    if (nMatches .gt. 0) then
475       FF_uses_Electrostatics = .true.
476    endif
532  
478    call getMatchingElementList(atypes, "is_Charge", .true., &
479         nMatches, MatchList)
480    if (nMatches .gt. 0) then
481       FF_uses_Charges = .true.  
482       FF_uses_Electrostatics = .true.
483    endif
484
533      call getMatchingElementList(atypes, "is_Dipole", .true., &
534           nMatches, MatchList)
535 <    if (nMatches .gt. 0) then
488 <       FF_uses_Dipoles = .true.
489 <       FF_uses_Electrostatics = .true.
490 <       FF_uses_DirectionalAtoms = .true.
491 <    endif
492 <
493 <    call getMatchingElementList(atypes, "is_Quadrupole", .true., &
494 <         nMatches, MatchList)
495 <    if (nMatches .gt. 0) then
496 <       FF_uses_Quadrupoles = .true.
497 <       FF_uses_Electrostatics = .true.
498 <       FF_uses_DirectionalAtoms = .true.
499 <    endif
500 <
501 <    call getMatchingElementList(atypes, "is_Sticky", .true., nMatches, &
502 <         MatchList)
503 <    if (nMatches .gt. 0) then
504 <       FF_uses_Sticky = .true.
505 <       FF_uses_DirectionalAtoms = .true.
506 <    endif
507 <
508 <    call getMatchingElementList(atypes, "is_StickyPower", .true., nMatches, &
509 <         MatchList)
510 <    if (nMatches .gt. 0) then
511 <       FF_uses_StickyPower = .true.
512 <       FF_uses_DirectionalAtoms = .true.
513 <    endif
535 >    if (nMatches .gt. 0) FF_uses_Dipoles = .true.
536      
537      call getMatchingElementList(atypes, "is_GayBerne", .true., &
538           nMatches, MatchList)
539 <    if (nMatches .gt. 0) then
518 <       FF_uses_GayBerne = .true.
519 <       FF_uses_DirectionalAtoms = .true.
520 <    endif
539 >    if (nMatches .gt. 0) FF_uses_GayBerne = .true.
540  
541      call getMatchingElementList(atypes, "is_EAM", .true., nMatches, MatchList)
542      if (nMatches .gt. 0) FF_uses_EAM = .true.
543  
525    call getMatchingElementList(atypes, "is_Shape", .true., &
526         nMatches, MatchList)
527    if (nMatches .gt. 0) then
528       FF_uses_Shapes = .true.
529       FF_uses_DirectionalAtoms = .true.
530    endif
544  
532    call getMatchingElementList(atypes, "is_FLARB", .true., &
533         nMatches, MatchList)
534    if (nMatches .gt. 0) FF_uses_FLARB = .true.
535
536    !! Assume sanity (for the sake of argument)
545      haveSaneForceField = .true.
546  
547 <    !! check to make sure the FF_uses_RF setting makes sense
547 >    !! check to make sure the reaction field setting makes sense
548  
549 <    if (FF_uses_dipoles) then
550 <       if (FF_uses_RF) then
549 >    if (FF_uses_Dipoles) then
550 >       if (electrostaticSummationMethod == 3) then
551            dielect = getDielect()
552            call initialize_rf(dielect)
553         endif
554      else
555 <       if (FF_uses_RF) then          
555 >       if (electrostaticSummationMethod == 3) then
556            write(default_error,*) 'Using Reaction Field with no dipoles?  Huh?'
557            thisStat = -1
558            haveSaneForceField = .false.
559            return
560         endif
561      endif
554
555    !sticky module does not contain check_sticky_FF anymore
556    !if (FF_uses_sticky) then
557    !   call check_sticky_FF(my_status)
558    !   if (my_status /= 0) then
559    !      thisStat = -1
560    !      haveSaneForceField = .false.
561    !      return
562    !   end if
563    !endif
562  
563      if (FF_uses_EAM) then
564         call init_EAM_FF(my_status)
# Line 581 | Line 579 | contains
579         endif
580      endif
581  
584    if (FF_uses_GayBerne .and. FF_uses_LennardJones) then
585    endif
586
582      if (.not. haveNeighborList) then
583         !! Create neighbor lists
584         call expandNeighborList(nLocal, my_status)
# Line 647 | Line 642 | contains
642      integer :: localError
643      integer :: propPack_i, propPack_j
644      integer :: loopStart, loopEnd, loop
645 <    integer :: iMap
645 >    integer :: iHash
646      real(kind=dp) :: listSkin = 1.0  
647  
648      !! initialize local variables  
# Line 738 | Line 733 | contains
733         iend = nGroups - 1
734   #endif
735         outer: do i = istart, iend
741
742 #ifdef IS_MPI
743             me_i = atid_row(i)
744 #else
745             me_i = atid(i)
746 #endif
736  
737            if (update_nlist) point(i) = nlist + 1
738  
# Line 781 | Line 770 | contains
770                    q_group(:,j), d_grp, rgrpsq)
771   #endif
772  
773 <             if (rgrpsq < InteractionMap(me_i,me_j)%rListsq) then
773 >             if (rgrpsq < gtypeCutoffMap(groupToGtype(i),groupToGtype(j))%rListsq) then
774                  if (update_nlist) then
775                     nlist = nlist + 1
776  
# Line 981 | Line 970 | contains
970  
971      if (FF_RequiresPostpairCalc() .and. SIM_requires_postpair_calc) then
972  
973 <       if (FF_uses_RF .and. SIM_uses_RF) then
973 >       if (electrostaticSummationMethod == 3) then
974  
975   #ifdef IS_MPI
976            call scatter(rf_Row,rf,plan_atom_row_3d)
# Line 999 | Line 988 | contains
988   #else
989               me_i = atid(i)
990   #endif
991 <             iMap = InteractionMap(me_i, me_j)%InteractionHash
991 >             iHash = InteractionHash(me_i,me_j)
992              
993 <             if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
993 >             if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then
994  
995                  mu_i = getDipoleMoment(me_i)
996  
# Line 1065 | Line 1054 | contains
1054      real ( kind = dp ), intent(inout) :: rijsq
1055      real ( kind = dp )                :: r
1056      real ( kind = dp ), intent(inout) :: d(3)
1068    real ( kind = dp ) :: ebalance
1057      integer :: me_i, me_j
1058  
1059 <    integer :: iMap
1059 >    integer :: iHash
1060  
1061      r = sqrt(rijsq)
1062      vpair = 0.0d0
# Line 1082 | Line 1070 | contains
1070      me_j = atid(j)
1071   #endif
1072  
1073 <    iMap = InteractionMap(me_i, me_j)%InteractionHash
1073 >    iHash = InteractionHash(me_i, me_j)
1074  
1075 <    if ( iand(iMap, LJ_PAIR).ne.0 ) then
1075 >    if ( iand(iHash, LJ_PAIR).ne.0 ) then
1076         call do_lj_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot)
1077      endif
1078  
1079 <    if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
1079 >    if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then
1080         call doElectrostaticPair(i, j, d, r, rijsq, sw, vpair, fpair, &
1081              pot, eFrame, f, t, do_pot)
1082  
1083 <       if (FF_uses_RF .and. SIM_uses_RF) then
1083 >       if (electrostaticSummationMethod == 3) then
1084  
1085            ! CHECK ME (RF needs to know about all electrostatic types)
1086            call accumulate_rf(i, j, r, eFrame, sw)
# Line 1101 | Line 1089 | contains
1089  
1090      endif
1091  
1092 <    if ( iand(iMap, STICKY_PAIR).ne.0 ) then
1092 >    if ( iand(iHash, STICKY_PAIR).ne.0 ) then
1093         call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1094              pot, A, f, t, do_pot)
1095      endif
1096  
1097 <    if ( iand(iMap, STICKYPOWER_PAIR).ne.0 ) then
1097 >    if ( iand(iHash, STICKYPOWER_PAIR).ne.0 ) then
1098         call do_sticky_power_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1099              pot, A, f, t, do_pot)
1100      endif
1101  
1102 <    if ( iand(iMap, GAYBERNE_PAIR).ne.0 ) then
1102 >    if ( iand(iHash, GAYBERNE_PAIR).ne.0 ) then
1103         call do_gb_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1104              pot, A, f, t, do_pot)
1105      endif
1106      
1107 <    if ( iand(iMap, GAYBERNE_LJ).ne.0 ) then
1107 >    if ( iand(iHash, GAYBERNE_LJ).ne.0 ) then
1108   !      call do_gblj_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1109   !           pot, A, f, t, do_pot)
1110      endif
1111  
1112 <    if ( iand(iMap, EAM_PAIR).ne.0 ) then      
1112 >    if ( iand(iHash, EAM_PAIR).ne.0 ) then      
1113         call do_eam_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, &
1114              do_pot)
1115      endif
1116  
1117 <    if ( iand(iMap, SHAPE_PAIR).ne.0 ) then      
1117 >    if ( iand(iHash, SHAPE_PAIR).ne.0 ) then      
1118         call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1119              pot, A, f, t, do_pot)
1120      endif
1121  
1122 <    if ( iand(iMap, SHAPE_LJ).ne.0 ) then      
1122 >    if ( iand(iHash, SHAPE_LJ).ne.0 ) then      
1123         call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1124              pot, A, f, t, do_pot)
1125      endif
# Line 1153 | Line 1141 | contains
1141      real ( kind = dp )                :: r, rc
1142      real ( kind = dp ), intent(inout) :: d(3), dc(3)
1143  
1144 <    integer :: me_i, me_j, iMap
1144 >    integer :: me_i, me_j, iHash
1145  
1146 +    r = sqrt(rijsq)
1147 +
1148   #ifdef IS_MPI  
1149      me_i = atid_row(i)
1150      me_j = atid_col(j)  
# Line 1163 | Line 1153 | contains
1153      me_j = atid(j)  
1154   #endif
1155  
1156 <    iMap = InteractionMap(me_i, me_j)%InteractionHash
1156 >    iHash = InteractionHash(me_i, me_j)
1157  
1158 <    if ( iand(iMap, EAM_PAIR).ne.0 ) then      
1158 >    if ( iand(iHash, EAM_PAIR).ne.0 ) then      
1159              call calc_EAM_prepair_rho(i, j, d, r, rijsq )
1160      endif
1161      
# Line 1362 | Line 1352 | contains
1352  
1353    function FF_UsesDirectionalAtoms() result(doesit)
1354      logical :: doesit
1355 <    doesit = FF_uses_DirectionalAtoms .or. FF_uses_Dipoles .or. &
1366 <         FF_uses_Quadrupoles .or. FF_uses_Sticky .or. &
1367 <         FF_uses_StickyPower .or. FF_uses_GayBerne .or. FF_uses_Shapes
1355 >    doesit = FF_uses_DirectionalAtoms
1356    end function FF_UsesDirectionalAtoms
1357  
1358    function FF_RequiresPrepairCalc() result(doesit)
# Line 1374 | Line 1362 | contains
1362  
1363    function FF_RequiresPostpairCalc() result(doesit)
1364      logical :: doesit
1365 <    doesit = FF_uses_RF
1365 >    if (electrostaticSummationMethod == 3) doesit = .true.
1366    end function FF_RequiresPostpairCalc
1367  
1368   #ifdef PROFILE

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines