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 2231 by chrisfen, Wed May 18 18:31:40 2005 UTC vs.
Revision 2262 by chuckv, Sun Jul 3 20:53:43 2005 UTC

# Line 45 | Line 45
45  
46   !! @author Charles F. Vardeman II
47   !! @author Matthew Meineke
48 < !! @version $Id: doForces.F90,v 1.18 2005-05-18 18:31:40 chrisfen Exp $, $Date: 2005-05-18 18:31:40 $, $Name: not supported by cvs2svn $, $Revision: 1.18 $
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 $
49  
50  
51   module doForces
# Line 73 | Line 73 | module doForces
73  
74   #define __FORTRAN90
75   #include "UseTheForce/fSwitchingFunction.h"
76 + #include "UseTheForce/DarkSide/fInteractionMap.h"
77  
78    INTEGER, PARAMETER:: PREPAIR_LOOP = 1
79    INTEGER, PARAMETER:: PAIR_LOOP    = 2
# Line 80 | Line 81 | module doForces
81    logical, save :: haveRlist = .false.
82    logical, save :: haveNeighborList = .false.
83    logical, save :: haveSIMvariables = .false.
83  logical, save :: havePropertyMap = .false.
84    logical, save :: haveSaneForceField = .false.
85 +  logical, save :: haveInteractionMap = .false.
86  
87    logical, save :: FF_uses_DirectionalAtoms
88    logical, save :: FF_uses_LennardJones
# Line 115 | Line 116 | module doForces
116    logical, save :: SIM_uses_PBC
117    logical, save :: SIM_uses_molecular_cutoffs
118  
119 <  real(kind=dp), save :: rlist, rlistsq
119 >  !!!GO AWAY---------
120 >  !!!!!real(kind=dp), save :: rlist, rlistsq
121  
122    public :: init_FF
123    public :: do_force_loop
124 <  public :: setRlistDF
124 > !  public :: setRlistDF
125 >  !public :: addInteraction
126 >  !public :: setInteractionHash
127 >  !public :: getInteractionHash
128 >  public :: createInteractionMap
129 >  public :: createRcuts
130  
131   #ifdef PROFILE
132    public :: getforcetime
# Line 128 | Line 135 | module doForces
135    integer :: nLoops
136   #endif
137  
138 <  type :: Properties
139 <     logical :: is_Directional   = .false.
140 <     logical :: is_LennardJones  = .false.
141 <     logical :: is_Electrostatic = .false.
142 <     logical :: is_Charge        = .false.
143 <     logical :: is_Dipole        = .false.
144 <     logical :: is_Quadrupole    = .false.
145 <     logical :: is_Sticky        = .false.
139 <     logical :: is_StickyPower   = .false.
140 <     logical :: is_GayBerne      = .false.
141 <     logical :: is_EAM           = .false.
142 <     logical :: is_Shape         = .false.
143 <     logical :: is_FLARB         = .false.
144 <  end type Properties
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
143 >  
144 >  type(Interaction), dimension(:,:),allocatable :: InteractionMap
145 >  
146  
147 <  type(Properties), dimension(:),allocatable :: PropertyMap
147 <
147 >  
148   contains
149  
150 <  subroutine setRlistDF( this_rlist )
151 <
152 <    real(kind=dp) :: this_rlist
153 <
154 <    rlist = this_rlist
155 <    rlistsq = rlist * rlist
156 <
157 <    haveRlist = .true.
158 <
159 <  end subroutine setRlistDF
160 <
161 <  subroutine createPropertyMap(status)
150 >
151 >  subroutine createInteractionMap(status)
152      integer :: nAtypes
153      integer :: status
154      integer :: i
155 <    logical :: thisProperty
156 <    real (kind=DP) :: thisDPproperty
157 <
158 <    status = 0
159 <
155 >    integer :: j
156 >    integer :: ihash
157 >    real(kind=dp) :: myRcut
158 > ! Test Types
159 >    logical :: i_is_LJ
160 >    logical :: i_is_Elect
161 >    logical :: i_is_Sticky
162 >    logical :: i_is_StickyP
163 >    logical :: i_is_GB
164 >    logical :: i_is_EAM
165 >    logical :: i_is_Shape
166 >    logical :: j_is_LJ
167 >    logical :: j_is_Elect
168 >    logical :: j_is_Sticky
169 >    logical :: j_is_StickyP
170 >    logical :: j_is_GB
171 >    logical :: j_is_EAM
172 >    logical :: j_is_Shape
173 >    
174 >    
175 >    if (.not. associated(atypes)) then
176 >       call handleError("atype", "atypes was not present before call of createDefaultInteractionMap!")
177 >       status = -1
178 >       return
179 >    endif
180 >    
181      nAtypes = getSize(atypes)
182 <
182 >    
183      if (nAtypes == 0) then
184         status = -1
185         return
186      end if
187  
188 <    if (.not. allocated(PropertyMap)) then
189 <       allocate(PropertyMap(nAtypes))
188 >    if (.not. allocated(InteractionMap)) then
189 >       allocate(InteractionMap(nAtypes,nAtypes))
190      endif
191 <
191 >        
192      do i = 1, nAtypes
193 <       call getElementProperty(atypes, i, "is_Directional", thisProperty)
194 <       PropertyMap(i)%is_Directional = thisProperty
193 >       call getElementProperty(atypes, i, "is_LennardJones", i_is_LJ)
194 >       call getElementProperty(atypes, i, "is_Electrostatic", i_is_Elect)
195 >       call getElementProperty(atypes, i, "is_Sticky", i_is_Sticky)
196 >       call getElementProperty(atypes, i, "is_StickyPower", i_is_StickyP)
197 >       call getElementProperty(atypes, i, "is_GayBerne", i_is_GB)
198 >       call getElementProperty(atypes, i, "is_EAM", i_is_EAM)
199 >       call getElementProperty(atypes, i, "is_Shape", i_is_Shape)
200  
201 <       call getElementProperty(atypes, i, "is_LennardJones", thisProperty)
186 <       PropertyMap(i)%is_LennardJones = thisProperty
201 >       do j = i, nAtypes
202  
203 <       call getElementProperty(atypes, i, "is_Electrostatic", thisProperty)
204 <       PropertyMap(i)%is_Electrostatic = thisProperty
203 >          iHash = 0
204 >          myRcut = 0.0_dp
205  
206 <       call getElementProperty(atypes, i, "is_Charge", thisProperty)
207 <       PropertyMap(i)%is_Charge = thisProperty
206 >          call getElementProperty(atypes, j, "is_LennardJones", j_is_LJ)
207 >          call getElementProperty(atypes, j, "is_Electrostatic", j_is_Elect)
208 >          call getElementProperty(atypes, j, "is_Sticky", j_is_Sticky)
209 >          call getElementProperty(atypes, j, "is_StickyPower", j_is_StickyP)
210 >          call getElementProperty(atypes, j, "is_GayBerne", j_is_GB)
211 >          call getElementProperty(atypes, j, "is_EAM", j_is_EAM)
212 >          call getElementProperty(atypes, j, "is_Shape", j_is_Shape)
213  
214 <       call getElementProperty(atypes, i, "is_Dipole", thisProperty)
215 <       PropertyMap(i)%is_Dipole = thisProperty
214 >          if (i_is_LJ .and. j_is_LJ) then
215 >             iHash = ior(iHash, LJ_PAIR)            
216 >          endif
217 >          
218 >          if (i_is_Elect .and. j_is_Elect) then
219 >             iHash = ior(iHash, ELECTROSTATIC_PAIR)
220 >          endif
221 >          
222 >          if (i_is_Sticky .and. j_is_Sticky) then
223 >             iHash = ior(iHash, STICKY_PAIR)
224 >          endif
225  
226 <       call getElementProperty(atypes, i, "is_Quadrupole", thisProperty)
227 <       PropertyMap(i)%is_Quadrupole = thisProperty
226 >          if (i_is_StickyP .and. j_is_StickyP) then
227 >             iHash = ior(iHash, STICKYPOWER_PAIR)
228 >          endif
229  
230 <       call getElementProperty(atypes, i, "is_Sticky", thisProperty)
231 <       PropertyMap(i)%is_Sticky = thisProperty
232 <      
203 <       call getElementProperty(atypes, i, "is_StickyPower", thisProperty)
204 <       PropertyMap(i)%is_StickyPower = thisProperty
230 >          if (i_is_EAM .and. j_is_EAM) then
231 >             iHash = ior(iHash, EAM_PAIR)
232 >          endif
233  
234 <       call getElementProperty(atypes, i, "is_GayBerne", thisProperty)
235 <       PropertyMap(i)%is_GayBerne = thisProperty
234 >          if (i_is_GB .and. j_is_GB) iHash = ior(iHash, GAYBERNE_PAIR)
235 >          if (i_is_GB .and. j_is_LJ) iHash = ior(iHash, GAYBERNE_LJ)
236 >          if (i_is_LJ .and. j_is_GB) iHash = ior(iHash, GAYBERNE_LJ)
237  
238 <       call getElementProperty(atypes, i, "is_EAM", thisProperty)
239 <       PropertyMap(i)%is_EAM = thisProperty
238 >          if (i_is_Shape .and. j_is_Shape) iHash = ior(iHash, SHAPE_PAIR)
239 >          if (i_is_Shape .and. j_is_LJ) iHash = ior(iHash, SHAPE_LJ)
240 >          if (i_is_LJ .and. j_is_Shape) iHash = ior(iHash, SHAPE_LJ)
241  
212       call getElementProperty(atypes, i, "is_Shape", thisProperty)
213       PropertyMap(i)%is_Shape = thisProperty
242  
243 <       call getElementProperty(atypes, i, "is_FLARB", thisProperty)
244 <       PropertyMap(i)%is_FLARB = thisProperty
243 >          InteractionMap(i,j)%InteractionHash = iHash
244 >          InteractionMap(j,i)%InteractionHash = iHash
245 >
246 >       end do
247 >
248      end do
249 +  end subroutine createInteractionMap
250  
251 <    havePropertyMap = .true.
251 > ! 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.
252 >  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
259  
260 <  end subroutine createPropertyMap
260 >    if(.not. allocated(InteractionMap)) return
261  
262 +    nAtypes = getSize(atypes)
263 + ! If we pass a default rcut, set all atypes to that cutoff distance
264 +    if(present(defaultRList)) then
265 +       InteractionMap(:,:)%rList = defaultRList
266 +       InteractionMap(:,:)%rListSq = defaultRList*defaultRList
267 +       haveRlist = .true.
268 +       return
269 +    end if
270 +
271 +    do map_i = 1,nAtypes
272 +       do map_j = map_i,nAtypes
273 +          iMap = InteractionMap(map_i, map_j)%InteractionHash
274 +          
275 +          if ( iand(iMap, LJ_PAIR).ne.0 ) then
276 + !            thisRCut = getLJCutOff(map_i,map_j)
277 +             if (thisRcut > actualCutoff) actualCutoff = thisRcut
278 +          endif
279 +          
280 +          if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
281 + !            thisRCut = getElectrostaticCutOff(map_i,map_j)
282 +             if (thisRcut > actualCutoff) actualCutoff = thisRcut
283 +          endif
284 +          
285 +          if ( iand(iMap, STICKY_PAIR).ne.0 ) then
286 + !             thisRCut = getStickyCutOff(map_i,map_j)
287 +              if (thisRcut > actualCutoff) actualCutoff = thisRcut
288 +           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
325 +
326 +
327 + !!! THIS GOES AWAY FOR SIZE DEPENDENT CUTOFF
328 + !!$  subroutine setRlistDF( this_rlist )
329 + !!$
330 + !!$   real(kind=dp) :: this_rlist
331 + !!$
332 + !!$    rlist = this_rlist
333 + !!$    rlistsq = rlist * rlist
334 + !!$
335 + !!$    haveRlist = .true.
336 + !!$
337 + !!$  end subroutine setRlistDF
338 +
339 +
340    subroutine setSimVariables()
341      SIM_uses_DirectionalAtoms = SimUsesDirectionalAtoms()
342      SIM_uses_LennardJones = SimUsesLennardJones()
# Line 249 | Line 366 | contains
366  
367      error = 0
368  
369 <    if (.not. havePropertyMap) then
369 >    if (.not. haveInteractionMap) then
370  
371         myStatus = 0
372  
373 <       call createPropertyMap(myStatus)
373 >       call createInteractionMap(myStatus)
374  
375         if (myStatus .ne. 0) then
376 <          write(default_error, *) 'createPropertyMap failed in doForces!'
376 >          write(default_error, *) 'createInteractionMap failed in doForces!'
377            error = -1
378            return
379         endif
# Line 514 | Line 631 | contains
631      integer :: localError
632      integer :: propPack_i, propPack_j
633      integer :: loopStart, loopEnd, loop
634 <
634 >    integer :: iMap
635      real(kind=dp) :: listSkin = 1.0  
636  
637      !! initialize local variables  
# Line 640 | Line 757 | contains
757                    q_group(:,j), d_grp, rgrpsq)
758   #endif
759  
760 <             if (rgrpsq < rlistsq) then
760 >             if (rgrpsq < InteractionMap(me_i,me_j)%rListsq) then
761                  if (update_nlist) then
762                     nlist = nlist + 1
763  
# Line 858 | Line 975 | contains
975   #else
976               me_i = atid(i)
977   #endif
978 <
979 <             if (PropertyMap(me_i)%is_Dipole) then
978 >             iMap = InteractionMap(me_i, me_j)%InteractionHash
979 >            
980 >             if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
981  
982                  mu_i = getDipoleMoment(me_i)
983  
# Line 926 | Line 1044 | contains
1044      real ( kind = dp ) :: ebalance
1045      integer :: me_i, me_j
1046  
1047 +    integer :: iMap
1048 +
1049      r = sqrt(rijsq)
1050      vpair = 0.0d0
1051      fpair(1:3) = 0.0d0
# Line 938 | Line 1058 | contains
1058      me_j = atid(j)
1059   #endif
1060  
1061 <    !    write(*,*) i, j, me_i, me_j
1061 >    iMap = InteractionMap(me_i, me_j)%InteractionHash
1062  
1063 <    if (FF_uses_LennardJones .and. SIM_uses_LennardJones) then
1064 <
945 <       if ( PropertyMap(me_i)%is_LennardJones .and. &
946 <            PropertyMap(me_j)%is_LennardJones ) then
947 <          call do_lj_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot)
948 <       endif
949 <
1063 >    if ( iand(iMap, LJ_PAIR).ne.0 ) then
1064 >       call do_lj_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot)
1065      endif
1066  
1067 <    if (FF_uses_Electrostatics .and. SIM_uses_Electrostatics) then
1067 >    if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
1068 >       call doElectrostaticPair(i, j, d, r, rijsq, sw, vpair, fpair, &
1069 >            pot, eFrame, f, t, do_pot)
1070  
1071 <       if (PropertyMap(me_i)%is_Electrostatic .and. &
955 <            PropertyMap(me_j)%is_Electrostatic) then
956 <          call doElectrostaticPair(i, j, d, r, rijsq, sw, vpair, fpair, &
957 <               pot, eFrame, f, t, do_pot, ebalance)
958 <       endif
1071 >       if (FF_uses_RF .and. SIM_uses_RF) then
1072  
1073 <       if (FF_uses_dipoles .and. SIM_uses_dipoles) then      
1074 <          if ( PropertyMap(me_i)%is_Dipole .and. &
1075 <               PropertyMap(me_j)%is_Dipole) then
963 <             if (FF_uses_RF .and. SIM_uses_RF) then
964 <                call accumulate_rf(i, j, r, eFrame, sw)
965 <                call rf_correct_forces(i, j, d, r, eFrame, sw, f, fpair)
966 <             endif
967 <          endif
1073 >          ! CHECK ME (RF needs to know about all electrostatic types)
1074 >          call accumulate_rf(i, j, r, eFrame, sw)
1075 >          call rf_correct_forces(i, j, d, r, eFrame, sw, f, fpair)
1076         endif
1077 +
1078      endif
1079  
1080 +    if ( iand(iMap, STICKY_PAIR).ne.0 ) then
1081 +       call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1082 +            pot, A, f, t, do_pot)
1083 +    endif
1084  
1085 <    if (FF_uses_Sticky .and. SIM_uses_sticky) then
1086 <
1087 <       if ( PropertyMap(me_i)%is_Sticky .and. PropertyMap(me_j)%is_Sticky) then
975 <          call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
976 <               pot, A, f, t, do_pot)
977 <       endif
978 <
1085 >    if ( iand(iMap, STICKYPOWER_PAIR).ne.0 ) then
1086 >       call do_sticky_power_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1087 >            pot, A, f, t, do_pot)
1088      endif
1089  
1090 <    if (FF_uses_StickyPower .and. SIM_uses_stickypower) then
1091 <       if ( PropertyMap(me_i)%is_StickyPower .and. &
1092 <            PropertyMap(me_j)%is_StickyPower) then
984 <          call do_sticky_power_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
985 <               pot, A, f, t, do_pot, ebalance)
986 <       endif
1090 >    if ( iand(iMap, GAYBERNE_PAIR).ne.0 ) then
1091 >       call do_gb_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1092 >            pot, A, f, t, do_pot)
1093      endif
1094      
1095 <    if (FF_uses_GayBerne .and. SIM_uses_GayBerne) then
1095 >    if ( iand(iMap, GAYBERNE_LJ).ne.0 ) then
1096 > !      call do_gblj_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1097 > !           pot, A, f, t, do_pot)
1098 >    endif
1099  
1100 <       if ( PropertyMap(me_i)%is_GayBerne .and. &
1101 <            PropertyMap(me_j)%is_GayBerne) then
1102 <          call do_gb_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
994 <               pot, A, f, t, do_pot)
995 <       endif
996 <
1100 >    if ( iand(iMap, EAM_PAIR).ne.0 ) then      
1101 >       call do_eam_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, &
1102 >            do_pot)
1103      endif
1104  
1105 <    if (FF_uses_EAM .and. SIM_uses_EAM) then
1106 <
1107 <       if ( PropertyMap(me_i)%is_EAM .and. PropertyMap(me_j)%is_EAM) then
1002 <          call do_eam_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, &
1003 <               do_pot)
1004 <       endif
1005 <
1105 >    if ( iand(iMap, SHAPE_PAIR).ne.0 ) then      
1106 >       call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1107 >            pot, A, f, t, do_pot)
1108      endif
1109  
1110 <
1111 <    !    write(*,*) PropertyMap(me_i)%is_Shape,PropertyMap(me_j)%is_Shape
1112 <
1011 <    if (FF_uses_Shapes .and. SIM_uses_Shapes) then
1012 <       if ( PropertyMap(me_i)%is_Shape .and. &
1013 <            PropertyMap(me_j)%is_Shape ) then
1014 <          call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1015 <               pot, A, f, t, do_pot)
1016 <       endif
1017 <       if ( (PropertyMap(me_i)%is_Shape .and. &
1018 <            PropertyMap(me_j)%is_LennardJones) .or. &
1019 <            (PropertyMap(me_i)%is_LennardJones .and. &
1020 <            PropertyMap(me_j)%is_Shape) ) then
1021 <          call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1022 <               pot, A, f, t, do_pot)
1023 <       endif
1110 >    if ( iand(iMap, SHAPE_LJ).ne.0 ) then      
1111 >       call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
1112 >            pot, A, f, t, do_pot)
1113      endif
1114 <
1114 >    
1115    end subroutine do_pair
1116  
1117    subroutine do_prepair(i, j, rijsq, d, sw, rcijsq, dc, &
# Line 1039 | Line 1128 | contains
1128      real ( kind = dp ), intent(inout)    :: rijsq, rcijsq
1129      real ( kind = dp )                :: r, rc
1130      real ( kind = dp ), intent(inout) :: d(3), dc(3)
1042
1043    logical :: is_EAM_i, is_EAM_j
1044
1045    integer :: me_i, me_j
1046
1131  
1132 <    r = sqrt(rijsq)
1049 <    if (SIM_uses_molecular_cutoffs) then
1050 <       rc = sqrt(rcijsq)
1051 <    else
1052 <       rc = r
1053 <    endif
1132 >    integer :: me_i, me_j, iMap
1133  
1055
1134   #ifdef IS_MPI  
1135      me_i = atid_row(i)
1136      me_j = atid_col(j)  
# Line 1061 | Line 1139 | contains
1139      me_j = atid(j)  
1140   #endif
1141  
1142 <    if (FF_uses_EAM .and. SIM_uses_EAM) then
1142 >    iMap = InteractionMap(me_i, me_j)%InteractionHash
1143  
1144 <       if (PropertyMap(me_i)%is_EAM .and. PropertyMap(me_j)%is_EAM) &
1144 >    if ( iand(iMap, EAM_PAIR).ne.0 ) then      
1145              call calc_EAM_prepair_rho(i, j, d, r, rijsq )
1068
1146      endif
1147 <
1147 >    
1148    end subroutine do_prepair
1149  
1150  

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines