ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/OpenMD/trunk/src/UseTheForce/DarkSide/MetalNonMetal.F90
Revision: 1284
Committed: Thu Jul 31 18:40:21 2008 UTC (16 years, 11 months ago) by gezelter
File size: 30068 byte(s)
Log Message:
fixed a strange compiler structure alignment problem with the
intel Mac compiler  (structs that cross between C and fortran
appear to need 8-byte boundary alignment on this compiler).

File Contents

# Content
1 !!
2 !! Copyright (c) 2007 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
43 !! Calculates Metal-Non Metal interactions.
44 !! @author Charles F. Vardeman II
45 !! @version $Id: MetalNonMetal.F90,v 1.16 2008-07-31 18:40:21 gezelter Exp $, $Date: 2008-07-31 18:40:21 $, $Name: not supported by cvs2svn $, $Revision: 1.16 $
46
47
48 module MetalNonMetal
49 use definitions
50 use atype_module
51 use vector_class
52 use simulation
53 use status
54 use fForceOptions
55 #ifdef IS_MPI
56 use mpiSimulation
57 #endif
58 use force_globals
59
60 implicit none
61 PRIVATE
62 #define __FORTRAN90
63 #include "UseTheForce/DarkSide/fInteractionMap.h"
64 #include "UseTheForce/DarkSide/fMnMInteractions.h"
65
66 logical, save :: useGeometricDistanceMixing = .false.
67 logical, save :: haveInteractionLookup = .false.
68
69 real(kind=DP), save :: defaultCutoff = 0.0_DP
70
71 logical, save :: defaultShiftPot = .false.
72 logical, save :: defaultShiftFrc = .false.
73 logical, save :: haveDefaultCutoff = .false.
74
75 type :: MnMinteraction
76 integer :: metal_atid
77 integer :: nonmetal_atid
78 integer :: interaction_type
79 real(kind=dp) :: R0
80 real(kind=dp) :: D0
81 real(kind=dp) :: beta0
82 real(kind=dp) :: betaH
83 real(kind=dp) :: ca1
84 real(kind=dp) :: cb1
85 real(kind=dp) :: sigma
86 real(kind=dp) :: epsilon
87 real(kind=dp) :: rCut = 0.0_dp
88 logical :: rCutWasSet = .false.
89 logical :: shiftedPot = .false.
90 logical :: shiftedFrc = .false.
91 end type MnMinteraction
92
93 type :: MnMinteractionMap
94 PRIVATE
95 integer :: initialCapacity = 10
96 integer :: capacityIncrement = 0
97 integer :: interactionCount = 0
98 type(MnMinteraction), pointer :: interactions(:) => null()
99 end type MnMinteractionMap
100
101 type (MnMInteractionMap), pointer :: MnM_Map
102
103 integer, allocatable, dimension(:,:) :: MnMinteractionLookup
104
105 public :: setMnMDefaultCutoff
106 public :: addInteraction
107 public :: deleteInteractions
108 public :: MNMtype
109 public :: do_mnm_pair
110
111 contains
112
113
114 subroutine do_mnm_pair(Atom1, Atom2, D, Rij, R2, Rcut, Sw, Vpair, Fpair, &
115 Pot, A, F,t, Do_pot)
116 integer, intent(in) :: atom1, atom2
117 integer :: atid1, atid2, ljt1, ljt2
118 real( kind = dp ), intent(in) :: rij, r2, rcut
119 real( kind = dp ) :: pot, sw, vpair
120 real( kind = dp ), intent(inout), dimension(3,nLocal) :: f
121 real (kind=dp), intent(in), dimension(9,nLocal) :: A
122 real (kind=dp), intent(inout), dimension(3,nLocal) :: t
123 real( kind = dp ), intent(in), dimension(3) :: d
124 real( kind = dp ), intent(inout), dimension(3) :: fpair
125 logical, intent(in) :: do_pot
126
127 integer :: interaction_id
128 integer :: interaction_type
129
130 #ifdef IS_MPI
131 atid1 = atid_Row(atom1)
132 atid2 = atid_Col(atom2)
133 #else
134 atid1 = atid(atom1)
135 atid2 = atid(atom2)
136 #endif
137
138 if(.not.haveInteractionLookup) then
139 call createInteractionLookup(MnM_MAP)
140 haveInteractionLookup =.true.
141 end if
142
143 interaction_id = MnMinteractionLookup(atid1, atid2)
144 interaction_type = MnM_Map%interactions(interaction_id)%interaction_type
145
146 select case (interaction_type)
147 case (MNM_LENNARDJONES)
148 call calc_mnm_lennardjones(Atom1, Atom2, D, Rij, R2, Rcut, Sw, Vpair, &
149 Fpair, Pot, F, Do_pot, interaction_id)
150 case(MNM_REPULSIVEMORSE, MNM_SHIFTEDMORSE)
151 call calc_mnm_morse(Atom1, Atom2, D, Rij, R2, Rcut, Sw, Vpair, Fpair, &
152 Pot, F, Do_pot, interaction_id, interaction_type)
153 case(MNM_MAW)
154 call calc_mnm_maw(Atom1, Atom2, D, Rij, R2, Rcut, Sw, Vpair, Fpair, &
155 Pot,A, F,t, Do_pot, interaction_id)
156 case default
157 call handleError("MetalNonMetal","Unknown interaction type")
158 end select
159
160 end subroutine do_mnm_pair
161
162 subroutine calc_mnm_lennardjones(Atom1, Atom2, D, Rij, R2, Rcut, Sw, Vpair, &
163 Fpair, Pot, F, Do_pot, interaction_id)
164
165 integer, intent(in) :: atom1, atom2
166 real( kind = dp ), intent(in) :: rij, r2, rcut
167 real( kind = dp ) :: pot, sw, vpair
168 real( kind = dp ), intent(inout), dimension(3,nLocal) :: f
169 real( kind = dp ), intent(in), dimension(3) :: d
170 real( kind = dp ), intent(inout), dimension(3) :: fpair
171 logical, intent(in) :: do_pot
172 integer, intent(in) :: interaction_id
173
174 ! local Variables
175 real( kind = dp ) :: drdx, drdy, drdz
176 real( kind = dp ) :: fx, fy, fz
177 real( kind = dp ) :: myPot, myPotC, myDeriv, myDerivC, ros, rcos
178 real( kind = dp ) :: pot_temp, dudr
179 real( kind = dp ) :: sigmai
180 real( kind = dp ) :: epsilon
181 logical :: isSoftCore, shiftedPot, shiftedFrc
182 integer :: id1, id2, localError
183
184 sigmai = 1.0_dp / MnM_Map%interactions(interaction_id)%sigma
185 epsilon = MnM_Map%interactions(interaction_id)%epsilon
186 shiftedPot = MnM_Map%interactions(interaction_id)%shiftedPot
187 shiftedFrc = MnM_Map%interactions(interaction_id)%shiftedFrc
188
189
190
191
192 ros = rij * sigmai
193
194 call getLJfunc(ros, myPot, myDeriv)
195
196 if (shiftedPot) then
197 rcos = rcut * sigmai
198 call getLJfunc(rcos, myPotC, myDerivC)
199 myDerivC = 0.0_dp
200 elseif (shiftedFrc) then
201 rcos = rcut * sigmai
202 call getLJfunc(rcos, myPotC, myDerivC)
203 myPotC = myPotC + myDerivC * (rij - rcut) * sigmai
204 else
205 myPotC = 0.0_dp
206 myDerivC = 0.0_dp
207 endif
208
209 pot_temp = epsilon * (myPot - myPotC)
210 vpair = vpair + pot_temp
211 dudr = sw * epsilon * (myDeriv - myDerivC) * sigmai
212
213 drdx = d(1) / rij
214 drdy = d(2) / rij
215 drdz = d(3) / rij
216
217 fx = dudr * drdx
218 fy = dudr * drdy
219 fz = dudr * drdz
220
221 #ifdef IS_MPI
222 if (do_pot) then
223 pot_Row(VDW_POT,atom1) = pot_Row(VDW_POT,atom1) + sw*pot_temp*0.5
224 pot_Col(VDW_POT,atom2) = pot_Col(VDW_POT,atom2) + sw*pot_temp*0.5
225 endif
226
227 f_Row(1,atom1) = f_Row(1,atom1) + fx
228 f_Row(2,atom1) = f_Row(2,atom1) + fy
229 f_Row(3,atom1) = f_Row(3,atom1) + fz
230
231 f_Col(1,atom2) = f_Col(1,atom2) - fx
232 f_Col(2,atom2) = f_Col(2,atom2) - fy
233 f_Col(3,atom2) = f_Col(3,atom2) - fz
234
235 #else
236 if (do_pot) pot = pot + sw*pot_temp
237
238 f(1,atom1) = f(1,atom1) + fx
239 f(2,atom1) = f(2,atom1) + fy
240 f(3,atom1) = f(3,atom1) + fz
241
242 f(1,atom2) = f(1,atom2) - fx
243 f(2,atom2) = f(2,atom2) - fy
244 f(3,atom2) = f(3,atom2) - fz
245 #endif
246
247 #ifdef IS_MPI
248 id1 = AtomRowToGlobal(atom1)
249 id2 = AtomColToGlobal(atom2)
250 #else
251 id1 = atom1
252 id2 = atom2
253 #endif
254
255 if (molMembershipList(id1) .ne. molMembershipList(id2)) then
256
257 fpair(1) = fpair(1) + fx
258 fpair(2) = fpair(2) + fy
259 fpair(3) = fpair(3) + fz
260
261 endif
262 return
263 end subroutine calc_mnm_lennardjones
264
265 subroutine calc_mnm_morse(Atom1, Atom2, D, Rij, R2, Rcut, Sw, Vpair, Fpair, &
266 Pot, f, Do_pot, interaction_id, interaction_type)
267 integer, intent(in) :: atom1, atom2
268 real( kind = dp ), intent(in) :: rij, r2, rcut
269 real( kind = dp ) :: pot, sw, vpair
270 real( kind = dp ), intent(inout), dimension(3,nLocal) :: f
271 real( kind = dp ), intent(in), dimension(3) :: d
272 real( kind = dp ), intent(inout), dimension(3) :: fpair
273 logical, intent(in) :: do_pot
274 integer, intent(in) :: interaction_id, interaction_type
275 logical :: shiftedPot, shiftedFrc
276
277 ! Local Variables
278 real(kind=dp) :: Beta0
279 real(kind=dp) :: R0
280 real(kind=dp) :: D0
281 real(kind=dp) :: expt
282 real(kind=dp) :: expt2
283 real(kind=dp) :: expfnc
284 real(kind=dp) :: expfnc2
285 real(kind=dp) :: D_expt
286 real(kind=dp) :: D_expt2
287 real(kind=dp) :: rcos
288 real(kind=dp) :: exptC
289 real(kind=dp) :: expt2C
290 real(kind=dp) :: expfncC
291 real(kind=dp) :: expfnc2C
292 real(kind=dp) :: D_expt2C
293 real(kind=dp) :: D_exptC
294
295 real(kind=dp) :: myPot
296 real(kind=dp) :: myPotC
297 real(kind=dp) :: myDeriv
298 real(kind=dp) :: myDerivC
299 real(kind=dp) :: pot_temp
300 real(kind=dp) :: fx,fy,fz
301 real(kind=dp) :: drdx,drdy,drdz
302 real(kind=dp) :: dudr
303 integer :: id1,id2
304
305
306 D0 = MnM_Map%interactions(interaction_id)%D0
307 R0 = MnM_Map%interactions(interaction_id)%r0
308 Beta0 = MnM_Map%interactions(interaction_id)%Beta0
309 shiftedPot = MnM_Map%interactions(interaction_id)%shiftedPot
310 shiftedFrc = MnM_Map%interactions(interaction_id)%shiftedFrc
311
312 ! V(r) = D_e exp(-a(r-re)(exp(-a(r-re))-2)
313
314 expt = -beta0*(rij - R0)
315 expfnc = exp(expt)
316 expfnc2 = expfnc*expfnc
317
318 if (shiftedPot .or. shiftedFrc) then
319 exptC = -beta0*(rcut - R0)
320 expfncC = exp(exptC)
321 expfnc2C = expfncC*expfncC
322 endif
323
324 select case (interaction_type)
325 case (MNM_SHIFTEDMORSE)
326
327 myPot = D0 * (expfnc2 - 2.0_dp * expfnc)
328 myDeriv = 2.0*D0*beta0*(expfnc - expfnc2)
329
330 if (shiftedPot) then
331 myPotC = D0 * (expfnc2C - 2.0_dp * expfncC)
332 myDerivC = 0.0_dp
333 elseif (shiftedFrc) then
334 myPotC = D0 * (expfnc2C - 2.0_dp * expfncC)
335 myDerivC = 2.0*D0*beta0*(expfnc2C - expfnc2C)
336 myPotC = myPotC + myDerivC * (rij - rcut)
337 else
338 myPotC = 0.0_dp
339 myDerivC = 0.0_dp
340 endif
341
342 case (MNM_REPULSIVEMORSE)
343
344 myPot = D0 * expfnc2
345 myDeriv = -2.0_dp * D0 * beta0 * expfnc2
346
347 if (shiftedPot) then
348 myPotC = D0 * expfnc2C
349 myDerivC = 0.0_dp
350 elseif (shiftedFrc) then
351 myPotC = D0 * expfnc2C
352 myDerivC = -2.0_dp * D0* beta0 * expfnc2C
353 myPotC = myPotC + myDerivC * (rij - rcut)
354 else
355 myPotC = 0.0_dp
356 myDerivC = 0.0_dp
357 endif
358 end select
359
360 pot_temp = (myPot - myPotC)
361 vpair = vpair + pot_temp
362 dudr = sw * (myDeriv - myDerivC)
363
364 drdx = d(1) / rij
365 drdy = d(2) / rij
366 drdz = d(3) / rij
367
368 fx = dudr * drdx
369 fy = dudr * drdy
370 fz = dudr * drdz
371
372 #ifdef IS_MPI
373 if (do_pot) then
374 pot_Row(VDW_POT,atom1) = pot_Row(VDW_POT,atom1) + sw*pot_temp*0.5
375 pot_Col(VDW_POT,atom2) = pot_Col(VDW_POT,atom2) + sw*pot_temp*0.5
376 endif
377
378 f_Row(1,atom1) = f_Row(1,atom1) + fx
379 f_Row(2,atom1) = f_Row(2,atom1) + fy
380 f_Row(3,atom1) = f_Row(3,atom1) + fz
381
382 f_Col(1,atom2) = f_Col(1,atom2) - fx
383 f_Col(2,atom2) = f_Col(2,atom2) - fy
384 f_Col(3,atom2) = f_Col(3,atom2) - fz
385
386 #else
387 if (do_pot) pot = pot + sw*pot_temp
388
389 f(1,atom1) = f(1,atom1) + fx
390 f(2,atom1) = f(2,atom1) + fy
391 f(3,atom1) = f(3,atom1) + fz
392
393 f(1,atom2) = f(1,atom2) - fx
394 f(2,atom2) = f(2,atom2) - fy
395 f(3,atom2) = f(3,atom2) - fz
396 #endif
397
398 #ifdef IS_MPI
399 id1 = AtomRowToGlobal(atom1)
400 id2 = AtomColToGlobal(atom2)
401 #else
402 id1 = atom1
403 id2 = atom2
404 #endif
405
406 if (molMembershipList(id1) .ne. molMembershipList(id2)) then
407
408 fpair(1) = fpair(1) + fx
409 fpair(2) = fpair(2) + fy
410 fpair(3) = fpair(3) + fz
411
412 endif
413
414 return
415 end subroutine calc_mnm_morse
416
417 subroutine calc_mnm_maw(Atom1, Atom2, D, Rij, R2, Rcut, Sw, Vpair, Fpair, &
418 Pot, A, F,t, Do_pot, interaction_id)
419 integer, intent(in) :: atom1, atom2
420 real( kind = dp ), intent(in) :: rij, r2, rcut
421 real( kind = dp ) :: pot, sw, vpair
422 real( kind = dp ), intent(inout), dimension(3,nLocal) :: f
423 real (kind=dp),intent(in), dimension(9,nLocal) :: A
424 real (kind=dp),intent(inout), dimension(3,nLocal) :: t
425
426 real( kind = dp ), intent(in), dimension(3) :: d
427 real( kind = dp ), intent(inout), dimension(3) :: fpair
428 logical, intent(in) :: do_pot
429
430 integer, intent(in) :: interaction_id
431
432 real(kind = dp) :: D0, R0, beta0, ca1, cb1, pot_temp
433 real(kind = dp) :: expt0, expfnc0, expfnc02
434 real(kind = dp) :: exptH, expfncH, expfncH2
435 real(kind = dp) :: x, y, z, x2, y2, z2, r3, r4
436 real(kind = dp) :: drdx, drdy, drdz
437 real(kind = dp) :: dvdx, dvdy, dvdz
438 real(kind = dp) :: Vang, dVangdx, dVangdy, dVangdz
439 real(kind = dp) :: dVangdux, dVangduy, dVangduz
440 real(kind = dp) :: dVmorsedr
441 real(kind = dp) :: Vmorse, dVmorsedx, dVmorsedy, dVmorsedz
442 real(kind = dp) :: a1, b1, s
443 real(kind = dp) :: da1dx, da1dy, da1dz, da1dux, da1duy, da1duz
444 real(kind = dp) :: db1dx, db1dy, db1dz, db1dux, db1duy, db1duz
445 real(kind = dp) :: fx, fy, fz, tx, ty, tz, fxl, fyl, fzl
446 real(kind = dp), parameter :: st = sqrt(3.0_dp)
447 integer :: atid1, atid2, id1, id2
448 logical :: shiftedPot, shiftedFrc
449
450 #ifdef IS_MPI
451 atid1 = atid_Row(atom1)
452 atid2 = atid_Col(atom2)
453
454 if (atid2.eq.MnM_Map%interactions(interaction_id)%metal_atid) then
455 ! rotate the inter-particle separation into the two different
456 ! body-fixed coordinate systems:
457
458 x = A_row(1,atom1)*d(1) + A_row(2,atom1)*d(2) + A_row(3,atom1)*d(3)
459 y = A_row(4,atom1)*d(1) + A_row(5,atom1)*d(2) + A_row(6,atom1)*d(3)
460 z = A_row(7,atom1)*d(1) + A_row(8,atom1)*d(2) + A_row(9,atom1)*d(3)
461 else
462 ! negative sign because this is the vector from j to i:
463
464 x = -(A_Col(1,atom2)*d(1) + A_Col(2,atom2)*d(2) + A_Col(3,atom2)*d(3))
465 y = -(A_Col(4,atom2)*d(1) + A_Col(5,atom2)*d(2) + A_Col(6,atom2)*d(3))
466 z = -(A_Col(7,atom2)*d(1) + A_Col(8,atom2)*d(2) + A_Col(9,atom2)*d(3))
467 endif
468
469 #else
470 atid1 = atid(atom1)
471 atid2 = atid(atom2)
472
473 if (atid2.eq.MnM_Map%interactions(interaction_id)%metal_atid) then
474 ! rotate the inter-particle separation into the two different
475 ! body-fixed coordinate systems:
476
477 x = a(1,atom1)*d(1) + a(2,atom1)*d(2) + a(3,atom1)*d(3)
478 y = a(4,atom1)*d(1) + a(5,atom1)*d(2) + a(6,atom1)*d(3)
479 z = a(7,atom1)*d(1) + a(8,atom1)*d(2) + a(9,atom1)*d(3)
480 else
481 ! negative sign because this is the vector from j to i:
482
483 x = -(a(1,atom2)*d(1) + a(2,atom2)*d(2) + a(3,atom2)*d(3))
484 y = -(a(4,atom2)*d(1) + a(5,atom2)*d(2) + a(6,atom2)*d(3))
485 z = -(a(7,atom2)*d(1) + a(8,atom2)*d(2) + a(9,atom2)*d(3))
486 endif
487
488 #endif
489
490 D0 = MnM_Map%interactions(interaction_id)%D0
491 R0 = MnM_Map%interactions(interaction_id)%r0
492 beta0 = MnM_Map%interactions(interaction_id)%beta0
493 ca1 = MnM_Map%interactions(interaction_id)%ca1
494 cb1 = MnM_Map%interactions(interaction_id)%cb1
495
496 shiftedPot = MnM_Map%interactions(interaction_id)%shiftedPot
497 shiftedFrc = MnM_Map%interactions(interaction_id)%shiftedFrc
498
499 expt0 = -beta0*(rij - R0)
500 expfnc0 = exp(expt0)
501 expfnc02 = expfnc0*expfnc0
502
503 !!$ if (shiftedPot .or. shiftedFrc) then
504 !!$ exptC0 = -beta0*(rcut - R0)
505 !!$ expfncC0 = exp(exptC0)
506 !!$ expfncC02 = expfncC0*expfncC0
507 !!$ exptCH = -betaH*(rcut - R0)
508 !!$ expfncCH = exp(exptCH)
509 !!$ expfncCH2 = expfncCH*expfncCH
510 !!$ endif
511
512 drdx = x / rij
513 drdy = y / rij
514 drdz = z / rij
515
516 x2 = x*x
517 y2 = y*y
518 z2 = z*z
519 r3 = r2*rij
520 r4 = r2*r2
521
522 Vmorse = D0 * (expfnc02 - 2.0_dp * expfnc0)
523
524 ! angular modulation of morse part of potential to approximate
525 ! the squares of the two HOMO lone pair orbitals in water:
526 !********************** old form*************************
527 ! s = 1 / (4 pi)
528 ! a1 = (s - pz)^2 = (1 - sqrt(3)*cos(theta))^2 / (4 pi)
529 ! b1 = px^2 = 3 * (sin(theta)*cos(phi))^2 / (4 pi)
530 !********************** old form*************************
531 ! we'll leave out the 4 pi for now
532
533 ! new functional form just using the p orbitals.
534 ! Vmorse(r)*[a*p_x + b p_z + (1-a-b)]
535 ! which is
536 ! Vmorse(r)*[a sin^2(theta) cos^2(phi) + b cos(theta) + (1-a-b)]
537 ! Vmorse(r)*[a*x2/r2 + b*z/r + (1-a-b)]
538
539
540
541 s = 1.0_dp
542 ! a1 = (1.0_dp - st * z / rij )**2
543 ! b1 = 3.0_dp * x2 / r2
544
545 ! Vang = s + ca1 * a1 + cb1 * b1
546
547 Vang = ca1 * x2/r2 + cb1 * z/rij + (0.8_dp-ca1/3.0_dp)
548
549 pot_temp = Vmorse*Vang
550
551 vpair = vpair + pot_temp
552
553 if (do_pot) then
554 #ifdef IS_MPI
555 pot_row(VDW_POT,atom1) = pot_row(VDW_POT,atom1) + 0.5_dp*pot_temp*sw
556 pot_col(VDW_POT,atom2) = pot_col(VDW_POT,atom2) + 0.5_dp*pot_temp*sw
557 #else
558 pot = pot + pot_temp*sw
559 #endif
560 endif
561
562 dVmorsedr = 2.0_dp*D0*beta0*(expfnc0 - expfnc02)
563
564 dVmorsedx = dVmorsedr * drdx
565 dVmorsedy = dVmorsedr * drdy
566 dVmorsedz = dVmorsedr * drdz
567
568 !da1dx = 2.0_dp * st * x * z / r3 - 6.0_dp * x * z2 / r4
569 !da1dy = 2.0_dp * st * y * z / r3 - 6.0_dp * y * z2 / r4
570 !da1dz = 2.0_dp * st * (x2 + y2) * (st * z - rij ) / r4
571
572 !db1dx = 6.0_dp * x * (1.0_dp - x2 / r2) / r2
573 !db1dy = -6.0_dp * x2 * y / r4
574 !db1dz = -6.0_dp * x2 * z / r4
575
576 !dVangdx = ca1 * da1dx + cb1 * db1dx
577 !dVangdy = ca1 * da1dy + cb1 * db1dy
578 !dVangdz = ca1 * da1dz + cb1 * db1dz
579
580 dVangdx = -2.0*ca1*x2*x/r4 + 2.0*ca1*x/r2 - cb1*x*z/r3
581 dVangdy = -2.0*ca1*x2*y/r4 - cb1*z*y/r3
582 dVangdz = -2.0*ca1*x2*z/r4 + cb1/rij - cb1*z2 /r3
583
584 ! chain rule to put these back on x, y, z
585 dvdx = Vang * dVmorsedx + Vmorse * dVangdx
586 dvdy = Vang * dVmorsedy + Vmorse * dVangdy
587 dvdz = Vang * dVmorsedz + Vmorse * dVangdz
588
589 ! Torques for Vang using method of Price:
590 ! S. L. Price, A. J. Stone, and M. Alderton, Mol. Phys. 52, 987 (1984).
591
592 !da1dux = 6.0_dp * y * z / r2 - 2.0_dp * st * y / rij
593 !da1duy = -6.0_dp * x * z / r2 + 2.0_dp * st * x / rij
594 !da1duz = 0.0_dp
595
596 !db1dux = 0.0_dp
597 !db1duy = 6.0_dp * x * z / r2
598 !db1duz = -6.0_dp * y * x / r2
599
600 !dVangdux = ca1 * da1dux + cb1 * db1dux
601 !dVangduy = ca1 * da1duy + cb1 * db1duy
602 !dVangduz = ca1 * da1duz + cb1 * db1duz
603
604 dVangdux = cb1*y/rij
605 dVangduy = 2.0*ca1*x*z/r2 - cb1*x/rij
606 dVangduz = -2.0*ca1*y*x/r2
607
608 ! do the torques first since they are easy:
609 ! remember that these are still in the body fixed axes
610
611 tx = Vmorse * dVangdux * sw
612 ty = Vmorse * dVangduy * sw
613 tz = Vmorse * dVangduz * sw
614
615 ! go back to lab frame using transpose of rotation matrix:
616
617 #ifdef IS_MPI
618 if (atid2.eq.MnM_Map%interactions(interaction_id)%metal_atid) then
619 t_Row(1,atom1) = t_Row(1,atom1) + a_Row(1,atom1)*tx + &
620 a_Row(4,atom1)*ty + a_Row(7,atom1)*tz
621 t_Row(2,atom1) = t_Row(2,atom1) + a_Row(2,atom1)*tx + &
622 a_Row(5,atom1)*ty + a_Row(8,atom1)*tz
623 t_Row(3,atom1) = t_Row(3,atom1) + a_Row(3,atom1)*tx + &
624 a_Row(6,atom1)*ty + a_Row(9,atom1)*tz
625 else
626 t_Col(1,atom2) = t_Col(1,atom2) + a_Col(1,atom2)*tx + &
627 a_Col(4,atom2)*ty + a_Col(7,atom2)*tz
628 t_Col(2,atom2) = t_Col(2,atom2) + a_Col(2,atom2)*tx + &
629 a_Col(5,atom2)*ty + a_Col(8,atom2)*tz
630 t_Col(3,atom2) = t_Col(3,atom2) + a_Col(3,atom2)*tx + &
631 a_Col(6,atom2)*ty + a_Col(9,atom2)*tz
632 endif
633 #else
634 if (atid2.eq.MnM_Map%interactions(interaction_id)%metal_atid) then
635 t(1,atom1) = t(1,atom1) + a(1,atom1)*tx + a(4,atom1)*ty + &
636 a(7,atom1)*tz
637 t(2,atom1) = t(2,atom1) + a(2,atom1)*tx + a(5,atom1)*ty + &
638 a(8,atom1)*tz
639 t(3,atom1) = t(3,atom1) + a(3,atom1)*tx + a(6,atom1)*ty + &
640 a(9,atom1)*tz
641 else
642 t(1,atom2) = t(1,atom2) + a(1,atom2)*tx + a(4,atom2)*ty + &
643 a(7,atom2)*tz
644 t(2,atom2) = t(2,atom2) + a(2,atom2)*tx + a(5,atom2)*ty + &
645 a(8,atom2)*tz
646 t(3,atom2) = t(3,atom2) + a(3,atom2)*tx + a(6,atom2)*ty + &
647 a(9,atom2)*tz
648 endif
649 #endif
650 ! Now, on to the forces (still in body frame of water)
651
652 fx = dvdx * sw
653 fy = dvdy * sw
654 fz = dvdz * sw
655
656 ! rotate the terms back into the lab frame:
657
658 #ifdef IS_MPI
659 if (atid2.eq.MnM_Map%interactions(interaction_id)%metal_atid) then
660 fxl = a_Row(1,atom1)*fx + a_Row(4,atom1)*fy + a_Row(7,atom1)*fz
661 fyl = a_Row(2,atom1)*fx + a_Row(5,atom1)*fy + a_Row(8,atom1)*fz
662 fzl = a_Row(3,atom1)*fx + a_Row(6,atom1)*fy + a_Row(9,atom1)*fz
663 else
664 ! negative sign because this is the vector from j to i:
665 fxl = -(a_Col(1,atom2)*fx + a_Col(4,atom2)*fy + a_Col(7,atom2)*fz)
666 fyl = -(a_Col(2,atom2)*fx + a_Col(5,atom2)*fy + a_Col(8,atom2)*fz)
667 fzl = -(a_Col(3,atom2)*fx + a_Col(6,atom2)*fy + a_Col(9,atom2)*fz)
668 endif
669 f_Row(1,atom1) = f_Row(1,atom1) + fxl
670 f_Row(2,atom1) = f_Row(2,atom1) + fyl
671 f_Row(3,atom1) = f_Row(3,atom1) + fzl
672
673 f_Col(1,atom2) = f_Col(1,atom2) - fxl
674 f_Col(2,atom2) = f_Col(2,atom2) - fyl
675 f_Col(3,atom2) = f_Col(3,atom2) - fzl
676 #else
677 if (atid2.eq.MnM_Map%interactions(interaction_id)%metal_atid) then
678 fxl = a(1,atom1)*fx + a(4,atom1)*fy + a(7,atom1)*fz
679 fyl = a(2,atom1)*fx + a(5,atom1)*fy + a(8,atom1)*fz
680 fzl = a(3,atom1)*fx + a(6,atom1)*fy + a(9,atom1)*fz
681 else
682 ! negative sign because this is the vector from j to i:
683 fxl = -(a(1,atom2)*fx + a(4,atom2)*fy + a(7,atom2)*fz)
684 fyl = -(a(2,atom2)*fx + a(5,atom2)*fy + a(8,atom2)*fz)
685 fzl = -(a(3,atom2)*fx + a(6,atom2)*fy + a(9,atom2)*fz)
686 endif
687 f(1,atom1) = f(1,atom1) + fxl
688 f(2,atom1) = f(2,atom1) + fyl
689 f(3,atom1) = f(3,atom1) + fzl
690
691 f(1,atom2) = f(1,atom2) - fxl
692 f(2,atom2) = f(2,atom2) - fyl
693 f(3,atom2) = f(3,atom2) - fzl
694 #endif
695
696 #ifdef IS_MPI
697 id1 = AtomRowToGlobal(atom1)
698 id2 = AtomColToGlobal(atom2)
699 #else
700 id1 = atom1
701 id2 = atom2
702 #endif
703
704 if (molMembershipList(id1) .ne. molMembershipList(id2)) then
705
706 fpair(1) = fpair(1) + fxl
707 fpair(2) = fpair(2) + fyl
708 fpair(3) = fpair(3) + fzl
709
710 endif
711
712 return
713 end subroutine calc_mnm_maw
714
715
716 subroutine setMnMDefaultCutoff(thisRcut, shiftedPot, shiftedFrc)
717 real(kind=dp), intent(in) :: thisRcut
718 logical, intent(in) :: shiftedPot
719 logical, intent(in) :: shiftedFrc
720 integer i, nInteractions
721 defaultCutoff = thisRcut
722 defaultShiftPot = shiftedPot
723 defaultShiftFrc = shiftedFrc
724
725 if (associated(MnM_Map)) then
726 if(MnM_Map%interactionCount /= 0) then
727 nInteractions = MnM_Map%interactionCount
728
729 do i = 1, nInteractions
730 MnM_Map%interactions(i)%shiftedPot = shiftedPot
731 MnM_Map%interactions(i)%shiftedFrc = shiftedFrc
732 MnM_Map%interactions(i)%rCut = thisRcut
733 MnM_Map%interactions(i)%rCutWasSet = .true.
734 enddo
735 end if
736 end if
737
738 end subroutine setMnMDefaultCutoff
739
740 subroutine copyAllData(v1, v2)
741 type(MnMinteractionMap), pointer :: v1
742 type(MnMinteractionMap), pointer :: v2
743 integer :: i, j
744
745 do i = 1, v1%interactionCount
746 v2%interactions(i) = v1%interactions(i)
747 enddo
748
749 v2%interactionCount = v1%interactionCount
750 return
751 end subroutine copyAllData
752
753 subroutine addInteraction(myInteraction)
754 type(MNMtype) :: myInteraction
755 type(MnMinteraction) :: nt
756 integer :: id
757
758 nt%interaction_type = myInteraction%MNMInteractionType
759 nt%metal_atid = &
760 getFirstMatchingElement(atypes, "c_ident", myInteraction%metal_atid)
761 nt%nonmetal_atid = &
762 getFirstMatchingElement(atypes, "c_ident", myInteraction%nonmetal_atid)
763
764 select case (nt%interaction_type)
765 case (MNM_LENNARDJONES)
766 nt%sigma = myInteraction%sigma
767 nt%epsilon = myInteraction%epsilon
768 case(MNM_REPULSIVEMORSE, MNM_SHIFTEDMORSE)
769 nt%R0 = myInteraction%R0
770 nt%D0 = myInteraction%D0
771 nt%beta0 = myInteraction%beta0
772 case(MNM_MAW)
773 nt%R0 = myInteraction%R0
774 nt%D0 = myInteraction%D0
775 nt%beta0 = myInteraction%beta0
776 nt%ca1 = myInteraction%ca1
777 nt%cb1 = myInteraction%cb1
778 case default
779 call handleError("MNM", "Unknown Interaction type")
780 end select
781
782 if (.not. associated(MnM_Map)) then
783 call ensureCapacityHelper(MnM_Map, 1)
784 else
785 call ensureCapacityHelper(MnM_Map, MnM_Map%interactionCount + 1)
786 end if
787
788 MnM_Map%interactionCount = MnM_Map%interactionCount + 1
789 id = MnM_Map%interactionCount
790 MnM_Map%interactions(id) = nt
791 end subroutine addInteraction
792
793 subroutine ensureCapacityHelper(this, minCapacity)
794 type(MnMinteractionMap), pointer :: this, that
795 integer, intent(in) :: minCapacity
796 integer :: oldCapacity
797 integer :: newCapacity
798 logical :: resizeFlag
799
800 resizeFlag = .false.
801
802 ! first time: allocate a new vector with default size
803
804 if (.not. associated(this)) then
805 this => MnMinitialize(minCapacity, 0)
806 endif
807
808 oldCapacity = size(this%interactions)
809
810 if (minCapacity > oldCapacity) then
811 if (this%capacityIncrement .gt. 0) then
812 newCapacity = oldCapacity + this%capacityIncrement
813 else
814 newCapacity = oldCapacity * 2
815 endif
816 if (newCapacity .lt. minCapacity) then
817 newCapacity = minCapacity
818 endif
819 resizeFlag = .true.
820 else
821 newCapacity = oldCapacity
822 endif
823
824 if (resizeFlag) then
825 that => MnMinitialize(newCapacity, this%capacityIncrement)
826 call copyAllData(this, that)
827 this => MnMdestroy(this)
828 this => that
829 endif
830 end subroutine ensureCapacityHelper
831
832 function MnMinitialize(cap, capinc) result(this)
833 integer, intent(in) :: cap, capinc
834 integer :: error
835 type(MnMinteractionMap), pointer :: this
836
837 nullify(this)
838
839 if (cap < 0) then
840 write(*,*) 'Bogus Capacity:', cap
841 return
842 endif
843 allocate(this,stat=error)
844 if ( error /= 0 ) then
845 write(*,*) 'Could not allocate MnMinteractionMap!'
846 return
847 end if
848
849 this%initialCapacity = cap
850 this%capacityIncrement = capinc
851
852 allocate(this%interactions(this%initialCapacity), stat=error)
853 if(error /= 0) write(*,*) 'Could not allocate MnMinteraction!'
854
855 end function MnMinitialize
856
857 subroutine createInteractionLookup(this)
858 type (MnMInteractionMap),pointer :: this
859 integer :: biggestAtid, i, metal_atid, nonmetal_atid, error
860
861 biggestAtid=-1
862 do i = 1, this%interactionCount
863 metal_atid = this%interactions(i)%metal_atid
864 nonmetal_atid = this%interactions(i)%nonmetal_atid
865
866 if (metal_atid .gt. biggestAtid) biggestAtid = metal_atid
867 if (nonmetal_atid .gt. biggestAtid) biggestAtid = nonmetal_atid
868 enddo
869
870 allocate(MnMinteractionLookup(biggestAtid,biggestAtid), stat=error)
871 if (error /= 0) write(*,*) 'Could not allocate MnMinteractionLookup'
872
873 do i = 1, this%interactionCount
874 metal_atid = this%interactions(i)%metal_atid
875 nonmetal_atid = this%interactions(i)%nonmetal_atid
876
877 MnMinteractionLookup(metal_atid, nonmetal_atid) = i
878 MnMinteractionLookup(nonmetal_atid, metal_atid) = i
879 enddo
880 end subroutine createInteractionLookup
881
882 function MnMdestroy(this) result(null_this)
883 logical :: done
884 type(MnMinteractionMap), pointer :: this
885 type(MnMinteractionMap), pointer :: null_this
886
887 if (.not. associated(this)) then
888 null_this => null()
889 return
890 end if
891
892 !! Walk down the list and deallocate each of the map's components
893 if(associated(this%interactions)) then
894 deallocate(this%interactions)
895 this%interactions=>null()
896 endif
897 deallocate(this)
898 this => null()
899 null_this => null()
900 end function MnMdestroy
901
902 subroutine deleteInteractions()
903 MnM_Map => MnMdestroy(MnM_Map)
904 return
905 end subroutine deleteInteractions
906
907 subroutine getLJfunc(r, myPot, myDeriv)
908
909 real(kind=dp), intent(in) :: r
910 real(kind=dp), intent(inout) :: myPot, myDeriv
911 real(kind=dp) :: ri, ri2, ri6, ri7, ri12, ri13
912 real(kind=dp) :: a, b, c, d, dx
913 integer :: j
914
915 ri = 1.0_DP / r
916 ri2 = ri*ri
917 ri6 = ri2*ri2*ri2
918 ri7 = ri6*ri
919 ri12 = ri6*ri6
920 ri13 = ri12*ri
921
922 myPot = 4.0_DP * (ri12 - ri6)
923 myDeriv = 24.0_DP * (ri7 - 2.0_DP * ri13)
924
925 return
926 end subroutine getLJfunc
927
928 subroutine getSoftFunc(r, myPot, myDeriv)
929
930 real(kind=dp), intent(in) :: r
931 real(kind=dp), intent(inout) :: myPot, myDeriv
932 real(kind=dp) :: ri, ri2, ri6, ri7
933 real(kind=dp) :: a, b, c, d, dx
934 integer :: j
935
936 ri = 1.0_DP / r
937 ri2 = ri*ri
938 ri6 = ri2*ri2*ri2
939 ri7 = ri6*ri
940 myPot = 4.0_DP * (ri6)
941 myDeriv = - 24.0_DP * ri7
942
943 return
944 end subroutine getSoftFunc
945 end module MetalNonMetal