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. 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 |
!! gayberne is the Gay-Berne interaction for ellipsoidal particles. The original |
43 |
!! paper (for identical uniaxial particles) is: |
44 |
!! J. G. Gay and B. J. Berne, J. Chem. Phys., 74, 3316-3319 (1981). |
45 |
!! A more-general GB potential for dissimilar uniaxial particles: |
46 |
!! D. J. Cleaver, C. M. Care, M. P. Allen and M. P. Neal, Phys. Rev. E, |
47 |
!! 54, 559-567 (1996). |
48 |
!! Further parameterizations can be found in: |
49 |
!! A. P. J. Emerson, G. R. Luckhurst and S. G. Whatling, Mol. Phys., |
50 |
!! 82, 113-124 (1994). |
51 |
!! And a nice force expression: |
52 |
!! G. R. Luckhurst and R. A. Stephens, Liq. Cryst. 8, 451-464 (1990). |
53 |
!! Even clearer force and torque expressions: |
54 |
!! P. A. Golubkov and P. Y. Ren, J. Chem. Phys., 125, 64103 (2006). |
55 |
!! New expressions for cross interactions of strength parameters: |
56 |
!! J. Wu, X. Zhen, H. Shen, G. Li, and P. Ren, J. Chem. Phys., |
57 |
!! 135, 155104 (2011). |
58 |
!! |
59 |
!! In this version of the GB interaction, each uniaxial ellipsoidal type |
60 |
!! is described using a set of 6 parameters: |
61 |
!! d: range parameter for side-by-side (S) and cross (X) configurations |
62 |
!! l: range parameter for end-to-end (E) configuration |
63 |
!! epsilon_X: well-depth parameter for cross (X) configuration |
64 |
!! epsilon_S: well-depth parameter for side-by-side (S) configuration |
65 |
!! epsilon_E: well depth parameter for end-to-end (E) configuration |
66 |
!! dw: "softness" of the potential |
67 |
!! |
68 |
!! Additionally, there are two "universal" paramters to govern the overall |
69 |
!! importance of the purely orientational (nu) and the mixed |
70 |
!! orientational / translational (mu) parts of strength of the interactions. |
71 |
!! These parameters have default or "canonical" values, but may be changed |
72 |
!! as a force field option: |
73 |
!! nu_: purely orientational part : defaults to 1 |
74 |
!! mu_: mixed orientational / translational part : defaults to 2 |
75 |
|
76 |
module gayberne |
77 |
use force_globals |
78 |
use definitions |
79 |
use simulation |
80 |
use atype_module |
81 |
use vector_class |
82 |
use linearalgebra |
83 |
use status |
84 |
use lj |
85 |
use fForceOptions |
86 |
|
87 |
implicit none |
88 |
|
89 |
private |
90 |
|
91 |
#define __FORTRAN90 |
92 |
#include "UseTheForce/DarkSide/fInteractionMap.h" |
93 |
|
94 |
logical, save :: haveGBMap = .false. |
95 |
logical, save :: haveMixingMap = .false. |
96 |
real(kind=dp), save :: mu = 2.0_dp |
97 |
real(kind=dp), save :: nu = 1.0_dp |
98 |
|
99 |
|
100 |
public :: newGBtype |
101 |
public :: complete_GB_FF |
102 |
public :: do_gb_pair |
103 |
public :: getGayBerneCut |
104 |
public :: destroyGBtypes |
105 |
|
106 |
type :: GBtype |
107 |
integer :: atid |
108 |
real(kind = dp ) :: d |
109 |
real(kind = dp ) :: l |
110 |
real(kind = dp ) :: epsX |
111 |
real(kind = dp ) :: epsS |
112 |
real(kind = dp ) :: epsE |
113 |
real(kind = dp ) :: dw |
114 |
logical :: isLJ |
115 |
end type GBtype |
116 |
|
117 |
type, private :: GBList |
118 |
integer :: nGBtypes = 0 |
119 |
integer :: currentGBtype = 0 |
120 |
type(GBtype), pointer :: GBtypes(:) => null() |
121 |
integer, pointer :: atidToGBtype(:) => null() |
122 |
end type GBList |
123 |
|
124 |
type(GBList), save :: GBMap |
125 |
|
126 |
type :: GBMixParameters |
127 |
real(kind=DP) :: sigma0 |
128 |
real(kind=DP) :: eps0 |
129 |
real(kind=DP) :: dw |
130 |
real(kind=DP) :: x2 |
131 |
real(kind=DP) :: xa2 |
132 |
real(kind=DP) :: xai2 |
133 |
real(kind=DP) :: xp2 |
134 |
real(kind=DP) :: xpap2 |
135 |
real(kind=DP) :: xpapi2 |
136 |
end type GBMixParameters |
137 |
|
138 |
type(GBMixParameters), dimension(:,:), allocatable :: GBMixingMap |
139 |
|
140 |
contains |
141 |
|
142 |
subroutine newGBtype(c_ident, d, l, epsX, epsS, epsE, dw, status) |
143 |
|
144 |
integer, intent(in) :: c_ident |
145 |
real( kind = dp ), intent(in) :: d, l, epsX, epsS, epsE, dw |
146 |
integer, intent(out) :: status |
147 |
|
148 |
integer :: nGBTypes, nLJTypes, ntypes, myATID |
149 |
integer, pointer :: MatchList(:) => null() |
150 |
integer :: current, i |
151 |
status = 0 |
152 |
|
153 |
if (.not.associated(GBMap%GBtypes)) then |
154 |
|
155 |
call getMatchingElementList(atypes, "is_GayBerne", .true., & |
156 |
nGBtypes, MatchList) |
157 |
|
158 |
call getMatchingElementList(atypes, "is_LennardJones", .true., & |
159 |
nLJTypes, MatchList) |
160 |
|
161 |
GBMap%nGBtypes = nGBtypes + nLJTypes |
162 |
|
163 |
allocate(GBMap%GBtypes(nGBtypes + nLJTypes)) |
164 |
|
165 |
ntypes = getSize(atypes) |
166 |
|
167 |
allocate(GBMap%atidToGBtype(ntypes)) |
168 |
endif |
169 |
|
170 |
GBMap%currentGBtype = GBMap%currentGBtype + 1 |
171 |
current = GBMap%currentGBtype |
172 |
|
173 |
myATID = getFirstMatchingElement(atypes, "c_ident", c_ident) |
174 |
|
175 |
GBMap%atidToGBtype(myATID) = current |
176 |
GBMap%GBtypes(current)%atid = myATID |
177 |
GBMap%GBtypes(current)%d = d |
178 |
GBMap%GBtypes(current)%l = l |
179 |
GBMap%GBtypes(current)%epsX = epsX |
180 |
GBMap%GBtypes(current)%epsS = epsS |
181 |
GBMap%GBtypes(current)%epsE = epsE |
182 |
GBMap%GBtypes(current)%dw = dw |
183 |
GBMap%GBtypes(current)%isLJ = .false. |
184 |
|
185 |
return |
186 |
end subroutine newGBtype |
187 |
|
188 |
subroutine complete_GB_FF(status) |
189 |
integer :: status |
190 |
integer :: i, j, l, m, lm, function_type |
191 |
real(kind=dp) :: thisDP, sigma |
192 |
integer :: alloc_stat, iTheta, iPhi, nSteps, nAtypes, myATID, current |
193 |
logical :: thisProperty |
194 |
|
195 |
status = 0 |
196 |
if (GBMap%currentGBtype == 0) then |
197 |
call handleError("complete_GB_FF", "No members in GBMap") |
198 |
status = -1 |
199 |
return |
200 |
end if |
201 |
|
202 |
nAtypes = getSize(atypes) |
203 |
|
204 |
if (nAtypes == 0) then |
205 |
status = -1 |
206 |
return |
207 |
end if |
208 |
|
209 |
! atypes comes from c side |
210 |
do i = 1, nAtypes |
211 |
|
212 |
myATID = getFirstMatchingElement(atypes, 'c_ident', i) |
213 |
call getElementProperty(atypes, myATID, "is_LennardJones", thisProperty) |
214 |
|
215 |
if (thisProperty) then |
216 |
GBMap%currentGBtype = GBMap%currentGBtype + 1 |
217 |
current = GBMap%currentGBtype |
218 |
|
219 |
GBMap%atidToGBtype(myATID) = current |
220 |
GBMap%GBtypes(current)%atid = myATID |
221 |
GBMap%GBtypes(current)%isLJ = .true. |
222 |
GBMap%GBtypes(current)%d = getSigma(myATID) / sqrt(2.0_dp) |
223 |
GBMap%GBtypes(current)%l = GBMap%GBtypes(current)%d |
224 |
GBMap%GBtypes(current)%epsX = getEpsilon(myATID) |
225 |
GBMap%GBtypes(current)%epsS = GBMap%GBtypes(current)%epsX |
226 |
GBMap%GBtypes(current)%epsE = GBMap%GBtypes(current)%epsX |
227 |
GBMap%GBtypes(current)%dw = 1.0_dp |
228 |
|
229 |
endif |
230 |
|
231 |
end do |
232 |
|
233 |
haveGBMap = .true. |
234 |
|
235 |
|
236 |
end subroutine complete_GB_FF |
237 |
|
238 |
subroutine createGBMixingMap() |
239 |
integer :: nGBtypes, i, j |
240 |
real (kind = dp) :: d1, l1, eX1, eS1, eE1, dw1 |
241 |
real (kind = dp) :: d2, l2, eX2, eS2, eE2, dw2 |
242 |
real (kind = dp) :: xp, ap2, mi |
243 |
|
244 |
if (GBMap%currentGBtype == 0) then |
245 |
call handleError("GB", "No members in GBMap") |
246 |
return |
247 |
end if |
248 |
|
249 |
nGBtypes = GBMap%nGBtypes |
250 |
|
251 |
if (.not. allocated(GBMixingMap)) then |
252 |
allocate(GBMixingMap(nGBtypes, nGBtypes)) |
253 |
endif |
254 |
|
255 |
do i = 1, nGBtypes |
256 |
|
257 |
d1 = GBMap%GBtypes(i)%d |
258 |
l1 = GBMap%GBtypes(i)%l |
259 |
eX1 = GBMap%GBtypes(i)%epsX |
260 |
eS1 = GBMap%GBtypes(i)%epsS |
261 |
eE1 = GBMap%GBtypes(i)%epsE |
262 |
dw1 = GBMap%GBtypes(i)%dw |
263 |
|
264 |
do j = 1, nGBtypes |
265 |
|
266 |
d2 = GBMap%GBtypes(j)%d |
267 |
l2 = GBMap%GBtypes(j)%l |
268 |
eX2 = GBMap%GBtypes(j)%epsX |
269 |
eS2 = GBMap%GBtypes(j)%epsS |
270 |
eE2 = GBMap%GBtypes(j)%epsE |
271 |
dw2 = GBMap%GBtypes(j)%dw |
272 |
|
273 |
! Cleaver paper uses sqrt of squares to get sigma0 for |
274 |
! mixed interactions. |
275 |
|
276 |
GBMixingMap(i,j)%sigma0 = sqrt(d1*d1 + d2*d2) |
277 |
GBMixingMap(i,j)%xa2 = (l1*l1 - d1*d1)/(l1*l1 + d2*d2) |
278 |
GBMixingMap(i,j)%xai2 = (l2*l2 - d2*d2)/(l2*l2 + d1*d1) |
279 |
GBMixingMap(i,j)%x2 = (l1*l1 - d1*d1) * (l2*l2 - d2*d2) / & |
280 |
((l2*l2 + d1*d1) * (l1*l1 + d2*d2)) |
281 |
|
282 |
! assumed LB mixing rules for now: |
283 |
|
284 |
GBMixingMap(i,j)%dw = 0.5_dp * (dw1 + dw2) |
285 |
GBMixingMap(i,j)%eps0 = sqrt(eX1 * eX2) |
286 |
|
287 |
mi = 1.0 / mu |
288 |
|
289 |
GBMixingMap(i,j)%xpap2 = ((eS1**mi) - (eE1**mi)) / & |
290 |
((eS1**mi) + (eE2**mi)) |
291 |
GBMixingMap(i,j)%xpapi2 = ((eS2**mi) - (eE2**mi)) / & |
292 |
((eS2**mi) + (eE1**mi)) |
293 |
GBMixingMap(i,j)%xp2 = ((eS1**mi) - (eE1**mi)) * & |
294 |
((eS2**mi) - (eE2**mi)) / & |
295 |
((eS2**mi) + (eE1**mi)) / ((eS1**mi) + (eE2**mi)) |
296 |
|
297 |
enddo |
298 |
enddo |
299 |
haveMixingMap = .true. |
300 |
mu = getGayBerneMu() |
301 |
nu = getGayBerneNu() |
302 |
end subroutine createGBMixingMap |
303 |
|
304 |
|
305 |
!! gay berne cutoff should be a parameter in globals, this is a temporary |
306 |
!! work around - this should be fixed when gay berne is up and running |
307 |
|
308 |
function getGayBerneCut(atomID) result(cutValue) |
309 |
integer, intent(in) :: atomID |
310 |
integer :: gbt1 |
311 |
real(kind=dp) :: cutValue, l, d |
312 |
|
313 |
if (GBMap%currentGBtype == 0) then |
314 |
call handleError("GB", "No members in GBMap") |
315 |
return |
316 |
end if |
317 |
|
318 |
gbt1 = GBMap%atidToGBtype(atomID) |
319 |
l = GBMap%GBtypes(gbt1)%l |
320 |
d = GBMap%GBtypes(gbt1)%d |
321 |
|
322 |
! sigma is actually sqrt(2)*l for prolate ellipsoids |
323 |
|
324 |
cutValue = 2.5_dp*sqrt(2.0_dp)*max(l,d) |
325 |
|
326 |
end function getGayBerneCut |
327 |
|
328 |
subroutine do_gb_pair(atid1, atid2, d, r, r2, sw, vdwMult, vpair, fpair, & |
329 |
pot, A1, A2, f1, t1, t2) |
330 |
|
331 |
integer, intent(in) :: atid1, atid2 |
332 |
integer :: gbt1, gbt2, id1, id2 |
333 |
real (kind=dp), intent(inout) :: r, r2, vdwMult |
334 |
real (kind=dp), dimension(3), intent(in) :: d |
335 |
real (kind=dp), dimension(3), intent(inout) :: fpair |
336 |
real (kind=dp) :: pot, sw, vpair |
337 |
real (kind=dp), dimension(9) :: A1, A2 |
338 |
real (kind=dp), dimension(3) :: f1 |
339 |
real (kind=dp), dimension(3) :: t1, t2 |
340 |
real (kind = dp), dimension(3) :: ul1, ul2, rxu1, rxu2, uxu, rhat |
341 |
|
342 |
real (kind = dp) :: sigma0, dw, eps0, x2, xa2, xai2, xp2, xpap2, xpapi2 |
343 |
real (kind = dp) :: e1, e2, eps, sigma, s3, s03, au2, bu2, au, bu, a, b, g, g2 |
344 |
real (kind = dp) :: U, BigR, R3, R6, R7, R12, R13, H, Hp, fx, fy, fz |
345 |
real (kind = dp) :: dUdr, dUda, dUdb, dUdg, pref1, pref2 |
346 |
logical :: i_is_lj, j_is_lj |
347 |
|
348 |
if (.not.haveMixingMap) then |
349 |
call createGBMixingMap() |
350 |
endif |
351 |
|
352 |
gbt1 = GBMap%atidToGBtype(atid1) |
353 |
gbt2 = GBMap%atidToGBtype(atid2) |
354 |
|
355 |
i_is_LJ = GBMap%GBTypes(gbt1)%isLJ |
356 |
j_is_LJ = GBMap%GBTypes(gbt2)%isLJ |
357 |
|
358 |
sigma0 = GBMixingMap(gbt1, gbt2)%sigma0 |
359 |
dw = GBMixingMap(gbt1, gbt2)%dw |
360 |
eps0 = GBMixingMap(gbt1, gbt2)%eps0 |
361 |
x2 = GBMixingMap(gbt1, gbt2)%x2 |
362 |
xa2 = GBMixingMap(gbt1, gbt2)%xa2 |
363 |
xai2 = GBMixingMap(gbt1, gbt2)%xai2 |
364 |
xp2 = GBMixingMap(gbt1, gbt2)%xp2 |
365 |
xpap2 = GBMixingMap(gbt1, gbt2)%xpap2 |
366 |
xpapi2 = GBMixingMap(gbt1, gbt2)%xpapi2 |
367 |
|
368 |
!!$ write(*,*) 'atypes = ',atid1, atid2 |
369 |
!!$ write(*,*) 'sigma0 = ',sigma0 |
370 |
!!$ write(*,*) 'dw = ',dw |
371 |
!!$ write(*,*) 'eps0 = ',eps0 |
372 |
!!$ write(*,*) 'x2 = ',x2 |
373 |
!!$ write(*,*) 'xa2 = ',xa2 |
374 |
!!$ write(*,*) 'xai2 = ',xai2 |
375 |
!!$ write(*,*) 'xp2 = ',xp2 |
376 |
!!$ write(*,*) 'xpap2 = ',xpap2 |
377 |
!!$ write(*,*) 'xpapi2 = ',xpapi2 |
378 |
|
379 |
|
380 |
ul1(1) = A1(7) |
381 |
ul1(2) = A1(8) |
382 |
ul1(3) = A1(9) |
383 |
|
384 |
ul2(1) = A2(7) |
385 |
ul2(2) = A2(8) |
386 |
ul2(3) = A2(9) |
387 |
|
388 |
!!$ write(*,*) 'ul1 = ', ul1(1), ul1(2), ul1(3) |
389 |
!!$ write(*,*) 'ul2 = ', ul2(1), ul2(2), ul2(3) |
390 |
|
391 |
if (i_is_LJ) then |
392 |
a = 0.0_dp |
393 |
ul1 = 0.0_dp |
394 |
else |
395 |
a = d(1)*ul1(1) + d(2)*ul1(2) + d(3)*ul1(3) |
396 |
endif |
397 |
|
398 |
if (j_is_LJ) then |
399 |
b = 0.0_dp |
400 |
ul2 = 0.0_dp |
401 |
else |
402 |
b = d(1)*ul2(1) + d(2)*ul2(2) + d(3)*ul2(3) |
403 |
endif |
404 |
|
405 |
if (i_is_LJ.or.j_is_LJ) then |
406 |
g = 0.0_dp |
407 |
else |
408 |
g = ul1(1)*ul2(1) + ul1(2)*ul2(2) + ul1(3)*ul2(3) |
409 |
endif |
410 |
|
411 |
au = a / r |
412 |
bu = b / r |
413 |
|
414 |
au2 = au * au |
415 |
bu2 = bu * bu |
416 |
g2 = g * g |
417 |
|
418 |
H = (xa2 * au2 + xai2 * bu2 - 2.0_dp*x2*au*bu*g) / (1.0_dp - x2*g2) |
419 |
Hp = (xpap2*au2 + xpapi2*bu2 - 2.0_dp*xp2*au*bu*g) / (1.0_dp - xp2*g2) |
420 |
|
421 |
!!$ write(*,*) 'au2 = ',au2 |
422 |
!!$ write(*,*) 'bu2 = ',bu2 |
423 |
!!$ write(*,*) 'g2 = ',g2 |
424 |
!!$ write(*,*) 'H = ',H |
425 |
!!$ write(*,*) 'Hp = ',Hp |
426 |
|
427 |
sigma = sigma0 / sqrt(1.0_dp - H) |
428 |
e1 = 1.0_dp / sqrt(1.0_dp - x2*g2) |
429 |
e2 = 1.0_dp - Hp |
430 |
eps = eps0 * (e1**nu) * (e2**mu) |
431 |
BigR = dw*sigma0 / (r - sigma + dw*sigma0) |
432 |
|
433 |
R3 = BigR*BigR*BigR |
434 |
R6 = R3*R3 |
435 |
R7 = R6 * BigR |
436 |
R12 = R6*R6 |
437 |
R13 = R6*R7 |
438 |
|
439 |
U = vdwMult * 4.0_dp * eps * (R12 - R6) |
440 |
|
441 |
s3 = sigma*sigma*sigma |
442 |
s03 = sigma0*sigma0*sigma0 |
443 |
|
444 |
!!$ write(*,*) 'vdwMult = ', vdwMult |
445 |
!!$ write(*,*) 'eps = ', eps |
446 |
!!$ write(*,*) 'mu = ', mu |
447 |
!!$ write(*,*) 'R12 = ', R12 |
448 |
!!$ write(*,*) 'R6 = ', R6 |
449 |
!!$ write(*,*) 'R13 = ', R13 |
450 |
!!$ write(*,*) 'R7 = ', R7 |
451 |
!!$ write(*,*) 'e2 = ', e2 |
452 |
!!$ write(*,*) 'rij = ', r |
453 |
!!$ write(*,*) 's3 = ', s3 |
454 |
!!$ write(*,*) 's03 = ', s03 |
455 |
!!$ write(*,*) 'dw = ', dw |
456 |
|
457 |
pref1 = - vdwMult * 8.0_dp * eps * mu * (R12 - R6) / (e2 * r) |
458 |
|
459 |
pref2 = vdwMult * 8.0_dp * eps * s3 * (6.0_dp*R13 - 3.0_dp*R7) / (dw*r*s03) |
460 |
|
461 |
dUdr = - (pref1 * Hp + pref2 * (sigma0*sigma0*r/s3 + H)) |
462 |
|
463 |
dUda = pref1 * (xpap2*au - xp2*bu*g) / (1.0_dp - xp2 * g2) & |
464 |
+ pref2 * (xa2 * au - x2 *bu*g) / (1.0_dp - x2 * g2) |
465 |
|
466 |
dUdb = pref1 * (xpapi2*bu - xp2*au*g) / (1.0_dp - xp2 * g2) & |
467 |
+ pref2 * (xai2 * bu - x2 *au*g) / (1.0_dp - x2 * g2) |
468 |
|
469 |
dUdg = 4.0_dp * eps * nu * (R12 - R6) * x2 * g / (1.0_dp - x2*g2) & |
470 |
+ 8.0_dp * eps * mu * (R12 - R6) * (xp2*au*bu - Hp*xp2*g) / & |
471 |
(1.0_dp - xp2 * g2) / e2 & |
472 |
+ 8.0_dp * eps * s3 * (3.0_dp * R7 - 6.0_dp * R13) * & |
473 |
(x2 * au * bu - H * x2 * g) / (1.0_dp - x2 * g2) / (dw * s03) |
474 |
!!$ write(*,*) 'pref = ',pref1 , pref2 |
475 |
!!$ write(*,*) 'dU = ',dUdr , dUda, dUdb , dUdg |
476 |
|
477 |
|
478 |
rhat = d / r |
479 |
|
480 |
fx = dUdr * rhat(1) + dUda * ul1(1) + dUdb * ul2(1) |
481 |
fy = dUdr * rhat(2) + dUda * ul1(2) + dUdb * ul2(2) |
482 |
fz = dUdr * rhat(3) + dUda * ul1(3) + dUdb * ul2(3) |
483 |
|
484 |
rxu1 = cross_product(d, ul1) |
485 |
rxu2 = cross_product(d, ul2) |
486 |
uxu = cross_product(ul1, ul2) |
487 |
|
488 |
pot = pot + U*sw |
489 |
|
490 |
f1(1) = f1(1) + fx*sw |
491 |
f1(2) = f1(2) + fy*sw |
492 |
f1(3) = f1(3) + fz*sw |
493 |
|
494 |
t1(1) = t1(1) + (dUda*rxu1(1) - dUdg*uxu(1))*sw |
495 |
t1(2) = t1(2) + (dUda*rxu1(2) - dUdg*uxu(2))*sw |
496 |
t1(3) = t1(3) + (dUda*rxu1(3) - dUdg*uxu(3))*sw |
497 |
|
498 |
t2(1) = t2(1) + (dUdb*rxu2(1) + dUdg*uxu(1))*sw |
499 |
t2(2) = t2(2) + (dUdb*rxu2(2) + dUdg*uxu(2))*sw |
500 |
t2(3) = t2(3) + (dUdb*rxu2(3) + dUdg*uxu(3))*sw |
501 |
|
502 |
vpair = vpair + U |
503 |
|
504 |
!!$ write(*,*) 'f1 term = ', fx*sw, fy*sw, fz*sw |
505 |
!!$ write(*,*) 't1 term = ', (dUda*rxu1(1) - dUdg*uxu(1))*sw, & |
506 |
!!$ (dUda*rxu1(2) - dUdg*uxu(2))*sw, & |
507 |
!!$ (dUda*rxu1(3) - dUdg*uxu(3))*sw |
508 |
!!$ write(*,*) 't2 term = ', (dUdb*rxu2(1) + dUdg*uxu(1))*sw, & |
509 |
!!$ (dUdb*rxu2(2) + dUdg*uxu(2))*sw, & |
510 |
!!$ (dUdb*rxu2(3) + dUdg*uxu(3))*sw |
511 |
!!$ write(*,*) 'vp term = ', U |
512 |
|
513 |
return |
514 |
end subroutine do_gb_pair |
515 |
|
516 |
subroutine destroyGBTypes() |
517 |
|
518 |
GBMap%nGBtypes = 0 |
519 |
GBMap%currentGBtype = 0 |
520 |
|
521 |
if (associated(GBMap%GBtypes)) then |
522 |
deallocate(GBMap%GBtypes) |
523 |
GBMap%GBtypes => null() |
524 |
end if |
525 |
|
526 |
if (associated(GBMap%atidToGBtype)) then |
527 |
deallocate(GBMap%atidToGBtype) |
528 |
GBMap%atidToGBtype => null() |
529 |
end if |
530 |
|
531 |
haveMixingMap = .false. |
532 |
|
533 |
end subroutine destroyGBTypes |
534 |
|
535 |
end module gayberne |
536 |
|