ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/OpenMD/trunk/src/UseTheForce/DarkSide/suttonchen.F90
Revision: 1419
Committed: Fri Mar 26 17:25:54 2010 UTC (15 years, 4 months ago) by gezelter
File size: 13719 byte(s)
Log Message:
Fixed a typo in EAM, cleaned up EAM and sutton chen a bit

File Contents

# Content
1 !!
2 !! Copyright (c) 2005, 2009 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. Redistributions of source code must retain the above copyright
10 !! notice, this list of conditions and the following disclaimer.
11 !!
12 !! 2. Redistributions in binary form must reproduce the above copyright
13 !! notice, this list of conditions and the following disclaimer in the
14 !! documentation and/or other materials provided with the
15 !! distribution.
16 !!
17 !! This software is provided "AS IS," without a warranty of any
18 !! kind. All express or implied conditions, representations and
19 !! warranties, including any implied warranty of merchantability,
20 !! fitness for a particular purpose or non-infringement, are hereby
21 !! excluded. The University of Notre Dame and its licensors shall not
22 !! be liable for any damages suffered by licensee as a result of
23 !! using, modifying or distributing the software or its
24 !! derivatives. In no event will the University of Notre Dame or its
25 !! licensors be liable for any lost revenue, profit or data, or for
26 !! direct, indirect, special, consequential, incidental or punitive
27 !! damages, however caused and regardless of the theory of liability,
28 !! arising out of the use of or inability to use software, even if the
29 !! University of Notre Dame has been advised of the possibility of
30 !! such damages.
31 !!
32 !! SUPPORT OPEN SCIENCE! If you use OpenMD or its source code in your
33 !! research, please cite the appropriate papers when you publish your
34 !! work. Good starting points are:
35 !!
36 !! [1] Meineke, et al., J. Comp. Chem. 26, 252-271 (2005).
37 !! [2] Fennell & Gezelter, J. Chem. Phys. 124, 234104 (2006).
38 !! [3] Sun, Lin & Gezelter, J. Chem. Phys. 128, 24107 (2008).
39 !! [4] Vardeman & Gezelter, in progress (2009).
40 !!
41
42 !! Impliments Sutton-Chen Metallic Potential
43 !! See A.P.SUTTON and J.CHEN,PHIL MAG LETT 61,139-146,1990
44
45
46 module suttonchen
47 use definitions
48 use simulation
49 use force_globals
50 use status
51 use atype_module
52 use vector_class
53 use fForceOptions
54 use interpolation
55 implicit none
56 PRIVATE
57 #define __FORTRAN90
58 #include "UseTheForce/DarkSide/fInteractionMap.h"
59
60 !! number of points for the spline approximations
61 INTEGER, PARAMETER :: np = 3000
62
63 logical, save :: SC_FF_initialized = .false.
64 integer, save :: SC_Mixing_Policy
65 real(kind = dp), save :: SC_rcut
66 logical, save :: haveRcut = .false.
67 logical, save :: haveMixingMap = .false.
68 logical, save :: useGeometricDistanceMixing = .false.
69 logical, save :: cleanArrays = .true.
70 logical, save :: arraysAllocated = .false.
71
72
73 character(len = statusMsgSize) :: errMesg
74 integer :: sc_err
75
76 character(len = 200) :: errMsg
77 character(len=*), parameter :: RoutineName = "Sutton-Chen MODULE"
78
79 type, private :: SCtype
80 integer :: atid
81 real(kind=dp) :: c
82 real(kind=dp) :: m
83 real(kind=dp) :: n
84 real(kind=dp) :: alpha
85 real(kind=dp) :: epsilon
86 real(kind=dp) :: sc_rcut
87 end type SCtype
88
89
90 type, private :: SCTypeList
91 integer :: nSCTypes = 0
92 integer :: currentSCtype = 0
93 type (SCtype), pointer :: SCtypes(:) => null()
94 integer, pointer :: atidToSCtype(:) => null()
95 end type SCTypeList
96
97 type (SCTypeList), save :: SCList
98
99 type:: MixParameters
100 real(kind=DP) :: alpha
101 real(kind=DP) :: epsilon
102 real(kind=DP) :: m
103 real(Kind=DP) :: n
104 real(kind=dp) :: rCut
105 real(kind=dp) :: vCut
106 logical :: rCutWasSet = .false.
107 type(cubicSpline) :: V
108 type(cubicSpline) :: phi
109 end type MixParameters
110
111 type(MixParameters), dimension(:,:), allocatable :: MixingMap
112
113 public :: setCutoffSC
114 public :: do_SC_pair
115 public :: newSCtype
116 public :: calc_SC_prepair_rho
117 public :: calc_SC_preforce_Frho
118 public :: destroySCtypes
119 public :: getSCCut
120 ! public :: setSCDefaultCutoff
121 ! public :: setSCUniformCutoff
122
123
124 contains
125
126
127 subroutine newSCtype(c_ident,c,m,n,alpha,epsilon,status)
128 real (kind = dp ) :: c ! Density Scaling
129 real (kind = dp ) :: m ! Density Exponent
130 real (kind = dp ) :: n ! Pair Potential Exponent
131 real (kind = dp ) :: alpha ! Length Scaling
132 real (kind = dp ) :: epsilon ! Energy Scaling
133 integer :: c_ident
134 integer :: status
135 integer :: nAtypes,nSCTypes,myATID
136 integer :: maxVals
137 integer :: alloc_stat
138 integer :: current
139 integer,pointer :: Matchlist(:) => null()
140
141 status = 0
142
143
144 !! Assume that atypes has already been set and get the total number of types in atypes
145
146
147 ! check to see if this is the first time into
148 if (.not.associated(SCList%SCTypes)) then
149 call getMatchingElementList(atypes, "is_SC", .true., nSCtypes, MatchList)
150 SCList%nSCtypes = nSCtypes
151 allocate(SCList%SCTypes(nSCTypes))
152 nAtypes = getSize(atypes)
153 allocate(SCList%atidToSCType(nAtypes))
154 SCList%atidToSCType = -1
155 end if
156
157 SCList%currentSCType = SCList%currentSCType + 1
158 current = SCList%currentSCType
159
160 myATID = getFirstMatchingElement(atypes, "c_ident", c_ident)
161 SCList%atidToSCType(myATID) = current
162
163
164 SCList%SCTypes(current)%atid = c_ident
165 SCList%SCTypes(current)%alpha = alpha
166 SCList%SCTypes(current)%c = c
167 SCList%SCTypes(current)%m = m
168 SCList%SCTypes(current)%n = n
169 SCList%SCTypes(current)%epsilon = epsilon
170 end subroutine newSCtype
171
172
173 subroutine destroySCTypes()
174 if (associated(SCList%SCtypes)) then
175 deallocate(SCList%SCTypes)
176 SCList%SCTypes=>null()
177 end if
178 if (associated(SCList%atidToSCtype)) then
179 deallocate(SCList%atidToSCtype)
180 SCList%atidToSCtype=>null()
181 end if
182 ! Reset Capacity
183 SCList%nSCTypes = 0
184 SCList%currentSCtype=0
185
186 end subroutine destroySCTypes
187
188 function getSCCut(atomID) result(cutValue)
189 integer, intent(in) :: atomID
190 integer :: scID
191 real(kind=dp) :: cutValue
192
193 scID = SCList%atidToSCType(atomID)
194 cutValue = 2.0_dp * SCList%SCTypes(scID)%alpha
195 end function getSCCut
196
197 subroutine createMixingMap()
198 integer :: nSCtypes, i, j, k
199 real ( kind = dp ) :: e1, e2, m1, m2, alpha1, alpha2, n1, n2
200 real ( kind = dp ) :: epsilon, m, n, alpha, rCut, vCut, dr, r
201 real ( kind = dp ), dimension(np) :: rvals, vvals, phivals
202
203 if (SCList%currentSCtype == 0) then
204 call handleError("SuttonChen", "No members in SCMap")
205 return
206 end if
207
208 nSCtypes = SCList%nSCtypes
209
210 if (.not. allocated(MixingMap)) then
211 allocate(MixingMap(nSCtypes, nSCtypes))
212 endif
213 useGeometricDistanceMixing = usesGeometricDistanceMixing()
214 do i = 1, nSCtypes
215
216 e1 = SCList%SCtypes(i)%epsilon
217 m1 = SCList%SCtypes(i)%m
218 n1 = SCList%SCtypes(i)%n
219 alpha1 = SCList%SCtypes(i)%alpha
220
221 do j = 1, nSCtypes
222
223 e2 = SCList%SCtypes(j)%epsilon
224 m2 = SCList%SCtypes(j)%m
225 n2 = SCList%SCtypes(j)%n
226 alpha2 = SCList%SCtypes(j)%alpha
227
228 if (useGeometricDistanceMixing) then
229 alpha = sqrt(alpha1 * alpha2) !SC formulation
230 else
231 alpha = 0.5_dp * (alpha1 + alpha2) ! Goddard formulation
232 endif
233 rcut = 2.0_dp * alpha
234 epsilon = sqrt(e1 * e2)
235 m = 0.5_dp*(m1+m2)
236 n = 0.5_dp*(n1+n2)
237
238 dr = (rCut) / dble(np-1)
239 rvals(1) = 0.0_dp
240 vvals(1) = 0.0_dp
241 phivals(1) = 0.0_dp
242
243 do k = 2, np
244 r = dble(k-1)*dr
245 rvals(k) = r
246 vvals(k) = epsilon*((alpha/r)**n)
247 phivals(k) = (alpha/r)**m
248 enddo
249
250 vCut = epsilon*((alpha/rCut)**n)
251
252 call newSpline(MixingMap(i,j)%V, rvals, vvals, .true.)
253 call newSpline(MixingMap(i,j)%phi, rvals, phivals, .true.)
254
255 MixingMap(i,j)%epsilon = epsilon
256 MixingMap(i,j)%m = m
257 MixingMap(i,j)%n = n
258 MixingMap(i,j)%alpha = alpha
259 MixingMap(i,j)%rCut = rcut
260 MixingMap(i,j)%vCut = vCut
261 enddo
262 enddo
263
264 haveMixingMap = .true.
265
266 end subroutine createMixingMap
267
268
269
270 subroutine setCutoffSC(rcut)
271 real(kind=dp) :: rcut
272 SC_rcut = rcut
273 end subroutine setCutoffSC
274
275
276 !! Calculates rho_r
277 subroutine calc_sc_prepair_rho(atom1, atom2, atid1, atid2, d, r, rijsq, rho_i_at_j, rho_j_at_i)
278 integer :: atom1, atom2, atid1, atid2
279 real(kind = dp), dimension(3) :: d
280 real(kind = dp), intent(inout) :: r
281 real(kind = dp), intent(inout) :: rijsq
282 ! value of electron density rho do to atom i at atom j
283 real(kind = dp), intent(inout) :: rho_i_at_j
284 ! value of electron density rho do to atom j at atom i
285 real(kind = dp), intent(inout) :: rho_j_at_i
286 ! we don't use the derivatives, dummy variables
287 real( kind = dp) :: drho
288 integer :: sc_err
289
290 integer :: myid_atom1 ! SC atid
291 integer :: myid_atom2
292
293 ! check to see if we need to be cleaned at the start of a force loop
294
295 if (.not.haveMixingMap) call createMixingMap()
296 haveMixingMap = .true.
297
298 Myid_atom1 = SCList%atidtoSCtype(Atid1)
299 Myid_atom2 = SCList%atidtoSCtype(Atid2)
300
301 call lookupUniformSpline(MixingMap(myid_atom1,myid_atom2)%phi, r, &
302 rho_i_at_j)
303 rho_j_at_i = rho_i_at_j
304
305 end subroutine calc_sc_prepair_rho
306
307
308 !! Calculate the rho_a for all local atoms
309 subroutine calc_sc_preforce_Frho(nlocal, pot, particle_pot)
310 integer :: nlocal
311 real(kind=dp) :: pot
312 real(kind=dp), dimension(nlocal) :: particle_pot
313 integer :: i,j
314 integer :: atom
315 integer :: atype1
316 integer :: atid1
317 integer :: myid
318
319 !! Calculate F(rho) and derivative
320 do atom = 1, nlocal
321 Myid = SCList%atidtoSctype(Atid(atom))
322 ! Myid is set to -1 for non SC atoms.
323 ! Punt if we are a non-SC atom type.
324 if (Myid == -1) then
325 frho(atom) = 0.0_dp
326 dfrhodrho(atom) = 0.0_dp
327 else
328 frho(atom) = - SCList%SCTypes(Myid)%c * &
329 SCList%SCTypes(Myid)%epsilon * sqrt(rho(atom))
330
331 dfrhodrho(atom) = 0.5_dp*frho(atom)/rho(atom)
332 end if
333 pot = pot + frho(atom)
334 particle_pot(atom) = particle_pot(atom) + frho(atom)
335 enddo
336
337 end subroutine calc_sc_preforce_Frho
338
339 !! Does Sutton-Chen pairwise Force calculation.
340 subroutine do_sc_pair(atom1, atom2, atid1, atid2, d, rij, r2, sw, vpair, &
341 fpair, pot, f1, rho_i, rho_j, dfrhodrho_i, dfrhodrho_j, &
342 fshift_i, fshift_j, do_pot)
343 !Arguments
344 integer, intent(in) :: atom1, atom2, atid1, atid2
345 real( kind = dp ), intent(in) :: rij, r2
346 real( kind = dp ) :: pot, sw, vpair
347 real( kind = dp ), dimension(3) :: f1
348 real( kind = dp ), intent(in), dimension(3) :: d
349 real( kind = dp ), intent(inout), dimension(3) :: fpair
350 real( kind = dp ), intent(inout) :: dfrhodrho_i, dfrhodrho_j
351 real( kind = dp ), intent(inout) :: rho_i, rho_j
352 real( kind = dp ), intent(inout):: fshift_i, fshift_j
353
354 logical, intent(in) :: do_pot
355
356 real( kind = dp ) :: drdx, drdy, drdz
357 real( kind = dp ) :: dvpdr
358 real( kind = dp ) :: rhtmp, drhodr
359 real( kind = dp ) :: dudr
360 real( kind = dp ) :: Fx,Fy,Fz
361 real( kind = dp ) :: pot_temp, vptmp
362 real( kind = dp ) :: rcij, vcij
363
364 integer :: id1, id2
365 integer :: mytype_atom1
366 integer :: mytype_atom2
367
368 mytype_atom1 = SCList%atidToSCType(atid1)
369 mytype_atom2 = SCList%atidTOSCType(atid2)
370
371 drdx = d(1)/rij
372 drdy = d(2)/rij
373 drdz = d(3)/rij
374
375 rcij = MixingMap(mytype_atom1,mytype_atom2)%rCut
376 vcij = MixingMap(mytype_atom1,mytype_atom2)%vCut
377
378 call lookupUniformSpline1d(MixingMap(mytype_atom1, mytype_atom2)%phi, &
379 rij, rhtmp, drhodr)
380
381 call lookupUniformSpline1d(MixingMap(mytype_atom1, mytype_atom2)%V, &
382 rij, vptmp, dvpdr)
383
384 dudr = drhodr*(dfrhodrho_i + dfrhodrho_j) + dvpdr
385
386 pot_temp = vptmp - vcij
387
388 vpair = vpair + pot_temp
389
390 fx = dudr * drdx
391 fy = dudr * drdy
392 fz = dudr * drdz
393
394 if (do_pot) then
395
396 ! particle_pot is the difference between the full potential
397 ! and the full potential without the presence of a particular
398 ! particle (atom1).
399 !
400 ! This reduces the density at other particle locations, so
401 ! we need to recompute the density at atom2 assuming atom1
402 ! didn't contribute. This then requires recomputing the
403 ! density functional for atom2 as well.
404 !
405 ! Most of the particle_pot heavy lifting comes from the
406 ! pair interaction, and will be handled by vpair.
407
408 fshift_i = -SCList%SCTypes(mytype_atom1)%c * &
409 SCList%SCTypes(mytype_atom1)%epsilon * &
410 sqrt(rho_i-rhtmp)
411 fshift_j = -SCList%SCTypes(mytype_atom2)%c * &
412 SCList%SCTypes(mytype_atom2)%epsilon * &
413 sqrt(rho_j-rhtmp)
414 end if
415
416
417 pot = pot + pot_temp
418
419 f1(1) = f1(1) + fx
420 f1(2) = f1(2) + fy
421 f1(3) = f1(3) + fz
422
423 end subroutine do_sc_pair
424 end module suttonchen