ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/DarkSide/electrostatic.F90
Revision: 2715
Committed: Sun Apr 16 02:51:16 2006 UTC (18 years, 4 months ago) by chrisfen
File size: 52693 byte(s)
Log Message:
added a cubic spline to switcheroo

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