27 use,
intrinsic :: iso_fortran_env
44 real(real64),
pointer :: system_mass(:) => null()
45 real(real64),
pointer :: system_pos(:,:) => null()
47 integer,
public :: partner_np = 0
48 real(real64),
allocatable,
public :: partner_mass(:)
49 real(real64),
allocatable,
public :: partner_pos(:,:)
65 class(interaction_partner_t),
target,
intent(inout) :: partner
66 class(gravity_t),
pointer :: this
72 this%label =
"gravity"
74 this%partner => partner
87 subroutine gravity_init(this, dim, system_np, system_mass, system_pos)
88 class(gravity_t),
intent(inout) :: this
89 integer,
intent(in) :: dim
90 integer,
intent(in) :: system_np
91 real(real64),
target,
intent(in) :: system_mass(:)
92 real(real64),
target,
intent(in) :: system_pos(:,:)
97 this%system_np = system_np
98 safe_allocate(this%force(1:dim, 1:system_np))
100 this%system_mass => system_mass
101 this%system_pos => system_pos
108 class(gravity_t),
intent(inout) :: this
111 real(real64),
parameter :: GG = 6.67430e-11_real64
112 real(real64) :: dist3
115 assert(
allocated(this%partner_mass))
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
122 dist3 = sum((this%partner_pos(1:this%dim, jp) - this%system_pos(1:this%dim, ip))**2)**(
m_three/
m_two)
124 this%force(1:this%dim, ip) = (this%partner_pos(1:this%dim, jp) - this%system_pos(1:this%dim, ip)) &
125 / (dist3 +
m_epsilon) * (gg * this%system_mass(ip) * this%partner_mass(jp))
134 class(gravity_t),
intent(inout) :: this
137 real(real64),
parameter :: gg = 6.67430e-11_real64
142 assert(
allocated(this%partner_mass))
143 assert(
allocated(this%partner_pos))
146 do ip = 1, this%system_np
147 do jp = 1, this%partner_np
148 if (this%intra_interaction .and. ip == jp ) cycle
150 dist =
sqrt(sum((this%partner_pos(1:this%dim, jp) - this%system_pos(1:this%dim, ip))**2))
152 this%energy = this%energy -
m_half / (dist +
m_epsilon) * (gg * this%system_mass(ip) * this%partner_mass(jp))
167 nullify(this%system_mass)
168 nullify(this%system_pos)
169 safe_deallocate_a(this%partner_pos)
170 safe_deallocate_a(this%partner_mass)
171 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
real(real64), parameter, public m_three
subroutine gravity_calculate_energy(this)
subroutine gravity_calculate(this)
class(gravity_t) function, pointer gravity_constructor(partner)
subroutine gravity_init(this, dim, system_np, system_mass, system_pos)
subroutine gravity_finalize(this)
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.
This module defines the quantity_t class and the IDs for quantities, which can be exposed by a system...
integer, parameter, public position
integer, parameter, public mass
Gravity interaction between two systems of particles. This should be used for testing purposes only....