MONC
configurationparser.F90
Go to the documentation of this file.
1 
5  use sax_xml_parser_mod, only : xml_parse
15  implicit none
16 
17 #ifndef TEST_MODE
18  private
19 #endif
20 
21  character(len=STRING_LENGTH), parameter :: default_file_title = "MONC diagnostics"
25  integer, parameter :: monc_size_stride=100, data_size_stride=10
26 
28 
31  end interface get_data_value_by_field_name
32 
34  integer :: data_type, dimensions, dim_sizes(4)
35  real(kind=DEFAULT_PRECISION), dimension(:), allocatable :: values
36  character(len=STRING_LENGTH), dimension(:), allocatable :: string_values
37  type(map_type) :: map_values
38  end type data_values_type
39 
42  type(map_type) :: registered_monc_types, registered_monc_buffer_sizes
43  type(map_type), dimension(:), allocatable :: field_start_locations, field_end_locations, dimensions
44  character(len=STRING_LENGTH), dimension(:), allocatable :: definition_names
45  integer :: active_threads, active_mutex, deactivate_condition_variable, local_dim_sizes(3), local_dim_starts(3), &
46  local_dim_ends(3), source_id
48 
51  character(len=STRING_LENGTH) :: name, namespace, dim_size_defns(4), units
52  integer :: field_type, data_type, dimensions
53  logical :: optional, collective
55 
58  character(len=STRING_LENGTH) :: name, namespace
59  logical :: send_on_terminate
60  integer :: number_of_data_fields, frequency
61  type(map_type) :: compiled_fields, trigger_field_types
62  type(io_configuration_field_type), dimension(:), allocatable :: fields
64 
66  character(len=STRING_LENGTH) :: name
67  integer :: message_tag
68  procedure(handle_recv_data_from_io_server), pointer, nopass :: handling_procedure
70 
72  character(len=STRING_LENGTH) :: type, namespace
73  type(map_type) :: embellishments
75 
77  character(len=STRING_LENGTH) :: name, dim_size_defns(4), units, namespace
78  integer :: field_type, data_type, dimensions
79  logical :: collective
80  type(list_type) :: members
82 
84  character(len=STRING_LENGTH) :: name, namespace
85  type(list_type) :: members
87 
89  integer :: facet_type, time_manipulation_type
90  real :: output_time_frequency
91  character(len=STRING_LENGTH) :: facet_name
93 
95  character(len=STRING_LENGTH) :: file_name, title
96  integer :: number_of_contents, write_timestep_frequency
97  real :: write_time_frequency
98  logical :: write_on_model_time, write_on_terminate, include_in_io_state_write
99  type(io_configuration_file_writer_facet_type), dimension(:), allocatable :: contents
101 
104  integer :: number_of_data_definitions, number_of_diagnostics, io_communicator, number_of_moncs, &
105  number_of_io_servers, my_io_rank, active_moncs, number_inter_io_communications, number_of_threads, number_of_groups, &
106  number_of_writers, number_of_distinct_data_fields, number_of_global_moncs, general_info_mutex
107  type(io_configuration_data_definition_type), dimension(:), allocatable :: data_definitions
108  type(io_configuration_diagnostic_field_type), dimension(:), allocatable :: diagnostics
109  type(io_configuration_group_type), dimension(:), allocatable :: groups
110  type(io_configuration_file_writer_type), dimension(:), allocatable :: file_writers
111  type(io_configuration_registered_monc_type), dimension(:), allocatable :: registered_moncs
112  type(io_configuration_inter_communication_description), dimension(:), allocatable :: inter_io_communications
113  type(map_type) :: monc_to_index, dimension_sizing
115  real(kind=DEFAULT_PRECISION), dimension(:), allocatable :: zn_field
116  type(list_type) :: q_field_names
117  logical :: general_info_set
118  character, dimension(:), allocatable :: text_configuration
119  end type io_configuration_type
120 
121  #ifndef DOXYGEN_SHOULD_SKIP_THIS
122  abstract interface
123  subroutine handle_recv_data_from_io_server(io_configuration, data_buffer, inter_io_index)
124  import io_configuration_type
125  type(io_configuration_type), intent(inout) :: io_configuration
126  character, dimension(:), intent(inout) :: data_buffer
127  integer, intent(in) :: inter_io_index
128  end subroutine handle_recv_data_from_io_server
129  end interface
130  #endif /* DOXYGEN_SHOULD_SKIP_THIS */
131 
132 
133  integer, parameter :: file_str_stride=10000, file_line_len=2000
134 
140  character(len=STRING_LENGTH) :: data_handling_namespace
141 
144 
147  time_averaged_type, instantaneous_type, none_type, group_type, field_type, io_state_type, handle_recv_data_from_io_server, &
155 contains
156 
161  recursive function get_io_xml(filename, funit_num) result(io_xml)
162  character(len=*), intent(in) :: filename
163  integer, intent(in), optional :: funit_num
164  character, dimension(:), allocatable :: io_xml, temp_io_xml
165 
166  character(len=FILE_LINE_LEN) :: temp_line, adjusted_io_line
167  character(len=FILE_STR_STRIDE) :: reading_buffer
168  integer :: ierr, first_quote, last_quote, chosen_unit
169 
170  if (present(funit_num)) then
171  chosen_unit=funit_num
172  else
173  chosen_unit=2
174  end if
175 
176  reading_buffer=""
177  open (unit=chosen_unit, file=filename, status='OLD', iostat=ierr)
178  if (ierr .ne. 0) call log_log(log_error, "Error opening file '"//trim(filename)//"'")
179  do while (ierr == 0)
180  read(chosen_unit,"(A)",iostat=ierr) temp_line
181  adjusted_io_line=adjustl(temp_line)
182  if (ierr == 0 .and. adjusted_io_line(1:1) .ne. "!" .and. adjusted_io_line(1:2) .ne. "//") then
183  if (index(temp_line, "#include") .ne. 0) then
184  first_quote=index(temp_line, """")
185  last_quote=index(temp_line, """", back=.true.)
186  if (first_quote .ne. 0 .and. last_quote .ne. 0) then
187  call add_in_specific_line(io_xml, reading_buffer)
188  temp_io_xml=get_io_xml(temp_line(first_quote+1:last_quote-1), chosen_unit+1)
189  call combine_xml_arrays(io_xml, temp_io_xml)
190  deallocate(temp_io_xml)
191  reading_buffer=new_line("A")
192  else
193  call log_log(log_error, "Malformed IO XML, include directives must have filename in quotes")
194  end if
195  else
196  if (len_trim(reading_buffer) + len_trim(temp_line) .ge. file_str_stride) then
197  call add_in_specific_line(io_xml, reading_buffer)
198  reading_buffer=""
199  end if
200  reading_buffer=trim(reading_buffer)//trim(temp_line)//new_line("A")
201  end if
202  end if
203  end do
204  if (len_trim(reading_buffer) .gt. 0) call add_in_specific_line(io_xml, reading_buffer)
205  close(chosen_unit)
206  end function get_io_xml
207 
211  subroutine configuration_parse(provided_options_database, raw_configuration, parsed_configuration)
212  type(hashmap_type), intent(inout) :: provided_options_database
213  character, dimension(:), intent(in) :: raw_configuration
214  type(io_configuration_type), intent(out) :: parsed_configuration
215 
216  options_database=provided_options_database
217 
218  inside_data_definition=.false.
220  inside_server_config=.false.
222  inside_group_config=.false.
223  inside_generic_writing=.false.
231  building_config%number_of_writers=0
232  building_config%number_of_groups=0
233  building_config%number_of_threads=-1
234  allocate(building_config%data_definitions(data_size_stride))
235  allocate(building_config%diagnostics(data_size_stride))
236  allocate(building_config%groups(data_size_stride))
237  allocate(building_config%file_writers(data_size_stride))
238  allocate(building_config%inter_io_communications(data_size_stride))
239  call xml_parse(raw_configuration, start_element_callback, end_element_callback)
240  call add_in_dimensions(provided_options_database)
241  building_config%options_database=options_database
242  building_config%number_of_distinct_data_fields=c_size(data_field_names)
243  building_config%number_of_moncs=0
244  building_config%active_moncs=0
245  allocate(building_config%registered_moncs(monc_size_stride))
246  parsed_configuration=building_config
247  parsed_configuration%number_inter_io_communications=0
248  parsed_configuration%general_info_set=.false.
250  allocate(parsed_configuration%text_configuration(size(raw_configuration)), source=raw_configuration)
251  end subroutine configuration_parse
252 
253  subroutine add_in_dimensions(provided_options_database)
254  type(hashmap_type), intent(inout) :: provided_options_database
255 
256  integer :: dim_size
257 
258  call c_put_integer(building_config%dimension_sizing, "x", options_get_integer(provided_options_database, "x_size"))
259  call c_put_integer(building_config%dimension_sizing, "y", options_get_integer(provided_options_database, "y_size"))
260  dim_size=options_get_integer(provided_options_database, "z_size")
261  call c_put_integer(building_config%dimension_sizing, "z", dim_size)
262  call c_put_integer(building_config%dimension_sizing, "zn", dim_size)
263  call c_put_integer(building_config%dimension_sizing, "qfields", &
264  options_get_integer(provided_options_database, "number_q_fields"))
265  call c_put_integer(building_config%dimension_sizing, "number_options", c_size(provided_options_database))
266  call c_put_integer(building_config%dimension_sizing, "active_q_indicies", get_number_active_q_indices())
267  end subroutine add_in_dimensions
268 
274  subroutine start_element_callback(element_name, number_of_attributes, attribute_names, attribute_values)
275  character(len=*), intent(in) :: element_name
276  character(len=*), dimension(:), intent(in) :: attribute_names, attribute_values
277  integer, intent(in) :: number_of_attributes
278 
279  integer :: namespace_index
280 
281  if (inside_data_definition) then
282  if (element_name == "field") then
283  call process_xml_into_field_description(attribute_names, attribute_values)
284  end if
285  else if (inside_handling_definition) then
286  if (inside_diagnostic_config) then
287  call add_misc_member_to_diagnostic(element_name, attribute_names, attribute_values)
288  else
289  if (element_name == "diagnostic") then
290  call define_diagnostic(attribute_names, attribute_values)
292  end if
293  end if
294  else if (inside_server_config) then
295  if (element_name == "thread_pool") then
296  call handle_thread_pool_configuration(attribute_names, attribute_values)
297  end if
298  else if (inside_group_config) then
299  call add_diagnostic_field_to_group(element_name, attribute_names, attribute_values)
300  else if (inside_generic_writing) then
302  if (element_name == "include") then
303  call add_include_to_file_writer(attribute_names, attribute_values)
304  end if
305  else if (element_name == "file") then
307  call define_file_writer(attribute_names, attribute_values)
308  end if
309  else if (element_name == "data-writing") then
311  else if (element_name == "data-definition") then
313  call handle_new_data_definition(attribute_names, attribute_values)
314  else if (element_name == "data-handling") then
315  namespace_index=get_field_index_from_name(attribute_names, "namespace")
316  if (namespace_index == 0) then
318  else
319  data_handling_namespace=retrieve_string_value(attribute_values(namespace_index), string_data_type)
320  end if
322  else if (element_name == "group") then
323  call define_group(attribute_names, attribute_values)
324  inside_group_config=.true.
325  else if (element_name == "server-configuration") then
326  inside_server_config=.true.
327  end if
328  end subroutine start_element_callback
329 
332  subroutine end_element_callback(element_name)
333  character(len=*), intent(in) :: element_name
334 
335  integer :: i
336 
337  if (element_name == "data-definition") then
338  building_config%data_definitions(current_building_definition)%number_of_data_fields=current_building_field-1
339  do i=1, current_building_field-1
340  building_config%data_definitions(current_building_definition)%fields(i)%namespace=&
341  building_config%data_definitions(current_building_definition)%namespace
342  end do
344  building_config%number_of_data_definitions=current_building_definition
346  inside_data_definition=.false.
347  else if (element_name == "data-handling") then
348  building_config%number_of_diagnostics=current_building_diagnostic-1
350  else if (element_name == "server-configuration") then
351  inside_server_config=.false.
352  else if (element_name == "action") then
353  inside_action_config=.false.
354  else if (element_name == "diagnostic") then
357  else if (element_name == "data-writing") then
358  inside_generic_writing=.false.
360  else if (element_name == "group") then
362  building_config%number_of_groups=building_config%number_of_groups+1
363  inside_group_config=.false.
364  else if (element_name == "file") then
367  end if
368  end subroutine end_element_callback
369 
370  subroutine handle_thread_pool_configuration(attribute_names, attribute_values)
371  character(len=*), dimension(:), intent(in) :: attribute_names, attribute_values
372 
373  integer :: number_index
374 
375  number_index=get_field_index_from_name(attribute_names, "number")
376 
377  if (number_index /= 0) then
378  building_config%number_of_threads=conv_to_integer(attribute_values(number_index))
379  end if
380  end subroutine handle_thread_pool_configuration
381 
386  subroutine handle_new_data_definition(attribute_names, attribute_values)
387  character(len=*), dimension(:), intent(in) :: attribute_names, attribute_values
388 
389  integer :: name_index, frequency_index, namespace_index, send_on_termination_index
390  character(len=STRING_LENGTH) :: namespace
391 
392  name_index=get_field_index_from_name(attribute_names, "name")
393  frequency_index=get_field_index_from_name(attribute_names, "frequency")
394  namespace_index=get_field_index_from_name(attribute_names, "namespace")
395  send_on_termination_index=get_field_index_from_name(attribute_names, "send_on_terminate")
396  if (name_index /= 0 .and. frequency_index /=0) then
397  if (current_building_definition .gt. size(building_config%data_definitions)) call extend_data_definition_array()
398  building_config%data_definitions(current_building_definition)%name=&
399  retrieve_string_value(attribute_values(name_index), string_data_type)
400  building_config%data_definitions(current_building_definition)%frequency=&
401  conv_to_integer(retrieve_string_value(attribute_values(frequency_index), integer_data_type))
402  if (namespace_index /= 0) then
403  namespace=retrieve_string_value(attribute_values(namespace_index), string_data_type)
404  building_config%data_definitions(current_building_definition)%namespace=namespace
405  else
406  namespace=""
407  building_config%data_definitions(current_building_definition)%namespace=""
408  end if
409  if (send_on_termination_index /= 0) then
410  building_config%data_definitions(current_building_definition)%send_on_terminate=&
411  retrieve_string_value(attribute_values(send_on_termination_index), string_data_type) == "true"
412  else
413  building_config%data_definitions(current_building_definition)%send_on_terminate=.false.
414  end if
415  else
416  call log_log(log_error, "A data definition requires a name and frequency")
417  end if
418  allocate(building_config%data_definitions(current_building_definition)%fields(data_size_stride))
419 
420  building_config%data_definitions(current_building_definition)%fields(1)%name="timestep"
421  building_config%data_definitions(current_building_definition)%fields(1)%namespace=namespace
422  building_config%data_definitions(current_building_definition)%fields(1)%field_type=scalar_field_type
423  building_config%data_definitions(current_building_definition)%fields(1)%dimensions=0
424  building_config%data_definitions(current_building_definition)%fields(1)%data_type=integer_data_type
425  building_config%data_definitions(current_building_definition)%fields(1)%optional=.false.
426  building_config%data_definitions(current_building_definition)%fields(1)%collective=.false.
427  building_config%data_definitions(current_building_definition)%fields(1)%units=""
428 
429  building_config%data_definitions(current_building_definition)%fields(2)%name="time"
430  building_config%data_definitions(current_building_definition)%fields(2)%namespace=namespace
431  building_config%data_definitions(current_building_definition)%fields(2)%field_type=scalar_field_type
432  building_config%data_definitions(current_building_definition)%fields(2)%dimensions=0
433  building_config%data_definitions(current_building_definition)%fields(2)%data_type=double_data_type
434  building_config%data_definitions(current_building_definition)%fields(2)%optional=.false.
435  building_config%data_definitions(current_building_definition)%fields(2)%collective=.false.
436  building_config%data_definitions(current_building_definition)%fields(2)%units=""
437 
438  building_config%data_definitions(current_building_definition)%fields(3)%name="terminated"
439  building_config%data_definitions(current_building_definition)%fields(3)%namespace=namespace
440  building_config%data_definitions(current_building_definition)%fields(3)%field_type=scalar_field_type
441  building_config%data_definitions(current_building_definition)%fields(3)%dimensions=0
442  building_config%data_definitions(current_building_definition)%fields(3)%data_type=boolean_data_type
443  building_config%data_definitions(current_building_definition)%fields(3)%optional=.false.
444  building_config%data_definitions(current_building_definition)%fields(3)%collective=.false.
445  building_config%data_definitions(current_building_definition)%fields(3)%units=""
446 
448  end subroutine handle_new_data_definition
449 
450  subroutine add_misc_member_to_diagnostic(element_name, attribute_names, attribute_values)
451  character(len=*), intent(in) :: element_name
452  character(len=*), dimension(:), intent(in) :: attribute_names, attribute_values
453 
454  type(io_configuration_misc_item_type), pointer :: misc_member
455  class(*), pointer :: generic
456  integer :: i
457 
458  allocate(misc_member)
459 
460  misc_member%type=retrieve_string_value(element_name, string_data_type)
461  misc_member%namespace=data_handling_namespace
462  do i=1, size(attribute_names)
463  call c_put_string(misc_member%embellishments, retrieve_string_value(attribute_names(i), string_data_type), &
464  retrieve_string_value(attribute_values(i), string_data_type))
465  end do
466  generic=>misc_member
467  call c_add_generic(building_config%diagnostics(current_building_diagnostic)%members, generic, .false.)
468  end subroutine add_misc_member_to_diagnostic
469 
470  subroutine add_diagnostic_field_to_group(element_name, attribute_names, attribute_values)
471  character(len=*), intent(in) :: element_name
472  character(len=*), dimension(:), intent(in) :: attribute_names, attribute_values
473 
474  integer :: field_index
475 
476  if (element_name == "member") then
477  field_index=get_field_index_from_name(attribute_names, "name")
478  if (field_index .gt. 0) then
479  call c_add_string(building_config%groups(current_building_group)%members, &
480  retrieve_string_value(attribute_values(field_index), string_data_type))
481  else
482  call log_log(log_error, "A diagnostics group member requires a name")
483  end if
484  else
485  call log_log(log_error, "Unrecognised diagnostics group participant, name is '"//trim(element_name)//"'")
486  end if
487  end subroutine add_diagnostic_field_to_group
488 
489  subroutine define_group(attribute_names, attribute_values)
490  character(len=*), dimension(:), intent(in) :: attribute_names, attribute_values
491 
492  integer :: field_index
493 
494  if (current_building_group .gt. size(building_config%groups)) call extend_groups_array()
495 
496  field_index=get_field_index_from_name(attribute_names, "name")
497  if (field_index .gt. 0) then
498  building_config%groups(current_building_group)%name=retrieve_string_value(attribute_values(field_index), string_data_type)
499  field_index=get_field_index_from_name(attribute_names, "namespace")
500  if (field_index .gt. 0) then
501  building_config%groups(current_building_group)%namespace=&
502  retrieve_string_value(attribute_values(field_index), string_data_type)
503  else
504  building_config%groups(current_building_group)%namespace=""
505  end if
506  else
507  call log_log(log_error, "A diagnostics group requires a name")
508  end if
509  end subroutine define_group
510 
511  subroutine add_include_to_file_writer(attribute_names, attribute_values)
512  character(len=*), dimension(:), intent(in) :: attribute_names, attribute_values
513 
514  integer :: field_index, number_of_contents
515 
516  number_of_contents=building_config%file_writers(current_building_file_writer)%number_of_contents+1
517 
518  if (number_of_contents .gt. &
520 
521  building_config%file_writers(current_building_file_writer)%contents(number_of_contents)%facet_type=0
522  field_index=get_field_index_from_name(attribute_names, "group")
523  if (field_index .gt. 0) then
524  building_config%file_writers(current_building_file_writer)%contents(number_of_contents)%facet_name=&
525  retrieve_string_value(attribute_values(field_index), string_data_type)
526  building_config%file_writers(current_building_file_writer)%contents(number_of_contents)%facet_type=group_type
527  call add_include_group_or_field_to_file_writer(attribute_names, attribute_values, number_of_contents)
528  else
529  field_index=get_field_index_from_name(attribute_names, "field")
530  if (field_index .gt. 0) then
531  building_config%file_writers(current_building_file_writer)%contents(number_of_contents)%facet_name=&
532  retrieve_string_value(attribute_values(field_index), string_data_type)
533  building_config%file_writers(current_building_file_writer)%contents(number_of_contents)%facet_type=field_type
534  call add_include_group_or_field_to_file_writer(attribute_names, attribute_values, number_of_contents)
535  else
536  field_index=get_field_index_from_name(attribute_names, "state")
537  if (field_index .gt. 0) then
538  if (trim(retrieve_string_value(attribute_values(field_index), string_data_type)) .eq. "io") then
539  building_config%file_writers(current_building_file_writer)%contents(number_of_contents)%facet_type=io_state_type
540  end if
541  end if
542  end if
543  end if
544 
545  if (building_config%file_writers(current_building_file_writer)%contents(number_of_contents)%facet_type == 0) then
546  call log_log(log_error, "Inclusion to file writer requires a field or group to include")
547  end if
548 
549  building_config%file_writers(current_building_file_writer)%number_of_contents=&
550  building_config%file_writers(current_building_file_writer)%number_of_contents+1
551  end subroutine add_include_to_file_writer
552 
553  subroutine add_include_group_or_field_to_file_writer(attribute_names, attribute_values, number_of_contents)
554  character(len=*), dimension(:), intent(in) :: attribute_names, attribute_values
555  integer, intent(in) :: number_of_contents
556 
557  character(len=STRING_LENGTH) :: time_manip
558  integer :: field_index
559 
560  field_index=get_field_index_from_name(attribute_names, "time_manipulation")
561  if (field_index .gt. 0) then
562  time_manip=retrieve_string_value(attribute_values(field_index), string_data_type)
563  if (time_manip == "instantaneous") then
564  building_config%file_writers(current_building_file_writer)%contents(number_of_contents)%time_manipulation_type=&
566  else if (time_manip == "averaged") then
567  building_config%file_writers(current_building_file_writer)%contents(number_of_contents)%time_manipulation_type=&
569  else if (time_manip == "none") then
570  building_config%file_writers(current_building_file_writer)%contents(number_of_contents)%time_manipulation_type=&
571  none_type
572  else
573  call log_log(log_error, "Time manipulation '"//trim(time_manip)//"' option not recognised")
574  end if
575  else
576  call log_log(log_error, "Inclusion to file writer requires time manipulation")
577  end if
578 
579  field_index=get_field_index_from_name(attribute_names, "output_frequency")
580  if (field_index .gt. 0) then
582  contents(number_of_contents)%output_time_frequency=&
583  conv_to_real(retrieve_string_value(attribute_values(field_index), double_data_type))
584  else if (building_config%file_writers(current_building_file_writer)%contents(number_of_contents)%time_manipulation_type &
585  == none_type) then
586  building_config%file_writers(current_building_file_writer)%contents(number_of_contents)%output_time_frequency=-1.0
587  else
588  call log_log(log_error, "Inclusion to file writer requires an output frequency")
589  end if
591 
592  subroutine define_file_writer(attribute_names, attribute_values)
593  character(len=*), dimension(:), intent(in) :: attribute_names, attribute_values
594 
595  integer :: field_index
596 
597  if (current_building_file_writer .gt. size(building_config%file_writers)) call extend_file_writer_array()
598 
599  field_index=get_field_index_from_name(attribute_names, "name")
600  if (field_index .gt. 0) then
601  building_config%file_writers(current_building_file_writer)%file_name=&
602  retrieve_string_value(attribute_values(field_index), string_data_type)
603  else
604  call log_log(log_error, "File writer requires a file name")
605  end if
606 
607  field_index=get_field_index_from_name(attribute_names, "write_time_frequency")
608  if (field_index .gt. 0) then
609  building_config%file_writers(current_building_file_writer)%write_time_frequency=&
610  conv_to_real(retrieve_string_value(attribute_values(field_index), double_data_type))
611  building_config%file_writers(current_building_file_writer)%write_on_model_time=.true.
612  else
613  field_index=get_field_index_from_name(attribute_names, "write_timestep_frequency")
614  if (field_index .gt. 0) then
615  building_config%file_writers(current_building_file_writer)%write_timestep_frequency=&
616  conv_to_real(retrieve_string_value(attribute_values(field_index), integer_data_type))
617  building_config%file_writers(current_building_file_writer)%write_on_model_time=.false.
618  else
619  call log_log(log_error, "File writer requires either a write time frequency or write timestep frequency")
620  end if
621  end if
622 
623  field_index=get_field_index_from_name(attribute_names, "title")
624  if (field_index .gt. 0) then
625  building_config%file_writers(current_building_file_writer)%title=&
626  retrieve_string_value(attribute_values(field_index), string_data_type)
627  else
629  end if
630 
631  field_index=get_field_index_from_name(attribute_names, "write_on_terminate")
632  if (field_index .gt. 0) then
633  building_config%file_writers(current_building_file_writer)%write_on_terminate=&
634  retrieve_string_value(attribute_values(field_index), string_data_type) == "true"
635  else
636  building_config%file_writers(current_building_file_writer)%write_on_terminate=.false.
637  end if
638 
639  field_index=get_field_index_from_name(attribute_names, "store_state")
640  if (field_index .gt. 0) then
641  building_config%file_writers(current_building_file_writer)%include_in_io_state_write=&
642  retrieve_string_value(attribute_values(field_index), string_data_type) == "true"
643  else
644  building_config%file_writers(current_building_file_writer)%include_in_io_state_write=.true.
645  end if
646 
647  building_config%file_writers(current_building_file_writer)%number_of_contents=0
648  allocate(building_config%file_writers(current_building_file_writer)%contents(data_size_stride))
649  end subroutine define_file_writer
650 
656  subroutine define_diagnostic(attribute_names, attribute_values)
657  character(len=*), dimension(:), intent(in) :: attribute_names, attribute_values
658 
659  integer :: field_index, type_field_index, data_field_index
660  character(len=STRING_LENGTH) :: field_type_str, field_data_type_str, size_definitions
661 
662  if (current_building_diagnostic .gt. size(building_config%diagnostics)) call extend_diagnostics_array()
663 
664  field_index=get_field_index_from_name(attribute_names, "field")
665  type_field_index=get_field_index_from_name(attribute_names, "type")
666  data_field_index=get_field_index_from_name(attribute_names, "data_type")
667 
668  if (field_index == 0 .or. type_field_index == 0 .or. data_field_index == 0) then
669  call log_log(log_error, "Each diagnostic definition requires a field name, field type and data type")
670  else
671  building_config%diagnostics(current_building_diagnostic)%name=&
672  retrieve_string_value(attribute_values(field_index), string_data_type)
674  field_type_str=retrieve_string_value(attribute_values(type_field_index), string_data_type)
675  building_config%diagnostics(current_building_diagnostic)%field_type=get_field_type_from_attribute(field_type_str)
676  if (building_config%diagnostics(current_building_diagnostic)%field_type==0) then
677  call log_log(log_error, "The field type of '"//trim(field_type_str)//"' is not recognised")
678  end if
679  field_data_type_str=retrieve_string_value(attribute_values(data_field_index), string_data_type)
680  building_config%diagnostics(current_building_diagnostic)%data_type=get_field_datatype_from_attribute(field_data_type_str)
681  if (building_config%diagnostics(current_building_diagnostic)%data_type==0) then
682  call log_log(log_error, "The field data type of '"//trim(field_data_type_str)//"' is not recognised")
683  end if
684  field_index=get_field_index_from_name(attribute_names, "units")
685  if (field_index .ne. 0) then
686  building_config%diagnostics(current_building_diagnostic)%units=&
687  retrieve_string_value(attribute_values(field_index), string_data_type)
688  else
689  building_config%diagnostics(current_building_diagnostic)%units=""
690  end if
691  if (building_config%diagnostics(current_building_diagnostic)%field_type == array_field_type .or. &
692  building_config%diagnostics(current_building_diagnostic)%field_type == map_field_type) then
693  field_index=get_field_index_from_name(attribute_names, "size")
694  if (field_index .ne. 0) then
695  size_definitions=retrieve_string_value(attribute_values(field_index), string_data_type)
696  building_config%diagnostics(current_building_diagnostic)%dimensions=process_sizing_definition(size_definitions, &
697  building_config%diagnostics(current_building_diagnostic)%dim_size_defns)
698  else
699  call log_log(log_error, "A diagnostic of field type array or map requires sizing a definition")
700  end if
701  field_index=get_field_index_from_name(attribute_names, "collective")
702  if (field_index .ne. 0) then
703  building_config%diagnostics(current_building_diagnostic)%collective=&
704  retrieve_string_value(attribute_values(field_index), string_data_type) == "true"
705  else
706  building_config%diagnostics(current_building_diagnostic)%collective=.false.
707  end if
708  else
709  building_config%diagnostics(current_building_diagnostic)%dimensions=0
710  building_config%diagnostics(current_building_diagnostic)%collective=.false.
711  end if
712  end if
713  end subroutine define_diagnostic
714 
715  integer function process_sizing_definition(size_definitions, individual_str_defn)
716  character(len=*), intent(in) :: size_definitions
717  character(len=STRING_LENGTH), intent(out) :: individual_str_defn(4)
718 
719  integer :: comma_index, sizing_index, cp
720 
721  cp=1
722  sizing_index=1
723  comma_index=index(size_definitions(cp:), ",")
724  do while (comma_index .ne. 0)
725  comma_index=comma_index+cp-1
726  individual_str_defn(sizing_index)= trim(size_definitions(cp:comma_index-1))
727  cp=comma_index+1
728  sizing_index=sizing_index+1
729  comma_index=index(size_definitions(cp:), ",")
730  if (sizing_index .gt. 4) then
731  call log_log(log_error, "Can only have a maximum of four diagnostic field sizing dimensions")
732  end if
733  end do
734  if (cp .le. len(size_definitions)) then
735  individual_str_defn(sizing_index)=trim(size_definitions(cp:))
736  sizing_index=sizing_index+1
737  end if
738  process_sizing_definition=sizing_index-1
739  end function process_sizing_definition
740 
747  subroutine process_xml_into_field_description(attribute_names, attribute_values)
748  character(len=*), dimension(:), intent(in) :: attribute_names, attribute_values
749 
750  character(len=STRING_LENGTH) :: field_type_str, field_data_type_str, sizing_defn_str
751  integer :: name_field_index, type_field_index, data_field_index, field_index, optional_field_index, idx
752 
753 
754  name_field_index=get_field_index_from_name(attribute_names, "name")
755  type_field_index=get_field_index_from_name(attribute_names, "type")
756  data_field_index=get_field_index_from_name(attribute_names, "data_type")
757 
758  if (name_field_index == 0 .or. type_field_index == 0 .or. data_field_index == 0) then
759  call log_log(log_error, "Each data field definition requires a name, field type and data type")
760  else
761  if (current_building_field .eq. size(building_config%data_definitions(current_building_definition)%fields)) &
762  call extend_field_array()
763 
765  retrieve_string_value(attribute_values(name_field_index), string_data_type)
766 
769 
770  field_type_str=retrieve_string_value(attribute_values(type_field_index), string_data_type)
771  building_config%data_definitions(current_building_definition)%fields(current_building_field)%field_type=&
772  get_field_type_from_attribute(field_type_str)
773 
774  if (building_config%data_definitions(current_building_definition)%fields(current_building_field)%field_type==0) then
775  call log_log(log_error, "The field type of '"//trim(field_type_str)//"' is not recognised")
776  end if
777 
778  building_config%data_definitions(current_building_definition)%fields(current_building_field)%dimensions=0
779 
780  if (building_config%data_definitions(current_building_definition)%fields(current_building_field)%field_type == &
781  array_field_type .or. &
782  building_config%data_definitions(current_building_definition)%fields(current_building_field)%field_type == &
783  map_field_type) then
784  idx=get_field_index_from_name(attribute_names, "size")
785  if (idx .ne. 0) then
786  sizing_defn_str=retrieve_string_value(attribute_values(idx), string_data_type)
787  building_config%data_definitions(current_building_definition)%fields(current_building_field)%dimensions=&
788  process_sizing_definition(sizing_defn_str, &
789  building_config%data_definitions(current_building_definition)%fields(current_building_field)%dim_size_defns)
790  end if
791 
792  field_index=get_field_index_from_name(attribute_names, "collective")
793  if (field_index .ne. 0) then
794  building_config%data_definitions(current_building_definition)%fields(current_building_field)%collective=&
795  retrieve_string_value(attribute_values(field_index), string_data_type) == "true"
796  else
797  building_config%data_definitions(current_building_definition)%fields(current_building_field)%collective=.false.
798  end if
799  else
800  building_config%data_definitions(current_building_definition)%fields(current_building_field)%collective=.false.
801  end if
802 
803  field_index=get_field_index_from_name(attribute_names, "units")
804  if (field_index .ne. 0) then
805  building_config%data_definitions(current_building_definition)%fields(current_building_field)%units=&
806  retrieve_string_value(attribute_values(field_index), string_data_type)
807  else
808  building_config%data_definitions(current_building_definition)%fields(current_building_field)%units=""
809  end if
810 
811  field_data_type_str=retrieve_string_value(attribute_values(data_field_index), string_data_type)
812  building_config%data_definitions(current_building_definition)%fields(current_building_field)%data_type=&
813  get_field_datatype_from_attribute(field_data_type_str)
814 
815  if (building_config%data_definitions(current_building_definition)%fields(current_building_field)%data_type==0) then
816  call log_log(log_error, "The field data type of '"//trim(field_data_type_str)//"' is not recognised")
817  end if
818 
819  if (building_config%data_definitions(current_building_definition)%fields(current_building_field)%field_type == &
820  map_field_type .and. building_config%data_definitions(current_building_definition)%fields(&
821  current_building_field)%data_type/=string_data_type) then
822  call log_log(log_error, "A map field type must have a data type of ""string""")
823  end if
824 
825  optional_field_index=get_field_index_from_name(attribute_names, "optional")
826  if (optional_field_index .ne. 0) then
827  if (retrieve_string_value(attribute_values(optional_field_index), string_data_type) == "true") then
828  building_config%data_definitions(current_building_definition)%fields(current_building_field)%optional=.true.
829  else
830  building_config%data_definitions(current_building_definition)%fields(current_building_field)%optional=.false.
831  end if
832  else
833  building_config%data_definitions(current_building_definition)%fields(current_building_field)%optional=.false.
834  end if
836  end if
838 
839  integer function get_field_type_from_attribute(field_type_str)
840  character(len=*), intent(in) :: field_type_str
841 
843  if (field_type_str == "scalar") get_field_type_from_attribute=scalar_field_type
844  if (field_type_str == "array") get_field_type_from_attribute=array_field_type
845  if (field_type_str == "map") get_field_type_from_attribute=map_field_type
846  end function get_field_type_from_attribute
847 
848  integer function get_field_datatype_from_attribute(field_data_type_str)
849  character(len=*), intent(in) :: field_data_type_str
850 
852  if (field_data_type_str == "integer") get_field_datatype_from_attribute=integer_data_type
853  if (field_data_type_str == "boolean") get_field_datatype_from_attribute=boolean_data_type
854  if (field_data_type_str == "string") get_field_datatype_from_attribute=string_data_type
855  if (field_data_type_str == "float") get_field_datatype_from_attribute=float_data_type
856  if (field_data_type_str == "double") get_field_datatype_from_attribute=double_data_type
858 
863  subroutine replace_characters_in_string(original_string, new_string, to_replace)
864  character(len=*), intent(in) :: original_string, to_replace
865  character(len=*), intent(out) :: new_string
866 
867  integer :: current_index, string_len, occurance
868 
869  current_index=1
870  string_len=len(original_string)
871  new_string=""
872  do while (current_index .lt. string_len)
873  occurance=index(original_string(current_index:), to_replace)
874  if (occurance .eq. 0) then
875  occurance=len(original_string)
876  else
877  occurance=occurance+current_index
878  end if
879  new_string=trim(new_string)//trim(original_string(current_index:occurance-len(to_replace)-1))
880  current_index=current_index+occurance+len(to_replace)-2
881  end do
882  end subroutine replace_characters_in_string
883 
884  character(len=STRING_LENGTH) function retrieve_string_value(original_string, field_value_type)
885  character(len=*), intent(in) :: original_string
886  integer, intent(in) :: field_value_type
887 
888  integer :: last_char
889  character(len=STRING_LENGTH) :: lookup_key
890 
891  call replace_characters_in_string(original_string, retrieve_string_value, """")
892 
894  if (retrieve_string_value(1:1)=="{") then
895  last_char=len_trim(retrieve_string_value)
896  if (retrieve_string_value(last_char:last_char)=="}") then
897  lookup_key=retrieve_string_value(2:last_char-1)
898  if (options_has_key(options_database, lookup_key)) then
899  if (field_value_type==integer_data_type) then
901  else if (field_value_type==boolean_data_type) then
903  else if (field_value_type==double_data_type) then
905  else if (field_value_type==string_data_type) then
907  end if
908  else
909  call log_log(log_error, "Can not find IO configuration key '"//trim(lookup_key)//"' in the options database")
910  end if
911  end if
912  end if
913  end function retrieve_string_value
914 
918  integer function get_field_index_from_name(attribute_names, search_name)
919  character(len=*), intent(in) :: search_name
920  character(len=*), dimension(:) :: attribute_names
921 
922  integer :: i, size_of_names
923 
924  size_of_names=size(attribute_names)
925  do i=1,size_of_names
926  if (attribute_names(i) == search_name) then
928  return
929  end if
930  end do
932  end function get_field_index_from_name
933 
937  subroutine extend_inter_io_comm_array(io_configuration)
938  type(io_configuration_type), intent(inout) :: io_configuration
939 
940  type(io_configuration_inter_communication_description), dimension(:), allocatable :: temp_descriptions
941 
942  allocate(temp_descriptions(lbound(io_configuration%inter_io_communications,1):&
943  ubound(io_configuration%inter_io_communications,1)+data_size_stride))
944  temp_descriptions(lbound(io_configuration%inter_io_communications,1):&
945  ubound(io_configuration%inter_io_communications,1)) = io_configuration%inter_io_communications
946  call move_alloc(from=temp_descriptions,to=io_configuration%inter_io_communications)
947  end subroutine extend_inter_io_comm_array
948 
950  type(io_configuration_file_writer_facet_type), dimension(:), allocatable :: temp_filewriter_contents
951 
952  allocate(temp_filewriter_contents(lbound(building_config%file_writers(current_building_file_writer)%contents,1): &
953  ubound(building_config%file_writers(current_building_file_writer)%contents,1)+data_size_stride))
954  temp_filewriter_contents(lbound(building_config%file_writers(current_building_file_writer)%contents,1):&
955  ubound(building_config%file_writers(current_building_file_writer)%contents,1)) = &
956  building_config%file_writers(current_building_file_writer)%contents
957  call move_alloc(from=temp_filewriter_contents,to=building_config%file_writers(current_building_file_writer)%contents)
958  end subroutine extend_file_writer_contents_array
959 
960  subroutine extend_file_writer_array()
961  type(io_configuration_file_writer_type), dimension(:), allocatable :: temp_filewriter
962 
963  allocate(temp_filewriter(lbound(building_config%file_writers,1): ubound(building_config%file_writers,1)+data_size_stride))
964  temp_filewriter(lbound(building_config%file_writers,1):ubound(building_config%file_writers,1)) = building_config%file_writers
965  call move_alloc(from=temp_filewriter,to=building_config%file_writers)
966  end subroutine extend_file_writer_array
967 
969  subroutine extend_diagnostics_array()
970  type(io_configuration_diagnostic_field_type), dimension(:), allocatable :: temp_diagnostics
971 
972  allocate(temp_diagnostics(lbound(building_config%diagnostics,1): ubound(building_config%diagnostics,1)+data_size_stride))
973  temp_diagnostics(lbound(building_config%diagnostics,1):ubound(building_config%diagnostics,1)) = building_config%diagnostics
974  call move_alloc(from=temp_diagnostics,to=building_config%diagnostics)
975  end subroutine extend_diagnostics_array
976 
977  subroutine extend_groups_array()
978  type(io_configuration_group_type), dimension(:), allocatable :: temp_groups
979 
980  allocate(temp_groups(lbound(building_config%groups,1): ubound(building_config%groups,1)+data_size_stride))
981  temp_groups(lbound(building_config%groups,1):ubound(building_config%groups,1)) = building_config%groups
982  call move_alloc(from=temp_groups,to=building_config%groups)
983  end subroutine extend_groups_array
984 
986  subroutine extend_field_array()
987  type(io_configuration_field_type), dimension(:), allocatable :: temp_fields
988 
989  allocate(temp_fields(lbound(building_config%data_definitions(current_building_definition)%fields,1):&
990  ubound(building_config%data_definitions(current_building_definition)%fields,1)+data_size_stride))
991  temp_fields(lbound(building_config%data_definitions(current_building_definition)%fields,1):&
992  ubound(building_config%data_definitions(current_building_definition)%fields,1)) = &
993  building_config%data_definitions(current_building_definition)%fields
994  call move_alloc(from=temp_fields,to=building_config%data_definitions(current_building_definition)%fields)
995  end subroutine extend_field_array
996 
998  subroutine extend_data_definition_array()
999  type(io_configuration_data_definition_type), dimension(:), allocatable :: temp_data_definitions
1000 
1001  allocate(temp_data_definitions(lbound(building_config%data_definitions, 1):&
1002  ubound(building_config%data_definitions,1)+data_size_stride))
1003  temp_data_definitions(lbound(building_config%data_definitions, 1):&
1004  ubound(building_config%data_definitions, 1)) = building_config%data_definitions
1005  call move_alloc(from=temp_data_definitions,to=building_config%data_definitions)
1006  end subroutine extend_data_definition_array
1007 
1010  subroutine extend_registered_moncs_array(io_configuration)
1011  type(io_configuration_type), intent(inout) :: io_configuration
1012 
1013  type(io_configuration_registered_monc_type), dimension(:), allocatable :: temp_registered_moncs
1014 
1015  allocate(temp_registered_moncs(lbound(io_configuration%registered_moncs, 1):&
1016  io_configuration%number_of_moncs+monc_size_stride))
1017  temp_registered_moncs(lbound(io_configuration%registered_moncs, 1):&
1018  ubound(io_configuration%registered_moncs, 1)) = io_configuration%registered_moncs
1019  call move_alloc(from=temp_registered_moncs,to=io_configuration%registered_moncs)
1020  end subroutine extend_registered_moncs_array
1021 
1026  integer function retrieve_data_definition(io_configuration, key)
1027  type(io_configuration_type), intent(inout) :: io_configuration
1028  character(len=*), intent(in) :: key
1029 
1030  integer :: i
1031 
1032  do i=1,io_configuration%number_of_data_definitions
1033  if (io_configuration%data_definitions(i)%name .eq. key) then
1035  return
1036  end if
1037  end do
1039  end function retrieve_data_definition
1040 
1046  logical function retrieve_monc_definition(io_configuration, source, monc_defn)
1047  type(io_configuration_type), intent(inout) :: io_configuration
1048  integer, intent(in) :: source
1049  type(io_configuration_registered_monc_type), intent(out) :: monc_defn
1050 
1051  class(*), pointer :: generic
1052  integer :: location
1053 
1054  generic=>c_get_generic(io_configuration%monc_to_index, conv_to_string(source))
1055  if (associated(generic)) then
1056  location=conv_to_integer(generic, .false.)
1057  monc_defn=io_configuration%registered_moncs(location)
1059  else
1060  retrieve_monc_definition=.false.
1061  end if
1062  end function retrieve_monc_definition
1063 
1067  function build_definition_description_type_from_configuration(io_configuration)
1068  type(io_configuration_type), intent(inout) :: io_configuration
1069  type(definition_description_type), dimension(:), allocatable :: build_definition_description_type_from_configuration
1070 
1071  integer :: i
1072 
1073  allocate(build_definition_description_type_from_configuration(io_configuration%number_of_data_definitions))
1074 
1075  do i=1, io_configuration%number_of_data_definitions
1076  build_definition_description_type_from_configuration(i)%definition_name=io_configuration%data_definitions(i)%name
1077  build_definition_description_type_from_configuration(i)%send_on_terminate=&
1078  io_configuration%data_definitions(i)%send_on_terminate
1079  build_definition_description_type_from_configuration(i)%number_fields=&
1080  io_configuration%data_definitions(i)%number_of_data_fields
1081  build_definition_description_type_from_configuration(i)%frequency=io_configuration%data_definitions(i)%frequency
1082  end do
1084 
1088  function build_field_description_type_from_configuration(io_configuration)
1089  type(io_configuration_type), intent(inout) :: io_configuration
1090  type(field_description_type), dimension(:), allocatable :: build_field_description_type_from_configuration
1091 
1092  integer :: i, j, field_index
1093 
1094  allocate(build_field_description_type_from_configuration(get_total_number_fields(io_configuration)))
1095  field_index=1
1096  do i=1, io_configuration%number_of_data_definitions
1097  do j=1, io_configuration%data_definitions(i)%number_of_data_fields
1098  build_field_description_type_from_configuration(field_index)%definition_name=io_configuration%data_definitions(i)%name
1099  build_field_description_type_from_configuration(field_index)%field_name=&
1100  io_configuration%data_definitions(i)%fields(j)%name
1101  build_field_description_type_from_configuration(field_index)%field_type=&
1102  io_configuration%data_definitions(i)%fields(j)%field_type
1103  build_field_description_type_from_configuration(field_index)%data_type=&
1104  io_configuration%data_definitions(i)%fields(j)%data_type
1105  build_field_description_type_from_configuration(field_index)%optional=&
1106  io_configuration%data_definitions(i)%fields(j)%optional
1107  field_index=field_index+1
1108  end do
1109  end do
1111 
1115  integer function get_total_number_fields(io_configuration)
1116  type(io_configuration_type), intent(inout) :: io_configuration
1117 
1118  integer :: i
1119 
1121  do i=1, io_configuration%number_of_data_definitions
1122  get_total_number_fields=get_total_number_fields+io_configuration%data_definitions(i)%number_of_data_fields
1123  end do
1124  end function get_total_number_fields
1125 
1133  integer function get_number_field_dimensions(io_configuration, field_name, source, data_id)
1134  type(io_configuration_type), intent(inout) :: io_configuration
1135  character(len=*), intent(in) :: field_name
1136  integer, intent(in) :: source, data_id
1137 
1138  integer :: monc_location
1139 
1140  monc_location=c_get_integer(io_configuration%monc_to_index, conv_to_string(source))
1141  get_number_field_dimensions=c_get_integer(io_configuration%registered_moncs(monc_location)%dimensions(data_id), field_name)
1142  end function get_number_field_dimensions
1143 
1148  function get_data_value_from_hashmap_by_field_name(collection, field_name)
1149  type(hashmap_type), intent(inout) :: collection
1150  character(len=*), intent(in) :: field_name
1151  type(data_values_type), pointer :: get_data_value_from_hashmap_by_field_name
1152 
1153  class(*), pointer :: generic
1154 
1155  generic=>c_get_generic(collection, field_name)
1156  if (associated(generic)) then
1157  select type(generic)
1158  type is (data_values_type)
1159  get_data_value_from_hashmap_by_field_name=>generic
1160  end select
1161  else
1162  get_data_value_from_hashmap_by_field_name=>null()
1163  end if
1165 
1170  function get_data_value_from_map_by_field_name(collection, field_name)
1171  type(map_type), intent(inout) :: collection
1172  character(len=*), intent(in) :: field_name
1173  type(data_values_type), pointer :: get_data_value_from_map_by_field_name
1174 
1175  class(*), pointer :: generic
1176 
1177  generic=>c_get_generic(collection, field_name)
1178  if (associated(generic)) then
1179  select type(generic)
1180  type is (data_values_type)
1181  get_data_value_from_map_by_field_name=>generic
1182  end select
1183  else
1184  get_data_value_from_map_by_field_name=>null()
1185  end if
1187 
1191  function get_data_value_from_map_entry(map_entry)
1192  type(mapentry_type), intent(in) :: map_entry
1193  type(data_values_type), pointer :: get_data_value_from_map_entry
1194 
1195  class(*), pointer :: generic
1196 
1197  generic=>c_get_generic(map_entry)
1198  if (associated(generic)) then
1199  select type(generic)
1200  type is (data_values_type)
1201  get_data_value_from_map_entry=>generic
1202  end select
1203  else
1204  get_data_value_from_map_entry=>null()
1205  end if
1206  end function get_data_value_from_map_entry
1207 
1211  integer function get_monc_location(io_configuration, source)
1212  type(io_configuration_type), intent(inout) :: io_configuration
1213  integer, intent(in) :: source
1214 
1215  get_monc_location=c_get_integer(io_configuration%monc_to_index, conv_to_string(source))
1216  end function get_monc_location
1217 
1223  logical function get_diagnostic_field_configuration(io_configuration, field_name, field_namespace, diagnostic_config)
1224  type(io_configuration_type), intent(inout) :: io_configuration
1225  character(len=*), intent(in) :: field_name, field_namespace
1226  type(io_configuration_diagnostic_field_type), intent(out) :: diagnostic_config
1227 
1228  integer :: i
1229 
1230  do i=1, size(io_configuration%diagnostics)
1231  if (io_configuration%diagnostics(i)%name == field_name .and. &
1232  io_configuration%diagnostics(i)%namespace == field_namespace) then
1233  diagnostic_config=io_configuration%diagnostics(i)
1235  return
1236  end if
1237  end do
1240 
1246  logical function get_prognostic_field_configuration(io_configuration, field_name, field_namespace, &
1247  prognostic_config, prognostic_containing_data_defn)
1248  type(io_configuration_type), intent(inout) :: io_configuration
1249  character(len=*), intent(in) :: field_name, field_namespace
1250  type(io_configuration_field_type), intent(out) :: prognostic_config
1251  type(io_configuration_data_definition_type), intent(out), optional :: prognostic_containing_data_defn
1252 
1253  integer :: i, j
1254  do i=1, io_configuration%number_of_data_definitions
1255  do j=1, io_configuration%data_definitions(i)%number_of_data_fields
1256  if (io_configuration%data_definitions(i)%fields(j)%name == field_name .and. &
1257  io_configuration%data_definitions(i)%fields(j)%namespace == field_namespace) then
1258  prognostic_config=io_configuration%data_definitions(i)%fields(j)
1259  if (present(prognostic_containing_data_defn)) then
1260  prognostic_containing_data_defn=io_configuration%data_definitions(i)
1261  end if
1263  return
1264  end if
1265  end do
1266  end do
1269 
1274  subroutine add_in_specific_line(io_xml, reading_buffer)
1275  character, dimension(:), allocatable, intent(inout) :: io_xml
1276  character(len=*), intent(in) :: reading_buffer
1277 
1278  character, dimension(:), allocatable :: temp_io_xml
1279  integer :: i
1280 
1281  if (.not. allocated(io_xml)) then
1282  allocate(io_xml(len_trim(reading_buffer)))
1283  do i=1, len_trim(reading_buffer)
1284  io_xml(i)=reading_buffer(i:i)
1285  end do
1286  else
1287  allocate(temp_io_xml(size(io_xml)+len_trim(reading_buffer)))
1288  temp_io_xml(:size(io_xml)) = io_xml
1289  do i=1, len_trim(reading_buffer)
1290  temp_io_xml(size(io_xml)+i) = reading_buffer(i:i)
1291  end do
1292  call move_alloc(from=temp_io_xml,to=io_xml)
1293  end if
1294  end subroutine add_in_specific_line
1295 
1299  subroutine combine_xml_arrays(io_xml, other_xml_array)
1300  character, dimension(:), allocatable, intent(inout) :: io_xml, other_xml_array
1301 
1302  character, dimension(:), allocatable :: temp_io_xml
1303 
1304  if (.not. allocated(other_xml_array)) return
1305 
1306  if (.not. allocated(io_xml)) then
1307  allocate(io_xml(size(other_xml_array)), source=other_xml_array)
1308  else
1309  allocate(temp_io_xml(size(io_xml)+size(other_xml_array)))
1310  temp_io_xml(:size(io_xml)) = io_xml
1311  temp_io_xml(size(io_xml)+1:) = other_xml_array
1312  call move_alloc(from=temp_io_xml,to=io_xml)
1313  end if
1314  end subroutine combine_xml_arrays
1315 end module configuration_parser_mod
subroutine add_misc_member_to_diagnostic(element_name, attribute_names, attribute_values)
subroutine extend_file_writer_contents_array()
type(hashmap_type) options_database
Gets a specific generic element out of the list, stack, queue or map with the corresponding key...
Puts an integer key-value pair into the map.
integer, parameter, public lt_operator_type
subroutine add_in_dimensions(provided_options_database)
integer, parameter, public float_data_type
Definition: ioclient.F90:40
character(len=string_length), parameter default_file_title
subroutine, public xml_parse(raw_contents, start_element_callback, end_element_callback)
Parses some raw XML raw_contents The raw (unparsed) XML string start_element_callback Subroutine to c...
Definition: saxparser.F90:36
integer, parameter, public log_error
Only log ERROR messages.
Definition: logging.F90:11
integer, parameter, public array_field_type
Definition: ioclient.F90:38
subroutine, public extend_registered_moncs_array(io_configuration)
Extends the data definitions array from the current size to the current size + data size stride...
integer, parameter monc_size_stride
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.
logical function, public get_diagnostic_field_configuration(io_configuration, field_name, field_namespace, diagnostic_config)
Retrieves the diagnostics field configuration corresponding to a specific field name and returns whet...
integer, parameter, public boolean_data_type
Definition: ioclient.F90:40
subroutine add_include_to_file_writer(attribute_names, attribute_values)
subroutine extend_diagnostics_array()
Extends the rules array of a specific rule from the current size to the current size + data size stri...
integer, parameter, public lte_operator_type
Logging utility.
Definition: logging.F90:2
integer, parameter, public data_size_stride
integer, parameter, public default_precision
MPI communication type which we use for the prognostic and calculation data.
Definition: datadefn.F90:17
character(len=string_length) function retrieve_string_value(original_string, field_value_type)
integer, parameter, public io_state_type
integer, parameter, public field_type
logical function, public retrieve_monc_definition(io_configuration, source, monc_defn)
Retrieves a specific MONC definition from the configuration which matches a source PID...
subroutine replace_characters_in_string(original_string, new_string, to_replace)
Replaces specific characters in a string and returns a new string with this replaced by nothing (i...
integer, parameter, public mod_operator_type
Contains common definitions for the data and datatypes used by MONC.
Definition: datadefn.F90:2
A hashmap structure, the same as a map but uses hashing for greatly improved performance when storing...
Definition: collections.F90:94
Gets a specific integer element out of the list, stack, queue or map with the corresponding key...
Conversion between common inbuilt FORTRAN data types.
Definition: conversions.F90:5
integer, parameter, public double_data_type
Definition: ioclient.F90:40
Converts data types to strings.
Definition: conversions.F90:36
integer, parameter, public instantaneous_type
subroutine extend_field_array()
Extends the fields array of the current data definition from the current size to the current size + d...
Puts a string key-value pair into the map.
subroutine add_include_group_or_field_to_file_writer(attribute_names, attribute_values, number_of_contents)
subroutine define_group(attribute_names, attribute_values)
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
integer, parameter file_str_stride
logical function, public get_prognostic_field_configuration(io_configuration, field_name, field_namespace, prognostic_config, prognostic_containing_data_defn)
Retrieves the prognostic field configuration corresponding to a specific field name and returns wheth...
integer function get_field_type_from_attribute(field_type_str)
integer, parameter, public string_data_type
Definition: ioclient.F90:40
This defines some constants and procedures that are useful to the IO server and clients that call it...
Definition: ioclient.F90:3
integer, parameter, public integer_data_type
Definition: ioclient.F90:40
type(data_values_type) function, pointer get_data_value_from_hashmap_by_field_name(collection, field_name)
Retrieves the data value (wrapper) by field name or null if no entry was found in the provided collec...
Map data structure that holds string (length 20 maximum) key value pairs.
Definition: collections.F90:86
type(data_values_type) function, pointer get_data_value_from_map_by_field_name(collection, field_name)
Retrieves the data value (wrapper) by field name or null if no entry was found in the provided collec...
subroutine start_element_callback(element_name, number_of_attributes, attribute_names, attribute_values)
XML element start (opening) call back. This handles most of the configuration parsing.
This manages the Q variables and specifically the mapping between names and the index that they are s...
Definition: q_indices.F90:2
type(io_configuration_type), save building_config
IO configuration that is build built up from XML parsing.
Returns the number of elements in the collection.
integer function, public get_number_active_q_indices()
Gets the number of active Q indicies (i.e. those allocated to specific uses)
Definition: q_indices.F90:87
integer function get_field_datatype_from_attribute(field_data_type_str)
subroutine combine_xml_arrays(io_xml, other_xml_array)
Combines two IO XML arrays together (for instance one returned from a recursive include) ...
subroutine, public extend_inter_io_comm_array(io_configuration)
Extends the array of inter io communications from its current suze to current size+data_stride+curren...
type(hashset_type) data_field_names
Collection data structures.
Definition: collections.F90:7
integer, parameter or_operator_type
integer, parameter file_line_len
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.
subroutine, public configuration_parse(provided_options_database, raw_configuration, parsed_configuration)
This will parse an XML string into the IO configuration.
integer, parameter, public log_warn
Log WARNING and ERROR messages.
Definition: logging.F90:12
integer function get_total_number_fields(io_configuration)
Retrieves the total number of fields held in all data definitions.
integer, parameter, public multiply_operator_type
Configuration that representes the state of a registered MONC process.
Converts data types to real.
Definition: conversions.F90:58
integer, parameter, public string_length
Default length of strings.
Definition: datadefn.F90:10
integer, parameter, public gt_operator_type
subroutine handle_new_data_definition(attribute_names, attribute_values)
Creates a new data definition configuration item based upon the attributes supplied.
integer function get_field_index_from_name(attribute_names, search_name)
Given the name of an attribute will return the index of this in the names collection or 0 if it is no...
integer, parameter, public time_averaged_type
integer function, public get_number_field_dimensions(io_configuration, field_name, source, data_id)
Retrieves the number of field dimensions that a specific field has from a MONC process within a data ...
integer, parameter, public gte_operator_type
List data structure which implements a doubly linked list. This list will preserve its order...
Definition: collections.F90:60
real(kind=default_precision) function, public options_get_real(options_database, key, index)
Retrieves a real value from the database that matches the provided key.
character(len=string_length) data_handling_namespace
Adds a generic element to the end of the list.
integer function, public retrieve_data_definition(io_configuration, key)
Retrieves a specific data definition from the configuration which matches a key.
A SAX parser for XML files. This is used to parse the description of the data and rules...
Definition: saxparser.F90:5
integer, parameter, public add_operator_type
integer function, public options_get_integer(options_database, key, index)
Retrieves an integer value from the database that matches the provided key.
subroutine define_diagnostic(attribute_names, attribute_values)
Defines a new data handling rule.
Manages the options database. Contains administration functions and deduce runtime options from the c...
logical function, public options_get_logical(options_database, key, index)
Retrieves a logical value from the database that matches the provided key.
Frees up all the allocatable, heap, memory associated with a list, stack, queue or map...
subroutine process_xml_into_field_description(attribute_names, attribute_values)
Process XML into a field description by identifying the attributes of the field and storing these in ...
subroutine add_diagnostic_field_to_group(element_name, attribute_names, attribute_values)
type(data_values_type) function, pointer, public get_data_value_from_map_entry(map_entry)
Retrieves the data value (wrapper) by field name or null if no entry was found in the provided map en...
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...
subroutine define_file_writer(attribute_names, attribute_values)
integer, parameter, public eq_operator_type
integer, parameter and_operator_type
Hashset structure which will store unique strings. The hashing aspect means that lookup is very fast ...
subroutine extend_data_definition_array()
Extends the data definitions array from the current size to the current size + data size stride...
subroutine end_element_callback(element_name)
XML element end (closing) call back.
Configuration associated with the representation of a specific data field.
Converts data types to integers.
Definition: conversions.F90:47
integer, parameter, public scalar_field_type
Definition: ioclient.F90:38
Adds a string to the end of the list.
subroutine add_in_specific_line(io_xml, reading_buffer)
Adds a specific line into the io xml. The IO XML is always exactly the correct size, so here is either allocated or resized to match what the read buffer requires.
integer, parameter, public div_operator_type
logical function, public options_has_key(options_database, key)
Determines whether a specific key is in the database.
integer, parameter, public map_field_type
Field data type identifiers.
Definition: ioclient.F90:38
integer function process_sizing_definition(size_definitions, individual_str_defn)
subroutine handle_thread_pool_configuration(attribute_names, attribute_values)
Parses the XML configuration file to produce the io configuration description which contains the data...
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...
integer, parameter, public group_type
integer, parameter, public none_type
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...
integer, parameter, public subtract_operator_type