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

Comparing trunk/OOPSE-2.0/src/UseTheForce/doForces.F90 (file contents):
Revision 2266 by chuckv, Thu Jul 28 22:12:45 2005 UTC vs.
Revision 2270 by gezelter, Tue Aug 9 22:33:37 2005 UTC

# Line 45 | Line 45
45  
46   !! @author Charles F. Vardeman II
47   !! @author Matthew Meineke
48 < !! @version $Id: doForces.F90,v 1.24 2005-07-28 22:12:45 chuckv Exp $, $Date: 2005-07-28 22:12:45 $, $Name: not supported by cvs2svn $, $Revision: 1.24 $
48 > !! @version $Id: doForces.F90,v 1.28 2005-08-09 22:33:37 gezelter Exp $, $Date: 2005-08-09 22:33:37 $, $Name: not supported by cvs2svn $, $Revision: 1.28 $
49  
50  
51   module doForces
# Line 78 | Line 78 | module doForces
78    INTEGER, PARAMETER:: PREPAIR_LOOP = 1
79    INTEGER, PARAMETER:: PAIR_LOOP    = 2
80  
81  logical, save :: haveRlist = .false.
81    logical, save :: haveNeighborList = .false.
82    logical, save :: haveSIMvariables = .false.
83    logical, save :: haveSaneForceField = .false.
84 <  logical, save :: haveInteractionMap = .false.
84 >  logical, save :: haveInteractionHash = .false.
85 >  logical, save :: haveGtypeCutoffMap = .false.
86  
87    logical, save :: FF_uses_DirectionalAtoms
88  logical, save :: FF_uses_LennardJones
89  logical, save :: FF_uses_Electrostatics
90  logical, save :: FF_uses_Charges
88    logical, save :: FF_uses_Dipoles
92  logical, save :: FF_uses_Quadrupoles
93  logical, save :: FF_uses_Sticky
94  logical, save :: FF_uses_StickyPower
89    logical, save :: FF_uses_GayBerne
90    logical, save :: FF_uses_EAM
97  logical, save :: FF_uses_Shapes
98  logical, save :: FF_uses_FLARB
91    logical, save :: FF_uses_RF
92  
93    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
94    logical, save :: SIM_uses_EAM
111  logical, save :: SIM_uses_Shapes
112  logical, save :: SIM_uses_FLARB
95    logical, save :: SIM_uses_RF
96    logical, save :: SIM_requires_postpair_calc
97    logical, save :: SIM_requires_prepair_calc
98    logical, save :: SIM_uses_PBC
117  logical, save :: SIM_uses_molecular_cutoffs
99  
119  !!!GO AWAY---------
120  !!!!!real(kind=dp), save :: rlist, rlistsq
121
100    public :: init_FF
101    public :: do_force_loop
102 < !  public :: setRlistDF
103 <  !public :: addInteraction
126 <  !public :: setInteractionHash
127 <  !public :: getInteractionHash
128 <  public :: createInteractionMap
129 <  public :: createRcuts
102 >  public :: createInteractionHash
103 >  public :: createGtypeCutoffMap
104  
105   #ifdef PROFILE
106    public :: getforcetime
# Line 134 | Line 108 | module doForces
108    real :: forceTimeInitial, forceTimeFinal
109    integer :: nLoops
110   #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
111    
112 <  type(Interaction), dimension(:,:),allocatable :: InteractionMap
112 >  !! Variables for cutoff mapping and interaction mapping
113 >  ! Bit hash to determine pair-pair interactions.
114 >  integer, dimension(:,:), allocatable :: InteractionHash
115 >  real(kind=dp), dimension(:), allocatable :: atypeMaxCutoff
116 >  real(kind=dp), dimension(:), allocatable :: groupMaxCutoff
117 >  integer, dimension(:), allocatable :: groupToGtype
118 >  real(kind=dp), dimension(:), allocatable :: gtypeMaxCutoff
119 >  type ::gtypeCutoffs
120 >     real(kind=dp) :: rcut
121 >     real(kind=dp) :: rcutsq
122 >     real(kind=dp) :: rlistsq
123 >  end type gtypeCutoffs
124 >  type(gtypeCutoffs), dimension(:,:), allocatable :: gtypeCutoffMap
125    
146
147  
126   contains
127  
128 <
151 <  subroutine createInteractionMap(status)
128 >  subroutine createInteractionHash(status)
129      integer :: nAtypes
130      integer, intent(out) :: status
131      integer :: i
132      integer :: j
133 <    integer :: ihash
134 <    real(kind=dp) :: myRcut
158 < ! Test Types
133 >    integer :: iHash
134 >    !! Test Types
135      logical :: i_is_LJ
136      logical :: i_is_Elect
137      logical :: i_is_Sticky
# Line 171 | Line 147 | contains
147      logical :: j_is_EAM
148      logical :: j_is_Shape
149      
150 <    status = 0
151 <    
150 >    status = 0  
151 >
152      if (.not. associated(atypes)) then
153 <       call handleError("atype", "atypes was not present before call of createDefaultInteractionMap!")
153 >       call handleError("atype", "atypes was not present before call of createInteractionHash!")
154         status = -1
155         return
156      endif
# Line 186 | Line 162 | contains
162         return
163      end if
164  
165 <    if (.not. allocated(InteractionMap)) then
166 <       allocate(InteractionMap(nAtypes,nAtypes))
165 >    if (.not. allocated(InteractionHash)) then
166 >       allocate(InteractionHash(nAtypes,nAtypes))
167      endif
168 +
169 +    if (.not. allocated(atypeMaxCutoff)) then
170 +       allocate(atypeMaxCutoff(nAtypes))
171 +    endif
172          
173      do i = 1, nAtypes
174         call getElementProperty(atypes, i, "is_LennardJones", i_is_LJ)
# Line 199 | Line 179 | contains
179         call getElementProperty(atypes, i, "is_EAM", i_is_EAM)
180         call getElementProperty(atypes, i, "is_Shape", i_is_Shape)
181  
182 +       if (i_is_LJ) then
183 +          thisCut = getDefaultLJCutoff(i)
184 +          if (thisCut .gt. atypeMaxCutoff(i)) atypeMaxCutoff(i) = thisCut
185 +       endif
186 +
187 +
188 +
189         do j = i, nAtypes
190  
191            iHash = 0
# Line 241 | Line 228 | contains
228            if (i_is_LJ .and. j_is_Shape) iHash = ior(iHash, SHAPE_LJ)
229  
230  
231 <          InteractionMap(i,j)%InteractionHash = iHash
232 <          InteractionMap(j,i)%InteractionHash = iHash
231 >          InteractionHash(i,j) = iHash
232 >          InteractionHash(j,i) = iHash
233  
234         end do
235  
236      end do
250  end subroutine createInteractionMap
237  
238 < ! 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.
239 <  subroutine createRcuts(defaultRList,stat)
254 <    real(kind=dp), intent(in), optional :: defaultRList
255 <    integer :: iMap
256 <    integer :: map_i,map_j
257 <    real(kind=dp) :: thisRCut = 0.0_dp
258 <    real(kind=dp) :: actualCutoff = 0.0_dp
259 <    integer, intent(out) :: stat
260 <    integer :: nAtypes
261 <    integer :: myStatus
238 >    haveInteractionHash = .true.
239 >  end subroutine createInteractionHash
240  
241 <    stat = 0
264 <    if (.not. haveInteractionMap) then
241 >  subroutine createGtypeCutoffMap(defaultRcut, defaultSkinThickness, stat)
242  
243 <       call createInteractionMap(myStatus)
243 >    real(kind=dp), intent(in), optional :: defaultRCut, defaultSkinThickness
244 >    integer, intent(out) :: stat
245  
246 +    integer :: myStatus, nAtypes
247 +
248 +    stat = 0
249 +    if (.not. haveInteractionHash) then
250 +       call createInteractionHash(myStatus)      
251         if (myStatus .ne. 0) then
252 <          write(default_error, *) 'createInteractionMap failed in doForces!'
252 >          write(default_error, *) 'createInteractionHash failed in doForces!'
253            stat = -1
254            return
255         endif
256      endif
257  
275
258      nAtypes = getSize(atypes)
277 ! If we pass a default rcut, set all atypes to that cutoff distance
278    if(present(defaultRList)) then
279       InteractionMap(:,:)%rList = defaultRList
280       InteractionMap(:,:)%rListSq = defaultRList*defaultRList
281       haveRlist = .true.
282       return
283    end if
259  
260 <    do map_i = 1,nAtypes
261 <       do map_j = map_i,nAtypes
262 <          iMap = InteractionMap(map_i, map_j)%InteractionHash
263 <          
264 <          if ( iand(iMap, LJ_PAIR).ne.0 ) then
290 < !            thisRCut = getLJCutOff(map_i,map_j)
291 <             if (thisRcut > actualCutoff) actualCutoff = thisRcut
292 <          endif
293 <          
294 <          if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
295 < !            thisRCut = getElectrostaticCutOff(map_i,map_j)
296 <             if (thisRcut > actualCutoff) actualCutoff = thisRcut
297 <          endif
298 <          
299 <          if ( iand(iMap, STICKY_PAIR).ne.0 ) then
300 < !             thisRCut = getStickyCutOff(map_i,map_j)
301 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
302 <           endif
303 <          
304 <           if ( iand(iMap, STICKYPOWER_PAIR).ne.0 ) then
305 < !              thisRCut = getStickyPowerCutOff(map_i,map_j)
306 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
307 <           endif
308 <          
309 <           if ( iand(iMap, GAYBERNE_PAIR).ne.0 ) then
310 < !              thisRCut = getGayberneCutOff(map_i,map_j)
311 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
312 <           endif
313 <          
314 <           if ( iand(iMap, GAYBERNE_LJ).ne.0 ) then
315 < !              thisRCut = getGaybrneLJCutOff(map_i,map_j)
316 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
317 <           endif
318 <          
319 <           if ( iand(iMap, EAM_PAIR).ne.0 ) then      
320 < !              thisRCut = getEAMCutOff(map_i,map_j)
321 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
322 <           endif
323 <          
324 <           if ( iand(iMap, SHAPE_PAIR).ne.0 ) then      
325 < !              thisRCut = getShapeCutOff(map_i,map_j)
326 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
327 <           endif
328 <          
329 <           if ( iand(iMap, SHAPE_LJ).ne.0 ) then      
330 < !              thisRCut = getShapeLJCutOff(map_i,map_j)
331 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
332 <           endif
333 <           InteractionMap(map_i, map_j)%rList = actualCutoff
334 <           InteractionMap(map_i, map_j)%rListSq = actualCutoff * actualCutoff
335 <        end do
336 <     end do
337 <          haveRlist = .true.
338 <  end subroutine createRcuts
260 >    do i = 1, nAtypes
261 >      
262 >       atypeMaxCutoff(i) =
263 >
264 >    
265  
266  
341 !!! THIS GOES AWAY FOR SIZE DEPENDENT CUTOFF
342 !!$  subroutine setRlistDF( this_rlist )
343 !!$
344 !!$   real(kind=dp) :: this_rlist
345 !!$
346 !!$    rlist = this_rlist
347 !!$    rlistsq = rlist * rlist
348 !!$
349 !!$    haveRlist = .true.
350 !!$
351 !!$  end subroutine setRlistDF
267  
268 +     haveGtypeCutoffMap = .true.
269 +   end subroutine createGtypeCutoffMap
270  
271    subroutine setSimVariables()
272      SIM_uses_DirectionalAtoms = SimUsesDirectionalAtoms()
356    SIM_uses_LennardJones = SimUsesLennardJones()
357    SIM_uses_Electrostatics = SimUsesElectrostatics()
358    SIM_uses_Charges = SimUsesCharges()
359    SIM_uses_Dipoles = SimUsesDipoles()
360    SIM_uses_Sticky = SimUsesSticky()
361    SIM_uses_StickyPower = SimUsesStickyPower()
362    SIM_uses_GayBerne = SimUsesGayBerne()
273      SIM_uses_EAM = SimUsesEAM()
364    SIM_uses_Shapes = SimUsesShapes()
365    SIM_uses_FLARB = SimUsesFLARB()
274      SIM_uses_RF = SimUsesRF()
275      SIM_requires_postpair_calc = SimRequiresPostpairCalc()
276      SIM_requires_prepair_calc = SimRequiresPrepairCalc()
# Line 380 | Line 288 | contains
288  
289      error = 0
290  
291 <    if (.not. haveInteractionMap) then
291 >    if (.not. haveInteractionHash) then      
292 >       myStatus = 0      
293 >       call createInteractionHash(myStatus)      
294 >       if (myStatus .ne. 0) then
295 >          write(default_error, *) 'createInteractionHash failed in doForces!'
296 >          error = -1
297 >          return
298 >       endif
299 >    endif
300  
301 <       myStatus = 0
302 <
303 <       call createInteractionMap(myStatus)
388 <
301 >    if (.not. haveGtypeCutoffMap) then        
302 >       myStatus = 0      
303 >       call createGtypeCutoffMap(myStatus)      
304         if (myStatus .ne. 0) then
305 <          write(default_error, *) 'createInteractionMap failed in doForces!'
305 >          write(default_error, *) 'createGtypeCutoffMap failed in doForces!'
306            error = -1
307            return
308         endif
# Line 448 | Line 363 | contains
363      !! interactions are used by the force field.    
364  
365      FF_uses_DirectionalAtoms = .false.
451    FF_uses_LennardJones = .false.
452    FF_uses_Electrostatics = .false.
453    FF_uses_Charges = .false.    
366      FF_uses_Dipoles = .false.
455    FF_uses_Sticky = .false.
456    FF_uses_StickyPower = .false.
367      FF_uses_GayBerne = .false.
368      FF_uses_EAM = .false.
459    FF_uses_Shapes = .false.
460    FF_uses_FLARB = .false.
369  
370      call getMatchingElementList(atypes, "is_Directional", .true., &
371           nMatches, MatchList)
372      if (nMatches .gt. 0) FF_uses_DirectionalAtoms = .true.
373  
466    call getMatchingElementList(atypes, "is_LennardJones", .true., &
467         nMatches, MatchList)
468    if (nMatches .gt. 0) FF_uses_LennardJones = .true.
469
470    call getMatchingElementList(atypes, "is_Electrostatic", .true., &
471         nMatches, MatchList)
472    if (nMatches .gt. 0) then
473       FF_uses_Electrostatics = .true.
474    endif
475
476    call getMatchingElementList(atypes, "is_Charge", .true., &
477         nMatches, MatchList)
478    if (nMatches .gt. 0) then
479       FF_uses_Charges = .true.  
480       FF_uses_Electrostatics = .true.
481    endif
482
374      call getMatchingElementList(atypes, "is_Dipole", .true., &
375           nMatches, MatchList)
376 <    if (nMatches .gt. 0) then
486 <       FF_uses_Dipoles = .true.
487 <       FF_uses_Electrostatics = .true.
488 <       FF_uses_DirectionalAtoms = .true.
489 <    endif
490 <
491 <    call getMatchingElementList(atypes, "is_Quadrupole", .true., &
492 <         nMatches, MatchList)
493 <    if (nMatches .gt. 0) then
494 <       FF_uses_Quadrupoles = .true.
495 <       FF_uses_Electrostatics = .true.
496 <       FF_uses_DirectionalAtoms = .true.
497 <    endif
498 <
499 <    call getMatchingElementList(atypes, "is_Sticky", .true., nMatches, &
500 <         MatchList)
501 <    if (nMatches .gt. 0) then
502 <       FF_uses_Sticky = .true.
503 <       FF_uses_DirectionalAtoms = .true.
504 <    endif
505 <
506 <    call getMatchingElementList(atypes, "is_StickyPower", .true., nMatches, &
507 <         MatchList)
508 <    if (nMatches .gt. 0) then
509 <       FF_uses_StickyPower = .true.
510 <       FF_uses_DirectionalAtoms = .true.
511 <    endif
376 >    if (nMatches .gt. 0) FF_uses_Dipoles = .true.
377      
378      call getMatchingElementList(atypes, "is_GayBerne", .true., &
379           nMatches, MatchList)
380 <    if (nMatches .gt. 0) then
516 <       FF_uses_GayBerne = .true.
517 <       FF_uses_DirectionalAtoms = .true.
518 <    endif
380 >    if (nMatches .gt. 0) FF_uses_GayBerne = .true.
381  
382      call getMatchingElementList(atypes, "is_EAM", .true., nMatches, MatchList)
383      if (nMatches .gt. 0) FF_uses_EAM = .true.
384  
523    call getMatchingElementList(atypes, "is_Shape", .true., &
524         nMatches, MatchList)
525    if (nMatches .gt. 0) then
526       FF_uses_Shapes = .true.
527       FF_uses_DirectionalAtoms = .true.
528    endif
385  
530    call getMatchingElementList(atypes, "is_FLARB", .true., &
531         nMatches, MatchList)
532    if (nMatches .gt. 0) FF_uses_FLARB = .true.
533
534    !! Assume sanity (for the sake of argument)
386      haveSaneForceField = .true.
387  
388      !! check to make sure the FF_uses_RF setting makes sense
389  
390 <    if (FF_uses_dipoles) then
390 >    if (FF_uses_Dipoles) then
391         if (FF_uses_RF) then
392            dielect = getDielect()
393            call initialize_rf(dielect)
# Line 550 | Line 401 | contains
401         endif
402      endif
403  
553    !sticky module does not contain check_sticky_FF anymore
554    !if (FF_uses_sticky) then
555    !   call check_sticky_FF(my_status)
556    !   if (my_status /= 0) then
557    !      thisStat = -1
558    !      haveSaneForceField = .false.
559    !      return
560    !   end if
561    !endif
562
404      if (FF_uses_EAM) then
405         call init_EAM_FF(my_status)
406         if (my_status /= 0) then
# Line 579 | Line 420 | contains
420         endif
421      endif
422  
582    if (FF_uses_GayBerne .and. FF_uses_LennardJones) then
583    endif
584
423      if (.not. haveNeighborList) then
424         !! Create neighbor lists
425         call expandNeighborList(nLocal, my_status)
# Line 645 | Line 483 | contains
483      integer :: localError
484      integer :: propPack_i, propPack_j
485      integer :: loopStart, loopEnd, loop
486 <    integer :: iMap
486 >    integer :: iHash
487      real(kind=dp) :: listSkin = 1.0  
488  
489      !! initialize local variables  
# Line 737 | Line 575 | contains
575   #endif
576         outer: do i = istart, iend
577  
578 + #ifdef IS_MPI
579 +             me_i = atid_row(i)
580 + #else
581 +             me_i = atid(i)
582 + #endif
583 +
584            if (update_nlist) point(i) = nlist + 1
585  
586            n_in_i = groupStartRow(i+1) - groupStartRow(i)
587  
588            if (update_nlist) then
589   #ifdef IS_MPI
746             me_i = atid_row(i)
590               jstart = 1
591               jend = nGroupsInCol
592   #else
750             me_i = atid(i)
593               jstart = i+1
594               jend = nGroups
595   #endif
# Line 775 | Line 617 | contains
617                    q_group(:,j), d_grp, rgrpsq)
618   #endif
619  
620 <             if (rgrpsq < InteractionMap(me_i,me_j)%rListsq) then
620 >             if (rgrpsq < InteractionHash(me_i,me_j)%rListsq) then
621                  if (update_nlist) then
622                     nlist = nlist + 1
623  
# Line 993 | Line 835 | contains
835   #else
836               me_i = atid(i)
837   #endif
838 <             iMap = InteractionMap(me_i, me_j)%InteractionHash
838 >             iHash = InteractionHash(me_i,me_j)
839              
840 <             if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
840 >             if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then
841  
842                  mu_i = getDipoleMoment(me_i)
843  
# Line 1062 | Line 904 | contains
904      real ( kind = dp ) :: ebalance
905      integer :: me_i, me_j
906  
907 <    integer :: iMap
907 >    integer :: iHash
908  
909      r = sqrt(rijsq)
910      vpair = 0.0d0
# Line 1076 | Line 918 | contains
918      me_j = atid(j)
919   #endif
920  
921 <    iMap = InteractionMap(me_i, me_j)%InteractionHash
921 >    iHash = InteractionHash(me_i, me_j)
922  
923 <    if ( iand(iMap, LJ_PAIR).ne.0 ) then
923 >    if ( iand(iHash, LJ_PAIR).ne.0 ) then
924         call do_lj_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot)
925      endif
926  
927 <    if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
927 >    if ( iand(iHash, ELECTROSTATIC_PAIR).ne.0 ) then
928         call doElectrostaticPair(i, j, d, r, rijsq, sw, vpair, fpair, &
929              pot, eFrame, f, t, do_pot)
930  
# Line 1095 | Line 937 | contains
937  
938      endif
939  
940 <    if ( iand(iMap, STICKY_PAIR).ne.0 ) then
940 >    if ( iand(iHash, STICKY_PAIR).ne.0 ) then
941         call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
942              pot, A, f, t, do_pot)
943      endif
944  
945 <    if ( iand(iMap, STICKYPOWER_PAIR).ne.0 ) then
945 >    if ( iand(iHash, STICKYPOWER_PAIR).ne.0 ) then
946         call do_sticky_power_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
947              pot, A, f, t, do_pot)
948      endif
949  
950 <    if ( iand(iMap, GAYBERNE_PAIR).ne.0 ) then
950 >    if ( iand(iHash, GAYBERNE_PAIR).ne.0 ) then
951         call do_gb_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
952              pot, A, f, t, do_pot)
953      endif
954      
955 <    if ( iand(iMap, GAYBERNE_LJ).ne.0 ) then
955 >    if ( iand(iHash, GAYBERNE_LJ).ne.0 ) then
956   !      call do_gblj_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
957   !           pot, A, f, t, do_pot)
958      endif
959  
960 <    if ( iand(iMap, EAM_PAIR).ne.0 ) then      
960 >    if ( iand(iHash, EAM_PAIR).ne.0 ) then      
961         call do_eam_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, &
962              do_pot)
963      endif
964  
965 <    if ( iand(iMap, SHAPE_PAIR).ne.0 ) then      
965 >    if ( iand(iHash, SHAPE_PAIR).ne.0 ) then      
966         call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
967              pot, A, f, t, do_pot)
968      endif
969  
970 <    if ( iand(iMap, SHAPE_LJ).ne.0 ) then      
970 >    if ( iand(iHash, SHAPE_LJ).ne.0 ) then      
971         call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
972              pot, A, f, t, do_pot)
973      endif
# Line 1147 | Line 989 | contains
989      real ( kind = dp )                :: r, rc
990      real ( kind = dp ), intent(inout) :: d(3), dc(3)
991  
992 <    integer :: me_i, me_j, iMap
992 >    integer :: me_i, me_j, iHash
993  
994   #ifdef IS_MPI  
995      me_i = atid_row(i)
# Line 1157 | Line 999 | contains
999      me_j = atid(j)  
1000   #endif
1001  
1002 <    iMap = InteractionMap(me_i, me_j)%InteractionHash
1002 >    iHash = InteractionHash(me_i, me_j)
1003  
1004 <    if ( iand(iMap, EAM_PAIR).ne.0 ) then      
1004 >    if ( iand(iHash, EAM_PAIR).ne.0 ) then      
1005              call calc_EAM_prepair_rho(i, j, d, r, rijsq )
1006      endif
1007      
# Line 1356 | Line 1198 | contains
1198  
1199    function FF_UsesDirectionalAtoms() result(doesit)
1200      logical :: doesit
1201 <    doesit = FF_uses_DirectionalAtoms .or. FF_uses_Dipoles .or. &
1360 <         FF_uses_Quadrupoles .or. FF_uses_Sticky .or. &
1361 <         FF_uses_StickyPower .or. FF_uses_GayBerne .or. FF_uses_Shapes
1201 >    doesit = FF_uses_DirectionalAtoms
1202    end function FF_UsesDirectionalAtoms
1203  
1204    function FF_RequiresPrepairCalc() result(doesit)

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines