Octopus
lorentz_force.F90
Go to the documentation of this file.
1!! Copyright (C) 2020 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
22 use debug_oct_m
24 use global_oct_m
31
32 implicit none
33
34 private
35 public :: &
37
39 type, extends(force_interaction_t) :: lorentz_force_t
40 private
41 real(real64), pointer :: system_charge(:) => null()
42 real(real64), pointer, public :: system_pos(:,:) => null()
43 real(real64), pointer :: system_vel(:,:) => null()
44
45 real(real64), allocatable, public :: partner_e_field(:,:)
46 real(real64), allocatable, public :: partner_b_field(:,:)
47
48 contains
49 procedure :: init => lorentz_force_init
50 procedure :: calculate => lorentz_force_calculate
51 procedure :: calculate_energy => lorentz_force_calculate_energy
53 end type lorentz_force_t
54
55 interface lorentz_force_t
56 module procedure lorentz_force_constructor
57 end interface lorentz_force_t
58
59contains
60
61 ! ---------------------------------------------------------
62 function lorentz_force_constructor(partner) result(this)
63 class(interaction_partner_t), target, intent(inout) :: partner
64 class(lorentz_force_t), pointer :: this
65
67
68 allocate(this)
69
70 this%label = "lorenz_force"
71
72 this%partner => partner
73
74 ! The Lorentz force needs the position, velocity and charge of the system
75 this%system_quantities = [position, velocity, charge]
76
77 ! The Lorenz force needs the E and B field of the interaction partner at the particle position
78 this%couplings_from_partner = [e_field, b_field]
79 this%intra_interaction = .false. ! This interaction does not support intra-interactions
80
81
83 end function lorentz_force_constructor
84
85 ! ---------------------------------------------------------
86 subroutine lorentz_force_init(this, dim, system_np, system_charge, system_pos, system_vel, namespace)
87 class(lorentz_force_t), intent(inout) :: this
88 integer, intent(in) :: dim
89 integer, intent(in) :: system_np
90 real(real64), target, intent(in) :: system_charge(:)
91 real(real64), target, intent(in) :: system_pos(:,:)
92 real(real64), target, intent(in) :: system_vel(:,:)
93 type(namespace_t), intent(in) :: namespace
94
95 push_sub(lorentz_force_init)
96
97 message(1) = "Energies for Lorentz forces are not yet implemented, and currently set to 0."
98 call messages_warning(1, namespace=namespace)
99
100 this%dim = dim
101 this%system_np = system_np
102 this%energy = m_zero
103 safe_allocate(this%force(dim, system_np))
104 this%force = m_zero
105
106 safe_allocate(this%partner_e_field(1:dim, 1:system_np))
107 this%partner_e_field = m_zero
108 safe_allocate(this%partner_b_field(1:dim, 1:system_np))
109 this%partner_b_field = m_zero
110
111 this%system_charge => system_charge
112 this%system_pos => system_pos
113 this%system_vel => system_vel
115 pop_sub(lorentz_force_init)
116 end subroutine lorentz_force_init
117
118 ! ---------------------------------------------------------
119 subroutine lorentz_force_calculate(this)
120 class(lorentz_force_t), intent(inout) :: this
121
122 integer :: ip
123
125
126 ! Curl is defined only in 3D
127 assert(this%dim == 3)
128 assert(.not. this%intra_interaction)
129
130 do ip = 1, this%system_np
131 this%force(1, ip) = this%partner_e_field(1, ip) + &
132 this%system_vel(2, ip)*this%partner_b_field(3, ip) - this%system_vel(3, ip)*this%partner_b_field(2, ip)
133
134 this%force(2, ip) = this%partner_e_field(2, ip) + &
135 this%system_vel(3, ip)*this%partner_b_field(1, ip) - this%system_vel(1, ip)*this%partner_b_field(3, ip)
137 this%force(3, ip) = this%partner_e_field(3, ip) + &
138 this%system_vel(1, ip)*this%partner_b_field(2, ip) - this%system_vel(2, ip)*this%partner_b_field(1, ip)
140 this%force(1:3, ip) = this%force(1:3, ip)*this%system_charge(ip)
141 end do
146 ! ---------------------------------------------------------
147 subroutine lorentz_force_calculate_energy(this)
148 class(lorentz_force_t), intent(inout) :: this
149
150 integer :: ip
151 real(real64) :: power
152
154
155 ! the rate at which the energy is transferred from the EM field to the particle
156 ! the B field does not contribute any energy to the particles
157 power = m_zero
158 do ip = 1, this%system_np
159 power = power - dot_product(this%system_vel(1:3,ip), this%force(1:3,ip))
160 end do
161
162 this%energy = m_zero
163 !TODO: We need to implement the proper time integration of the power.
164 ! However, to that end, we first need to implement another clock at which the energies are
165 ! calculated.
166 ! this%energy = this%energy + power*this%partner%iteration%get_time_step()
167
169 end subroutine lorentz_force_calculate_energy
170
171
172 ! ---------------------------------------------------------
173 subroutine lorentz_force_finalize(this)
174 type(lorentz_force_t), intent(inout) :: this
175
176 push_sub(lorentz_force_finalize)
177
178 this%force = m_zero
179 nullify(this%system_charge)
180 nullify(this%system_pos)
181 nullify(this%system_vel)
182 safe_deallocate_a(this%force)
183 safe_deallocate_a(this%partner_e_field)
184 safe_deallocate_a(this%partner_b_field)
185
186 call interaction_end(this)
187
189 end subroutine lorentz_force_finalize
190
191end module lorentz_force_oct_m
192
193!! Local Variables:
194!! mode: f90
195!! coding: utf-8
196!! End:
real(real64), parameter, public m_zero
Definition: global.F90:187
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 lorentz_force_calculate_energy(this)
class(lorentz_force_t) function, pointer lorentz_force_constructor(partner)
subroutine lorentz_force_finalize(this)
subroutine lorentz_force_init(this, dim, system_np, system_charge, system_pos, system_vel, namespace)
subroutine lorentz_force_calculate(this)
subroutine, public messages_warning(no_lines, all_nodes, namespace)
Definition: messages.F90:543
character(len=256), dimension(max_lines), public message
to be output by fatal, warning
Definition: messages.F90:160
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 velocity
Definition: quantity.F90:146
integer, parameter, public position
Definition: quantity.F90:146
integer, parameter, public b_field
Definition: quantity.F90:146
integer, parameter, public charge
Definition: quantity.F90:146
integer, parameter, public e_field
Definition: quantity.F90:146
Lorenz force between a systems of particles and an electromagnetic field.