MONC
datautils.F90
Go to the documentation of this file.
1 
10  use logging_mod, only : log_error, log_log
11  implicit none
12 
13 #ifndef TEST_MODE
14  private
15 #endif
16 
17  integer, parameter :: array_step_threshold=204800
18 
26 contains
27 
33  integer function unpack_scalar_integer_from_bytedata(data, start_point)
34  character, dimension(:), intent(in) :: data
35  integer, intent(inout) :: start_point
36 
37  unpack_scalar_integer_from_bytedata=transfer(data(start_point:start_point+&
39  start_point=start_point+kind(unpack_scalar_integer_from_bytedata)
41 
47  logical function unpack_scalar_logical_from_bytedata(data, start_point)
48  character, dimension(:), intent(in) :: data
49  integer, intent(inout) :: start_point
50 
51  unpack_scalar_logical_from_bytedata=transfer(data(start_point:start_point+&
53  start_point=start_point+kind(unpack_scalar_logical_from_bytedata)
55 
61  character(len=STRING_LENGTH) function unpack_scalar_string_from_bytedata(data, start_point)
62  character, dimension(:), intent(in) :: data
63  integer, intent(inout) :: start_point
64 
66  start_point=start_point+string_length
68 
74  real function unpack_scalar_real_from_bytedata(data, start_point)
75  character, dimension(:), intent(in) :: data
76  integer, intent(inout) :: start_point
77 
78  unpack_scalar_real_from_bytedata=transfer(data(start_point:start_point+&
80  start_point=start_point+kind(unpack_scalar_real_from_bytedata)
82 
88  real(kind=double_precision) function unpack_scalar_dp_real_from_bytedata(data, start_point)
89  character, dimension(:), intent(in) :: data
90  integer, intent(inout) :: start_point
91 
92  unpack_scalar_dp_real_from_bytedata=transfer(data(start_point:start_point+&
94  start_point=start_point+kind(unpack_scalar_dp_real_from_bytedata)
96 
100  character(len=STRING_LENGTH) function get_action_attribute_string(action_attributes, field_name)
101  type(map_type), intent(inout) :: action_attributes
102  character(len=*), intent(in) :: field_name
103 
104  if (.not. c_contains(action_attributes, field_name)) call log_log(log_error, &
105  "You must provide the field name in the collective operation configuration")
106 
107  get_action_attribute_string=c_get_string(action_attributes, field_name)
108  end function get_action_attribute_string
109 
113  integer function get_action_attribute_integer(action_attributes, field_name)
114  type(map_type), intent(inout) :: action_attributes
115  character(len=*), intent(in) :: field_name
116 
117  character(len=STRING_LENGTH) :: str_val
118 
119  str_val=get_action_attribute_string(action_attributes, field_name)
120  if (.not. conv_is_integer(str_val)) call log_log(log_error, "Can not convert string '"//trim(str_val)//"' to an integer")
121  get_action_attribute_integer=conv_to_integer(str_val)
122  end function get_action_attribute_integer
123 
127  logical function get_action_attribute_logical(action_attributes, field_name)
128  type(map_type), intent(inout) :: action_attributes
129  character(len=*), intent(in) :: field_name
130 
131  if (c_contains(action_attributes, field_name)) then
132  get_action_attribute_logical=trim(c_get_string(action_attributes, field_name)) .eq. "true"
133  else
135  end if
136  end function get_action_attribute_logical
137 
138  !! Allows one to check if an optional field is present in the data being provided by a MONC
139  !! process or not
140  !! @param io_configuration Configuration of the IO server
141  !! @param source PID of the MONC process
142  !! @param data_id The ID of the data definition that is represented by the dump
143  !! @param key Key of the field to retrieve
144  !! @returns Whether the field is present or not
145  logical function is_field_present(io_configuration, source, data_id, key)
146  type(io_configuration_type), intent(inout) :: io_configuration
147  integer, intent(in) :: source, data_id
148  character(len=*), intent(in) :: key
149 
150  integer :: start_index, end_index, monc_location
151  class(*), pointer :: generic
152 
153  monc_location=c_get_integer(io_configuration%monc_to_index, conv_to_string(source))
154 
155  generic=>c_get_generic(io_configuration%registered_moncs(monc_location)%field_start_locations(data_id), key)
156  if (.not. associated(generic)) then
157  is_field_present=.false.
158  return
159  end if
160  start_index=conv_to_integer(generic, .false.)
161  generic=>c_get_generic(io_configuration%registered_moncs(monc_location)%field_end_locations(data_id), key)
162  if (.not. associated(generic)) then
163  is_field_present=.false.
164  return
165  end if
166  end_index=conv_to_integer(generic, .false.)
167 
168  is_field_present = end_index .gt. start_index
169  end function is_field_present
170 
177  integer function get_field_size(field_starts, field_ends, key, data_type)
178  type(map_type), intent(inout) :: field_starts, field_ends
179  character(len=*), intent(in) :: key
180  integer, intent(in) :: data_type
181 
182  integer :: start_index, end_index, element_size
183  real(kind=double_precision) :: dreal
184  real(kind=single_precision) :: sreal
185 
186  start_index=c_get_integer(field_starts, key)
187  end_index=c_get_integer(field_ends, key)
188 
189  if (data_type == integer_data_type) then
190  element_size=kind(start_index)
191  else if (data_type == double_data_type) then
192  element_size=kind(dreal)
193  else if (data_type == float_data_type) then
194  element_size=kind(sreal)
195  else if (data_type == string_data_type) then
196  element_size=string_length
197  end if
198  get_field_size=((end_index-start_index)+1)/element_size
199  end function get_field_size
200 
207  type(map_type) function get_map(field_starts, field_ends, data_dump, key)
208  type(map_type), intent(inout) :: field_starts, field_ends
209  character, dimension(:), allocatable, intent(in) :: data_dump
210  character(len=*), intent(in) :: key
211 
212  integer :: start_index, end_index, elements, i
213  character(len=STRING_LENGTH) :: retrieved1, retrieved2
214 
215  if (.not. c_contains(field_starts, key) .or. .not. c_contains(field_ends, key)) &
216  call log_log(log_error, "Field name `"//key//"` not found in the data definition")
217 
218  start_index=c_get_integer(field_starts, key)
219  end_index=c_get_integer(field_ends, key)
220 
221  elements = (end_index+1 - start_index) / (string_length*2)
222 
223  do i=1, elements
224  retrieved1=transfer(data_dump(start_index:start_index+string_length-1), retrieved1)
225  start_index=start_index+string_length
226  retrieved2=transfer(data_dump(start_index:start_index+string_length-1), retrieved2)
227  start_index=start_index+string_length
228  call c_put_string(get_map, retrieved1, retrieved2)
229  end do
230  end function get_map
231 
239  type(map_type) function get_map_from_monc(io_configuration, source, data_id, data_dump, key)
240  type(io_configuration_type), intent(inout) :: io_configuration
241  integer, intent(in) :: source, data_id
242  character, dimension(:), allocatable, intent(in) :: data_dump
243  character(len=*), intent(in) :: key
244 
245  integer :: monc_location
246 
247  monc_location=c_get_integer(io_configuration%monc_to_index, conv_to_string(source))
248 
249  get_map_from_monc=get_map(io_configuration%registered_moncs(monc_location)%field_start_locations(data_id), &
250  io_configuration%registered_moncs(monc_location)%field_end_locations(data_id), data_dump, key)
251  end function get_map_from_monc
252 
259  function get_string(field_starts, field_ends, data_dump, key)
260  type(map_type), intent(inout) :: field_starts, field_ends
261  character, dimension(:), allocatable, intent(in) :: data_dump
262  character(len=*), intent(in) :: key
263  character(len=STRING_LENGTH) :: get_string
264 
265  integer :: start_index, end_index
266 
267  if (.not. c_contains(field_starts, key) .or. .not. c_contains(field_ends, key)) &
268  call log_log(log_error, "Field name `"//key//"` not found in the data definition")
269 
270  start_index=c_get_integer(field_starts, key)
271  end_index=c_get_integer(field_ends, key)
272 
273  get_string=transfer(data_dump(start_index:end_index), get_string)
274  end function get_string
275 
283  function get_string_from_monc(io_configuration, source, data_id, data_dump, key)
284  type(io_configuration_type), intent(inout) :: io_configuration
285  integer, intent(in) :: source, data_id
286  character, dimension(:), allocatable, intent(in) :: data_dump
287  character(len=*), intent(in) :: key
288  character(len=STRING_LENGTH) :: get_string_from_monc
289 
290  integer :: monc_location
291 
292  monc_location=c_get_integer(io_configuration%monc_to_index, conv_to_string(source))
293 
294  get_string_from_monc=get_string(io_configuration%registered_moncs(monc_location)%field_start_locations(data_id), &
295  io_configuration%registered_moncs(monc_location)%field_end_locations(data_id), data_dump, key)
296  end function get_string_from_monc
297 
304  logical function get_scalar_logical(field_starts, field_ends, data_dump, key)
305  type(map_type), intent(inout) :: field_starts, field_ends
306  character, dimension(:), allocatable, intent(in) :: data_dump
307  character(len=*), intent(in) :: key
308 
309  integer :: start_index, end_index
310 
311  if (.not. c_contains(field_starts, key) .or. .not. c_contains(field_ends, key)) &
312  call log_log(log_error, "Field name `"//key//"` not found in the data definition")
313 
314  start_index=c_get_integer(field_starts, key)
315  end_index=c_get_integer(field_ends, key)
316 
317  get_scalar_logical=transfer(data_dump(start_index:end_index), get_scalar_logical)
318  end function get_scalar_logical
319 
327  logical function get_scalar_logical_from_monc(io_configuration, source, data_id, data_dump, key)
328  type(io_configuration_type), intent(inout) :: io_configuration
329  integer, intent(in) :: source, data_id
330  character, dimension(:), allocatable, intent(in) :: data_dump
331  character(len=*), intent(in) :: key
332 
333  integer :: monc_location
334 
335  monc_location=c_get_integer(io_configuration%monc_to_index, conv_to_string(source))
336 
338  io_configuration%registered_moncs(monc_location)%field_start_locations(data_id), &
339  io_configuration%registered_moncs(monc_location)%field_end_locations(data_id), data_dump, key)
340  end function get_scalar_logical_from_monc
341 
348  integer function get_scalar_integer(field_starts, field_ends, data_dump, key)
349  type(map_type), intent(inout) :: field_starts, field_ends
350  character, dimension(:), allocatable, intent(in) :: data_dump
351  character(len=*), intent(in) :: key
352 
353  integer :: start_index, end_index
354 
355  if (.not. c_contains(field_starts, key) .or. .not. c_contains(field_ends, key)) &
356  call log_log(log_error, "Field name `"//key//"` not found in the data definition")
357 
358  start_index=c_get_integer(field_starts, key)
359  end_index=c_get_integer(field_ends, key)
360 
361  get_scalar_integer=transfer(data_dump(start_index:end_index), get_scalar_integer)
362  end function get_scalar_integer
363 
371  integer function get_scalar_integer_from_monc(io_configuration, source, data_id, data_dump, key)
372  type(io_configuration_type), intent(inout) :: io_configuration
373  integer, intent(in) :: source, data_id
374  character, dimension(:), allocatable, intent(in) :: data_dump
375  character(len=*), intent(in) :: key
376 
377  integer :: monc_location
378 
379  monc_location=c_get_integer(io_configuration%monc_to_index, conv_to_string(source))
380 
382  io_configuration%registered_moncs(monc_location)%field_start_locations(data_id), &
383  io_configuration%registered_moncs(monc_location)%field_end_locations(data_id), data_dump, key)
384  end function get_scalar_integer_from_monc
385 
392  real(kind=double_precision) function get_scalar_real(field_starts, field_ends, data_dump, key)
393  type(map_type), intent(inout) :: field_starts, field_ends
394  character, dimension(:), allocatable, intent(in) :: data_dump
395  character(len=*), intent(in) :: key
396 
397  integer :: start_index, end_index
398 
399  if (.not. c_contains(field_starts, key) .or. .not. c_contains(field_ends, key)) &
400  call log_log(log_error, "Field name `"//key//"` not found in the data definition")
401 
402  start_index=c_get_integer(field_starts, key)
403  end_index=c_get_integer(field_ends, key)
404 
405  get_scalar_real=transfer(data_dump(start_index:end_index), get_scalar_real)
406  end function get_scalar_real
407 
415  real(kind=double_precision) function get_scalar_real_from_monc(io_configuration, source, data_id, data_dump, key)
416  type(io_configuration_type), intent(inout) :: io_configuration
417  integer, intent(in) :: source, data_id
418  character, dimension(:), allocatable, intent(in) :: data_dump
419  character(len=*), intent(in) :: key
420 
421  integer :: monc_location
422 
423  monc_location=c_get_integer(io_configuration%monc_to_index, conv_to_string(source))
424 
426  io_configuration%registered_moncs(monc_location)%field_start_locations(data_id), &
427  io_configuration%registered_moncs(monc_location)%field_end_locations(data_id), data_dump, key)
428  end function get_scalar_real_from_monc
429 
437  function get_array_double(field_starts, field_ends, data_dump, key)
438  type(map_type), intent(inout) :: field_starts, field_ends
439  character, dimension(:), allocatable, intent(in) :: data_dump
440  character(len=*), intent(in) :: key
441  real(kind=double_precision), dimension(:), allocatable :: get_array_double
442 
443  integer :: start_index, end_index, elements, start_e, end_e, current_start_index, current_end_index
444 
445  if (.not. c_contains(field_starts, key) .or. .not. c_contains(field_ends, key)) &
446  call log_log(log_error, "Field name `"//key//"` not found in the data definition")
447 
448  start_index=c_get_integer(field_starts, key)
449  end_index=c_get_integer(field_ends, key)
450 
451  elements = ceiling((end_index - start_index) / real(kind(get_array_double)))
452 
453  allocate(get_array_double(elements))
454  if (elements .ge. array_step_threshold) then
455  current_start_index=start_index
456  do while (current_start_index .lt. end_index)
457  current_end_index=current_start_index+array_step_threshold-1
458  if (current_end_index .gt. end_index) current_end_index=end_index
459  start_e=((current_start_index-start_index)/kind(get_array_double))+1
460  end_e=ceiling((current_end_index-start_index)/real(kind(get_array_double)))
461  get_array_double(start_e:end_e)=transfer(data_dump(current_start_index:current_end_index), get_array_double)
462  current_start_index=current_start_index+array_step_threshold
463  end do
464  else
465  get_array_double=transfer(data_dump(start_index:end_index), get_array_double, elements)
466  end if
467  end function get_array_double
468 
477  function get_array_double_from_monc(io_configuration, source, data_id, data_dump, key)
478  type(io_configuration_type), intent(inout) :: io_configuration
479  integer, intent(in) :: source, data_id
480  character, dimension(:), allocatable, intent(in) :: data_dump
481  character(len=*), intent(in) :: key
482  real(kind=double_precision), dimension(:), allocatable :: get_array_double_from_monc
483 
484  integer :: monc_location
485 
486  monc_location=c_get_integer(io_configuration%monc_to_index, conv_to_string(source))
487 
489  io_configuration%registered_moncs(monc_location)%field_start_locations(data_id), &
490  io_configuration%registered_moncs(monc_location)%field_end_locations(data_id), data_dump, key)
491  end function get_array_double_from_monc
492 
500  function get_array_integer(field_starts, field_ends, data_dump, key)
501  type(map_type), intent(inout) :: field_starts, field_ends
502  character, dimension(:), allocatable, intent(in) :: data_dump
503  character(len=*), intent(in) :: key
504  integer, dimension(:), allocatable :: get_array_integer
505 
506  integer :: start_index, end_index, elements
507 
508  if (.not. c_contains(field_starts, key) .or. .not. c_contains(field_ends, key)) &
509  call log_log(log_error, "Field name `"//key//"` not found in the data definition")
510 
511  start_index=c_get_integer(field_starts, key)
512  end_index=c_get_integer(field_ends, key)
513 
514  elements = (end_index - start_index) / kind(get_array_integer)
515 
516  allocate(get_array_integer(elements))
517  get_array_integer=transfer(data_dump(start_index:end_index), get_array_integer)
518  end function get_array_integer
519 
528  function get_array_integer_from_monc(io_configuration, source, data_id, data_dump, key)
529  type(io_configuration_type), intent(inout) :: io_configuration
530  integer, intent(in) :: source, data_id
531  character, dimension(:), allocatable, intent(in) :: data_dump
532  character(len=*), intent(in) :: key
533  integer, dimension(:), allocatable :: get_array_integer_from_monc
534 
535  integer :: monc_location
536 
537  monc_location=c_get_integer(io_configuration%monc_to_index, conv_to_string(source))
538 
540  io_configuration%registered_moncs(monc_location)%field_start_locations(data_id), &
541  io_configuration%registered_moncs(monc_location)%field_end_locations(data_id), data_dump, key)
542  end function get_array_integer_from_monc
543 
556  subroutine get_2darray_double_from_monc(io_configuration, source, data_id, data_dump, key, target_data, size1, size2)
557  type(io_configuration_type), intent(inout) :: io_configuration
558  integer, intent(in) :: source, data_id, size1, size2
559  character, dimension(:), allocatable, intent(in) :: data_dump
560  character(len=*), intent(in) :: key
561  real(kind=double_precision), dimension(:,:), pointer, contiguous, intent(inout) :: target_data
562 
563  integer :: monc_location
564 
565  monc_location=c_get_integer(io_configuration%monc_to_index, conv_to_string(source))
566 
567  call get_2darray_double(io_configuration%registered_moncs(monc_location)%field_start_locations(data_id), &
568  io_configuration%registered_moncs(monc_location)%field_end_locations(data_id), data_dump, key, target_data, &
569  size1, size2)
570  end subroutine get_2darray_double_from_monc
571 
583  subroutine get_2darray_double(field_starts, field_ends, data_dump, key, target_data, size1, size2)
584  type(map_type), intent(inout) :: field_starts, field_ends
585  integer, intent(in) :: size1, size2
586  character, dimension(:), allocatable, intent(in) :: data_dump
587  character(len=*), intent(in) :: key
588  real(kind=double_precision), dimension(:,:), pointer, contiguous, intent(inout) :: target_data
589 
590  integer :: start_index, end_index, element_size
591  real(kind=double_precision), dimension(:), pointer :: temp_data
592 
593  ! Pointer bounds remapping as transfer needs 1D array but for performance don't want to allocate another array and copy using reshape
594  temp_data(1:size1*size2)=>target_data
595 
596  if (.not. c_contains(field_starts, key) .or. .not. c_contains(field_ends, key)) &
597  call log_log(log_error, "Field name `"//key//"` not found in the data definition")
598 
599  start_index=c_get_integer(field_starts, key)
600  end_index=c_get_integer(field_ends, key)
601 
602  element_size=(end_index-start_index) / kind(target_data)
603 
604  temp_data=transfer(data_dump(start_index:end_index), temp_data)
605  end subroutine get_2darray_double
606 
619  subroutine get_3darray_double(field_starts, field_ends, data_dump, key, target_data, size1, size2, size3)
620  type(map_type), intent(inout) :: field_starts, field_ends
621  integer, intent(in) :: size1, size2, size3
622  character, dimension(:), allocatable, intent(in) :: data_dump
623  character(len=*), intent(in) :: key
624  real(kind=double_precision), dimension(:,:,:), pointer, contiguous, intent(inout) :: target_data
625 
626  integer :: start_index, end_index, element_size
627  real(kind=double_precision), dimension(:), pointer :: temp_data
628 
629  ! Pointer bounds remapping as transfer needs 1D array but for performance don't want to allocate another array and copy using reshape
630  temp_data(1:size1*size2*size3)=>target_data
631 
632  if (.not. c_contains(field_starts, key) .or. .not. c_contains(field_ends, key)) &
633  call log_log(log_error, "Field name `"//key//"` not found in the data definition")
634 
635  start_index=c_get_integer(field_starts, key)
636  end_index=c_get_integer(field_ends, key)
637 
638  element_size=(end_index-start_index) / kind(target_data)
639 
640  temp_data=transfer(data_dump(start_index:end_index), temp_data)
641  end subroutine get_3darray_double
642 
656  subroutine get_3darray_double_from_monc(io_configuration, source, data_id, data_dump, key, target_data, size1, size2, size3)
657  type(io_configuration_type), intent(inout) :: io_configuration
658  integer, intent(in) :: source, data_id, size1, size2, size3
659  character, dimension(:), allocatable, intent(in) :: data_dump
660  character(len=*), intent(in) :: key
661  real(kind=double_precision), dimension(:,:,:), pointer, contiguous, intent(inout) :: target_data
662 
663  integer :: monc_location
664 
665  monc_location=c_get_integer(io_configuration%monc_to_index, conv_to_string(source))
666 
667  call get_3darray_double(io_configuration%registered_moncs(monc_location)%field_start_locations(data_id), &
668  io_configuration%registered_moncs(monc_location)%field_end_locations(data_id), data_dump, key, target_data, &
669  size1, size2, size3)
670  end subroutine get_3darray_double_from_monc
671 
685  subroutine get_4darray_double(field_starts, field_ends, data_dump, key, target_data, size1, size2, size3, size4)
686  type(map_type), intent(inout) :: field_starts, field_ends
687  integer, intent(in) :: size1, size2, size3, size4
688  character, dimension(:), allocatable, intent(in) :: data_dump
689  character(len=*), intent(in) :: key
690  real(kind=double_precision), dimension(:,:,:,:), pointer, contiguous, intent(inout) :: target_data
691 
692  integer :: start_index, end_index, element_size
693  real(kind=double_precision), dimension(:), pointer :: temp_data
694 
695  ! Pointer bounds remapping as transfer needs 1D array but for performance don't want to allocate another array and copy using reshape
696  temp_data(1:size1*size2*size3*size4)=>target_data
697 
698  if (.not. c_contains(field_starts, key) .or. .not. c_contains(field_ends, key)) &
699  call log_log(log_error, "Field name `"//key//"` not found in the data definition")
700 
701  start_index=c_get_integer(field_starts, key)
702  end_index=c_get_integer(field_ends, key)
703 
704  element_size=(end_index-start_index) / kind(target_data)
705 
706  temp_data=transfer(data_dump(start_index:end_index), temp_data)
707  end subroutine get_4darray_double
708 
723  subroutine get_4darray_double_from_monc(io_configuration, source, data_id, data_dump, key, target_data, size1, &
724  size2, size3, size4)
725  type(io_configuration_type), intent(inout) :: io_configuration
726  integer, intent(in) :: source, data_id, size1, size2, size3, size4
727  character, dimension(:), allocatable, intent(in) :: data_dump
728  character(len=*), intent(in) :: key
729  real(kind=double_precision), dimension(:,:,:,:), pointer, contiguous, intent(inout) :: target_data
730 
731  integer :: monc_location
732 
733  monc_location=c_get_integer(io_configuration%monc_to_index, conv_to_string(source))
734 
735  call get_4darray_double(io_configuration%registered_moncs(monc_location)%field_start_locations(data_id), &
736  io_configuration%registered_moncs(monc_location)%field_end_locations(data_id), data_dump, key, target_data, &
737  size1, size2, size3, size4)
738  end subroutine get_4darray_double_from_monc
739 end module data_utils_mod
logging_mod::log_error
integer, parameter, public log_error
Only log ERROR messages.
Definition: logging.F90:11
conversions_mod
Conversion between common inbuilt FORTRAN data types.
Definition: conversions.F90:5
collections_mod::map_type
Map data structure that holds string (length 20 maximum) key value pairs.
Definition: collections.F90:86
io_server_client_mod::float_data_type
integer, parameter, public float_data_type
Definition: ioclient.F90:40
io_server_client_mod::string_data_type
integer, parameter, public string_data_type
Definition: ioclient.F90:40
data_utils_mod::is_field_present
logical function, public is_field_present(io_configuration, source, data_id, key)
Definition: datautils.F90:146
conversions_mod::conv_to_integer
Converts data types to integers.
Definition: conversions.F90:49
data_utils_mod::get_2darray_double
subroutine, public get_2darray_double(field_starts, field_ends, data_dump, key, target_data, size1, size2)
Retreives a 2D array of doubles with a corresponding key from the raw data dump. The size depends on ...
Definition: datautils.F90:584
data_utils_mod
Contains functionality for managing and extracting data from the raw data dumps that the IO server re...
Definition: datautils.F90:3
io_server_client_mod::integer_data_type
integer, parameter, public integer_data_type
Definition: ioclient.F90:40
data_utils_mod::get_3darray_double
subroutine, public get_3darray_double(field_starts, field_ends, data_dump, key, target_data, size1, size2, size3)
Retreives a 3D array of doubles with a corresponding key from the raw data dump. The size depends on ...
Definition: datautils.F90:620
collections_mod
Collection data structures.
Definition: collections.F90:7
data_utils_mod::array_step_threshold
integer, parameter array_step_threshold
Definition: datautils.F90:17
collections_mod::c_get_string
Gets a specific string element out of the list, stack, queue or map with the corresponding key.
Definition: collections.F90:388
data_utils_mod::get_scalar_integer
integer function, public get_scalar_integer(field_starts, field_ends, data_dump, key)
Retrieves a single integer element (scalar) from the data dump.
Definition: datautils.F90:349
data_utils_mod::get_action_attribute_integer
integer function, public get_action_attribute_integer(action_attributes, field_name)
Retrieves the name of a field from the attributes specified in the configuration.
Definition: datautils.F90:114
data_utils_mod::get_map
type(map_type) function, public get_map(field_starts, field_ends, data_dump, key)
Retrieves a map data structure with key->value pairs, each of which are strings.
Definition: datautils.F90:208
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
data_utils_mod::get_2darray_double_from_monc
subroutine, public get_2darray_double_from_monc(io_configuration, source, data_id, data_dump, key, target_data, size1, size2)
Retreives a 2D array of doubles with a corresponding key from the raw data dump. The size depends on ...
Definition: datautils.F90:557
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
data_utils_mod::get_scalar_integer_from_monc
integer function, public get_scalar_integer_from_monc(io_configuration, source, data_id, data_dump, key)
Retrieves a single integer element (scalar) from the data dump.
Definition: datautils.F90:372
collections_mod::c_get_generic
Gets a specific generic element out of the list, stack, queue or map with the corresponding key.
Definition: collections.F90:367
io_server_client_mod::double_data_type
integer, parameter, public double_data_type
Definition: ioclient.F90:40
collections_mod::c_contains
Determines whether or not a map contains a specific key.
Definition: collections.F90:447
data_utils_mod::get_array_double_from_monc
real(kind=double_precision) function, dimension(:), allocatable, public get_array_double_from_monc(io_configuration, source, data_id, data_dump, key)
Retreives an array of doubles with a corresponding key from the raw data dump. The size depends on th...
Definition: datautils.F90:478
data_utils_mod::get_string
character(len=string_length) function, public get_string(field_starts, field_ends, data_dump, key)
Retrieves a string from the data dump.
Definition: datautils.F90:260
data_utils_mod::get_string_from_monc
character(len=string_length) function, public get_string_from_monc(io_configuration, source, data_id, data_dump, key)
Retrieves a string from the data dump.
Definition: datautils.F90:284
datadefn_mod::single_precision
integer, parameter, public single_precision
Single precision (32 bit) kind.
Definition: datadefn.F90:13
data_utils_mod::get_scalar_logical
logical function, public get_scalar_logical(field_starts, field_ends, data_dump, key)
Retrieves a single logical element (scalar) from the data dump.
Definition: datautils.F90:305
conversions_mod::conv_to_string
Converts data types to strings.
Definition: conversions.F90:38
data_utils_mod::get_field_size
integer function, public get_field_size(field_starts, field_ends, key, data_type)
Retrieves the size of a field from the data definition.
Definition: datautils.F90:178
data_utils_mod::unpack_scalar_integer_from_bytedata
integer function, public unpack_scalar_integer_from_bytedata(data, start_point)
Unpacks a scalar integer from some byte data, this is a very simple unpack routine wrapping the trans...
Definition: datautils.F90:34
configuration_parser_mod::io_configuration_type
Overall IO configuration.
Definition: configurationparser.F90:104
conversions_mod::conv_is_integer
Determines whether a data item can be represented as an integer or not.
Definition: conversions.F90:81
collections_mod::c_put_string
Puts a string key-value pair into the map.
Definition: collections.F90:331
data_utils_mod::unpack_scalar_string_from_bytedata
character(len=string_length) function, public unpack_scalar_string_from_bytedata(data, start_point)
Unpacks a string from some byte data with default length, this is a very simple unpack routine wrappi...
Definition: datautils.F90:62
logging_mod
Logging utility.
Definition: logging.F90:2
data_utils_mod::get_scalar_logical_from_monc
logical function, public get_scalar_logical_from_monc(io_configuration, source, data_id, data_dump, key)
Retrieves a single logical element (scalar) from the data dump.
Definition: datautils.F90:328
datadefn_mod::double_precision
integer, parameter, public double_precision
Double precision (64 bit) kind.
Definition: datadefn.F90:14
datadefn_mod
Contains common definitions for the data and datatypes used by MONC.
Definition: datadefn.F90:2
datadefn_mod::string_length
integer, parameter, public string_length
Default length of strings.
Definition: datadefn.F90:10
data_utils_mod::get_action_attribute_logical
logical function, public get_action_attribute_logical(action_attributes, field_name)
Retrieves a logical value from the attribute which corresponds to a specific key.
Definition: datautils.F90:128
data_utils_mod::get_4darray_double
subroutine, public get_4darray_double(field_starts, field_ends, data_dump, key, target_data, size1, size2, size3, size4)
Retreives a 4D array of doubles with a corresponding key from the raw data dump. The size depends on ...
Definition: datautils.F90:686
data_utils_mod::get_array_double
real(kind=double_precision) function, dimension(:), allocatable, public get_array_double(field_starts, field_ends, data_dump, key)
Retreives an array of doubles with a corresponding key from the raw data dump. The size depends on th...
Definition: datautils.F90:438
data_utils_mod::unpack_scalar_real_from_bytedata
real function, public unpack_scalar_real_from_bytedata(data, start_point)
Unpacks a scalar real from some byte data, this is a very simple unpack routine wrapping the transfer...
Definition: datautils.F90:75
data_utils_mod::get_scalar_real
real(kind=double_precision) function, public get_scalar_real(field_starts, field_ends, data_dump, key)
Retreives a scalar real with a corresponding key from the raw data dump.
Definition: datautils.F90:393
data_utils_mod::unpack_scalar_dp_real_from_bytedata
real(kind=double_precision) function, public unpack_scalar_dp_real_from_bytedata(data, start_point)
Unpacks a double precision scalar real from some byte data, this is a very simple unpack routine wrap...
Definition: datautils.F90:89
data_utils_mod::get_scalar_real_from_monc
real(kind=double_precision) function, public get_scalar_real_from_monc(io_configuration, source, data_id, data_dump, key)
Retreives a scalar real with a corresponding key from the raw data dump.
Definition: datautils.F90:416
data_utils_mod::get_map_from_monc
type(map_type) function, public get_map_from_monc(io_configuration, source, data_id, data_dump, key)
Retrieves a map data structure with key->value pairs, each of which are strings.
Definition: datautils.F90:240
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
io_server_client_mod::boolean_data_type
integer, parameter, public boolean_data_type
Definition: ioclient.F90:40
data_utils_mod::get_4darray_double_from_monc
subroutine, public get_4darray_double_from_monc(io_configuration, source, data_id, data_dump, key, target_data, size1, size2, size3, size4)
Retreives a 4D array of doubles with a corresponding key from the raw data dump. The size depends on ...
Definition: datautils.F90:725
configuration_parser_mod
Parses the XML configuration file to produce the io configuration description which contains the data...
Definition: configurationparser.F90:3
data_utils_mod::get_3darray_double_from_monc
subroutine, public get_3darray_double_from_monc(io_configuration, source, data_id, data_dump, key, target_data, size1, size2, size3)
Retreives a 3D array of doubles with a corresponding key from the raw data dump. The size depends on ...
Definition: datautils.F90:657
data_utils_mod::get_array_integer
integer function, dimension(:), allocatable, public get_array_integer(field_starts, field_ends, data_dump, key)
Retreives an array of integers with a corresponding key from the raw data dump. The size depends on t...
Definition: datautils.F90:501
data_utils_mod::unpack_scalar_logical_from_bytedata
logical function, public unpack_scalar_logical_from_bytedata(data, start_point)
Unpacks a scalar logical from some byte data, this is a very simple unpack routine wrapping the trans...
Definition: datautils.F90:48
data_utils_mod::get_action_attribute_string
character(len=string_length) function, public get_action_attribute_string(action_attributes, field_name)
Retrieves the name of a field from the attributes specified in the configuration.
Definition: datautils.F90:101
data_utils_mod::get_array_integer_from_monc
integer function, dimension(:), allocatable, public get_array_integer_from_monc(io_configuration, source, data_id, data_dump, key)
Retreives an array of integers with a corresponding key from the raw data dump. The size depends on t...
Definition: datautils.F90:529