Octopus
gravity.F90
Go to the documentation of this file.
1!! Copyright (C) 2020 M. Oliveira, Heiko Appel
2!!
3!! This program is free software; you can redistribute it and/or modify
4!! it under the terms of the GNU General Public License as published by
5!! the Free Software Foundation; either version 2, or (at your option)
6!! any later version.
7!!
8!! This program is distributed in the hope that it will be useful,
9!! but WITHOUT ANY WARRANTY; without even the implied warranty of
10!! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
11!! GNU General Public License for more details.
12!!
13!! You should have received a copy of the GNU General Public License
14!! along with this program; if not, write to the Free Software
15!! Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
16!! 02110-1301, USA.
17!!
18
19#include "global.h"
20
21module gravity_oct_m
22 use debug_oct_m
24 use global_oct_m
27 use, intrinsic :: iso_fortran_env
32
33 implicit none
34
35 private
36 public :: &
38
42 type, extends(force_interaction_t) :: gravity_t
43 private
44 real(real64), pointer :: system_mass(:) => null()
45 real(real64), pointer :: system_pos(:,:) => null()
46
47 integer, public :: partner_np = 0
48 real(real64), allocatable, public :: partner_mass(:)
49 real(real64), allocatable, public :: partner_pos(:,:)
50
51 contains
52 procedure :: init => gravity_init
53 procedure :: calculate => gravity_calculate
54 procedure :: calculate_energy => gravity_calculate_energy
55 final :: gravity_finalize
56 end type gravity_t
57
58 interface gravity_t
59 module procedure gravity_constructor
60 end interface gravity_t
61
62contains
63 ! ---------------------------------------------------------
64 function gravity_constructor(partner) result(this)
65 class(interaction_partner_t), target, intent(inout) :: partner
66 class(gravity_t), pointer :: this
67
68 push_sub(gravity_constructor)
69
70 allocate(this)
71
72 this%label = "gravity"
73
74 this%partner => partner
75
76 ! Gravity interaction needs two quantities from each system: the position and the mass
77 ! From the sytem:
78 this%system_quantities = [position, mass]
79
80 ! From the partner:
81 this%couplings_from_partner = [position, mass]
82
83 pop_sub(gravity_constructor)
84 end function gravity_constructor
85
86 ! ---------------------------------------------------------
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(:,:)
93
94 push_sub(gravity_init)
95
96 this%dim = dim
97 this%system_np = system_np
98 safe_allocate(this%force(1:dim, 1:system_np))
99 this%force = m_zero
100 this%system_mass => system_mass
101 this%system_pos => system_pos
102
103 pop_sub(gravity_init)
104 end subroutine gravity_init
105
106 ! ---------------------------------------------------------
107 subroutine gravity_calculate(this)
108 class(gravity_t), intent(inout) :: this
109
110 integer :: ip, jp
111 real(real64), parameter :: GG = 6.67430e-11_real64 ! In S.I. units!
112 real(real64) :: dist3
113 push_sub(gravity_calculate)
115 assert(allocated(this%partner_mass))
116 assert(allocated(this%partner_pos))
117
118 do ip = 1, this%system_np
119 do jp = 1, this%partner_np
120 if (this%intra_interaction .and. ip == jp ) cycle
121
122 dist3 = sum((this%partner_pos(1:this%dim, jp) - this%system_pos(1:this%dim, ip))**2)**(m_three/m_two)
123
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))
126 end do
127 end do
128
129 pop_sub(gravity_calculate)
130 end subroutine gravity_calculate
131
132 ! ---------------------------------------------------------
133 subroutine gravity_calculate_energy(this)
134 class(gravity_t), intent(inout) :: this
136 integer :: ip, jp
137 real(real64), parameter :: gg = 6.67430e-11_real64 ! In S.I. units!
138 real(real64) :: dist
139
142 assert(allocated(this%partner_mass))
143 assert(allocated(this%partner_pos))
144
145 this%energy = m_zero
146 do ip = 1, this%system_np
147 do jp = 1, this%partner_np
148 if (this%intra_interaction .and. ip == jp ) cycle
149
150 dist = sqrt(sum((this%partner_pos(1:this%dim, jp) - this%system_pos(1:this%dim, ip))**2))
151
152 this%energy = this%energy - m_half / (dist + m_epsilon) * (gg * this%system_mass(ip) * this%partner_mass(jp))
153 end do
154 end do
155
158
159
160 ! ---------------------------------------------------------
161 subroutine gravity_finalize(this)
162 type(gravity_t), intent(inout) :: this
163
164 push_sub(gravity_finalize)
165
166 this%force = m_zero
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)
172
173 call interaction_end(this)
174
175 pop_sub(gravity_finalize)
176 end subroutine gravity_finalize
177
178end module gravity_oct_m
179
180!! Local Variables:
181!! mode: f90
182!! coding: utf-8
183!! End:
double sqrt(double __x) __attribute__((__nothrow__
real(real64), parameter, public m_two
Definition: global.F90:189
real(real64), parameter, public m_zero
Definition: global.F90:187
real(real64), parameter, public m_epsilon
Definition: global.F90:203
real(real64), parameter, public m_half
Definition: global.F90:193
real(real64), parameter, public m_three
Definition: global.F90:190
subroutine gravity_calculate_energy(this)
Definition: gravity.F90:227
subroutine gravity_calculate(this)
Definition: gravity.F90:201
class(gravity_t) function, pointer gravity_constructor(partner)
Definition: gravity.F90:158
subroutine gravity_init(this, dim, system_np, system_mass, system_pos)
Definition: gravity.F90:181
subroutine gravity_finalize(this)
Definition: gravity.F90:255
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...
Definition: quantity.F90:137
integer, parameter, public position
Definition: quantity.F90:146
integer, parameter, public mass
Definition: quantity.F90:146
Gravity interaction between two systems of particles. This should be used for testing purposes only....
Definition: gravity.F90:135