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 2282 by chuckv, Tue Sep 6 17:32:42 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.36 2005-09-06 17:32:42 chuckv Exp $, $Date: 2005-09-06 17:32:42 $, $Name: not supported by cvs2svn $, $Revision: 1.36 $
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
157 <    real(kind=dp) :: myRcut
147 >    integer :: iHash
148      !! Test Types
149      logical :: i_is_LJ
150      logical :: i_is_Elect
# 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
245  
246 <    haveInteractionMap = .true.
247 <  end subroutine createInteractionMap
246 >    haveInteractionHash = .true.
247 >  end subroutine createInteractionHash
248  
249 < ! 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
249 >  subroutine createGtypeCutoffMap(stat)
250  
251 <    stat = 0
252 <    if (.not. haveInteractionMap) then
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 <       call createInteractionMap(myStatus)
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, *) 'createInteractionMap failed in doForces!'
269 >          write(default_error, *) 'createInteractionHash failed in doForces!'
270            stat = -1
271            return
272         endif
273      endif
274  
277
275      nAtypes = getSize(atypes)
276 <    !! If we pass a default rcut, set all atypes to that cutoff distance
277 <    if(present(defaultRList)) then
278 <       InteractionMap(:,:)%rList = defaultRList
279 <       InteractionMap(:,:)%rListSq = defaultRList*defaultRList
280 <       haveRlist = .true.
281 <       return
282 <    end if
283 <
284 <    do map_i = 1,nAtypes
285 <       do map_j = map_i,nAtypes
289 <          iMap = InteractionMap(map_i, map_j)%InteractionHash
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, LJ_PAIR).ne.0 ) then
288 <             ! thisRCut = getLJCutOff(map_i,map_j)
289 <             if (thisRcut > actualCutoff) actualCutoff = thisRcut
287 >          atypeMaxCutoff(i) = 0.0_dp
288 >          if (i_is_LJ) then
289 >             thisRcut = getSigma(i) * 2.5_dp
290 >             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
291            endif
292 <          
293 <          if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
294 <             ! thisRCut = getElectrostaticCutOff(map_i,map_j)
298 <             if (thisRcut > actualCutoff) actualCutoff = thisRcut
292 >          if (i_is_Elect) then
293 >             thisRcut = defaultRcut
294 >             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
295            endif
296 +          if (i_is_Sticky) then
297 +             thisRcut = getStickyCut(i)
298 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
299 +          endif
300 +          if (i_is_StickyP) then
301 +             thisRcut = getStickyPowerCut(i)
302 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
303 +          endif
304 +          if (i_is_GB) then
305 +             thisRcut = getGayBerneCut(i)
306 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
307 +          endif
308 +          if (i_is_EAM) then
309 +             thisRcut = getEAMCut(i)
310 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
311 +          endif
312 +          if (i_is_Shape) then
313 +             thisRcut = getShapeCut(i)
314 +             if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
315 +          endif
316            
317 <          if ( iand(iMap, STICKY_PAIR).ne.0 ) then
318 <             ! thisRCut = getStickyCutOff(map_i,map_j)
319 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
320 <           endif
321 <          
322 <           if ( iand(iMap, STICKYPOWER_PAIR).ne.0 ) then
323 <              ! thisRCut = getStickyPowerCutOff(map_i,map_j)
324 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
325 <           endif
326 <          
327 <           if ( iand(iMap, GAYBERNE_PAIR).ne.0 ) then
328 <              ! thisRCut = getGayberneCutOff(map_i,map_j)
329 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
330 <           endif
331 <          
332 <           if ( iand(iMap, GAYBERNE_LJ).ne.0 ) then
333 < !              thisRCut = getGaybrneLJCutOff(map_i,map_j)
334 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
335 <           endif
336 <          
337 <           if ( iand(iMap, EAM_PAIR).ne.0 ) then      
338 < !              thisRCut = getEAMCutOff(map_i,map_j)
339 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
340 <           endif
341 <          
342 <           if ( iand(iMap, SHAPE_PAIR).ne.0 ) then      
343 < !              thisRCut = getShapeCutOff(map_i,map_j)
344 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
345 <           endif
346 <          
347 <           if ( iand(iMap, SHAPE_LJ).ne.0 ) then      
348 < !              thisRCut = getShapeLJCutOff(map_i,map_j)
349 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
350 <           endif
351 <           InteractionMap(map_i, map_j)%rList = actualCutoff
352 <           InteractionMap(map_i, map_j)%rListSq = actualCutoff * actualCutoff
353 <        end do
354 <     end do
355 <     haveRlist = .true.
356 <  end subroutine createRcuts
357 <
358 <
359 < !!! THIS GOES AWAY FOR SIZE DEPENDENT CUTOFF
360 < !!$  subroutine setRlistDF( this_rlist )
361 < !!$
362 < !!$   real(kind=dp) :: this_rlist
363 < !!$
364 < !!$    rlist = this_rlist
365 < !!$    rlistsq = rlist * rlist
366 < !!$
367 < !!$    haveRlist = .true.
368 < !!$
369 < !!$  end subroutine setRlistDF
317 >          if (atypeMaxCutoff(i).gt.biggestAtypeCutoff) then
318 >             biggestAtypeCutoff = atypeMaxCutoff(i)
319 >          endif
320 >       endif
321 >    enddo
322 >  
323 >    nGroupTypes = 0
324 >    
325 >    istart = 1
326 > #ifdef IS_MPI
327 >    iend = nGroupsInRow
328 > #else
329 >    iend = nGroups
330 > #endif
331 >    
332 >    !! allocate the groupToGtype and gtypeMaxCutoff here.
333 >    if(.not.allocated(groupToGtype)) then
334 >       allocate(groupToGtype(iend))
335 >       allocate(groupMaxCutoff(iend))
336 >       allocate(gtypeMaxCutoff(iend))
337 >    endif
338 >    !! first we do a single loop over the cutoff groups to find the
339 >    !! largest cutoff for any atypes present in this group.  We also
340 >    !! create gtypes at this point.
341 >    
342 >    tol = 1.0d-6
343 >    
344 >    do i = istart, iend      
345 >       n_in_i = groupStartRow(i+1) - groupStartRow(i)
346 >       groupMaxCutoff(i) = 0.0_dp
347 >       do ia = groupStartRow(i), groupStartRow(i+1)-1
348 >          atom1 = groupListRow(ia)
349 > #ifdef IS_MPI
350 >          me_i = atid_row(atom1)
351 > #else
352 >          me_i = atid(atom1)
353 > #endif          
354 >          if (atypeMaxCutoff(me_i).gt.groupMaxCutoff(i)) then
355 >             groupMaxCutoff(i)=atypeMaxCutoff(me_i)
356 >          endif
357 >       enddo
358 >       if (nGroupTypes.eq.0) then
359 >          nGroupTypes = nGroupTypes + 1
360 >          gtypeMaxCutoff(nGroupTypes) = groupMaxCutoff(i)
361 >          groupToGtype(i) = nGroupTypes
362 >       else
363 >          do g = 1, nGroupTypes
364 >             if ( abs(groupMaxCutoff(i) - gtypeMaxCutoff(g)).gt.tol) then
365 >                nGroupTypes = nGroupTypes + 1
366 >                gtypeMaxCutoff(nGroupTypes) = groupMaxCutoff(i)
367 >                groupToGtype(i) = nGroupTypes
368 >             else
369 >                groupToGtype(i) = g
370 >             endif
371 >          enddo
372 >       endif
373 >    enddo
374 >    
375 >    !! allocate the gtypeCutoffMap here.
376 >    allocate(gtypeCutoffMap(nGroupTypes,nGroupTypes))
377 >    !! then we do a double loop over all the group TYPES to find the cutoff
378 >    !! map between groups of two types
379 >    
380 >    do i = 1, nGroupTypes
381 >       do j = 1, nGroupTypes
382 >      
383 >          select case(cutoffPolicy)
384 >          case(TRADITIONAL_CUTOFF_POLICY)
385 >             thisRcut = maxval(gtypeMaxCutoff)
386 >          case(MIX_CUTOFF_POLICY)
387 >             thisRcut = 0.5_dp * (gtypeMaxCutoff(i) + gtypeMaxCutoff(j))
388 >          case(MAX_CUTOFF_POLICY)
389 >             thisRcut = max(gtypeMaxCutoff(i), gtypeMaxCutoff(j))
390 >          case default
391 >             call handleError("createGtypeCutoffMap", "Unknown Cutoff Policy")
392 >             return
393 >          end select
394 >          gtypeCutoffMap(i,j)%rcut = thisRcut
395 >          gtypeCutoffMap(i,j)%rcutsq = thisRcut*thisRcut
396 >          skin = defaultRlist - defaultRcut
397 >          gtypeCutoffMap(i,j)%rlistsq = (thisRcut + skin)**2
398 >       enddo
399 >    enddo
400 >    
401 >    haveGtypeCutoffMap = .true.
402 >    
403 >  end subroutine createGtypeCutoffMap
404 >  
405 >  subroutine setDefaultCutoffs(defRcut, defRsw, defRlist, cutPolicy)
406 >    real(kind=dp),intent(in) :: defRcut, defRsw, defRlist
407 >    integer, intent(in) :: cutPolicy
408 >    
409 >    defaultRcut = defRcut
410 >    defaultRsw = defRsw
411 >    defaultRlist = defRlist
412 >    cutoffPolicy = cutPolicy
413 >  end subroutine setDefaultCutoffs
414 >  
415 >  subroutine setCutoffPolicy(cutPolicy)
416  
417 +     integer, intent(in) :: cutPolicy
418 +     cutoffPolicy = cutPolicy
419 +     call createGtypeCutoffMap()
420  
421 +   end subroutine setCutoffPolicy
422 +    
423 +    
424    subroutine setSimVariables()
425      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()
426      SIM_uses_EAM = SimUsesEAM()
366    SIM_uses_Shapes = SimUsesShapes()
367    SIM_uses_FLARB = SimUsesFLARB()
427      SIM_uses_RF = SimUsesRF()
428      SIM_requires_postpair_calc = SimRequiresPostpairCalc()
429      SIM_requires_prepair_calc = SimRequiresPrepairCalc()
# Line 382 | Line 441 | contains
441  
442      error = 0
443  
444 <    if (.not. haveInteractionMap) then
444 >    if (.not. haveInteractionHash) then      
445 >       myStatus = 0      
446 >       call createInteractionHash(myStatus)      
447 >       if (myStatus .ne. 0) then
448 >          write(default_error, *) 'createInteractionHash failed in doForces!'
449 >          error = -1
450 >          return
451 >       endif
452 >    endif
453  
454 <       myStatus = 0
455 <
456 <       call createInteractionMap(myStatus)
390 <
454 >    if (.not. haveGtypeCutoffMap) then        
455 >       myStatus = 0      
456 >       call createGtypeCutoffMap(myStatus)      
457         if (myStatus .ne. 0) then
458 <          write(default_error, *) 'createInteractionMap failed in doForces!'
458 >          write(default_error, *) 'createGtypeCutoffMap failed in doForces!'
459            error = -1
460            return
461         endif
# Line 399 | Line 465 | contains
465         call setSimVariables()
466      endif
467  
468 <    if (.not. haveRlist) then
469 <       write(default_error, *) 'rList has not been set in doForces!'
470 <       error = -1
471 <       return
472 <    endif
468 >  !  if (.not. haveRlist) then
469 >  !     write(default_error, *) 'rList has not been set in doForces!'
470 >  !     error = -1
471 >  !     return
472 >  !  endif
473  
474      if (.not. haveNeighborList) then
475         write(default_error, *) 'neighbor list has not been initialized in doForces!'
# Line 428 | Line 494 | contains
494    end subroutine doReadyCheck
495  
496  
497 <  subroutine init_FF(use_RF_c, thisStat)
497 >  subroutine init_FF(use_RF, use_UW, use_DW, thisStat)
498  
499 <    logical, intent(in) :: use_RF_c
500 <
499 >    logical, intent(in) :: use_RF
500 >    logical, intent(in) :: use_UW
501 >    logical, intent(in) :: use_DW
502      integer, intent(out) :: thisStat  
503      integer :: my_status, nMatches
504 +    integer :: corrMethod
505      integer, pointer :: MatchList(:) => null()
506      real(kind=dp) :: rcut, rrf, rt, dielect
507  
# Line 441 | Line 509 | contains
509      thisStat = 0
510  
511      !! Fortran's version of a cast:
512 <    FF_uses_RF = use_RF_c
512 >    FF_uses_RF = use_RF
513  
514 +    !! set the electrostatic correction method
515 +    if (use_UW) then
516 +       corrMethod = 1
517 +    elseif (use_DW) then
518 +       corrMethod = 2
519 +    else
520 +       corrMethod = 0
521 +    endif
522 +    
523      !! init_FF is called *after* all of the atom types have been
524      !! defined in atype_module using the new_atype subroutine.
525      !!
# Line 450 | Line 527 | contains
527      !! interactions are used by the force field.    
528  
529      FF_uses_DirectionalAtoms = .false.
453    FF_uses_LennardJones = .false.
454    FF_uses_Electrostatics = .false.
455    FF_uses_Charges = .false.    
530      FF_uses_Dipoles = .false.
457    FF_uses_Sticky = .false.
458    FF_uses_StickyPower = .false.
531      FF_uses_GayBerne = .false.
532      FF_uses_EAM = .false.
461    FF_uses_Shapes = .false.
462    FF_uses_FLARB = .false.
533  
534      call getMatchingElementList(atypes, "is_Directional", .true., &
535           nMatches, MatchList)
536      if (nMatches .gt. 0) FF_uses_DirectionalAtoms = .true.
537  
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
477
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
538      call getMatchingElementList(atypes, "is_Dipole", .true., &
539           nMatches, MatchList)
540 <    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
540 >    if (nMatches .gt. 0) FF_uses_Dipoles = .true.
541      
542      call getMatchingElementList(atypes, "is_GayBerne", .true., &
543           nMatches, MatchList)
544 <    if (nMatches .gt. 0) then
518 <       FF_uses_GayBerne = .true.
519 <       FF_uses_DirectionalAtoms = .true.
520 <    endif
544 >    if (nMatches .gt. 0) FF_uses_GayBerne = .true.
545  
546      call getMatchingElementList(atypes, "is_EAM", .true., nMatches, MatchList)
547      if (nMatches .gt. 0) FF_uses_EAM = .true.
548  
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
549  
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)
550      haveSaneForceField = .true.
551  
552      !! check to make sure the FF_uses_RF setting makes sense
553  
554 <    if (FF_uses_dipoles) then
554 >    if (FF_uses_Dipoles) then
555         if (FF_uses_RF) then
556            dielect = getDielect()
557            call initialize_rf(dielect)
# Line 552 | Line 565 | contains
565         endif
566      endif
567  
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
564
568      if (FF_uses_EAM) then
569         call init_EAM_FF(my_status)
570         if (my_status /= 0) then
# Line 581 | Line 584 | contains
584         endif
585      endif
586  
584    if (FF_uses_GayBerne .and. FF_uses_LennardJones) then
585    endif
586
587      if (.not. haveNeighborList) then
588         !! Create neighbor lists
589         call expandNeighborList(nLocal, my_status)
# Line 647 | Line 647 | contains
647      integer :: localError
648      integer :: propPack_i, propPack_j
649      integer :: loopStart, loopEnd, loop
650 <    integer :: iMap
650 >    integer :: iHash
651      real(kind=dp) :: listSkin = 1.0  
652  
653      !! initialize local variables  
# Line 739 | Line 739 | contains
739   #endif
740         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
747
742            if (update_nlist) point(i) = nlist + 1
743  
744            n_in_i = groupStartRow(i+1) - groupStartRow(i)
# Line 781 | Line 775 | contains
775                    q_group(:,j), d_grp, rgrpsq)
776   #endif
777  
778 <             if (rgrpsq < InteractionMap(me_i,me_j)%rListsq) then
778 >             if (rgrpsq < gtypeCutoffMap(groupToGtype(i),groupToGtype(j))%rListsq) then
779                  if (update_nlist) then
780                     nlist = nlist + 1
781  
# Line 999 | Line 993 | contains
993   #else
994               me_i = atid(i)
995   #endif
996 <             iMap = InteractionMap(me_i, me_j)%InteractionHash
996 >             iHash = InteractionHash(me_i,me_j)
997              
998 <             if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
998 >             if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then
999  
1000                  mu_i = getDipoleMoment(me_i)
1001  
# Line 1068 | Line 1062 | contains
1062      real ( kind = dp ) :: ebalance
1063      integer :: me_i, me_j
1064  
1065 <    integer :: iMap
1065 >    integer :: iHash
1066  
1067      r = sqrt(rijsq)
1068      vpair = 0.0d0
# Line 1082 | Line 1076 | contains
1076      me_j = atid(j)
1077   #endif
1078  
1079 <    iMap = InteractionMap(me_i, me_j)%InteractionHash
1079 >    iHash = InteractionHash(me_i, me_j)
1080  
1081 <    if ( iand(iMap, LJ_PAIR).ne.0 ) then
1081 >    if ( iand(iHash, LJ_PAIR).ne.0 ) then
1082         call do_lj_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot)
1083      endif
1084  
1085 <    if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
1085 >    if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then
1086         call doElectrostaticPair(i, j, d, r, rijsq, sw, vpair, fpair, &
1087 <            pot, eFrame, f, t, do_pot)
1087 >            pot, eFrame, f, t, do_pot, corrMethod)
1088  
1089         if (FF_uses_RF .and. SIM_uses_RF) then
1090  
# Line 1101 | Line 1095 | contains
1095  
1096      endif
1097  
1098 <    if ( iand(iMap, STICKY_PAIR).ne.0 ) then
1098 >    if ( iand(iHash, STICKY_PAIR).ne.0 ) then
1099         call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1100              pot, A, f, t, do_pot)
1101      endif
1102  
1103 <    if ( iand(iMap, STICKYPOWER_PAIR).ne.0 ) then
1103 >    if ( iand(iHash, STICKYPOWER_PAIR).ne.0 ) then
1104         call do_sticky_power_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1105              pot, A, f, t, do_pot)
1106      endif
1107  
1108 <    if ( iand(iMap, GAYBERNE_PAIR).ne.0 ) then
1108 >    if ( iand(iHash, GAYBERNE_PAIR).ne.0 ) then
1109         call do_gb_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1110              pot, A, f, t, do_pot)
1111      endif
1112      
1113 <    if ( iand(iMap, GAYBERNE_LJ).ne.0 ) then
1113 >    if ( iand(iHash, GAYBERNE_LJ).ne.0 ) then
1114   !      call do_gblj_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1115   !           pot, A, f, t, do_pot)
1116      endif
1117  
1118 <    if ( iand(iMap, EAM_PAIR).ne.0 ) then      
1118 >    if ( iand(iHash, EAM_PAIR).ne.0 ) then      
1119         call do_eam_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, &
1120              do_pot)
1121      endif
1122  
1123 <    if ( iand(iMap, SHAPE_PAIR).ne.0 ) then      
1123 >    if ( iand(iHash, SHAPE_PAIR).ne.0 ) then      
1124         call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1125              pot, A, f, t, do_pot)
1126      endif
1127  
1128 <    if ( iand(iMap, SHAPE_LJ).ne.0 ) then      
1128 >    if ( iand(iHash, SHAPE_LJ).ne.0 ) then      
1129         call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1130              pot, A, f, t, do_pot)
1131      endif
# Line 1153 | Line 1147 | contains
1147      real ( kind = dp )                :: r, rc
1148      real ( kind = dp ), intent(inout) :: d(3), dc(3)
1149  
1150 <    integer :: me_i, me_j, iMap
1150 >    integer :: me_i, me_j, iHash
1151  
1152   #ifdef IS_MPI  
1153      me_i = atid_row(i)
# Line 1163 | Line 1157 | contains
1157      me_j = atid(j)  
1158   #endif
1159  
1160 <    iMap = InteractionMap(me_i, me_j)%InteractionHash
1160 >    iHash = InteractionHash(me_i, me_j)
1161  
1162 <    if ( iand(iMap, EAM_PAIR).ne.0 ) then      
1162 >    if ( iand(iHash, EAM_PAIR).ne.0 ) then      
1163              call calc_EAM_prepair_rho(i, j, d, r, rijsq )
1164      endif
1165      
# Line 1362 | Line 1356 | contains
1356  
1357    function FF_UsesDirectionalAtoms() result(doesit)
1358      logical :: doesit
1359 <    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
1359 >    doesit = FF_uses_DirectionalAtoms
1360    end function FF_UsesDirectionalAtoms
1361  
1362    function FF_RequiresPrepairCalc() result(doesit)

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines