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 306 by chuckv, Mon Mar 10 19:26:45 2003 UTC vs.
Revision 309 by gezelter, Mon Mar 10 23:19:23 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.2 2003-03-10 19:26:45 chuckv Exp $, $Date: 2003-03-10 19:26:45 $, $Name: not supported by cvs2svn $, $Revision: 1.2 $
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 $
6  
7  
8  
9 < module lj_ff
9 > module lj
10    use simulation
11    use definitions
12 <  use generic_lists
13 <
12 >  use forceGlobals
13 >  use atype_typedefs
14 >  use generic_atypes
15   #ifdef IS_MPI
16    use mpiSimulation
17   #endif
18    implicit none
19    PRIVATE
20 <
21 < !! Logical has lj force field module been initialized?
20 >  
21 >  !! Logical has lj force field module been initialized?
22    logical, save :: isljFFinit = .false.
23 <
24 <
25 < !! Public methods and data
25 <  public :: getLjPot
23 >  
24 >  
25 >  !! Public methods and data
26    public :: init_ljFF
27 <
27 >  public :: do_lj_pair
28 >  
29    type :: lj_mixed_params
30 <     !! Mass of Particle
30 <     real ( kind = dp )  :: mass = 0.0_dp
31 < !! Lennard-Jones epslon
30 >     !! Lennard-Jones epsilon
31       real ( kind = dp )  :: epsilon = 0.0_dp
32 < !! Lennard-Jones Sigma
32 >     !! Lennard-Jones Sigma
33       real ( kind = dp )  :: sigma = 0.0_dp
34 < !! Lennard-Jones Sigma Squared
34 >     !! Lennard-Jones Sigma Squared
35       real ( kind = dp )  :: sigma2 = 0.0_dp
36 < !! Lennard-Jones Sigma to sixth
36 >     !! Lennard-Jones Sigma to sixth
37       real ( kind = dp )  :: sigma6 = 0.0_dp
38    end type lj_mixed_params
39    
40 <  type (lj_mixed_params), dimension(:,:) :: ljMixed
41 <
40 >  type (lj_mixed_params), dimension(:,:), pointer :: ljMixed
41 >  
42   contains
43  
44    subroutine init_ljFF(ListHead,status)
45      type (atype),pointer :: ListHead
46      integer :: nTypes
47      integer, intent(out) :: status
48 <
48 >    
49      integer :: myStatus
50 <
50 >    
51      status = 0
52      call createMixingList(ListHead,myStatus)
53      if (myStatus /= 0) then
54         status = -1
55         return
56      end if
57 <
57 >    
58    end subroutine init_ljFF
59 <
59 >  
60    subroutine createMixingList(ListHead,status)
61      type (atype), pointer :: ListHead
62      integer :: listSize
63      integer :: status
64      integer :: i
65      integer :: j
67
68    integer :: i = 0
69    integer :: j = 0
66      type (atype), pointer :: tmpPtr_i => null()
67      type (atype), pointer :: tmpPtr_j => null()
68      status = 0
69 <
70 <    listSize = getListLen(ListHead)
69 >    
70 >    listSize = get_this_ListLen(ListHead)
71      if (listSize == 0) then
72         status = -1
73         return
74      end if
75 <  
76 <
75 >    
76 >    
77      if (.not. associated(ljMixed)) then
78         allocate(ljMixed(listSize,listSize))
79      else
80         status = -1
81         return
82      end if
87
83      
84 <
84 >    
85 >    
86      tmpPtr_i => ListHead
87      tmpPtr_j => tmpPtr_i%next
88      do while (associated(tmpPtr_i))
89         i = i + 1
90 < ! do self mixing rule
91 <       ljMixed(i,i)%sigma   = tmpPtr_i%sigma
92 <                                                                                                  
90 >       ! do self mixing rule
91 >       ljMixed(i,i)%sigma   = tmpPtr_i%lj_sigma
92 >      
93         ljMixed(i,i)%sigma2  = (ljMixed(i,i)%sigma) ** 2
94 <                                                                                                  
94 >      
95         ljMixed(i,i)%sigma6  = (ljMixed(i,i)%sigma) ** 6                                                                                                  
96 <       ljMixed(i,i)%epsilon = tmpPtr_i%epsilon
97 <
96 >       ljMixed(i,i)%epsilon = tmpPtr_i%lj_epsilon
97 >      
98         j = i + 1
99         do while (associated(tmpPtr_j))
100            
101            ljMixed(i,j)%sigma  =  &
102 <               calcLJMix("sigma",tmpPtr_i%sigma, &
103 <               tmpPtr_j%sigma)
102 >               calcLJMix("sigma",tmpPtr_i%lj_sigma, &
103 >               tmpPtr_j%lj_sigma)
104            
105            ljMixed(i,j)%sigma2  = &
106                 (ljMixed(i,j)%sigma)**2
# Line 113 | Line 109 | contains
109                 (ljMixed(i,j)%sigma)**6
110            
111            ljMixed(i,j)%epsilon = &
112 <               calcLJMix("epsilon",tmpPtr_i%epsilon, &
113 <               tmpPtr_j%epsilon)
112 >               calcLJMix("epsilon",tmpPtr_i%lj_epsilon, &
113 >               tmpPtr_j%lj_epsilon)
114            ljMixed(j,i)%sigma   = ljMixed(i,j)%sigma
115            ljMixed(j,i)%sigma2  = ljMixed(i,j)%sigma2
116            ljMixed(j,i)%sigma6  = ljMixed(i,j)%sigma6
117            ljMixed(j,i)%epsilon = ljMixed(i,j)%epsilon
118 <
119 <
118 >          
119 >          
120            tmpPtr_j => tmpPtr_j%next
121            j = j + 1
122         end do
123 < ! advance pointers
123 >       ! advance pointers
124         tmpPtr_i => tmpPtr_i%next
125         if (associated(tmpPtr_i)) then
126            tmpPtr_j => tmpPtr_i%next
127         endif
128        
129      end do
130 <
130 >    
131    end subroutine createMixingList
132 +  
133  
134 +  subroutine do_lj_pair(atom1, atom2, atype1, atype2, dx, dy, dz, rij, &
135 +       pot, f)
136  
137 <
138 <
139 <
140 < !! Calculates the potential between two lj particles based on two lj_atype pointers, optionally returns second
142 < !! derivatives.
143 <  subroutine getLjForce(r,pot,dudr,atype1,atype2,d2,status)
144 < ! arguments
145 < !! Length of vector between particles
146 <    real( kind = dp ), intent(in)  :: r
147 < !! Potential Energy
148 <    real( kind = dp ), intent(out) :: pot
149 < !! Derivatve wrt postion
150 <    real( kind = dp ), intent(out) :: dudr
151 < !! Second Derivative, optional, used mainly for normal mode calculations.
152 <    real( kind = dp ), intent(out), optional :: d2
153 <    
137 >    integer, intent(in) ::  atom1, atom2
138 >    real( kind = dp ), intent(in) :: dx, dy, dz, rij
139 >    real( kind = dp ) :: pot
140 >    real( kind = dp ), dimension(3, getNlocal()) :: f    
141      type (atype), pointer :: atype1
142      type (atype), pointer :: atype2
143  
144 <    integer, intent(out), optional :: status
145 <
146 < ! local Variables
144 >    ! local Variables
145 >    real( kind = dp ) :: drdx, drdy, drdz
146 >    real( kind = dp ) :: fx, fy, fz
147 >    real( kind = dp ) :: pot_temp, dudr
148      real( kind = dp ) :: sigma
149      real( kind = dp ) :: sigma2
150      real( kind = dp ) :: sigma6
# Line 174 | Line 162 | contains
162      real( kind = dp ) :: tp12
163      real( kind = dp ) :: delta
164  
165 <    logical :: doSec = .false.
178 <
179 <    integer :: errorStat
180 <
181 < !! Optional Argument Checking
182 < ! Check to see if we need to do second derivatives
183 <    
184 <    if (present(d2))     doSec = .true.
185 <    if (present(status)) status = 0
186 <
187 < ! Look up the correct parameters in the mixing matrix
165 >    ! Look up the correct parameters in the mixing matrix
166      sigma    = ljMixed(atype1%atype_ident,atype2%atype_ident)%sigma
167      sigma2   = ljMixed(atype1%atype_ident,atype2%atype_ident)%sigma2
168      sigma6   = ljMixed(atype1%atype_ident,atype2%atype_ident)%sigma6
169      epsilon  = ljMixed(atype1%atype_ident,atype2%atype_ident)%epsilon
170 <
171 <
170 >  
171 >    call getRcut(rcut,rcut2=rcut2,rcut6=rcut6)
172      
173 <
196 <    call getRcut(rcut,rcut2=rcut2,rcut6=rcut6,status=errorStat)
197 <    
198 <    r2 = r * r
173 >    r2 = rij * rij
174      r6 = r2 * r2 * r2
175  
176      t6  = sigma6/ r6
177      t12 = t6 * t6
203
204
178                                                                                
179      tp6 = sigma6 / rcut6
180      tp12 = tp6*tp6
181                                                                                
182 <    delta = -4.0E0_DP*epsilon * (tp12 - tp6)
183 <                                                                              
184 <    if (r.le.rcut) then
185 <       pot = 4.0E0_DP * epsilon * (t12 - t6) + delta
186 <       dudr = 24.0E0_DP * epsilon * (t6 - 2.0E0_DP*t12) / r
214 <       if(doSec)  d2 = 24.0E0_DP * epsilon * (26.0E0_DP*t12 - 7.0E0_DP*t6)/r/r
215 <    else
216 <       pot = 0.0E0_DP
217 <       dudr = 0.0E0_DP
218 <       if(doSec) d2 = 0.0E0_DP
219 <    endif
220 <                                                                              
221 <  return
182 >    delta = -4.0_DP * epsilon * (tp12 - tp6)
183 >    
184 >    if (rij.le.rcut) then
185 >      
186 >       pot_temp = 4.0E0_DP * epsilon * (t12 - t6) + delta      
187  
188 +       dudr = 24.0E0_DP * epsilon * (t6 - 2.0E0_DP*t12) / rij
189  
190 +       drdx = -dx / rij
191 +       drdy = -dy / rij
192 +       drdz = -dz / rij
193 +      
194 +       fx = dudr * drdx
195 +       fy = dudr * drdy
196 +       fz = dudr * drdz
197 +    
198 + #ifdef IS_MPI
199 +       pot_Row(atom1) = pot_Row(atom1) + pot_temp*0.5
200 +       pot_Col(atom2) = pot_Col(atom2) + pot_temp*0.5
201  
202 <  end subroutine getLJForce
202 >       f_Row(1,atom1) = f_Row(1,atom1) + fx
203 >       f_Row(2,atom1) = f_Row(2,atom1) + fy
204 >       f_Row(3,atom1) = f_Row(3,atom1) + fz
205  
206 +       f_Col(1,atom2) = f_Col(1,atom2) - fx
207 +       f_Col(2,atom2) = f_Col(2,atom2) - fy
208 +       f_Col(3,atom2) = f_Col(3,atom2) - fz      
209  
210 < !! Calculates the mixing for sigma or epslon based on character string for initialzition of mixing array.
210 > #else
211 >       pot = pot + pot_temp
212 >
213 >       f(1,atom1) = f(1,atom1) + fx
214 >       f(2,atom1) = f(2,atom1) + fy
215 >       f(3,atom1) = f(3,atom1) + fz
216 >
217 >       f(1,atom2) = f(1,atom2) - fx
218 >       f(2,atom2) = f(2,atom2) - fy
219 >       f(3,atom2) = f(3,atom2) - fz
220 > #endif
221 >      
222 >       if (doStress()) then
223 >          tau_Temp(1) = tau_Temp(1) + fx * dx
224 >          tau_Temp(2) = tau_Temp(2) + fx * dy
225 >          tau_Temp(3) = tau_Temp(3) + fx * dz
226 >          tau_Temp(4) = tau_Temp(4) + fy * dx
227 >          tau_Temp(5) = tau_Temp(5) + fy * dy
228 >          tau_Temp(6) = tau_Temp(6) + fy * dz
229 >          tau_Temp(7) = tau_Temp(7) + fz * dx
230 >          tau_Temp(8) = tau_Temp(8) + fz * dy
231 >          tau_Temp(9) = tau_Temp(9) + fz * dz
232 >          virial_Temp = virial_Temp + (tau_Temp(1) + tau_Temp(5) + tau_Temp(9))
233 >       endif
234 >
235 >    endif
236 >    return          
237 >  end subroutine do_lj_pair
238 >
239 >
240 >  !! Calculates the mixing for sigma or epslon based on character
241 >  !! string for initialzition of mixing array.
242    function calcLJMix(thisParam,param1,param2,status) result(myMixParam)
243      character(len=*) :: thisParam
244      real(kind = dp)  :: param1
# Line 233 | Line 246 | contains
246      real(kind = dp ) :: myMixParam
247      character(len = getStringLen()) :: thisMixingRule
248      integer, optional :: status
249 <
250 < !! get the mixing rules from the simulation
249 >    
250 >    !! get the mixing rules from the simulation
251      thisMixingRule = returnMixingRules()
252      myMixParam = 0.0_dp
253 <
253 >    
254      if (present(status)) status = 0
255      select case (thisMixingRule)
256 <       case ("standard")
257 <          select case (thisParam)
258 <          case ("sigma")
259 <             myMixParam = 0.5_dp * (param1 + param2)
260 <          case ("epsilon")
261 <             myMixParam = sqrt(param1 * param2)
262 <          case default
263 <             status = -1
264 <          end select
256 >    case ("standard")
257 >       select case (thisParam)
258 >       case ("sigma")
259 >          myMixParam = 0.5_dp * (param1 + param2)
260 >       case ("epsilon")
261 >          myMixParam = sqrt(param1 * param2)
262 >       case default
263 >          status = -1
264 >       end select
265      case("LJglass")
266      case default
267         status = -1
268      end select
269    end function calcLJMix
270 <
271 <
259 <
260 < end module lj_ff
270 >  
271 > end module lj

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines