ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/DarkSide/sticky.F90
Revision: 2229
Committed: Tue May 17 22:35:01 2005 UTC (19 years, 2 months ago) by chrisfen
File size: 31764 byte(s)
Log Message:
Modifications to tap.  Also correcting changes to the previous merge that were not caught

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