31  integer, 
parameter, 
public ::   &
 
   32    COUPLINGS_UNDEFINED      = 0, &
 
   44    type(namespace_t), 
public :: namespace
 
   46    integer, 
allocatable, 
public :: supported_interactions_as_partner(:)
 
   49    type(quantity_t),  
public :: quantities(MAX_QUANTITIES)
 
   57    procedure(interaction_partner_init_interaction_as_partner),    
deferred :: init_interaction_as_partner
 
   59    procedure(interaction_partner_copy_quantities_to_interaction), 
deferred :: copy_quantities_to_interaction
 
   68      class(interaction_partner_t),     
intent(in)    :: partner
 
   69      class(interaction_surrogate_t),   
intent(inout) :: interaction
 
   76      class(interaction_partner_t),     
intent(inout) :: partner
 
   77      class(interaction_surrogate_t),   
intent(inout) :: interaction
 
  108    class(interaction_partner_t),           
intent(in)    :: this
 
  109    class(partner_list_t),                  
intent(inout) :: list
 
  110    integer,                      
optional, 
intent(in)    :: interaction_type
 
  112    if (
present(interaction_type)) 
then 
  113      if (any(this%supported_interactions_as_partner == interaction_type)) 
then 
  131    class(interaction_partner_t), 
intent(inout) :: this
 
  132    integer,                      
intent(in)    :: iq
 
  136    write(
message(1), 
'(a,a,a,a,a)') 
'Interation partner "', trim(this%namespace%get()), &
 
  153    integer,                              
intent(in)    :: quantities(:)
 
  155    logical,                              
intent(in)    :: retardation_allowed
 
  160    do iq = 1, 
size(quantities)
 
  162      q_id = quantities(iq)
 
  163      quantity => this%quantities(q_id)
 
  166      if (quantity%iteration >= requested_iteration .or. .not. quantity%updated_on_demand) cycle
 
  168      if (quantity%always_available) 
then 
  171        quantity%iteration = requested_iteration
 
  174          quantity%iteration, 
"set"))
 
  175        call this%update_quantity(q_id)
 
  177      else if (quantity%iteration + 1 <= requested_iteration .or. &
 
  178        (retardation_allowed .and. quantity%iteration + 1 > requested_iteration)) 
then 
  181        quantity%iteration = quantity%iteration + 1
 
  184          quantity%iteration, 
"set"))
 
  185        call this%update_quantity(q_id)
 
  201    integer,                      
intent(in)    :: couplings(:)
 
  204    integer, 
allocatable :: relevant_couplings(:)
 
  205    integer :: ahead, on_time
 
  210    relevant_couplings = pack(couplings, .not. this%quantities(couplings)%always_available)
 
  213    on_time = count(this%quantities(relevant_couplings)%iteration == requested_iteration)
 
  214    ahead = count(this%quantities(relevant_couplings)%iteration > requested_iteration)
 
  217    if (on_time > 0 .and. ahead > 0) 
then 
  218      status = couplings_undefined
 
  219    else if (on_time + ahead < 
size(relevant_couplings)) 
then 
  221    else if (on_time == 
size(relevant_couplings)) 
then 
  223    else if (ahead == 
size(relevant_couplings)) 
then 
  239    call this%add_ptr(partner)
 
  253    select type (ptr => this%get_next_ptr())
 
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
 
subroutine interaction_partner_update_quantity(this, iq)
Method to be overriden by interaction partners that have quantities that can be updated on demand.
 
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
 
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, quantities, requested_iteration, retardation_allowed)
Given a list of quantities, update the ones that can be update 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
 
subroutine, public messages_fatal(no_lines, only_root_writes, namespace)
 
This module implements the multisystem debug functionality.
 
subroutine, public multisystem_debug_write_marker(system_namespace, event)
 
This module defines the quantity_t class and the IDs for quantities, which can be exposed by a system...
 
character(len=17), dimension(max_quantities), parameter, public quantity_label
 
abstract class for general interaction partners
 
iterator for the list of 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.
 
events marking an iteration update
 
Systems (system_t) can expose quantities that can be used to calculate interactions with other system...