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 1610 by gezelter, Wed Oct 20 04:19:55 2004 UTC vs.
Revision 1930 by gezelter, Wed Jan 12 22:41:40 2005 UTC

# Line 1 | Line 1
1 + !!
2 + !! Copyright (c) 2005 The University of Notre Dame. All Rights Reserved.
3 + !!
4 + !! The University of Notre Dame grants you ("Licensee") a
5 + !! non-exclusive, royalty free, license to use, modify and
6 + !! redistribute this software in source and binary code form, provided
7 + !! that the following conditions are met:
8 + !!
9 + !! 1. Acknowledgement of the program authors must be made in any
10 + !!    publication of scientific results based in part on use of the
11 + !!    program.  An acceptable form of acknowledgement is citation of
12 + !!    the article in which the program was described (Matthew
13 + !!    A. Meineke, Charles F. Vardeman II, Teng Lin, Christopher
14 + !!    J. Fennell and J. Daniel Gezelter, "OOPSE: An Object-Oriented
15 + !!    Parallel Simulation Engine for Molecular Dynamics,"
16 + !!    J. Comput. Chem. 26, pp. 252-271 (2005))
17 + !!
18 + !! 2. Redistributions of source code must retain the above copyright
19 + !!    notice, this list of conditions and the following disclaimer.
20 + !!
21 + !! 3. Redistributions in binary form must reproduce the above copyright
22 + !!    notice, this list of conditions and the following disclaimer in the
23 + !!    documentation and/or other materials provided with the
24 + !!    distribution.
25 + !!
26 + !! This software is provided "AS IS," without a warranty of any
27 + !! kind. All express or implied conditions, representations and
28 + !! warranties, including any implied warranty of merchantability,
29 + !! fitness for a particular purpose or non-infringement, are hereby
30 + !! excluded.  The University of Notre Dame and its licensors shall not
31 + !! be liable for any damages suffered by licensee as a result of
32 + !! using, modifying or distributing the software or its
33 + !! derivatives. In no event will the University of Notre Dame or its
34 + !! licensors be liable for any lost revenue, profit or data, or for
35 + !! direct, indirect, special, consequential, incidental or punitive
36 + !! damages, however caused and regardless of the theory of liability,
37 + !! arising out of the use of or inability to use software, even if the
38 + !! University of Notre Dame has been advised of the possibility of
39 + !! such damages.
40 + !!
41 +
42   !! doForces.F90
43   !! module doForces
44   !! Calculates Long Range forces.
45  
46   !! @author Charles F. Vardeman II
47   !! @author Matthew Meineke
48 < !! @version $Id: doForces.F90,v 1.1 2004-10-20 04:19:55 gezelter Exp $, $Date: 2004-10-20 04:19:55 $, $Name: not supported by cvs2svn $, $Revision: 1.1 $
48 > !! @version $Id: doForces.F90,v 1.9 2005-01-12 22:40:37 gezelter Exp $, $Date: 2005-01-12 22:40:37 $, $Name: not supported by cvs2svn $, $Revision: 1.9 $
49  
50 +
51   module doForces
52    use force_globals
53    use simulation
# Line 14 | Line 56 | module doForces
56    use switcheroo
57    use neighborLists  
58    use lj
59 <  use sticky_pair
59 >  use sticky
60    use dipole_dipole
61    use charge_charge
62    use reaction_field
63    use gb_pair
64 +  use shapes
65    use vector_class
66    use eam
67    use status
# Line 30 | Line 73 | module doForces
73    PRIVATE
74  
75   #define __FORTRAN90
33 #include "UseTheForce/fForceField.h"
76   #include "UseTheForce/fSwitchingFunction.h"
77  
78    INTEGER, PARAMETER:: PREPAIR_LOOP = 1
# Line 38 | Line 80 | module doForces
80  
81    logical, save :: haveRlist = .false.
82    logical, save :: haveNeighborList = .false.
41  logical, save :: havePolicies = .false.
83    logical, save :: haveSIMvariables = .false.
84    logical, save :: havePropertyMap = .false.
85    logical, save :: haveSaneForceField = .false.
86 <  logical, save :: FF_uses_LJ
87 <  logical, save :: FF_uses_sticky
86 >  
87 >  logical, save :: FF_uses_DirectionalAtoms
88 >  logical, save :: FF_uses_LennardJones
89 >  logical, save :: FF_uses_Electrostatic
90    logical, save :: FF_uses_charges
91    logical, save :: FF_uses_dipoles
92 <  logical, save :: FF_uses_RF
93 <  logical, save :: FF_uses_GB
92 >  logical, save :: FF_uses_sticky
93 >  logical, save :: FF_uses_GayBerne
94    logical, save :: FF_uses_EAM
95 <  logical, save :: SIM_uses_LJ
96 <  logical, save :: SIM_uses_sticky
97 <  logical, save :: SIM_uses_charges
98 <  logical, save :: SIM_uses_dipoles
99 <  logical, save :: SIM_uses_RF
100 <  logical, save :: SIM_uses_GB
95 >  logical, save :: FF_uses_Shapes
96 >  logical, save :: FF_uses_FLARB
97 >  logical, save :: FF_uses_RF
98 >
99 >  logical, save :: SIM_uses_DirectionalAtoms
100 >  logical, save :: SIM_uses_LennardJones
101 >  logical, save :: SIM_uses_Electrostatics
102 >  logical, save :: SIM_uses_Charges
103 >  logical, save :: SIM_uses_Dipoles
104 >  logical, save :: SIM_uses_Sticky
105 >  logical, save :: SIM_uses_GayBerne
106    logical, save :: SIM_uses_EAM
107 +  logical, save :: SIM_uses_Shapes
108 +  logical, save :: SIM_uses_FLARB
109 +  logical, save :: SIM_uses_RF
110    logical, save :: SIM_requires_postpair_calc
111    logical, save :: SIM_requires_prepair_calc
61  logical, save :: SIM_uses_directional_atoms
112    logical, save :: SIM_uses_PBC
113    logical, save :: SIM_uses_molecular_cutoffs
114  
# Line 76 | Line 126 | module doForces
126   #endif
127  
128    type :: Properties
129 <     logical :: is_lj     = .false.
130 <     logical :: is_sticky = .false.
131 <     logical :: is_dp     = .false.
132 <     logical :: is_gb     = .false.
133 <     logical :: is_eam    = .false.
134 <     logical :: is_charge = .false.
135 <     real(kind=DP) :: charge = 0.0_DP
136 <     real(kind=DP) :: dipole_moment = 0.0_DP
129 >     logical :: is_Directional   = .false.
130 >     logical :: is_LennardJones  = .false.
131 >     logical :: is_Electrostatic = .false.
132 >     logical :: is_Charge        = .false.
133 >     logical :: is_Dipole        = .false.
134 >     logical :: is_Sticky        = .false.
135 >     logical :: is_GayBerne      = .false.
136 >     logical :: is_EAM           = .false.
137 >     logical :: is_Shape         = .false.
138 >     logical :: is_FLARB         = .false.
139    end type Properties
140  
141    type(Properties), dimension(:),allocatable :: PropertyMap
# Line 122 | Line 174 | contains
174      endif
175  
176      do i = 1, nAtypes
177 <       call getElementProperty(atypes, i, "is_LJ", thisProperty)
178 <       PropertyMap(i)%is_LJ = thisProperty
177 >       call getElementProperty(atypes, i, "is_Directional", thisProperty)
178 >       PropertyMap(i)%is_Directional = thisProperty
179  
180 +       call getElementProperty(atypes, i, "is_LennardJones", thisProperty)
181 +       PropertyMap(i)%is_LennardJones = thisProperty
182 +      
183 +       call getElementProperty(atypes, i, "is_Electrostatic", thisProperty)
184 +       PropertyMap(i)%is_Electrostatic = thisProperty
185 +
186         call getElementProperty(atypes, i, "is_Charge", thisProperty)
187         PropertyMap(i)%is_Charge = thisProperty
188        
189 <       if (thisProperty) then
190 <          call getElementProperty(atypes, i, "charge", thisDPproperty)
133 <          PropertyMap(i)%charge = thisDPproperty
134 <       endif
189 >       call getElementProperty(atypes, i, "is_Dipole", thisProperty)
190 >       PropertyMap(i)%is_Dipole = thisProperty
191  
136       call getElementProperty(atypes, i, "is_DP", thisProperty)
137       PropertyMap(i)%is_DP = thisProperty
138
139       if (thisProperty) then
140          call getElementProperty(atypes, i, "dipole_moment", thisDPproperty)
141          PropertyMap(i)%dipole_moment = thisDPproperty
142       endif
143
192         call getElementProperty(atypes, i, "is_Sticky", thisProperty)
193         PropertyMap(i)%is_Sticky = thisProperty
194 <       call getElementProperty(atypes, i, "is_GB", thisProperty)
195 <       PropertyMap(i)%is_GB = thisProperty
194 >
195 >       call getElementProperty(atypes, i, "is_GayBerne", thisProperty)
196 >       PropertyMap(i)%is_GayBerne = thisProperty
197 >
198         call getElementProperty(atypes, i, "is_EAM", thisProperty)
199         PropertyMap(i)%is_EAM = thisProperty
200 +
201 +       call getElementProperty(atypes, i, "is_Shape", thisProperty)
202 +       PropertyMap(i)%is_Shape = thisProperty
203 +
204 +       call getElementProperty(atypes, i, "is_FLARB", thisProperty)
205 +       PropertyMap(i)%is_FLARB = thisProperty
206      end do
207  
208      havePropertyMap = .true.
# Line 154 | Line 210 | contains
210    end subroutine createPropertyMap
211  
212    subroutine setSimVariables()
213 <    SIM_uses_LJ = SimUsesLJ()
214 <    SIM_uses_sticky = SimUsesSticky()
215 <    SIM_uses_charges = SimUsesCharges()
216 <    SIM_uses_dipoles = SimUsesDipoles()
217 <    SIM_uses_RF = SimUsesRF()
218 <    SIM_uses_GB = SimUsesGB()
213 >    SIM_uses_DirectionalAtoms = SimUsesDirectionalAtoms()
214 >    SIM_uses_LennardJones = SimUsesLennardJones()
215 >    SIM_uses_Electrostatics = SimUsesElectrostatics()
216 >    SIM_uses_Charges = SimUsesCharges()
217 >    SIM_uses_Dipoles = SimUsesDipoles()
218 >    SIM_uses_Sticky = SimUsesSticky()
219 >    SIM_uses_GayBerne = SimUsesGayBerne()
220      SIM_uses_EAM = SimUsesEAM()
221 +    SIM_uses_Shapes = SimUsesShapes()
222 +    SIM_uses_FLARB = SimUsesFLARB()
223 +    SIM_uses_RF = SimUsesRF()
224      SIM_requires_postpair_calc = SimRequiresPostpairCalc()
225      SIM_requires_prepair_calc = SimRequiresPrepairCalc()
166    SIM_uses_directional_atoms = SimUsesDirectionalAtoms()
226      SIM_uses_PBC = SimUsesPBC()
168    !SIM_uses_molecular_cutoffs = SimUsesMolecularCutoffs()
227  
228      haveSIMvariables = .true.
229  
# Line 202 | Line 260 | contains
260         return
261      endif
262  
205    if (SIM_uses_LJ .and. FF_uses_LJ) then
206       if (.not. havePolicies) then
207          write(default_error, *) 'LJ mixing Policies have not been set in doForces!'
208          error = -1
209          return
210       endif
211    endif
212
263      if (.not. haveNeighborList) then
264         write(default_error, *) 'neighbor list has not been initialized in doForces!'
265         error = -1
# Line 233 | Line 283 | contains
283    end subroutine doReadyCheck
284      
285  
286 <  subroutine init_FF(LJMIXPOLICY, use_RF_c, thisStat)
286 >  subroutine init_FF(use_RF_c, thisStat)
287  
238    integer, intent(in) :: LJMIXPOLICY
288      logical, intent(in) :: use_RF_c
289  
290      integer, intent(out) :: thisStat  
# Line 255 | Line 304 | contains
304      !! this will scan through the known atypes and figure out what
305      !! interactions are used by the force field.    
306    
307 <    FF_uses_LJ = .false.
308 <    FF_uses_sticky = .false.
309 <    FF_uses_charges = .false.
310 <    FF_uses_dipoles = .false.
311 <    FF_uses_GB = .false.
307 >    FF_uses_DirectionalAtoms = .false.
308 >    FF_uses_LennardJones = .false.
309 >    FF_uses_Electrostatic = .false.
310 >    FF_uses_Charges = .false.    
311 >    FF_uses_Dipoles = .false.
312 >    FF_uses_Sticky = .false.
313 >    FF_uses_GayBerne = .false.
314      FF_uses_EAM = .false.
315 +    FF_uses_Shapes = .false.
316 +    FF_uses_FLARB = .false.
317      
318 <    call getMatchingElementList(atypes, "is_LJ", .true., nMatches, MatchList)
319 <    if (nMatches .gt. 0) FF_uses_LJ = .true.
318 >    call getMatchingElementList(atypes, "is_Directional", .true., &
319 >         nMatches, MatchList)
320 >    if (nMatches .gt. 0) FF_uses_DirectionalAtoms = .true.
321  
322 <    call getMatchingElementList(atypes, "is_Charge", .true., nMatches, MatchList)
323 <    if (nMatches .gt. 0) FF_uses_charges = .true.  
322 >    call getMatchingElementList(atypes, "is_LennardJones", .true., &
323 >         nMatches, MatchList)
324 >    if (nMatches .gt. 0) FF_uses_LennardJones = .true.
325 >    
326 >    call getMatchingElementList(atypes, "is_Electrostatic", .true., &
327 >         nMatches, MatchList)
328 >    if (nMatches .gt. 0) then
329 >       FF_uses_Electrostatic = .true.
330 >    endif
331  
332 <    call getMatchingElementList(atypes, "is_DP", .true., nMatches, MatchList)
333 <    if (nMatches .gt. 0) FF_uses_dipoles = .true.
332 >    call getMatchingElementList(atypes, "is_Charge", .true., &
333 >         nMatches, MatchList)
334 >    if (nMatches .gt. 0) then
335 >       FF_uses_charges = .true.  
336 >       FF_uses_electrostatic = .true.
337 >    endif
338      
339 +    call getMatchingElementList(atypes, "is_Dipole", .true., &
340 +         nMatches, MatchList)
341 +    if (nMatches .gt. 0) then
342 +       FF_uses_dipoles = .true.
343 +       FF_uses_electrostatic = .true.
344 +       FF_uses_DirectionalAtoms = .true.
345 +    endif
346 +    
347      call getMatchingElementList(atypes, "is_Sticky", .true., nMatches, &
348           MatchList)
349 <    if (nMatches .gt. 0) FF_uses_Sticky = .true.
349 >    if (nMatches .gt. 0) then
350 >       FF_uses_Sticky = .true.
351 >       FF_uses_DirectionalAtoms = .true.
352 >    endif
353      
354 <    call getMatchingElementList(atypes, "is_GB", .true., nMatches, MatchList)
355 <    if (nMatches .gt. 0) FF_uses_GB = .true.
354 >    call getMatchingElementList(atypes, "is_GayBerne", .true., &
355 >         nMatches, MatchList)
356 >    if (nMatches .gt. 0) then
357 >       FF_uses_GayBerne = .true.
358 >       FF_uses_DirectionalAtoms = .true.
359 >    endif
360      
361      call getMatchingElementList(atypes, "is_EAM", .true., nMatches, MatchList)
362      if (nMatches .gt. 0) FF_uses_EAM = .true.
363      
364 +    call getMatchingElementList(atypes, "is_Shape", .true., &
365 +         nMatches, MatchList)
366 +    if (nMatches .gt. 0) then
367 +       FF_uses_Shapes = .true.
368 +       FF_uses_DirectionalAtoms = .true.
369 +    endif
370 +
371 +    call getMatchingElementList(atypes, "is_FLARB", .true., &
372 +         nMatches, MatchList)
373 +    if (nMatches .gt. 0) FF_uses_FLARB = .true.
374 +
375      !! Assume sanity (for the sake of argument)
376      haveSaneForceField = .true.
377 <
377 >    
378      !! check to make sure the FF_uses_RF setting makes sense
379      
380      if (FF_uses_dipoles) then
# Line 300 | Line 391 | contains
391         endif
392      endif
393  
394 <    if (FF_uses_LJ) then
395 <      
396 <       select case (LJMIXPOLICY)
397 <       case (LB_MIXING_RULE)
398 <          call init_lj_FF(LB_MIXING_RULE, my_status)            
399 <       case (EXPLICIT_MIXING_RULE)
400 <          call init_lj_FF(EXPLICIT_MIXING_RULE, my_status)
401 <       case default
402 <          write(default_error,*) 'unknown LJ Mixing Policy!'
312 <          thisStat = -1
313 <          haveSaneForceField = .false.
314 <          return            
315 <       end select
316 <       if (my_status /= 0) then
317 <          thisStat = -1
318 <          haveSaneForceField = .false.
319 <          return
320 <       end if
321 <       havePolicies = .true.
322 <    endif
394 >    !sticky module does not contain check_sticky_FF anymore
395 >    !if (FF_uses_sticky) then
396 >    !   call check_sticky_FF(my_status)
397 >    !   if (my_status /= 0) then
398 >    !      thisStat = -1
399 >    !      haveSaneForceField = .false.
400 >    !      return
401 >    !   end if
402 >    !endif
403  
324    if (FF_uses_sticky) then
325       call check_sticky_FF(my_status)
326       if (my_status /= 0) then
327          thisStat = -1
328          haveSaneForceField = .false.
329          return
330       end if
331    endif
332
333
404      if (FF_uses_EAM) then
405           call init_EAM_FF(my_status)
406         if (my_status /= 0) then
# Line 341 | Line 411 | contains
411         end if
412      endif
413  
414 <    if (FF_uses_GB) then
414 >    if (FF_uses_GayBerne) then
415         call check_gb_pair_FF(my_status)
416         if (my_status .ne. 0) then
417            thisStat = -1
# Line 350 | Line 420 | contains
420         endif
421      endif
422  
423 <    if (FF_uses_GB .and. FF_uses_LJ) then
423 >    if (FF_uses_GayBerne .and. FF_uses_LennardJones) then
424      endif
425 +    
426      if (.not. haveNeighborList) then
427         !! Create neighbor lists
428         call expandNeighborList(nLocal, my_status)
# Line 361 | Line 432 | contains
432            return
433         endif
434         haveNeighborList = .true.
435 <    endif
365 <
435 >    endif    
436      
367    
437    end subroutine init_FF
438    
439  
440    !! Does force loop over i,j pairs. Calls do_pair to calculates forces.
441    !------------------------------------------------------------->
442 <  subroutine do_force_loop(q, q_group, A, u_l, f, t, tau, pot, &
442 >  subroutine do_force_loop(q, q_group, A, eFrame, f, t, tau, pot, &
443         do_pot_c, do_stress_c, error)
444      !! Position array provided by C, dimensioned by getNlocal
445      real ( kind = dp ), dimension(3, nLocal) :: q
# Line 379 | Line 448 | contains
448      !! Rotation Matrix for each long range particle in simulation.
449      real( kind = dp), dimension(9, nLocal) :: A    
450      !! Unit vectors for dipoles (lab frame)
451 <    real( kind = dp ), dimension(3,nLocal) :: u_l
451 >    real( kind = dp ), dimension(9,nLocal) :: eFrame
452      !! Force array provided by C, dimensioned by getNlocal
453      real ( kind = dp ), dimension(3,nLocal) :: f
454      !! Torsion array provided by C, dimensioned by getNlocal
# Line 453 | Line 522 | contains
522      call gather(q_group, q_group_Row, plan_group_row_3d)
523      call gather(q_group, q_group_Col, plan_group_col_3d)
524          
525 <    if (FF_UsesDirectionalAtoms() .and. SIM_uses_directional_atoms) then
526 <       call gather(u_l, u_l_Row, plan_atom_row_3d)
527 <       call gather(u_l, u_l_Col, plan_atom_col_3d)
525 >    if (FF_UsesDirectionalAtoms() .and. SIM_uses_DirectionalAtoms) then
526 >       call gather(eFrame, eFrame_Row, plan_atom_row_rotation)
527 >       call gather(eFrame, eFrame_Col, plan_atom_col_rotation)
528        
529         call gather(A, A_Row, plan_atom_row_rotation)
530         call gather(A, A_Col, plan_atom_col_rotation)
# Line 601 | Line 670 | contains
670   #ifdef IS_MPI                      
671                           call do_prepair(atom1, atom2, ratmsq, d_atm, sw, &
672                                rgrpsq, d_grp, do_pot, do_stress, &
673 <                              u_l, A, f, t, pot_local)
673 >                              eFrame, A, f, t, pot_local)
674   #else
675                           call do_prepair(atom1, atom2, ratmsq, d_atm, sw, &
676                                rgrpsq, d_grp, do_pot, do_stress, &
677 <                              u_l, A, f, t, pot)
677 >                              eFrame, A, f, t, pot)
678   #endif                                              
679                        else
680   #ifdef IS_MPI                      
681                           call do_pair(atom1, atom2, ratmsq, d_atm, sw, &
682                                do_pot, &
683 <                              u_l, A, f, t, pot_local, vpair, fpair)
683 >                              eFrame, A, f, t, pot_local, vpair, fpair)
684   #else
685                           call do_pair(atom1, atom2, ratmsq, d_atm, sw, &
686                                do_pot,  &
687 <                              u_l, A, f, t, pot, vpair, fpair)
687 >                              eFrame, A, f, t, pot, vpair, fpair)
688   #endif
689  
690                           vij = vij + vpair
# Line 707 | Line 776 | contains
776         f(1:3,i) = f(1:3,i) + f_temp(1:3,i)
777      end do
778      
779 <    if (FF_UsesDirectionalAtoms() .and. SIM_uses_directional_atoms) then
779 >    if (FF_UsesDirectionalAtoms() .and. SIM_uses_DirectionalAtoms) then
780         t_temp = 0.0_dp
781         call scatter(t_Row,t_temp,plan_atom_row_3d)
782         do i = 1,nlocal
# Line 762 | Line 831 | contains
831               me_i = atid(i)
832   #endif
833              
834 <             if (PropertyMap(me_i)%is_DP) then
834 >             if (PropertyMap(me_i)%is_Dipole) then
835                  
836 <                mu_i = PropertyMap(me_i)%dipole_moment
836 >                mu_i = getDipoleMoment(me_i)
837                  
838                  !! The reaction field needs to include a self contribution
839                  !! to the field:
840 <                call accumulate_self_rf(i, mu_i, u_l)
840 >                call accumulate_self_rf(i, mu_i, eFrame)
841                  !! Get the reaction field contribution to the
842                  !! potential and torques:
843 <                call reaction_field_final(i, mu_i, u_l, rfpot, t, do_pot)
843 >                call reaction_field_final(i, mu_i, eFrame, rfpot, t, do_pot)
844   #ifdef IS_MPI
845                  pot_local = pot_local + rfpot
846   #else
# Line 811 | Line 880 | contains
880    end subroutine do_force_loop
881    
882    subroutine do_pair(i, j, rijsq, d, sw, do_pot, &
883 <       u_l, A, f, t, pot, vpair, fpair)
883 >       eFrame, A, f, t, pot, vpair, fpair)
884  
885      real( kind = dp ) :: pot, vpair, sw
886      real( kind = dp ), dimension(3) :: fpair
887      real( kind = dp ), dimension(nLocal)   :: mfact
888 <    real( kind = dp ), dimension(3,nLocal) :: u_l
888 >    real( kind = dp ), dimension(9,nLocal) :: eFrame
889      real( kind = dp ), dimension(9,nLocal) :: A
890      real( kind = dp ), dimension(3,nLocal) :: f
891      real( kind = dp ), dimension(3,nLocal) :: t
# Line 839 | Line 908 | contains
908      me_i = atid(i)
909      me_j = atid(j)
910   #endif
911 +
912 + !    write(*,*) i, j, me_i, me_j
913      
914 <    if (FF_uses_LJ .and. SIM_uses_LJ) then
914 >    if (FF_uses_LennardJones .and. SIM_uses_LennardJones) then
915        
916 <       if ( PropertyMap(me_i)%is_LJ .and. PropertyMap(me_j)%is_LJ ) then
916 >       if ( PropertyMap(me_i)%is_LennardJones .and. &
917 >            PropertyMap(me_j)%is_LennardJones ) then
918            call do_lj_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot)
919         endif
920        
# Line 851 | Line 923 | contains
923      if (FF_uses_charges .and. SIM_uses_charges) then
924        
925         if (PropertyMap(me_i)%is_Charge .and. PropertyMap(me_j)%is_Charge) then
926 <          call do_charge_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, f, do_pot)
926 >          call do_charge_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
927 >               pot, f, do_pot)
928         endif
929        
930      endif
931      
932      if (FF_uses_dipoles .and. SIM_uses_dipoles) then
933        
934 <       if ( PropertyMap(me_i)%is_DP .and. PropertyMap(me_j)%is_DP) then
935 <          call do_dipole_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, u_l, f, t, &
936 <               do_pot)
934 >       if ( PropertyMap(me_i)%is_Dipole .and. PropertyMap(me_j)%is_Dipole) then
935 >          call do_dipole_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
936 >               pot, eFrame, f, t, do_pot)
937            if (FF_uses_RF .and. SIM_uses_RF) then
938 <             call accumulate_rf(i, j, r, u_l, sw)
939 <             call rf_correct_forces(i, j, d, r, u_l, sw, f, fpair)
940 <          endif          
938 >             call accumulate_rf(i, j, r, eFrame, sw)
939 >             call rf_correct_forces(i, j, d, r, eFrame, sw, f, fpair)
940 >          endif
941         endif
942  
943      endif
# Line 872 | Line 945 | contains
945      if (FF_uses_Sticky .and. SIM_uses_sticky) then
946  
947         if ( PropertyMap(me_i)%is_Sticky .and. PropertyMap(me_j)%is_Sticky) then
948 <          call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, A, f, t, &
949 <               do_pot)
948 >          call do_sticky_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
949 >               pot, A, f, t, do_pot)
950         endif
951 <
951 >      
952      endif
953  
954  
955 <    if (FF_uses_GB .and. SIM_uses_GB) then
955 >    if (FF_uses_GayBerne .and. SIM_uses_GayBerne) then
956        
957 <       if ( PropertyMap(me_i)%is_GB .and. PropertyMap(me_j)%is_GB) then
958 <          call do_gb_pair(i, j, d, r, rijsq, sw, vpair, fpair, pot, u_l, f, t, &
959 <               do_pot)
957 >       if ( PropertyMap(me_i)%is_GayBerne .and. &
958 >            PropertyMap(me_j)%is_GayBerne) then
959 >          call do_gb_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
960 >               pot, A, f, t, do_pot)
961         endif
888
889    endif
962        
963 +    endif
964 +    
965      if (FF_uses_EAM .and. SIM_uses_EAM) then
966        
967         if ( PropertyMap(me_i)%is_EAM .and. PropertyMap(me_j)%is_EAM) then
# Line 896 | Line 970 | contains
970         endif
971        
972      endif
973 +
974 +
975 + !    write(*,*) PropertyMap(me_i)%is_Shape,PropertyMap(me_j)%is_Shape
976 +
977 +    if (FF_uses_Shapes .and. SIM_uses_Shapes) then
978 +       if ( PropertyMap(me_i)%is_Shape .and. &
979 +            PropertyMap(me_j)%is_Shape ) then
980 +          call do_shape_pair(i, j, d, r, rijsq, sw, vpair, fpair, &
981 +               pot, A, f, t, do_pot)
982 +       endif
983 +      
984 +    endif
985      
986    end subroutine do_pair
987  
988    subroutine do_prepair(i, j, rijsq, d, sw, rcijsq, dc, &
989 <       do_pot, do_stress, u_l, A, f, t, pot)
989 >       do_pot, do_stress, eFrame, A, f, t, pot)
990  
991     real( kind = dp ) :: pot, sw
992 <   real( kind = dp ), dimension(3,nLocal) :: u_l
992 >   real( kind = dp ), dimension(9,nLocal) :: eFrame
993     real (kind=dp), dimension(9,nLocal) :: A
994     real (kind=dp), dimension(3,nLocal) :: f
995     real (kind=dp), dimension(3,nLocal) :: t
# Line 1018 | Line 1104 | contains
1104     q_group_Row = 0.0_dp
1105     q_group_Col = 0.0_dp  
1106    
1107 <   u_l_Row = 0.0_dp
1108 <   u_l_Col = 0.0_dp
1107 >   eFrame_Row = 0.0_dp
1108 >   eFrame_Col = 0.0_dp
1109    
1110     A_Row = 0.0_dp
1111     A_Col = 0.0_dp
# Line 1135 | Line 1221 | contains
1221  
1222   function FF_UsesDirectionalAtoms() result(doesit)
1223     logical :: doesit
1224 <   doesit = FF_uses_dipoles .or. FF_uses_sticky .or. &
1225 <        FF_uses_GB .or. FF_uses_RF
1224 >   doesit = FF_uses_DirectionalAtoms .or. FF_uses_Dipoles .or. &
1225 >        FF_uses_Sticky .or. FF_uses_GayBerne .or. FF_uses_Shapes
1226   end function FF_UsesDirectionalAtoms
1227  
1228   function FF_RequiresPrepairCalc() result(doesit)
# Line 1185 | Line 1271 | end module doForces
1271  
1272   !! Interfaces for C programs to module....
1273  
1274 < subroutine initFortranFF(LJMIXPOLICY, use_RF_c, thisStat)
1274 > subroutine initFortranFF(use_RF_c, thisStat)
1275      use doForces, ONLY: init_FF
1190    integer, intent(in) :: LJMIXPOLICY
1276      logical, intent(in) :: use_RF_c
1277  
1278      integer, intent(out) :: thisStat  
1279 <    call init_FF(LJMIXPOLICY, use_RF_c, thisStat)
1279 >    call init_FF(use_RF_c, thisStat)
1280  
1281   end subroutine initFortranFF
1282  
1283 <  subroutine doForceloop(q, q_group, A, u_l, f, t, tau, pot, &
1283 >  subroutine doForceloop(q, q_group, A, eFrame, f, t, tau, pot, &
1284         do_pot_c, do_stress_c, error)
1285        
1286         use definitions, ONLY: dp
# Line 1208 | Line 1293 | end module doForces
1293      !! Rotation Matrix for each long range particle in simulation.
1294      real( kind = dp), dimension(9, nLocal) :: A    
1295      !! Unit vectors for dipoles (lab frame)
1296 <    real( kind = dp ), dimension(3,nLocal) :: u_l
1296 >    real( kind = dp ), dimension(9,nLocal) :: eFrame
1297      !! Force array provided by C, dimensioned by getNlocal
1298      real ( kind = dp ), dimension(3,nLocal) :: f
1299      !! Torsion array provided by C, dimensioned by getNlocal
# Line 1220 | Line 1305 | end module doForces
1305      logical ( kind = 2) :: do_pot_c, do_stress_c
1306      integer :: error
1307      
1308 <    call do_force_loop(q, q_group, A, u_l, f, t, tau, pot, &
1308 >    call do_force_loop(q, q_group, A, eFrame, f, t, tau, pot, &
1309         do_pot_c, do_stress_c, error)
1310        
1311   end subroutine doForceloop

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines