MONC
ioserver.F90
Go to the documentation of this file.
1 
11 
38  use mpi, only : mpi_comm_world, mpi_statuses_ignore, mpi_byte
40  implicit none
41 
42 #ifndef TEST_MODE
43  private
44 #endif
45 
46  integer :: mpi_type_data_sizing_description, & !< The MPI type for field sizing (i.e. array size etc send when MONCs register)
47  mpi_type_definition_description, & !< The MPI data type for data descriptions sent to MONCs
49  type(io_configuration_type), volatile, save :: io_configuration
50  logical, volatile :: contine_poll_messages, & !< Whether to continue waiting command messages from any MONC processes
53  type(field_description_type), dimension(:), allocatable :: registree_field_descriptions
55 
56  integer, volatile :: monc_registration_lock
57 
58  public io_server_run
59 contains
60 
66  subroutine io_server_run(options_database, io_communicator_arg, &
67  provided_threading, total_global_processes, continuation_run, io_configuration_file)
68  type(hashmap_type), intent(inout) :: options_database
69  integer, intent(in) :: io_communicator_arg, provided_threading, total_global_processes
70  logical, intent(in) :: continuation_run
71  character(len=LONG_STRING_LENGTH), intent(in) :: io_configuration_file
72 
73  integer :: command, source, my_rank, ierr
74  character, dimension(:), allocatable :: data_buffer, io_xml_configuration
75  type(hashmap_type) :: diagnostic_generation_frequency
76 
77 
78  if (continuation_run) then
79  ! Handle case where we need to allocate this due to no IO server config
80  call read_io_server_configuration(options_get_string(options_database, "checkpoint"), &
81  io_xml_configuration, io_communicator_arg)
82  end if
83 
84  if (.not. allocated(io_xml_configuration)) then
85  io_xml_configuration=get_io_xml(io_configuration_file)
86  if (continuation_run) then
87  call mpi_comm_rank(io_communicator_arg, my_rank, ierr)
88  if (my_rank == 0) then
89  call log_log(log_warn, "No IO server configuration in checkpoint file - starting from XML provided file instead")
90  end if
91  end if
92  end if
93 
94  call check_for_condi_conflict(io_xml_configuration, options_database)
95  call configuration_parse(options_database, io_xml_configuration, io_configuration)
96  deallocate(io_xml_configuration)
98  call initialise_mpi_communication(provided_threading)
100  call check_thread_status(forthread_mutex_init(io_configuration%general_info_mutex, -1))
102  contine_poll_messages=.true.
105  io_configuration%io_communicator=io_communicator_arg
106  io_configuration%number_of_io_servers=get_number_io_servers(io_communicator_arg)
107  io_configuration%number_of_global_moncs=total_global_processes-io_configuration%number_of_io_servers
108  io_configuration%my_io_rank=get_my_io_rank(io_communicator_arg)
109  call initialise_logging(io_configuration%my_io_rank)
112  diagnostic_generation_frequency=initialise_diagnostic_federator(io_configuration)
113  call initialise_writer_federator(io_configuration, diagnostic_generation_frequency, continuation_run)
114  call c_free(diagnostic_generation_frequency)
115  call initialise_writer_field_manager(io_configuration, continuation_run)
116 
120 
122 
123  do while (await_command(command, source, data_buffer))
124  call handle_command_message(command, source, data_buffer)
125  end do
126  call threadpool_deactivate()
132  call cancel_requests()
136  call threadpool_finalise()
137  end subroutine io_server_run
138 
145  subroutine check_for_condi_conflict(raw_contents, options_database)
146  character, dimension(:), intent(in) :: raw_contents
147  type(hashmap_type), intent(inout) :: options_database
148  character(len=size(raw_contents)) :: string_to_process
149  integer :: i
150 
151  if (.not. options_get_logical(options_database, "conditional_diagnostics_column_enabled")) then
152  do i=1, size(raw_contents)
153  string_to_process(i:i)=raw_contents(i)
154  end do
155  if (index(string_to_process,"CondDiags_") .ne. 0) then
156  call log_log(log_error, &
157  "Conditional diagnostics are DISABLED but requested via xml. Enable or remove request to resolve.")
158  end if
159  end if
160  end subroutine check_for_condi_conflict
161 
166  logical function await_command(command, source, data_buffer)
167  integer, intent(out) :: command, source
168  character, dimension(:), allocatable :: data_buffer
169 
170  logical :: completed, inter_io_complete
171 
172  completed=.false.
173  await_command=.false.
174  do while(.not. completed)
175  if (.not. contine_poll_messages .and. .not. contine_poll_interio_messages) return
176  if (contine_poll_messages) then
177  if (test_for_command(command, source)) then
178  await_command=.true.
179  return
180  end if
181  end if
182  if (contine_poll_interio_messages .and. allocated(io_configuration%inter_io_communications)) then
183  inter_io_complete=test_for_inter_io(io_configuration%inter_io_communications, &
184  io_configuration%number_inter_io_communications, io_configuration%io_communicator, command, source, data_buffer)
185  if (inter_io_complete) then
186  await_command=.true.
187  return
188  end if
189  end if
190  if (.not. contine_poll_messages .and. .not. already_registered_finishing_call) then
194  end if
195  end if
196  if (.not. completed) call pause_for_mpi_interleaving()
197  end do
198  end function await_command
199 
206  subroutine termination_callback(io_configuration, values, field_name, timestep)
207  type(io_configuration_type), intent(inout) :: io_configuration
208  real(DEFAULT_PRECISION), dimension(:) :: values
209  character(len=STRING_LENGTH) :: field_name
210  integer :: timestep
211 
213  end subroutine termination_callback
214 
218  subroutine handle_command_message(command, source, data_buffer)
219  integer, intent(in) :: command, source
220  character, dimension(:), allocatable, intent(inout) :: data_buffer
221 
222  if (command == register_command) then
224  else if (command == deregister_command) then
226  else if (command == inter_io_communication) then
227  call threadpool_start_thread(handle_inter_io_communication_command, (/ source /), data_buffer=data_buffer)
228  deallocate(data_buffer)
229  else if (command .ge. data_command_start) then
231  end if
232  end subroutine handle_command_message
233 
236  subroutine handle_inter_io_communication_command(arguments, data_buffer)
237  integer, dimension(:), intent(in) :: arguments
238  character, dimension(:), allocatable, intent(inout), optional :: data_buffer
239 
240  integer :: source
241 
242  source=arguments(1)
243 
244  call io_configuration%inter_io_communications(source)%handling_procedure(io_configuration, data_buffer, source)
246 
251  integer :: i, specific_monc_data_type
252  type(iterator_type) :: types_iterator
253 
254  do i=1, size(io_configuration%registered_moncs)
255  types_iterator=c_get_iterator(io_configuration%registered_moncs(i)%registered_monc_types)
256  do while (c_has_next(types_iterator))
257  specific_monc_data_type=c_get_integer(c_next_mapentry(types_iterator))
258  call free_mpi_type(specific_monc_data_type)
259  end do
260  if (allocated(io_configuration%registered_moncs(i)%field_start_locations)) &
261  deallocate(io_configuration%registered_moncs(i)%field_start_locations)
262  if (allocated(io_configuration%registered_moncs(i)%field_end_locations)) &
263  deallocate(io_configuration%registered_moncs(i)%field_end_locations)
264  if (allocated(io_configuration%registered_moncs(i)%definition_names)) &
265  deallocate(io_configuration%registered_moncs(i)%definition_names)
266  if (allocated(io_configuration%registered_moncs(i)%dimensions)) deallocate(io_configuration%registered_moncs(i)%dimensions)
267  end do
269 
272  subroutine handle_deregistration_command(arguments, data_buffer)
273  integer, dimension(:), intent(in) :: arguments
274  character, dimension(:), allocatable, intent(inout), optional :: data_buffer
275 
276  integer :: monc_location, source
277 
278  source=arguments(1)
279  monc_location=get_monc_location(io_configuration, source)
280  call check_thread_status(forthread_mutex_lock(io_configuration%registered_moncs(monc_location)%active_mutex))
281  do while (io_configuration%registered_moncs(monc_location)%active_threads .gt. 0)
282  call check_thread_status(forthread_cond_wait(io_configuration%registered_moncs(monc_location)%deactivate_condition_variable,&
283  io_configuration%registered_moncs(monc_location)%active_mutex))
284  end do
285  call check_thread_status(forthread_mutex_unlock(io_configuration%registered_moncs(monc_location)%active_mutex))
287  io_configuration%active_moncs=io_configuration%active_moncs-1
288  if (io_configuration%active_moncs==0) contine_poll_messages=.false.
290  end subroutine handle_deregistration_command
291 
296  subroutine pull_back_data_message_and_handle(source, data_set)
297  integer, intent(in) :: source, data_set
298 
299  integer :: specific_monc_data_type, specific_monc_buffer_size, recv_count, monc_location
300  character, dimension(:), allocatable :: data_buffer
301 
303  monc_location=get_monc_location(io_configuration, source)
304 
305  specific_monc_data_type=c_get_integer(io_configuration%registered_moncs(monc_location)%registered_monc_types, &
306  conv_to_string(data_set))
307  specific_monc_buffer_size=c_get_integer(io_configuration%registered_moncs(monc_location)%registered_monc_buffer_sizes, &
308  conv_to_string(data_set))
309 
310  allocate(data_buffer(specific_monc_buffer_size))
311  recv_count=data_receive(specific_monc_data_type, 1, source, dump_data=data_buffer, data_dump_id=data_set)
312 
314  call threadpool_start_thread(handle_data_message, (/ source, data_set /), data_buffer=data_buffer)
315  deallocate(data_buffer)
316  end subroutine pull_back_data_message_and_handle
317 
322  subroutine handle_data_message(arguments, data_buffer)
323  integer, dimension(:), intent(in) :: arguments
324  character, dimension(:), allocatable, intent(inout), optional :: data_buffer
325 
326  integer :: monc_location, data_set, source, matched_datadefn_index
327 
328  source=arguments(1)
329  data_set=arguments(2)
330 
332  monc_location=get_monc_location(io_configuration, source)
333 
334  call check_thread_status(forthread_mutex_lock(io_configuration%registered_moncs(monc_location)%active_mutex))
335  io_configuration%registered_moncs(monc_location)%active_threads=&
336  io_configuration%registered_moncs(monc_location)%active_threads+1
337  call check_thread_status(forthread_mutex_unlock(io_configuration%registered_moncs(monc_location)%active_mutex))
338 
339  matched_datadefn_index=retrieve_data_definition(io_configuration, &
340  io_configuration%registered_moncs(monc_location)%definition_names(data_set))
341 
342  if (matched_datadefn_index .gt. 0) then
343  call inform_writer_federator_time_point(io_configuration, source, data_set, data_buffer)
344  call pass_fields_to_diagnostics_federator(io_configuration, source, data_set, data_buffer)
345  call provide_monc_data_to_writer_federator(io_configuration, source, data_set, data_buffer)
346  call check_writer_for_trigger(io_configuration, source, data_set, data_buffer)
347  else
348  call log_log(log_warn, "IO server can not find matching data definition with name "&
349  //io_configuration%registered_moncs(monc_location)%definition_names(data_set))
350  end if
351 
352  call check_thread_status(forthread_mutex_lock(io_configuration%registered_moncs(monc_location)%active_mutex))
353  io_configuration%registered_moncs(monc_location)%active_threads=&
354  io_configuration%registered_moncs(monc_location)%active_threads-1
355  call check_thread_status(forthread_cond_signal(io_configuration%registered_moncs(monc_location)%deactivate_condition_variable))
356  call check_thread_status(forthread_mutex_unlock(io_configuration%registered_moncs(monc_location)%active_mutex))
358  end subroutine handle_data_message
359 
364  subroutine handle_monc_registration(arguments, data_buffer)
365  integer, dimension(:), intent(in) :: arguments
366  character, dimension(:), allocatable, intent(inout), optional :: data_buffer
367 
368  integer :: configuration_send_request(2), ierr, number_data_definitions, this_monc_index, source
369 
370  source=arguments(1)
371  configuration_send_request=send_configuration_to_registree(source)
372  number_data_definitions=io_configuration%number_of_data_definitions
373 
375 
376  io_configuration%number_of_moncs=io_configuration%number_of_moncs+1
377  this_monc_index=io_configuration%number_of_moncs
378  if (io_configuration%number_of_moncs .gt. size(io_configuration%registered_moncs)) then
379  call log_log(log_error, "You have a high ratio of computational cores to IO servers, the limit is currently 100")
380  ! The extension of the MONC registration array is broken as the pointers involved in the map does not get copied across
381  ! we could manually do this, but that is for another day! If you need to extend these limits either increase the constants
382  ! or fix the extension, I don't think it will be too hard to fix the extension bit (copy the maps manually)
384  end if
385 
386  io_configuration%active_moncs=io_configuration%active_moncs+1
388 
389  call c_put_integer(io_configuration%monc_to_index, conv_to_string(source), this_monc_index)
390 
391  call check_thread_status(forthread_mutex_init(io_configuration%registered_moncs(this_monc_index)%active_mutex, -1))
393  io_configuration%registered_moncs(this_monc_index)%deactivate_condition_variable, -1))
394  io_configuration%registered_moncs(this_monc_index)%active_threads=0
395  io_configuration%registered_moncs(this_monc_index)%source_id=source
396 
397  allocate(io_configuration%registered_moncs(this_monc_index)%field_start_locations(number_data_definitions), &
398  io_configuration%registered_moncs(this_monc_index)%field_end_locations(number_data_definitions), &
399  io_configuration%registered_moncs(this_monc_index)%definition_names(number_data_definitions), &
400  io_configuration%registered_moncs(this_monc_index)%dimensions(number_data_definitions))
401 
402  ! Wait for configuration to have been sent to registree
403  call waitall_for_mpi_requests(configuration_send_request, 2)
404  call init_data_definition(source, io_configuration%registered_moncs(this_monc_index))
405  end subroutine handle_monc_registration
406 
411  integer, intent(in) :: source
412  integer :: send_configuration_to_registree(2)
413 
414  integer :: ierr, srequest(2)
415 
416  call lock_mpi()
418  source, data_tag, mpi_comm_world, srequest(1), ierr)
420  source, data_tag, mpi_comm_world, srequest(2), ierr)
421  call unlock_mpi()
422 
424  end function send_configuration_to_registree
425 
433  subroutine init_data_definition(source, monc_defn)
434  integer, intent(in) :: source
435  type(io_configuration_registered_monc_type), intent(inout) :: monc_defn
436 
437  type(data_sizing_description_type) :: data_description(io_configuration%number_of_distinct_data_fields+4)
438  integer :: created_mpi_type, data_size, recv_count, i
439  type(data_sizing_description_type) :: field_description
440  logical :: field_found
441 
442  recv_count=data_receive(mpi_type_data_sizing_description, io_configuration%number_of_distinct_data_fields+4, &
443  source, description_data=data_description)
444 
445  call handle_monc_dimension_information(data_description, monc_defn)
446 
447  do i=1, io_configuration%number_of_data_definitions
448  created_mpi_type=build_mpi_datatype(io_configuration%data_definitions(i), data_description, data_size, &
449  monc_defn%field_start_locations(i), monc_defn%field_end_locations(i), monc_defn%dimensions(i))
450 
451  call c_put_integer(monc_defn%registered_monc_types, conv_to_string(i), created_mpi_type)
452  call c_put_integer(monc_defn%registered_monc_buffer_sizes, conv_to_string(i), data_size)
453 
454  monc_defn%definition_names(i)=io_configuration%data_definitions(i)%name
455  end do
456  if (.not. initialised_present_data) then
458  field_found=get_data_description_from_name(data_description, number_q_indicies_key, field_description)
459  call c_put_integer(io_configuration%dimension_sizing, "active_q_indicies", field_description%dim_sizes(1))
460  call register_present_field_names_to_federators(data_description, recv_count)
461  end if
462  call get_monc_information_data(source)
463  end subroutine init_data_definition
464 
468  subroutine get_monc_information_data(source)
469  integer, intent(in) :: source
470 
471  character, dimension(:), allocatable :: buffer
472  character(len=STRING_LENGTH) :: q_field_name, cd_field_name
473  integer :: buffer_size, z_size, num_q_fields, n, current_point, recv_count
474  type(data_sizing_description_type) :: field_description
475  real(kind=default_precision) :: dreal
476  logical :: field_found
477 
478 
479  z_size=c_get_integer(io_configuration%dimension_sizing, "z")
480  num_q_fields=c_get_integer(io_configuration%dimension_sizing, "qfields")
481 
482  buffer_size=(kind(dreal)*z_size)*2 + (string_length * num_q_fields) &
484  allocate(buffer(buffer_size))
485  recv_count=data_receive(mpi_byte, buffer_size, source, buffer)
486  if (.not. io_configuration%general_info_set) then
488  if (.not. io_configuration%general_info_set) then
489  io_configuration%general_info_set=.true.
490  allocate(io_configuration%zn_field(z_size))
491  allocate(io_configuration%z_field(z_size))
492  io_configuration%zn_field=transfer(buffer(1:kind(dreal)*z_size), io_configuration%zn_field)
493  current_point=(kind(dreal)*z_size)
494  if (num_q_fields .gt. 0) then
495  do n=1, num_q_fields
496  q_field_name=transfer(buffer(current_point+1:current_point+string_length), q_field_name)
497  current_point=current_point+string_length
498  call replace_character(q_field_name, " ", "_")
499  call c_add_string(io_configuration%q_field_names, q_field_name)
500  end do
501  end if
502  io_configuration%z_field=transfer(buffer(current_point+1:current_point+kind(dreal)*z_size), &
503  io_configuration%z_field)
504  current_point=current_point+(kind(dreal)*z_size)
505 
506  do n=1,ncond
507  cond_request(n)=transfer(buffer(current_point+1:current_point+string_length), cd_field_name)
508  current_point=current_point+string_length
509  cond_long(n)=transfer(buffer(current_point+1:current_point+string_length), cd_field_name)
510  current_point=current_point+string_length
511  end do
512  do n=1,ndiag
513  diag_request(n)=transfer(buffer(current_point+1:current_point+string_length), cd_field_name)
514  current_point=current_point+string_length
515  diag_long(n)=transfer(buffer(current_point+1:current_point+string_length), cd_field_name)
516  current_point=current_point+string_length
517  end do
518 
519  end if
522  end if
523  deallocate(buffer)
524  end subroutine get_monc_information_data
525 
531  subroutine register_present_field_names_to_federators(data_description, recv_count)
532  type(data_sizing_description_type), dimension(:), intent(in) :: data_description
533  integer, intent(in) :: recv_count
534 
535  type(hashset_type) :: present_field_names
536  type(hashmap_type) :: diagnostics_field_names_and_roots
537  integer :: i, j
538 
539  do i=1, recv_count
540  call c_add_string(present_field_names, data_description(i)%field_name)
541  end do
542  do i=1, io_configuration%number_of_data_definitions
543  do j=1, io_configuration%data_definitions(i)%number_of_data_fields
544  if (io_configuration%data_definitions(i)%fields(j)%field_type == scalar_field_type .and. .not. &
545  io_configuration%data_definitions(i)%fields(j)%optional) then
546  call c_add_string(present_field_names, io_configuration%data_definitions(i)%fields(j)%name)
547  end if
548  end do
549  end do
550  call c_add_string(present_field_names, "time")
551  call c_add_string(present_field_names, "timestep")
553  diagnostics_field_names_and_roots=determine_diagnostics_fields_available(present_field_names)
554  call inform_writer_federator_fields_present(io_configuration, diag_field_names_and_roots=diagnostics_field_names_and_roots)
555  call c_free(present_field_names)
556  call c_free(diagnostics_field_names_and_roots)
558 
562  subroutine handle_monc_dimension_information(data_description, monc_defn)
563  type(io_configuration_registered_monc_type), intent(inout) :: monc_defn
564  type(data_sizing_description_type), dimension(:) :: data_description
565 
566  type(data_sizing_description_type) :: field_description
567  integer :: i
568  logical :: field_found
569 
570  field_found=get_data_description_from_name(data_description, local_sizes_key, field_description)
571  if (.not. field_found) call log_log(log_error, "Malformed MONC registration, no local size information")
572  do i=1,3
573  monc_defn%local_dim_sizes(i)=field_description%dim_sizes(i)
574  end do
575  field_found=get_data_description_from_name(data_description, local_start_points_key, field_description)
576  if (.not. field_found) call log_log(log_error, "Malformed MONC registration, no local start point information")
577  do i=1,3
578  monc_defn%local_dim_starts(i)=field_description%dim_sizes(i)
579  end do
580  field_found=get_data_description_from_name(data_description, local_end_points_key, field_description)
581  if (.not. field_found) call log_log(log_error, "Malformed MONC registration, no local end point information")
582  do i=1,3
583  monc_defn%local_dim_ends(i)=field_description%dim_sizes(i)
584  end do
585  end subroutine handle_monc_dimension_information
586 end module io_server_mod
mpi_communication_mod::get_my_io_rank
integer function, public get_my_io_rank(io_comm)
Retrieves my IO server rank out of the number of IO servers that are running.
Definition: mpicommunication.F90:140
logging_mod::log_error
integer, parameter, public log_error
Only log ERROR messages.
Definition: logging.F90:11
global_callback_inter_io_mod
Global callback inter IO, which registers the callback with identifiers and then the procedure is act...
Definition: global-callback.F90:3
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
io_server_client_mod::number_q_indicies_key
character(len=string_length), parameter, public number_q_indicies_key
Definition: ioclient.F90:43
collections_mod::c_is_empty
Returns whether a collection is empty.
Definition: collections.F90:437
configuration_parser_mod::cond_request
character(len=string_length), dimension(:), allocatable, public cond_request
Definition: configurationparser.F90:147
io_server_client_mod::register_command
integer, parameter, public register_command
Definition: ioclient.F90:34
io_server_state_reader_mod
Reads the IO server state that was stored in a NetCDF checkpoint file.
Definition: io_state_reader.F90:2
mpi_communication_mod::register_command_receive
subroutine, public register_command_receive()
Registers a request for receiving a command from any MONC process on the command channel.
Definition: mpicommunication.F90:150
logging_mod::initialise_logging
subroutine, public initialise_logging(pid)
Initialises the logging. This is done to make it easier for master logging only, so that we don't hav...
Definition: logging.F90:37
io_server_mod::registree_field_descriptions
type(field_description_type), dimension(:), allocatable registree_field_descriptions
Definition: ioserver.F90:53
forthread_mod::forthread_mutex_lock
integer function forthread_mutex_lock(mutex_id)
Definition: forthread.F90:284
mpi_communication_mod::waitall_for_mpi_requests
subroutine, public waitall_for_mpi_requests(requests, count)
Waits for all MPI requests to complete, either by managing thread safety and interleaving or just a c...
Definition: mpicommunication.F90:106
io_server_client_mod::deregister_command
integer, parameter, public deregister_command
Definition: ioclient.F90:34
logging_mod::log_warn
integer, parameter, public log_warn
Log WARNING and ERROR messages.
Definition: logging.F90:12
writer_field_manager_mod::provide_monc_data_to_writer_federator
subroutine, public provide_monc_data_to_writer_federator(io_configuration, source, data_id, data_dump)
Data communicated from MONC is provided to this write federator and then included if the configuratio...
Definition: writer_field_manager.F90:110
io_server_client_mod::local_start_points_key
character(len=string_length), parameter, public local_start_points_key
Definition: ioclient.F90:43
io_server_mod::handle_command_message
subroutine handle_command_message(command, source, data_buffer)
Called to handle a specific command that has been recieved.
Definition: ioserver.F90:219
io_server_mod::send_configuration_to_registree
integer function, dimension(2) send_configuration_to_registree(source)
Sends the data and field descriptions to the MONC process that just registered with the IO server.
Definition: ioserver.F90:411
io_server_mod::mpi_type_field_description
integer mpi_type_field_description
The MPI data type for field descriptions sent to MONCs.
Definition: ioserver.F90:46
io_server_client_mod::field_description_type
Definition: ioclient.F90:21
configuration_parser_mod::diag_long
character(len=string_length), dimension(:), allocatable, public diag_long
Definition: configurationparser.F90:147
mpi_communication_mod
Abstraction layer around MPI, this issues and marshals the lower level communication details.
Definition: mpicommunication.F90:2
io_server_client_mod::build_mpi_type_definition_description
integer function, public build_mpi_type_definition_description()
Builds the MPI data type for sending data descriptions to registree MONCs.
Definition: ioclient.F90:76
io_server_mod
The main IO server functionality which handles waiting for commands and data both of which are delt w...
Definition: ioserver.F90:5
writer_field_manager_mod::finalise_writer_field_manager
subroutine, public finalise_writer_field_manager()
Finalises the writer field manager.
Definition: writer_field_manager.F90:72
io_server_mod::initialised_present_data
logical, volatile initialised_present_data
Definition: ioserver.F90:50
threadpool_mod::threadpool_is_idle
logical function, public threadpool_is_idle()
Determines whether the thread pool is idle or not (i.e. all threads are idle and waiting for work)
Definition: threadpool.F90:164
writer_federator_mod
This federates over the writing of diagnostic and prognostic data to the file system....
Definition: writer_federator.F90:3
global_callback_inter_io_mod::perform_global_callback
subroutine, public perform_global_callback(io_configuration, field_name, timestep, completion_procedure)
Performs a global callback.
Definition: global-callback.F90:39
forthread_mod::forthread_mutex_init
integer function forthread_mutex_init(mutex_id, attr_id)
Definition: forthread.F90:274
writer_field_manager_mod
The writer field manager will manage aspects of the fields being provided to the writer federator....
Definition: writer_field_manager.F90:5
collections_mod
Collection data structures.
Definition: collections.F90:7
io_server_mod::handle_monc_dimension_information
subroutine handle_monc_dimension_information(data_description, monc_defn)
Handles the provided local MONC dimension and data layout information.
Definition: ioserver.F90:563
collections_mod::c_has_next
Definition: collections.F90:586
io_server_state_reader_mod::read_io_server_configuration
subroutine, public read_io_server_configuration(checkpoint_filename, io_xml_configuration, io_communicator_arg)
Reads the IO server configuration, which is the XML configuration initially run with and stored in th...
Definition: io_state_reader.F90:72
configuration_parser_mod::diag_request
character(len=string_length), dimension(:), allocatable, public diag_request
Definition: configurationparser.F90:147
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
io_server_client_mod::scalar_field_type
integer, parameter, public scalar_field_type
Definition: ioclient.F90:38
io_server_mod::io_server_run
subroutine, public io_server_run(options_database, io_communicator_arg, provided_threading, total_global_processes, continuation_run, io_configuration_file)
Called to start the IO server and once this subroutine returns then it indicates that the IO server h...
Definition: ioserver.F90:68
string_utils_mod::replace_character
subroutine, public replace_character(str, src_char, tgt_char)
Replaces all occurances of a character in a string with another character.
Definition: string_utils.F90:17
forthread_mod
Definition: forthread.F90:1
io_server_mod::termination_callback
subroutine termination_callback(io_configuration, values, field_name, timestep)
This is the termination callback which is called once all MONCs have deregistered,...
Definition: ioserver.F90:207
mpi_communication_mod::pause_for_mpi_interleaving
subroutine, public pause_for_mpi_interleaving()
Pauses for a specific number of ms to allow for MPI interleaving, this is to avoid starvation.
Definition: mpicommunication.F90:68
configuration_parser_mod::ndiag
integer, public ndiag
Definition: configurationparser.F90:148
io_server_mod::handle_monc_registration
subroutine handle_monc_registration(arguments, data_buffer)
Handles registration from some MONC process. The source process sends some data description to this I...
Definition: ioserver.F90:365
io_server_mod::registree_definition_descriptions
type(definition_description_type), dimension(:), allocatable registree_definition_descriptions
Definition: ioserver.F90:54
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
diagnostic_federator_mod::finalise_diagnostic_federator
subroutine, public finalise_diagnostic_federator(io_configuration)
Finalises the diagnostics federator, waiting for all outstanding requests and then freeing data.
Definition: diagnostic_federator.F90:125
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
datadefn_mod::long_string_length
integer, parameter, public long_string_length
Length of longer strings.
Definition: datadefn.F90:11
configuration_parser_mod::data_size_stride
integer, parameter, public data_size_stride
Definition: configurationparser.F90:26
io_server_mod::contine_poll_messages
logical, volatile contine_poll_messages
Whether to continue waiting command messages from any MONC processes.
Definition: ioserver.F90:50
io_server_client_mod::build_mpi_type_field_description
integer function, public build_mpi_type_field_description()
Builds the MPI data type for sending field descriptions to registree MONCs.
Definition: ioclient.F90:108
io_server_mod::io_configuration
type(io_configuration_type), save, volatile io_configuration
Internal representation of the IO configuration.
Definition: ioserver.F90:49
configuration_parser_mod::io_configuration_data_definition_type
Configuration of a specific data definition.
Definition: configurationparser.F90:58
io_server_client_mod::data_tag
integer, parameter, public data_tag
Definition: ioclient.F90:34
io_server_client_mod
This defines some constants and procedures that are useful to the IO server and clients that call it....
Definition: ioclient.F90:3
io_server_mod::monc_registration_lock
integer, volatile monc_registration_lock
Definition: ioserver.F90:56
io_server_mod::free_individual_registered_monc_aspects
subroutine free_individual_registered_monc_aspects()
Frees up the memory associated with individual registered MONCs. This is done at the end for all MONC...
Definition: ioserver.F90:251
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
forthread_mod::forthread_rwlock_tryrdlock
integer function forthread_rwlock_tryrdlock(lock_id)
Definition: forthread.F90:523
diagnostic_federator_mod::pass_fields_to_diagnostics_federator
subroutine, public pass_fields_to_diagnostics_federator(io_configuration, source, data_id, data_dump)
Entry point into the diagnostics federator this runs the diagnostics, executing the defined rules bas...
Definition: diagnostic_federator.F90:192
optionsdatabase_mod::options_get_string
character(len=string_length) function, public options_get_string(options_database, key, index)
Retrieves a string value from the database that matches the provided key.
Definition: optionsdatabase.F90:280
io_server_mod::register_present_field_names_to_federators
subroutine register_present_field_names_to_federators(data_description, recv_count)
Registers with the writer federator the set of fields (prognostic and diagnostic) that are available,...
Definition: ioserver.F90:532
writer_federator_mod::inform_writer_federator_time_point
subroutine, public inform_writer_federator_time_point(io_configuration, source, data_id, data_dump)
Definition: writer_federator.F90:132
writer_federator_mod::initialise_writer_federator
subroutine, public initialise_writer_federator(io_configuration, diagnostic_generation_frequency, continuation_run)
Initialises the write federator and configures it based on the user configuration....
Definition: writer_federator.F90:58
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
mpi_communication_mod::initialise_mpi_communication
subroutine, public initialise_mpi_communication(provided_threading)
Initialises MPI communication.
Definition: mpicommunication.F90:46
io_server_client_mod::get_data_description_from_name
logical function, public get_data_description_from_name(descriptions, name, field_description)
Look up the data description that corresponds to a specific field keyed by its name.
Definition: ioclient.F90:355
io_server_client_mod::local_sizes_key
character(len=string_length), parameter, public local_sizes_key
Definition: ioclient.F90:43
collections_mod::c_integer_at
Retrieves the integer value held at the specific map index or null if index > map elements.
Definition: collections.F90:477
configuration_parser_mod::ncond
integer, public ncond
Definition: configurationparser.F90:148
diagnostic_federator_mod
This diagnostics federator will take in data fields sent from a MONC, perform operators on these as r...
Definition: diagnostic_federator.F90:3
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
io_server_mod::already_registered_finishing_call
logical, volatile already_registered_finishing_call
Definition: ioserver.F90:52
io_server_client_mod::data_command_start
integer, parameter, public data_command_start
Definition: ioclient.F90:34
configuration_parser_mod::configuration_parse
subroutine, public configuration_parse(provided_options_database, raw_configuration, parsed_configuration)
This will parse an XML string into the IO configuration.
Definition: configurationparser.F90:220
mpi_communication_mod::test_for_command
logical function, public test_for_command(command, source)
Tests for a command message based upon the request already registered.
Definition: mpicommunication.F90:219
conversions_mod::conv_to_string
Converts data types to strings.
Definition: conversions.F90:38
writer_federator_mod::inform_writer_federator_fields_present
subroutine, public inform_writer_federator_fields_present(io_configuration, field_names, diag_field_names_and_roots)
Informs the writer federator that specific fields are present and should be reflected in the diagnost...
Definition: writer_federator.F90:162
forthread_mod::forthread_cond_signal
integer function forthread_cond_signal(cond_id)
Definition: forthread.F90:394
mpi_communication_mod::test_for_inter_io
logical function, public test_for_inter_io(inter_io_communications, number_of_inter_io, io_communicator, command, source, data_buffer)
Tests for inter IO server communication.
Definition: mpicommunication.F90:244
collections_mod::iterator_type
Definition: collections.F90:51
configuration_parser_mod::extend_registered_moncs_array
subroutine, public extend_registered_moncs_array(io_configuration)
Extends the data definitions array from the current size to the current size + data size stride.
Definition: configurationparser.F90:1033
writer_federator_mod::provide_q_field_names_to_writer_federator
subroutine, public provide_q_field_names_to_writer_federator(q_provided_field_names)
Provides the Q field names to the write federator, this is required as on initialisation we don't kno...
Definition: writer_federator.F90:278
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
forthread_mod::forthread_cond_wait
integer function forthread_cond_wait(cond_id, mutex_id)
Definition: forthread.F90:376
collections_mod::c_put_integer
Puts an integer key-value pair into the map.
Definition: collections.F90:318
io_server_mod::contine_poll_interio_messages
logical, volatile contine_poll_interio_messages
Definition: ioserver.F90:52
mpi_communication_mod::free_mpi_type
subroutine, public free_mpi_type(the_type)
Frees an MPI type, used in clean up.
Definition: mpicommunication.F90:274
mpi_communication_mod::cancel_requests
subroutine, public cancel_requests()
Cancels all outstanding communication requests.
Definition: mpicommunication.F90:197
io_server_mod::handle_inter_io_communication_command
subroutine handle_inter_io_communication_command(arguments, data_buffer)
Handles inter IO server communications.
Definition: ioserver.F90:237
collections_mod::c_free
Frees up all the allocatable, heap, memory associated with a list, stack, queue or map.
Definition: collections.F90:577
writer_federator_mod::finalise_writer_federator
subroutine, public finalise_writer_federator()
Finalises the write federator and the manipulations.
Definition: writer_federator.F90:123
diagnostic_federator_mod::determine_diagnostics_fields_available
type(hashmap_type) function, public determine_diagnostics_fields_available(monc_field_names)
Determines the diagnostics fields that are available based upon the input MONC fields on registration...
Definition: diagnostic_federator.F90:142
io_server_client_mod::definition_description_type
Definition: ioclient.F90:27
optionsdatabase_mod::options_get_logical
logical function, public options_get_logical(options_database, key, index)
Retrieves a logical value from the database that matches the provided key.
Definition: optionsdatabase.F90:154
configuration_parser_mod::build_definition_description_type_from_configuration
type(definition_description_type) function, dimension(:), allocatable, public build_definition_description_type_from_configuration(io_configuration)
Builds up the data definition description type from the structured definitions in the IO configuratio...
Definition: configurationparser.F90:1090
io_server_mod::mpi_type_definition_description
integer mpi_type_definition_description
The MPI data type for data descriptions sent to MONCs.
Definition: ioserver.F90:46
io_server_mod::mpi_type_data_sizing_description
integer mpi_type_data_sizing_description
The MPI type for field sizing (i.e. array size etc send when MONCs register)
Definition: ioserver.F90:46
io_server_client_mod::local_end_points_key
character(len=string_length), parameter, public local_end_points_key
Definition: ioclient.F90:43
io_server_mod::init_data_definition
subroutine init_data_definition(source, monc_defn)
Initialise the sizing of data definitions from a MONC process. The IO server determines,...
Definition: ioserver.F90:434
mpi_communication_mod::build_mpi_datatype
integer function, public build_mpi_datatype(data_definition, data_size_info, data_size, field_start_locations, field_end_locations, field_dimensions)
Builds the MPI type that corresponds to the data which will be received from a specific MONC process....
Definition: mpicommunication.F90:293
io_server_client_mod::data_sizing_description_type
Definition: ioclient.F90:16
io_server_client_mod::inter_io_communication
integer, parameter, public inter_io_communication
Field type identifiers.
Definition: ioclient.F90:34
configuration_parser_mod::io_configuration_registered_monc_type
Configuration that representes the state of a registered MONC process.
Definition: configurationparser.F90:42
threadpool_mod::threadpool_finalise
subroutine, public threadpool_finalise()
Finalises the thread pool.
Definition: threadpool.F90:192
configuration_parser_mod::get_io_xml
recursive character function, dimension(:), allocatable, public get_io_xml(filename, funit_num)
Reads in textual data from a file and returns this, used to read the IO server XML configuration file...
Definition: configurationparser.F90:170
logging_mod
Logging utility.
Definition: logging.F90:2
datadefn_mod
Contains common definitions for the data and datatypes used by MONC.
Definition: datadefn.F90:2
mpi_communication_mod::data_receive
integer function, public data_receive(mpi_datatype, num_elements, source, dump_data, data_dump_id, description_data)
Awaits some data on the data channel. This is of the type, size from the source provided and can eith...
Definition: mpicommunication.F90:166
threadpool_mod::threadpool_deactivate
subroutine, public threadpool_deactivate()
This waits for all busy threads to complete and then shuts all the pthreads down. The deactivation an...
Definition: threadpool.F90:174
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
io_server_mod::handle_deregistration_command
subroutine handle_deregistration_command(arguments, data_buffer)
Deregisteres a specific MONC source process.
Definition: ioserver.F90:273
io_server_mod::get_monc_information_data
subroutine get_monc_information_data(source)
Retrieves MONC information data, this is sent by MONC (and received) regardless, but only actioned if...
Definition: ioserver.F90:469
writer_federator_mod::check_writer_for_trigger
subroutine, public check_writer_for_trigger(io_configuration, source, data_id, data_dump)
Checks all writer entries for any trigger fires and issues the underlying file storage.
Definition: writer_federator.F90:643
diagnostic_federator_mod::initialise_diagnostic_federator
type(hashmap_type) function, public initialise_diagnostic_federator(io_configuration)
Initialises the diagnostics action and sets up the diagnostics master definitions.
Definition: diagnostic_federator.F90:90
io_server_client_mod::build_mpi_type_data_sizing_description
integer function, public build_mpi_type_data_sizing_description()
Builds the MPI type used for sending to the IO server a description of the data, namely the size of t...
Definition: ioclient.F90:147
configuration_parser_mod::get_monc_location
integer function, public get_monc_location(io_configuration, source)
A helper function to get the location of a MONC's configuration in the IO data structure.
Definition: configurationparser.F90:1234
io_server_mod::check_for_condi_conflict
subroutine check_for_condi_conflict(raw_contents, options_database)
Handle potential conditional diagnostics conflict Provides a more helpful error in the case where con...
Definition: ioserver.F90:146
io_server_mod::await_command
logical function await_command(command, source, data_buffer)
Awaits a command or shutdown from MONC processes and other IO servers.
Definition: ioserver.F90:167
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
configuration_parser_mod::cond_long
character(len=string_length), dimension(:), allocatable, public cond_long
Definition: configurationparser.F90:147
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
collections_mod::c_get_integer
Gets a specific integer element out of the list, stack, queue or map with the corresponding key.
Definition: collections.F90:378
forthread_mod::forthread_rwlock_rdlock
integer function forthread_rwlock_rdlock(lock_id)
Definition: forthread.F90:514
io_server_mod::handle_data_message
subroutine handle_data_message(arguments, data_buffer)
Handles the command for data download from a specific process. This will allocate the receive buffer ...
Definition: ioserver.F90:323
configuration_parser_mod::build_field_description_type_from_configuration
type(field_description_type) function, dimension(:), allocatable, public build_field_description_type_from_configuration(io_configuration)
Builds up the field definition description type from the structured definitions in the IO configurati...
Definition: configurationparser.F90:1111
collections_mod::c_add_string
Adds a string to the end of the list.
Definition: collections.F90:222
optionsdatabase_mod
Manages the options database. Contains administration functions and deduce runtime options from the c...
Definition: optionsdatabase.F90:7
string_utils_mod
String utility functionality that is commonly used throughout MONC.
Definition: string_utils.F90:2
configuration_parser_mod
Parses the XML configuration file to produce the io configuration description which contains the data...
Definition: configurationparser.F90:3
forthread_mod::forthread_rwlock_unlock
integer function forthread_rwlock_unlock(lock_id)
Definition: forthread.F90:550
io_server_mod::pull_back_data_message_and_handle
subroutine pull_back_data_message_and_handle(source, data_set)
Retrieves the message from MONC off the data channel and throws this to a thread in the thread pool t...
Definition: ioserver.F90:297
forthread_mod::forthread_cond_init
integer function forthread_cond_init(cond_id, attr_id)
Definition: forthread.F90:356
threadpool_mod::threadpool_init
subroutine, public threadpool_init(io_configuration)
Initialises the thread pool and marks each thread as idle.
Definition: threadpool.F90:51
collections_mod::hashset_type
Hashset structure which will store unique strings. The hashing aspect means that lookup is very fast ...
Definition: collections.F90:102
diagnostic_federator_mod::check_diagnostic_federator_for_completion
logical function, public check_diagnostic_federator_for_completion(io_configuration)
Checks whether the diagnostics federator has completed or not, this is really checking all the underl...
Definition: diagnostic_federator.F90:111
mpi_communication_mod::get_number_io_servers
integer function, public get_number_io_servers(io_comm)
Retrieves the number of IO servers that are running in total.
Definition: mpicommunication.F90:128
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::retrieve_data_definition
integer function, public retrieve_data_definition(io_configuration, key)
Retrieves a specific data definition from the configuration which matches a key.
Definition: configurationparser.F90:1049
writer_field_manager_mod::initialise_writer_field_manager
subroutine, public initialise_writer_field_manager(io_configuration, continuation_run)
Initialises the writer field manager.
Definition: writer_field_manager.F90:59