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 2259 by gezelter, Mon Jun 27 21:01:36 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.20 2005-06-27 21:01:30 gezelter Exp $, $Date: 2005-06-27 21:01:30 $, $Name: not supported by cvs2svn $, $Revision: 1.20 $
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 81 | Line 81 | module doForces
81    logical, save :: haveRlist = .false.
82    logical, save :: haveNeighborList = .false.
83    logical, save :: haveSIMvariables = .false.
84  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 116 | 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 129 | 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.
140 <     logical :: is_StickyPower   = .false.
141 <     logical :: is_GayBerne      = .false.
142 <     logical :: is_EAM           = .false.
143 <     logical :: is_Shape         = .false.
144 <     logical :: is_FLARB         = .false.
145 <  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
148 <
147 >  
148   contains
149  
150 <  subroutine setRlistDF( this_rlist )
151 <
153 <    real(kind=dp) :: this_rlist
154 <
155 <    rlist = this_rlist
156 <    rlistsq = rlist * rlist
157 <
158 <    haveRlist = .true.
159 <
160 <  end subroutine setRlistDF
161 <
162 <  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)
187 <       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 <      
204 <       call getElementProperty(atypes, i, "is_StickyPower", thisProperty)
205 <       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  
213       call getElementProperty(atypes, i, "is_Shape", thisProperty)
214       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()
# Line 250 | 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 515 | 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 641 | 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 859 | 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 951 | Line 1068 | contains
1068         call doElectrostaticPair(i, j, d, r, rijsq, sw, vpair, fpair, &
1069              pot, eFrame, f, t, do_pot)
1070  
1071 <       if (FF_uses_dipoles .and. SIM_uses_dipoles) then                
1072 <          if ( PropertyMap(me_i)%is_Dipole .and. &
1073 <               PropertyMap(me_j)%is_Dipole) then
1074 <             if (FF_uses_RF .and. SIM_uses_RF) then
1075 <                call accumulate_rf(i, j, r, eFrame, sw)
959 <                call rf_correct_forces(i, j, d, r, eFrame, sw, f, fpair)
960 <             endif
961 <          endif
1071 >       if (FF_uses_RF .and. SIM_uses_RF) then
1072 >
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
# Line 978 | Line 1093 | contains
1093      endif
1094      
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)
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 ( iand(iMap, EAM_PAIR).ne.0 ) then      

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines