27 use,
intrinsic :: iso_fortran_env
41 real(real64),
pointer :: system_pos(:,:) => null()
42 real(real64),
public :: lj_epsilon
43 real(real64),
public :: lj_sigma
45 integer,
public :: partner_np = 0
46 real(real64),
allocatable,
public :: partner_pos(:,:)
63 class(interaction_partner_t),
target,
intent(inout) :: partner
64 class(lennard_jones_t),
pointer :: this
70 this%label =
"lennard_jones"
72 this%partner => partner
75 this%system_quantities = [
"position"]
78 this%couplings_from_partner = [
"position"]
84 subroutine lennard_jones_init(this, dim, system_np, system_pos, system_eps, system_sigma)
85 class(lennard_jones_t),
intent(inout) :: this
86 integer,
intent(in) :: dim
87 integer,
intent(in) :: system_np
88 real(real64),
target,
intent(in) :: system_pos(:,:)
89 real(real64),
intent(in) :: system_eps
90 real(real64),
intent(in) :: system_sigma
95 this%system_np = system_np
96 safe_allocate(this%force(1:dim, 1:system_np))
99 this%lj_epsilon = system_eps
100 this%lj_sigma = system_sigma
102 this%system_pos => system_pos
109 class(lennard_jones_t),
intent(inout) :: this
112 real(real64) :: dist, rr(1:this%dim), lj_force
116 assert(
allocated(this%partner_pos))
118 do ip = 1, this%system_np
119 do jp = 1, this%partner_np
120 if (this%intra_interaction .and. ip == jp ) cycle
123 rr(1:this%dim) = this%system_pos(1:this%dim, ip) - this%partner_pos(1:this%dim, jp)
124 dist =
sqrt(sum(rr(1:this%dim)**2))
127 lj_force = 48.0_real64 * this%lj_epsilon * (this%lj_sigma**12 / dist**13 - &
128 m_half * this%lj_sigma**6 / dist**7)
132 this%force(1:this%dim, ip) = rr(1:this%dim) / dist * lj_force
148 assert(
allocated(this%partner_pos))
151 do ip = 1, this%system_np
152 do jp = 1, this%partner_np
153 if (this%intra_interaction .and. ip == jp ) cycle
155 dist =
sqrt(sum((this%system_pos(1:this%dim, ip) - this%partner_pos(1:this%dim, jp))**2)) +
m_epsilon
158 this%energy = this%energy +
m_two * this%lj_epsilon * ( (this%lj_sigma / dist)**12 - &
159 (this%lj_sigma / dist)**6 )
174 nullify(this%system_pos)
175 safe_deallocate_a(this%partner_pos)
176 safe_deallocate_a(this%force)
double sqrt(double __x) __attribute__((__nothrow__
real(real64), parameter, public m_two
real(real64), parameter, public m_zero
real(real64), parameter, public m_epsilon
real(real64), parameter, public m_half
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.
subroutine lennard_jones_calculate_energy(this)
subroutine lennard_jones_init(this, dim, system_np, system_pos, system_eps, system_sigma)
subroutine lennard_jones_calculate(this)
class(lennard_jones_t) function, pointer lennard_jones_constructor(partner)
subroutine lennard_jones_finalize(this)
Lennard-Jones interaction between two systems of particles.