Octopus
interaction.F90
Go to the documentation of this file.
1!! Copyright (C) 2020-2023 M. Oliveira
2!!
3!! This Source Code Form is subject to the terms of the Mozilla Public
4!! License, v. 2.0. If a copy of the MPL was not distributed with this
5!! file, You can obtain one at https://mozilla.org/MPL/2.0/.
6!!
7#include "global.h"
8
96!
98 use debug_oct_m
99 use global_oct_m
108 implicit none
109
110 private
111 public :: &
116
117 integer, parameter, public :: &
118 TIMING_EXACT = 1, &
120
130 !
131 type, extends(interaction_surrogate_t), abstract :: interaction_t
132 ! General information about the interaction
133 type(iteration_counter_t) :: iteration
134 ! !! at which the interaction was last updated.
135 character(len=:), allocatable :: label
136 logical :: intra_interaction
137 integer :: timing
139 real(real64) :: energy
140
141 ! The interaction requires access to some quantities from a system to be evaluated.
142 character(len=:), allocatable :: system_quantities(:)
143
144 ! Information regarding the partner
145 class(interaction_partner_t), pointer :: partner => null()
146 character(len=:), allocatable :: couplings_from_partner(:)
147 logical :: partner_couplings_up_to_date = .false.
148
149 contains
150 procedure(interaction_calculate), deferred :: calculate
151 procedure(interaction_calculate_energy), deferred :: calculate_energy
152 procedure :: update => interaction_update
153 procedure :: update_partner_couplings => interaction_update_partner_couplings
154 procedure :: restart_read => interaction_restart_read
155 procedure :: restart_write => interaction_restart_write
156 end type interaction_t
157
158 abstract interface
159
162 subroutine interaction_calculate(this)
163 import interaction_t
164 class(interaction_t), intent(inout) :: this
165 end subroutine interaction_calculate
166
170 subroutine interaction_calculate_energy(this)
171 import interaction_t
172 class(interaction_t), intent(inout) :: this
173 end subroutine interaction_calculate_energy
174 end interface
175
176
178 type, extends(linked_list_t) :: interaction_list_t
179 private
180 contains
181 procedure :: add => interaction_list_add_node
182 end type interaction_list_t
183
186 private
187 contains
188 procedure :: get_next => interaction_iterator_get_next
191contains
192
193 ! ---------------------------------------------------------
195 subroutine interaction_update_partner_couplings(this, requested_iteration)
196 class(interaction_t), intent(inout) :: this
197 class(iteration_counter_t), intent(in) :: requested_iteration
198
199 type(event_handle_t) :: debug_handle
200
202
203 if (this%partner_couplings_up_to_date) then
204 ! Couplings have already been updated
206 return
207 end if
208
209 if (.not. allocated(this%couplings_from_partner)) then
210 ! No couplings to update
211 this%partner_couplings_up_to_date = .true.
213 return
214 end if
215
216 debug_handle = multisystem_debug_write_event_in(system_namespace = this%partner%namespace, &
217 event = event_function_call_t("system_update_exposed_quantities"), &
218 requested_iteration = requested_iteration, &
219 interaction_iteration = this%iteration)
220
221 ! Update all the necessary couplings that are updated on demand
222 call this%partner%update_on_demand_quantities(this%couplings_from_partner, requested_iteration, &
223 retardation_allowed = this%timing == timing_retarded)
225 ! Check the status of all the couplings and take the appropriate actions
226 select case (this%partner%check_couplings_status(this%couplings_from_partner, requested_iteration))
227 case (couplings_on_time)
228 ! Update was successful and we need to copy the couplings to the interaction
229 this%partner_couplings_up_to_date = .true.
230 call this%partner%copy_quantities_to_interaction(this)
231
233 ! Update is successful, only if retarded interaction is allowed. If that
234 ! is the case, the interaction should use the couplings it already has, so
235 ! there is no need to copy them to the interaction
236 this%partner_couplings_up_to_date = (this%timing == timing_retarded)
237
239 ! For now we will mark this case as unsuccessful, but it could be
240 ! successful if interpolation was allowed
241 this%partner_couplings_up_to_date = .false.
242
244 ! Partner couplings are in an undefined state (some are ahead of the
245 ! requested iteration and some are at the requested iteration). This
246 ! should never happen!
247 assert(.false.)
248 end select
249
250 call multisystem_debug_write_event_out(debug_handle, update=this%partner_couplings_up_to_date, &
251 requested_iteration = requested_iteration, &
252 interaction_iteration = this%iteration)
253
257
258 ! ---------------------------------------------------------
260 subroutine interaction_update(this, requested_iteration)
261 class(interaction_t), intent(inout) :: this
262 class(iteration_counter_t), intent(in) :: requested_iteration
264 type(event_handle_t) :: debug_handle
265
266 push_sub(interaction_update)
267
268 ! We should only try to update the interaction if it is not yet at the requested iteration
269 assert(.not. (this%iteration == requested_iteration))
270
271 debug_handle = multisystem_debug_write_event_in(event = event_function_call_t("interaction_update"), &
272 extra="target: "//trim(this%label)//"-"//trim(this%partner%namespace%get()), &
273 interaction_iteration = this%iteration, &
274 requested_iteration = requested_iteration)
275
276 call this%calculate()
277
278 ! Set new interaction iteration
279 call this%iteration%set(requested_iteration)
280 call multisystem_debug_write_marker(event = event_iteration_update_t( "interaction", &
281 trim(this%label)//"-"//trim(this%partner%namespace%get()), &
282 this%iteration, "set"))
283
284 ! After leaving this routine, the partner quantities will need to updated
285 ! again for the next interaction update
286 this%partner_couplings_up_to_date = .false.
287
288 call multisystem_debug_write_event_out(debug_handle, update = .true., &
289 interaction_iteration = this%iteration, &
290 requested_iteration = requested_iteration)
291
292 pop_sub(interaction_update)
293 end subroutine interaction_update
294
295 ! ---------------------------------------------------------
296 subroutine interaction_end(this)
297 class(interaction_t), intent(inout) :: this
298
299 push_sub(interaction_end)
300
301 if (allocated(this%couplings_from_partner)) then
302 deallocate(this%couplings_from_partner)
303 end if
304 nullify(this%partner)
305
306 if (allocated(this%system_quantities)) then
307 deallocate(this%system_quantities)
308 end if
309
310 if (allocated(this%label)) then
311 deallocate(this%label)
312 end if
313
314 pop_sub(interaction_end)
315 end subroutine interaction_end
316
317 ! ---------------------------------------------------------
321 logical function interaction_restart_read(this, namespace)
322 class(interaction_t), intent(inout) :: this
323 type(namespace_t), intent(in) :: namespace
324
326
327 interaction_restart_read = this%iteration%restart_read('restart_iteration_interaction_'//trim(this%label), &
328 namespace)
329
331 end function interaction_restart_read
332
333 ! ---------------------------------------------------------
334 subroutine interaction_restart_write(this, namespace)
335 class(interaction_t), intent(inout) :: this
336 type(namespace_t), intent(in) :: namespace
337
339
340 call this%iteration%restart_write('restart_iteration_interaction_'//trim(this%label), namespace)
341
343 end subroutine interaction_restart_write
344
345 ! ---------------------------------------------------------
346 subroutine interaction_list_add_node(this, interaction)
347 class(interaction_list_t) :: this
348 class(interaction_t), target :: interaction
349
351
352 call this%add_ptr(interaction)
355 end subroutine interaction_list_add_node
356
357 ! ---------------------------------------------------------
358 function interaction_iterator_get_next(this) result(interaction)
359 class(interaction_iterator_t), intent(inout) :: this
360 class(interaction_t), pointer :: interaction
361
363
364 select type (ptr => this%get_next_ptr())
365 class is (interaction_t)
366 interaction => ptr
367 class default
368 assert(.false.)
369 end select
370
373
374end module interaction_oct_m
375
376!! Local Variables:
377!! mode: f90
378!! coding: utf-8
379!! End:
All interactions need to implement the following deferred method, which takes information form the in...
All interactions need to implement the following deferred method, which takes information form the in...
This module defines the abstract interaction_t class, and some auxiliary classes for interactions.
subroutine interaction_update_partner_couplings(this, requested_iteration)
Try to update all the couplings needed from the partner to update the interaction.
subroutine, public interaction_end(this)
subroutine interaction_update(this, requested_iteration)
Update the interaction to the requested_iteration.
logical function interaction_restart_read(this, namespace)
read restart information
class(interaction_t) function, pointer interaction_iterator_get_next(this)
integer, parameter, public timing_retarded
subroutine interaction_restart_write(this, namespace)
subroutine interaction_list_add_node(this, interaction)
This module defines classes and functions for interaction partners.
integer, parameter, public couplings_on_time
integer, parameter, public couplings_behind_in_time
integer, parameter, public couplings_ahead_in_time
integer, parameter, public couplings_undefined
This module implements fully polymorphic linked lists, and some specializations thereof.
This module implements the multisystem debug functionality.
subroutine, public multisystem_debug_write_marker(system_namespace, event)
type(event_handle_t) function, public multisystem_debug_write_event_in(system_namespace, event, extra, system_iteration, algo_iteration, interaction_iteration, partner_iteration, requested_iteration)
subroutine, public multisystem_debug_write_event_out(handle, extra, update, system_iteration, algo_iteration, interaction_iteration, partner_iteration, requested_iteration)
This module defines the quantity_t class and the IDs for quantities, which can be exposed by a system...
Definition: quantity.F90:138
These class extend the list and list iterator to make an interaction list.
These classes extend the list and list iterator to make an interaction list.
abstract interaction class
surrogate interaction class to avoid circular dependencies between modules.
This class implements the iteration counter used by the multisystem algorithms. As any iteration coun...
This class implements an iterator for the polymorphic linked list.
This class implements a linked list of unlimited polymorphic values.
handle to keep track of in- out- events
int true(void)