Octopus
interaction_partner.F90
Go to the documentation of this file.
1!! Copyright (C) 2020 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
8#include "global.h"
9
14 use debug_oct_m
15 use global_oct_m
23 implicit none
24
25 private
26 public :: &
30
31 integer, parameter, public :: &
32 COUPLINGS_UNDEFINED = 0, &
36
42 type, abstract :: interaction_partner_t
43 private
44 type(namespace_t), public :: namespace
45
46 integer, allocatable, public :: supported_interactions_as_partner(:)
48
49 type(quantity_list_t), public :: quantities
50 contains
51 procedure :: add_partners_to_list => interaction_partner_add_partners_to_list
52 procedure :: update_quantity => interaction_partner_update_quantity
53 procedure :: update_on_demand_quantity => interaction_partner_update_on_demand_quantity
54 procedure :: update_on_demand_quantities => interaction_partner_update_on_demand_quantities
55 procedure :: check_couplings_status => interaction_partner_check_couplings_status
56 procedure(interaction_partner_init_interaction_as_partner), deferred :: init_interaction_as_partner
57
58 procedure(interaction_partner_copy_quantities_to_interaction), deferred :: copy_quantities_to_interaction
59
61
62 abstract interface
63 ! ---------------------------------------------------------
64 subroutine interaction_partner_init_interaction_as_partner(partner, interaction)
67 class(interaction_partner_t), intent(in) :: partner
68 class(interaction_surrogate_t), intent(inout) :: interaction
70
71 ! ---------------------------------------------------------
72 subroutine interaction_partner_copy_quantities_to_interaction(partner, interaction)
75 class(interaction_partner_t), intent(inout) :: partner
76 class(interaction_surrogate_t), intent(inout) :: interaction
78
79 end interface
80
84 type, extends(linked_list_t) :: partner_list_t
85 private
86 contains
87 procedure :: add => partner_list_add_node
88 end type partner_list_t
89
94 private
95 contains
96 procedure :: get_next => partner_iterator_get_next
97 end type partner_iterator_t
98
99contains
100
101 ! ---------------------------------------------------------
106 recursive subroutine interaction_partner_add_partners_to_list(this, list, interaction_type)
107 class(interaction_partner_t), intent(in) :: this
108 class(partner_list_t), intent(inout) :: list
109 integer, optional, intent(in) :: interaction_type
110
111 if (present(interaction_type)) then
112 if (any(this%supported_interactions_as_partner == interaction_type)) then
113 call list%add(this)
114 end if
115 else
116 call list%add(this)
117 end if
118
120
121 ! ---------------------------------------------------------
129 subroutine interaction_partner_update_quantity(this, label)
130 class(interaction_partner_t), intent(inout) :: this
131 character(len=*), intent(in) :: label
132
134
135 write(message(1), '(a,a,a,a,a)') 'Interation partner "', trim(this%namespace%get()), &
136 '"does not know how to update quantity"', trim(label), '".'
137 call messages_fatal(1, namespace=this%namespace)
138
141
142 !! NOTE: here we update the quantity to be exactly at
143 !! requested_iteration. This is different than what is done in
144 !! interaction_partner_update_on_demand_quantities and it means the caller
145 !! needs to pass the correct requested_iteration.
146 recursive subroutine interaction_partner_update_on_demand_quantity(this, quantity, requested_iteration)
147 class(interaction_partner_t), intent(inout) :: this
149 type(quantity_t), intent(inout) :: quantity
150 class(iteration_counter_t), intent(in) :: requested_iteration
152 integer :: i
153 type(quantity_t), pointer :: parent
154
155 ! Before updating this quantity, we also need to update its parents
156 do i = 1, size(quantity%parents)
157 parent => this%quantities%get(quantity%parents(i))
158
159 ! We are only allowed to update on demand quantities that are behind the requested iteration
160 if (parent%iteration >= requested_iteration .or. .not. parent%updated_on_demand) cycle
161
162 call this%update_on_demand_quantity(parent, requested_iteration)
163 end do
164
165 ! If all parents are at the requested time, we can proceed with updating the quantity itself
166 ! Note that here we ignore quantities that are available at any time.
167 if (all(this%quantities%iteration_equal(quantity%parents, requested_iteration) .or. &
168 this%quantities%always_available(quantity%parents))) then
169
170 quantity%iteration = requested_iteration
171 call multisystem_debug_write_marker(this%namespace, event_iteration_update_t("quantity", quantity%label, &
172 quantity%iteration, "set"))
173 call this%update_quantity(quantity%label)
174 end if
175
178
179 ! ---------------------------------------------------------
187 subroutine interaction_partner_update_on_demand_quantities(this, labels, requested_iteration, retardation_allowed)
188 class(interaction_partner_t), target, intent(inout) :: this
189 character(len=*), intent(in) :: labels(:)
190 class(iteration_counter_t), intent(in) :: requested_iteration
191 logical, intent(in) :: retardation_allowed
192
193 integer :: iq
194 type(quantity_t), pointer :: quantity
195
196 do iq = 1, size(labels)
197 ! Get a pointer to the quantity
198 quantity => this%quantities%get(labels(iq))
200 ! We are only updating on demand quantities that are behind the requested iteration
201 if (quantity%iteration >= requested_iteration .or. .not. quantity%updated_on_demand) cycle
202
203 if (quantity%always_available) then
204 ! We set the quantity iteration to the requested one, so that the partner
205 ! can use this information when updating the quantity
206 call this%update_on_demand_quantity(quantity, requested_iteration)
207
208 else if (quantity%iteration + 1 <= requested_iteration .or. &
209 (retardation_allowed .and. quantity%iteration + 1 > requested_iteration)) then
210 ! We can update because the partner will reach this iteration in the next algorithmic step
211 ! For retarded interactions, we need to allow the quantity to get ahead by one iteration
212 call this%update_on_demand_quantity(quantity, quantity%iteration + 1)
213
214 end if
215 end do
216
218
219 ! ---------------------------------------------------------
227 integer function interaction_partner_check_couplings_status(this, couplings, requested_iteration) result(status)
228 class(interaction_partner_t), intent(inout) :: this
229 character(len=*), intent(in) :: couplings(:)
230 class(iteration_counter_t), intent(in) :: requested_iteration
231
232 type(quantity_t), pointer :: coupling
233 integer :: i, ahead, on_time, relevant_couplings
234 character(len=200) :: marker_info
235 character(len=20) :: status_string
236 type(event_handle_t) :: debug_handle
237
238
240
241 debug_handle = multisystem_debug_write_event_in(system_namespace = this%namespace, &
242 event = event_function_call_t("check_couplings_status"), &
243 requested_iteration = requested_iteration)
244
245
246 ! Count couplings on time and ahead
247 on_time = 0
248 ahead = 0
249 relevant_couplings = 0
250 do i = 1, size(couplings)
251 coupling => this%quantities%get(couplings(i))
252
253 ! Couplings that are available at any time do not affect the status, so we will ignore them
254 if (coupling%always_available) cycle
255
256 relevant_couplings = relevant_couplings + 1
257 if (coupling%iteration == requested_iteration) on_time = on_time + 1
258 if (coupling%iteration > requested_iteration) ahead = ahead + 1
259 end do
260
261 ! Determine status
262 if (on_time > 0 .and. ahead > 0) then
263 status = couplings_undefined
264 status_string = "UNDEFINED"
265 else if (on_time + ahead < relevant_couplings) then
267 status_string = "BEHIND"
268 else if (on_time == relevant_couplings) then
269 status = couplings_on_time
270 status_string = "ON_TIME"
271 else if (ahead == relevant_couplings) then
273 status_string = "AHEAD"
274 end if
275
276 write(marker_info, '(A20," check_couplings_status: ahead = ",I5,", on_time = ",I5,", relevant = ",I5, ", status = ",A9)') &
277 trim(this%namespace%get()), ahead, on_time, relevant_couplings, trim(status_string)
278 call multisystem_debug_write_event_out(debug_handle, extra=marker_info, requested_iteration=requested_iteration)
279
282
283 ! ---------------------------------------------------------
286 subroutine partner_list_add_node(this, partner)
287 class(partner_list_t) :: this
288 class(interaction_partner_t), target :: partner
289
290 push_sub(partner_list_add_node)
291
292 call this%add_ptr(partner)
293
294 pop_sub(partner_list_add_node)
295 end subroutine partner_list_add_node
296
297 ! ---------------------------------------------------------
300 function partner_iterator_get_next(this) result(partner)
301 class(partner_iterator_t), intent(inout) :: this
302 class(interaction_partner_t), pointer :: partner
303
305
306 select type (ptr => this%get_next_ptr())
307 class is (interaction_partner_t)
308 partner => ptr
309 class default
310 assert(.false.)
311 end select
312
314 end function partner_iterator_get_next
315
317
318!! Local Variables:
319!! mode: f90
320!! coding: utf-8
321!! End:
This module defines classes and functions for interaction partners.
integer, parameter, public couplings_on_time
recursive subroutine interaction_partner_add_partners_to_list(this, list, interaction_type)
add interaction partner to a list
integer function interaction_partner_check_couplings_status(this, couplings, requested_iteration)
Check the status of some couplings.
class(interaction_partner_t) function, pointer partner_iterator_get_next(this)
get next partner from the list
recursive subroutine interaction_partner_update_on_demand_quantity(this, quantity, requested_iteration)
subroutine partner_list_add_node(this, partner)
add a partner to the list
integer, parameter, public couplings_behind_in_time
subroutine interaction_partner_update_on_demand_quantities(this, labels, requested_iteration, retardation_allowed)
Given a list of quantities, update the ones that can be update on demand.
subroutine interaction_partner_update_quantity(this, label)
Method to be overriden by interaction partners that have quantities that can be updated on demand.
integer, parameter, public couplings_ahead_in_time
This module implements fully polymorphic linked lists, and some specializations thereof.
character(len=256), dimension(max_lines), public message
to be output by fatal, warning
Definition: messages.F90:160
subroutine, public messages_fatal(no_lines, only_root_writes, namespace)
Definition: messages.F90:414
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
abstract class for general interaction partners
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
Systems (system_t) can expose quantities that can be used to calculate interactions with other system...
Definition: quantity.F90:171