ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/doForces.F90
(Generate patch)

Comparing trunk/OOPSE-4/src/UseTheForce/doForces.F90 (file contents):
Revision 2262 by chuckv, Sun Jul 3 20:53:43 2005 UTC vs.
Revision 2317 by chrisfen, Wed Sep 21 17:20:14 2005 UTC

# Line 45 | Line 45
45  
46   !! @author Charles F. Vardeman II
47   !! @author Matthew Meineke
48 < !! @version $Id: doForces.F90,v 1.23 2005-07-03 20:53:43 chuckv Exp $, $Date: 2005-07-03 20:53:43 $, $Name: not supported by cvs2svn $, $Revision: 1.23 $
48 > !! @version $Id: doForces.F90,v 1.48 2005-09-21 17:20:10 chrisfen Exp $, $Date: 2005-09-21 17:20:10 $, $Name: not supported by cvs2svn $, $Revision: 1.48 $
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 + #include "UseTheForce/DarkSide/fElectrostaticSummationMethod.h"
79  
80 +
81    INTEGER, PARAMETER:: PREPAIR_LOOP = 1
82    INTEGER, PARAMETER:: PAIR_LOOP    = 2
83  
81  logical, save :: haveRlist = .false.
84    logical, save :: haveNeighborList = .false.
85    logical, save :: haveSIMvariables = .false.
86    logical, save :: haveSaneForceField = .false.
87 <  logical, save :: haveInteractionMap = .false.
87 >  logical, save :: haveInteractionHash = .false.
88 >  logical, save :: haveGtypeCutoffMap = .false.
89 >  logical, save :: haveDefaultCutoffs = .false.
90 >  logical, save :: haveRlist = .false.
91  
92    logical, save :: FF_uses_DirectionalAtoms
88  logical, save :: FF_uses_LennardJones
89  logical, save :: FF_uses_Electrostatics
90  logical, save :: FF_uses_Charges
93    logical, save :: FF_uses_Dipoles
92  logical, save :: FF_uses_Quadrupoles
93  logical, save :: FF_uses_Sticky
94  logical, save :: FF_uses_StickyPower
94    logical, save :: FF_uses_GayBerne
95    logical, save :: FF_uses_EAM
97  logical, save :: FF_uses_Shapes
98  logical, save :: FF_uses_FLARB
99  logical, save :: FF_uses_RF
96  
97    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
98    logical, save :: SIM_uses_EAM
111  logical, save :: SIM_uses_Shapes
112  logical, save :: SIM_uses_FLARB
113  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 :: electrostaticSummationMethod
104  
105    public :: init_FF
106 +  public :: setDefaultCutoffs
107    public :: do_force_loop
108 < !  public :: setRlistDF
109 <  !public :: addInteraction
110 <  !public :: setInteractionHash
111 <  !public :: getInteractionHash
112 <  public :: createInteractionMap
113 <  public :: createRcuts
108 >  public :: createInteractionHash
109 >  public :: createGtypeCutoffMap
110 >  public :: getStickyCut
111 >  public :: getStickyPowerCut
112 >  public :: getGayBerneCut
113 >  public :: getEAMCut
114 >  public :: getShapeCut
115  
116   #ifdef PROFILE
117    public :: getforcetime
# Line 134 | Line 119 | module doForces
119    real :: forceTimeInitial, forceTimeFinal
120    integer :: nLoops
121   #endif
137
138  type, public :: Interaction
139     integer :: InteractionHash
140     real(kind=dp) :: rList = 0.0_dp
141     real(kind=dp) :: rListSq = 0.0_dp
142  end type Interaction
122    
123 <  type(Interaction), dimension(:,:),allocatable :: InteractionMap
124 <  
123 >  !! Variables for cutoff mapping and interaction mapping
124 >  ! Bit hash to determine pair-pair interactions.
125 >  integer, dimension(:,:), allocatable :: InteractionHash
126 >  real(kind=dp), dimension(:), allocatable :: atypeMaxCutoff
127 >  real(kind=dp), dimension(:), allocatable :: groupMaxCutoff
128 >  integer, dimension(:), allocatable :: groupToGtype
129 >  real(kind=dp), dimension(:), allocatable :: gtypeMaxCutoff
130 >  type ::gtypeCutoffs
131 >     real(kind=dp) :: rcut
132 >     real(kind=dp) :: rcutsq
133 >     real(kind=dp) :: rlistsq
134 >  end type gtypeCutoffs
135 >  type(gtypeCutoffs), dimension(:,:), allocatable :: gtypeCutoffMap
136  
137 +  integer, save :: cutoffPolicy = TRADITIONAL_CUTOFF_POLICY
138 +  real(kind=dp),save :: defaultRcut, defaultRsw, defaultRlist
139    
140   contains
141  
142 <
151 <  subroutine createInteractionMap(status)
142 >  subroutine createInteractionHash(status)
143      integer :: nAtypes
144 <    integer :: status
144 >    integer, intent(out) :: status
145      integer :: i
146      integer :: j
147 <    integer :: ihash
148 <    real(kind=dp) :: myRcut
158 < ! Test Types
147 >    integer :: iHash
148 >    !! Test Types
149      logical :: i_is_LJ
150      logical :: i_is_Elect
151      logical :: i_is_Sticky
# Line 170 | Line 160 | contains
160      logical :: j_is_GB
161      logical :: j_is_EAM
162      logical :: j_is_Shape
163 <    
164 <    
163 >    real(kind=dp) :: myRcut
164 >
165 >    status = 0  
166 >
167      if (.not. associated(atypes)) then
168 <       call handleError("atype", "atypes was not present before call of createDefaultInteractionMap!")
168 >       call handleError("atype", "atypes was not present before call of createInteractionHash!")
169         status = -1
170         return
171      endif
# Line 185 | Line 177 | contains
177         return
178      end if
179  
180 <    if (.not. allocated(InteractionMap)) then
181 <       allocate(InteractionMap(nAtypes,nAtypes))
180 >    if (.not. allocated(InteractionHash)) then
181 >       allocate(InteractionHash(nAtypes,nAtypes))
182      endif
183 +
184 +    if (.not. allocated(atypeMaxCutoff)) then
185 +       allocate(atypeMaxCutoff(nAtypes))
186 +    endif
187          
188      do i = 1, nAtypes
189         call getElementProperty(atypes, i, "is_LennardJones", i_is_LJ)
# Line 240 | Line 236 | contains
236            if (i_is_LJ .and. j_is_Shape) iHash = ior(iHash, SHAPE_LJ)
237  
238  
239 <          InteractionMap(i,j)%InteractionHash = iHash
240 <          InteractionMap(j,i)%InteractionHash = iHash
239 >          InteractionHash(i,j) = iHash
240 >          InteractionHash(j,i) = iHash
241  
242         end do
243  
244      end do
249  end subroutine createInteractionMap
245  
246 < ! Query each potential and return the cutoff for that potential. We build the neighbor list based on the largest cutoff value for that atype. Each potential can decide whether to calculate the force for that atype based upon it's own cutoff.
247 <  subroutine createRcuts(defaultRList)
253 <    real(kind=dp), intent(in), optional :: defaultRList
254 <    integer :: iMap
255 <    integer :: map_i,map_j
256 <    real(kind=dp) :: thisRCut = 0.0_dp
257 <    real(kind=dp) :: actualCutoff = 0.0_dp
258 <    integer :: nAtypes
246 >    haveInteractionHash = .true.
247 >  end subroutine createInteractionHash
248  
249 <    if(.not. allocated(InteractionMap)) return
249 >  subroutine createGtypeCutoffMap(stat)
250  
251 <    nAtypes = getSize(atypes)
252 < ! If we pass a default rcut, set all atypes to that cutoff distance
253 <    if(present(defaultRList)) then
254 <       InteractionMap(:,:)%rList = defaultRList
255 <       InteractionMap(:,:)%rListSq = defaultRList*defaultRList
256 <       haveRlist = .true.
257 <       return
258 <    end if
251 >    integer, intent(out), optional :: stat
252 >    logical :: i_is_LJ
253 >    logical :: i_is_Elect
254 >    logical :: i_is_Sticky
255 >    logical :: i_is_StickyP
256 >    logical :: i_is_GB
257 >    logical :: i_is_EAM
258 >    logical :: i_is_Shape
259 >    logical :: GtypeFound
260  
261 <    do map_i = 1,nAtypes
262 <       do map_j = map_i,nAtypes
263 <          iMap = InteractionMap(map_i, map_j)%InteractionHash
264 <          
265 <          if ( iand(iMap, LJ_PAIR).ne.0 ) then
266 < !            thisRCut = getLJCutOff(map_i,map_j)
267 <             if (thisRcut > actualCutoff) actualCutoff = thisRcut
268 <          endif
269 <          
270 <          if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
271 < !            thisRCut = getElectrostaticCutOff(map_i,map_j)
272 <             if (thisRcut > actualCutoff) actualCutoff = thisRcut
261 >    integer :: myStatus, nAtypes,  i, j, istart, iend, jstart, jend
262 >    integer :: n_in_i, me_i, ia, g, atom1, nGroupTypes
263 >    integer :: nGroupsInRow
264 >    real(kind=dp):: thisSigma, bigSigma, thisRcut, tol, skin
265 >    real(kind=dp) :: biggestAtypeCutoff
266 >
267 >    stat = 0
268 >    if (.not. haveInteractionHash) then
269 >       call createInteractionHash(myStatus)      
270 >       if (myStatus .ne. 0) then
271 >          write(default_error, *) 'createInteractionHash failed in doForces!'
272 >          stat = -1
273 >          return
274 >       endif
275 >    endif
276 > #ifdef IS_MPI
277 >    nGroupsInRow = getNgroupsInRow(plan_group_row)
278 > #endif
279 >    nAtypes = getSize(atypes)
280 > ! Set all of the initial cutoffs to zero.
281 >    atypeMaxCutoff = 0.0_dp
282 >    do i = 1, nAtypes
283 >       if (SimHasAtype(i)) then    
284 >          call getElementProperty(atypes, i, "is_LennardJones", i_is_LJ)
285 >          call getElementProperty(atypes, i, "is_Electrostatic", i_is_Elect)
286 >          call getElementProperty(atypes, i, "is_Sticky", i_is_Sticky)
287 >          call getElementProperty(atypes, i, "is_StickyPower", i_is_StickyP)
288 >          call getElementProperty(atypes, i, "is_GayBerne", i_is_GB)
289 >          call getElementProperty(atypes, i, "is_EAM", i_is_EAM)
290 >          call getElementProperty(atypes, i, "is_Shape", i_is_Shape)
291 >          
292 >
293 >          if (haveDefaultCutoffs) then
294 >             atypeMaxCutoff(i) = defaultRcut
295 >          else
296 >             if (i_is_LJ) then          
297 >                thisRcut = getSigma(i) * 2.5_dp
298 >                if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
299 >             endif
300 >             if (i_is_Elect) then
301 >                thisRcut = defaultRcut
302 >                if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
303 >             endif
304 >             if (i_is_Sticky) then
305 >                thisRcut = getStickyCut(i)
306 >                if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
307 >             endif
308 >             if (i_is_StickyP) then
309 >                thisRcut = getStickyPowerCut(i)
310 >                if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
311 >             endif
312 >             if (i_is_GB) then
313 >                thisRcut = getGayBerneCut(i)
314 >                if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
315 >             endif
316 >             if (i_is_EAM) then
317 >                thisRcut = getEAMCut(i)
318 >                if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
319 >             endif
320 >             if (i_is_Shape) then
321 >                thisRcut = getShapeCut(i)
322 >                if (thisRCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisRCut
323 >             endif
324            endif
325            
326 <          if ( iand(iMap, STICKY_PAIR).ne.0 ) then
327 < !             thisRCut = getStickyCutOff(map_i,map_j)
328 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
329 <           endif
289 <          
290 <           if ( iand(iMap, STICKYPOWER_PAIR).ne.0 ) then
291 < !              thisRCut = getStickyPowerCutOff(map_i,map_j)
292 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
293 <           endif
294 <          
295 <           if ( iand(iMap, GAYBERNE_PAIR).ne.0 ) then
296 < !              thisRCut = getGayberneCutOff(map_i,map_j)
297 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
298 <           endif
299 <          
300 <           if ( iand(iMap, GAYBERNE_LJ).ne.0 ) then
301 < !              thisRCut = getGaybrneLJCutOff(map_i,map_j)
302 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
303 <           endif
304 <          
305 <           if ( iand(iMap, EAM_PAIR).ne.0 ) then      
306 < !              thisRCut = getEAMCutOff(map_i,map_j)
307 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
308 <           endif
309 <          
310 <           if ( iand(iMap, SHAPE_PAIR).ne.0 ) then      
311 < !              thisRCut = getShapeCutOff(map_i,map_j)
312 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
313 <           endif
314 <          
315 <           if ( iand(iMap, SHAPE_LJ).ne.0 ) then      
316 < !              thisRCut = getShapeLJCutOff(map_i,map_j)
317 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
318 <           endif
319 <           InteractionMap(map_i, map_j)%rList = actualCutoff
320 <           InteractionMap(map_i, map_j)%rListSq = actualCutoff * actualCutoff
321 <        end do
322 <     end do
323 <          haveRlist = .true.
324 <  end subroutine createRcuts
326 >          
327 >          if (atypeMaxCutoff(i).gt.biggestAtypeCutoff) then
328 >             biggestAtypeCutoff = atypeMaxCutoff(i)
329 >          endif
330  
331 <
332 < !!! THIS GOES AWAY FOR SIZE DEPENDENT CUTOFF
333 < !!$  subroutine setRlistDF( this_rlist )
334 < !!$
335 < !!$   real(kind=dp) :: this_rlist
336 < !!$
337 < !!$    rlist = this_rlist
338 < !!$    rlistsq = rlist * rlist
339 < !!$
340 < !!$    haveRlist = .true.
341 < !!$
342 < !!$  end subroutine setRlistDF
331 >       endif
332 >    enddo
333 >  
334 >    nGroupTypes = 0
335 >    
336 >    istart = 1
337 > #ifdef IS_MPI
338 >    iend = nGroupsInRow
339 > #else
340 >    iend = nGroups
341 > #endif
342 >    
343 >    !! allocate the groupToGtype and gtypeMaxCutoff here.
344 >    if(.not.allocated(groupToGtype)) then
345 >       allocate(groupToGtype(iend))
346 >       allocate(groupMaxCutoff(iend))
347 >       allocate(gtypeMaxCutoff(iend))
348 >       groupMaxCutoff = 0.0_dp
349 >       gtypeMaxCutoff = 0.0_dp
350 >    endif
351 >    !! first we do a single loop over the cutoff groups to find the
352 >    !! largest cutoff for any atypes present in this group.  We also
353 >    !! create gtypes at this point.
354 >    
355 >    tol = 1.0d-6
356 >    
357 >    do i = istart, iend      
358 >       n_in_i = groupStartRow(i+1) - groupStartRow(i)
359 >       groupMaxCutoff(i) = 0.0_dp
360 >       do ia = groupStartRow(i), groupStartRow(i+1)-1
361 >          atom1 = groupListRow(ia)
362 > #ifdef IS_MPI
363 >          me_i = atid_row(atom1)
364 > #else
365 >          me_i = atid(atom1)
366 > #endif          
367 >          if (atypeMaxCutoff(me_i).gt.groupMaxCutoff(i)) then
368 >             groupMaxCutoff(i)=atypeMaxCutoff(me_i)
369 >          endif          
370 >       enddo
371  
372 +       if (nGroupTypes.eq.0) then
373 +          nGroupTypes = nGroupTypes + 1
374 +          gtypeMaxCutoff(nGroupTypes) = groupMaxCutoff(i)
375 +          groupToGtype(i) = nGroupTypes
376 +       else
377 +          GtypeFound = .false.
378 +          do g = 1, nGroupTypes
379 +             if ( abs(groupMaxCutoff(i) - gtypeMaxCutoff(g)).lt.tol) then
380 +                groupToGtype(i) = g
381 +                GtypeFound = .true.
382 +             endif
383 +          enddo
384 +          if (.not.GtypeFound) then            
385 +             nGroupTypes = nGroupTypes + 1
386 +             gtypeMaxCutoff(nGroupTypes) = groupMaxCutoff(i)
387 +             groupToGtype(i) = nGroupTypes
388 +          endif
389 +       endif
390 +    enddo    
391  
392 +    !! allocate the gtypeCutoffMap here.
393 +    allocate(gtypeCutoffMap(nGroupTypes,nGroupTypes))
394 +    !! then we do a double loop over all the group TYPES to find the cutoff
395 +    !! map between groups of two types
396 +    
397 +    do i = 1, nGroupTypes
398 +       do j = 1, nGroupTypes
399 +      
400 +          select case(cutoffPolicy)
401 +          case(TRADITIONAL_CUTOFF_POLICY)
402 +             thisRcut = maxval(gtypeMaxCutoff)
403 +          case(MIX_CUTOFF_POLICY)
404 +             thisRcut = 0.5_dp * (gtypeMaxCutoff(i) + gtypeMaxCutoff(j))
405 +          case(MAX_CUTOFF_POLICY)
406 +             thisRcut = max(gtypeMaxCutoff(i), gtypeMaxCutoff(j))
407 +          case default
408 +             call handleError("createGtypeCutoffMap", "Unknown Cutoff Policy")
409 +             return
410 +          end select
411 +          gtypeCutoffMap(i,j)%rcut = thisRcut
412 +          gtypeCutoffMap(i,j)%rcutsq = thisRcut*thisRcut
413 +          skin = defaultRlist - defaultRcut
414 +          gtypeCutoffMap(i,j)%rlistsq = (thisRcut + skin)**2
415 +
416 +          ! sanity check
417 +
418 +          if (haveDefaultCutoffs) then
419 +             if (abs(gtypeCutoffMap(i,j)%rcut - defaultRcut).gt.0.0001) then
420 +                call handleError("createGtypeCutoffMap", "user-specified rCut does not match computed group Cutoff")
421 +             endif
422 +          endif
423 +       enddo
424 +    enddo
425 +
426 +    haveGtypeCutoffMap = .true.
427 +   end subroutine createGtypeCutoffMap
428 +
429 +   subroutine setDefaultCutoffs(defRcut, defRsw, defRlist, cutPolicy)
430 +     real(kind=dp),intent(in) :: defRcut, defRsw, defRlist
431 +     integer, intent(in) :: cutPolicy
432 +
433 +     defaultRcut = defRcut
434 +     defaultRsw = defRsw
435 +     defaultRlist = defRlist
436 +     cutoffPolicy = cutPolicy
437 +
438 +     haveDefaultCutoffs = .true.
439 +   end subroutine setDefaultCutoffs
440 +
441 +   subroutine setCutoffPolicy(cutPolicy)
442 +
443 +     integer, intent(in) :: cutPolicy
444 +     cutoffPolicy = cutPolicy
445 +     call createGtypeCutoffMap()
446 +   end subroutine setCutoffPolicy
447 +    
448 +    
449    subroutine setSimVariables()
450      SIM_uses_DirectionalAtoms = SimUsesDirectionalAtoms()
342    SIM_uses_LennardJones = SimUsesLennardJones()
343    SIM_uses_Electrostatics = SimUsesElectrostatics()
344    SIM_uses_Charges = SimUsesCharges()
345    SIM_uses_Dipoles = SimUsesDipoles()
346    SIM_uses_Sticky = SimUsesSticky()
347    SIM_uses_StickyPower = SimUsesStickyPower()
348    SIM_uses_GayBerne = SimUsesGayBerne()
451      SIM_uses_EAM = SimUsesEAM()
350    SIM_uses_Shapes = SimUsesShapes()
351    SIM_uses_FLARB = SimUsesFLARB()
352    SIM_uses_RF = SimUsesRF()
452      SIM_requires_postpair_calc = SimRequiresPostpairCalc()
453      SIM_requires_prepair_calc = SimRequiresPrepairCalc()
454      SIM_uses_PBC = SimUsesPBC()
# Line 366 | Line 465 | contains
465  
466      error = 0
467  
468 <    if (.not. haveInteractionMap) then
468 >    if (.not. haveInteractionHash) then      
469 >       myStatus = 0      
470 >       call createInteractionHash(myStatus)      
471 >       if (myStatus .ne. 0) then
472 >          write(default_error, *) 'createInteractionHash failed in doForces!'
473 >          error = -1
474 >          return
475 >       endif
476 >    endif
477  
478 <       myStatus = 0
479 <
480 <       call createInteractionMap(myStatus)
374 <
478 >    if (.not. haveGtypeCutoffMap) then        
479 >       myStatus = 0      
480 >       call createGtypeCutoffMap(myStatus)      
481         if (myStatus .ne. 0) then
482 <          write(default_error, *) 'createInteractionMap failed in doForces!'
482 >          write(default_error, *) 'createGtypeCutoffMap failed in doForces!'
483            error = -1
484            return
485         endif
# Line 383 | Line 489 | contains
489         call setSimVariables()
490      endif
491  
492 <    if (.not. haveRlist) then
493 <       write(default_error, *) 'rList has not been set in doForces!'
494 <       error = -1
495 <       return
496 <    endif
492 >  !  if (.not. haveRlist) then
493 >  !     write(default_error, *) 'rList has not been set in doForces!'
494 >  !     error = -1
495 >  !     return
496 >  !  endif
497  
498      if (.not. haveNeighborList) then
499         write(default_error, *) 'neighbor list has not been initialized in doForces!'
# Line 412 | Line 518 | contains
518    end subroutine doReadyCheck
519  
520  
521 <  subroutine init_FF(use_RF_c, thisStat)
521 >  subroutine init_FF(thisESM, thisStat)
522  
523 <    logical, intent(in) :: use_RF_c
418 <
523 >    integer, intent(in) :: thisESM
524      integer, intent(out) :: thisStat  
525      integer :: my_status, nMatches
526      integer, pointer :: MatchList(:) => null()
# Line 424 | Line 529 | contains
529      !! assume things are copacetic, unless they aren't
530      thisStat = 0
531  
532 <    !! Fortran's version of a cast:
428 <    FF_uses_RF = use_RF_c
532 >    electrostaticSummationMethod = thisESM
533  
534      !! init_FF is called *after* all of the atom types have been
535      !! defined in atype_module using the new_atype subroutine.
# Line 434 | Line 538 | contains
538      !! interactions are used by the force field.    
539  
540      FF_uses_DirectionalAtoms = .false.
437    FF_uses_LennardJones = .false.
438    FF_uses_Electrostatics = .false.
439    FF_uses_Charges = .false.    
541      FF_uses_Dipoles = .false.
441    FF_uses_Sticky = .false.
442    FF_uses_StickyPower = .false.
542      FF_uses_GayBerne = .false.
543      FF_uses_EAM = .false.
445    FF_uses_Shapes = .false.
446    FF_uses_FLARB = .false.
544  
545      call getMatchingElementList(atypes, "is_Directional", .true., &
546           nMatches, MatchList)
547      if (nMatches .gt. 0) FF_uses_DirectionalAtoms = .true.
451
452    call getMatchingElementList(atypes, "is_LennardJones", .true., &
453         nMatches, MatchList)
454    if (nMatches .gt. 0) FF_uses_LennardJones = .true.
548  
456    call getMatchingElementList(atypes, "is_Electrostatic", .true., &
457         nMatches, MatchList)
458    if (nMatches .gt. 0) then
459       FF_uses_Electrostatics = .true.
460    endif
461
462    call getMatchingElementList(atypes, "is_Charge", .true., &
463         nMatches, MatchList)
464    if (nMatches .gt. 0) then
465       FF_uses_Charges = .true.  
466       FF_uses_Electrostatics = .true.
467    endif
468
549      call getMatchingElementList(atypes, "is_Dipole", .true., &
550           nMatches, MatchList)
551 <    if (nMatches .gt. 0) then
472 <       FF_uses_Dipoles = .true.
473 <       FF_uses_Electrostatics = .true.
474 <       FF_uses_DirectionalAtoms = .true.
475 <    endif
476 <
477 <    call getMatchingElementList(atypes, "is_Quadrupole", .true., &
478 <         nMatches, MatchList)
479 <    if (nMatches .gt. 0) then
480 <       FF_uses_Quadrupoles = .true.
481 <       FF_uses_Electrostatics = .true.
482 <       FF_uses_DirectionalAtoms = .true.
483 <    endif
484 <
485 <    call getMatchingElementList(atypes, "is_Sticky", .true., nMatches, &
486 <         MatchList)
487 <    if (nMatches .gt. 0) then
488 <       FF_uses_Sticky = .true.
489 <       FF_uses_DirectionalAtoms = .true.
490 <    endif
491 <
492 <    call getMatchingElementList(atypes, "is_StickyPower", .true., nMatches, &
493 <         MatchList)
494 <    if (nMatches .gt. 0) then
495 <       FF_uses_StickyPower = .true.
496 <       FF_uses_DirectionalAtoms = .true.
497 <    endif
551 >    if (nMatches .gt. 0) FF_uses_Dipoles = .true.
552      
553      call getMatchingElementList(atypes, "is_GayBerne", .true., &
554           nMatches, MatchList)
555 <    if (nMatches .gt. 0) then
502 <       FF_uses_GayBerne = .true.
503 <       FF_uses_DirectionalAtoms = .true.
504 <    endif
555 >    if (nMatches .gt. 0) FF_uses_GayBerne = .true.
556  
557      call getMatchingElementList(atypes, "is_EAM", .true., nMatches, MatchList)
558      if (nMatches .gt. 0) FF_uses_EAM = .true.
559  
509    call getMatchingElementList(atypes, "is_Shape", .true., &
510         nMatches, MatchList)
511    if (nMatches .gt. 0) then
512       FF_uses_Shapes = .true.
513       FF_uses_DirectionalAtoms = .true.
514    endif
560  
516    call getMatchingElementList(atypes, "is_FLARB", .true., &
517         nMatches, MatchList)
518    if (nMatches .gt. 0) FF_uses_FLARB = .true.
519
520    !! Assume sanity (for the sake of argument)
561      haveSaneForceField = .true.
562  
563 <    !! check to make sure the FF_uses_RF setting makes sense
563 >    !! check to make sure the reaction field setting makes sense
564  
565 <    if (FF_uses_dipoles) then
566 <       if (FF_uses_RF) then
565 >    if (FF_uses_Dipoles) then
566 >       if (electrostaticSummationMethod == REACTION_FIELD) then
567            dielect = getDielect()
568            call initialize_rf(dielect)
569         endif
570      else
571 <       if (FF_uses_RF) then          
571 >       if (electrostaticSummationMethod == REACTION_FIELD) then
572            write(default_error,*) 'Using Reaction Field with no dipoles?  Huh?'
573            thisStat = -1
574            haveSaneForceField = .false.
575            return
576         endif
577      endif
538
539    !sticky module does not contain check_sticky_FF anymore
540    !if (FF_uses_sticky) then
541    !   call check_sticky_FF(my_status)
542    !   if (my_status /= 0) then
543    !      thisStat = -1
544    !      haveSaneForceField = .false.
545    !      return
546    !   end if
547    !endif
578  
579      if (FF_uses_EAM) then
580         call init_EAM_FF(my_status)
# Line 565 | Line 595 | contains
595         endif
596      endif
597  
568    if (FF_uses_GayBerne .and. FF_uses_LennardJones) then
569    endif
570
598      if (.not. haveNeighborList) then
599         !! Create neighbor lists
600         call expandNeighborList(nLocal, my_status)
# Line 631 | Line 658 | contains
658      integer :: localError
659      integer :: propPack_i, propPack_j
660      integer :: loopStart, loopEnd, loop
661 <    integer :: iMap
661 >    integer :: iHash
662      real(kind=dp) :: listSkin = 1.0  
663  
664      !! initialize local variables  
# Line 750 | Line 777 | contains
777               endif
778  
779   #ifdef IS_MPI
780 +             me_j = atid_col(j)
781               call get_interatomic_vector(q_group_Row(:,i), &
782                    q_group_Col(:,j), d_grp, rgrpsq)
783   #else
784 +             me_j = atid(j)
785               call get_interatomic_vector(q_group(:,i), &
786                    q_group(:,j), d_grp, rgrpsq)
787 < #endif
787 > #endif      
788  
789 <             if (rgrpsq < InteractionMap(me_i,me_j)%rListsq) then
789 >             if (rgrpsq < gtypeCutoffMap(groupToGtype(i),groupToGtype(j))%rListsq) then
790                  if (update_nlist) then
791                     nlist = nlist + 1
792  
# Line 957 | Line 986 | contains
986  
987      if (FF_RequiresPostpairCalc() .and. SIM_requires_postpair_calc) then
988  
989 <       if (FF_uses_RF .and. SIM_uses_RF) then
989 >       if (electrostaticSummationMethod == REACTION_FIELD) then
990  
991   #ifdef IS_MPI
992            call scatter(rf_Row,rf,plan_atom_row_3d)
# Line 975 | Line 1004 | contains
1004   #else
1005               me_i = atid(i)
1006   #endif
1007 <             iMap = InteractionMap(me_i, me_j)%InteractionHash
1007 >             iHash = InteractionHash(me_i,me_j)
1008              
1009 <             if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
1009 >             if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then
1010  
1011                  mu_i = getDipoleMoment(me_i)
1012  
# Line 1041 | Line 1070 | contains
1070      real ( kind = dp ), intent(inout) :: rijsq
1071      real ( kind = dp )                :: r
1072      real ( kind = dp ), intent(inout) :: d(3)
1044    real ( kind = dp ) :: ebalance
1073      integer :: me_i, me_j
1074  
1075 <    integer :: iMap
1075 >    integer :: iHash
1076  
1077      r = sqrt(rijsq)
1078      vpair = 0.0d0
# Line 1058 | Line 1086 | contains
1086      me_j = atid(j)
1087   #endif
1088  
1089 <    iMap = InteractionMap(me_i, me_j)%InteractionHash
1089 >    iHash = InteractionHash(me_i, me_j)
1090  
1091 <    if ( iand(iMap, LJ_PAIR).ne.0 ) then
1091 >    if ( iand(iHash, LJ_PAIR).ne.0 ) then
1092         call do_lj_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot)
1093      endif
1094  
1095 <    if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
1095 >    if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then
1096         call doElectrostaticPair(i, j, d, r, rijsq, sw, vpair, fpair, &
1097              pot, eFrame, f, t, do_pot)
1098  
1099 <       if (FF_uses_RF .and. SIM_uses_RF) then
1099 >       if (electrostaticSummationMethod == REACTION_FIELD) then
1100  
1101            ! CHECK ME (RF needs to know about all electrostatic types)
1102            call accumulate_rf(i, j, r, eFrame, sw)
# Line 1077 | Line 1105 | contains
1105  
1106      endif
1107  
1108 <    if ( iand(iMap, STICKY_PAIR).ne.0 ) then
1108 >    if ( iand(iHash, STICKY_PAIR).ne.0 ) then
1109         call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1110              pot, A, f, t, do_pot)
1111      endif
1112  
1113 <    if ( iand(iMap, STICKYPOWER_PAIR).ne.0 ) then
1113 >    if ( iand(iHash, STICKYPOWER_PAIR).ne.0 ) then
1114         call do_sticky_power_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1115              pot, A, f, t, do_pot)
1116      endif
1117  
1118 <    if ( iand(iMap, GAYBERNE_PAIR).ne.0 ) then
1118 >    if ( iand(iHash, GAYBERNE_PAIR).ne.0 ) then
1119         call do_gb_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1120              pot, A, f, t, do_pot)
1121      endif
1122      
1123 <    if ( iand(iMap, GAYBERNE_LJ).ne.0 ) then
1123 >    if ( iand(iHash, GAYBERNE_LJ).ne.0 ) then
1124   !      call do_gblj_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1125   !           pot, A, f, t, do_pot)
1126      endif
1127  
1128 <    if ( iand(iMap, EAM_PAIR).ne.0 ) then      
1128 >    if ( iand(iHash, EAM_PAIR).ne.0 ) then      
1129         call do_eam_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, &
1130              do_pot)
1131      endif
1132  
1133 <    if ( iand(iMap, SHAPE_PAIR).ne.0 ) then      
1133 >    if ( iand(iHash, SHAPE_PAIR).ne.0 ) then      
1134         call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1135              pot, A, f, t, do_pot)
1136      endif
1137  
1138 <    if ( iand(iMap, SHAPE_LJ).ne.0 ) then      
1138 >    if ( iand(iHash, SHAPE_LJ).ne.0 ) then      
1139         call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1140              pot, A, f, t, do_pot)
1141      endif
# Line 1129 | Line 1157 | contains
1157      real ( kind = dp )                :: r, rc
1158      real ( kind = dp ), intent(inout) :: d(3), dc(3)
1159  
1160 <    integer :: me_i, me_j, iMap
1160 >    integer :: me_i, me_j, iHash
1161  
1162 +    r = sqrt(rijsq)
1163 +
1164   #ifdef IS_MPI  
1165      me_i = atid_row(i)
1166      me_j = atid_col(j)  
# Line 1139 | Line 1169 | contains
1169      me_j = atid(j)  
1170   #endif
1171  
1172 <    iMap = InteractionMap(me_i, me_j)%InteractionHash
1172 >    iHash = InteractionHash(me_i, me_j)
1173  
1174 <    if ( iand(iMap, EAM_PAIR).ne.0 ) then      
1174 >    if ( iand(iHash, EAM_PAIR).ne.0 ) then      
1175              call calc_EAM_prepair_rho(i, j, d, r, rijsq )
1176      endif
1177      
# Line 1338 | Line 1368 | contains
1368  
1369    function FF_UsesDirectionalAtoms() result(doesit)
1370      logical :: doesit
1371 <    doesit = FF_uses_DirectionalAtoms .or. FF_uses_Dipoles .or. &
1342 <         FF_uses_Quadrupoles .or. FF_uses_Sticky .or. &
1343 <         FF_uses_StickyPower .or. FF_uses_GayBerne .or. FF_uses_Shapes
1371 >    doesit = FF_uses_DirectionalAtoms
1372    end function FF_UsesDirectionalAtoms
1373  
1374    function FF_RequiresPrepairCalc() result(doesit)
# Line 1350 | Line 1378 | contains
1378  
1379    function FF_RequiresPostpairCalc() result(doesit)
1380      logical :: doesit
1381 <    doesit = FF_uses_RF
1381 >    if (electrostaticSummationMethod == REACTION_FIELD) doesit = .true.
1382    end function FF_RequiresPostpairCalc
1383  
1384   #ifdef PROFILE

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines