ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE_old/src/mdtools/libmdCode/calc_LJ_FF.F90
(Generate patch)

Comparing trunk/OOPSE_old/src/mdtools/libmdCode/calc_LJ_FF.F90 (file contents):
Revision 309 by gezelter, Mon Mar 10 23:19:23 2003 UTC vs.
Revision 329 by gezelter, Wed Mar 12 22:27:59 2003 UTC

# Line 2 | Line 2
2   !! Corresponds to the force field defined in lj_FF.cpp
3   !! @author Charles F. Vardeman II
4   !! @author Matthew Meineke
5 < !! @version $Id: calc_LJ_FF.F90,v 1.3 2003-03-10 23:19:23 gezelter Exp $, $Date: 2003-03-10 23:19:23 $, $Name: not supported by cvs2svn $, $Revision: 1.3 $
5 > !! @version $Id: calc_LJ_FF.F90,v 1.9 2003-03-12 22:27:59 gezelter Exp $, $Date: 2003-03-12 22:27:59 $, $Name: not supported by cvs2svn $, $Revision: 1.9 $
6  
7
8
7   module lj
8    use simulation
9    use definitions
10 <  use forceGlobals
11 <  use atype_typedefs
14 <  use generic_atypes
10 >  use atype_module
11 >  use vector_class
12   #ifdef IS_MPI
13    use mpiSimulation
14   #endif
15    implicit none
16    PRIVATE
17 +
18 +  integer, save :: LJ_Mixing_Policy
19 +  integer, parameter :: LB_Mixing_Rule = 1
20 +  integer, parameter :: Explicit_Mixing_Rule = 2
21    
22    !! Logical has lj force field module been initialized?
22  logical, save :: isljFFinit = .false.
23    
24 +  logical, save :: LJ_FF_initialized = .false.
25    
26    !! Public methods and data
27 <  public :: init_ljFF
27 >  public :: init_LJ_FF
28    public :: do_lj_pair
29    
30    type :: lj_mixed_params
# Line 31 | Line 32 | module lj
32       real ( kind = dp )  :: epsilon = 0.0_dp
33       !! Lennard-Jones Sigma
34       real ( kind = dp )  :: sigma = 0.0_dp
34     !! Lennard-Jones Sigma Squared
35     real ( kind = dp )  :: sigma2 = 0.0_dp
35       !! Lennard-Jones Sigma to sixth
36       real ( kind = dp )  :: sigma6 = 0.0_dp
37 +     !!
38 +     real ( kind = dp )  :: tp6
39 +     real ( kind = dp )  :: tp12
40 +
41 +     real ( kind = dp )  :: delta  = 0.0_dp
42 +
43    end type lj_mixed_params
44    
45    type (lj_mixed_params), dimension(:,:), pointer :: ljMixed
46    
47   contains
48  
49 <  subroutine init_ljFF(ListHead,status)
50 <    type (atype),pointer :: ListHead
46 <    integer :: nTypes
49 >  subroutine init_LJ_FF(mix_Policy, status)
50 >    character(len=100), intent(in) :: mix_Policy
51      integer, intent(out) :: status
48    
52      integer :: myStatus
53      
54 +    if ((mix_Policy == "standard") .or.  (mix_Policy == "LB")) then
55 +       LJ_Mixing_Policy = LB_Mixing_Rule
56 +    else
57 +       if (mix_Policy == "explicit") then
58 +          LJ_Mixing_Policy = Explicit_Mixing_Rule
59 +       else
60 +          write(*,*) 'Unknown Mixing Policy!'
61 +          status = -1
62 +          return
63 +       endif
64 +    endif
65 +        
66      status = 0
67 <    call createMixingList(ListHead,myStatus)
67 >    call createMixingList(myStatus)
68      if (myStatus /= 0) then
69         status = -1
70         return
71      end if
72      
73 <  end subroutine init_ljFF
73 >    LJ_FF_initialized = .true.
74 >
75 >  end subroutine init_LJ_FF
76    
77 <  subroutine createMixingList(ListHead,status)
78 <    type (atype), pointer :: ListHead
62 <    integer :: listSize
77 >  subroutine createMixingList(status)
78 >    integer :: nAtypes
79      integer :: status
80      integer :: i
81      integer :: j
82 <    type (atype), pointer :: tmpPtr_i => null()
83 <    type (atype), pointer :: tmpPtr_j => null()
82 >    real ( kind = dp ) :: mySigma_i,mySigma_j
83 >    real ( kind = dp ) :: myEpsilon_i,myEpsilon_j
84 >    real ( kind = dp ) :: rcut, rcut6
85      status = 0
86      
87 <    listSize = get_this_ListLen(ListHead)
88 <    if (listSize == 0) then
87 >    nAtypes = getSize(atypes)
88 >    if (nAtypes == 0) then
89         status = -1
90         return
91      end if
92 <    
76 <    
92 >        
93      if (.not. associated(ljMixed)) then
94 <       allocate(ljMixed(listSize,listSize))
94 >       allocate(ljMixed(nAtypes, nAtypes))
95      else
96         status = -1
97         return
98      end if
99 <    
100 <    
101 <    
102 <    tmpPtr_i => ListHead
103 <    tmpPtr_j => tmpPtr_i%next
88 <    do while (associated(tmpPtr_i))
89 <       i = i + 1
99 >    call getRcut(rcut, rc6=rcut6)
100 >    do i = 1, nAtypes
101 >
102 >       call getElementProperty(atypes,i,"lj_epsilon",myEpsilon_i)
103 >       call getElementProperty(atypes,i,"lj_sigma",  mySigma_i)
104         ! do self mixing rule
105 <       ljMixed(i,i)%sigma   = tmpPtr_i%lj_sigma
105 >       ljMixed(i,i)%sigma   = mySigma_i
106        
93       ljMixed(i,i)%sigma2  = (ljMixed(i,i)%sigma) ** 2
94      
107         ljMixed(i,i)%sigma6  = (ljMixed(i,i)%sigma) ** 6                                                                                                  
108 <       ljMixed(i,i)%epsilon = tmpPtr_i%lj_epsilon
109 <      
110 <       j = i + 1
111 <       do while (associated(tmpPtr_j))
108 >       ljMixed(i,i)%tp6     = ljMixed(i,i)%sigma6/rcut6
109 >
110 >       ljMixed(i,i)%tp12    = (ljMixed(i,i)%tp6) ** 2
111 >
112 >       ljMixed(i,i)%epsilon = myEpsilon_i
113 >
114 >       ljMixed(i,i)%delta = -4.0_DP * ljMixed(i,i)%epsilon * &
115 >            (ljMixed(i,i)%tp12 - ljMixed(i,i)%tp6)
116 >      
117 >       do j = i + 1, nAtypes
118 >          call getElementProperty(atypes,j,"lj_epsilon",myEpsilon_j)
119 >          call getElementProperty(atypes,j,"lj_sigma",  mySigma_j)
120            
121            ljMixed(i,j)%sigma  =  &
122 <               calcLJMix("sigma",tmpPtr_i%lj_sigma, &
123 <               tmpPtr_j%lj_sigma)
122 >               calcLJMix("sigma",mySigma_i, &
123 >               mySigma_j)
124            
105          ljMixed(i,j)%sigma2  = &
106               (ljMixed(i,j)%sigma)**2
107          
125            ljMixed(i,j)%sigma6 = &
126                 (ljMixed(i,j)%sigma)**6
127            
128 +          
129 +          ljMixed(i,j)%tp6     = ljMixed(i,j)%sigma6/rcut6
130 +          
131 +          ljMixed(i,j)%tp12    = (ljMixed(i,j)%tp6) ** 2
132 +          
133 +          
134            ljMixed(i,j)%epsilon = &
135 <               calcLJMix("epsilon",tmpPtr_i%lj_epsilon, &
136 <               tmpPtr_j%lj_epsilon)
135 >               calcLJMix("epsilon",myEpsilon_i, &
136 >               myEpsilon_j)
137 >          
138 >          ljMixed(i,j)%delta = -4.0_DP * ljMixed(i,j)%epsilon * &
139 >               (ljMixed(i,j)%tp12 - ljMixed(i,j)%tp6)
140 >          
141 >          
142            ljMixed(j,i)%sigma   = ljMixed(i,j)%sigma
115          ljMixed(j,i)%sigma2  = ljMixed(i,j)%sigma2
143            ljMixed(j,i)%sigma6  = ljMixed(i,j)%sigma6
144 +          ljMixed(j,i)%tp6     = ljMixed(i,j)%tp6
145 +          ljMixed(j,i)%tp12    = ljMixed(i,j)%tp12
146            ljMixed(j,i)%epsilon = ljMixed(i,j)%epsilon
147 +          ljMixed(j,i)%delta   = ljMixed(i,j)%delta
148            
119          
120          tmpPtr_j => tmpPtr_j%next
121          j = j + 1
149         end do
123       ! advance pointers
124       tmpPtr_i => tmpPtr_i%next
125       if (associated(tmpPtr_i)) then
126          tmpPtr_j => tmpPtr_i%next
127       endif
128      
150      end do
151      
152    end subroutine createMixingList
153    
154  
155 <  subroutine do_lj_pair(atom1, atom2, atype1, atype2, dx, dy, dz, rij, &
135 <       pot, f)
155 >  subroutine do_lj_pair(atom1, atom2, d, rij, r2, pot, f, do_pot, do_stress)
156  
157      integer, intent(in) ::  atom1, atom2
158 <    real( kind = dp ), intent(in) :: dx, dy, dz, rij
158 >    real( kind = dp ), intent(in) :: rij, r2
159      real( kind = dp ) :: pot
160      real( kind = dp ), dimension(3, getNlocal()) :: f    
161 <    type (atype), pointer :: atype1
162 <    type (atype), pointer :: atype2
161 >    real( kind = dp ), intent(in), dimension(3) :: d
162 >    logical, intent(in) :: do_pot, do_stress
163  
164      ! local Variables
165      real( kind = dp ) :: drdx, drdy, drdz
166      real( kind = dp ) :: fx, fy, fz
167      real( kind = dp ) :: pot_temp, dudr
148    real( kind = dp ) :: sigma
149    real( kind = dp ) :: sigma2
168      real( kind = dp ) :: sigma6
169      real( kind = dp ) :: epsilon
152
170      real( kind = dp ) :: rcut
154    real( kind = dp ) :: rcut2
155    real( kind = dp ) :: rcut6
156    real( kind = dp ) :: r2
171      real( kind = dp ) :: r6
158
172      real( kind = dp ) :: t6
173      real( kind = dp ) :: t12
161    real( kind = dp ) :: tp6
162    real( kind = dp ) :: tp12
174      real( kind = dp ) :: delta
175  
176      ! Look up the correct parameters in the mixing matrix
177 <    sigma    = ljMixed(atype1%atype_ident,atype2%atype_ident)%sigma
178 <    sigma2   = ljMixed(atype1%atype_ident,atype2%atype_ident)%sigma2
179 <    sigma6   = ljMixed(atype1%atype_ident,atype2%atype_ident)%sigma6
180 <    epsilon  = ljMixed(atype1%atype_ident,atype2%atype_ident)%epsilon
177 > #ifdef IS_MPI
178 >    sigma6   = ljMixed(atid_Row(atom1),atid_Col(atom2))%sigma6
179 >    epsilon  = ljMixed(atid_Row(atom1),atid_Col(atom2))%epsilon
180 >    delta    = ljMixed(atid_Row(atom1),atid_Col(atom2))%delta
181 > #else
182 >    sigma6   = ljMixed(atid(atom1),atid(atom2))%sigma6
183 >    epsilon  = ljMixed(atid(atom1),atid(atom2))%epsilon
184 >    delta    = ljMixed(atid(atom1),atid(atom2))%delta
185 > #endif
186    
187 <    call getRcut(rcut,rcut2=rcut2,rcut6=rcut6)
187 >    call getRcut(rcut)
188      
173    r2 = rij * rij
189      r6 = r2 * r2 * r2
190  
191      t6  = sigma6/ r6
192      t12 = t6 * t6
193 <                                                                              
179 <    tp6 = sigma6 / rcut6
180 <    tp12 = tp6*tp6
181 <                                                                              
182 <    delta = -4.0_DP * epsilon * (tp12 - tp6)
183 <    
193 >      
194      if (rij.le.rcut) then
195        
196         pot_temp = 4.0E0_DP * epsilon * (t12 - t6) + delta      
197  
198         dudr = 24.0E0_DP * epsilon * (t6 - 2.0E0_DP*t12) / rij
199  
200 <       drdx = -dx / rij
201 <       drdy = -dy / rij
202 <       drdz = -dz / rij
200 >       drdx = -d(1) / rij
201 >       drdy = -d(2) / rij
202 >       drdz = -d(3) / rij
203        
204         fx = dudr * drdx
205         fy = dudr * drdy
206         fz = dudr * drdz
207      
208   #ifdef IS_MPI
209 <       pot_Row(atom1) = pot_Row(atom1) + pot_temp*0.5
210 <       pot_Col(atom2) = pot_Col(atom2) + pot_temp*0.5
209 >       if (do_pot) then
210 >          pot_Row(atom1) = pot_Row(atom1) + pot_temp*0.5
211 >          pot_Col(atom2) = pot_Col(atom2) + pot_temp*0.5
212 >       endif
213  
214         f_Row(1,atom1) = f_Row(1,atom1) + fx
215         f_Row(2,atom1) = f_Row(2,atom1) + fy
# Line 208 | Line 220 | contains
220         f_Col(3,atom2) = f_Col(3,atom2) - fz      
221  
222   #else
223 <       pot = pot + pot_temp
223 >       if (do_pot) pot = pot + pot_temp
224  
225         f(1,atom1) = f(1,atom1) + fx
226         f(2,atom1) = f(2,atom1) + fy
# Line 219 | Line 231 | contains
231         f(3,atom2) = f(3,atom2) - fz
232   #endif
233        
234 <       if (doStress()) then
235 <          tau_Temp(1) = tau_Temp(1) + fx * dx
236 <          tau_Temp(2) = tau_Temp(2) + fx * dy
237 <          tau_Temp(3) = tau_Temp(3) + fx * dz
238 <          tau_Temp(4) = tau_Temp(4) + fy * dx
239 <          tau_Temp(5) = tau_Temp(5) + fy * dy
240 <          tau_Temp(6) = tau_Temp(6) + fy * dz
241 <          tau_Temp(7) = tau_Temp(7) + fz * dx
242 <          tau_Temp(8) = tau_Temp(8) + fz * dy
243 <          tau_Temp(9) = tau_Temp(9) + fz * dz
234 >       if (do_stress) then
235 >          tau_Temp(1) = tau_Temp(1) + fx * d(1)
236 >          tau_Temp(2) = tau_Temp(2) + fx * d(2)
237 >          tau_Temp(3) = tau_Temp(3) + fx * d(3)
238 >          tau_Temp(4) = tau_Temp(4) + fy * d(1)
239 >          tau_Temp(5) = tau_Temp(5) + fy * d(2)
240 >          tau_Temp(6) = tau_Temp(6) + fy * d(3)
241 >          tau_Temp(7) = tau_Temp(7) + fz * d(1)
242 >          tau_Temp(8) = tau_Temp(8) + fz * d(2)
243 >          tau_Temp(9) = tau_Temp(9) + fz * d(3)
244            virial_Temp = virial_Temp + (tau_Temp(1) + tau_Temp(5) + tau_Temp(9))
245         endif
246 <
246 >      
247      endif
248      return          
249    end subroutine do_lj_pair
250  
251  
252 <  !! Calculates the mixing for sigma or epslon based on character
253 <  !! string for initialzition of mixing array.
252 >  !! Calculates the mixing for sigma or epslon
253 >
254    function calcLJMix(thisParam,param1,param2,status) result(myMixParam)
255      character(len=*) :: thisParam
256      real(kind = dp)  :: param1
257      real(kind = dp)  :: param2
258      real(kind = dp ) :: myMixParam
259 <    character(len = getStringLen()) :: thisMixingRule
260 <    integer, optional :: status
261 <    
250 <    !! get the mixing rules from the simulation
251 <    thisMixingRule = returnMixingRules()
259 >
260 >    integer, optional :: status  
261 >
262      myMixParam = 0.0_dp
263      
264      if (present(status)) status = 0
265 <    select case (thisMixingRule)
266 <    case ("standard")
265 >    select case (LJ_Mixing_Policy)
266 >    case (LB_Mixing_Rule)
267         select case (thisParam)
268         case ("sigma")
269            myMixParam = 0.5_dp * (param1 + param2)
# Line 262 | Line 272 | contains
272         case default
273            status = -1
274         end select
265    case("LJglass")
275      case default
276         status = -1
277      end select

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines