ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/DarkSide/electrostatic.F90
(Generate patch)

Comparing trunk/OOPSE-4/src/UseTheForce/DarkSide/electrostatic.F90 (file contents):
Revision 2390 by chrisfen, Wed Oct 19 19:24:40 2005 UTC vs.
Revision 2715 by chrisfen, Sun Apr 16 02:51:16 2006 UTC

# Line 47 | Line 47 | module electrostatic_module
47    use vector_class
48    use simulation
49    use status
50 +  use interpolation
51   #ifdef IS_MPI
52    use mpiSimulation
53   #endif
# Line 58 | Line 59 | module electrostatic_module
59   #define __FORTRAN90
60   #include "UseTheForce/DarkSide/fInteractionMap.h"
61   #include "UseTheForce/DarkSide/fElectrostaticSummationMethod.h"
62 + #include "UseTheForce/DarkSide/fElectrostaticScreeningMethod.h"
63  
64  
65    !! these prefactors convert the multipole interactions into kcal / mol
# Line 74 | Line 76 | module electrostatic_module
76    !! This unit is also known affectionately as an esu centi-barn.
77    real(kind=dp), parameter :: pre14 = 69.13373_dp
78  
79 <  !! variables to handle different summation methods for long-range electrostatics:
79 >  !! variables to handle different summation methods for long-range
80 >  !! electrostatics:
81    integer, save :: summationMethod = NONE
82 +  integer, save :: screeningMethod = UNDAMPED
83    logical, save :: summationMethodChecked = .false.
84    real(kind=DP), save :: defaultCutoff = 0.0_DP
85    real(kind=DP), save :: defaultCutoff2 = 0.0_DP
86    logical, save :: haveDefaultCutoff = .false.
87    real(kind=DP), save :: dampingAlpha = 0.0_DP
88 +  real(kind=DP), save :: alpha2 = 0.0_DP
89    logical, save :: haveDampingAlpha = .false.
90    real(kind=DP), save :: dielectric = 1.0_DP
91    logical, save :: haveDielectric = .false.
87  real(kind=DP), save :: constERFC = 0.0_DP
92    real(kind=DP), save :: constEXP = 0.0_DP
89  logical, save :: haveDWAconstants = .false.
93    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
# Line 97 | Line 100 | module electrostatic_module
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 <  logical, save :: preRFCalculated = .false.
104 <
105 < #ifdef __IFC
103 >  real(kind=dp), save :: preRF2 = 0.0_DP
104 >  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 >  real(kind=dp), save :: f3 = 0.0_DP
108 >  real(kind=dp), save :: f4 = 0.0_DP
109 >  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 >  real(kind=dp), save :: f3c = 0.0_DP
113 >  real(kind=dp), save :: f4c = 0.0_DP
114 >
115 > #if defined(__IFC) || defined(__PGI)
116   ! error function for ifc version > 7.
117    double precision, external :: derfc
118   #endif
119    
120    public :: setElectrostaticSummationMethod
121 +  public :: setScreeningMethod
122    public :: setElectrostaticCutoffRadius
123 <  public :: setDampedWolfAlpha
123 >  public :: setDampingAlpha
124    public :: setReactionFieldDielectric
125 <  public :: setReactionFieldPrefactor
125 >  public :: buildElectroSplines
126    public :: newElectrostaticType
127    public :: setCharge
128    public :: setDipoleMoment
# Line 117 | Line 131 | module electrostatic_module
131    public :: doElectrostaticPair
132    public :: getCharge
133    public :: getDipoleMoment
120  public :: pre22
134    public :: destroyElectrostaticTypes
135 <  public :: accumulate_rf
136 <  public :: accumulate_self_rf
124 <  public :: reaction_field_final
125 <  public :: rf_correct_forces
135 >  public :: self_self
136 >  public :: rf_self_excludes
137  
138 +
139    type :: Electrostatic
140       integer :: c_ident
141       logical :: is_Charge = .false.
# Line 152 | Line 164 | contains
164  
165    end subroutine setElectrostaticSummationMethod
166  
167 +  subroutine setScreeningMethod(the_SM)
168 +    integer, intent(in) :: the_SM    
169 +    screeningMethod = the_SM
170 +  end subroutine setScreeningMethod
171 +
172    subroutine setElectrostaticCutoffRadius(thisRcut, thisRsw)
173      real(kind=dp), intent(in) :: thisRcut
174      real(kind=dp), intent(in) :: thisRsw
175      defaultCutoff = thisRcut
176 +    defaultCutoff2 = defaultCutoff*defaultCutoff
177      rrf = defaultCutoff
178      rt = thisRsw
179      haveDefaultCutoff = .true.
180    end subroutine setElectrostaticCutoffRadius
181  
182 <  subroutine setDampedWolfAlpha(thisAlpha)
182 >  subroutine setDampingAlpha(thisAlpha)
183      real(kind=dp), intent(in) :: thisAlpha
184      dampingAlpha = thisAlpha
185 +    alpha2 = dampingAlpha*dampingAlpha
186      haveDampingAlpha = .true.
187 <  end subroutine setDampedWolfAlpha
187 >  end subroutine setDampingAlpha
188    
189    subroutine setReactionFieldDielectric(thisDielectric)
190      real(kind=dp), intent(in) :: thisDielectric
# Line 173 | Line 192 | contains
192      haveDielectric = .true.
193    end subroutine setReactionFieldDielectric
194  
195 <  subroutine setReactionFieldPrefactor
196 <    if (haveDefaultCutoff .and. haveDielectric) then
178 <       defaultCutoff2 = defaultCutoff*defaultCutoff
179 <       preRF = pre22 * 2.0d0*(dielectric-1.0d0) / &
180 <            ((2.0d0*dielectric+1.0d0)*defaultCutoff2*defaultCutoff)
181 <       preRFCalculated = .true.
182 <    else if (.not.haveDefaultCutoff) then
183 <       call handleError("setReactionFieldPrefactor", "Default cutoff not set")
184 <    else
185 <       call handleError("setReactionFieldPrefactor", "Dielectric not set")
186 <    endif
187 <  end subroutine setReactionFieldPrefactor
195 >  subroutine buildElectroSplines()
196 >  end subroutine buildElectroSplines
197  
198    subroutine newElectrostaticType(c_ident, is_Charge, is_Dipole, &
199         is_SplitDipole, is_Quadrupole, is_Tap, status)
# Line 407 | Line 416 | contains
416      rcuti3 = rcuti2*rcuti
417      rcuti4 = rcuti2*rcuti2
418  
419 <    if (summationMethod .eq. DAMPED_WOLF) then
420 <       if (.not.haveDWAconstants) then
421 <          
422 <          if (.not.haveDampingAlpha) then
423 <             call handleError("checkSummationMethod", "no Damping Alpha set!")
424 <          endif
425 <          
417 <          if (.not.haveDefaultCutoff) then
418 <             call handleError("checkSummationMethod", "no Default Cutoff set!")
419 <          endif
420 <
421 <          constEXP = exp(-dampingAlpha*dampingAlpha*defaultCutoff*defaultCutoff)
422 <          constERFC = derfc(dampingAlpha*defaultCutoff)
423 <          invRootPi = 0.56418958354775628695d0
424 <          alphaPi = 2*dampingAlpha*invRootPi
425 <  
426 <          haveDWAconstants = .true.
419 >    if (screeningMethod .eq. DAMPED) then
420 >       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 +
428 +       constEXP = exp(-alpha2*defaultCutoff2)
429 +       invRootPi = 0.56418958354775628695d0
430 +       alphaPi = 2.0d0*dampingAlpha*invRootPi
431 +       f0c = derfc(dampingAlpha*defaultCutoff)
432 +       f1c = alphaPi*defaultCutoff*constEXP + f0c
433 +       f2c = alphaPi*2.0d0*alpha2*constEXP
434 +       f3c = alphaPi*2.0d0*alpha2*constEXP*defaultCutoff2*defaultCutoff
435      endif
436  
437      if (summationMethod .eq. REACTION_FIELD) then
438 <       if (.not.haveDielectric) then
439 <          call handleError("checkSummationMethod", "no reaction field Dielectric set!")
438 >       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         endif
446 +      
447      endif
448  
449      summationMethodChecked = .true.
450    end subroutine checkSummationMethod
451  
452  
453 <
441 <  subroutine doElectrostaticPair(atom1, atom2, d, rij, r2, sw, &
453 >  subroutine doElectrostaticPair(atom1, atom2, d, rij, r2, rcut, sw, &
454         vpair, fpair, pot, eFrame, f, t, do_pot)
455  
456      logical, intent(in) :: do_pot
# Line 446 | Line 458 | contains
458      integer, intent(in) :: atom1, atom2
459      integer :: localError
460  
461 <    real(kind=dp), intent(in) :: rij, r2, sw
461 >    real(kind=dp), intent(in) :: rij, r2, sw, rcut
462      real(kind=dp), intent(in), dimension(3) :: d
463      real(kind=dp), intent(inout) :: vpair
464 <    real(kind=dp), intent(inout), dimension(3) :: fpair
464 >    real(kind=dp), intent(inout), dimension(3) :: fpair    
465  
466      real( kind = dp ) :: pot
467      real( kind = dp ), dimension(9,nLocal) :: eFrame
468      real( kind = dp ), dimension(3,nLocal) :: f
469 +    real( kind = dp ), dimension(3,nLocal) :: felec
470      real( kind = dp ), dimension(3,nLocal) :: t
471  
472      real (kind = dp), dimension(3) :: ux_i, uy_i, uz_i
# Line 471 | Line 484 | contains
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 <    real (kind=dp) :: ct_i, ct_j, ct_ij, a1
487 >    real (kind=dp) :: ct_i, ct_j, ct_ij, a0, a1
488      real (kind=dp) :: riji, ri, ri2, ri3, ri4
489      real (kind=dp) :: pref, vterm, epot, dudr, vterm1, vterm2
490      real (kind=dp) :: xhat, yhat, zhat
491      real (kind=dp) :: dudx, dudy, dudz
492      real (kind=dp) :: scale, sc2, bigR
493 <    real (kind=dp) :: varERFC, varEXP
494 <    real (kind=dp) :: limScale
493 >    real (kind=dp) :: varEXP
494 >    real (kind=dp) :: pot_term
495 >    real (kind=dp) :: preVal, rfVal
496 >    real (kind=dp) :: f13, f134
497  
498      if (.not.allocated(ElectrostaticMap)) then
499         call handleError("electrostatic", "no ElectrostaticMap was present before first call of do_electrostatic_pair!")
# Line 487 | Line 502 | contains
502  
503      if (.not.summationMethodChecked) then
504         call checkSummationMethod()
490      
505      endif
506  
493
507   #ifdef IS_MPI
508      me1 = atid_Row(atom1)
509      me2 = atid_Col(atom2)
# Line 641 | Line 654 | contains
654      if (i_is_Charge) then
655  
656         if (j_is_Charge) then
657 +          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  
663 <          if (summationMethod .eq. UNDAMPED_WOLF) then
663 >          preVal = pre11 * q_i * q_j
664  
665 <             vterm = pre11 * q_i * q_j * (riji - rcuti)
666 <             vpair = vpair + vterm
649 <             epot = epot + sw*vterm
665 >          if (summationMethod .eq. SHIFTED_POTENTIAL) then
666 >             vterm = preVal * (riji*f0 - rcuti*f0c)
667              
668 <             dudr  = -sw*pre11*q_i*q_j * (riji*riji-rcuti2)*riji
668 >             dudr  = -sw * preVal * riji * riji * f1
669 >  
670 >          elseif (summationMethod .eq. SHIFTED_FORCE) then
671 >             vterm = preVal * ( riji*f0 - rcuti*f0c + &
672 >                  f1c*rcuti2*(rij-defaultCutoff) )
673              
674 <             dudx = dudx + dudr * d(1)
675 <             dudy = dudy + dudr * d(2)
676 <             dudz = dudz + dudr * d(3)
677 <
678 <          elseif (summationMethod .eq. DAMPED_WOLF) then
658 <
659 <             varERFC = derfc(dampingAlpha*rij)
660 <             varEXP = exp(-dampingAlpha*dampingAlpha*rij*rij)
661 <             vterm = pre11 * q_i * q_j * (varERFC*riji - constERFC*rcuti)
662 <             vpair = vpair + vterm
663 <             epot = epot + sw*vterm
674 >             dudr  = -sw*preVal * (riji*riji*f1 - rcuti2*f1c)
675 >  
676 >          elseif (summationMethod .eq. REACTION_FIELD) then
677 >             rfVal = preRF*rij*rij
678 >             vterm = preVal * ( riji + rfVal )
679              
680 <             dudr  = -sw*pre11*q_i*q_j * ( riji*((varERFC*riji*riji &
681 <                                                  + alphaPi*varEXP) &
667 <                                                 - (constERFC*rcuti2 &
668 <                                                    + alphaPi*constEXP)) )
669 <            
670 <             dudx = dudx + dudr * d(1)
671 <             dudy = dudy + dudr * d(2)
672 <             dudz = dudz + dudr * d(3)
673 <
680 >             dudr  = sw * preVal * ( 2.0d0*rfVal - riji )*riji
681 >  
682            else
683 <
676 <             vterm = pre11 * q_i * q_j * riji
677 <             vpair = vpair + vterm
678 <             epot = epot + sw*vterm
683 >             vterm = preVal * riji*f0
684              
685 <             dudr  = - sw * vterm * riji
686 <            
682 <             dudx = dudx + dudr * xhat
683 <             dudy = dudy + dudr * yhat
684 <             dudz = dudz + dudr * zhat
685 <
685 >             dudr  = - sw * preVal * riji*riji*f1
686 >  
687            endif
688  
689 +          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         endif
697  
698         if (j_is_Dipole) then
699 +          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  
706            pref = pre12 * q_i * mu_j
707  
708 <          if (summationMethod .eq. UNDAMPED_WOLF) then
708 >          if (summationMethod .eq. REACTION_FIELD) then
709               ri2 = riji * riji
710               ri3 = ri2 * riji
711 <
712 <             pref = pre12 * q_i * mu_j
699 <             vterm = - pref * ct_j * (ri2 - rcuti2)
711 >    
712 >             vterm = - pref * ct_j * ( ri2 - preRF2*rij )
713               vpair = vpair + vterm
714               epot = epot + sw*vterm
715              
# Line 704 | Line 717 | contains
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 <                  - rcuti3*( uz_j(1) - 3.0d0*ct_j*d(1)*rcuti ) )
722 <             dudy = dudy - sw*pref * ( ri3*( uz_j(2) - 3.0d0*ct_j*yhat) &
723 <                  - rcuti3*( uz_j(2) - 3.0d0*ct_j*d(2)*rcuti ) )
724 <             dudz = dudz - sw*pref * ( ri3*( uz_j(3) - 3.0d0*ct_j*zhat) &
725 <                  - rcuti3*( uz_j(3) - 3.0d0*ct_j*d(3)*rcuti ) )
726 <            
727 <             duduz_j(1) = duduz_j(1) - sw*pref*( ri2*xhat - d(1)*rcuti3 )
728 <             duduz_j(2) = duduz_j(2) - sw*pref*( ri2*yhat - d(2)*rcuti3 )
716 <             duduz_j(3) = duduz_j(3) - sw*pref*( ri2*zhat - d(3)*rcuti3 )
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            else
731               if (j_is_SplitDipole) then
# Line 729 | Line 741 | contains
741               ri3 = ri2 * ri
742               sc2 = scale * scale
743  
744 <             pref = pre12 * q_i * mu_j
745 <             vterm = - pref * ct_j * ri2 * scale
744 >             pot_term =  ri2 * scale * f1
745 >             vterm = - pref * ct_j * pot_term
746               vpair = vpair + vterm
747               epot = epot + sw*vterm
748              
# Line 738 | Line 750 | contains
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 <             dudx = dudx - sw*pref * ri3 * ( uz_j(1) - 3.0d0*ct_j*xhat*sc2)
754 <             dudy = dudy - sw*pref * ri3 * ( uz_j(2) - 3.0d0*ct_j*yhat*sc2)
755 <             dudz = dudz - sw*pref * ri3 * ( uz_j(3) - 3.0d0*ct_j*zhat*sc2)
756 <            
757 <             duduz_j(1) = duduz_j(1) - sw*pref * ri2 * xhat * scale
758 <             duduz_j(2) = duduz_j(2) - sw*pref * ri2 * yhat * scale
759 <             duduz_j(3) = duduz_j(3) - sw*pref * ri2 * zhat * scale
753 >             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  
764            endif
765         endif
766  
767         if (j_is_Quadrupole) then
768 +          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            ri2 = riji * riji
778            ri3 = ri2 * riji
779            ri4 = ri2 * ri2
# Line 757 | Line 781 | contains
781            cy2 = cy_j * cy_j
782            cz2 = cz_j * cz_j
783  
784 <          if (summationMethod .eq. UNDAMPED_WOLF) then
785 <             pref =  pre14 * q_i / 3.0_dp
786 <             vterm1 = pref * ri3*( qxx_j * (3.0_dp*cx2 - 1.0_dp) + &
787 <                  qyy_j * (3.0_dp*cy2 - 1.0_dp) + &
788 <                  qzz_j * (3.0_dp*cz2 - 1.0_dp) )
789 <             vterm2 = pref * rcuti3*( qxx_j * (3.0_dp*cx2 - 1.0_dp) + &
790 <                  qyy_j * (3.0_dp*cy2 - 1.0_dp) + &
767 <                  qzz_j * (3.0_dp*cz2 - 1.0_dp) )
768 <             vpair = vpair + ( vterm1 - vterm2 )
769 <             epot = epot + sw*( vterm1 - vterm2 )
770 <            
771 <             dudx = dudx - (5.0_dp * &
772 <                  (vterm1*riji*xhat - vterm2*rcuti2*d(1))) + sw*pref * ( &
773 <                  (ri4 - rcuti4)*(qxx_j*(6.0_dp*cx_j*ux_j(1)) - &
774 <                  qxx_j*2.0_dp*(xhat - rcuti*d(1))) + &
775 <                  (ri4 - rcuti4)*(qyy_j*(6.0_dp*cy_j*uy_j(1)) - &
776 <                  qyy_j*2.0_dp*(xhat - rcuti*d(1))) + &
777 <                  (ri4 - rcuti4)*(qzz_j*(6.0_dp*cz_j*uz_j(1)) - &
778 <                  qzz_j*2.0_dp*(xhat - rcuti*d(1))) )
779 <             dudy = dudy - (5.0_dp * &
780 <                  (vterm1*riji*yhat - vterm2*rcuti2*d(2))) + sw*pref * ( &
781 <                  (ri4 - rcuti4)*(qxx_j*(6.0_dp*cx_j*ux_j(2)) - &
782 <                  qxx_j*2.0_dp*(yhat - rcuti*d(2))) + &
783 <                  (ri4 - rcuti4)*(qyy_j*(6.0_dp*cy_j*uy_j(2)) - &
784 <                  qyy_j*2.0_dp*(yhat - rcuti*d(2))) + &
785 <                  (ri4 - rcuti4)*(qzz_j*(6.0_dp*cz_j*uz_j(2)) - &
786 <                  qzz_j*2.0_dp*(yhat - rcuti*d(2))) )
787 <             dudz = dudz - (5.0_dp * &
788 <                  (vterm1*riji*zhat - vterm2*rcuti2*d(3))) + sw*pref * ( &
789 <                  (ri4 - rcuti4)*(qxx_j*(6.0_dp*cx_j*ux_j(3)) - &
790 <                  qxx_j*2.0_dp*(zhat - rcuti*d(3))) + &
791 <                  (ri4 - rcuti4)*(qyy_j*(6.0_dp*cy_j*uy_j(3)) - &
792 <                  qyy_j*2.0_dp*(zhat - rcuti*d(3))) + &
793 <                  (ri4 - rcuti4)*(qzz_j*(6.0_dp*cz_j*uz_j(3)) - &
794 <                  qzz_j*2.0_dp*(zhat - rcuti*d(3))) )
795 <            
796 <             dudux_j(1) = dudux_j(1) + sw*pref*(ri3*(qxx_j*6.0_dp*cx_j*xhat) -&
797 <                  rcuti4*(qxx_j*6.0_dp*cx_j*d(1)))
798 <             dudux_j(2) = dudux_j(2) + sw*pref*(ri3*(qxx_j*6.0_dp*cx_j*yhat) -&
799 <                  rcuti4*(qxx_j*6.0_dp*cx_j*d(2)))
800 <             dudux_j(3) = dudux_j(3) + sw*pref*(ri3*(qxx_j*6.0_dp*cx_j*zhat) -&
801 <                  rcuti4*(qxx_j*6.0_dp*cx_j*d(3)))
802 <            
803 <             duduy_j(1) = duduy_j(1) + sw*pref*(ri3*(qyy_j*6.0_dp*cy_j*xhat) -&
804 <                  rcuti4*(qyy_j*6.0_dp*cx_j*d(1)))
805 <             duduy_j(2) = duduy_j(2) + sw*pref*(ri3*(qyy_j*6.0_dp*cy_j*yhat) -&
806 <                  rcuti4*(qyy_j*6.0_dp*cx_j*d(2)))
807 <             duduy_j(3) = duduy_j(3) + sw*pref*(ri3*(qyy_j*6.0_dp*cy_j*zhat) -&
808 <                  rcuti4*(qyy_j*6.0_dp*cx_j*d(3)))
809 <            
810 <             duduz_j(1) = duduz_j(1) + sw*pref*(ri3*(qzz_j*6.0_dp*cz_j*xhat) -&
811 <                  rcuti4*(qzz_j*6.0_dp*cx_j*d(1)))
812 <             duduz_j(2) = duduz_j(2) + sw*pref*(ri3*(qzz_j*6.0_dp*cz_j*yhat) -&
813 <                  rcuti4*(qzz_j*6.0_dp*cx_j*d(2)))
814 <             duduz_j(3) = duduz_j(3) + sw*pref*(ri3*(qzz_j*6.0_dp*cz_j*zhat) -&
815 <                  rcuti4*(qzz_j*6.0_dp*cx_j*d(3)))
816 <        
817 <          else
818 <             pref =  pre14 * q_i / 3.0_dp
819 <             vterm = pref * ri3 * (qxx_j * (3.0_dp*cx2 - 1.0_dp) + &
820 <                  qyy_j * (3.0_dp*cy2 - 1.0_dp) + &
821 <                  qzz_j * (3.0_dp*cz2 - 1.0_dp))
822 <             vpair = vpair + vterm
823 <             epot = epot + sw*vterm
824 <            
825 <             dudx = dudx - 5.0_dp*sw*vterm*riji*xhat + sw*pref * ri4 * ( &
826 <                  qxx_j*(6.0_dp*cx_j*ux_j(1) - 2.0_dp*xhat) + &
827 <                  qyy_j*(6.0_dp*cy_j*uy_j(1) - 2.0_dp*xhat) + &
828 <                  qzz_j*(6.0_dp*cz_j*uz_j(1) - 2.0_dp*xhat) )
829 <             dudy = dudy - 5.0_dp*sw*vterm*riji*yhat + sw*pref * ri4 * ( &
830 <                  qxx_j*(6.0_dp*cx_j*ux_j(2) - 2.0_dp*yhat) + &
831 <                  qyy_j*(6.0_dp*cy_j*uy_j(2) - 2.0_dp*yhat) + &
832 <                  qzz_j*(6.0_dp*cz_j*uz_j(2) - 2.0_dp*yhat) )
833 <             dudz = dudz - 5.0_dp*sw*vterm*riji*zhat + sw*pref * ri4 * ( &
834 <                  qxx_j*(6.0_dp*cx_j*ux_j(3) - 2.0_dp*zhat) + &
835 <                  qyy_j*(6.0_dp*cy_j*uy_j(3) - 2.0_dp*zhat) + &
836 <                  qzz_j*(6.0_dp*cz_j*uz_j(3) - 2.0_dp*zhat) )
837 <            
838 <             dudux_j(1) = dudux_j(1) + sw*pref * ri3*(qxx_j*6.0_dp*cx_j*xhat)
839 <             dudux_j(2) = dudux_j(2) + sw*pref * ri3*(qxx_j*6.0_dp*cx_j*yhat)
840 <             dudux_j(3) = dudux_j(3) + sw*pref * ri3*(qxx_j*6.0_dp*cx_j*zhat)
841 <            
842 <             duduy_j(1) = duduy_j(1) + sw*pref * ri3*(qyy_j*6.0_dp*cy_j*xhat)
843 <             duduy_j(2) = duduy_j(2) + sw*pref * ri3*(qyy_j*6.0_dp*cy_j*yhat)
844 <             duduy_j(3) = duduy_j(3) + sw*pref * ri3*(qyy_j*6.0_dp*cy_j*zhat)
845 <            
846 <             duduz_j(1) = duduz_j(1) + sw*pref * ri3*(qzz_j*6.0_dp*cz_j*xhat)
847 <             duduz_j(2) = duduz_j(2) + sw*pref * ri3*(qzz_j*6.0_dp*cz_j*yhat)
848 <             duduz_j(3) = duduz_j(3) + sw*pref * ri3*(qzz_j*6.0_dp*cz_j*zhat)
784 >          pref =  pre14 * q_i / 3.0_dp
785 >          pot_term = ri3*(qxx_j * (3.0_dp*cx2 - 1.0_dp) + &
786 >               qyy_j * (3.0_dp*cy2 - 1.0_dp) + &
787 >               qzz_j * (3.0_dp*cz2 - 1.0_dp))
788 >          vterm = pref * (pot_term*f1 + (qxx_j*cx2 + qyy_j*cy2 + qzz_j*cz2)*f2)
789 >          vpair = vpair + vterm
790 >          epot = epot + sw*vterm
791            
792 <          endif
792 >          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 >          
811 >          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 >          
818 >          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 >          
825 >          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         endif
833      endif
834 <
834 >    
835      if (i_is_Dipole) then
836  
837         if (j_is_Charge) then
838 +          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            
845            pref = pre12 * q_j * mu_i
846            
847 <          if (summationMethod .eq. UNDAMPED_WOLF) then
847 >          if (summationMethod .eq. SHIFTED_POTENTIAL) then
848               ri2 = riji * riji
849               ri3 = ri2 * riji
850 +            
851 +             pot_term = ri2*f1 - rcuti2*f1c
852 +             vterm = pref * ct_i * pot_term
853 +             vpair = vpair + vterm
854 +             epot = epot + sw*vterm
855 +            
856 +             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 +            
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  
864 <             pref = pre12 * q_j * mu_i
865 <             vterm = pref * ct_i * (ri2 - rcuti2)
864 >          elseif (summationMethod .eq. SHIFTED_FORCE) then
865 >             ri2 = riji * riji
866 >             ri3 = ri2 * riji
867 >
868 >             !! 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 >             vterm = pref * ct_i * pot_term
872               vpair = vpair + vterm
873               epot = epot + sw*vterm
874              
875 <             !! this has a + sign in the () because the rij vector is
876 <             !! r_j - r_i and the charge-dipole potential takes the origin
877 <             !! as the point dipole, which is atom j in this case.
875 >             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              
882 <             dudx = dudx + sw*pref * ( ri3*( uz_i(1) - 3.0d0*ct_i*xhat) &
883 <                  - rcuti3*( uz_i(1) - 3.0d0*ct_i*d(1)*rcuti ) )
884 <             dudy = dudy + sw*pref * ( ri3*( uz_i(2) - 3.0d0*ct_i*yhat) &
885 <                  - rcuti3*( uz_i(2) - 3.0d0*ct_i*d(2)*rcuti ) )
886 <             dudz = dudz + sw*pref * ( ri3*( uz_i(3) - 3.0d0*ct_i*zhat) &
887 <                  - rcuti3*( uz_i(3) - 3.0d0*ct_i*d(3)*rcuti ) )
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 >
886 >          elseif (summationMethod .eq. REACTION_FIELD) then
887 >             ri2 = riji * riji
888 >             ri3 = ri2 * riji
889 >
890 >             vterm = pref * ct_i * ( ri2 - preRF2*rij )
891 >             vpair = vpair + vterm
892 >             epot = epot + sw*vterm
893              
894 <             duduz_i(1) = duduz_i(1) - sw*pref*( ri2*xhat - d(1)*rcuti3 )
895 <             duduz_i(2) = duduz_i(2) - sw*pref*( ri2*yhat - d(2)*rcuti3 )
896 <             duduz_i(3) = duduz_i(3) - sw*pref*( ri2*zhat - d(3)*rcuti3 )
894 >             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 >            
901 >             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  
905            else
906               if (i_is_SplitDipole) then
# Line 895 | Line 916 | contains
916               ri3 = ri2 * ri
917               sc2 = scale * scale
918  
919 <             pref = pre12 * q_j * mu_i
920 <             vterm = pref * ct_i * ri2 * scale
919 >             pot_term = ri2 * f1 * scale
920 >             vterm = pref * ct_i * pot_term
921               vpair = vpair + vterm
922               epot = epot + sw*vterm
923              
924 <             dudx = dudx + sw*pref * ri3 * ( uz_i(1) - 3.0d0 * ct_i * xhat*sc2)
925 <             dudy = dudy + sw*pref * ri3 * ( uz_i(2) - 3.0d0 * ct_i * yhat*sc2)
926 <             dudz = dudz + sw*pref * ri3 * ( uz_i(3) - 3.0d0 * ct_i * zhat*sc2)
924 >             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              
931 <             duduz_i(1) = duduz_i(1) + sw*pref * ri2 * xhat * scale
932 <             duduz_i(2) = duduz_i(2) + sw*pref * ri2 * yhat * scale
933 <             duduz_i(3) = duduz_i(3) + sw*pref * ri2 * zhat * scale
931 >             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            endif
935         endif
936        
937         if (j_is_Dipole) then
938 +          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 <          if (summationMethod .eq. UNDAMPED_WOLF) then
948 <             ri2 = riji * riji
949 <             ri3 = ri2 * riji
950 <             ri4 = ri2 * ri2
947 >          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  
955 <             pref = pre22 * mu_i * mu_j
956 <             vterm = pref * (ri3 - rcuti3) * (ct_ij - 3.0d0 * ct_i * ct_j)
955 >          if (summationMethod .eq. REACTION_FIELD) then
956 >             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)) &
929 <                         - sw*pref*3.0d0*rcuti4 &
930 <                             * (a1*rcuti*d(1)-ct_i*uz_j(1)-ct_j*uz_i(1))
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)) &
933 <                         - sw*pref*3.0d0*rcuti4 &
934 <                             * (a1*rcuti*d(2)-ct_i*uz_j(2)-ct_j*uz_i(2))
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)) &
937 <                         - sw*pref*3.0d0*rcuti4 &
938 <                             * (a1*rcuti*d(3)-ct_i*uz_j(3)-ct_j*uz_i(3))
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 <                  - rcuti3*(uz_j(1) - 3.0d0*ct_j*d(1)*rcuti))
971 >                  - preRF2*uz_j(1))
972               duduz_i(2) = duduz_i(2) + sw*pref*(ri3*(uz_j(2)-3.0d0*ct_j*yhat) &
973 <                  - rcuti3*(uz_j(2) - 3.0d0*ct_j*d(2)*rcuti))
973 >                  - preRF2*uz_j(2))
974               duduz_i(3) = duduz_i(3) + sw*pref*(ri3*(uz_j(3)-3.0d0*ct_j*zhat) &
975 <                  - rcuti3*(uz_j(3) - 3.0d0*ct_j*d(3)*rcuti))
975 >                  - preRF2*uz_j(3))
976               duduz_j(1) = duduz_j(1) + sw*pref*(ri3*(uz_i(1)-3.0d0*ct_i*xhat) &
977 <                  - rcuti3*(uz_i(1) - 3.0d0*ct_i*d(1)*rcuti))
977 >                  - preRF2*uz_i(1))
978               duduz_j(2) = duduz_j(2) + sw*pref*(ri3*(uz_i(2)-3.0d0*ct_i*yhat) &
979 <                  - rcuti3*(uz_i(2) - 3.0d0*ct_i*d(2)*rcuti))
979 >                  - preRF2*uz_i(2))
980               duduz_j(3) = duduz_j(3) + sw*pref*(ri3*(uz_i(3)-3.0d0*ct_i*zhat) &
981 <                  - rcuti3*(uz_i(3) - 3.0d0*ct_i*d(3)*rcuti))
981 >                  - preRF2*uz_i(3))
982  
983            else
984               if (i_is_SplitDipole) then
# Line 970 | Line 1000 | contains
1000                  endif
1001               endif
1002              
973             ct_ij = uz_i(1)*uz_j(1) + uz_i(2)*uz_j(2) + uz_i(3)*uz_j(3)
974            
975             ri2 = ri * ri
976             ri3 = ri2 * ri
977             ri4 = ri2 * ri2
1003               sc2 = scale * scale
1004 <            
1005 <             pref = pre22 * mu_i * mu_j
1006 <             vterm = pref * ri3 * (ct_ij - 3.0d0 * ct_i * ct_j * sc2)
1004 >
1005 >             pot_term = (ct_ij - 3.0d0 * ct_i * ct_j * sc2)
1006 >             vterm = pref * ( ri3*pot_term*f1 + (ct_i * ct_j)*f2 )
1007               vpair = vpair + vterm
1008               epot = epot + sw*vterm
1009              
1010 <             a1 = 5.0d0 * ct_i * ct_j * sc2 - ct_ij
1010 >             f13 = f1+f3
1011 >             f134 = f13 + f4
1012              
1013 <             dudx = dudx + sw*pref*3.0d0*ri4*scale &
1014 <                             *(a1*xhat-ct_i*uz_j(1)-ct_j*uz_i(1))
1015 <             dudy = dudy + sw*pref*3.0d0*ri4*scale &
1016 <                             *(a1*yhat-ct_i*uz_j(2)-ct_j*uz_i(2))
1017 <             dudz = dudz + sw*pref*3.0d0*ri4*scale &
1018 <                             *(a1*zhat-ct_i*uz_j(3)-ct_j*uz_i(3))
1019 <            
1020 <             duduz_i(1) = duduz_i(1) + sw*pref*ri3 &
1021 <                                         *(uz_j(1) - 3.0d0*ct_j*xhat*sc2)
1022 <             duduz_i(2) = duduz_i(2) + sw*pref*ri3 &
1023 <                                         *(uz_j(2) - 3.0d0*ct_j*yhat*sc2)
1024 <             duduz_i(3) = duduz_i(3) + sw*pref*ri3 &
1025 <                                         *(uz_j(3) - 3.0d0*ct_j*zhat*sc2)
1013 > !!$             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              
1039 <             duduz_j(1) = duduz_j(1) + sw*pref*ri3 &
1040 <                                         *(uz_i(1) - 3.0d0*ct_i*xhat*sc2)
1041 <             duduz_j(2) = duduz_j(2) + sw*pref*ri3 &
1042 <                                         *(uz_i(2) - 3.0d0*ct_i*yhat*sc2)
1043 <             duduz_j(3) = duduz_j(3) + sw*pref*ri3 &
1044 <                                         *(uz_i(3) - 3.0d0*ct_i*zhat*sc2)
1039 >             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 >            
1046 >             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            endif
1053         endif
1054      endif
1055  
1056      if (i_is_Quadrupole) then
1057         if (j_is_Charge) then
1058 +          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            ri2 = riji * riji
1068            ri3 = ri2 * riji
# Line 1018 | Line 1071 | contains
1071            cy2 = cy_i * cy_i
1072            cz2 = cz_i * cz_i
1073  
1074 <          if (summationMethod .eq. UNDAMPED_WOLF) then
1075 <             pref = pre14 * q_j / 3.0_dp
1076 <             vterm1 = pref * ri3*( qxx_i * (3.0_dp*cx2 - 1.0_dp) + &
1077 <                  qyy_i * (3.0_dp*cy2 - 1.0_dp) + &
1078 <                  qzz_i * (3.0_dp*cz2 - 1.0_dp) )
1079 <             vterm2 = pref * rcuti3*( qxx_i * (3.0_dp*cx2 - 1.0_dp) + &
1080 <                  qyy_i * (3.0_dp*cy2 - 1.0_dp) + &
1081 <                  qzz_i * (3.0_dp*cz2 - 1.0_dp) )
1082 <             vpair = vpair + ( vterm1 - vterm2 )
1083 <             epot = epot + sw*( vterm1 - vterm2 )
1084 <            
1085 <             dudx = dudx - sw*(5.0_dp*(vterm1*riji*xhat-vterm2*rcuti2*d(1))) +&
1086 <                  sw*pref * ( (ri4 - rcuti4)*(qxx_i*(6.0_dp*cx_i*ux_i(1)) - &
1087 <                  qxx_i*2.0_dp*(xhat - rcuti*d(1))) + &
1088 <                  (ri4 - rcuti4)*(qyy_i*(6.0_dp*cy_i*uy_i(1)) - &
1089 <                  qyy_i*2.0_dp*(xhat - rcuti*d(1))) + &
1090 <                  (ri4 - rcuti4)*(qzz_i*(6.0_dp*cz_i*uz_i(1)) - &
1091 <                  qzz_i*2.0_dp*(xhat - rcuti*d(1))) )
1092 <             dudy = dudy - sw*(5.0_dp*(vterm1*riji*yhat-vterm2*rcuti2*d(2))) +&
1093 <                  sw*pref * ( (ri4 - rcuti4)*(qxx_i*(6.0_dp*cx_i*ux_i(2)) - &
1094 <                  qxx_i*2.0_dp*(yhat - rcuti*d(2))) + &
1095 <                  (ri4 - rcuti4)*(qyy_i*(6.0_dp*cy_i*uy_i(2)) - &
1096 <                  qyy_i*2.0_dp*(yhat - rcuti*d(2))) + &
1097 <                  (ri4 - rcuti4)*(qzz_i*(6.0_dp*cz_i*uz_i(2)) - &
1098 <                  qzz_i*2.0_dp*(yhat - rcuti*d(2))) )
1099 <             dudz = dudz - sw*(5.0_dp*(vterm1*riji*zhat-vterm2*rcuti2*d(3))) +&
1100 <                  sw*pref * ( (ri4 - rcuti4)*(qxx_i*(6.0_dp*cx_i*ux_i(3)) - &
1101 <                  qxx_i*2.0_dp*(zhat - rcuti*d(3))) + &
1102 <                  (ri4 - rcuti4)*(qyy_i*(6.0_dp*cy_i*uy_i(3)) - &
1103 <                  qyy_i*2.0_dp*(zhat - rcuti*d(3))) + &
1104 <                  (ri4 - rcuti4)*(qzz_i*(6.0_dp*cz_i*uz_i(3)) - &
1105 <                  qzz_i*2.0_dp*(zhat - rcuti*d(3))) )
1106 <            
1107 <             dudux_i(1) = dudux_i(1) + sw*pref*(ri3*(qxx_i*6.0_dp*cx_i*xhat) -&
1108 <                  rcuti4*(qxx_i*6.0_dp*cx_i*d(1)))
1109 <             dudux_i(2) = dudux_i(2) + sw*pref*(ri3*(qxx_i*6.0_dp*cx_i*yhat) -&
1110 <                  rcuti4*(qxx_i*6.0_dp*cx_i*d(2)))
1111 <             dudux_i(3) = dudux_i(3) + sw*pref*(ri3*(qxx_i*6.0_dp*cx_i*zhat) -&
1112 <                  rcuti4*(qxx_i*6.0_dp*cx_i*d(3)))
1113 <            
1114 <             duduy_i(1) = duduy_i(1) + sw*pref*(ri3*(qyy_i*6.0_dp*cy_i*xhat) -&
1115 <                  rcuti4*(qyy_i*6.0_dp*cx_i*d(1)))
1116 <             duduy_i(2) = duduy_i(2) + sw*pref*(ri3*(qyy_i*6.0_dp*cy_i*yhat) -&
1117 <                  rcuti4*(qyy_i*6.0_dp*cx_i*d(2)))
1118 <             duduy_i(3) = duduy_i(3) + sw*pref*(ri3*(qyy_i*6.0_dp*cy_i*zhat) -&
1119 <                  rcuti4*(qyy_i*6.0_dp*cx_i*d(3)))
1120 <            
1068 <             duduz_i(1) = duduz_i(1) + sw*pref*(ri3*(qzz_i*6.0_dp*cz_i*xhat) -&
1069 <                  rcuti4*(qzz_i*6.0_dp*cx_i*d(1)))
1070 <             duduz_i(2) = duduz_i(2) + sw*pref*(ri3*(qzz_i*6.0_dp*cz_i*yhat) -&
1071 <                  rcuti4*(qzz_i*6.0_dp*cx_i*d(2)))
1072 <             duduz_i(3) = duduz_i(3) + sw*pref*(ri3*(qzz_i*6.0_dp*cz_i*zhat) -&
1073 <                  rcuti4*(qzz_i*6.0_dp*cx_i*d(3)))
1074 >          pref = pre14 * q_j / 3.0_dp
1075 >          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 >          vpair = vpair + vterm
1080 >          epot = epot + sw*vterm
1081 >          
1082 >          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 >          
1101 >          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 >          
1108 >          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 >          
1115 >          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  
1075          else
1076             pref = pre14 * q_j / 3.0_dp
1077             vterm = pref * ri3 * (qxx_i * (3.0_dp*cx2 - 1.0_dp) + &
1078                  qyy_i * (3.0_dp*cy2 - 1.0_dp) + &
1079                  qzz_i * (3.0_dp*cz2 - 1.0_dp))
1080             vpair = vpair + vterm
1081             epot = epot + sw*vterm
1082            
1083             dudx = dudx - 5.0_dp*sw*vterm*riji*xhat + sw*pref*ri4 * ( &
1084                  qxx_i*(6.0_dp*cx_i*ux_i(1) - 2.0_dp*xhat) + &
1085                  qyy_i*(6.0_dp*cy_i*uy_i(1) - 2.0_dp*xhat) + &
1086                  qzz_i*(6.0_dp*cz_i*uz_i(1) - 2.0_dp*xhat) )
1087             dudy = dudy - 5.0_dp*sw*vterm*riji*yhat + sw*pref*ri4 * ( &
1088                  qxx_i*(6.0_dp*cx_i*ux_i(2) - 2.0_dp*yhat) + &
1089                  qyy_i*(6.0_dp*cy_i*uy_i(2) - 2.0_dp*yhat) + &
1090                  qzz_i*(6.0_dp*cz_i*uz_i(2) - 2.0_dp*yhat) )
1091             dudz = dudz - 5.0_dp*sw*vterm*riji*zhat + sw*pref*ri4 * ( &
1092                  qxx_i*(6.0_dp*cx_i*ux_i(3) - 2.0_dp*zhat) + &
1093                  qyy_i*(6.0_dp*cy_i*uy_i(3) - 2.0_dp*zhat) + &
1094                  qzz_i*(6.0_dp*cz_i*uz_i(3) - 2.0_dp*zhat) )
1095            
1096             dudux_i(1) = dudux_i(1) + sw*pref*ri3*(qxx_i*6.0_dp*cx_i*xhat)
1097             dudux_i(2) = dudux_i(2) + sw*pref*ri3*(qxx_i*6.0_dp*cx_i*yhat)
1098             dudux_i(3) = dudux_i(3) + sw*pref*ri3*(qxx_i*6.0_dp*cx_i*zhat)
1099            
1100             duduy_i(1) = duduy_i(1) + sw*pref*ri3*(qyy_i*6.0_dp*cy_i*xhat)
1101             duduy_i(2) = duduy_i(2) + sw*pref*ri3*(qyy_i*6.0_dp*cy_i*yhat)
1102             duduy_i(3) = duduy_i(3) + sw*pref*ri3*(qyy_i*6.0_dp*cy_i*zhat)
1103            
1104             duduz_i(1) = duduz_i(1) + sw*pref*ri3*(qzz_i*6.0_dp*cz_i*xhat)
1105             duduz_i(2) = duduz_i(2) + sw*pref*ri3*(qzz_i*6.0_dp*cz_i*yhat)
1106             duduz_i(3) = duduz_i(3) + sw*pref*ri3*(qzz_i*6.0_dp*cz_i*zhat)
1107          endif
1122         endif
1123      endif
1124  
# Line 1223 | Line 1237 | contains
1237  
1238    end subroutine destroyElectrostaticTypes
1239  
1240 <  subroutine accumulate_rf(atom1, atom2, rij, eFrame, taper)
1241 <
1228 <    integer, intent(in) :: atom1, atom2
1229 <    real (kind = dp), intent(in) :: rij
1230 <    real (kind = dp), dimension(9,nLocal) :: eFrame
1231 <
1232 <    integer :: me1, me2
1233 <    real (kind = dp), intent(in) :: taper
1234 <    real (kind = dp):: mu1, mu2
1235 <    real (kind = dp), dimension(3) :: ul1
1236 <    real (kind = dp), dimension(3) :: ul2  
1237 <
1238 <    integer :: localError
1239 <
1240 < #ifdef IS_MPI
1241 <    me1 = atid_Row(atom1)
1242 <    ul1(1) = eFrame_Row(3,atom1)
1243 <    ul1(2) = eFrame_Row(6,atom1)
1244 <    ul1(3) = eFrame_Row(9,atom1)
1245 <
1246 <    me2 = atid_Col(atom2)
1247 <    ul2(1) = eFrame_Col(3,atom2)
1248 <    ul2(2) = eFrame_Col(6,atom2)
1249 <    ul2(3) = eFrame_Col(9,atom2)
1250 < #else
1251 <    me1 = atid(atom1)
1252 <    ul1(1) = eFrame(3,atom1)
1253 <    ul1(2) = eFrame(6,atom1)
1254 <    ul1(3) = eFrame(9,atom1)
1255 <
1256 <    me2 = atid(atom2)
1257 <    ul2(1) = eFrame(3,atom2)
1258 <    ul2(2) = eFrame(6,atom2)
1259 <    ul2(3) = eFrame(9,atom2)
1260 < #endif
1261 <
1262 <    mu1 = getDipoleMoment(me1)
1263 <    mu2 = getDipoleMoment(me2)
1264 <
1265 < #ifdef IS_MPI
1266 <    rf_Row(1,atom1) = rf_Row(1,atom1) + ul2(1)*mu2*taper
1267 <    rf_Row(2,atom1) = rf_Row(2,atom1) + ul2(2)*mu2*taper
1268 <    rf_Row(3,atom1) = rf_Row(3,atom1) + ul2(3)*mu2*taper
1269 <
1270 <    rf_Col(1,atom2) = rf_Col(1,atom2) + ul1(1)*mu1*taper
1271 <    rf_Col(2,atom2) = rf_Col(2,atom2) + ul1(2)*mu1*taper
1272 <    rf_Col(3,atom2) = rf_Col(3,atom2) + ul1(3)*mu1*taper
1273 < #else
1274 <    rf(1,atom1) = rf(1,atom1) + ul2(1)*mu2*taper
1275 <    rf(2,atom1) = rf(2,atom1) + ul2(2)*mu2*taper
1276 <    rf(3,atom1) = rf(3,atom1) + ul2(3)*mu2*taper
1277 <
1278 <    rf(1,atom2) = rf(1,atom2) + ul1(1)*mu1*taper
1279 <    rf(2,atom2) = rf(2,atom2) + ul1(2)*mu1*taper
1280 <    rf(3,atom2) = rf(3,atom2) + ul1(3)*mu1*taper    
1281 < #endif
1282 <    return  
1283 <  end subroutine accumulate_rf
1284 <
1285 <  subroutine accumulate_self_rf(atom1, mu1, eFrame)
1286 <
1240 >  subroutine self_self(atom1, eFrame, mypot, t, do_pot)
1241 >    logical, intent(in) :: do_pot
1242      integer, intent(in) :: atom1
1243 <    real(kind=dp), intent(in) :: mu1
1243 >    integer :: atid1
1244      real(kind=dp), dimension(9,nLocal) :: eFrame
1245 +    real(kind=dp), dimension(3,nLocal) :: t
1246 +    real(kind=dp) :: mu1, c1
1247 +    real(kind=dp) :: preVal, epot, mypot
1248 +    real(kind=dp) :: eix, eiy, eiz
1249  
1250 <    !! should work for both MPI and non-MPI version since this is not pairwise.
1251 <    rf(1,atom1) = rf(1,atom1) + eFrame(3,atom1)*mu1
1293 <    rf(2,atom1) = rf(2,atom1) + eFrame(6,atom1)*mu1
1294 <    rf(3,atom1) = rf(3,atom1) + eFrame(9,atom1)*mu1
1250 >    ! this is a local only array, so we use the local atom type id's:
1251 >    atid1 = atid(atom1)
1252  
1253 <    return
1254 <  end subroutine accumulate_self_rf
1255 <
1256 <  subroutine reaction_field_final(a1, mu1, eFrame, rfpot, t, do_pot)
1257 <
1258 <    integer, intent(in) :: a1
1259 <    real (kind=dp), intent(in) :: mu1
1260 <    real (kind=dp), intent(inout) :: rfpot
1261 <    logical, intent(in) :: do_pot
1262 <    real (kind = dp), dimension(9,nLocal) :: eFrame
1263 <    real (kind = dp), dimension(3,nLocal) :: t
1264 <
1265 <    integer :: localError
1253 >    if (.not.summationMethodChecked) then
1254 >       call checkSummationMethod()
1255 >    endif
1256 >    
1257 >    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 <    if (.not.preRFCalculated) then
1283 <       call setReactionFieldPrefactor()
1282 >    elseif ( (summationMethod .eq. SHIFTED_FORCE) .or. &
1283 >         (summationMethod .eq. SHIFTED_POTENTIAL) ) then
1284 >       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 +    
1298 +    return
1299 +  end subroutine self_self
1300  
1301 <    ! compute torques on dipoles:
1302 <    ! pre converts from mu in units of debye to kcal/mol
1301 >  subroutine rf_self_excludes(atom1, atom2, sw, eFrame, d, rij, vpair, myPot, &
1302 >       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 >    real(kind=dp) :: pref, preVal, rfVal, myPot
1326 >    real(kind=dp) :: dudx, dudy, dudz, dudr
1327  
1328 <    ! The torque contribution is dipole cross reaction_field  
1329 <
1319 <    t(1,a1) = t(1,a1) + preRF*mu1*(eFrame(6,a1)*rf(3,a1) - &
1320 <                                   eFrame(9,a1)*rf(2,a1))
1321 <    t(2,a1) = t(2,a1) + preRF*mu1*(eFrame(9,a1)*rf(1,a1) - &
1322 <                                   eFrame(3,a1)*rf(3,a1))
1323 <    t(3,a1) = t(3,a1) + preRF*mu1*(eFrame(3,a1)*rf(2,a1) - &
1324 <                                   eFrame(6,a1)*rf(1,a1))
1325 <
1326 <    ! the potential contribution is -1/2 dipole dot reaction_field
1327 <
1328 <    if (do_pot) then
1329 <       rfpot = rfpot - 0.5d0 * preRF * mu1 * &
1330 <            (rf(1,a1)*eFrame(3,a1) + rf(2,a1)*eFrame(6,a1) + &
1331 <             rf(3,a1)*eFrame(9,a1))
1328 >    if (.not.summationMethodChecked) then
1329 >       call checkSummationMethod()
1330      endif
1331  
1332 <    return
1333 <  end subroutine reaction_field_final
1332 >    dudx = 0.0d0
1333 >    dudy = 0.0d0
1334 >    dudz = 0.0d0
1335  
1336 <  subroutine rf_correct_forces(atom1, atom2, d, rij, eFrame, taper, f, fpair)
1336 >    riji = 1.0d0/rij
1337  
1338 <    integer, intent(in) :: atom1, atom2
1339 <    real(kind=dp), dimension(3), intent(in) :: d
1340 <    real(kind=dp), intent(in) :: rij, taper
1342 <    real( kind = dp ), dimension(9,nLocal) :: eFrame
1343 <    real( kind = dp ), dimension(3,nLocal) :: f
1344 <    real( kind = dp ), dimension(3), intent(inout) :: fpair
1338 >    xhat = d(1) * riji
1339 >    yhat = d(2) * riji
1340 >    zhat = d(3) * riji
1341  
1342 <    real (kind = dp), dimension(3) :: ul1
1343 <    real (kind = dp), dimension(3) :: ul2
1344 <    real (kind = dp) :: dtdr
1345 <    real (kind = dp) :: dudx, dudy, dudz, u1dotu2
1346 <    integer :: me1, me2, id1, id2
1347 <    real (kind = dp) :: mu1, mu2
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 <    integer :: localError
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 >       myPot = myPot + sw*vterm
1359 >      
1360 >       dudr  = sw*preVal * 2.0d0*rfVal*riji
1361 >      
1362 >       dudx = dudx + dudr * xhat
1363 >       dudy = dudy + dudr * yhat
1364 >       dudz = dudz + dudr * zhat
1365 >      
1366 >    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 >      
1374 >       ri2 = riji * riji
1375 >       ri3 = ri2 * riji
1376 >      
1377 >       pref = pre12 * q_i * mu_j
1378 >       vterm = - pref * ct_j * ( ri2 - preRF2*rij )
1379 >       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 >       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 >      
1392 >    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 >      
1400 >       ri2 = riji * riji
1401 >       ri3 = ri2 * riji
1402 >      
1403 >       pref = pre12 * q_j * mu_i
1404 >       vterm = pref * ct_i * ( ri2 - preRF2*rij )
1405 >       myPot = myPot + sw*vterm
1406 >      
1407 >       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 >      
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 >      
1420  
1421 <    if (.not.preRFCalculated) then
1422 <       call setReactionFieldPrefactor()
1421 >    ! accumulate the forces and torques resulting from the self term
1422 >    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  
1359    if (rij.le.rrf) then
1360
1361       if (rij.lt.rt) then
1362          dtdr = 0.0d0
1363       else
1364          !         write(*,*) 'rf correct in taper region'
1365          dtdr = 6.0d0*(rij*rij - rij*rt - rij*rrf +rrf*rt)/((rrf-rt)**3)
1366       endif
1367
1368 #ifdef IS_MPI
1369       me1 = atid_Row(atom1)
1370       ul1(1) = eFrame_Row(3,atom1)
1371       ul1(2) = eFrame_Row(6,atom1)
1372       ul1(3) = eFrame_Row(9,atom1)
1373
1374       me2 = atid_Col(atom2)
1375       ul2(1) = eFrame_Col(3,atom2)
1376       ul2(2) = eFrame_Col(6,atom2)
1377       ul2(3) = eFrame_Col(9,atom2)
1378 #else
1379       me1 = atid(atom1)
1380       ul1(1) = eFrame(3,atom1)
1381       ul1(2) = eFrame(6,atom1)
1382       ul1(3) = eFrame(9,atom1)
1383
1384       me2 = atid(atom2)
1385       ul2(1) = eFrame(3,atom2)
1386       ul2(2) = eFrame(6,atom2)
1387       ul2(3) = eFrame(9,atom2)
1388 #endif
1389
1390       mu1 = getDipoleMoment(me1)
1391       mu2 = getDipoleMoment(me2)
1392
1393       u1dotu2 = ul1(1)*ul2(1) + ul1(2)*ul2(2) + ul1(3)*ul2(3)
1394
1395       dudx = - preRF*mu1*mu2*u1dotu2*dtdr*d(1)/rij
1396       dudy = - preRF*mu1*mu2*u1dotu2*dtdr*d(2)/rij
1397       dudz = - preRF*mu1*mu2*u1dotu2*dtdr*d(3)/rij
1398
1399 #ifdef IS_MPI
1400       f_Row(1,atom1) = f_Row(1,atom1) + dudx
1401       f_Row(2,atom1) = f_Row(2,atom1) + dudy
1402       f_Row(3,atom1) = f_Row(3,atom1) + dudz
1403
1404       f_Col(1,atom2) = f_Col(1,atom2) - dudx
1405       f_Col(2,atom2) = f_Col(2,atom2) - dudy
1406       f_Col(3,atom2) = f_Col(3,atom2) - dudz
1407 #else
1408       f(1,atom1) = f(1,atom1) + dudx
1409       f(2,atom1) = f(2,atom1) + dudy
1410       f(3,atom1) = f(3,atom1) + dudz
1411
1412       f(1,atom2) = f(1,atom2) - dudx
1413       f(2,atom2) = f(2,atom2) - dudy
1414       f(3,atom2) = f(3,atom2) - dudz
1415 #endif
1416
1417 #ifdef IS_MPI
1418       id1 = AtomRowToGlobal(atom1)
1419       id2 = AtomColToGlobal(atom2)
1420 #else
1421       id1 = atom1
1422       id2 = atom2
1423 #endif
1424
1425       if (molMembershipList(id1) .ne. molMembershipList(id2)) then
1426
1427          fpair(1) = fpair(1) + dudx
1428          fpair(2) = fpair(2) + dudy
1429          fpair(3) = fpair(3) + dudz
1430
1431       endif
1432
1433    end if
1440      return
1441 <  end subroutine rf_correct_forces
1441 >  end subroutine rf_self_excludes
1442  
1443   end module electrostatic_module

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines