MONC
reduction-inter-io.F90
Go to the documentation of this file.
1 
15  use logging_mod, only : log_error, log_log
18  use mpi, only : mpi_double_precision, mpi_int, mpi_any_source, mpi_request_null, mpi_status_ignore, mpi_character, mpi_byte
20  implicit none
21 
22 #ifndef TEST_MODE
23  private
24 #endif
25 
26 
27  integer, parameter :: mean=1, min=2, max=3, sum=4
28  integer, parameter :: my_inter_io_tag=1, perform_clean_every=200
29  character(len=*), parameter :: my_inter_io_name="reductioninterio"
30 
32  real(default_precision), dimension(:), allocatable :: values
33  character, dimension(:), allocatable :: send_buffer
34  character(len=STRING_LENGTH) :: field_name
35  integer :: contributed_moncs, contributed_io_servers, timestep, reduction_operator, async_handle, mutex, root
36  procedure(handle_completion), pointer, nopass :: completion_procedure
37  end type reduction_progress_type
38 
42  logical, volatile :: initialised=.false.
43 
46 contains
47 
50  subroutine init_reduction_inter_io(io_configuration)
51  type(io_configuration_type), intent(inout) :: io_configuration
52 
53  if (.not. initialised) then
54  initialised=.true.
62  end if
63  end subroutine init_reduction_inter_io
64 
69  subroutine handle_recv_data_from_io_server(io_configuration, data_buffer, inter_io_index)
70  type(io_configuration_type), intent(inout) :: io_configuration
71  character, dimension(:), intent(inout) :: data_buffer
72  integer, intent(in) :: inter_io_index
73 
74  call handle_process_recv_from_other_io_server(io_configuration, io_configuration%inter_io_communications(inter_io_index), &
75  io_configuration%my_io_rank, data_buffer, io_configuration%number_of_io_servers)
76  end subroutine handle_recv_data_from_io_server
77 
82  logical function check_reduction_inter_io_for_completion(io_configuration)
83  type(io_configuration_type), intent(inout) :: io_configuration
84 
87 
90  subroutine finalise_reduction_inter_io(io_configuration)
91  type(io_configuration_type), intent(inout) :: io_configuration
92 
93  type(reduction_progress_type) :: progress
94  type(iterator_type) :: iterator
95 
96  if (initialised) then
98  if (.not. c_is_empty(reduction_progresses)) then
100  do while (c_has_next(iterator))
101  progress=retrieve_reduction_progress(c_next_mapentry(iterator))
102  if (progress%async_handle /= mpi_request_null) then
103  call wait_for_mpi_request(progress%async_handle)
104  end if
105  end do
106  end if
112  initialised=.false.
113  end if
114  end subroutine finalise_reduction_inter_io
115 
125  subroutine perform_inter_io_reduction(io_configuration, field_values, field_size, reduction_field_name, reduction_op, &
126  root, timestep, completion_procedure)
127  type(io_configuration_type), intent(inout) :: io_configuration
128  real(kind=double_precision), dimension(:) :: field_values
129  integer, intent(in) :: field_size, reduction_op, root, timestep
130  character(len=*), intent(in) :: reduction_field_name
131  procedure(handle_completion) :: completion_procedure
132 
133  type(reduction_progress_type), pointer :: reduction_progress
134  logical :: collective_values_new
135 
136  call clean_progress(io_configuration%my_io_rank)
137  reduction_progress=>find_or_add_reduction_progress(timestep, reduction_op, root, reduction_field_name, completion_procedure)
138 
139  call check_thread_status(forthread_mutex_lock(reduction_progress%mutex))
140  reduction_progress%contributed_moncs=reduction_progress%contributed_moncs+1
141 
142  collective_values_new=.not. allocated(reduction_progress%values)
143  if (collective_values_new) allocate(reduction_progress%values(field_size))
144 
145  call integrate_io_server_collective_values(reduction_op, reduction_progress, field_values, field_size, collective_values_new)
146  if (reduction_progress%contributed_moncs == io_configuration%number_of_moncs) then
147  reduction_progress%contributed_io_servers=reduction_progress%contributed_io_servers+1
148  call handle_local_moncs_completed_collective(io_configuration, reduction_progress)
149  else
150  call check_thread_status(forthread_mutex_unlock(reduction_progress%mutex))
151  end if
152  end subroutine perform_inter_io_reduction
153 
154  subroutine clean_progress(myrank)
155  integer, intent(in) :: myrank
156 
157  logical :: cc_dummy
158 
164  cc_dummy=check_and_clean_progress(myrank)
165  else
167  end if
168  end subroutine clean_progress
169 
174  logical function check_and_clean_progress(myrank)
175  integer, intent(in) :: myrank
176 
177  integer :: i, entries, completed, ierr, num_to_remove, have_lock
178  type(list_type) :: entries_to_remove
179  type(iterator_type) :: iterator
180  type(mapentry_type) :: mapentry
181  type(reduction_progress_type), pointer :: specific_reduction_progress
182  character(len=STRING_LENGTH) :: entry_key
183  class(*), pointer :: generic
184  logical :: destroy_lock
185 
188  if (have_lock == 0) then
191  do while (c_has_next(iterator))
192  mapentry=c_next_mapentry(iterator)
193  destroy_lock=.false.
194  specific_reduction_progress=>retrieve_reduction_progress(mapentry)
195  if (myrank /= specific_reduction_progress%root) then
196  call check_thread_status(forthread_mutex_lock(specific_reduction_progress%mutex))
197  if (specific_reduction_progress%async_handle /= mpi_request_null) then
198  call wait_for_mpi_request(specific_reduction_progress%async_handle)
199  !if (completed == 1) then
200  if (specific_reduction_progress%async_handle == mpi_request_null) then
201  if (allocated(specific_reduction_progress%send_buffer)) deallocate(specific_reduction_progress%send_buffer)
202  destroy_lock=.true.
203  call c_add_string(entries_to_remove, mapentry%key)
204  else
206  end if
207  end if
208  call check_thread_status(forthread_mutex_unlock(specific_reduction_progress%mutex))
209  if (destroy_lock) call check_thread_status(forthread_mutex_destroy(specific_reduction_progress%mutex))
210  end if
211  end do
213 
214  if (.not. c_is_empty(entries_to_remove)) then
216  iterator=c_get_iterator(entries_to_remove)
217  do while (c_has_next(iterator))
218  entry_key=c_next_string(iterator)
219  generic=>c_get_generic(reduction_progresses, entry_key)
220  call c_remove(reduction_progresses, entry_key)
221  deallocate(generic)
222  end do
224  end if
225  call c_free(entries_to_remove)
227  end if
228  end function check_and_clean_progress
229 
237  subroutine integrate_io_server_collective_values(reduction_op, reduction_progress, single_server_values, &
238  number_elements, collective_values_empty)
239  integer, intent(in) :: reduction_op, number_elements
240  logical, intent(in) :: collective_values_empty
241  type(reduction_progress_type), intent(inout) :: reduction_progress
242  real(kind=double_precision), dimension(:), intent(in) :: single_server_values
243 
244  integer :: k
245 
246  if (collective_values_empty) then
247  reduction_progress%values=single_server_values
248  else
249  if (reduction_op == mean .or. reduction_op == sum) then
250  reduction_progress%values=reduction_progress%values+single_server_values
251  else if (reduction_op == min .or. reduction_op == max) then
252  do k=1, number_elements
253  if (reduction_op == min) then
254  if (single_server_values(k) .lt. reduction_progress%values(k)) &
255  reduction_progress%values(k)=single_server_values(k)
256  else if (reduction_op == max) then
257  if (single_server_values(k) .gt. reduction_progress%values(k)) &
258  reduction_progress%values(k)=single_server_values(k)
259  end if
260  end do
261  end if
262  end if
264 
272  subroutine handle_local_moncs_completed_collective(io_configuration, reduction_progress)
273  type(io_configuration_type), intent(inout) :: io_configuration
274  type(reduction_progress_type), intent(inout) :: reduction_progress
275 
276  integer :: ierr, inter_io_comm_index
277 
278  if (io_configuration%my_io_rank == reduction_progress%root .and. &
279  reduction_progress%contributed_io_servers == io_configuration%number_of_io_servers) then
280  call handle_collective_completed(io_configuration, reduction_progress)
281  else
282  if (io_configuration%my_io_rank /= reduction_progress%root) then
283  inter_io_comm_index=find_inter_io_from_name(io_configuration, my_inter_io_name)
284 
285  reduction_progress%send_buffer=package_inter_io_communication_message(reduction_progress%field_name, &
286  reduction_progress%timestep, reduction_progress%values, reduction_progress%reduction_operator)
287  call lock_mpi()
288  call mpi_isend(reduction_progress%send_buffer, size(reduction_progress%send_buffer), &
289  mpi_byte, reduction_progress%root, &
290  io_configuration%inter_io_communications(inter_io_comm_index)%message_tag, &
291  io_configuration%io_communicator, reduction_progress%async_handle, ierr)
292  call unlock_mpi()
293  ! Deallocate the current value as this is finished with and has been packed into the send buffer
294  if (allocated(reduction_progress%values)) deallocate(reduction_progress%values)
295  end if
296  call check_thread_status(forthread_mutex_unlock(reduction_progress%mutex))
297  end if
299 
304  subroutine handle_process_recv_from_other_io_server(io_configuration, inter_io_comm, myrank, data_buffer, number_io_servers)
305  type(io_configuration_type), intent(inout) :: io_configuration
306  type(io_configuration_inter_communication_description), intent(inout) :: inter_io_comm
307  character, dimension(:), intent(inout) :: data_buffer
308  integer, intent(in) :: number_io_servers, myrank
309 
310  type(reduction_progress_type), pointer :: reduction_progress
311  character(len=STRING_LENGTH) :: field_name
312  integer :: timestep, reduction_op
313  real(kind=default_precision), dimension(:), allocatable :: field_values
314  logical :: collective_values_new
315 
316  call unpackage_inter_io_communication_message(data_buffer, field_name, timestep, field_values, reduction_op)
317  reduction_progress=>find_or_add_reduction_progress(timestep, reduction_op, myrank, field_name)
318 
319  call check_thread_status(forthread_mutex_lock(reduction_progress%mutex))
320  collective_values_new=.not. allocated(reduction_progress%values)
321  if (collective_values_new) allocate(reduction_progress%values(size(field_values)))
322 
323  reduction_progress%contributed_io_servers=reduction_progress%contributed_io_servers+1
324  call integrate_io_server_collective_values(reduction_op, reduction_progress, &
325  field_values, size(field_values), collective_values_new)
326  if (reduction_progress%contributed_io_servers == number_io_servers) then
327  call handle_collective_completed(io_configuration, reduction_progress)
328  deallocate(field_values)
329  return
330  end if
331  deallocate(field_values)
332  call check_thread_status(forthread_mutex_unlock(reduction_progress%mutex))
334 
338  subroutine handle_collective_completed(io_configuration, reduction_progress)
339  type(io_configuration_type), intent(inout) :: io_configuration
340  type(reduction_progress_type), intent(inout) :: reduction_progress
341 
342  if (reduction_progress%reduction_operator == mean) then
343  reduction_progress%values=reduction_progress%values/io_configuration%number_of_global_moncs
344  end if
345  call reduction_progress%completion_procedure(io_configuration, reduction_progress%values, &
346  reduction_progress%field_name, reduction_progress%timestep)
347  call check_thread_status(forthread_mutex_unlock(reduction_progress%mutex))
348  call check_thread_status(forthread_mutex_destroy(reduction_progress%mutex))
349  if (allocated(reduction_progress%values)) deallocate(reduction_progress%values)
350  call remove_reduction_progress(reduction_progress)
351  end subroutine handle_collective_completed
352 
360  function find_or_add_reduction_progress(timestep, reduction_operator, root, field_name, completion_procedure)
361  integer, intent(in) :: timestep, reduction_operator, root
363  character(len=*), intent(in) :: field_name
364  procedure(handle_completion), optional :: completion_procedure
365 
366  class(*), pointer :: generic
367  type(reduction_progress_type), pointer :: new_progress
368 
369  find_or_add_reduction_progress=>find_reduction_progress(timestep, reduction_operator, field_name)
370  if (.not. associated(find_or_add_reduction_progress)) then
372  find_or_add_reduction_progress=>find_reduction_progress(timestep, reduction_operator, field_name, issue_read_lock=.false.)
373  if (.not. associated(find_or_add_reduction_progress)) then
374  allocate(new_progress)
375  call check_thread_status(forthread_mutex_init(new_progress%mutex, -1))
376  new_progress%timestep=timestep
377  new_progress%reduction_operator=reduction_operator
378  new_progress%contributed_moncs=0
379  new_progress%contributed_io_servers=0
380  new_progress%root=root
381  new_progress%async_handle=mpi_request_null
382  new_progress%field_name=field_name
383  if (present(completion_procedure)) then
384  new_progress%completion_procedure=>completion_procedure
385  else
386  new_progress%completion_procedure=>null()
387  end if
388  generic=>new_progress
389  call c_put_generic(reduction_progresses, generate_reduction_key(field_name, timestep, reduction_operator), &
390  generic, .false.)
391  find_or_add_reduction_progress=>new_progress
392  end if
394  end if
395  if (.not. associated(find_or_add_reduction_progress%completion_procedure) .and. present(completion_procedure)) then
396  find_or_add_reduction_progress%completion_procedure=>completion_procedure
397  end if
398  end function find_or_add_reduction_progress
399 
406  function find_reduction_progress(timestep, reduction_operator, field_name, issue_read_lock)
407  integer, intent(in) :: timestep, reduction_operator
408  logical, intent(in), optional :: issue_read_lock
410  character(len=*), intent(in) :: field_name
411 
412  class(*), pointer :: generic
413  logical :: do_read_lock
414 
415  if (present(issue_read_lock)) then
416  do_read_lock=issue_read_lock
417  else
418  do_read_lock=.true.
419  end if
420 
422  generic=>c_get_generic(reduction_progresses, generate_reduction_key(field_name, timestep, reduction_operator))
424  if (associated(generic)) then
425  select type(generic)
426  type is (reduction_progress_type)
427  find_reduction_progress=>generic
428  end select
429  else
431  end if
432  end function find_reduction_progress
433 
436  subroutine remove_reduction_progress(reduction_progress)
437  type(reduction_progress_type), intent(in) :: reduction_progress
438 
439  class(*), pointer :: generic
440  character(len=STRING_LENGTH) :: specific_key
441 
442  specific_key=generate_reduction_key(reduction_progress%field_name, reduction_progress%timestep,&
443  reduction_progress%reduction_operator)
445  generic=>c_get_generic(reduction_progresses, specific_key)
446  call c_remove(reduction_progresses, specific_key)
448  if (associated(generic)) deallocate(generic)
449  end subroutine remove_reduction_progress
450 
455  character(len=STRING_LENGTH) function generate_reduction_key(field_name, timestep, reduction_operator)
456  character(len=*), intent(in) :: field_name
457  integer, intent(in) :: timestep, reduction_operator
458 
459  generate_reduction_key=trim(field_name)//"#"//trim(conv_to_string(timestep))//"#"// trim(conv_to_string(reduction_operator))
460  end function generate_reduction_key
461 
465  function retrieve_reduction_progress(mapentry)
466  type(mapentry_type), intent(in) :: mapentry
468 
469  class(*), pointer :: generic
470 
471  generic=>c_get_generic(mapentry)
472 
473  if (associated(generic)) then
474  select type(generic)
475  type is (reduction_progress_type)
477  end select
478  else
480  end if
481  end function retrieve_reduction_progress
482 
487  integer function get_reduction_operator(op_string)
488  character(len=*), intent(in) :: op_string
489 
490  if (op_string .eq. "mean") then
492  else if (op_string .eq. "min") then
494  else if (op_string .eq. "max") then
496  else if (op_string .eq. "sum") then
498  else
499  call log_log(log_error, "Reduction operator '"//trim(op_string)//"' not recognised")
500  end if
501  end function get_reduction_operator
502 end module reduction_inter_io_mod
logging_mod::log_error
integer, parameter, public log_error
Only log ERROR messages.
Definition: logging.F90:11
conversions_mod
Conversion between common inbuilt FORTRAN data types.
Definition: conversions.F90:5
collections_mod::map_type
Map data structure that holds string (length 20 maximum) key value pairs.
Definition: collections.F90:86
collections_mod::c_is_empty
Returns whether a collection is empty.
Definition: collections.F90:437
reduction_inter_io_mod::integrate_io_server_collective_values
subroutine integrate_io_server_collective_values(reduction_op, reduction_progress, single_server_values, number_elements, collective_values_empty)
Integrates the collective values from another IO server into the currently stored values.
Definition: reduction-inter-io.F90:239
reduction_inter_io_mod::clean_progress_mutex
integer, volatile clean_progress_mutex
Definition: reduction-inter-io.F90:39
reduction_inter_io_mod::perform_clean_every
integer, parameter perform_clean_every
Definition: reduction-inter-io.F90:28
reduction_inter_io_mod::inter_io_description_mutex
integer, volatile inter_io_description_mutex
Definition: reduction-inter-io.F90:39
reduction_inter_io_mod::my_inter_io_tag
integer, parameter my_inter_io_tag
Definition: reduction-inter-io.F90:28
reduction_inter_io_mod::previous_clean_reduction_count
integer, volatile previous_clean_reduction_count
Definition: reduction-inter-io.F90:39
reduction_inter_io_mod::init_reduction_inter_io
subroutine, public init_reduction_inter_io(io_configuration)
Initialises the reduction action.
Definition: reduction-inter-io.F90:51
forthread_mod::forthread_mutex_lock
integer function forthread_mutex_lock(mutex_id)
Definition: forthread.F90:284
reduction_inter_io_mod::handle_process_recv_from_other_io_server
subroutine handle_process_recv_from_other_io_server(io_configuration, inter_io_comm, myrank, data_buffer, number_io_servers)
Handles the data received from another IO server, locates the correct reduction progress,...
Definition: reduction-inter-io.F90:305
collections_mod::c_put_generic
Puts a generic key-value pair into the map.
Definition: collections.F90:305
mpi_communication_mod
Abstraction layer around MPI, this issues and marshals the lower level communication details.
Definition: mpicommunication.F90:2
reduction_inter_io_mod::check_reduction_inter_io_for_completion
logical function, public check_reduction_inter_io_for_completion(io_configuration)
Checks this action for completion, when all are completed then the IO server can shutdown as this is ...
Definition: reduction-inter-io.F90:83
forthread_mod::forthread_mutex_init
integer function forthread_mutex_init(mutex_id, attr_id)
Definition: forthread.F90:274
collections_mod
Collection data structures.
Definition: collections.F90:7
reduction_inter_io_mod::initialised
logical, volatile initialised
Definition: reduction-inter-io.F90:42
collections_mod::c_get_string
Gets a specific string element out of the list, stack, queue or map with the corresponding key.
Definition: collections.F90:388
reduction_inter_io_mod::perform_inter_io_reduction
subroutine, public perform_inter_io_reduction(io_configuration, field_values, field_size, reduction_field_name, reduction_op, root, timestep, completion_procedure)
Actually handles the processing for this data wrt the vertical reduction.
Definition: reduction-inter-io.F90:127
reduction_inter_io_mod::min
integer, parameter min
Definition: reduction-inter-io.F90:27
collections_mod::c_has_next
Definition: collections.F90:586
reduction_inter_io_mod::reduction_count_mutex
integer, volatile reduction_count_mutex
Definition: reduction-inter-io.F90:39
reduction_inter_io_mod::handle_local_moncs_completed_collective
subroutine handle_local_moncs_completed_collective(io_configuration, reduction_progress)
Handles the case where the local MONC processes have completed their collective operation for a speci...
Definition: reduction-inter-io.F90:273
collections_mod::hashmap_type
A hashmap structure, the same as a map but uses hashing for greatly improved performance when storing...
Definition: collections.F90:94
forthread_mod
Definition: forthread.F90:1
inter_io_specifics_mod
Inter IO server communication specific functionality. This manages all of the communication that migh...
Definition: inter-io-specifics.F90:3
reduction_inter_io_mod::handle_recv_data_from_io_server
subroutine handle_recv_data_from_io_server(io_configuration, data_buffer, inter_io_index)
Handles the receiving of data from some other IO server. This is issued call back style within a thre...
Definition: reduction-inter-io.F90:70
logging_mod::log_log
subroutine, public log_log(level, message, str)
Logs a message at the specified level. If the level is above the current level then the message is ig...
Definition: logging.F90:75
forthread_mod::forthread_rwlock_destroy
integer function forthread_rwlock_destroy(rwlock_id)
Definition: forthread.F90:495
mpi_communication_mod::lock_mpi
subroutine, public lock_mpi()
If we are explicitly managing MPI thread safety (SERIALIZED mode) then locks MPI.
Definition: mpicommunication.F90:58
inter_io_specifics_mod::package_inter_io_communication_message
character function, dimension(:), allocatable, public package_inter_io_communication_message(field_name, timestep, field_values, other_int)
Packages up fields into an io binary message (allocated here) which is used for sending.
Definition: inter-io-specifics.F90:84
forthread_mod::forthread_mutex_destroy
integer function forthread_mutex_destroy(mutex_id)
Definition: forthread.F90:265
mpi_communication_mod::wait_for_mpi_request
subroutine, public wait_for_mpi_request(request, status)
Waits for a specific MPI request to complete, either by managing thread safety and interleaving or ju...
Definition: mpicommunication.F90:75
collections_mod::mapentry_type
Definition: collections.F90:46
threadpool_mod::threadpool_start_thread
subroutine, public threadpool_start_thread(proc, arguments, data_buffer)
Starts an idle thread from the pool to execute a specific procedure with some data....
Definition: threadpool.F90:102
collections_mod::c_get_generic
Gets a specific generic element out of the list, stack, queue or map with the corresponding key.
Definition: collections.F90:367
collections_mod::c_generic_at
Retrieves the generic value held at the specific map index or null if index > map elements.
Definition: collections.F90:467
collections_mod::c_contains
Determines whether or not a map contains a specific key.
Definition: collections.F90:447
reduction_inter_io_mod::handle_collective_completed
subroutine handle_collective_completed(io_configuration, reduction_progress)
Handles the situation where collective communication for a specific reduction has completed across al...
Definition: reduction-inter-io.F90:339
threadpool_mod
This is a thread pool and the single management "main" thread will spawn out free threads in the pool...
Definition: threadpool.F90:5
reduction_inter_io_mod::sum
integer, parameter sum
Definition: reduction-inter-io.F90:27
reduction_inter_io_mod::my_inter_io_name
character(len= *), parameter my_inter_io_name
Definition: reduction-inter-io.F90:29
threadpool_mod::check_thread_status
subroutine, public check_thread_status(ierr)
Checks the error status of any thread operation and reports an error if it failed.
Definition: threadpool.F90:229
conversions_mod::conv_to_string
Converts data types to strings.
Definition: conversions.F90:38
forthread_mod::forthread_rwlock_trywrlock
integer function forthread_rwlock_trywrlock(lock_id)
Definition: forthread.F90:541
reduction_inter_io_mod::reduction_progresses
type(hashmap_type), volatile reduction_progresses
Definition: reduction-inter-io.F90:41
collections_mod::iterator_type
Definition: collections.F90:51
reduction_inter_io_mod::generate_reduction_key
character(len=string_length) function generate_reduction_key(field_name, timestep, reduction_operator)
Generates the lookup key that is used for the map storage of reduction progresses.
Definition: reduction-inter-io.F90:456
reduction_inter_io_mod
Reduction inter IO action which will perform reductions between IO servers. This is not as trivial as...
Definition: reduction-inter-io.F90:4
forthread_mod::forthread_rwlock_init
integer function forthread_rwlock_init(rwlock_id, attr_id)
Definition: forthread.F90:504
configuration_parser_mod::io_configuration_type
Overall IO configuration.
Definition: configurationparser.F90:104
inter_io_specifics_mod::register_inter_io_communication
subroutine, public register_inter_io_communication(io_configuration, message_tag, handling_procedure, name)
Registers an inter IO communication operation.
Definition: inter-io-specifics.F90:39
collections_mod::c_free
Frees up all the allocatable, heap, memory associated with a list, stack, queue or map.
Definition: collections.F90:577
reduction_inter_io_mod::reduction_count
integer, volatile reduction_count
Definition: reduction-inter-io.F90:39
reduction_inter_io_mod::check_and_clean_progress
logical function check_and_clean_progress(myrank)
Checks all the reduction progresses and will remove any that have completed. This is designed to be c...
Definition: reduction-inter-io.F90:175
reduction_inter_io_mod::reduction_progress_type
Definition: reduction-inter-io.F90:31
logging_mod
Logging utility.
Definition: logging.F90:2
forthread_mod::forthread_mutex_trylock
integer function forthread_mutex_trylock(mutex_id)
Definition: forthread.F90:293
datadefn_mod::double_precision
integer, parameter, public double_precision
Double precision (64 bit) kind.
Definition: datadefn.F90:14
reduction_inter_io_mod::reduction_progress_rwlock
integer, volatile reduction_progress_rwlock
Definition: reduction-inter-io.F90:39
datadefn_mod
Contains common definitions for the data and datatypes used by MONC.
Definition: datadefn.F90:2
reduction_inter_io_mod::finalise_reduction_inter_io
subroutine, public finalise_reduction_inter_io(io_configuration)
Finalises the reduction action, waiting for all outstanding requests and then freeing data.
Definition: reduction-inter-io.F90:91
inter_io_specifics_mod::find_inter_io_from_name
integer function, public find_inter_io_from_name(io_configuration, name)
Locates a the index of an inter IO entry from the operator name or returns 0 if none is found.
Definition: inter-io-specifics.F90:63
datadefn_mod::string_length
integer, parameter, public string_length
Default length of strings.
Definition: datadefn.F90:10
forthread_mod::forthread_mutex_unlock
integer function forthread_mutex_unlock(mutex_id)
Definition: forthread.F90:302
collections_mod::c_get_iterator
Definition: collections.F90:581
inter_io_specifics_mod::unpackage_inter_io_communication_message
subroutine, public unpackage_inter_io_communication_message(data_buffer, field_name, timestep, field_values, other_int)
Unpackages some binary data into its individual fields. The field values are allocated here and the s...
Definition: inter-io-specifics.F90:110
collections_mod::list_type
List data structure which implements a doubly linked list. This list will preserve its order.
Definition: collections.F90:60
reduction_inter_io_mod::mean
integer, parameter mean
Definition: reduction-inter-io.F90:27
reduction_inter_io_mod::remove_reduction_progress
subroutine remove_reduction_progress(reduction_progress)
Removes a specific reduction progress.
Definition: reduction-inter-io.F90:437
reduction_inter_io_mod::retrieve_reduction_progress
type(reduction_progress_type) function, pointer retrieve_reduction_progress(mapentry)
Helper function to retrieve the reduction progress from a mapentry.
Definition: reduction-inter-io.F90:466
mpi_communication_mod::unlock_mpi
subroutine, public unlock_mpi()
If we are explicitly managing MPI thread safety (SERIALIZED mode) then unlocks MPI.
Definition: mpicommunication.F90:63
collections_mod::c_remove
Removes a specific element from the list or map.
Definition: collections.F90:419
collections_mod::c_next_string
Definition: collections.F90:594
forthread_mod::forthread_rwlock_wrlock
integer function forthread_rwlock_wrlock(lock_id)
Definition: forthread.F90:532
collections_mod::c_next_mapentry
Definition: collections.F90:606
forthread_mod::forthread_rwlock_rdlock
integer function forthread_rwlock_rdlock(lock_id)
Definition: forthread.F90:514
reduction_inter_io_mod::get_reduction_operator
integer function, public get_reduction_operator(op_string)
Given the map of action attributes this procedure will identify the reduction operator that has been ...
Definition: reduction-inter-io.F90:488
reduction_inter_io_mod::find_reduction_progress
type(reduction_progress_type) function, pointer find_reduction_progress(timestep, reduction_operator, field_name, issue_read_lock)
Locates a specific reduction progress based upon the timestep, operator and field name.
Definition: reduction-inter-io.F90:407
collections_mod::c_add_string
Adds a string to the end of the list.
Definition: collections.F90:222
reduction_inter_io_mod::clean_progress
subroutine clean_progress(myrank)
Definition: reduction-inter-io.F90:155
configuration_parser_mod
Parses the XML configuration file to produce the io configuration description which contains the data...
Definition: configurationparser.F90:3
reduction_inter_io_mod::find_or_add_reduction_progress
type(reduction_progress_type) function, pointer find_or_add_reduction_progress(timestep, reduction_operator, root, field_name, completion_procedure)
Finds or adds a specific reduction progress based upon the timestep and reduction operator....
Definition: reduction-inter-io.F90:361
forthread_mod::forthread_rwlock_unlock
integer function forthread_rwlock_unlock(lock_id)
Definition: forthread.F90:550
inter_io_specifics_mod::handle_completion
Definition: inter-io-specifics.F90:18
reduction_inter_io_mod::max
integer, parameter max
Definition: reduction-inter-io.F90:27
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
configuration_parser_mod::io_configuration_inter_communication_description
Definition: configurationparser.F90:66