MONC
writer_field_manager.F90
Go to the documentation of this file.
1 
25  implicit none
26 
27 #ifndef TEST_MODE
28  private
29 #endif
30 
32  character(len=STRING_LENGTH) :: field_name, field_namespace
33  integer :: timestep, frequency, source
34  type(data_values_type), allocatable :: field_values
35  real(kind=DEFAULT_PRECISION) :: time
37 
39  type(hashmap_type) :: timestep_to_value
40  integer :: access_mutex, last_timestep_access, frequency
41  end type field_ordering_type
42 
47 
48  integer, volatile :: field_lock
49  type(hashmap_type), volatile :: field_orderings
50 
53 contains
54 
58  subroutine initialise_writer_field_manager(io_configuration, continuation_run)
59  type(io_configuration_type), intent(inout) :: io_configuration
60  logical, intent(in) :: continuation_run
61 
65  if (continuation_run) then
67  end if
68  end subroutine initialise_writer_field_manager
69 
73  end subroutine finalise_writer_field_manager
74 
79  logical function is_write_field_manager_up_to_date(timestep)
80  integer, intent(in) :: timestep
81 
82  type(iterator_type) :: iterator
83  type(mapentry_type) :: mapentry
84  class(*), pointer :: generic
85 
89  do while (c_has_next(iterator))
90  mapentry=c_next_mapentry(iterator)
91  generic=>c_get_generic(mapentry)
92  select type(generic)
93  type is (field_ordering_type)
94  if (generic%last_timestep_access .lt. timestep) then
96  exit
97  end if
98  end select
99  end do
102 
109  subroutine provide_monc_data_to_writer_federator(io_configuration, source, data_id, data_dump)
110  type(io_configuration_type), intent(inout) :: io_configuration
111  integer, intent(in) :: source, data_id
112  character, dimension(:), allocatable, intent(in) :: data_dump
113 
114  integer :: i, num_fields, timestep
115  character(len=STRING_LENGTH) :: field_name, field_namespace
116  real(kind=DEFAULT_PRECISION) :: time
117  type(data_values_type) :: monc_value
118  logical :: terminated_case
119 
120  if (is_field_present(io_configuration, source, data_id, "timestep") .and. &
121  is_field_present(io_configuration, source, data_id, "time")) then
122  timestep=get_scalar_integer_from_monc(io_configuration, source, data_id, data_dump, "timestep")
123  time=get_scalar_real_from_monc(io_configuration, source, data_id, data_dump, "time")
124 
125  if (is_field_present(io_configuration, source, data_id, "terminated")) then
126  terminated_case=get_scalar_logical_from_monc(io_configuration, source, data_id, data_dump, "terminated") .and. &
127  io_configuration%data_definitions(data_id)%send_on_terminate
128  else
129  terminated_case=.false.
130  end if
131 
132  num_fields=io_configuration%data_definitions(data_id)%number_of_data_fields
133 
134  do i=1, num_fields
135  field_name=io_configuration%data_definitions(data_id)%fields(i)%name
136  field_namespace=io_configuration%data_definitions(data_id)%fields(i)%namespace
137  if (is_field_present(io_configuration, source, data_id, field_name) .and. &
138  (is_field_used_by_writer_federator(field_name, field_namespace) .or. is_field_split_on_q(field_name))) then
139  monc_value=get_value_from_monc_data(io_configuration, source, data_id, data_dump, field_name, field_namespace)
140  call provide_field_to_writer_federator_src(io_configuration, field_name, field_namespace, monc_value, timestep, time, &
141  io_configuration%data_definitions(data_id)%frequency, source, terminated_case)
142 
143  !deallocate(monc_value)
144  end if
145  end do
146  else
147  call log_log(log_warn, "Can not run pass MONC fields to writer federator without a time and timestep")
148  end if
150 
158  function get_value_from_monc_data(io_configuration, source, data_id, data_dump, field_name, field_namespace)
159  type(io_configuration_type), intent(inout) :: io_configuration
160  integer, intent(in) :: source, data_id
161  character, dimension(:), allocatable, intent(in) :: data_dump
162  character(len=*), intent(in) :: field_name, field_namespace
163  type(data_values_type) :: get_value_from_monc_data
164  type(map_type) :: retrieved_map
165  type(iterator_type) :: iterator
166  type(mapentry_type) :: map_entry
167 
168  integer :: field_data_type, field_field_type, i
169  integer, dimension(:), allocatable :: int_values
170 
171  call get_type_of_field(io_configuration%data_definitions(data_id)%fields, field_name, field_namespace, &
172  field_field_type, field_data_type)
173  if (field_data_type == 0) then
174  call log_log(log_error, "No data type for field '"//trim(field_name)//"'")
175  end if
176 
177  if (field_data_type == double_data_type) then
178  get_value_from_monc_data%values=get_array_double_from_monc(io_configuration, source, data_id, data_dump, field_name)
179  get_value_from_monc_data%data_type=double_data_type
180  else if (field_data_type == integer_data_type) then
181  get_value_from_monc_data%data_type=double_data_type
182  int_values=get_array_integer_from_monc(io_configuration, source, data_id, data_dump, field_name)
183  allocate(get_value_from_monc_data%values(size(int_values)))
184  do i=1, size(int_values)
185  get_value_from_monc_data%values(i)=conv_to_real(int_values(i))
186  end do
187  deallocate(int_values)
188  else if (field_data_type == string_data_type) then
189  get_value_from_monc_data%data_type=string_data_type
190  if (field_field_type == scalar_field_type) then
191  allocate(get_value_from_monc_data%string_values(1))
192  get_value_from_monc_data%string_values(1)=get_string_from_monc(io_configuration, source, data_id, data_dump, field_name)
193  else if (field_field_type == map_field_type) then
194  get_value_from_monc_data%map_values=get_map_from_monc(io_configuration, source, data_id, data_dump, field_name)
195  end if
196  end if
197  end function get_value_from_monc_data
198 
203  subroutine get_type_of_field(fields, field_name, field_namespace, field_type, data_type)
204  type(io_configuration_field_type), dimension(:), intent(in) :: fields
205  character(len=*), intent(in) :: field_name, field_namespace
206  integer, intent(out) :: field_type, data_type
207 
208  integer :: i
209 
210  do i=1, size(fields)
211  if (fields(i)%name .eq. field_name .and. fields(i)%namespace .eq. field_namespace) then
212  data_type=fields(i)%data_type
213  field_type=fields(i)%field_type
214  return
215  end if
216  end do
217  data_type=0
218  field_type=0
219  end subroutine get_type_of_field
220 
221  subroutine provide_field_to_writer_federator_rvalues_src(io_configuration, field_name, field_namespace, &
222  field_values, timestep, time, frequency, source)
223  type(io_configuration_type), intent(inout) :: io_configuration
224  character(len=*), intent(in) :: field_name, field_namespace
225  integer, intent(in) :: timestep, frequency, source
226  real(kind=DEFAULT_PRECISION), dimension(:), intent(in) :: field_values
227  real(kind=DEFAULT_PRECISION), intent(in) :: time
228 
229  type(data_values_type) :: packaged_data
230 
231  allocate(packaged_data%values(size(field_values)))
232  packaged_data%values=field_values
233  packaged_data%data_type=double_data_type
234  call provide_field_to_writer_federator_src(io_configuration, field_name, field_namespace, packaged_data, &
235  timestep, time, frequency, source)
237 
238  subroutine provide_field_to_writer_federator_rvalues_nosrc(io_configuration, field_name, field_namespace, &
239  field_values, timestep, time, frequency)
240  type(io_configuration_type), intent(inout) :: io_configuration
241  character(len=*), intent(in) :: field_name, field_namespace
242  integer, intent(in) :: timestep, frequency
243  real(kind=DEFAULT_PRECISION), dimension(:), intent(in) :: field_values
244  real(kind=DEFAULT_PRECISION), intent(in) :: time
245 
246  call provide_field_to_writer_federator_rvalues_src(io_configuration, field_name, field_namespace, &
247  field_values, timestep, time, frequency, -1)
249 
257  subroutine provide_field_to_writer_federator_nosrc(io_configuration, field_name, field_namespace, &
258  field_values, timestep, time, frequency)
259  type(io_configuration_type), intent(inout) :: io_configuration
260  character(len=*), intent(in) :: field_name, field_namespace
261  integer, intent(in) :: timestep, frequency
262  type(data_values_type), intent(inout) :: field_values
263  real(kind=DEFAULT_PRECISION), intent(in) :: time
264 
265  call provide_field_to_writer_federator_src(io_configuration, field_name, field_namespace, &
266  field_values, timestep, time, frequency, -1)
268 
277  subroutine provide_field_to_writer_federator_src(io_configuration, field_name, field_namespace, &
278  field_values, timestep, time, frequency, source, terminated_case)
279  type(io_configuration_type), intent(inout) :: io_configuration
280  character(len=*), intent(in) :: field_name, field_namespace
281  integer, intent(in) :: timestep, frequency, source
282  type(data_values_type), intent(inout) :: field_values
283  real(kind=DEFAULT_PRECISION), intent(in) :: time
284  logical, intent(in), optional :: terminated_case
285 
286  type(field_ordering_type), pointer :: field_ordering
287  class(*), pointer :: generic
288  logical :: this_is_termination
289 
290  if (present(terminated_case)) then
291  this_is_termination=terminated_case
292  else
293  this_is_termination=.false.
294  end if
295 
296  field_ordering=>get_or_add_field_ordering(field_name, field_namespace, frequency, source)
297  call check_thread_status(forthread_mutex_lock(field_ordering%access_mutex))
298  if (timestep == field_ordering%last_timestep_access + frequency .or. this_is_termination) then
299  if (.not. this_is_termination) field_ordering%last_timestep_access=timestep
300  call provide_ordered_field_to_writer_federator(io_configuration, field_name, field_namespace, &
301  field_values, timestep, time, source)
302  if (allocated(field_values%values)) deallocate(field_values%values)
303  else
304  generic=>generate_value_container(field_name, field_namespace, field_values, timestep, time, frequency, source)
305  call c_put_generic(field_ordering%timestep_to_value, conv_to_string(timestep), generic, .false.)
306  end if
307  call process_queued_items(io_configuration, field_ordering)
308  call check_thread_status(forthread_mutex_unlock(field_ordering%access_mutex))
310 
315  subroutine process_queued_items(io_configuration, field_ordering)
316  type(io_configuration_type), intent(inout) :: io_configuration
317  type(field_ordering_type), intent(inout) :: field_ordering
318 
319  integer :: next_timestep
320  type(field_ordering_value_type), pointer :: field_ordering_value_at_timestep
321 
322  do while (.not. c_is_empty(field_ordering%timestep_to_value))
323  next_timestep=field_ordering%last_timestep_access + field_ordering%frequency
324  if (c_contains(field_ordering%timestep_to_value, conv_to_string(next_timestep))) then
325  field_ordering_value_at_timestep=>get_field_ordering_value_at_timestep(field_ordering%timestep_to_value, next_timestep)
326  call c_remove(field_ordering%timestep_to_value, conv_to_string(next_timestep))
327  field_ordering%last_timestep_access=next_timestep
328  call provide_ordered_field_to_writer_federator(io_configuration, field_ordering_value_at_timestep%field_name, &
329  field_ordering_value_at_timestep%field_namespace, field_ordering_value_at_timestep%field_values, &
330  field_ordering_value_at_timestep%timestep, field_ordering_value_at_timestep%time, &
331  field_ordering_value_at_timestep%source)
332  if (allocated(field_ordering_value_at_timestep%field_values)) then
333  if (allocated(field_ordering_value_at_timestep%field_values%values)) &
334  deallocate(field_ordering_value_at_timestep%field_values%values)
335  deallocate(field_ordering_value_at_timestep%field_values)
336  end if
337  deallocate(field_ordering_value_at_timestep)
338  else
339  exit
340  end if
341  end do
342  end subroutine process_queued_items
343 
348  function get_field_ordering_value_at_timestep(collection, timestep)
349  type(hashmap_type), intent(inout) :: collection
350  integer, intent(in) :: timestep
351  type(field_ordering_value_type), pointer :: get_field_ordering_value_at_timestep
352 
353  class(*), pointer :: generic
354 
355  generic=>c_get_generic(collection, conv_to_string(timestep))
356  if (associated(generic)) then
357  select type(generic)
358  type is (field_ordering_value_type)
359  get_field_ordering_value_at_timestep=>generic
360  end select
361  else
362  get_field_ordering_value_at_timestep=>null()
363  end if
365 
375  function generate_value_container(field_name, field_namespace, field_values, timestep, time, frequency, source)
376  character(len=*), intent(in) :: field_name, field_namespace
377  integer, intent(in) :: timestep, frequency, source
378  type(data_values_type), intent(in) :: field_values
379  real(kind=DEFAULT_PRECISION), intent(in) :: time
380  type(field_ordering_value_type), pointer :: generate_value_container
381 
382  allocate(generate_value_container)
383  generate_value_container%field_name=field_name
384  generate_value_container%field_namespace=field_namespace
385  generate_value_container%timestep=timestep
386  generate_value_container%frequency=frequency
387  generate_value_container%time=time
388  generate_value_container%source=source
389  allocate(generate_value_container%field_values, source=field_values)
390  end function generate_value_container
391 
397  function get_or_add_field_ordering(field_name, field_namespace, frequency, source)
398  character(len=*), intent(in) :: field_name, field_namespace
399  integer, intent(in) :: frequency, source
400  type(field_ordering_type), pointer :: get_or_add_field_ordering
401 
402  class(*), pointer :: generic
403  character(len=STRING_LENGTH) :: entry_key
404 
405  if (source .gt. -1) then
406  entry_key=trim(field_name)//"#"//trim(field_namespace)//"#"//trim(conv_to_string(source))
407  else
408  entry_key=field_name
409  end if
410 
411  get_or_add_field_ordering=>get_field_ordering(entry_key, .true.)
412  if (.not. associated(get_or_add_field_ordering)) then
414  get_or_add_field_ordering=>get_field_ordering(entry_key, .false.)
415  if (.not. associated(get_or_add_field_ordering)) then
416  allocate(get_or_add_field_ordering)
417  get_or_add_field_ordering%last_timestep_access=0
418  get_or_add_field_ordering%frequency=frequency
419  call check_thread_status(forthread_mutex_init(get_or_add_field_ordering%access_mutex, -1))
420  generic=>get_or_add_field_ordering
421  call c_put_generic(field_orderings, entry_key, generic, .false.)
422  end if
424  end if
425  end function get_or_add_field_ordering
426 
431  function get_field_ordering(field_name, do_lock)
432  character(len=*), intent(in) :: field_name
433  logical, intent(in) :: do_lock
434  type(field_ordering_type), pointer :: get_field_ordering
435 
436  class(*), pointer :: generic
437 
439  generic=>c_get_generic(field_orderings, field_name)
441  if (associated(generic)) then
442  select type(generic)
443  type is (field_ordering_type)
444  get_field_ordering=>generic
445  end select
446  else
447  get_field_ordering=>null()
448  end if
449  end function get_field_ordering
450 
453  integer(kind=8) function prepare_to_serialise_field_manager_state()
454  type(mapentry_type) :: map_entry
455  type(iterator_type) :: iterator
456  class(*), pointer :: generic
457 
460 
462  do while (c_has_next(iterator))
463  map_entry=c_next_mapentry(iterator)
464  generic=>c_get_generic(map_entry)
465  if (associated(generic)) then
466  select type(generic)
467  type is (field_ordering_type)
470  (kind(prepare_to_serialise_field_manager_state)*2)+len(trim(map_entry%key))
471  end select
472  end if
473  end do
475 
478  subroutine serialise_field_manager_state(byte_data)
479  character, dimension(:), allocatable, intent(inout) :: byte_data
480 
481  integer :: current_data_point, prev_pt
482  type(mapentry_type) :: map_entry
483  type(iterator_type) :: iterator
484  class(*), pointer :: generic
485 
486  current_data_point=1
487  current_data_point=pack_scalar_field(byte_data, current_data_point, c_size(field_orderings))
488 
490  do while (c_has_next(iterator))
491  map_entry=c_next_mapentry(iterator)
492  generic=>c_get_generic(map_entry)
493  if (associated(generic)) then
494  select type(generic)
495  type is (field_ordering_type)
496  current_data_point=pack_scalar_field(byte_data, current_data_point, len(trim(map_entry%key)))
497  byte_data(current_data_point:current_data_point+len(trim(map_entry%key))-1) = transfer(trim(map_entry%key), &
498  byte_data(current_data_point:current_data_point+len(trim(map_entry%key))-1))
499  current_data_point=current_data_point+len(trim(map_entry%key))
500 
501  prev_pt=current_data_point
502  current_data_point=current_data_point+kind(current_data_point)
503  call serialise_specific_field_ordering(generic, byte_data, current_data_point)
504  prev_pt=pack_scalar_field(byte_data, prev_pt, (current_data_point-kind(current_data_point))-prev_pt)
505  end select
506  end if
507  end do
508 
510  end subroutine serialise_field_manager_state
511 
514  subroutine unserialise_field_manager_state(byte_data)
515  character, dimension(:), intent(in) :: byte_data
516 
517  integer :: current_data_point, number_of_entries, i, byte_size, key_size
518  character(len=STRING_LENGTH) :: value_key
519  class(*), pointer :: generic
520 
521  current_data_point=1
522  number_of_entries=unpack_scalar_integer_from_bytedata(byte_data, current_data_point)
523 
524  if (number_of_entries .gt. 0) then
525  do i=1, number_of_entries
526  key_size=unpack_scalar_integer_from_bytedata(byte_data, current_data_point)
527  value_key=transfer(byte_data(current_data_point:current_data_point+key_size-1), value_key)
528  value_key(key_size+1:)=" "
529  current_data_point=current_data_point+key_size
530  byte_size=unpack_scalar_integer_from_bytedata(byte_data, current_data_point)
531  generic=>unserialise_specific_field_ordering(byte_data(current_data_point:current_data_point+byte_size-1))
532  call c_put_generic(field_orderings, value_key, generic, .false.)
533  current_data_point=current_data_point+byte_size
534  end do
535  end if
536  end subroutine unserialise_field_manager_state
537 
541  integer(kind=8) function prepare_to_serialise_specific_field_ordering(specific_field_ordering)
542  type(field_ordering_type), intent(inout) :: specific_field_ordering
543 
544  type(mapentry_type) :: map_entry
545  type(iterator_type) :: iterator
546  class(*), pointer :: generic
547 
548  call check_thread_status(forthread_mutex_lock(specific_field_ordering%access_mutex))
549 
551 
552  iterator=c_get_iterator(specific_field_ordering%timestep_to_value)
553  do while (c_has_next(iterator))
554  map_entry=c_next_mapentry(iterator)
555  generic=>c_get_generic(map_entry)
556  if (associated(generic)) then
557  select type(generic)
558  type is (field_ordering_value_type)
561  len(trim(map_entry%key))
562  end select
563  end if
564  end do
566 
571  subroutine serialise_specific_field_ordering(specific_field_ordering, byte_data, current_data_point)
572  type(field_ordering_type), intent(inout) :: specific_field_ordering
573  character, dimension(:), allocatable, intent(inout) :: byte_data
574  integer, intent(inout) :: current_data_point
575 
576  integer :: prev_pt
577  type(mapentry_type) :: map_entry
578  type(iterator_type) :: iterator
579  class(*), pointer :: generic
580 
581  current_data_point=pack_scalar_field(byte_data, current_data_point, specific_field_ordering%last_timestep_access)
582  current_data_point=pack_scalar_field(byte_data, current_data_point, specific_field_ordering%frequency)
583  current_data_point=pack_scalar_field(byte_data, current_data_point, c_size(specific_field_ordering%timestep_to_value))
584 
585  iterator=c_get_iterator(specific_field_ordering%timestep_to_value)
586  do while (c_has_next(iterator))
587  map_entry=c_next_mapentry(iterator)
588  generic=>c_get_generic(map_entry)
589  if (associated(generic)) then
590  select type(generic)
591  type is (field_ordering_value_type)
592  current_data_point=pack_scalar_field(byte_data, current_data_point, len(trim(map_entry%key)))
593  byte_data(current_data_point:current_data_point+len(trim(map_entry%key))-1) = transfer(trim(map_entry%key), &
594  byte_data(current_data_point:current_data_point+len(trim(map_entry%key))-1))
595  current_data_point=current_data_point+len(trim(map_entry%key))
596 
597  prev_pt=current_data_point
598  current_data_point=current_data_point+kind(current_data_point)
599  call serialise_field_ordering_value(generic, byte_data, current_data_point)
600  prev_pt=pack_scalar_field(byte_data, prev_pt, (current_data_point-kind(current_data_point))-prev_pt)
601  end select
602  end if
603  end do
604 
605  call check_thread_status(forthread_mutex_unlock(specific_field_ordering%access_mutex))
606  end subroutine serialise_specific_field_ordering
607 
611  function unserialise_specific_field_ordering(byte_data)
612  character, dimension(:), intent(in) :: byte_data
613  type(field_ordering_type), pointer :: unserialise_specific_field_ordering
614 
615  integer :: current_data_point, number_of_values, byte_size, i, key_size
616  character(len=STRING_LENGTH) :: value_key
617  class(*), pointer :: generic
618 
619  allocate(unserialise_specific_field_ordering)
620 
621  current_data_point=1
622  unserialise_specific_field_ordering%last_timestep_access=unpack_scalar_integer_from_bytedata(byte_data, current_data_point)
623  unserialise_specific_field_ordering%frequency=unpack_scalar_integer_from_bytedata(byte_data, current_data_point)
624  number_of_values=unpack_scalar_integer_from_bytedata(byte_data, current_data_point)
625 
626  if (number_of_values .gt. 0) then
627  do i=1, number_of_values
628  key_size=unpack_scalar_integer_from_bytedata(byte_data, current_data_point)
629  value_key=transfer(byte_data(current_data_point:current_data_point+key_size-1), value_key)
630  value_key(key_size+1:)=" "
631  current_data_point=current_data_point+key_size
632  byte_size=unpack_scalar_integer_from_bytedata(byte_data, current_data_point)
633  generic=>unserialise_field_ordering_value(byte_data(current_data_point:current_data_point+byte_size-1))
634  call c_put_generic(unserialise_specific_field_ordering%timestep_to_value, value_key, generic, .false.)
635  current_data_point=current_data_point+byte_size
636  end do
637  end if
638  call check_thread_status(forthread_mutex_init(unserialise_specific_field_ordering%access_mutex, -1))
640 
644  integer(kind=8) function prepare_to_serialise_field_ordering_value(specific_field_value)
645  type(field_ordering_value_type), intent(inout) :: specific_field_value
646 
649  (kind(specific_field_value%timestep) * 6) + len(trim(specific_field_value%field_name)) + &
650  len(trim(specific_field_value%field_namespace)) + kind(specific_field_value%time)
652 
657  subroutine serialise_field_ordering_value(specific_field_value, byte_data, current_data_point)
658  type(field_ordering_value_type), intent(inout) :: specific_field_value
659  character, dimension(:), allocatable, intent(inout) :: byte_data
660  integer, intent(inout) :: current_data_point
661 
662  integer :: prev_pt
663 
664  current_data_point=pack_scalar_field(byte_data, current_data_point, specific_field_value%timestep)
665  current_data_point=pack_scalar_field(byte_data, current_data_point, specific_field_value%frequency)
666  current_data_point=pack_scalar_field(byte_data, current_data_point, specific_field_value%source)
667  current_data_point=pack_scalar_field(byte_data, current_data_point, len(trim(specific_field_value%field_name)))
668  byte_data(current_data_point:current_data_point+len(trim(specific_field_value%field_name))-1) = &
669  transfer(trim(specific_field_value%field_name), byte_data(current_data_point:current_data_point+&
670  len(trim(specific_field_value%field_name))-1))
671  current_data_point=current_data_point+len(trim(specific_field_value%field_name))
672  current_data_point=pack_scalar_field(byte_data, current_data_point, len(trim(specific_field_value%field_namespace)))
673  byte_data(current_data_point:current_data_point+len(trim(specific_field_value%field_namespace))-1) = &
674  transfer(trim(specific_field_value%field_namespace), byte_data(current_data_point:current_data_point+&
675  len(trim(specific_field_value%field_namespace))-1))
676  current_data_point=current_data_point+len(trim(specific_field_value%field_namespace))
677  current_data_point=pack_scalar_field(byte_data, current_data_point, double_real_value=specific_field_value%time)
678 
679  prev_pt=current_data_point
680  current_data_point=current_data_point+kind(current_data_point)
681  call serialise_data_values_type(specific_field_value%field_values, byte_data, current_data_point)
682  prev_pt=pack_scalar_field(byte_data, prev_pt, (current_data_point-kind(current_data_point))-prev_pt)
683  end subroutine serialise_field_ordering_value
684 
688  function unserialise_field_ordering_value(byte_data)
689  character, dimension(:), intent(in) :: byte_data
690  type(field_ordering_value_type), pointer :: unserialise_field_ordering_value
691 
692  integer :: current_data_point, byte_size, str_size
693 
694  allocate(unserialise_field_ordering_value)
695  current_data_point=1
696  unserialise_field_ordering_value%timestep=unpack_scalar_integer_from_bytedata(byte_data, current_data_point)
697  unserialise_field_ordering_value%frequency=unpack_scalar_integer_from_bytedata(byte_data, current_data_point)
698  unserialise_field_ordering_value%source=unpack_scalar_integer_from_bytedata(byte_data, current_data_point)
699  str_size=unpack_scalar_integer_from_bytedata(byte_data, current_data_point)
700  unserialise_field_ordering_value%field_name=transfer(byte_data(current_data_point:current_data_point+str_size-1), &
701  unserialise_field_ordering_value%field_name)
702  unserialise_field_ordering_value%field_name(str_size+1:)=" "
703  current_data_point=current_data_point+str_size
704  str_size=unpack_scalar_integer_from_bytedata(byte_data, current_data_point)
705  unserialise_field_ordering_value%field_namespace=transfer(byte_data(current_data_point:current_data_point+str_size-1), &
706  unserialise_field_ordering_value%field_namespace)
707  unserialise_field_ordering_value%field_namespace(str_size+1:)=" "
708  current_data_point=current_data_point+str_size
709  unserialise_field_ordering_value%time=unpack_scalar_dp_real_from_bytedata(byte_data, current_data_point)
710  byte_size=unpack_scalar_integer_from_bytedata(byte_data, current_data_point)
711  unserialise_field_ordering_value%field_values=unserialise_data_values_type(byte_data(current_data_point:&
712  current_data_point+byte_size-1))
714 end module writer_field_manager_mod
type(data_values_type) function, pointer, public unserialise_data_values_type(byte_data)
Unserialises some byte data into data values.
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
integer(kind=8) function prepare_to_serialise_field_manager_state()
Prepares to serialise the field manager state, both determines storage needed and also issues any loc...
subroutine, public set_serialise_write_field_manager_state(serialise_writer_field_manager_state_arg, prepare_to_serialise_writer_field_manager_state_arg, is_write_field_manager_up_to_date_arg)
Sets the procedure to call for serialises the field manager state, this is handled in this manner due...
type(field_ordering_type) function, pointer unserialise_specific_field_ordering(byte_data)
Unserialises some field ordering.
integer function forthread_rwlock_init(rwlock_id, attr_id)
Definition: forthread.F90:504
Gets a specific generic element out of the list, stack, queue or map with the corresponding key...
Returns whether a collection is empty.
integer function forthread_mutex_unlock(mutex_id)
Definition: forthread.F90:302
type(hashmap_type), volatile field_orderings
subroutine provide_field_to_writer_federator_rvalues_src(io_configuration, field_name, field_namespace, field_values, timestep, time, frequency, source)
integer, parameter, public log_error
Only log ERROR messages.
Definition: logging.F90:11
subroutine, public provide_ordered_field_to_writer_federator(io_configuration, field_name, field_namespace, field_values, timestep, time, source)
integer function forthread_mutex_destroy(mutex_id)
Definition: forthread.F90:265
Reads the IO server state that was stored in a NetCDF checkpoint file.
Contains functionality for managing and extracting data from the raw data dumps that the IO server re...
Definition: datautils.F90:3
Logging utility.
Definition: logging.F90:2
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
integer, parameter, public default_precision
MPI communication type which we use for the prognostic and calculation data.
Definition: datadefn.F90:17
The writer field manager will manage aspects of the fields being provided to the writer federator...
type(field_ordering_type) function, pointer get_field_ordering(field_name, do_lock)
Retrieves a field ordering based upon the name or null if none can be found.
logical function, public is_field_used_by_writer_federator(field_name, field_namespace)
Determines whether a field is used by the writer federator or not.
logical function, public is_field_split_on_q(field_name)
Determines whether a field is split on Q or not.
subroutine serialise_field_ordering_value(specific_field_value, byte_data, current_data_point)
Serialises a field ordering value and releases any issued locks.
integer function forthread_rwlock_rdlock(lock_id)
Definition: forthread.F90:514
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
integer function forthread_mutex_init(mutex_id, attr_id)
Definition: forthread.F90:274
subroutine, public serialise_data_values_type(data_values_to_serialise, byte_data, current_data_point)
Serialises some data values to store or transmit. This releases any locks issued during preparation...
Conversion between common inbuilt FORTRAN data types.
Definition: conversions.F90:5
integer, parameter, public double_data_type
Definition: ioclient.F90:40
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
Converts data types to strings.
Definition: conversions.F90:36
integer function forthread_rwlock_wrlock(lock_id)
Definition: forthread.F90:532
type(field_ordering_value_type) function, pointer unserialise_field_ordering_value(byte_data)
Unseralises some field ordering from its byte representation.
subroutine provide_field_to_writer_federator_src(io_configuration, field_name, field_namespace, field_values, timestep, time, frequency, source, terminated_case)
Provides a field to the write federator (a collective diagnostic or prognostic)
type(field_ordering_value_type) function, pointer get_field_ordering_value_at_timestep(collection, timestep)
Retrieves a specific field ordering value at the corresponding timestep or null if none is found...
integer(kind=8) function prepare_to_serialise_field_ordering_value(specific_field_value)
Prepares to serialise a specific field ordering value, determines both the storage size and issues lo...
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
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
Writer types which are shared across writing functionality. Also includes serialisation functionality...
Definition: writer_types.F90:2
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
logical function, public is_field_present(io_configuration, source, data_id, key)
Definition: datautils.F90:146
Map data structure that holds string (length 20 maximum) key value pairs.
Definition: collections.F90:86
type(field_ordering_type) function, pointer get_or_add_field_ordering(field_name, field_namespace, frequency, source)
Retrieves or adds ordering for a specific field (and MONC source)
This is a thread pool and the single management "main" thread will spawn out free threads in the pool...
Definition: threadpool.F90:5
Returns the number of elements in the collection.
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
subroutine, public check_thread_status(ierr)
Checks the error status of any thread operation and reports an error if it failed.
Definition: threadpool.F90:229
integer function forthread_mutex_lock(mutex_id)
Definition: forthread.F90:284
subroutine provide_field_to_writer_federator_rvalues_nosrc(io_configuration, field_name, field_namespace, field_values, timestep, time, frequency)
Collection data structures.
Definition: collections.F90:7
subroutine serialise_field_manager_state(byte_data)
Serialises the current field manager, releases any locks issued during preparation.
integer(kind=8) function, public prepare_to_serialise_data_values_type(data_values_to_serialise)
Prepares to serialise a specific data values type, both determines the byte size required and also is...
subroutine unserialise_field_manager_state(byte_data)
Unserialses from some byte data into the state.
integer, parameter, public log_warn
Log WARNING and ERROR messages.
Definition: logging.F90:12
logical function, public is_write_field_manager_up_to_date(timestep)
Determines whether the state of the write field manager is up to date with respect to the timestep th...
type(field_ordering_value_type) function, pointer generate_value_container(field_name, field_namespace, field_values, timestep, time, frequency, source)
Generates the field value container which is then filled in with appropriate values and added into th...
Converts data types to real.
Definition: conversions.F90:58
integer(kind=8) function prepare_to_serialise_specific_field_ordering(specific_field_ordering)
Prepares to serialise a specific field ordering, both determines storage size and issues locks...
integer, parameter, public string_length
Default length of strings.
Definition: datadefn.F90:10
subroutine, public initialise_writer_field_manager(io_configuration, continuation_run)
Initialises the writer field manager.
This federates over the writing of diagnostic and prognostic data to the file system. It also manages the time manipulation of fields and groups.
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
integer function forthread_rwlock_destroy(rwlock_id)
Definition: forthread.F90:495
subroutine, public provide_monc_data_to_writer_federator(io_configuration, source, data_id, data_dump)
Data communicated from MONC is provided to this write federator and then included if the configuratio...
subroutine serialise_specific_field_ordering(specific_field_ordering, byte_data, current_data_point)
Serialises a specific fields ordering and releases any locks issued during preparation.
integer function forthread_rwlock_unlock(lock_id)
Definition: forthread.F90:550
subroutine provide_field_to_writer_federator_nosrc(io_configuration, field_name, field_namespace, field_values, timestep, time, frequency)
Provides a field to the write federator with no source (a none collective diagnostic) ...
Puts a generic key-value pair into the map.
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
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
subroutine, public finalise_writer_field_manager()
Finalises the writer field manager.
subroutine get_type_of_field(fields, field_name, field_namespace, field_type, data_type)
Retrieves the data type of a field or 0 if the field was not found.
Configuration associated with the representation of a specific data field.
subroutine, public reactivate_writer_field_manager_state(io_configuration, unserialise_writer_field_manager)
Reactivates the writer field manager state from the checkpoint file, for memory reasons this will ope...
Determines whether or not a map contains a specific key.
integer, parameter, public scalar_field_type
Definition: ioclient.F90:38
integer, parameter, public map_field_type
Field data type identifiers.
Definition: ioclient.F90:38
Gets a specific string element out of the list, stack, queue or map with the corresponding key...
Parses the XML configuration file to produce the io configuration description which contains the data...
The IO server state module which will write out the current state of the IO server to a NetCDF file...
subroutine process_queued_items(io_configuration, field_ordering)
Processes queued up items for a specific field's ordering. This will send any available fields to the...
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
integer function, public pack_scalar_field(buffer, start_offset, int_value, real_value, single_real_value, double_real_value, string_value, logical_value)
Packs the data of a scalar field into a buffer.
Definition: ioclient.F90:312
Removes a specific element from the list or map.
type(data_values_type) function get_value_from_monc_data(io_configuration, source, data_id, data_dump, field_name, field_namespace)
Retrieves a value from the communicated MONC data. If this was an integer then converts to a real...