ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/DarkSide/electrostatic.F90
Revision: 2355
Committed: Wed Oct 12 18:59:16 2005 UTC (18 years, 10 months ago) by chuckv
File size: 46723 byte(s)
Log Message:
Breaky Breaky: Add Support for seperating potential contributions.

File Contents

# User Rev Content
1 gezelter 2095 !!
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     module electrostatic_module
43 gezelter 2204
44 gezelter 2095 use force_globals
45     use definitions
46     use atype_module
47     use vector_class
48     use simulation
49     use status
50     #ifdef IS_MPI
51     use mpiSimulation
52     #endif
53     implicit none
54    
55     PRIVATE
56    
57 chuckv 2355
58 gezelter 2301 #define __FORTRAN90
59 chuckv 2355 #include "UseTheForce/DarkSide/fInteractionMap.h"
60 gezelter 2301 #include "UseTheForce/DarkSide/fElectrostaticSummationMethod.h"
61    
62 chuckv 2355
63 gezelter 2118 !! these prefactors convert the multipole interactions into kcal / mol
64     !! all were computed assuming distances are measured in angstroms
65     !! Charge-Charge, assuming charges are measured in electrons
66 gezelter 2095 real(kind=dp), parameter :: pre11 = 332.0637778_dp
67 gezelter 2118 !! Charge-Dipole, assuming charges are measured in electrons, and
68     !! dipoles are measured in debyes
69     real(kind=dp), parameter :: pre12 = 69.13373_dp
70     !! Dipole-Dipole, assuming dipoles are measured in debyes
71     real(kind=dp), parameter :: pre22 = 14.39325_dp
72     !! Charge-Quadrupole, assuming charges are measured in electrons, and
73     !! quadrupoles are measured in 10^-26 esu cm^2
74     !! This unit is also known affectionately as an esu centi-barn.
75     real(kind=dp), parameter :: pre14 = 69.13373_dp
76 gezelter 2095
77 gezelter 2301 !! variables to handle different summation methods for long-range electrostatics:
78     integer, save :: summationMethod = NONE
79 chrisfen 2302 logical, save :: summationMethodChecked = .false.
80 gezelter 2301 real(kind=DP), save :: defaultCutoff = 0.0_DP
81     logical, save :: haveDefaultCutoff = .false.
82     real(kind=DP), save :: dampingAlpha = 0.0_DP
83     logical, save :: haveDampingAlpha = .false.
84     real(kind=DP), save :: dielectric = 0.0_DP
85     logical, save :: haveDielectric = .false.
86     real(kind=DP), save :: constERFC = 0.0_DP
87     real(kind=DP), save :: constEXP = 0.0_DP
88     logical, save :: haveDWAconstants = .false.
89 chrisfen 2306 real(kind=dp), save :: rcuti = 0.0_dp
90     real(kind=dp), save :: rcuti2 = 0.0_dp
91     real(kind=dp), save :: rcuti3 = 0.0_dp
92     real(kind=dp), save :: rcuti4 = 0.0_dp
93 chrisfen 2339 real(kind=dp), save :: alphaPi = 0.0_dp
94     real(kind=dp), save :: invRootPi = 0.0_dp
95    
96 chuckv 2331 #ifdef __IFC
97     ! error function for ifc version > 7.
98 chuckv 2330 double precision, external :: derfc
99 chuckv 2331 #endif
100    
101 gezelter 2301 public :: setElectrostaticSummationMethod
102     public :: setElectrostaticCutoffRadius
103     public :: setDampedWolfAlpha
104     public :: setReactionFieldDielectric
105 gezelter 2095 public :: newElectrostaticType
106     public :: setCharge
107     public :: setDipoleMoment
108     public :: setSplitDipoleDistance
109     public :: setQuadrupoleMoments
110     public :: doElectrostaticPair
111     public :: getCharge
112     public :: getDipoleMoment
113 chrisfen 2129 public :: pre22
114 chuckv 2189 public :: destroyElectrostaticTypes
115 gezelter 2095
116     type :: Electrostatic
117     integer :: c_ident
118     logical :: is_Charge = .false.
119     logical :: is_Dipole = .false.
120     logical :: is_SplitDipole = .false.
121     logical :: is_Quadrupole = .false.
122 chrisfen 2229 logical :: is_Tap = .false.
123 gezelter 2095 real(kind=DP) :: charge = 0.0_DP
124     real(kind=DP) :: dipole_moment = 0.0_DP
125     real(kind=DP) :: split_dipole_distance = 0.0_DP
126     real(kind=DP), dimension(3) :: quadrupole_moments = 0.0_DP
127     end type Electrostatic
128    
129     type(Electrostatic), dimension(:), allocatable :: ElectrostaticMap
130    
131     contains
132    
133 gezelter 2301 subroutine setElectrostaticSummationMethod(the_ESM)
134     integer, intent(in) :: the_ESM
135    
136     if ((the_ESM .le. 0) .or. (the_ESM .gt. REACTION_FIELD)) then
137     call handleError("setElectrostaticSummationMethod", "Unsupported Summation Method")
138     endif
139    
140 chrisfen 2309 summationMethod = the_ESM
141 chrisfen 2325
142 gezelter 2301 end subroutine setElectrostaticSummationMethod
143    
144     subroutine setElectrostaticCutoffRadius(thisRcut)
145     real(kind=dp), intent(in) :: thisRcut
146     defaultCutoff = thisRcut
147     haveDefaultCutoff = .true.
148     end subroutine setElectrostaticCutoffRadius
149    
150     subroutine setDampedWolfAlpha(thisAlpha)
151     real(kind=dp), intent(in) :: thisAlpha
152     dampingAlpha = thisAlpha
153     haveDampingAlpha = .true.
154     end subroutine setDampedWolfAlpha
155    
156     subroutine setReactionFieldDielectric(thisDielectric)
157     real(kind=dp), intent(in) :: thisDielectric
158     dielectric = thisDielectric
159     haveDielectric = .true.
160     end subroutine setReactionFieldDielectric
161    
162 gezelter 2095 subroutine newElectrostaticType(c_ident, is_Charge, is_Dipole, &
163 chrisfen 2229 is_SplitDipole, is_Quadrupole, is_Tap, status)
164 gezelter 2204
165 gezelter 2095 integer, intent(in) :: c_ident
166     logical, intent(in) :: is_Charge
167     logical, intent(in) :: is_Dipole
168     logical, intent(in) :: is_SplitDipole
169     logical, intent(in) :: is_Quadrupole
170 chrisfen 2229 logical, intent(in) :: is_Tap
171 gezelter 2095 integer, intent(out) :: status
172     integer :: nAtypes, myATID, i, j
173    
174     status = 0
175     myATID = getFirstMatchingElement(atypes, "c_ident", c_ident)
176 gezelter 2204
177 gezelter 2095 !! Be simple-minded and assume that we need an ElectrostaticMap that
178     !! is the same size as the total number of atom types
179    
180     if (.not.allocated(ElectrostaticMap)) then
181 gezelter 2204
182 gezelter 2095 nAtypes = getSize(atypes)
183 gezelter 2204
184 gezelter 2095 if (nAtypes == 0) then
185     status = -1
186     return
187     end if
188 gezelter 2204
189 gezelter 2095 if (.not. allocated(ElectrostaticMap)) then
190     allocate(ElectrostaticMap(nAtypes))
191     endif
192 gezelter 2204
193 gezelter 2095 end if
194    
195     if (myATID .gt. size(ElectrostaticMap)) then
196     status = -1
197     return
198     endif
199 gezelter 2204
200 gezelter 2095 ! set the values for ElectrostaticMap for this atom type:
201    
202     ElectrostaticMap(myATID)%c_ident = c_ident
203     ElectrostaticMap(myATID)%is_Charge = is_Charge
204     ElectrostaticMap(myATID)%is_Dipole = is_Dipole
205     ElectrostaticMap(myATID)%is_SplitDipole = is_SplitDipole
206     ElectrostaticMap(myATID)%is_Quadrupole = is_Quadrupole
207 chrisfen 2229 ElectrostaticMap(myATID)%is_Tap = is_Tap
208 gezelter 2204
209 gezelter 2095 end subroutine newElectrostaticType
210    
211     subroutine setCharge(c_ident, charge, status)
212     integer, intent(in) :: c_ident
213     real(kind=dp), intent(in) :: charge
214     integer, intent(out) :: status
215     integer :: myATID
216    
217     status = 0
218     myATID = getFirstMatchingElement(atypes, "c_ident", c_ident)
219    
220     if (.not.allocated(ElectrostaticMap)) then
221     call handleError("electrostatic", "no ElectrostaticMap was present before first call of setCharge!")
222     status = -1
223     return
224     end if
225    
226     if (myATID .gt. size(ElectrostaticMap)) then
227     call handleError("electrostatic", "ElectrostaticMap was found to be too small during setCharge!")
228     status = -1
229     return
230     endif
231    
232     if (.not.ElectrostaticMap(myATID)%is_Charge) then
233     call handleError("electrostatic", "Attempt to setCharge of an atom type that is not a charge!")
234     status = -1
235     return
236 gezelter 2204 endif
237 gezelter 2095
238     ElectrostaticMap(myATID)%charge = charge
239     end subroutine setCharge
240    
241     subroutine setDipoleMoment(c_ident, dipole_moment, status)
242     integer, intent(in) :: c_ident
243     real(kind=dp), intent(in) :: dipole_moment
244     integer, intent(out) :: status
245     integer :: myATID
246    
247     status = 0
248     myATID = getFirstMatchingElement(atypes, "c_ident", c_ident)
249    
250     if (.not.allocated(ElectrostaticMap)) then
251     call handleError("electrostatic", "no ElectrostaticMap was present before first call of setDipoleMoment!")
252     status = -1
253     return
254     end if
255    
256     if (myATID .gt. size(ElectrostaticMap)) then
257     call handleError("electrostatic", "ElectrostaticMap was found to be too small during setDipoleMoment!")
258     status = -1
259     return
260     endif
261    
262     if (.not.ElectrostaticMap(myATID)%is_Dipole) then
263     call handleError("electrostatic", "Attempt to setDipoleMoment of an atom type that is not a dipole!")
264     status = -1
265     return
266     endif
267    
268     ElectrostaticMap(myATID)%dipole_moment = dipole_moment
269     end subroutine setDipoleMoment
270    
271     subroutine setSplitDipoleDistance(c_ident, split_dipole_distance, status)
272     integer, intent(in) :: c_ident
273     real(kind=dp), intent(in) :: split_dipole_distance
274     integer, intent(out) :: status
275     integer :: myATID
276    
277     status = 0
278     myATID = getFirstMatchingElement(atypes, "c_ident", c_ident)
279    
280     if (.not.allocated(ElectrostaticMap)) then
281     call handleError("electrostatic", "no ElectrostaticMap was present before first call of setSplitDipoleDistance!")
282     status = -1
283     return
284     end if
285    
286     if (myATID .gt. size(ElectrostaticMap)) then
287     call handleError("electrostatic", "ElectrostaticMap was found to be too small during setSplitDipoleDistance!")
288     status = -1
289     return
290     endif
291    
292     if (.not.ElectrostaticMap(myATID)%is_SplitDipole) then
293     call handleError("electrostatic", "Attempt to setSplitDipoleDistance of an atom type that is not a splitDipole!")
294     status = -1
295     return
296     endif
297    
298     ElectrostaticMap(myATID)%split_dipole_distance = split_dipole_distance
299     end subroutine setSplitDipoleDistance
300    
301     subroutine setQuadrupoleMoments(c_ident, quadrupole_moments, status)
302     integer, intent(in) :: c_ident
303     real(kind=dp), intent(in), dimension(3) :: quadrupole_moments
304     integer, intent(out) :: status
305     integer :: myATID, i, j
306    
307     status = 0
308     myATID = getFirstMatchingElement(atypes, "c_ident", c_ident)
309    
310     if (.not.allocated(ElectrostaticMap)) then
311     call handleError("electrostatic", "no ElectrostaticMap was present before first call of setQuadrupoleMoments!")
312     status = -1
313     return
314     end if
315    
316     if (myATID .gt. size(ElectrostaticMap)) then
317     call handleError("electrostatic", "ElectrostaticMap was found to be too small during setQuadrupoleMoments!")
318     status = -1
319     return
320     endif
321    
322     if (.not.ElectrostaticMap(myATID)%is_Quadrupole) then
323     call handleError("electrostatic", "Attempt to setQuadrupoleMoments of an atom type that is not a quadrupole!")
324     status = -1
325     return
326     endif
327 gezelter 2204
328 gezelter 2095 do i = 1, 3
329 gezelter 2204 ElectrostaticMap(myATID)%quadrupole_moments(i) = &
330     quadrupole_moments(i)
331     enddo
332 gezelter 2095
333     end subroutine setQuadrupoleMoments
334    
335 gezelter 2204
336 gezelter 2095 function getCharge(atid) result (c)
337     integer, intent(in) :: atid
338     integer :: localError
339     real(kind=dp) :: c
340 gezelter 2204
341 gezelter 2095 if (.not.allocated(ElectrostaticMap)) then
342     call handleError("electrostatic", "no ElectrostaticMap was present before first call of getCharge!")
343     return
344     end if
345 gezelter 2204
346 gezelter 2095 if (.not.ElectrostaticMap(atid)%is_Charge) then
347     call handleError("electrostatic", "getCharge was called for an atom type that isn't a charge!")
348     return
349     endif
350 gezelter 2204
351 gezelter 2095 c = ElectrostaticMap(atid)%charge
352     end function getCharge
353    
354     function getDipoleMoment(atid) result (dm)
355     integer, intent(in) :: atid
356     integer :: localError
357     real(kind=dp) :: dm
358 gezelter 2204
359 gezelter 2095 if (.not.allocated(ElectrostaticMap)) then
360     call handleError("electrostatic", "no ElectrostaticMap was present before first call of getDipoleMoment!")
361     return
362     end if
363 gezelter 2204
364 gezelter 2095 if (.not.ElectrostaticMap(atid)%is_Dipole) then
365     call handleError("electrostatic", "getDipoleMoment was called for an atom type that isn't a dipole!")
366     return
367     endif
368 gezelter 2204
369 gezelter 2095 dm = ElectrostaticMap(atid)%dipole_moment
370     end function getDipoleMoment
371    
372 gezelter 2301 subroutine checkSummationMethod()
373    
374 chrisfen 2306 if (.not.haveDefaultCutoff) then
375     call handleError("checkSummationMethod", "no Default Cutoff set!")
376     endif
377    
378     rcuti = 1.0d0 / defaultCutoff
379     rcuti2 = rcuti*rcuti
380     rcuti3 = rcuti2*rcuti
381     rcuti4 = rcuti2*rcuti2
382    
383 gezelter 2301 if (summationMethod .eq. DAMPED_WOLF) then
384     if (.not.haveDWAconstants) then
385    
386     if (.not.haveDampingAlpha) then
387     call handleError("checkSummationMethod", "no Damping Alpha set!")
388     endif
389    
390 chrisfen 2302 if (.not.haveDefaultCutoff) then
391     call handleError("checkSummationMethod", "no Default Cutoff set!")
392     endif
393    
394     constEXP = exp(-dampingAlpha*dampingAlpha*defaultCutoff*defaultCutoff)
395 chuckv 2330 constERFC = derfc(dampingAlpha*defaultCutoff)
396 chrisfen 2339 invRootPi = 0.56418958354775628695d0
397     alphaPi = 2*dampingAlpha*invRootPi
398 chrisfen 2343
399 gezelter 2301 haveDWAconstants = .true.
400     endif
401     endif
402    
403 chrisfen 2302 if (summationMethod .eq. REACTION_FIELD) then
404     if (.not.haveDielectric) then
405     call handleError("checkSummationMethod", "no reaction field Dielectric set!")
406     endif
407     endif
408    
409     summationMethodChecked = .true.
410 gezelter 2301 end subroutine checkSummationMethod
411    
412    
413    
414 gezelter 2095 subroutine doElectrostaticPair(atom1, atom2, d, rij, r2, sw, &
415 chrisfen 2306 vpair, fpair, pot, eFrame, f, t, do_pot)
416 gezelter 2204
417 gezelter 2095 logical, intent(in) :: do_pot
418 gezelter 2204
419 gezelter 2095 integer, intent(in) :: atom1, atom2
420     integer :: localError
421    
422 chrisfen 2306 real(kind=dp), intent(in) :: rij, r2, sw
423 gezelter 2095 real(kind=dp), intent(in), dimension(3) :: d
424     real(kind=dp), intent(inout) :: vpair
425     real(kind=dp), intent(inout), dimension(3) :: fpair
426    
427 chrisfen 2325 real( kind = dp ) :: pot
428 gezelter 2095 real( kind = dp ), dimension(9,nLocal) :: eFrame
429     real( kind = dp ), dimension(3,nLocal) :: f
430     real( kind = dp ), dimension(3,nLocal) :: t
431 gezelter 2204
432 gezelter 2123 real (kind = dp), dimension(3) :: ux_i, uy_i, uz_i
433     real (kind = dp), dimension(3) :: ux_j, uy_j, uz_j
434     real (kind = dp), dimension(3) :: dudux_i, duduy_i, duduz_i
435     real (kind = dp), dimension(3) :: dudux_j, duduy_j, duduz_j
436 gezelter 2095
437     logical :: i_is_Charge, i_is_Dipole, i_is_SplitDipole, i_is_Quadrupole
438     logical :: j_is_Charge, j_is_Dipole, j_is_SplitDipole, j_is_Quadrupole
439 chrisfen 2229 logical :: i_is_Tap, j_is_Tap
440 gezelter 2095 integer :: me1, me2, id1, id2
441     real (kind=dp) :: q_i, q_j, mu_i, mu_j, d_i, d_j
442 gezelter 2123 real (kind=dp) :: qxx_i, qyy_i, qzz_i
443     real (kind=dp) :: qxx_j, qyy_j, qzz_j
444     real (kind=dp) :: cx_i, cy_i, cz_i
445     real (kind=dp) :: cx_j, cy_j, cz_j
446     real (kind=dp) :: cx2, cy2, cz2
447 gezelter 2095 real (kind=dp) :: ct_i, ct_j, ct_ij, a1
448 gezelter 2105 real (kind=dp) :: riji, ri, ri2, ri3, ri4
449 chrisfen 2296 real (kind=dp) :: pref, vterm, epot, dudr, vterm1, vterm2
450 gezelter 2105 real (kind=dp) :: xhat, yhat, zhat
451 gezelter 2095 real (kind=dp) :: dudx, dudy, dudz
452 chrisfen 2325 real (kind=dp) :: scale, sc2, bigR
453 chrisfen 2339 real (kind=dp) :: varERFC, varEXP
454 chrisfen 2343 real (kind=dp) :: limScale
455 gezelter 2095
456     if (.not.allocated(ElectrostaticMap)) then
457     call handleError("electrostatic", "no ElectrostaticMap was present before first call of do_electrostatic_pair!")
458     return
459     end if
460    
461 gezelter 2301 if (.not.summationMethodChecked) then
462     call checkSummationMethod()
463 chrisfen 2310
464 gezelter 2301 endif
465    
466    
467 gezelter 2095 #ifdef IS_MPI
468     me1 = atid_Row(atom1)
469     me2 = atid_Col(atom2)
470     #else
471     me1 = atid(atom1)
472     me2 = atid(atom2)
473     #endif
474    
475     !! some variables we'll need independent of electrostatic type:
476    
477     riji = 1.0d0 / rij
478 chrisfen 2343
479 gezelter 2105 xhat = d(1) * riji
480     yhat = d(2) * riji
481     zhat = d(3) * riji
482 gezelter 2095
483     !! logicals
484     i_is_Charge = ElectrostaticMap(me1)%is_Charge
485     i_is_Dipole = ElectrostaticMap(me1)%is_Dipole
486     i_is_SplitDipole = ElectrostaticMap(me1)%is_SplitDipole
487     i_is_Quadrupole = ElectrostaticMap(me1)%is_Quadrupole
488 chrisfen 2229 i_is_Tap = ElectrostaticMap(me1)%is_Tap
489 gezelter 2095
490     j_is_Charge = ElectrostaticMap(me2)%is_Charge
491     j_is_Dipole = ElectrostaticMap(me2)%is_Dipole
492     j_is_SplitDipole = ElectrostaticMap(me2)%is_SplitDipole
493     j_is_Quadrupole = ElectrostaticMap(me2)%is_Quadrupole
494 chrisfen 2229 j_is_Tap = ElectrostaticMap(me2)%is_Tap
495 gezelter 2095
496     if (i_is_Charge) then
497     q_i = ElectrostaticMap(me1)%charge
498     endif
499 gezelter 2204
500 gezelter 2095 if (i_is_Dipole) then
501     mu_i = ElectrostaticMap(me1)%dipole_moment
502     #ifdef IS_MPI
503 gezelter 2123 uz_i(1) = eFrame_Row(3,atom1)
504     uz_i(2) = eFrame_Row(6,atom1)
505     uz_i(3) = eFrame_Row(9,atom1)
506 gezelter 2095 #else
507 gezelter 2123 uz_i(1) = eFrame(3,atom1)
508     uz_i(2) = eFrame(6,atom1)
509     uz_i(3) = eFrame(9,atom1)
510 gezelter 2095 #endif
511 gezelter 2123 ct_i = uz_i(1)*xhat + uz_i(2)*yhat + uz_i(3)*zhat
512 gezelter 2095
513     if (i_is_SplitDipole) then
514     d_i = ElectrostaticMap(me1)%split_dipole_distance
515     endif
516 gezelter 2204
517 gezelter 2095 endif
518    
519 gezelter 2123 if (i_is_Quadrupole) then
520     qxx_i = ElectrostaticMap(me1)%quadrupole_moments(1)
521     qyy_i = ElectrostaticMap(me1)%quadrupole_moments(2)
522     qzz_i = ElectrostaticMap(me1)%quadrupole_moments(3)
523     #ifdef IS_MPI
524     ux_i(1) = eFrame_Row(1,atom1)
525     ux_i(2) = eFrame_Row(4,atom1)
526     ux_i(3) = eFrame_Row(7,atom1)
527     uy_i(1) = eFrame_Row(2,atom1)
528     uy_i(2) = eFrame_Row(5,atom1)
529     uy_i(3) = eFrame_Row(8,atom1)
530     uz_i(1) = eFrame_Row(3,atom1)
531     uz_i(2) = eFrame_Row(6,atom1)
532     uz_i(3) = eFrame_Row(9,atom1)
533     #else
534     ux_i(1) = eFrame(1,atom1)
535     ux_i(2) = eFrame(4,atom1)
536     ux_i(3) = eFrame(7,atom1)
537     uy_i(1) = eFrame(2,atom1)
538     uy_i(2) = eFrame(5,atom1)
539     uy_i(3) = eFrame(8,atom1)
540     uz_i(1) = eFrame(3,atom1)
541     uz_i(2) = eFrame(6,atom1)
542     uz_i(3) = eFrame(9,atom1)
543     #endif
544     cx_i = ux_i(1)*xhat + ux_i(2)*yhat + ux_i(3)*zhat
545     cy_i = uy_i(1)*xhat + uy_i(2)*yhat + uy_i(3)*zhat
546     cz_i = uz_i(1)*xhat + uz_i(2)*yhat + uz_i(3)*zhat
547     endif
548    
549 gezelter 2095 if (j_is_Charge) then
550     q_j = ElectrostaticMap(me2)%charge
551     endif
552 gezelter 2204
553 gezelter 2095 if (j_is_Dipole) then
554     mu_j = ElectrostaticMap(me2)%dipole_moment
555     #ifdef IS_MPI
556 gezelter 2123 uz_j(1) = eFrame_Col(3,atom2)
557     uz_j(2) = eFrame_Col(6,atom2)
558     uz_j(3) = eFrame_Col(9,atom2)
559 gezelter 2095 #else
560 gezelter 2123 uz_j(1) = eFrame(3,atom2)
561     uz_j(2) = eFrame(6,atom2)
562     uz_j(3) = eFrame(9,atom2)
563 gezelter 2095 #endif
564 chrisfen 2162 ct_j = uz_j(1)*xhat + uz_j(2)*yhat + uz_j(3)*zhat
565 gezelter 2095
566     if (j_is_SplitDipole) then
567     d_j = ElectrostaticMap(me2)%split_dipole_distance
568     endif
569     endif
570    
571 gezelter 2123 if (j_is_Quadrupole) then
572     qxx_j = ElectrostaticMap(me2)%quadrupole_moments(1)
573     qyy_j = ElectrostaticMap(me2)%quadrupole_moments(2)
574     qzz_j = ElectrostaticMap(me2)%quadrupole_moments(3)
575     #ifdef IS_MPI
576     ux_j(1) = eFrame_Col(1,atom2)
577     ux_j(2) = eFrame_Col(4,atom2)
578     ux_j(3) = eFrame_Col(7,atom2)
579     uy_j(1) = eFrame_Col(2,atom2)
580     uy_j(2) = eFrame_Col(5,atom2)
581     uy_j(3) = eFrame_Col(8,atom2)
582     uz_j(1) = eFrame_Col(3,atom2)
583     uz_j(2) = eFrame_Col(6,atom2)
584     uz_j(3) = eFrame_Col(9,atom2)
585     #else
586     ux_j(1) = eFrame(1,atom2)
587     ux_j(2) = eFrame(4,atom2)
588     ux_j(3) = eFrame(7,atom2)
589     uy_j(1) = eFrame(2,atom2)
590     uy_j(2) = eFrame(5,atom2)
591     uy_j(3) = eFrame(8,atom2)
592     uz_j(1) = eFrame(3,atom2)
593     uz_j(2) = eFrame(6,atom2)
594     uz_j(3) = eFrame(9,atom2)
595     #endif
596     cx_j = ux_j(1)*xhat + ux_j(2)*yhat + ux_j(3)*zhat
597     cy_j = uy_j(1)*xhat + uy_j(2)*yhat + uy_j(3)*zhat
598     cz_j = uz_j(1)*xhat + uz_j(2)*yhat + uz_j(3)*zhat
599     endif
600 chrisfen 2251
601 gezelter 2095 epot = 0.0_dp
602     dudx = 0.0_dp
603     dudy = 0.0_dp
604     dudz = 0.0_dp
605    
606 gezelter 2123 dudux_i = 0.0_dp
607     duduy_i = 0.0_dp
608     duduz_i = 0.0_dp
609 gezelter 2095
610 gezelter 2123 dudux_j = 0.0_dp
611     duduy_j = 0.0_dp
612     duduz_j = 0.0_dp
613 gezelter 2095
614     if (i_is_Charge) then
615    
616     if (j_is_Charge) then
617 gezelter 2204
618 chrisfen 2310 if (summationMethod .eq. UNDAMPED_WOLF) then
619 chrisfen 2325
620 chrisfen 2296 vterm = pre11 * q_i * q_j * (riji - rcuti)
621     vpair = vpair + vterm
622 chrisfen 2325 epot = epot + sw*vterm
623 chrisfen 2296
624 chrisfen 2343 dudr = -sw*pre11*q_i*q_j * (riji*riji-rcuti2)*riji
625 chrisfen 2296
626     dudx = dudx + dudr * d(1)
627     dudy = dudy + dudr * d(2)
628     dudz = dudz + dudr * d(3)
629 gezelter 2095
630 chrisfen 2339 elseif (summationMethod .eq. DAMPED_WOLF) then
631    
632     varERFC = derfc(dampingAlpha*rij)
633     varEXP = exp(-dampingAlpha*dampingAlpha*rij*rij)
634     vterm = pre11 * q_i * q_j * (varERFC*riji - constERFC*rcuti)
635     vpair = vpair + vterm
636     epot = epot + sw*vterm
637    
638 chrisfen 2343 dudr = -sw*pre11*q_i*q_j * ( riji*((varERFC*riji*riji &
639     + alphaPi*varEXP) &
640     - (constERFC*rcuti2 &
641     + alphaPi*constEXP)) )
642 chrisfen 2339
643     dudx = dudx + dudr * d(1)
644     dudy = dudy + dudr * d(2)
645     dudz = dudz + dudr * d(3)
646    
647 chrisfen 2296 else
648 chrisfen 2325
649 chrisfen 2296 vterm = pre11 * q_i * q_j * riji
650     vpair = vpair + vterm
651 chrisfen 2325 epot = epot + sw*vterm
652 chrisfen 2296
653     dudr = - sw * vterm * riji
654    
655     dudx = dudx + dudr * xhat
656     dudy = dudy + dudr * yhat
657     dudz = dudz + dudr * zhat
658    
659     endif
660    
661 gezelter 2095 endif
662    
663     if (j_is_Dipole) then
664    
665 chrisfen 2325 pref = pre12 * q_i * mu_j
666 gezelter 2095
667 chrisfen 2310 if (summationMethod .eq. UNDAMPED_WOLF) then
668 chrisfen 2296 ri2 = riji * riji
669     ri3 = ri2 * riji
670 gezelter 2204
671 chrisfen 2325 pref = pre12 * q_i * mu_j
672 chrisfen 2296 vterm = - pref * ct_j * (ri2 - rcuti2)
673 chrisfen 2325 vpair = vpair + vterm
674     epot = epot + sw*vterm
675 chrisfen 2296
676     !! this has a + sign in the () because the rij vector is
677     !! r_j - r_i and the charge-dipole potential takes the origin
678     !! as the point dipole, which is atom j in this case.
679    
680 chrisfen 2325 dudx = dudx - sw*pref * ( ri3*( uz_j(1) - 3.0d0*ct_j*xhat) &
681 chrisfen 2296 - rcuti3*( uz_j(1) - 3.0d0*ct_j*d(1)*rcuti ) )
682 chrisfen 2325 dudy = dudy - sw*pref * ( ri3*( uz_j(2) - 3.0d0*ct_j*yhat) &
683 chrisfen 2296 - rcuti3*( uz_j(2) - 3.0d0*ct_j*d(2)*rcuti ) )
684 chrisfen 2325 dudz = dudz - sw*pref * ( ri3*( uz_j(3) - 3.0d0*ct_j*zhat) &
685 chrisfen 2296 - rcuti3*( uz_j(3) - 3.0d0*ct_j*d(3)*rcuti ) )
686    
687 chrisfen 2325 duduz_j(1) = duduz_j(1) - sw*pref*( ri2*xhat - d(1)*rcuti3 )
688     duduz_j(2) = duduz_j(2) - sw*pref*( ri2*yhat - d(2)*rcuti3 )
689     duduz_j(3) = duduz_j(3) - sw*pref*( ri2*zhat - d(3)*rcuti3 )
690 gezelter 2095
691 chrisfen 2296 else
692     if (j_is_SplitDipole) then
693     BigR = sqrt(r2 + 0.25_dp * d_j * d_j)
694     ri = 1.0_dp / BigR
695     scale = rij * ri
696     else
697     ri = riji
698     scale = 1.0_dp
699     endif
700    
701     ri2 = ri * ri
702     ri3 = ri2 * ri
703     sc2 = scale * scale
704 chrisfen 2325
705     pref = pre12 * q_i * mu_j
706 chrisfen 2296 vterm = - pref * ct_j * ri2 * scale
707 chrisfen 2325 vpair = vpair + vterm
708     epot = epot + sw*vterm
709 chrisfen 2296
710     !! this has a + sign in the () because the rij vector is
711     !! r_j - r_i and the charge-dipole potential takes the origin
712     !! as the point dipole, which is atom j in this case.
713    
714 chrisfen 2325 dudx = dudx - sw*pref * ri3 * ( uz_j(1) - 3.0d0*ct_j*xhat*sc2)
715     dudy = dudy - sw*pref * ri3 * ( uz_j(2) - 3.0d0*ct_j*yhat*sc2)
716     dudz = dudz - sw*pref * ri3 * ( uz_j(3) - 3.0d0*ct_j*zhat*sc2)
717 chrisfen 2296
718 chrisfen 2325 duduz_j(1) = duduz_j(1) - sw*pref * ri2 * xhat * scale
719     duduz_j(2) = duduz_j(2) - sw*pref * ri2 * yhat * scale
720     duduz_j(3) = duduz_j(3) - sw*pref * ri2 * zhat * scale
721 gezelter 2095
722 chrisfen 2296 endif
723 gezelter 2095 endif
724 gezelter 2105
725 gezelter 2123 if (j_is_Quadrupole) then
726     ri2 = riji * riji
727     ri3 = ri2 * riji
728 gezelter 2124 ri4 = ri2 * ri2
729 gezelter 2123 cx2 = cx_j * cx_j
730     cy2 = cy_j * cy_j
731     cz2 = cz_j * cz_j
732    
733 chrisfen 2310 if (summationMethod .eq. UNDAMPED_WOLF) then
734 chrisfen 2325 pref = pre14 * q_i / 3.0_dp
735 chrisfen 2296 vterm1 = pref * ri3*( qxx_j * (3.0_dp*cx2 - 1.0_dp) + &
736     qyy_j * (3.0_dp*cy2 - 1.0_dp) + &
737     qzz_j * (3.0_dp*cz2 - 1.0_dp) )
738     vterm2 = pref * rcuti3*( qxx_j * (3.0_dp*cx2 - 1.0_dp) + &
739     qyy_j * (3.0_dp*cy2 - 1.0_dp) + &
740     qzz_j * (3.0_dp*cz2 - 1.0_dp) )
741 chrisfen 2325 vpair = vpair + ( vterm1 - vterm2 )
742     epot = epot + sw*( vterm1 - vterm2 )
743 chrisfen 2296
744     dudx = dudx - (5.0_dp * &
745 chrisfen 2325 (vterm1*riji*xhat - vterm2*rcuti2*d(1))) + sw*pref * ( &
746 chrisfen 2296 (ri4 - rcuti4)*(qxx_j*(6.0_dp*cx_j*ux_j(1)) - &
747     qxx_j*2.0_dp*(xhat - rcuti*d(1))) + &
748     (ri4 - rcuti4)*(qyy_j*(6.0_dp*cy_j*uy_j(1)) - &
749     qyy_j*2.0_dp*(xhat - rcuti*d(1))) + &
750     (ri4 - rcuti4)*(qzz_j*(6.0_dp*cz_j*uz_j(1)) - &
751     qzz_j*2.0_dp*(xhat - rcuti*d(1))) )
752     dudy = dudy - (5.0_dp * &
753 chrisfen 2325 (vterm1*riji*yhat - vterm2*rcuti2*d(2))) + sw*pref * ( &
754 chrisfen 2296 (ri4 - rcuti4)*(qxx_j*(6.0_dp*cx_j*ux_j(2)) - &
755     qxx_j*2.0_dp*(yhat - rcuti*d(2))) + &
756     (ri4 - rcuti4)*(qyy_j*(6.0_dp*cy_j*uy_j(2)) - &
757     qyy_j*2.0_dp*(yhat - rcuti*d(2))) + &
758     (ri4 - rcuti4)*(qzz_j*(6.0_dp*cz_j*uz_j(2)) - &
759     qzz_j*2.0_dp*(yhat - rcuti*d(2))) )
760     dudz = dudz - (5.0_dp * &
761 chrisfen 2325 (vterm1*riji*zhat - vterm2*rcuti2*d(3))) + sw*pref * ( &
762 chrisfen 2296 (ri4 - rcuti4)*(qxx_j*(6.0_dp*cx_j*ux_j(3)) - &
763     qxx_j*2.0_dp*(zhat - rcuti*d(3))) + &
764     (ri4 - rcuti4)*(qyy_j*(6.0_dp*cy_j*uy_j(3)) - &
765     qyy_j*2.0_dp*(zhat - rcuti*d(3))) + &
766     (ri4 - rcuti4)*(qzz_j*(6.0_dp*cz_j*uz_j(3)) - &
767     qzz_j*2.0_dp*(zhat - rcuti*d(3))) )
768    
769 chrisfen 2325 dudux_j(1) = dudux_j(1) + sw*pref*(ri3*(qxx_j*6.0_dp*cx_j*xhat) -&
770 chrisfen 2296 rcuti4*(qxx_j*6.0_dp*cx_j*d(1)))
771 chrisfen 2325 dudux_j(2) = dudux_j(2) + sw*pref*(ri3*(qxx_j*6.0_dp*cx_j*yhat) -&
772 chrisfen 2296 rcuti4*(qxx_j*6.0_dp*cx_j*d(2)))
773 chrisfen 2325 dudux_j(3) = dudux_j(3) + sw*pref*(ri3*(qxx_j*6.0_dp*cx_j*zhat) -&
774 chrisfen 2296 rcuti4*(qxx_j*6.0_dp*cx_j*d(3)))
775    
776 chrisfen 2325 duduy_j(1) = duduy_j(1) + sw*pref*(ri3*(qyy_j*6.0_dp*cy_j*xhat) -&
777 chrisfen 2296 rcuti4*(qyy_j*6.0_dp*cx_j*d(1)))
778 chrisfen 2325 duduy_j(2) = duduy_j(2) + sw*pref*(ri3*(qyy_j*6.0_dp*cy_j*yhat) -&
779 chrisfen 2296 rcuti4*(qyy_j*6.0_dp*cx_j*d(2)))
780 chrisfen 2325 duduy_j(3) = duduy_j(3) + sw*pref*(ri3*(qyy_j*6.0_dp*cy_j*zhat) -&
781 chrisfen 2296 rcuti4*(qyy_j*6.0_dp*cx_j*d(3)))
782    
783 chrisfen 2325 duduz_j(1) = duduz_j(1) + sw*pref*(ri3*(qzz_j*6.0_dp*cz_j*xhat) -&
784 chrisfen 2296 rcuti4*(qzz_j*6.0_dp*cx_j*d(1)))
785 chrisfen 2325 duduz_j(2) = duduz_j(2) + sw*pref*(ri3*(qzz_j*6.0_dp*cz_j*yhat) -&
786 chrisfen 2296 rcuti4*(qzz_j*6.0_dp*cx_j*d(2)))
787 chrisfen 2325 duduz_j(3) = duduz_j(3) + sw*pref*(ri3*(qzz_j*6.0_dp*cz_j*zhat) -&
788 chrisfen 2296 rcuti4*(qzz_j*6.0_dp*cx_j*d(3)))
789    
790     else
791 chrisfen 2325 pref = pre14 * q_i / 3.0_dp
792 chrisfen 2296 vterm = pref * ri3 * (qxx_j * (3.0_dp*cx2 - 1.0_dp) + &
793     qyy_j * (3.0_dp*cy2 - 1.0_dp) + &
794     qzz_j * (3.0_dp*cz2 - 1.0_dp))
795 chrisfen 2325 vpair = vpair + vterm
796     epot = epot + sw*vterm
797 chrisfen 2296
798 chrisfen 2325 dudx = dudx - 5.0_dp*sw*vterm*riji*xhat + sw*pref * ri4 * ( &
799 chrisfen 2296 qxx_j*(6.0_dp*cx_j*ux_j(1) - 2.0_dp*xhat) + &
800     qyy_j*(6.0_dp*cy_j*uy_j(1) - 2.0_dp*xhat) + &
801     qzz_j*(6.0_dp*cz_j*uz_j(1) - 2.0_dp*xhat) )
802 chrisfen 2325 dudy = dudy - 5.0_dp*sw*vterm*riji*yhat + sw*pref * ri4 * ( &
803 chrisfen 2296 qxx_j*(6.0_dp*cx_j*ux_j(2) - 2.0_dp*yhat) + &
804     qyy_j*(6.0_dp*cy_j*uy_j(2) - 2.0_dp*yhat) + &
805     qzz_j*(6.0_dp*cz_j*uz_j(2) - 2.0_dp*yhat) )
806 chrisfen 2325 dudz = dudz - 5.0_dp*sw*vterm*riji*zhat + sw*pref * ri4 * ( &
807 chrisfen 2296 qxx_j*(6.0_dp*cx_j*ux_j(3) - 2.0_dp*zhat) + &
808     qyy_j*(6.0_dp*cy_j*uy_j(3) - 2.0_dp*zhat) + &
809     qzz_j*(6.0_dp*cz_j*uz_j(3) - 2.0_dp*zhat) )
810    
811 chrisfen 2325 dudux_j(1) = dudux_j(1) + sw*pref * ri3*(qxx_j*6.0_dp*cx_j*xhat)
812     dudux_j(2) = dudux_j(2) + sw*pref * ri3*(qxx_j*6.0_dp*cx_j*yhat)
813     dudux_j(3) = dudux_j(3) + sw*pref * ri3*(qxx_j*6.0_dp*cx_j*zhat)
814 chrisfen 2296
815 chrisfen 2325 duduy_j(1) = duduy_j(1) + sw*pref * ri3*(qyy_j*6.0_dp*cy_j*xhat)
816     duduy_j(2) = duduy_j(2) + sw*pref * ri3*(qyy_j*6.0_dp*cy_j*yhat)
817     duduy_j(3) = duduy_j(3) + sw*pref * ri3*(qyy_j*6.0_dp*cy_j*zhat)
818 chrisfen 2296
819 chrisfen 2325 duduz_j(1) = duduz_j(1) + sw*pref * ri3*(qzz_j*6.0_dp*cz_j*xhat)
820     duduz_j(2) = duduz_j(2) + sw*pref * ri3*(qzz_j*6.0_dp*cz_j*yhat)
821     duduz_j(3) = duduz_j(3) + sw*pref * ri3*(qzz_j*6.0_dp*cz_j*zhat)
822 chrisfen 2296
823     endif
824 gezelter 2123 endif
825 gezelter 2095 endif
826 gezelter 2204
827 gezelter 2095 if (i_is_Dipole) then
828 gezelter 2204
829 gezelter 2095 if (j_is_Charge) then
830 chrisfen 2325
831     pref = pre12 * q_j * mu_i
832    
833 chrisfen 2310 if (summationMethod .eq. UNDAMPED_WOLF) then
834 chrisfen 2296 ri2 = riji * riji
835     ri3 = ri2 * riji
836 gezelter 2204
837 chrisfen 2325 pref = pre12 * q_j * mu_i
838 chrisfen 2296 vterm = pref * ct_i * (ri2 - rcuti2)
839 chrisfen 2325 vpair = vpair + vterm
840     epot = epot + sw*vterm
841 chrisfen 2296
842     !! this has a + sign in the () because the rij vector is
843     !! r_j - r_i and the charge-dipole potential takes the origin
844     !! as the point dipole, which is atom j in this case.
845    
846 chrisfen 2325 dudx = dudx + sw*pref * ( ri3*( uz_i(1) - 3.0d0*ct_i*xhat) &
847 chrisfen 2296 - rcuti3*( uz_i(1) - 3.0d0*ct_i*d(1)*rcuti ) )
848 chrisfen 2325 dudy = dudy + sw*pref * ( ri3*( uz_i(2) - 3.0d0*ct_i*yhat) &
849 chrisfen 2296 - rcuti3*( uz_i(2) - 3.0d0*ct_i*d(2)*rcuti ) )
850 chrisfen 2325 dudz = dudz + sw*pref * ( ri3*( uz_i(3) - 3.0d0*ct_i*zhat) &
851 chrisfen 2296 - rcuti3*( uz_i(3) - 3.0d0*ct_i*d(3)*rcuti ) )
852    
853 chrisfen 2325 duduz_i(1) = duduz_i(1) - sw*pref*( ri2*xhat - d(1)*rcuti3 )
854     duduz_i(2) = duduz_i(2) - sw*pref*( ri2*yhat - d(2)*rcuti3 )
855     duduz_i(3) = duduz_i(3) - sw*pref*( ri2*zhat - d(3)*rcuti3 )
856 gezelter 2095
857 chrisfen 2296 else
858     if (i_is_SplitDipole) then
859 gezelter 2105 BigR = sqrt(r2 + 0.25_dp * d_i * d_i)
860     ri = 1.0_dp / BigR
861 chrisfen 2296 scale = rij * ri
862     else
863 gezelter 2105 ri = riji
864     scale = 1.0_dp
865     endif
866 chrisfen 2296
867     ri2 = ri * ri
868     ri3 = ri2 * ri
869     sc2 = scale * scale
870 chrisfen 2325
871     pref = pre12 * q_j * mu_i
872 chrisfen 2296 vterm = pref * ct_i * ri2 * scale
873 chrisfen 2325 vpair = vpair + vterm
874     epot = epot + sw*vterm
875 chrisfen 2296
876 chrisfen 2325 dudx = dudx + sw*pref * ri3 * ( uz_i(1) - 3.0d0 * ct_i * xhat*sc2)
877     dudy = dudy + sw*pref * ri3 * ( uz_i(2) - 3.0d0 * ct_i * yhat*sc2)
878     dudz = dudz + sw*pref * ri3 * ( uz_i(3) - 3.0d0 * ct_i * zhat*sc2)
879 chrisfen 2296
880 chrisfen 2325 duduz_i(1) = duduz_i(1) + sw*pref * ri2 * xhat * scale
881     duduz_i(2) = duduz_i(2) + sw*pref * ri2 * yhat * scale
882     duduz_i(3) = duduz_i(3) + sw*pref * ri2 * zhat * scale
883 gezelter 2105 endif
884 chrisfen 2296 endif
885 chrisfen 2325
886 chrisfen 2296 if (j_is_Dipole) then
887 gezelter 2105
888 chrisfen 2310 if (summationMethod .eq. UNDAMPED_WOLF) then
889 chrisfen 2296 ri2 = riji * riji
890     ri3 = ri2 * riji
891     ri4 = ri2 * ri2
892 gezelter 2204
893 chrisfen 2325 pref = pre22 * mu_i * mu_j
894 chrisfen 2296 vterm = pref * (ri3 - rcuti3) * (ct_ij - 3.0d0 * ct_i * ct_j)
895 chrisfen 2325 vpair = vpair + vterm
896     epot = epot + sw*vterm
897 chrisfen 2296
898     a1 = 5.0d0 * ct_i * ct_j - ct_ij
899    
900 chrisfen 2325 dudx = dudx + sw*pref*3.0d0*ri4 &
901     * (a1*xhat-ct_i*uz_j(1)-ct_j*uz_i(1)) &
902     - sw*pref*3.0d0*rcuti4 &
903     * (a1*rcuti*d(1)-ct_i*uz_j(1)-ct_j*uz_i(1))
904     dudy = dudy + sw*pref*3.0d0*ri4 &
905     * (a1*yhat-ct_i*uz_j(2)-ct_j*uz_i(2)) &
906     - sw*pref*3.0d0*rcuti4 &
907     * (a1*rcuti*d(2)-ct_i*uz_j(2)-ct_j*uz_i(2))
908     dudz = dudz + sw*pref*3.0d0*ri4 &
909     * (a1*zhat-ct_i*uz_j(3)-ct_j*uz_i(3)) &
910     - sw*pref*3.0d0*rcuti4 &
911     * (a1*rcuti*d(3)-ct_i*uz_j(3)-ct_j*uz_i(3))
912 chrisfen 2296
913 chrisfen 2325 duduz_i(1) = duduz_i(1) + sw*pref*(ri3*(uz_j(1)-3.0d0*ct_j*xhat) &
914 chrisfen 2296 - rcuti3*(uz_j(1) - 3.0d0*ct_j*d(1)*rcuti))
915 chrisfen 2325 duduz_i(2) = duduz_i(2) + sw*pref*(ri3*(uz_j(2)-3.0d0*ct_j*yhat) &
916 chrisfen 2296 - rcuti3*(uz_j(2) - 3.0d0*ct_j*d(2)*rcuti))
917 chrisfen 2325 duduz_i(3) = duduz_i(3) + sw*pref*(ri3*(uz_j(3)-3.0d0*ct_j*zhat) &
918 chrisfen 2296 - rcuti3*(uz_j(3) - 3.0d0*ct_j*d(3)*rcuti))
919 chrisfen 2325 duduz_j(1) = duduz_j(1) + sw*pref*(ri3*(uz_i(1)-3.0d0*ct_i*xhat) &
920 chrisfen 2296 - rcuti3*(uz_i(1) - 3.0d0*ct_i*d(1)*rcuti))
921 chrisfen 2325 duduz_j(2) = duduz_j(2) + sw*pref*(ri3*(uz_i(2)-3.0d0*ct_i*yhat) &
922 chrisfen 2296 - rcuti3*(uz_i(2) - 3.0d0*ct_i*d(2)*rcuti))
923 chrisfen 2325 duduz_j(3) = duduz_j(3) + sw*pref*(ri3*(uz_i(3)-3.0d0*ct_i*zhat) &
924 chrisfen 2296 - rcuti3*(uz_i(3) - 3.0d0*ct_i*d(3)*rcuti))
925 chrisfen 2325
926 chrisfen 2296 else
927     if (i_is_SplitDipole) then
928     if (j_is_SplitDipole) then
929     BigR = sqrt(r2 + 0.25_dp * d_i * d_i + 0.25_dp * d_j * d_j)
930     else
931     BigR = sqrt(r2 + 0.25_dp * d_i * d_i)
932     endif
933     ri = 1.0_dp / BigR
934     scale = rij * ri
935     else
936     if (j_is_SplitDipole) then
937     BigR = sqrt(r2 + 0.25_dp * d_j * d_j)
938     ri = 1.0_dp / BigR
939     scale = rij * ri
940     else
941     ri = riji
942     scale = 1.0_dp
943     endif
944     endif
945    
946     ct_ij = uz_i(1)*uz_j(1) + uz_i(2)*uz_j(2) + uz_i(3)*uz_j(3)
947    
948     ri2 = ri * ri
949     ri3 = ri2 * ri
950     ri4 = ri2 * ri2
951     sc2 = scale * scale
952    
953 chrisfen 2325 pref = pre22 * mu_i * mu_j
954 chrisfen 2296 vterm = pref * ri3 * (ct_ij - 3.0d0 * ct_i * ct_j * sc2)
955 chrisfen 2325 vpair = vpair + vterm
956     epot = epot + sw*vterm
957 chrisfen 2296
958     a1 = 5.0d0 * ct_i * ct_j * sc2 - ct_ij
959    
960 chrisfen 2325 dudx = dudx + sw*pref*3.0d0*ri4*scale &
961     *(a1*xhat-ct_i*uz_j(1)-ct_j*uz_i(1))
962     dudy = dudy + sw*pref*3.0d0*ri4*scale &
963     *(a1*yhat-ct_i*uz_j(2)-ct_j*uz_i(2))
964     dudz = dudz + sw*pref*3.0d0*ri4*scale &
965     *(a1*zhat-ct_i*uz_j(3)-ct_j*uz_i(3))
966 chrisfen 2296
967 chrisfen 2325 duduz_i(1) = duduz_i(1) + sw*pref*ri3 &
968     *(uz_j(1) - 3.0d0*ct_j*xhat*sc2)
969     duduz_i(2) = duduz_i(2) + sw*pref*ri3 &
970     *(uz_j(2) - 3.0d0*ct_j*yhat*sc2)
971     duduz_i(3) = duduz_i(3) + sw*pref*ri3 &
972     *(uz_j(3) - 3.0d0*ct_j*zhat*sc2)
973 chrisfen 2296
974 chrisfen 2325 duduz_j(1) = duduz_j(1) + sw*pref*ri3 &
975     *(uz_i(1) - 3.0d0*ct_i*xhat*sc2)
976     duduz_j(2) = duduz_j(2) + sw*pref*ri3 &
977     *(uz_i(2) - 3.0d0*ct_i*yhat*sc2)
978     duduz_j(3) = duduz_j(3) + sw*pref*ri3 &
979     *(uz_i(3) - 3.0d0*ct_i*zhat*sc2)
980 chrisfen 2296 endif
981 gezelter 2095 endif
982     endif
983 gezelter 2123
984     if (i_is_Quadrupole) then
985     if (j_is_Charge) then
986 gezelter 2204
987 gezelter 2123 ri2 = riji * riji
988     ri3 = ri2 * riji
989 gezelter 2124 ri4 = ri2 * ri2
990 gezelter 2123 cx2 = cx_i * cx_i
991     cy2 = cy_i * cy_i
992     cz2 = cz_i * cz_i
993 gezelter 2204
994 chrisfen 2310 if (summationMethod .eq. UNDAMPED_WOLF) then
995 chrisfen 2325 pref = pre14 * q_j / 3.0_dp
996 chrisfen 2296 vterm1 = pref * ri3*( qxx_i * (3.0_dp*cx2 - 1.0_dp) + &
997     qyy_i * (3.0_dp*cy2 - 1.0_dp) + &
998     qzz_i * (3.0_dp*cz2 - 1.0_dp) )
999     vterm2 = pref * rcuti3*( qxx_i * (3.0_dp*cx2 - 1.0_dp) + &
1000     qyy_i * (3.0_dp*cy2 - 1.0_dp) + &
1001     qzz_i * (3.0_dp*cz2 - 1.0_dp) )
1002 chrisfen 2325 vpair = vpair + ( vterm1 - vterm2 )
1003     epot = epot + sw*( vterm1 - vterm2 )
1004 chrisfen 2296
1005 chrisfen 2325 dudx = dudx - sw*(5.0_dp*(vterm1*riji*xhat-vterm2*rcuti2*d(1))) +&
1006     sw*pref * ( (ri4 - rcuti4)*(qxx_i*(6.0_dp*cx_i*ux_i(1)) - &
1007 chrisfen 2296 qxx_i*2.0_dp*(xhat - rcuti*d(1))) + &
1008     (ri4 - rcuti4)*(qyy_i*(6.0_dp*cy_i*uy_i(1)) - &
1009     qyy_i*2.0_dp*(xhat - rcuti*d(1))) + &
1010     (ri4 - rcuti4)*(qzz_i*(6.0_dp*cz_i*uz_i(1)) - &
1011     qzz_i*2.0_dp*(xhat - rcuti*d(1))) )
1012 chrisfen 2325 dudy = dudy - sw*(5.0_dp*(vterm1*riji*yhat-vterm2*rcuti2*d(2))) +&
1013     sw*pref * ( (ri4 - rcuti4)*(qxx_i*(6.0_dp*cx_i*ux_i(2)) - &
1014 chrisfen 2296 qxx_i*2.0_dp*(yhat - rcuti*d(2))) + &
1015     (ri4 - rcuti4)*(qyy_i*(6.0_dp*cy_i*uy_i(2)) - &
1016     qyy_i*2.0_dp*(yhat - rcuti*d(2))) + &
1017     (ri4 - rcuti4)*(qzz_i*(6.0_dp*cz_i*uz_i(2)) - &
1018     qzz_i*2.0_dp*(yhat - rcuti*d(2))) )
1019 chrisfen 2325 dudz = dudz - sw*(5.0_dp*(vterm1*riji*zhat-vterm2*rcuti2*d(3))) +&
1020     sw*pref * ( (ri4 - rcuti4)*(qxx_i*(6.0_dp*cx_i*ux_i(3)) - &
1021 chrisfen 2296 qxx_i*2.0_dp*(zhat - rcuti*d(3))) + &
1022     (ri4 - rcuti4)*(qyy_i*(6.0_dp*cy_i*uy_i(3)) - &
1023     qyy_i*2.0_dp*(zhat - rcuti*d(3))) + &
1024     (ri4 - rcuti4)*(qzz_i*(6.0_dp*cz_i*uz_i(3)) - &
1025     qzz_i*2.0_dp*(zhat - rcuti*d(3))) )
1026    
1027 chrisfen 2325 dudux_i(1) = dudux_i(1) + sw*pref*(ri3*(qxx_i*6.0_dp*cx_i*xhat) -&
1028 chrisfen 2296 rcuti4*(qxx_i*6.0_dp*cx_i*d(1)))
1029 chrisfen 2325 dudux_i(2) = dudux_i(2) + sw*pref*(ri3*(qxx_i*6.0_dp*cx_i*yhat) -&
1030 chrisfen 2296 rcuti4*(qxx_i*6.0_dp*cx_i*d(2)))
1031 chrisfen 2325 dudux_i(3) = dudux_i(3) + sw*pref*(ri3*(qxx_i*6.0_dp*cx_i*zhat) -&
1032 chrisfen 2296 rcuti4*(qxx_i*6.0_dp*cx_i*d(3)))
1033    
1034 chrisfen 2325 duduy_i(1) = duduy_i(1) + sw*pref*(ri3*(qyy_i*6.0_dp*cy_i*xhat) -&
1035 chrisfen 2296 rcuti4*(qyy_i*6.0_dp*cx_i*d(1)))
1036 chrisfen 2325 duduy_i(2) = duduy_i(2) + sw*pref*(ri3*(qyy_i*6.0_dp*cy_i*yhat) -&
1037 chrisfen 2296 rcuti4*(qyy_i*6.0_dp*cx_i*d(2)))
1038 chrisfen 2325 duduy_i(3) = duduy_i(3) + sw*pref*(ri3*(qyy_i*6.0_dp*cy_i*zhat) -&
1039 chrisfen 2296 rcuti4*(qyy_i*6.0_dp*cx_i*d(3)))
1040    
1041 chrisfen 2325 duduz_i(1) = duduz_i(1) + sw*pref*(ri3*(qzz_i*6.0_dp*cz_i*xhat) -&
1042 chrisfen 2296 rcuti4*(qzz_i*6.0_dp*cx_i*d(1)))
1043 chrisfen 2325 duduz_i(2) = duduz_i(2) + sw*pref*(ri3*(qzz_i*6.0_dp*cz_i*yhat) -&
1044 chrisfen 2296 rcuti4*(qzz_i*6.0_dp*cx_i*d(2)))
1045 chrisfen 2325 duduz_i(3) = duduz_i(3) + sw*pref*(ri3*(qzz_i*6.0_dp*cz_i*zhat) -&
1046 chrisfen 2296 rcuti4*(qzz_i*6.0_dp*cx_i*d(3)))
1047 gezelter 2204
1048 chrisfen 2296 else
1049 chrisfen 2325 pref = pre14 * q_j / 3.0_dp
1050 chrisfen 2296 vterm = pref * ri3 * (qxx_i * (3.0_dp*cx2 - 1.0_dp) + &
1051     qyy_i * (3.0_dp*cy2 - 1.0_dp) + &
1052     qzz_i * (3.0_dp*cz2 - 1.0_dp))
1053 chrisfen 2325 vpair = vpair + vterm
1054     epot = epot + sw*vterm
1055 chrisfen 2296
1056 chrisfen 2325 dudx = dudx - 5.0_dp*sw*vterm*riji*xhat + sw*pref*ri4 * ( &
1057 chrisfen 2296 qxx_i*(6.0_dp*cx_i*ux_i(1) - 2.0_dp*xhat) + &
1058     qyy_i*(6.0_dp*cy_i*uy_i(1) - 2.0_dp*xhat) + &
1059     qzz_i*(6.0_dp*cz_i*uz_i(1) - 2.0_dp*xhat) )
1060 chrisfen 2325 dudy = dudy - 5.0_dp*sw*vterm*riji*yhat + sw*pref*ri4 * ( &
1061 chrisfen 2296 qxx_i*(6.0_dp*cx_i*ux_i(2) - 2.0_dp*yhat) + &
1062     qyy_i*(6.0_dp*cy_i*uy_i(2) - 2.0_dp*yhat) + &
1063     qzz_i*(6.0_dp*cz_i*uz_i(2) - 2.0_dp*yhat) )
1064 chrisfen 2325 dudz = dudz - 5.0_dp*sw*vterm*riji*zhat + sw*pref*ri4 * ( &
1065 chrisfen 2296 qxx_i*(6.0_dp*cx_i*ux_i(3) - 2.0_dp*zhat) + &
1066     qyy_i*(6.0_dp*cy_i*uy_i(3) - 2.0_dp*zhat) + &
1067     qzz_i*(6.0_dp*cz_i*uz_i(3) - 2.0_dp*zhat) )
1068    
1069 chrisfen 2325 dudux_i(1) = dudux_i(1) + sw*pref*ri3*(qxx_i*6.0_dp*cx_i*xhat)
1070     dudux_i(2) = dudux_i(2) + sw*pref*ri3*(qxx_i*6.0_dp*cx_i*yhat)
1071     dudux_i(3) = dudux_i(3) + sw*pref*ri3*(qxx_i*6.0_dp*cx_i*zhat)
1072 chrisfen 2296
1073 chrisfen 2325 duduy_i(1) = duduy_i(1) + sw*pref*ri3*(qyy_i*6.0_dp*cy_i*xhat)
1074     duduy_i(2) = duduy_i(2) + sw*pref*ri3*(qyy_i*6.0_dp*cy_i*yhat)
1075     duduy_i(3) = duduy_i(3) + sw*pref*ri3*(qyy_i*6.0_dp*cy_i*zhat)
1076 chrisfen 2296
1077 chrisfen 2325 duduz_i(1) = duduz_i(1) + sw*pref*ri3*(qzz_i*6.0_dp*cz_i*xhat)
1078     duduz_i(2) = duduz_i(2) + sw*pref*ri3*(qzz_i*6.0_dp*cz_i*yhat)
1079     duduz_i(3) = duduz_i(3) + sw*pref*ri3*(qzz_i*6.0_dp*cz_i*zhat)
1080 chrisfen 2296 endif
1081 gezelter 2123 endif
1082     endif
1083 gezelter 2204
1084    
1085 gezelter 2095 if (do_pot) then
1086     #ifdef IS_MPI
1087 chuckv 2355 pot_row(ELECTROSTATIC_POT,atom1) = pot_row(ELECTROSTATIC_POT,atom1) + 0.5d0*epot
1088     pot_col(ELECTROSTATIC_POT,atom2) = pot_col(ELECTROSTATIC_POT,atom2) + 0.5d0*epot
1089 gezelter 2095 #else
1090     pot = pot + epot
1091     #endif
1092     endif
1093 gezelter 2204
1094 gezelter 2095 #ifdef IS_MPI
1095     f_Row(1,atom1) = f_Row(1,atom1) + dudx
1096     f_Row(2,atom1) = f_Row(2,atom1) + dudy
1097     f_Row(3,atom1) = f_Row(3,atom1) + dudz
1098 gezelter 2204
1099 gezelter 2095 f_Col(1,atom2) = f_Col(1,atom2) - dudx
1100     f_Col(2,atom2) = f_Col(2,atom2) - dudy
1101     f_Col(3,atom2) = f_Col(3,atom2) - dudz
1102 gezelter 2204
1103 gezelter 2095 if (i_is_Dipole .or. i_is_Quadrupole) then
1104 gezelter 2123 t_Row(1,atom1)=t_Row(1,atom1) - uz_i(2)*duduz_i(3) + uz_i(3)*duduz_i(2)
1105     t_Row(2,atom1)=t_Row(2,atom1) - uz_i(3)*duduz_i(1) + uz_i(1)*duduz_i(3)
1106     t_Row(3,atom1)=t_Row(3,atom1) - uz_i(1)*duduz_i(2) + uz_i(2)*duduz_i(1)
1107 gezelter 2095 endif
1108 gezelter 2123 if (i_is_Quadrupole) then
1109     t_Row(1,atom1)=t_Row(1,atom1) - ux_i(2)*dudux_i(3) + ux_i(3)*dudux_i(2)
1110     t_Row(2,atom1)=t_Row(2,atom1) - ux_i(3)*dudux_i(1) + ux_i(1)*dudux_i(3)
1111     t_Row(3,atom1)=t_Row(3,atom1) - ux_i(1)*dudux_i(2) + ux_i(2)*dudux_i(1)
1112 gezelter 2095
1113 gezelter 2123 t_Row(1,atom1)=t_Row(1,atom1) - uy_i(2)*duduy_i(3) + uy_i(3)*duduy_i(2)
1114     t_Row(2,atom1)=t_Row(2,atom1) - uy_i(3)*duduy_i(1) + uy_i(1)*duduy_i(3)
1115     t_Row(3,atom1)=t_Row(3,atom1) - uy_i(1)*duduy_i(2) + uy_i(2)*duduy_i(1)
1116     endif
1117    
1118 gezelter 2095 if (j_is_Dipole .or. j_is_Quadrupole) then
1119 gezelter 2123 t_Col(1,atom2)=t_Col(1,atom2) - uz_j(2)*duduz_j(3) + uz_j(3)*duduz_j(2)
1120     t_Col(2,atom2)=t_Col(2,atom2) - uz_j(3)*duduz_j(1) + uz_j(1)*duduz_j(3)
1121     t_Col(3,atom2)=t_Col(3,atom2) - uz_j(1)*duduz_j(2) + uz_j(2)*duduz_j(1)
1122 gezelter 2095 endif
1123 gezelter 2123 if (j_is_Quadrupole) then
1124     t_Col(1,atom2)=t_Col(1,atom2) - ux_j(2)*dudux_j(3) + ux_j(3)*dudux_j(2)
1125     t_Col(2,atom2)=t_Col(2,atom2) - ux_j(3)*dudux_j(1) + ux_j(1)*dudux_j(3)
1126     t_Col(3,atom2)=t_Col(3,atom2) - ux_j(1)*dudux_j(2) + ux_j(2)*dudux_j(1)
1127 gezelter 2095
1128 gezelter 2123 t_Col(1,atom2)=t_Col(1,atom2) - uy_j(2)*duduy_j(3) + uy_j(3)*duduy_j(2)
1129     t_Col(2,atom2)=t_Col(2,atom2) - uy_j(3)*duduy_j(1) + uy_j(1)*duduy_j(3)
1130     t_Col(3,atom2)=t_Col(3,atom2) - uy_j(1)*duduy_j(2) + uy_j(2)*duduy_j(1)
1131     endif
1132    
1133 gezelter 2095 #else
1134     f(1,atom1) = f(1,atom1) + dudx
1135     f(2,atom1) = f(2,atom1) + dudy
1136     f(3,atom1) = f(3,atom1) + dudz
1137 gezelter 2204
1138 gezelter 2095 f(1,atom2) = f(1,atom2) - dudx
1139     f(2,atom2) = f(2,atom2) - dudy
1140     f(3,atom2) = f(3,atom2) - dudz
1141 gezelter 2204
1142 gezelter 2095 if (i_is_Dipole .or. i_is_Quadrupole) then
1143 gezelter 2123 t(1,atom1)=t(1,atom1) - uz_i(2)*duduz_i(3) + uz_i(3)*duduz_i(2)
1144     t(2,atom1)=t(2,atom1) - uz_i(3)*duduz_i(1) + uz_i(1)*duduz_i(3)
1145     t(3,atom1)=t(3,atom1) - uz_i(1)*duduz_i(2) + uz_i(2)*duduz_i(1)
1146 gezelter 2095 endif
1147 gezelter 2123 if (i_is_Quadrupole) then
1148     t(1,atom1)=t(1,atom1) - ux_i(2)*dudux_i(3) + ux_i(3)*dudux_i(2)
1149     t(2,atom1)=t(2,atom1) - ux_i(3)*dudux_i(1) + ux_i(1)*dudux_i(3)
1150     t(3,atom1)=t(3,atom1) - ux_i(1)*dudux_i(2) + ux_i(2)*dudux_i(1)
1151    
1152     t(1,atom1)=t(1,atom1) - uy_i(2)*duduy_i(3) + uy_i(3)*duduy_i(2)
1153     t(2,atom1)=t(2,atom1) - uy_i(3)*duduy_i(1) + uy_i(1)*duduy_i(3)
1154     t(3,atom1)=t(3,atom1) - uy_i(1)*duduy_i(2) + uy_i(2)*duduy_i(1)
1155     endif
1156    
1157 gezelter 2095 if (j_is_Dipole .or. j_is_Quadrupole) then
1158 gezelter 2123 t(1,atom2)=t(1,atom2) - uz_j(2)*duduz_j(3) + uz_j(3)*duduz_j(2)
1159     t(2,atom2)=t(2,atom2) - uz_j(3)*duduz_j(1) + uz_j(1)*duduz_j(3)
1160     t(3,atom2)=t(3,atom2) - uz_j(1)*duduz_j(2) + uz_j(2)*duduz_j(1)
1161 gezelter 2095 endif
1162 gezelter 2123 if (j_is_Quadrupole) then
1163     t(1,atom2)=t(1,atom2) - ux_j(2)*dudux_j(3) + ux_j(3)*dudux_j(2)
1164     t(2,atom2)=t(2,atom2) - ux_j(3)*dudux_j(1) + ux_j(1)*dudux_j(3)
1165     t(3,atom2)=t(3,atom2) - ux_j(1)*dudux_j(2) + ux_j(2)*dudux_j(1)
1166    
1167     t(1,atom2)=t(1,atom2) - uy_j(2)*duduy_j(3) + uy_j(3)*duduy_j(2)
1168     t(2,atom2)=t(2,atom2) - uy_j(3)*duduy_j(1) + uy_j(1)*duduy_j(3)
1169     t(3,atom2)=t(3,atom2) - uy_j(1)*duduy_j(2) + uy_j(2)*duduy_j(1)
1170     endif
1171    
1172 gezelter 2095 #endif
1173 gezelter 2204
1174 gezelter 2095 #ifdef IS_MPI
1175     id1 = AtomRowToGlobal(atom1)
1176     id2 = AtomColToGlobal(atom2)
1177     #else
1178     id1 = atom1
1179     id2 = atom2
1180     #endif
1181    
1182     if (molMembershipList(id1) .ne. molMembershipList(id2)) then
1183 gezelter 2204
1184 gezelter 2095 fpair(1) = fpair(1) + dudx
1185     fpair(2) = fpair(2) + dudy
1186     fpair(3) = fpair(3) + dudz
1187    
1188     endif
1189    
1190     return
1191     end subroutine doElectrostaticPair
1192 chuckv 2189
1193 chrisfen 2229 !! calculates the switching functions and their derivatives for a given
1194     subroutine calc_switch(r, mu, scale, dscale)
1195 gezelter 2204
1196 chrisfen 2229 real (kind=dp), intent(in) :: r, mu
1197     real (kind=dp), intent(inout) :: scale, dscale
1198     real (kind=dp) :: rl, ru, mulow, minRatio, temp, scaleVal
1199    
1200     ! distances must be in angstroms
1201     rl = 2.75d0
1202 chrisfen 2231 ru = 3.75d0
1203     mulow = 0.0d0 !3.3856d0 ! 1.84 * 1.84
1204 chrisfen 2229 minRatio = mulow / (mu*mu)
1205     scaleVal = 1.0d0 - minRatio
1206    
1207     if (r.lt.rl) then
1208     scale = minRatio
1209     dscale = 0.0d0
1210     elseif (r.gt.ru) then
1211     scale = 1.0d0
1212     dscale = 0.0d0
1213     else
1214     scale = 1.0d0 - scaleVal*((ru + 2.0d0*r - 3.0d0*rl) * (ru-r)**2) &
1215     / ((ru - rl)**3)
1216     dscale = -scaleVal * 6.0d0 * (r-ru)*(r-rl)/((ru - rl)**3)
1217     endif
1218    
1219     return
1220     end subroutine calc_switch
1221    
1222 chuckv 2189 subroutine destroyElectrostaticTypes()
1223    
1224 gezelter 2204 if(allocated(ElectrostaticMap)) deallocate(ElectrostaticMap)
1225    
1226 chuckv 2189 end subroutine destroyElectrostaticTypes
1227    
1228 gezelter 2095 end module electrostatic_module