(git:34ef472)
pair_potential_coulomb.F
Go to the documentation of this file.
1 !--------------------------------------------------------------------------------------------------!
2 ! CP2K: A general program to perform molecular dynamics simulations !
3 ! Copyright 2000-2024 CP2K developers group <https://cp2k.org> !
4 ! !
5 ! SPDX-License-Identifier: GPL-2.0-or-later !
6 !--------------------------------------------------------------------------------------------------!
7 
9 
10  USE kinds, ONLY: dp
11  USE mathconstants, ONLY: oorootpi
13 #include "./base/base_uses.f90"
14 
15  IMPLICIT NONE
16 
17  PRIVATE
18  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'pair_potential_coulomb'
19 
20  PUBLIC :: potential_coulomb
21 
22 CONTAINS
23 
24 ! **************************************************************************************************
25 !> \brief Evaluates the electrostatic energy and force
26 !> \param r2 ...
27 !> \param fscalar ...
28 !> \param qfac ...
29 !> \param ewald_type ...
30 !> \param alpha ...
31 !> \param beta ...
32 !> \param interaction_cutoff ...
33 !> \return ...
34 !> \author Toon.Verstraelen@gmail.com
35 ! **************************************************************************************************
36  FUNCTION potential_coulomb(r2, fscalar, qfac, ewald_type, alpha, beta, &
37  interaction_cutoff)
38 
39  REAL(kind=dp), INTENT(IN) :: r2
40  REAL(kind=dp), INTENT(INOUT) :: fscalar
41  REAL(kind=dp), INTENT(IN) :: qfac
42  INTEGER, INTENT(IN) :: ewald_type
43  REAL(kind=dp), INTENT(IN) :: alpha, beta, interaction_cutoff
44  REAL(kind=dp) :: potential_coulomb
45 
46  REAL(kind=dp), PARAMETER :: two_over_sqrt_pi = 2.0_dp*oorootpi
47 
48  REAL(kind=dp) :: r, x1, x2
49 
50  r = sqrt(r2)
51  IF (beta > 0.0_dp) THEN
52  IF (ewald_type == do_ewald_none) THEN
53  x2 = r*beta
54  potential_coulomb = erf(x2)/r
55  fscalar = fscalar + qfac*(potential_coulomb - &
56  two_over_sqrt_pi*exp(-x2*x2)*beta)/r2
57  ELSE
58  x1 = alpha*r
59  x2 = r*beta
60  potential_coulomb = (erf(x2) - erf(x1))/r
61  fscalar = fscalar + qfac*(potential_coulomb + &
62  two_over_sqrt_pi*(exp(-x1*x1)*alpha - exp(-x2*x2)*beta))/r2
63  END IF
64  ELSE
65  IF (ewald_type == do_ewald_none) THEN
66  potential_coulomb = 1.0_dp/r
67  fscalar = fscalar + qfac*potential_coulomb/r2
68  ELSE
69  x1 = alpha*r
70  potential_coulomb = erfc(x1)/r
71  fscalar = fscalar + qfac*(potential_coulomb + &
72  two_over_sqrt_pi*exp(-x1*x1)*alpha)/r2
73  END IF
74  END IF
75 
76  potential_coulomb = qfac*(potential_coulomb - interaction_cutoff)
77 
78  END FUNCTION potential_coulomb
79 
80 END MODULE pair_potential_coulomb
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public dp
Definition: kinds.F:34
Definition of mathematical constants and functions.
Definition: mathconstants.F:16
real(kind=dp), parameter, public oorootpi
real(kind=dp) function, public potential_coulomb(r2, fscalar, qfac, ewald_type, alpha, beta, interaction_cutoff)
Evaluates the electrostatic energy and force.
functions related to the poisson solver on regular grids
integer, parameter, public do_ewald_none