ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-2.0/src/UseTheForce/DarkSide/sticky.F90
Revision: 2357
Committed: Wed Oct 12 20:18:17 2005 UTC (18 years, 8 months ago) by chuckv
File size: 29458 byte(s)
Log Message:
More Change goodness for calculation of potential.

File Contents

# Content
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 !! This Module Calculates forces due to SSD potential and VDW interactions
43 !! [Chandra and Ichiye, J. Chem. Phys. 111, 2701 (1999)].
44
45 !! This module contains the Public procedures:
46
47
48 !! Corresponds to the force field defined in ssd_FF.cpp
49 !! @author Charles F. Vardeman II
50 !! @author Matthew Meineke
51 !! @author Christopher Fennell
52 !! @author J. Daniel Gezelter
53 !! @version $Id: sticky.F90,v 1.16 2005-10-12 20:18:17 chuckv Exp $, $Date: 2005-10-12 20:18:17 $, $Name: not supported by cvs2svn $, $Revision: 1.16 $
54
55 module sticky
56
57 use force_globals
58 use definitions
59 use atype_module
60 use vector_class
61 use simulation
62 use status
63 #ifdef IS_MPI
64 use mpiSimulation
65 #endif
66 implicit none
67
68 PRIVATE
69 #define __FORTRAN90
70 #include "UseTheForce/DarkSide/fInteractionMap.h"
71
72 public :: newStickyType
73 public :: do_sticky_pair
74 public :: destroyStickyTypes
75 public :: do_sticky_power_pair
76 public :: getStickyCut
77 public :: getStickyPowerCut
78
79 type :: StickyList
80 integer :: c_ident
81 real( kind = dp ) :: w0 = 0.0_dp
82 real( kind = dp ) :: v0 = 0.0_dp
83 real( kind = dp ) :: v0p = 0.0_dp
84 real( kind = dp ) :: rl = 0.0_dp
85 real( kind = dp ) :: ru = 0.0_dp
86 real( kind = dp ) :: rlp = 0.0_dp
87 real( kind = dp ) :: rup = 0.0_dp
88 real( kind = dp ) :: rbig = 0.0_dp
89 end type StickyList
90
91 type(StickyList), dimension(:),allocatable :: StickyMap
92
93 contains
94
95 subroutine newStickyType(c_ident, w0, v0, v0p, rl, ru, rlp, rup, isError)
96
97 integer, intent(in) :: c_ident
98 integer, intent(inout) :: isError
99 real( kind = dp ), intent(in) :: w0, v0, v0p
100 real( kind = dp ), intent(in) :: rl, ru
101 real( kind = dp ), intent(in) :: rlp, rup
102 integer :: nATypes, myATID
103
104
105 isError = 0
106 myATID = getFirstMatchingElement(atypes, "c_ident", c_ident)
107
108 !! Be simple-minded and assume that we need a StickyMap that
109 !! is the same size as the total number of atom types
110
111 if (.not.allocated(StickyMap)) then
112
113 nAtypes = getSize(atypes)
114
115 if (nAtypes == 0) then
116 isError = -1
117 return
118 end if
119
120 if (.not. allocated(StickyMap)) then
121 allocate(StickyMap(nAtypes))
122 endif
123
124 end if
125
126 if (myATID .gt. size(StickyMap)) then
127 isError = -1
128 return
129 endif
130
131 ! set the values for StickyMap for this atom type:
132
133 StickyMap(myATID)%c_ident = c_ident
134
135 ! we could pass all 5 parameters if we felt like it...
136
137 StickyMap(myATID)%w0 = w0
138 StickyMap(myATID)%v0 = v0
139 StickyMap(myATID)%v0p = v0p
140 StickyMap(myATID)%rl = rl
141 StickyMap(myATID)%ru = ru
142 StickyMap(myATID)%rlp = rlp
143 StickyMap(myATID)%rup = rup
144
145 if (StickyMap(myATID)%ru .gt. StickyMap(myATID)%rup) then
146 StickyMap(myATID)%rbig = StickyMap(myATID)%ru
147 else
148 StickyMap(myATID)%rbig = StickyMap(myATID)%rup
149 endif
150
151 return
152 end subroutine newStickyType
153
154 function getStickyCut(atomID) result(cutValue)
155 integer, intent(in) :: atomID
156 real(kind=dp) :: cutValue
157
158 cutValue = StickyMap(atomID)%rbig
159 end function getStickyCut
160
161 function getStickyPowerCut(atomID) result(cutValue)
162 integer, intent(in) :: atomID
163 real(kind=dp) :: cutValue
164
165 cutValue = StickyMap(atomID)%rbig
166 end function getStickyPowerCut
167
168 subroutine do_sticky_pair(atom1, atom2, d, rij, r2, sw, vpair, fpair, &
169 pot, A, f, t, do_pot)
170
171 !! This routine does only the sticky portion of the SSD potential
172 !! [Chandra and Ichiye, J. Chem. Phys. 111, 2701 (1999)].
173 !! The Lennard-Jones and dipolar interaction must be handled separately.
174
175 !! We assume that the rotation matrices have already been calculated
176 !! and placed in the A array.
177
178 !! i and j are pointers to the two SSD atoms
179
180 integer, intent(in) :: atom1, atom2
181 real (kind=dp), intent(inout) :: rij, r2
182 real (kind=dp), dimension(3), intent(in) :: d
183 real (kind=dp), dimension(3), intent(inout) :: fpair
184 real (kind=dp) :: pot, vpair, sw
185 real (kind=dp), dimension(9,nLocal) :: A
186 real (kind=dp), dimension(3,nLocal) :: f
187 real (kind=dp), dimension(3,nLocal) :: t
188 logical, intent(in) :: do_pot
189
190 real (kind=dp) :: xi, yi, zi, xj, yj, zj, xi2, yi2, zi2, xj2, yj2, zj2
191 real (kind=dp) :: r3, r5, r6, s, sp, dsdr, dspdr
192 real (kind=dp) :: wi, wj, w, wip, wjp, wp
193 real (kind=dp) :: dwidx, dwidy, dwidz, dwjdx, dwjdy, dwjdz
194 real (kind=dp) :: dwipdx, dwipdy, dwipdz, dwjpdx, dwjpdy, dwjpdz
195 real (kind=dp) :: dwidux, dwiduy, dwiduz, dwjdux, dwjduy, dwjduz
196 real (kind=dp) :: dwipdux, dwipduy, dwipduz, dwjpdux, dwjpduy, dwjpduz
197 real (kind=dp) :: zif, zis, zjf, zjs, uglyi, uglyj
198 real (kind=dp) :: drdx, drdy, drdz
199 real (kind=dp) :: txi, tyi, tzi, txj, tyj, tzj
200 real (kind=dp) :: fxii, fyii, fzii, fxjj, fyjj, fzjj
201 real (kind=dp) :: fxij, fyij, fzij, fxji, fyji, fzji
202 real (kind=dp) :: fxradial, fyradial, fzradial
203 real (kind=dp) :: rijtest, rjitest
204 real (kind=dp) :: radcomxi, radcomyi, radcomzi
205 real (kind=dp) :: radcomxj, radcomyj, radcomzj
206 integer :: id1, id2
207 integer :: me1, me2
208 real (kind=dp) :: w0, v0, v0p, rl, ru, rlp, rup, rbig
209
210 if (.not.allocated(StickyMap)) then
211 call handleError("sticky", "no StickyMap was present before first call of do_sticky_pair!")
212 return
213 end if
214
215 #ifdef IS_MPI
216 me1 = atid_Row(atom1)
217 me2 = atid_Col(atom2)
218 #else
219 me1 = atid(atom1)
220 me2 = atid(atom2)
221 #endif
222
223 if (me1.eq.me2) then
224 w0 = StickyMap(me1)%w0
225 v0 = StickyMap(me1)%v0
226 v0p = StickyMap(me1)%v0p
227 rl = StickyMap(me1)%rl
228 ru = StickyMap(me1)%ru
229 rlp = StickyMap(me1)%rlp
230 rup = StickyMap(me1)%rup
231 rbig = StickyMap(me1)%rbig
232 else
233 ! This is silly, but if you want 2 sticky types in your
234 ! simulation, we'll let you do it with the Lorentz-
235 ! Berthelot mixing rules.
236 ! (Warning: you'll be SLLLLLLLLLLLLLLLOOOOOOOOOOWWWWWWWWWWW)
237 rl = 0.5_dp * ( StickyMap(me1)%rl + StickyMap(me2)%rl )
238 ru = 0.5_dp * ( StickyMap(me1)%ru + StickyMap(me2)%ru )
239 rlp = 0.5_dp * ( StickyMap(me1)%rlp + StickyMap(me2)%rlp )
240 rup = 0.5_dp * ( StickyMap(me1)%rup + StickyMap(me2)%rup )
241 rbig = max(ru, rup)
242 w0 = sqrt( StickyMap(me1)%w0 * StickyMap(me2)%w0 )
243 v0 = sqrt( StickyMap(me1)%v0 * StickyMap(me2)%v0 )
244 v0p = sqrt( StickyMap(me1)%v0p * StickyMap(me2)%v0p )
245 endif
246
247 if ( rij .LE. rbig ) then
248
249 r3 = r2*rij
250 r5 = r3*r2
251
252 drdx = d(1) / rij
253 drdy = d(2) / rij
254 drdz = d(3) / rij
255
256 #ifdef IS_MPI
257 ! rotate the inter-particle separation into the two different
258 ! body-fixed coordinate systems:
259
260 xi = A_row(1,atom1)*d(1) + A_row(2,atom1)*d(2) + A_row(3,atom1)*d(3)
261 yi = A_row(4,atom1)*d(1) + A_row(5,atom1)*d(2) + A_row(6,atom1)*d(3)
262 zi = A_row(7,atom1)*d(1) + A_row(8,atom1)*d(2) + A_row(9,atom1)*d(3)
263
264 ! negative sign because this is the vector from j to i:
265
266 xj = -(A_Col(1,atom2)*d(1) + A_Col(2,atom2)*d(2) + A_Col(3,atom2)*d(3))
267 yj = -(A_Col(4,atom2)*d(1) + A_Col(5,atom2)*d(2) + A_Col(6,atom2)*d(3))
268 zj = -(A_Col(7,atom2)*d(1) + A_Col(8,atom2)*d(2) + A_Col(9,atom2)*d(3))
269 #else
270 ! rotate the inter-particle separation into the two different
271 ! body-fixed coordinate systems:
272
273 xi = a(1,atom1)*d(1) + a(2,atom1)*d(2) + a(3,atom1)*d(3)
274 yi = a(4,atom1)*d(1) + a(5,atom1)*d(2) + a(6,atom1)*d(3)
275 zi = a(7,atom1)*d(1) + a(8,atom1)*d(2) + a(9,atom1)*d(3)
276
277 ! negative sign because this is the vector from j to i:
278
279 xj = -(a(1,atom2)*d(1) + a(2,atom2)*d(2) + a(3,atom2)*d(3))
280 yj = -(a(4,atom2)*d(1) + a(5,atom2)*d(2) + a(6,atom2)*d(3))
281 zj = -(a(7,atom2)*d(1) + a(8,atom2)*d(2) + a(9,atom2)*d(3))
282 #endif
283
284 xi2 = xi*xi
285 yi2 = yi*yi
286 zi2 = zi*zi
287
288 xj2 = xj*xj
289 yj2 = yj*yj
290 zj2 = zj*zj
291
292 call calc_sw_fnc(rij, rl, ru, rlp, rup, s, sp, dsdr, dspdr)
293
294 wi = 2.0d0*(xi2-yi2)*zi / r3
295 wj = 2.0d0*(xj2-yj2)*zj / r3
296 w = wi+wj
297
298 zif = zi/rij - 0.6d0
299 zis = zi/rij + 0.8d0
300
301 zjf = zj/rij - 0.6d0
302 zjs = zj/rij + 0.8d0
303
304 wip = zif*zif*zis*zis - w0
305 wjp = zjf*zjf*zjs*zjs - w0
306 wp = wip + wjp
307
308 vpair = vpair + 0.5d0*(v0*s*w + v0p*sp*wp)
309 if (do_pot) then
310 #ifdef IS_MPI
311 pot_row(STICKY_POT,atom1) = pot_row(STICKY_POT,atom1) + 0.25d0*(v0*s*w + v0p*sp*wp)*sw
312 pot_col(STICKY_POT,atom2) = pot_col(STICKY_POT,atom2) + 0.25d0*(v0*s*w + v0p*sp*wp)*sw
313 #else
314 pot = pot + 0.5d0*(v0*s*w + v0p*sp*wp)*sw
315 #endif
316 endif
317
318 dwidx = 4.0d0*xi*zi/r3 - 6.0d0*xi*zi*(xi2-yi2)/r5
319 dwidy = - 4.0d0*yi*zi/r3 - 6.0d0*yi*zi*(xi2-yi2)/r5
320 dwidz = 2.0d0*(xi2-yi2)/r3 - 6.0d0*zi2*(xi2-yi2)/r5
321
322 dwjdx = 4.0d0*xj*zj/r3 - 6.0d0*xj*zj*(xj2-yj2)/r5
323 dwjdy = - 4.0d0*yj*zj/r3 - 6.0d0*yj*zj*(xj2-yj2)/r5
324 dwjdz = 2.0d0*(xj2-yj2)/r3 - 6.0d0*zj2*(xj2-yj2)/r5
325
326 uglyi = zif*zif*zis + zif*zis*zis
327 uglyj = zjf*zjf*zjs + zjf*zjs*zjs
328
329 dwipdx = -2.0d0*xi*zi*uglyi/r3
330 dwipdy = -2.0d0*yi*zi*uglyi/r3
331 dwipdz = 2.0d0*(1.0d0/rij - zi2/r3)*uglyi
332
333 dwjpdx = -2.0d0*xj*zj*uglyj/r3
334 dwjpdy = -2.0d0*yj*zj*uglyj/r3
335 dwjpdz = 2.0d0*(1.0d0/rij - zj2/r3)*uglyj
336
337 dwidux = 4.0d0*(yi*zi2 + 0.5d0*yi*(xi2-yi2))/r3
338 dwiduy = 4.0d0*(xi*zi2 - 0.5d0*xi*(xi2-yi2))/r3
339 dwiduz = - 8.0d0*xi*yi*zi/r3
340
341 dwjdux = 4.0d0*(yj*zj2 + 0.5d0*yj*(xj2-yj2))/r3
342 dwjduy = 4.0d0*(xj*zj2 - 0.5d0*xj*(xj2-yj2))/r3
343 dwjduz = - 8.0d0*xj*yj*zj/r3
344
345 dwipdux = 2.0d0*yi*uglyi/rij
346 dwipduy = -2.0d0*xi*uglyi/rij
347 dwipduz = 0.0d0
348
349 dwjpdux = 2.0d0*yj*uglyj/rij
350 dwjpduy = -2.0d0*xj*uglyj/rij
351 dwjpduz = 0.0d0
352
353 ! do the torques first since they are easy:
354 ! remember that these are still in the body fixed axes
355
356 txi = 0.5d0*(v0*s*dwidux + v0p*sp*dwipdux)*sw
357 tyi = 0.5d0*(v0*s*dwiduy + v0p*sp*dwipduy)*sw
358 tzi = 0.5d0*(v0*s*dwiduz + v0p*sp*dwipduz)*sw
359
360 txj = 0.5d0*(v0*s*dwjdux + v0p*sp*dwjpdux)*sw
361 tyj = 0.5d0*(v0*s*dwjduy + v0p*sp*dwjpduy)*sw
362 tzj = 0.5d0*(v0*s*dwjduz + v0p*sp*dwjpduz)*sw
363
364 ! go back to lab frame using transpose of rotation matrix:
365
366 #ifdef IS_MPI
367 t_Row(1,atom1) = t_Row(1,atom1) + a_Row(1,atom1)*txi + &
368 a_Row(4,atom1)*tyi + a_Row(7,atom1)*tzi
369 t_Row(2,atom1) = t_Row(2,atom1) + a_Row(2,atom1)*txi + &
370 a_Row(5,atom1)*tyi + a_Row(8,atom1)*tzi
371 t_Row(3,atom1) = t_Row(3,atom1) + a_Row(3,atom1)*txi + &
372 a_Row(6,atom1)*tyi + a_Row(9,atom1)*tzi
373
374 t_Col(1,atom2) = t_Col(1,atom2) + a_Col(1,atom2)*txj + &
375 a_Col(4,atom2)*tyj + a_Col(7,atom2)*tzj
376 t_Col(2,atom2) = t_Col(2,atom2) + a_Col(2,atom2)*txj + &
377 a_Col(5,atom2)*tyj + a_Col(8,atom2)*tzj
378 t_Col(3,atom2) = t_Col(3,atom2) + a_Col(3,atom2)*txj + &
379 a_Col(6,atom2)*tyj + a_Col(9,atom2)*tzj
380 #else
381 t(1,atom1) = t(1,atom1) + a(1,atom1)*txi + a(4,atom1)*tyi + a(7,atom1)*tzi
382 t(2,atom1) = t(2,atom1) + a(2,atom1)*txi + a(5,atom1)*tyi + a(8,atom1)*tzi
383 t(3,atom1) = t(3,atom1) + a(3,atom1)*txi + a(6,atom1)*tyi + a(9,atom1)*tzi
384
385 t(1,atom2) = t(1,atom2) + a(1,atom2)*txj + a(4,atom2)*tyj + a(7,atom2)*tzj
386 t(2,atom2) = t(2,atom2) + a(2,atom2)*txj + a(5,atom2)*tyj + a(8,atom2)*tzj
387 t(3,atom2) = t(3,atom2) + a(3,atom2)*txj + a(6,atom2)*tyj + a(9,atom2)*tzj
388 #endif
389 ! Now, on to the forces:
390
391 ! first rotate the i terms back into the lab frame:
392
393 radcomxi = (v0*s*dwidx+v0p*sp*dwipdx)*sw
394 radcomyi = (v0*s*dwidy+v0p*sp*dwipdy)*sw
395 radcomzi = (v0*s*dwidz+v0p*sp*dwipdz)*sw
396
397 radcomxj = (v0*s*dwjdx+v0p*sp*dwjpdx)*sw
398 radcomyj = (v0*s*dwjdy+v0p*sp*dwjpdy)*sw
399 radcomzj = (v0*s*dwjdz+v0p*sp*dwjpdz)*sw
400
401 #ifdef IS_MPI
402 fxii = a_Row(1,atom1)*(radcomxi) + &
403 a_Row(4,atom1)*(radcomyi) + &
404 a_Row(7,atom1)*(radcomzi)
405 fyii = a_Row(2,atom1)*(radcomxi) + &
406 a_Row(5,atom1)*(radcomyi) + &
407 a_Row(8,atom1)*(radcomzi)
408 fzii = a_Row(3,atom1)*(radcomxi) + &
409 a_Row(6,atom1)*(radcomyi) + &
410 a_Row(9,atom1)*(radcomzi)
411
412 fxjj = a_Col(1,atom2)*(radcomxj) + &
413 a_Col(4,atom2)*(radcomyj) + &
414 a_Col(7,atom2)*(radcomzj)
415 fyjj = a_Col(2,atom2)*(radcomxj) + &
416 a_Col(5,atom2)*(radcomyj) + &
417 a_Col(8,atom2)*(radcomzj)
418 fzjj = a_Col(3,atom2)*(radcomxj)+ &
419 a_Col(6,atom2)*(radcomyj) + &
420 a_Col(9,atom2)*(radcomzj)
421 #else
422 fxii = a(1,atom1)*(radcomxi) + &
423 a(4,atom1)*(radcomyi) + &
424 a(7,atom1)*(radcomzi)
425 fyii = a(2,atom1)*(radcomxi) + &
426 a(5,atom1)*(radcomyi) + &
427 a(8,atom1)*(radcomzi)
428 fzii = a(3,atom1)*(radcomxi) + &
429 a(6,atom1)*(radcomyi) + &
430 a(9,atom1)*(radcomzi)
431
432 fxjj = a(1,atom2)*(radcomxj) + &
433 a(4,atom2)*(radcomyj) + &
434 a(7,atom2)*(radcomzj)
435 fyjj = a(2,atom2)*(radcomxj) + &
436 a(5,atom2)*(radcomyj) + &
437 a(8,atom2)*(radcomzj)
438 fzjj = a(3,atom2)*(radcomxj)+ &
439 a(6,atom2)*(radcomyj) + &
440 a(9,atom2)*(radcomzj)
441 #endif
442
443 fxij = -fxii
444 fyij = -fyii
445 fzij = -fzii
446
447 fxji = -fxjj
448 fyji = -fyjj
449 fzji = -fzjj
450
451 ! now assemble these with the radial-only terms:
452
453 fxradial = 0.5d0*(v0*dsdr*drdx*w + v0p*dspdr*drdx*wp + fxii + fxji)
454 fyradial = 0.5d0*(v0*dsdr*drdy*w + v0p*dspdr*drdy*wp + fyii + fyji)
455 fzradial = 0.5d0*(v0*dsdr*drdz*w + v0p*dspdr*drdz*wp + fzii + fzji)
456
457 #ifdef IS_MPI
458 f_Row(1,atom1) = f_Row(1,atom1) + fxradial
459 f_Row(2,atom1) = f_Row(2,atom1) + fyradial
460 f_Row(3,atom1) = f_Row(3,atom1) + fzradial
461
462 f_Col(1,atom2) = f_Col(1,atom2) - fxradial
463 f_Col(2,atom2) = f_Col(2,atom2) - fyradial
464 f_Col(3,atom2) = f_Col(3,atom2) - fzradial
465 #else
466 f(1,atom1) = f(1,atom1) + fxradial
467 f(2,atom1) = f(2,atom1) + fyradial
468 f(3,atom1) = f(3,atom1) + fzradial
469
470 f(1,atom2) = f(1,atom2) - fxradial
471 f(2,atom2) = f(2,atom2) - fyradial
472 f(3,atom2) = f(3,atom2) - fzradial
473 #endif
474
475 #ifdef IS_MPI
476 id1 = AtomRowToGlobal(atom1)
477 id2 = AtomColToGlobal(atom2)
478 #else
479 id1 = atom1
480 id2 = atom2
481 #endif
482
483 if (molMembershipList(id1) .ne. molMembershipList(id2)) then
484
485 fpair(1) = fpair(1) + fxradial
486 fpair(2) = fpair(2) + fyradial
487 fpair(3) = fpair(3) + fzradial
488
489 endif
490 endif
491 end subroutine do_sticky_pair
492
493 !! calculates the switching functions and their derivatives for a given
494 subroutine calc_sw_fnc(r, rl, ru, rlp, rup, s, sp, dsdr, dspdr)
495
496 real (kind=dp), intent(in) :: r, rl, ru, rlp, rup
497 real (kind=dp), intent(inout) :: s, sp, dsdr, dspdr
498
499 ! distances must be in angstroms
500
501 if (r.lt.rl) then
502 s = 1.0d0
503 dsdr = 0.0d0
504 elseif (r.gt.ru) then
505 s = 0.0d0
506 dsdr = 0.0d0
507 else
508 s = ((ru + 2.0d0*r - 3.0d0*rl) * (ru-r)**2) / &
509 ((ru - rl)**3)
510 dsdr = 6.0d0*(r-ru)*(r-rl)/((ru - rl)**3)
511 endif
512
513 if (r.lt.rlp) then
514 sp = 1.0d0
515 dspdr = 0.0d0
516 elseif (r.gt.rup) then
517 sp = 0.0d0
518 dspdr = 0.0d0
519 else
520 sp = ((rup + 2.0d0*r - 3.0d0*rlp) * (rup-r)**2) / &
521 ((rup - rlp)**3)
522 dspdr = 6.0d0*(r-rup)*(r-rlp)/((rup - rlp)**3)
523 endif
524
525 return
526 end subroutine calc_sw_fnc
527
528 subroutine destroyStickyTypes()
529 if(allocated(StickyMap)) deallocate(StickyMap)
530 end subroutine destroyStickyTypes
531
532 subroutine do_sticky_power_pair(atom1, atom2, d, rij, r2, sw, vpair, fpair, &
533 pot, A, f, t, do_pot)
534 !! We assume that the rotation matrices have already been calculated
535 !! and placed in the A array.
536
537 !! i and j are pointers to the two SSD atoms
538
539 integer, intent(in) :: atom1, atom2
540 real (kind=dp), intent(inout) :: rij, r2
541 real (kind=dp), dimension(3), intent(in) :: d
542 real (kind=dp), dimension(3), intent(inout) :: fpair
543 real (kind=dp) :: pot, vpair, sw
544 real (kind=dp), dimension(9,nLocal) :: A
545 real (kind=dp), dimension(3,nLocal) :: f
546 real (kind=dp), dimension(3,nLocal) :: t
547 logical, intent(in) :: do_pot
548
549 real (kind=dp) :: xi, yi, zi, xj, yj, zj, xi2, yi2, zi2, xj2, yj2, zj2
550 real (kind=dp) :: xihat, yihat, zihat, xjhat, yjhat, zjhat
551 real (kind=dp) :: rI, rI2, rI3, rI4, rI5, rI6, rI7, s, sp, dsdr, dspdr
552 real (kind=dp) :: wi, wj, w, wi2, wj2, eScale, v0scale
553 real (kind=dp) :: dwidx, dwidy, dwidz, dwjdx, dwjdy, dwjdz
554 real (kind=dp) :: dwidux, dwiduy, dwiduz, dwjdux, dwjduy, dwjduz
555 real (kind=dp) :: drdx, drdy, drdz
556 real (kind=dp) :: txi, tyi, tzi, txj, tyj, tzj
557 real (kind=dp) :: fxii, fyii, fzii, fxjj, fyjj, fzjj
558 real (kind=dp) :: fxij, fyij, fzij, fxji, fyji, fzji
559 real (kind=dp) :: fxradial, fyradial, fzradial
560 real (kind=dp) :: rijtest, rjitest
561 real (kind=dp) :: radcomxi, radcomyi, radcomzi
562 real (kind=dp) :: radcomxj, radcomyj, radcomzj
563 integer :: id1, id2
564 integer :: me1, me2
565 real (kind=dp) :: w0, v0, v0p, rl, ru, rlp, rup, rbig
566 real (kind=dp) :: zi3, zi4, zi5, zj3, zj4, zj5
567 real (kind=dp) :: frac1, frac2
568
569 if (.not.allocated(StickyMap)) then
570 call handleError("sticky", "no StickyMap was present before first call of do_sticky_power_pair!")
571 return
572 end if
573
574 #ifdef IS_MPI
575 me1 = atid_Row(atom1)
576 me2 = atid_Col(atom2)
577 #else
578 me1 = atid(atom1)
579 me2 = atid(atom2)
580 #endif
581
582 if (me1.eq.me2) then
583 w0 = StickyMap(me1)%w0
584 v0 = StickyMap(me1)%v0
585 v0p = StickyMap(me1)%v0p
586 rl = StickyMap(me1)%rl
587 ru = StickyMap(me1)%ru
588 rlp = StickyMap(me1)%rlp
589 rup = StickyMap(me1)%rup
590 rbig = StickyMap(me1)%rbig
591 else
592 ! This is silly, but if you want 2 sticky types in your
593 ! simulation, we'll let you do it with the Lorentz-
594 ! Berthelot mixing rules.
595 ! (Warning: you'll be SLLLLLLLLLLLLLLLOOOOOOOOOOWWWWWWWWWWW)
596 rl = 0.5_dp * ( StickyMap(me1)%rl + StickyMap(me2)%rl )
597 ru = 0.5_dp * ( StickyMap(me1)%ru + StickyMap(me2)%ru )
598 rlp = 0.5_dp * ( StickyMap(me1)%rlp + StickyMap(me2)%rlp )
599 rup = 0.5_dp * ( StickyMap(me1)%rup + StickyMap(me2)%rup )
600 rbig = max(ru, rup)
601 w0 = sqrt( StickyMap(me1)%w0 * StickyMap(me2)%w0 )
602 v0 = sqrt( StickyMap(me1)%v0 * StickyMap(me2)%v0 )
603 v0p = sqrt( StickyMap(me1)%v0p * StickyMap(me2)%v0p )
604 endif
605
606 if ( rij .LE. rbig ) then
607
608 rI = 1.0d0/rij
609 rI2 = rI*rI
610 rI3 = rI2*rI
611 rI4 = rI2*rI2
612 rI5 = rI3*rI2
613 rI6 = rI3*rI3
614 rI7 = rI4*rI3
615
616 drdx = d(1) * rI
617 drdy = d(2) * rI
618 drdz = d(3) * rI
619
620 #ifdef IS_MPI
621 ! rotate the inter-particle separation into the two different
622 ! body-fixed coordinate systems:
623
624 xi = A_row(1,atom1)*d(1) + A_row(2,atom1)*d(2) + A_row(3,atom1)*d(3)
625 yi = A_row(4,atom1)*d(1) + A_row(5,atom1)*d(2) + A_row(6,atom1)*d(3)
626 zi = A_row(7,atom1)*d(1) + A_row(8,atom1)*d(2) + A_row(9,atom1)*d(3)
627
628 ! negative sign because this is the vector from j to i:
629
630 xj = -(A_Col(1,atom2)*d(1) + A_Col(2,atom2)*d(2) + A_Col(3,atom2)*d(3))
631 yj = -(A_Col(4,atom2)*d(1) + A_Col(5,atom2)*d(2) + A_Col(6,atom2)*d(3))
632 zj = -(A_Col(7,atom2)*d(1) + A_Col(8,atom2)*d(2) + A_Col(9,atom2)*d(3))
633 #else
634 ! rotate the inter-particle separation into the two different
635 ! body-fixed coordinate systems:
636
637 xi = a(1,atom1)*d(1) + a(2,atom1)*d(2) + a(3,atom1)*d(3)
638 yi = a(4,atom1)*d(1) + a(5,atom1)*d(2) + a(6,atom1)*d(3)
639 zi = a(7,atom1)*d(1) + a(8,atom1)*d(2) + a(9,atom1)*d(3)
640
641 ! negative sign because this is the vector from j to i:
642
643 xj = -(a(1,atom2)*d(1) + a(2,atom2)*d(2) + a(3,atom2)*d(3))
644 yj = -(a(4,atom2)*d(1) + a(5,atom2)*d(2) + a(6,atom2)*d(3))
645 zj = -(a(7,atom2)*d(1) + a(8,atom2)*d(2) + a(9,atom2)*d(3))
646 #endif
647
648 xi2 = xi*xi
649 yi2 = yi*yi
650 zi2 = zi*zi
651 zi3 = zi2*zi
652 zi4 = zi2*zi2
653 zi5 = zi3*zi2
654 xihat = xi*rI
655 yihat = yi*rI
656 zihat = zi*rI
657
658 xj2 = xj*xj
659 yj2 = yj*yj
660 zj2 = zj*zj
661 zj3 = zj2*zj
662 zj4 = zj2*zj2
663 zj5 = zj3*zj2
664 xjhat = xj*rI
665 yjhat = yj*rI
666 zjhat = zj*rI
667
668 call calc_sw_fnc(rij, rl, ru, rlp, rup, s, sp, dsdr, dspdr)
669
670 frac1 = 0.25d0
671 frac2 = 0.75d0
672
673 wi = 2.0d0*(xi2-yi2)*zi*rI3
674 wj = 2.0d0*(xj2-yj2)*zj*rI3
675
676 wi2 = wi*wi
677 wj2 = wj*wj
678
679 w = frac1*wi*wi2 + frac2*wi + frac1*wj*wj2 + frac2*wj + v0p
680
681 vpair = vpair + 0.5d0*(v0*s*w)
682
683 if (do_pot) then
684 #ifdef IS_MPI
685 pot_row(STICKY_POT,atom1) = pot_row(STICKY_POT,atom1) + 0.25d0*(v0*s*w)*sw
686 pot_col(STICKY_POT,atom2) = pot_col(STICKY_POT,atom2) + 0.25d0*(v0*s*w)*sw
687 #else
688 pot = pot + 0.5d0*(v0*s*w)*sw
689 #endif
690 endif
691
692 dwidx = ( 4.0d0*xi*zi*rI3 - 6.0d0*xi*zi*(xi2-yi2)*rI5 )
693 dwidy = ( -4.0d0*yi*zi*rI3 - 6.0d0*yi*zi*(xi2-yi2)*rI5 )
694 dwidz = ( 2.0d0*(xi2-yi2)*rI3 - 6.0d0*zi2*(xi2-yi2)*rI5 )
695
696 dwidx = frac1*3.0d0*wi2*dwidx + frac2*dwidx
697 dwidy = frac1*3.0d0*wi2*dwidy + frac2*dwidy
698 dwidz = frac1*3.0d0*wi2*dwidz + frac2*dwidz
699
700 dwjdx = ( 4.0d0*xj*zj*rI3 - 6.0d0*xj*zj*(xj2-yj2)*rI5 )
701 dwjdy = ( -4.0d0*yj*zj*rI3 - 6.0d0*yj*zj*(xj2-yj2)*rI5 )
702 dwjdz = ( 2.0d0*(xj2-yj2)*rI3 - 6.0d0*zj2*(xj2-yj2)*rI5 )
703
704 dwjdx = frac1*3.0d0*wj2*dwjdx + frac2*dwjdx
705 dwjdy = frac1*3.0d0*wj2*dwjdy + frac2*dwjdy
706 dwjdz = frac1*3.0d0*wj2*dwjdz + frac2*dwjdz
707
708 dwidux = ( 4.0d0*(yi*zi2 + 0.5d0*yi*(xi2-yi2))*rI3 )
709 dwiduy = ( 4.0d0*(xi*zi2 - 0.5d0*xi*(xi2-yi2))*rI3 )
710 dwiduz = ( -8.0d0*xi*yi*zi*rI3 )
711
712 dwidux = frac1*3.0d0*wi2*dwidux + frac2*dwidux
713 dwiduy = frac1*3.0d0*wi2*dwiduy + frac2*dwiduy
714 dwiduz = frac1*3.0d0*wi2*dwiduz + frac2*dwiduz
715
716 dwjdux = ( 4.0d0*(yj*zj2 + 0.5d0*yj*(xj2-yj2))*rI3 )
717 dwjduy = ( 4.0d0*(xj*zj2 - 0.5d0*xj*(xj2-yj2))*rI3 )
718 dwjduz = ( -8.0d0*xj*yj*zj*rI3 )
719
720 dwjdux = frac1*3.0d0*wj2*dwjdux + frac2*dwjdux
721 dwjduy = frac1*3.0d0*wj2*dwjduy + frac2*dwjduy
722 dwjduz = frac1*3.0d0*wj2*dwjduz + frac2*dwjduz
723
724 ! do the torques first since they are easy:
725 ! remember that these are still in the body fixed axes
726
727 txi = 0.5d0*(v0*s*dwidux)*sw
728 tyi = 0.5d0*(v0*s*dwiduy)*sw
729 tzi = 0.5d0*(v0*s*dwiduz)*sw
730
731 txj = 0.5d0*(v0*s*dwjdux)*sw
732 tyj = 0.5d0*(v0*s*dwjduy)*sw
733 tzj = 0.5d0*(v0*s*dwjduz)*sw
734
735 ! go back to lab frame using transpose of rotation matrix:
736
737 #ifdef IS_MPI
738 t_Row(1,atom1) = t_Row(1,atom1) + a_Row(1,atom1)*txi + &
739 a_Row(4,atom1)*tyi + a_Row(7,atom1)*tzi
740 t_Row(2,atom1) = t_Row(2,atom1) + a_Row(2,atom1)*txi + &
741 a_Row(5,atom1)*tyi + a_Row(8,atom1)*tzi
742 t_Row(3,atom1) = t_Row(3,atom1) + a_Row(3,atom1)*txi + &
743 a_Row(6,atom1)*tyi + a_Row(9,atom1)*tzi
744
745 t_Col(1,atom2) = t_Col(1,atom2) + a_Col(1,atom2)*txj + &
746 a_Col(4,atom2)*tyj + a_Col(7,atom2)*tzj
747 t_Col(2,atom2) = t_Col(2,atom2) + a_Col(2,atom2)*txj + &
748 a_Col(5,atom2)*tyj + a_Col(8,atom2)*tzj
749 t_Col(3,atom2) = t_Col(3,atom2) + a_Col(3,atom2)*txj + &
750 a_Col(6,atom2)*tyj + a_Col(9,atom2)*tzj
751 #else
752 t(1,atom1) = t(1,atom1) + a(1,atom1)*txi + a(4,atom1)*tyi + a(7,atom1)*tzi
753 t(2,atom1) = t(2,atom1) + a(2,atom1)*txi + a(5,atom1)*tyi + a(8,atom1)*tzi
754 t(3,atom1) = t(3,atom1) + a(3,atom1)*txi + a(6,atom1)*tyi + a(9,atom1)*tzi
755
756 t(1,atom2) = t(1,atom2) + a(1,atom2)*txj + a(4,atom2)*tyj + a(7,atom2)*tzj
757 t(2,atom2) = t(2,atom2) + a(2,atom2)*txj + a(5,atom2)*tyj + a(8,atom2)*tzj
758 t(3,atom2) = t(3,atom2) + a(3,atom2)*txj + a(6,atom2)*tyj + a(9,atom2)*tzj
759 #endif
760 ! Now, on to the forces:
761
762 ! first rotate the i terms back into the lab frame:
763
764 radcomxi = (v0*s*dwidx)*sw
765 radcomyi = (v0*s*dwidy)*sw
766 radcomzi = (v0*s*dwidz)*sw
767
768 radcomxj = (v0*s*dwjdx)*sw
769 radcomyj = (v0*s*dwjdy)*sw
770 radcomzj = (v0*s*dwjdz)*sw
771
772 #ifdef IS_MPI
773 fxii = a_Row(1,atom1)*(radcomxi) + &
774 a_Row(4,atom1)*(radcomyi) + &
775 a_Row(7,atom1)*(radcomzi)
776 fyii = a_Row(2,atom1)*(radcomxi) + &
777 a_Row(5,atom1)*(radcomyi) + &
778 a_Row(8,atom1)*(radcomzi)
779 fzii = a_Row(3,atom1)*(radcomxi) + &
780 a_Row(6,atom1)*(radcomyi) + &
781 a_Row(9,atom1)*(radcomzi)
782
783 fxjj = a_Col(1,atom2)*(radcomxj) + &
784 a_Col(4,atom2)*(radcomyj) + &
785 a_Col(7,atom2)*(radcomzj)
786 fyjj = a_Col(2,atom2)*(radcomxj) + &
787 a_Col(5,atom2)*(radcomyj) + &
788 a_Col(8,atom2)*(radcomzj)
789 fzjj = a_Col(3,atom2)*(radcomxj)+ &
790 a_Col(6,atom2)*(radcomyj) + &
791 a_Col(9,atom2)*(radcomzj)
792 #else
793 fxii = a(1,atom1)*(radcomxi) + &
794 a(4,atom1)*(radcomyi) + &
795 a(7,atom1)*(radcomzi)
796 fyii = a(2,atom1)*(radcomxi) + &
797 a(5,atom1)*(radcomyi) + &
798 a(8,atom1)*(radcomzi)
799 fzii = a(3,atom1)*(radcomxi) + &
800 a(6,atom1)*(radcomyi) + &
801 a(9,atom1)*(radcomzi)
802
803 fxjj = a(1,atom2)*(radcomxj) + &
804 a(4,atom2)*(radcomyj) + &
805 a(7,atom2)*(radcomzj)
806 fyjj = a(2,atom2)*(radcomxj) + &
807 a(5,atom2)*(radcomyj) + &
808 a(8,atom2)*(radcomzj)
809 fzjj = a(3,atom2)*(radcomxj)+ &
810 a(6,atom2)*(radcomyj) + &
811 a(9,atom2)*(radcomzj)
812 #endif
813
814 fxij = -fxii
815 fyij = -fyii
816 fzij = -fzii
817
818 fxji = -fxjj
819 fyji = -fyjj
820 fzji = -fzjj
821
822 ! now assemble these with the radial-only terms:
823
824 fxradial = 0.5d0*(v0*dsdr*w*drdx + fxii + fxji)
825 fyradial = 0.5d0*(v0*dsdr*w*drdy + fyii + fyji)
826 fzradial = 0.5d0*(v0*dsdr*w*drdz + fzii + fzji)
827
828 #ifdef IS_MPI
829 f_Row(1,atom1) = f_Row(1,atom1) + fxradial
830 f_Row(2,atom1) = f_Row(2,atom1) + fyradial
831 f_Row(3,atom1) = f_Row(3,atom1) + fzradial
832
833 f_Col(1,atom2) = f_Col(1,atom2) - fxradial
834 f_Col(2,atom2) = f_Col(2,atom2) - fyradial
835 f_Col(3,atom2) = f_Col(3,atom2) - fzradial
836 #else
837 f(1,atom1) = f(1,atom1) + fxradial
838 f(2,atom1) = f(2,atom1) + fyradial
839 f(3,atom1) = f(3,atom1) + fzradial
840
841 f(1,atom2) = f(1,atom2) - fxradial
842 f(2,atom2) = f(2,atom2) - fyradial
843 f(3,atom2) = f(3,atom2) - fzradial
844 #endif
845
846 #ifdef IS_MPI
847 id1 = AtomRowToGlobal(atom1)
848 id2 = AtomColToGlobal(atom2)
849 #else
850 id1 = atom1
851 id2 = atom2
852 #endif
853
854 if (molMembershipList(id1) .ne. molMembershipList(id2)) then
855
856 fpair(1) = fpair(1) + fxradial
857 fpair(2) = fpair(2) + fyradial
858 fpair(3) = fpair(3) + fzradial
859
860 endif
861 endif
862 end subroutine do_sticky_power_pair
863
864 end module sticky