MONC
Data Types | Functions/Subroutines | Variables
broadcast_inter_io_mod Module Reference

Broadcast inter IO communication which sends a value from one IO server to all others. This tracks field name and timestep and only issues one call (and one results call to completion) for that combination. More...

Data Types

type  inter_io_broadcast
 
type  threaded_callback_parameters_type
 

Functions/Subroutines

subroutine, public init_broadcast_inter_io (io_configuration)
 Initialises the broadcast inter IO functionality. More...
 
subroutine, public finalise_broadcast_inter_io ()
 Finalises the broadcast inter IO functionality. More...
 
logical function, public check_broadcast_inter_io_for_completion (io_configuration)
 Checks the statuses for broadcast completion and returns whether they are all finished or not. More...
 
subroutine handle_recv_data_from_io_server (io_configuration, data_buffer, inter_io_index)
 Handles receiving data from another IO server and processing this. If the request has already been registered (with a callback) then this simply calls out. Otherwise it has to cache the data and awaits a thread calling the broadcast to call out to the callback. More...
 
subroutine, public perform_inter_io_broadcast (io_configuration, field_values, field_size, field_name, root, timestep, completion_procedure)
 Performs an inter IO broadcast of data from the root to all other IO servers. Note that this is on the IO server (and not MONC level) so might require some translation between the user's logical view and this view. Broadcasts are only issued once for a specific field_name and timestep pair. More...
 
subroutine issue_thread_call_to_completion (field_name, timestep, values, completion_procedure)
 Issues the call into the thread pool to call the completion procedure, this runs in a seperate thread and ensures the semantics of one IO server or many with message ordering are independent. More...
 
subroutine thread_call_to_completion (arguments, data_buffer)
 Called by the thread pool, this will call onto the completion procedure before cleaning up @arguments Integer arguments, this is the ID of the entry in the state @data_buffer Unused here. More...
 
subroutine clean_broadcast_progress_if_needed ()
 Calls out to do a broadcast progress clean if needed (i.e. every n steps.) More...
 
subroutine clean_broadcast_progress ()
 Performs a clean of the broadcast progresses that no longer need to be stored. More...
 
type(inter_io_broadcast) function, pointer find_or_add_broadcast_item (field_name, timestep, completion_procedure)
 Locates and returns or adds and returns a specific broadcast item representing a timestep and field. More...
 
type(inter_io_broadcast) function, pointer find_broadcast_item (field_name, timestep, do_read_lock)
 Finds a specific broadcast item or null if none is found. More...
 
type(inter_io_broadcast) function, pointer retrieve_broadcast_item (mapentry)
 Locates a broadcast item within a mapentry or null if none exists. More...
 

Variables

integer, parameter my_inter_io_tag =2
 
integer, parameter perform_clean_every =200
 
character(len= *), parameter my_inter_io_name ="bcastinterio"
 Type keeping track of broadcast statuses. More...
 
type(io_configuration_type), pointer stored_io_configuration
 
type(hashmap_type), volatile broadcast_statuses
 
type(hashmap_type), volatile thread_callback_params
 
integer, volatile broadcast_statuses_rwlock
 
integer, volatile inter_io_description_mutex
 
integer, volatile clean_progress_mutex
 
integer, volatile bcast_count_mutex
 
integer, volatile bcast_clean_reduction_count
 
integer, volatile bcast_count
 
integer, volatile thread_callback_params_id
 
integer, volatile thread_callback_params_mutex
 
logical, volatile initialised =.false.
 

Detailed Description

Broadcast inter IO communication which sends a value from one IO server to all others. This tracks field name and timestep and only issues one call (and one results call to completion) for that combination.

Function/Subroutine Documentation

◆ check_broadcast_inter_io_for_completion()

logical function, public broadcast_inter_io_mod::check_broadcast_inter_io_for_completion ( type(io_configuration_type), intent(inout)  io_configuration)

Checks the statuses for broadcast completion and returns whether they are all finished or not.

Parameters
io_configurationThe IO server configuration
Returns
Whether the broadcast inter IO has finished (i.e. no messages in transit)

Definition at line 109 of file broadcast-inter-io.F90.

110  type(io_configuration_type), intent(inout) :: io_configuration
111 
112  type(inter_io_broadcast), pointer :: broadcast_item
113  type(iterator_type) :: iterator
114 
115  check_broadcast_inter_io_for_completion=.true.
116  call check_thread_status(forthread_rwlock_rdlock(broadcast_statuses_rwlock))
117  if (.not. c_is_empty(broadcast_statuses)) then
118  iterator=c_get_iterator(broadcast_statuses)
119  do while (c_has_next(iterator))
120  broadcast_item=>retrieve_broadcast_item(c_next_mapentry(iterator))
121  if (.not. broadcast_item%handled) then
122  check_broadcast_inter_io_for_completion=.false.
123  exit
124  end if
125  end do
126  end if
127  call check_thread_status(forthread_rwlock_unlock(broadcast_statuses_rwlock))
Here is the call graph for this function:

◆ clean_broadcast_progress()

subroutine broadcast_inter_io_mod::clean_broadcast_progress
private

Performs a clean of the broadcast progresses that no longer need to be stored.

Definition at line 291 of file broadcast-inter-io.F90.

292  type(inter_io_broadcast), pointer :: specific_broadcast_item_at_index
293  integer :: completion_flag, ierr, num_to_remove, have_lock
294  character(len=STRING_LENGTH) :: entry_key
295  type(list_type) :: entries_to_remove
296  logical :: destroy_lock
297  type(iterator_type) :: iterator
298  type(mapentry_type) :: mapentry
299  class(*), pointer :: generic
300 
301  have_lock=forthread_mutex_trylock(clean_progress_mutex)
302  if (have_lock==0) then
303  call check_thread_status(forthread_rwlock_rdlock(broadcast_statuses_rwlock))
304  iterator=c_get_iterator(broadcast_statuses)
305  do while (c_has_next(iterator))
306  destroy_lock=.false.
307  mapentry=c_next_mapentry(iterator)
308  specific_broadcast_item_at_index=>retrieve_broadcast_item(mapentry)
309  call check_thread_status(forthread_mutex_lock(specific_broadcast_item_at_index%mutex))
310  if (allocated(specific_broadcast_item_at_index%send_requests)) then
311  call lock_mpi()
312  call mpi_testall(size(specific_broadcast_item_at_index%send_requests), specific_broadcast_item_at_index%send_requests, &
313  completion_flag, mpi_statuses_ignore, ierr)
314  call unlock_mpi()
315  if (completion_flag == 1) then
316  deallocate(specific_broadcast_item_at_index%send_requests)
317  if (allocated(specific_broadcast_item_at_index%send_buffer)) deallocate(specific_broadcast_item_at_index%send_buffer)
318  call c_add_string(entries_to_remove, mapentry%key)
319  destroy_lock=.true.
320  end if
321  else
322  if (specific_broadcast_item_at_index%handled) then
323  if (allocated(specific_broadcast_item_at_index%cached_values)) then
324  deallocate(specific_broadcast_item_at_index%cached_values)
325  end if
326  call c_add_string(entries_to_remove, mapentry%key)
327  destroy_lock=.true.
328  end if
329  end if
330  call check_thread_status(forthread_mutex_unlock(specific_broadcast_item_at_index%mutex))
331  if (destroy_lock) call check_thread_status(forthread_mutex_destroy(specific_broadcast_item_at_index%mutex))
332  end do
333  call check_thread_status(forthread_rwlock_unlock(broadcast_statuses_rwlock))
334 
335  if (.not. c_is_empty(entries_to_remove)) then
336  call check_thread_status(forthread_rwlock_wrlock(broadcast_statuses_rwlock))
337  iterator=c_get_iterator(entries_to_remove)
338  do while (c_has_next(iterator))
339  entry_key=c_next_string(iterator)
340  generic=>c_get_generic(broadcast_statuses, entry_key)
341  call c_remove(broadcast_statuses, entry_key)
342  deallocate(generic)
343  end do
344  call check_thread_status(forthread_rwlock_unlock(broadcast_statuses_rwlock))
345  end if
346  call c_free(entries_to_remove)
347  call check_thread_status(forthread_mutex_unlock(clean_progress_mutex))
348  end if
Here is the call graph for this function:
Here is the caller graph for this function:

◆ clean_broadcast_progress_if_needed()

subroutine broadcast_inter_io_mod::clean_broadcast_progress_if_needed
private

Calls out to do a broadcast progress clean if needed (i.e. every n steps.)

Definition at line 278 of file broadcast-inter-io.F90.

279  call check_thread_status(forthread_mutex_lock(bcast_count_mutex))
280  bcast_count=bcast_count+1
281  if (bcast_clean_reduction_count + perform_clean_every .lt. bcast_count) then
282  bcast_clean_reduction_count=bcast_count
283  call check_thread_status(forthread_mutex_unlock(bcast_count_mutex))
284  call clean_broadcast_progress()
285  else
286  call check_thread_status(forthread_mutex_unlock(bcast_count_mutex))
287  end if
Here is the call graph for this function:
Here is the caller graph for this function:

◆ finalise_broadcast_inter_io()

subroutine, public broadcast_inter_io_mod::finalise_broadcast_inter_io

Finalises the broadcast inter IO functionality.

Definition at line 76 of file broadcast-inter-io.F90.

77  type(inter_io_broadcast), pointer :: broadcast_item
78  type(iterator_type) :: iterator
79 
80  if (initialised) then
81  call check_thread_status(forthread_rwlock_rdlock(broadcast_statuses_rwlock))
82  if (.not. c_is_empty(broadcast_statuses)) then
83  iterator=c_get_iterator(broadcast_statuses)
84  do while (c_has_next(iterator))
85  broadcast_item=>retrieve_broadcast_item(c_next_mapentry(iterator))
86  call check_thread_status(forthread_mutex_lock(broadcast_item%mutex))
87  if (allocated(broadcast_item%send_requests)) then
88  call waitall_for_mpi_requests(broadcast_item%send_requests, size(broadcast_item%send_requests))
89  deallocate(broadcast_item%send_requests)
90  if (allocated(broadcast_item%send_buffer)) deallocate(broadcast_item%send_buffer)
91  end if
92  call check_thread_status(forthread_mutex_unlock(broadcast_item%mutex))
93  call check_thread_status(forthread_mutex_destroy(broadcast_item%mutex))
94  end do
95  end if
96  call check_thread_status(forthread_rwlock_unlock(broadcast_statuses_rwlock))
97  call check_thread_status(forthread_rwlock_destroy(broadcast_statuses_rwlock))
98  call check_thread_status(forthread_mutex_destroy(inter_io_description_mutex))
99  call check_thread_status(forthread_mutex_destroy(thread_callback_params_mutex))
100  call check_thread_status(forthread_mutex_destroy(clean_progress_mutex))
101  call check_thread_status(forthread_mutex_destroy(bcast_count_mutex))
102  initialised=.false.
103  end if
Here is the call graph for this function:
Here is the caller graph for this function:

◆ find_broadcast_item()

type(inter_io_broadcast) function, pointer broadcast_inter_io_mod::find_broadcast_item ( character(len=*), intent(in)  field_name,
integer, intent(in)  timestep,
logical, intent(in)  do_read_lock 
)
private

Finds a specific broadcast item or null if none is found.

Parameters
field_nameCorresponding field name to find
timestepCorresponding timestep to find
do_read_lockWhether to issue a read lock or not
Returns
The corresponding broadcast status item or null if none is found

Definition at line 389 of file broadcast-inter-io.F90.

390  character(len=*), intent(in) :: field_name
391  integer, intent(in) :: timestep
392  logical, intent(in) :: do_read_lock
393  type(inter_io_broadcast), pointer :: find_broadcast_item
394 
395  class(*), pointer :: generic
396 
397  if (do_read_lock) call check_thread_status(forthread_rwlock_rdlock(broadcast_statuses_rwlock))
398  generic=>c_get_generic(broadcast_statuses, trim(field_name)//"#"//conv_to_string(timestep))
399  if (do_read_lock) call check_thread_status(forthread_rwlock_unlock(broadcast_statuses_rwlock))
400 
401  if (associated(generic)) then
402  select type(generic)
403  type is (inter_io_broadcast)
404  find_broadcast_item=>generic
405  end select
406  else
407  find_broadcast_item=>null()
408  end if
Here is the call graph for this function:
Here is the caller graph for this function:

◆ find_or_add_broadcast_item()

type(inter_io_broadcast) function, pointer broadcast_inter_io_mod::find_or_add_broadcast_item ( character(len=*), intent(in)  field_name,
integer, intent(in)  timestep,
procedure(handle_completion), optional  completion_procedure 
)
private

Locates and returns or adds and returns a specific broadcast item representing a timestep and field.

Parameters
field_nameThe field name this represents
timestepThe timestep this represents
completion_procedureThe (optional) completion procedure which is called once values are received
Returns
The existing or new broadcast item

Definition at line 356 of file broadcast-inter-io.F90.

357  character(len=*), intent(in) :: field_name
358  integer, intent(in) :: timestep
359  procedure(handle_completion), optional :: completion_procedure
360  type(inter_io_broadcast), pointer :: find_or_add_broadcast_item
361 
362  class(*), pointer :: generic
363 
364  find_or_add_broadcast_item=>find_broadcast_item(field_name, timestep, .true.)
365  if (.not. associated(find_or_add_broadcast_item)) then
366  call check_thread_status(forthread_rwlock_wrlock(broadcast_statuses_rwlock))
367  find_or_add_broadcast_item=>find_broadcast_item(field_name, timestep, .false.)
368  if (.not. associated(find_or_add_broadcast_item)) then
369  allocate(find_or_add_broadcast_item)
370  if (present(completion_procedure)) then
371  find_or_add_broadcast_item%completion_procedure=>completion_procedure
372  else
373  find_or_add_broadcast_item%completion_procedure=>null()
374  end if
375  find_or_add_broadcast_item%handled=.false.
376  call check_thread_status(forthread_mutex_init(find_or_add_broadcast_item%mutex, -1))
377  generic=>find_or_add_broadcast_item
378  call c_put_generic(broadcast_statuses, trim(field_name)//"#"//conv_to_string(timestep), generic, .false.)
379  end if
380  call check_thread_status(forthread_rwlock_unlock(broadcast_statuses_rwlock))
381  end if
Here is the call graph for this function:
Here is the caller graph for this function:

◆ handle_recv_data_from_io_server()

subroutine broadcast_inter_io_mod::handle_recv_data_from_io_server ( type(io_configuration_type), intent(inout)  io_configuration,
character, dimension(:), intent(inout)  data_buffer,
integer, intent(in)  inter_io_index 
)
private

Handles receiving data from another IO server and processing this. If the request has already been registered (with a callback) then this simply calls out. Otherwise it has to cache the data and awaits a thread calling the broadcast to call out to the callback.

Parameters
io_configurationThe IO server configuration
data_bufferData received from other IO server
inter_io_indexIndex of the inter IO communication description

Definition at line 136 of file broadcast-inter-io.F90.

137  type(io_configuration_type), intent(inout) :: io_configuration
138  character, dimension(:), intent(inout) :: data_buffer
139  integer, intent(in) :: inter_io_index
140 
141  type(inter_io_broadcast), pointer :: broadcast_item
142  real(kind=default_precision), dimension(:), allocatable :: data_values
143  character(len=STRING_LENGTH) :: field_name
144  integer :: timestep
145 
146  call unpackage_inter_io_communication_message(data_buffer, field_name, timestep, data_values)
147 
148  broadcast_item=>find_or_add_broadcast_item(field_name, timestep)
149 
150  if (associated(broadcast_item%completion_procedure)) then
151  call check_thread_status(forthread_mutex_lock(broadcast_item%mutex))
152  broadcast_item%handled=.true.
153  call check_thread_status(forthread_mutex_unlock(broadcast_item%mutex))
154  call issue_thread_call_to_completion(field_name, timestep, data_values, broadcast_item%completion_procedure)
155  else
156  call check_thread_status(forthread_mutex_lock(broadcast_item%mutex))
157  allocate(broadcast_item%cached_values(size(data_values)), source=data_values)
158  broadcast_item%cached_values=data_values
159  call check_thread_status(forthread_mutex_unlock(broadcast_item%mutex))
160  end if
161  if (allocated(data_values)) deallocate(data_values)
Here is the call graph for this function:
Here is the caller graph for this function:

◆ init_broadcast_inter_io()

subroutine, public broadcast_inter_io_mod::init_broadcast_inter_io ( type(io_configuration_type), intent(inout), target  io_configuration)

Initialises the broadcast inter IO functionality.

Parameters
io_configurationThe IO server configuration

Definition at line 57 of file broadcast-inter-io.F90.

58  type(io_configuration_type), intent(inout), target :: io_configuration
59 
60  if (.not. initialised) then
61  stored_io_configuration=>io_configuration
62  initialised=.true.
63  bcast_count=0
64  thread_callback_params_id=0
65  bcast_clean_reduction_count=0
66  call check_thread_status(forthread_rwlock_init(broadcast_statuses_rwlock, -1))
67  call check_thread_status(forthread_mutex_init(inter_io_description_mutex, -1))
68  call check_thread_status(forthread_mutex_init(thread_callback_params_mutex, -1))
69  call check_thread_status(forthread_mutex_init(clean_progress_mutex, -1))
70  call check_thread_status(forthread_mutex_init(bcast_count_mutex, -1))
71  call register_inter_io_communication(io_configuration, my_inter_io_tag, handle_recv_data_from_io_server, my_inter_io_name)
72  end if
Here is the call graph for this function:
Here is the caller graph for this function:

◆ issue_thread_call_to_completion()

subroutine broadcast_inter_io_mod::issue_thread_call_to_completion ( character(len=*), intent(in)  field_name,
integer, intent(in)  timestep,
real(default_precision), dimension(:), intent(in)  values,
procedure(handle_completion completion_procedure 
)
private

Issues the call into the thread pool to call the completion procedure, this runs in a seperate thread and ensures the semantics of one IO server or many with message ordering are independent.

Parameters
field_nameThe name of the field
timestepThe timestep
valuesData values
completion_procedureThe completion procedure to call

Definition at line 225 of file broadcast-inter-io.F90.

226  integer, intent(in) :: timestep
227  character(len=*), intent(in) :: field_name
228  real(DEFAULT_PRECISION), dimension(:), intent(in) :: values
229  procedure(handle_completion) :: completion_procedure
230 
231  type(threaded_callback_parameters_type), pointer :: threaded_callback_state
232  class(*), pointer :: generic
233 
234  allocate(threaded_callback_state)
235 
236  threaded_callback_state%field_name=field_name
237  threaded_callback_state%timestep=timestep
238  allocate(threaded_callback_state%values(size(values)), source=values)
239  threaded_callback_state%completion_procedure=>completion_procedure
240 
241  call check_thread_status(forthread_mutex_lock(thread_callback_params_mutex))
242  generic=>threaded_callback_state
243  call c_put_generic(thread_callback_params, trim(conv_to_string(thread_callback_params_id)), generic, .false.)
244  thread_callback_params_id=thread_callback_params_id+1
245  call check_thread_status(forthread_mutex_unlock(thread_callback_params_mutex))
246 
247  call threadpool_start_thread(thread_call_to_completion, (/ thread_callback_params_id-1 /))
Here is the call graph for this function:
Here is the caller graph for this function:

◆ perform_inter_io_broadcast()

subroutine, public broadcast_inter_io_mod::perform_inter_io_broadcast ( type(io_configuration_type), intent(inout)  io_configuration,
real(kind=double_precision), dimension(:)  field_values,
integer, intent(in)  field_size,
character(len=*), intent(in)  field_name,
integer, intent(in)  root,
integer, intent(in)  timestep,
procedure(handle_completion completion_procedure 
)

Performs an inter IO broadcast of data from the root to all other IO servers. Note that this is on the IO server (and not MONC level) so might require some translation between the user's logical view and this view. Broadcasts are only issued once for a specific field_name and timestep pair.

Parameters
io_configurationConfiguration of the IO server
field_valuesThe values to communicate
field_sizeNumber of elements to communicate
field_nameField name that the reduction will be performed over
rootThe root IO server process
timestepThe timestep this is issued at
completion_procedureCallback completion procedure

Definition at line 174 of file broadcast-inter-io.F90.

176  type(io_configuration_type), intent(inout) :: io_configuration
177  real(kind=double_precision), dimension(:) :: field_values
178  integer, intent(in) :: field_size, root, timestep
179  character(len=*), intent(in) :: field_name
180  procedure(handle_completion) :: completion_procedure
181 
182  type(inter_io_broadcast), pointer :: broadcast_item
183  integer :: inter_io_comm_index, i, ierr
184 
185  call clean_broadcast_progress_if_needed()
186  inter_io_comm_index=find_inter_io_from_name(io_configuration, my_inter_io_name)
187  broadcast_item=>find_or_add_broadcast_item(field_name, timestep, completion_procedure)
188 
189  call check_thread_status(forthread_mutex_lock(broadcast_item%mutex))
190  if (io_configuration%my_io_rank == root .and. .not. broadcast_item%handled) then
191  broadcast_item%handled=.true.
192 
193  allocate(broadcast_item%send_requests(io_configuration%number_of_io_servers))
194  broadcast_item%send_buffer=package_inter_io_communication_message(field_name, timestep, field_values)
195 
196  do i=0, io_configuration%number_of_io_servers-1
197  if (i .ne. io_configuration%my_io_rank) then
198  call lock_mpi()
199  call mpi_isend(broadcast_item%send_buffer, size(broadcast_item%send_buffer), mpi_byte, i, &
200  io_configuration%inter_io_communications(inter_io_comm_index)%message_tag, &
201  io_configuration%io_communicator, broadcast_item%send_requests(i+1), ierr)
202  call unlock_mpi()
203  else
204  broadcast_item%send_requests(i+1)=mpi_request_null
205  end if
206  end do
207  ! Still call the completion procedure on the root
208  call issue_thread_call_to_completion(field_name, timestep, field_values, completion_procedure)
209  else
210  if (allocated(broadcast_item%cached_values) .and. .not. broadcast_item%handled) then
211  broadcast_item%handled=.true.
212  call issue_thread_call_to_completion(field_name, timestep, broadcast_item%cached_values, completion_procedure)
213  if (allocated(broadcast_item%cached_values)) deallocate(broadcast_item%cached_values)
214  end if
215  end if
216  call check_thread_status(forthread_mutex_unlock(broadcast_item%mutex))
Here is the call graph for this function:
Here is the caller graph for this function:

◆ retrieve_broadcast_item()

type(inter_io_broadcast) function, pointer broadcast_inter_io_mod::retrieve_broadcast_item ( type(mapentry_type), intent(in)  mapentry)
private

Locates a broadcast item within a mapentry or null if none exists.

Parameters
mapentryThe map entry to use for this retrieval
Returns
The broadcast status or null if none exists

Definition at line 414 of file broadcast-inter-io.F90.

415  type(mapentry_type), intent(in) :: mapentry
416  type(inter_io_broadcast), pointer :: retrieve_broadcast_item
417 
418  class(*), pointer :: generic
419 
420  generic=>c_get_generic(mapentry)
421 
422  if (associated(generic)) then
423  select type(generic)
424  type is (inter_io_broadcast)
425  retrieve_broadcast_item=>generic
426  end select
427  else
428  retrieve_broadcast_item=>null()
429  end if
Here is the caller graph for this function:

◆ thread_call_to_completion()

subroutine broadcast_inter_io_mod::thread_call_to_completion ( integer, dimension(:), intent(in)  arguments,
character, dimension(:), intent(inout), optional, allocatable  data_buffer 
)
private

Called by the thread pool, this will call onto the completion procedure before cleaning up @arguments Integer arguments, this is the ID of the entry in the state @data_buffer Unused here.

Definition at line 253 of file broadcast-inter-io.F90.

254  integer, dimension(:), intent(in) :: arguments
255  character, dimension(:), allocatable, intent(inout), optional :: data_buffer
256 
257  class(*), pointer :: generic
258  type(threaded_callback_parameters_type), pointer :: threaded_callback_state
259 
260  call check_thread_status(forthread_mutex_lock(thread_callback_params_mutex))
261  generic=>c_get_generic(thread_callback_params, trim(conv_to_string(arguments(1))))
262  select type(generic)
263  type is (threaded_callback_parameters_type)
264  threaded_callback_state=>generic
265  call c_remove(thread_callback_params, trim(conv_to_string(arguments(1))))
266  end select
267  call check_thread_status(forthread_mutex_unlock(thread_callback_params_mutex))
268 
269  if (associated(threaded_callback_state)) then
270  call threaded_callback_state%completion_procedure(stored_io_configuration, threaded_callback_state%values, &
271  threaded_callback_state%field_name, threaded_callback_state%timestep)
272  deallocate(threaded_callback_state%values)
273  deallocate(threaded_callback_state)
274  end if
Here is the call graph for this function:
Here is the caller graph for this function:

Variable Documentation

◆ bcast_clean_reduction_count

integer, volatile broadcast_inter_io_mod::bcast_clean_reduction_count
private

Definition at line 48 of file broadcast-inter-io.F90.

◆ bcast_count

integer, volatile broadcast_inter_io_mod::bcast_count
private

Definition at line 48 of file broadcast-inter-io.F90.

◆ bcast_count_mutex

integer, volatile broadcast_inter_io_mod::bcast_count_mutex
private

Definition at line 48 of file broadcast-inter-io.F90.

◆ broadcast_statuses

type(hashmap_type), volatile broadcast_inter_io_mod::broadcast_statuses
private

Definition at line 47 of file broadcast-inter-io.F90.

47  type(hashmap_type), volatile :: broadcast_statuses, thread_callback_params

◆ broadcast_statuses_rwlock

integer, volatile broadcast_inter_io_mod::broadcast_statuses_rwlock
private

Definition at line 48 of file broadcast-inter-io.F90.

48  integer, volatile :: broadcast_statuses_rwlock, inter_io_description_mutex, clean_progress_mutex, &
49  bcast_count_mutex, bcast_clean_reduction_count, bcast_count, thread_callback_params_id, thread_callback_params_mutex

◆ clean_progress_mutex

integer, volatile broadcast_inter_io_mod::clean_progress_mutex
private

Definition at line 48 of file broadcast-inter-io.F90.

◆ initialised

logical, volatile broadcast_inter_io_mod::initialised =.false.
private

Definition at line 50 of file broadcast-inter-io.F90.

50  logical, volatile :: initialised=.false.

◆ inter_io_description_mutex

integer, volatile broadcast_inter_io_mod::inter_io_description_mutex
private

Definition at line 48 of file broadcast-inter-io.F90.

◆ my_inter_io_name

character(len=*), parameter broadcast_inter_io_mod::my_inter_io_name ="bcastinterio"
private

Type keeping track of broadcast statuses.

Definition at line 26 of file broadcast-inter-io.F90.

26  character(len=*), parameter :: MY_INTER_IO_NAME="bcastinterio"

◆ my_inter_io_tag

integer, parameter broadcast_inter_io_mod::my_inter_io_tag =2
private

Definition at line 25 of file broadcast-inter-io.F90.

25  integer, parameter :: MY_INTER_IO_TAG=2, perform_clean_every=200

◆ perform_clean_every

integer, parameter broadcast_inter_io_mod::perform_clean_every =200
private

Definition at line 25 of file broadcast-inter-io.F90.

◆ stored_io_configuration

type(io_configuration_type), pointer broadcast_inter_io_mod::stored_io_configuration
private

Definition at line 46 of file broadcast-inter-io.F90.

46  type(io_configuration_type), pointer :: stored_io_configuration

◆ thread_callback_params

type(hashmap_type), volatile broadcast_inter_io_mod::thread_callback_params
private

Definition at line 47 of file broadcast-inter-io.F90.

◆ thread_callback_params_id

integer, volatile broadcast_inter_io_mod::thread_callback_params_id
private

Definition at line 48 of file broadcast-inter-io.F90.

◆ thread_callback_params_mutex

integer, volatile broadcast_inter_io_mod::thread_callback_params_mutex
private

Definition at line 48 of file broadcast-inter-io.F90.

datadefn_mod::default_precision
integer, parameter, public default_precision
MPI communication type which we use for the prognostic and calculation data.
Definition: datadefn.F90:17