40 real(real64),
pointer :: system_charge(:) => null()
41 real(real64),
pointer :: system_pos(:,:) => null()
43 integer,
public :: partner_np = 0
44 real(real64),
allocatable,
public :: partner_charge(:)
45 real(real64),
allocatable,
public :: partner_pos(:,:)
62 class(interaction_partner_t),
target,
intent(inout) :: partner
63 class(coulomb_force_t),
pointer :: this
69 this%label =
"coulomb_force"
71 this%partner => partner
74 this%system_quantities = [
character(8) ::
"position",
"charge"]
77 this%couplings_from_partner = [
character(8) ::
"position",
"charge"]
84 class(coulomb_force_t),
intent(inout) :: this
85 integer,
intent(in) :: dim
86 integer,
intent(in) :: system_np
87 real(real64),
target,
intent(in) :: system_charge(:)
88 real(real64),
target,
intent(in) :: system_pos(:,:)
93 this%system_np = system_np
94 safe_allocate(this%force(1:dim, 1:system_np))
97 this%system_charge => system_charge
98 this%system_pos => system_pos
105 class(coulomb_force_t),
intent(inout) :: this
108 real(real64),
parameter :: COULCONST =
m_one
109 real(real64) :: dist3
113 assert(
allocated(this%partner_charge))
114 assert(
allocated(this%partner_pos))
116 do ip = 1, this%system_np
117 do jp = 1, this%partner_np
118 if (this%intra_interaction .and. ip == jp ) cycle
120 dist3 = sum((this%partner_pos(1:this%dim, jp) - this%system_pos(1:this%dim, ip))**2)**(
m_three/
m_two)
122 this%force(1:this%dim, ip) = -(this%partner_pos(1:this%dim, jp) - this%system_pos(1:this%dim, ip)) &
123 / (dist3 +
m_epsilon) * (coulconst * this%system_charge(ip) * this%partner_charge(jp))
132 class(coulomb_force_t),
intent(inout) :: this
135 real(real64),
parameter :: coulconst =
m_one
140 assert(
allocated(this%partner_charge))
141 assert(
allocated(this%partner_pos))
144 do ip = 1, this%system_np
145 do jp = 1, this%partner_np
146 if (this%intra_interaction .and. ip == jp ) cycle
148 dist =
sqrt(sum((this%partner_pos(1:this%dim, jp) - this%system_pos(1:this%dim, ip))**2))
150 this%energy = this%energy +
m_half / (dist +
m_epsilon) * (coulconst * this%system_charge(ip) * this%partner_charge(jp))
165 nullify(this%system_charge)
166 nullify(this%system_pos)
167 safe_deallocate_a(this%partner_pos)
168 safe_deallocate_a(this%partner_charge)
169 safe_deallocate_a(this%force)
double sqrt(double __x) __attribute__((__nothrow__
subroutine coulomb_force_calculate_energy(this)
subroutine coulomb_force_calculate(this)
subroutine coulomb_force_finalize(this)
subroutine coulomb_force_init(this, dim, system_np, system_charge, system_pos)
class(coulomb_force_t) function, pointer coulomb_force_constructor(partner)
real(real64), parameter, public m_two
real(real64), parameter, public m_zero
real(real64), parameter, public m_epsilon
real(real64), parameter, public m_half
real(real64), parameter, public m_one
real(real64), parameter, public m_three
This module defines the abstract interaction_t class, and some auxiliary classes for interactions.
subroutine, public interaction_end(this)
This module defines classes and functions for interaction partners.
Coulomb interaction between two systems of particles.