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 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.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.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
157 <    real(kind=dp) :: myRcut
133 >    integer :: iHash
134      !! Test Types
135      logical :: i_is_LJ
136      logical :: i_is_Elect
# 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
237  
238 <    haveInteractionMap = .true.
239 <  end subroutine createInteractionMap
238 >    haveInteractionHash = .true.
239 >  end subroutine createInteractionHash
240  
241 < ! 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.
242 <  subroutine createRcuts(defaultRList,stat)
243 <    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
241 >  subroutine createGtypeCutoffMap(defaultRcut, defaultSkinThickness, stat)
242 >
243 >    real(kind=dp), intent(in), optional :: defaultRCut, defaultSkinThickness
244      integer, intent(out) :: stat
262    integer :: nAtypes
263    integer :: myStatus
245  
246 <    stat = 0
266 <    if (.not. haveInteractionMap) then
246 >    integer :: myStatus, nAtypes
247  
248 <       call createInteractionMap(myStatus)
249 <
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  
277
258      nAtypes = getSize(atypes)
279    !! If we pass a default rcut, set all atypes to that cutoff distance
280    if(present(defaultRList)) then
281       InteractionMap(:,:)%rList = defaultRList
282       InteractionMap(:,:)%rListSq = defaultRList*defaultRList
283       haveRlist = .true.
284       return
285    end if
259  
260 <    do map_i = 1,nAtypes
261 <       do map_j = map_i,nAtypes
262 <          iMap = InteractionMap(map_i, map_j)%InteractionHash
290 <          
291 <          if ( iand(iMap, LJ_PAIR).ne.0 ) then
292 <             ! thisRCut = getLJCutOff(map_i,map_j)
293 <             if (thisRcut > actualCutoff) actualCutoff = thisRcut
294 <          endif
295 <          
296 <          if ( iand(iMap, ELECTROSTATIC_PAIR).ne.0 ) then
297 <             ! thisRCut = getElectrostaticCutOff(map_i,map_j)
298 <             if (thisRcut > actualCutoff) actualCutoff = thisRcut
299 <          endif
300 <          
301 <          if ( iand(iMap, STICKY_PAIR).ne.0 ) then
302 <             ! thisRCut = getStickyCutOff(map_i,map_j)
303 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
304 <           endif
305 <          
306 <           if ( iand(iMap, STICKYPOWER_PAIR).ne.0 ) then
307 <              ! thisRCut = getStickyPowerCutOff(map_i,map_j)
308 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
309 <           endif
310 <          
311 <           if ( iand(iMap, GAYBERNE_PAIR).ne.0 ) then
312 <              ! thisRCut = getGayberneCutOff(map_i,map_j)
313 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
314 <           endif
315 <          
316 <           if ( iand(iMap, GAYBERNE_LJ).ne.0 ) then
317 < !              thisRCut = getGaybrneLJCutOff(map_i,map_j)
318 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
319 <           endif
320 <          
321 <           if ( iand(iMap, EAM_PAIR).ne.0 ) then      
322 < !              thisRCut = getEAMCutOff(map_i,map_j)
323 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
324 <           endif
325 <          
326 <           if ( iand(iMap, SHAPE_PAIR).ne.0 ) then      
327 < !              thisRCut = getShapeCutOff(map_i,map_j)
328 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
329 <           endif
330 <          
331 <           if ( iand(iMap, SHAPE_LJ).ne.0 ) then      
332 < !              thisRCut = getShapeLJCutOff(map_i,map_j)
333 <              if (thisRcut > actualCutoff) actualCutoff = thisRcut
334 <           endif
335 <           InteractionMap(map_i, map_j)%rList = actualCutoff
336 <           InteractionMap(map_i, map_j)%rListSq = actualCutoff * actualCutoff
337 <        end do
338 <     end do
339 <     haveRlist = .true.
340 <  end subroutine createRcuts
260 >    do i = 1, nAtypes
261 >      
262 >       atypeMaxCutoff(i) =
263  
264 +    
265  
343 !!! THIS GOES AWAY FOR SIZE DEPENDENT CUTOFF
344 !!$  subroutine setRlistDF( this_rlist )
345 !!$
346 !!$   real(kind=dp) :: this_rlist
347 !!$
348 !!$    rlist = this_rlist
349 !!$    rlistsq = rlist * rlist
350 !!$
351 !!$    haveRlist = .true.
352 !!$
353 !!$  end subroutine setRlistDF
266  
267  
268 +     haveGtypeCutoffMap = .true.
269 +   end subroutine createGtypeCutoffMap
270 +
271    subroutine setSimVariables()
272      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()
273      SIM_uses_EAM = SimUsesEAM()
366    SIM_uses_Shapes = SimUsesShapes()
367    SIM_uses_FLARB = SimUsesFLARB()
274      SIM_uses_RF = SimUsesRF()
275      SIM_requires_postpair_calc = SimRequiresPostpairCalc()
276      SIM_requires_prepair_calc = SimRequiresPrepairCalc()
# Line 382 | 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)
390 <
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 450 | Line 363 | contains
363      !! interactions are used by the force field.    
364  
365      FF_uses_DirectionalAtoms = .false.
453    FF_uses_LennardJones = .false.
454    FF_uses_Electrostatics = .false.
455    FF_uses_Charges = .false.    
366      FF_uses_Dipoles = .false.
457    FF_uses_Sticky = .false.
458    FF_uses_StickyPower = .false.
367      FF_uses_GayBerne = .false.
368      FF_uses_EAM = .false.
461    FF_uses_Shapes = .false.
462    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  
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
374      call getMatchingElementList(atypes, "is_Dipole", .true., &
375           nMatches, MatchList)
376 <    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
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
518 <       FF_uses_GayBerne = .true.
519 <       FF_uses_DirectionalAtoms = .true.
520 <    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  
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
385  
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)
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 552 | Line 401 | contains
401         endif
402      endif
403  
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
404      if (FF_uses_EAM) then
405         call init_EAM_FF(my_status)
406         if (my_status /= 0) then
# Line 581 | Line 420 | contains
420         endif
421      endif
422  
584    if (FF_uses_GayBerne .and. FF_uses_LennardJones) then
585    endif
586
423      if (.not. haveNeighborList) then
424         !! Create neighbor lists
425         call expandNeighborList(nLocal, my_status)
# Line 647 | 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 781 | 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 999 | 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 1068 | 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 1082 | 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 1101 | 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 1153 | 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 1163 | 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 1362 | Line 1198 | contains
1198  
1199    function FF_UsesDirectionalAtoms() result(doesit)
1200      logical :: doesit
1201 <    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
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