MONC
netcdf_filetype.F90
Go to the documentation of this file.
1 
20  use netcdf, only : nf90_double, nf90_real, nf90_int, nf90_char, nf90_global, nf90_clobber, nf90_netcdf4, nf90_mpiio, &
21  nf90_collective, nf90_unlimited, nf90_def_var, nf90_var_par_access, nf90_def_var_fill, nf90_put_att, &
22  nf90_create, nf90_put_var, nf90_def_dim, nf90_enddef, nf90_close, nf90_ebaddim, nf90_enotatt, nf90_enotvar, &
23  nf90_noerr, nf90_strerror, nf90_redef, nf90_inq_varid
27  use mpi, only : mpi_info_null
29  use grids_mod, only : z_index, y_index, x_index
32  use mpi, only : mpi_status_ignore, mpi_request_null, mpi_int
33 
34  implicit none
35 
36 #ifndef TEST_MODE
37  private
38 #endif
39 
40  type(hashmap_type), volatile :: file_states
41  integer, volatile :: file_states_rwlock, netcdf_mutex
42 
43  logical :: l_nc_dim, l_nd_dim
46 
49 contains
50 
55  end subroutine initialise_netcdf_filetype
56 
61  end subroutine finalise_netcdf_filetype
62 
69  subroutine define_netcdf_file(io_configuration, file_writer_information, timestep, time, time_points, termination_write)
70  type(io_configuration_type), intent(inout) :: io_configuration
71  type(writer_type), intent(inout), target :: file_writer_information
72  type(map_type), intent(inout) :: time_points
73  integer, intent(in) :: timestep
74  real, intent(in) :: time
75  logical, intent(in) :: termination_write
76 
77  character(len=STRING_LENGTH) :: unique_filename
78  type(netcdf_diagnostics_type), pointer :: ncdf_writer_state
79  class(*), pointer :: generic
80  integer :: zn_var_id
81  integer :: z_var_id
82 
83  ncdf_writer_state=>get_file_state(file_writer_information%filename, timestep, .true.)
84  if (.not. associated(ncdf_writer_state)) then
86  ncdf_writer_state=>get_file_state(file_writer_information%filename, timestep, .false.)
87  if (.not. associated(ncdf_writer_state)) then
88  allocate(ncdf_writer_state)
89  ncdf_writer_state%corresponding_writer_entry=>file_writer_information
90  ncdf_writer_state%termination_write=termination_write
91  call check_thread_status(forthread_mutex_init(ncdf_writer_state%mutex, -1))
92  call check_thread_status(forthread_mutex_lock(ncdf_writer_state%mutex))
93  generic=>ncdf_writer_state
94  call c_put_generic(file_states, trim(file_writer_information%filename)//"#"//trim(conv_to_string(timestep)), &
95  generic, .false.)
97 
98  if (file_writer_information%write_on_model_time) then
99  call generate_unique_filename(file_writer_information%filename, unique_filename, &
100  file_writer_information%defined_write_time)
101  else
102  call generate_unique_filename(file_writer_information%filename, unique_filename, timestep=timestep)
103  end if
105  call lock_mpi()
106  call check_netcdf_status(nf90_create(unique_filename, ior(nf90_netcdf4, nf90_mpiio), ncdf_writer_state%ncid, &
107  comm = io_configuration%io_communicator, info = mpi_info_null))
108  call unlock_mpi()
109  call write_out_global_attributes(io_configuration, ncdf_writer_state%ncid, file_writer_information, timestep, time)
110  call define_dimensions(ncdf_writer_state, io_configuration%dimension_sizing)
111  call define_time_series_dimensions(ncdf_writer_state, file_writer_information, time, time_points, termination_write)
112  call define_variables(io_configuration, ncdf_writer_state, file_writer_information)
113  zn_var_id = define_coordinate_variable(ncdf_writer_state,"zn")
114  z_var_id = define_coordinate_variable(ncdf_writer_state,"z")
115  nopt_var_id = define_options_database_variable(ncdf_writer_state)
116  call lock_mpi()
117  call check_netcdf_status(nf90_enddef(ncdf_writer_state%ncid))
118  call unlock_mpi()
119 
121  if (io_configuration%my_io_rank == 0) then
123  if (l_nc_dim) then
124  call write_condition_variable(ncdf_writer_state, nc_var_id_s, cond_request)
125  call write_condition_variable(ncdf_writer_state, nc_var_id_l, cond_long)
126  end if
127  if (l_nd_dim) then
128  call write_condition_variable(ncdf_writer_state, nd_var_id_s, diag_request)
129  call write_condition_variable(ncdf_writer_state, nd_var_id_l, diag_long)
130  end if
131 
133  call write_out_options(io_configuration, ncdf_writer_state)
134  call write_coordinate_variable(ncdf_writer_state, zn_var_id, io_configuration%zn_field)
135  call write_coordinate_variable(ncdf_writer_state, z_var_id, io_configuration%z_field)
136  end if ! end write isolation
137 
138  call check_thread_status(forthread_mutex_unlock(ncdf_writer_state%mutex))
140 
141  else
143  end if
144  end if
145  end subroutine define_netcdf_file
146 
151  subroutine store_io_server_state(io_configuration, writer_entries, time_points, file_writer_information, timestep)
152  type(io_configuration_type), intent(inout) :: io_configuration
153  type(writer_type), volatile, dimension(:), intent(inout) :: writer_entries
154  type(hashmap_type), volatile, intent(inout) :: time_points
155  type(writer_type), intent(inout), target :: file_writer_information
156  integer, intent(in) :: timestep
157 
158  type(netcdf_diagnostics_type), pointer :: ncdf_writer_state
159 
160  ncdf_writer_state=>get_file_state(file_writer_information%filename, timestep, .true.)
161  call lock_mpi()
162  call check_netcdf_status(nf90_redef(ncdf_writer_state%ncid))
163  call unlock_mpi()
164  call define_io_server_state_contributions(io_configuration, writer_entries, time_points, ncdf_writer_state)
165  call lock_mpi()
166  call check_netcdf_status(nf90_enddef(ncdf_writer_state%ncid))
167  call unlock_mpi()
168  call write_io_server_state(io_configuration, writer_entries, time_points, ncdf_writer_state)
169  end subroutine store_io_server_state
170 
175  function get_writer_entry_from_netcdf(field_name, timestep, terminated)
176  character(len=STRING_LENGTH) :: field_name
177  integer :: timestep
178  logical, intent(out), optional :: terminated
179  type(writer_type), pointer :: get_writer_entry_from_netcdf
180 
181  type(netcdf_diagnostics_type), pointer :: file_state
182 
183  file_state=>get_file_state(field_name, timestep, .true.)
184  if (present(terminated)) terminated=file_state%termination_write
185  get_writer_entry_from_netcdf=>file_state%corresponding_writer_entry
186  end function get_writer_entry_from_netcdf
187 
193  subroutine close_netcdf_file(io_configuration, field_name, timestep)
194  type(io_configuration_type), intent(inout) :: io_configuration
195  character(len=STRING_LENGTH) :: field_name
196  integer :: timestep
197 
198  type(iterator_type) :: iterator
199  class(*), pointer :: generic
200 
201  type(netcdf_diagnostics_type), pointer :: file_state
202 
203  file_state=>get_file_state(field_name, timestep, .true.)
204  call check_thread_status(forthread_mutex_lock(file_state%mutex))
206  call lock_mpi()
207  call check_netcdf_status(nf90_close(file_state%ncid))
208  call unlock_mpi()
210  call check_thread_status(forthread_mutex_unlock(file_state%mutex))
211  call check_thread_status(forthread_mutex_destroy(file_state%mutex))
212  call c_free(file_state%dimension_to_id)
213  call c_free(file_state%variable_to_id)
214  iterator=c_get_iterator(file_state%timeseries_dimension)
215  do while (c_has_next(iterator))
216  generic=>c_get_generic(c_next_mapentry(iterator))
217  select type(generic)
219  deallocate(generic)
220  end select
221  end do
222  call c_free(file_state%timeseries_dimension)
224  call c_remove(file_states, trim(field_name)//"#"//trim(conv_to_string(timestep)))
226  if (log_get_logging_level() .ge. log_debug .and. log_is_master()) then
227  call log_master_log(log_debug, "Done physical close for NetCDF file at timestep "//trim(conv_to_string(timestep)))
228  end if
229  end subroutine close_netcdf_file
230 
237  subroutine write_variable(io_configuration, field_to_write_information, filename, timestep, time)
238  type(io_configuration_type), intent(inout) :: io_configuration
239  type(writer_field_type), intent(inout) :: field_to_write_information
240  character(len=*), intent(in) :: filename
241  integer, intent(in) :: timestep
242  real, intent(in) :: time
243 
244  type(netcdf_diagnostics_type), pointer :: file_state
245 
246  file_state=>get_file_state(filename, timestep, .true.)
247  if (field_to_write_information%collective_write) then
248  if (field_to_write_information%collective_contiguous_optimisation) then
249  call write_contiguous_collective_variable_to_diagnostics(io_configuration, field_to_write_information, &
250  timestep, time, file_state)
251  else
252  call write_collective_variable_to_diagnostics(io_configuration, field_to_write_information, timestep, time, file_state)
253  end if
254  else
255  call write_independent_variable_to_diagnostics(field_to_write_information, timestep, time, file_state)
256  end if
257  end subroutine write_variable
258 
263  integer function get_dimension_identifier(dim_name, is_auto_dimension)
264  character(len=*), intent(in) :: dim_name
265  logical, intent(out), optional :: is_auto_dimension
266 
267  integer :: dash_idx
268  logical :: is_modified_size
269 
270  dash_idx=index(dim_name, "_")
271  dash_idx=dash_idx-1
272  is_modified_size=dash_idx .ne. -1
273  if (.not. is_modified_size) dash_idx=len_trim(dim_name)
274 
275  if (dim_name(:dash_idx) .eq. "z" .or. dim_name(:dash_idx) .eq. "zn") then
277  else if (dim_name(:dash_idx) .eq. "y") then
279  else if (dim_name(:dash_idx) .eq. "x") then
281  else
283  end if
284 
285  if (present(is_auto_dimension)) is_auto_dimension=is_modified_size
286  end function get_dimension_identifier
287 
292  integer function get_dimension_original_size(dim_name, dimension_store)
293  character(len=*), intent(in) :: dim_name
294  type(map_type), intent(inout) :: dimension_store
295 
296  integer :: dash_idx
297 
298  dash_idx=index(dim_name, "_")
299  dash_idx=dash_idx-1
300  if (dash_idx .eq. -1) dash_idx=len_trim(dim_name)
301 
302  get_dimension_original_size=c_get_integer(dimension_store, dim_name(:dash_idx))
303  end function get_dimension_original_size
304 
309  subroutine write_coordinate_variable(file_state, coord_var_id, field_values)
310  type(netcdf_diagnostics_type), intent(inout) :: file_state
311  integer, intent(in) :: coord_var_id
312  real(kind=default_precision), dimension(:), intent(in) :: field_values
313 
314  integer :: count_to_write(1)
315 
316  count_to_write(1)=size(field_values)
317  call lock_mpi()
318  call check_netcdf_status(nf90_put_var(file_state%ncid, coord_var_id, field_values, count=count_to_write))
319  call unlock_mpi()
320  end subroutine write_coordinate_variable
321 
326  subroutine write_condition_variable(file_state, c_var_id, field_values)
327  type(netcdf_diagnostics_type), intent(inout) :: file_state
328  integer, intent(in) :: c_var_id
329  character(len=STRING_LENGTH), dimension(:), intent(in) :: field_values
330 
331  integer :: count_to_write(2), start_pos(2)
332  integer :: pos, string_size
333  character(len=STRING_LENGTH) :: dum_string
334 
335  count_to_write(2)=1 ! element count
336  start_pos(1)=1 ! string character start position
337  call lock_mpi()
338  do pos=1,size(field_values)
339  dum_string = trim(field_values(pos))
340  count_to_write(1) = len(trim(field_values(pos)))
341  start_pos(2)=pos
342  call check_netcdf_status(nf90_put_var(file_state%ncid, c_var_id, dum_string, &
343  start=start_pos, count=count_to_write))
344  end do
345  call unlock_mpi()
346  end subroutine write_condition_variable
347 
357  subroutine write_contiguous_collective_variable_to_diagnostics(io_configuration, field_to_write_information, timestep, &
358  time, file_state)
359  type(io_configuration_type), intent(inout) :: io_configuration
360  type(writer_field_type), intent(inout) :: field_to_write_information
361  integer, intent(in) :: timestep
362  real, intent(in) :: time
363  type(netcdf_diagnostics_type), intent(inout) :: file_state
364 
365  real :: value_to_test
366  real(kind=default_precision), dimension(:,:,:,:), allocatable :: contiguous_values
367  type(hashset_type) :: items_to_remove
368  real(kind=default_precision), dimension(:), allocatable :: timeseries_time_to_write
369  type(iterator_type) :: value_to_write_iterator, collective_descriptor_iterator, monc_iterator, value_to_remove_iterator
370  type(mapentry_type) :: value_to_write_map_entry
371  class(*), pointer :: generic
372  type(write_field_collective_descriptor_type), pointer :: collective_descriptor
373  type(netcdf_diagnostics_timeseries_type), pointer :: timeseries_diag
374  type(write_field_collective_monc_info_type), pointer :: monc_descriptor
375  type(write_field_collective_values_type), pointer :: multi_monc_entries
376  type(data_values_type), pointer :: data_value
377  integer :: number_time_entries, i, start(4), count(4), field_id, ierr
378  character(len=STRING_LENGTH) :: removal_key
379 
380  timeseries_diag=>get_specific_timeseries_dimension(file_state, field_to_write_information%output_frequency, &
381  field_to_write_information%timestep_frequency)
382  field_id=c_get_integer(file_state%variable_to_id, get_field_key(field_to_write_information))
383  if (.not. timeseries_diag%variable_written) allocate(timeseries_time_to_write(timeseries_diag%num_entries))
384 
385  number_time_entries=0
386  value_to_write_iterator=c_get_iterator(field_to_write_information%values_to_write)
387  do while (c_has_next(value_to_write_iterator))
388  value_to_write_map_entry=c_next_mapentry(value_to_write_iterator)
389  value_to_test=conv_to_real(value_to_write_map_entry%key)
390  if (value_to_test .le. time .and. value_to_test .gt. field_to_write_information%previous_write_time) then
391  number_time_entries=number_time_entries+1
392  call c_add_string(items_to_remove, value_to_write_map_entry%key)
393  end if
394  end do
395 
396  if (number_time_entries .ne. timeseries_diag%num_entries) then
397  call log_log(log_warn, "Expected "//trim(conv_to_string(timeseries_diag%num_entries))//&
398  " but have "//trim(conv_to_string(number_time_entries)))
399  if (number_time_entries .gt. timeseries_diag%num_entries) number_time_entries=timeseries_diag%num_entries
400  end if
401 
402  collective_descriptor_iterator=c_get_iterator(field_to_write_information%collective_descriptors)
403  do while (c_has_next(collective_descriptor_iterator))
404  collective_descriptor=>get_next_collective_descriptor(collective_descriptor_iterator)
405  allocate(contiguous_values(collective_descriptor%count(1), collective_descriptor%count(2), &
406  collective_descriptor%count(3), number_time_entries))
407  monc_iterator=c_get_iterator(collective_descriptor%specific_monc_info)
408  do while (c_has_next(monc_iterator))
409  monc_descriptor=>get_next_specific_monc_info(monc_iterator)
410  value_to_write_iterator=c_get_iterator(field_to_write_information%values_to_write)
411  i=0
412  do while (c_has_next(value_to_write_iterator))
413  value_to_write_map_entry=c_next_mapentry(value_to_write_iterator)
414  value_to_test=conv_to_real(value_to_write_map_entry%key)
415  if (value_to_test .le. time .and. value_to_test .gt. field_to_write_information%previous_write_time) then
416  i=i+1
417  if (allocated(timeseries_time_to_write)) timeseries_time_to_write(i)=value_to_test
418  generic=>c_get_generic(value_to_write_map_entry)
419  select type(generic)
421  multi_monc_entries=>generic
422  end select
423  data_value=>get_data_value_by_field_name(multi_monc_entries%monc_values, &
424  trim(conv_to_string(monc_descriptor%monc_source)))
425  if (collective_descriptor%split_dim == y_index) then
426  contiguous_values(:,monc_descriptor%relative_dimension_start:monc_descriptor%relative_dimension_start+&
427  monc_descriptor%counts(y_index)-1,:,i)=reshape(data_value%values, (/ monc_descriptor%counts(z_index), &
428  monc_descriptor%counts(y_index), monc_descriptor%counts(x_index)/))
429  else
430  contiguous_values(:,:,monc_descriptor%relative_dimension_start:monc_descriptor%relative_dimension_start+&
431  monc_descriptor%counts(x_index)-1,i)=reshape(data_value%values, (/ monc_descriptor%counts(z_index), &
432  monc_descriptor%counts(y_index), monc_descriptor%counts(x_index)/))
433  end if
434  deallocate(data_value%values)
435  deallocate(data_value)
436  end if
437  end do
438  end do
439  count(1:3)=collective_descriptor%count
440  count(4)=number_time_entries
441  start(1:3)=collective_descriptor%absolute_start
442  start(4)=1
443  call check_thread_status(forthread_mutex_lock(file_state%mutex))
445  call lock_mpi()
446  call check_netcdf_status(nf90_put_var(file_state%ncid, field_id, contiguous_values, start=start, count=count))
447  call unlock_mpi()
449  call check_thread_status(forthread_mutex_unlock(file_state%mutex))
450  deallocate(contiguous_values)
451  if (allocated(timeseries_time_to_write)) then
453  call lock_mpi()
454  call check_netcdf_status(nf90_put_var(file_state%ncid, timeseries_diag%netcdf_var_id, &
455  timeseries_time_to_write, count=(/ timeseries_diag%num_entries /)))
456  call unlock_mpi()
458  timeseries_diag%variable_written=.true.
459  deallocate(timeseries_time_to_write)
460  end if
461  end do
462  if (.not. c_is_empty(items_to_remove)) then
463  value_to_remove_iterator=c_get_iterator(items_to_remove)
464  do while (c_has_next(value_to_remove_iterator))
465  removal_key=c_next_string(value_to_remove_iterator)
466  generic=>c_get_generic(field_to_write_information%values_to_write, removal_key)
467  select type(generic)
469  multi_monc_entries=>generic
470  end select
471  call c_free(multi_monc_entries%monc_values)
472  deallocate(multi_monc_entries)
473  call c_remove(field_to_write_information%values_to_write, removal_key)
474  end do
475  call c_free(items_to_remove)
476  end if
477  if (field_to_write_information%max_num_collective_writes_request_handle .ne. mpi_request_null) then
478  call wait_for_mpi_request(field_to_write_information%max_num_collective_writes_request_handle)
479  end if
480  if (c_size(field_to_write_information%collective_descriptors) .lt. field_to_write_information%max_num_collective_writes) then
481  call check_thread_status(forthread_mutex_lock(file_state%mutex))
483  call lock_mpi()
484  do i=c_size(field_to_write_information%collective_descriptors), field_to_write_information%max_num_collective_writes-1
485  call check_netcdf_status(nf90_put_var(file_state%ncid, field_id, (/1.0/), start=(/1/), count=(/0/)))
486  end do
487  call unlock_mpi()
489  call check_thread_status(forthread_mutex_unlock(file_state%mutex))
490  end if
492 
497  type(iterator_type), intent(inout) :: iterator
499 
500  class(*), pointer :: generic
501 
502  generic=>c_next_generic(iterator)
503  select type(generic)
506  end select
507  end function get_next_collective_descriptor
508 
512  function get_next_specific_monc_info(iterator)
513  type(iterator_type) :: iterator
515 
516  class(*), pointer :: generic
517 
518  generic=>c_next_generic(iterator)
519  select type(generic)
522  end select
523  end function get_next_specific_monc_info
524 
531  subroutine write_collective_variable_to_diagnostics(io_configuration, field_to_write_information, timestep, time, file_state)
532  type(io_configuration_type), intent(inout) :: io_configuration
533  type(writer_field_type), intent(inout) :: field_to_write_information
534  integer, intent(in) :: timestep
535  real, intent(in) :: time
536  type(netcdf_diagnostics_type), intent(inout) :: file_state
537 
538  real :: value_to_test
539  integer :: i, k, included_num, field_id, start(field_to_write_information%dimensions+1), &
540  count(field_to_write_information%dimensions+1), monc_location, dim_identifier, auto_period, dim_start
541  class(*), pointer :: generic
542  type(write_field_collective_values_type), pointer :: multi_monc_entries
543  logical :: is_auto_dimension
544  real(kind=default_precision), dimension(:), allocatable :: timeseries_time_to_write
545  character(len=STRING_LENGTH), dimension(:), allocatable :: items_to_remove
546  type(data_values_type), pointer :: data_value
547  type(netcdf_diagnostics_timeseries_type), pointer :: timeseries_diag
548  type(iterator_type) :: value_to_write_iterator, monc_entries_iterator
549  type(mapentry_type) :: value_to_write_map_entry, monc_entries_map_entry
550 
551  timeseries_diag=>get_specific_timeseries_dimension(file_state, field_to_write_information%output_frequency, &
552  field_to_write_information%timestep_frequency)
553  if (.not. timeseries_diag%variable_written) allocate(timeseries_time_to_write(timeseries_diag%num_entries))
554 
555  allocate(items_to_remove(timeseries_diag%num_entries))
556  included_num=1
557  field_id=c_get_integer(file_state%variable_to_id, get_field_key(field_to_write_information))
558  value_to_write_iterator=c_get_iterator(field_to_write_information%values_to_write)
559  do while (c_has_next(value_to_write_iterator))
560  value_to_write_map_entry=c_next_mapentry(value_to_write_iterator)
561  value_to_test=conv_to_real(value_to_write_map_entry%key)
562  if (value_to_test .le. time .and. value_to_test .gt. field_to_write_information%previous_write_time) then
563  if (included_num .le. timeseries_diag%num_entries) then
564  if (allocated(timeseries_time_to_write)) timeseries_time_to_write(included_num)=value_to_test
565  generic=>c_get_generic(value_to_write_map_entry)
566  select type(generic)
568  multi_monc_entries=>generic
569  end select
570  monc_entries_iterator=c_get_iterator(multi_monc_entries%monc_values)
571  do while(c_has_next(monc_entries_iterator))
572  monc_entries_map_entry=c_next_mapentry(monc_entries_iterator)
573  data_value=>get_data_value_by_field_name(multi_monc_entries%monc_values, monc_entries_map_entry%key)
574  monc_location=c_get_integer(io_configuration%monc_to_index, monc_entries_map_entry%key)
575  do k=1, field_to_write_information%dimensions
576  dim_identifier=get_dimension_identifier(field_to_write_information%dim_size_defns(k), is_auto_dimension)
577  if (dim_identifier .gt. -1) then
578  start(k)=io_configuration%registered_moncs(monc_location)%local_dim_starts(dim_identifier)
579  count(k)=io_configuration%registered_moncs(monc_location)%local_dim_sizes(dim_identifier)
580  if (is_auto_dimension) then
581  auto_period=ceiling(real(get_dimension_original_size(field_to_write_information%dim_size_defns(k), &
582  io_configuration%dimension_sizing))/field_to_write_information%actual_dim_size(k))
583  start(k)=(start(k)/auto_period)+1
584  if (io_configuration%registered_moncs(monc_location)%local_dim_starts(dim_identifier)==1) then
585  dim_start=1
586  else
587  dim_start=auto_period - &
588  mod(io_configuration%registered_moncs(monc_location)%local_dim_starts(dim_identifier)-2, auto_period)
589  end if
590  count(k)=ceiling(real(io_configuration%registered_moncs(monc_location)%local_dim_sizes(dim_identifier) - &
591  (dim_start-1))/auto_period)
592  end if
593  else
594  call log_log(log_error, "Can not locate dimension "//trim(field_to_write_information%dim_size_defns(k)))
595  end if
596  end do
597  start(field_to_write_information%dimensions+1) = included_num
598  count(field_to_write_information%dimensions+1) = 1
599  call check_thread_status(forthread_mutex_lock(file_state%mutex))
601  call lock_mpi()
602  call check_netcdf_status(nf90_put_var(file_state%ncid, field_id, data_value%values, start=start, count=count))
603  call unlock_mpi()
605  call check_thread_status(forthread_mutex_unlock(file_state%mutex))
606  deallocate(data_value%values)
607  deallocate(data_value)
608  end do
609  items_to_remove(included_num)=value_to_write_map_entry%key
610  included_num=included_num+1
611  call c_free(multi_monc_entries%monc_values)
612  deallocate(multi_monc_entries)
613  else
614  call log_log(log_warn, "Omitted time entry of field '"//trim(field_to_write_information%field_name)//&
615  "' as past dimension length at time "//conv_to_string(value_to_test))
616  end if
617  end if
618  end do
619  if (included_num-1 .ne. timeseries_diag%num_entries) then
620  call log_log(log_warn, "Miss match of time entries for field '"//trim(field_to_write_information%field_name)//&
621  "', included entries="//trim(conv_to_string(included_num-1))//" but expected entries="//&
622  trim(conv_to_string(timeseries_diag%num_entries)))
623  end if
624  if (allocated(timeseries_time_to_write)) then
626  call lock_mpi()
627  call check_netcdf_status(nf90_put_var(file_state%ncid, timeseries_diag%netcdf_var_id, &
628  timeseries_time_to_write, count=(/ timeseries_diag%num_entries /)))
629  call unlock_mpi()
631  timeseries_diag%variable_written=.true.
632  end if
633  if (included_num .gt. 1) then
634  do i=1, included_num-1
635  call c_remove(field_to_write_information%values_to_write, items_to_remove(i))
636  end do
637  end if
638  deallocate(items_to_remove)
639  if (allocated(timeseries_time_to_write)) deallocate(timeseries_time_to_write)
641 
648  subroutine write_independent_variable_to_diagnostics(field_to_write_information, timestep, time, file_state)
649  type(writer_field_type), intent(inout) :: field_to_write_information
650  integer, intent(in) :: timestep
651  real, intent(in) :: time
652  type(netcdf_diagnostics_type), intent(inout) :: file_state
653 
654  if (field_to_write_information%field_type == array_field_type .or. &
655  field_to_write_information%field_type == scalar_field_type) then
656  if (field_to_write_information%data_type == double_data_type .or. &
657  field_to_write_information%data_type == integer_data_type) then
658  call write_out_number_values(field_to_write_information, timestep, time, file_state)
659  end if
660  else if (field_to_write_information%field_type == map_field_type) then
661  call write_out_map(field_to_write_information, timestep, time, file_state)
662  end if
664 
665  subroutine write_out_number_values(field_to_write_information, timestep, time, file_state)
666  type(writer_field_type), intent(inout) :: field_to_write_information
667  integer, intent(in) :: timestep
668  real, intent(in) :: time
669  type(netcdf_diagnostics_type), intent(inout) :: file_state
670 
671  real(kind=default_precision), dimension(:), allocatable :: values_to_write, timeseries_time_to_write
672  real :: value_to_test
673  integer :: i, field_id, next_entry_index, array_size, included_num
674  integer, dimension(:), allocatable :: count_to_write
675  type(iterator_type) :: iterator
676  type(mapentry_type) :: map_entry
677 
678  type(data_values_type), pointer :: data_value
679  character(len=STRING_LENGTH), dimension(:), allocatable :: items_to_remove
680  type(netcdf_diagnostics_timeseries_type), pointer :: timeseries_diag
681 
682  timeseries_diag=>get_specific_timeseries_dimension(file_state, field_to_write_information%output_frequency, &
683  field_to_write_information%timestep_frequency)
684 
685  next_entry_index=1
686  included_num=1
687  array_size=1
688 
689  if (.not. timeseries_diag%variable_written) allocate(timeseries_time_to_write(timeseries_diag%num_entries))
690 
691  allocate(count_to_write(field_to_write_information%dimensions+1))
692  if (field_to_write_information%dimensions .gt. 0) then
693  do i=1, field_to_write_information%dimensions
694  array_size=array_size*field_to_write_information%actual_dim_size(i)
695  count_to_write(i)=field_to_write_information%actual_dim_size(i)
696  end do
697  end if
698  allocate(values_to_write(array_size*timeseries_diag%num_entries))
699  allocate(items_to_remove(timeseries_diag%num_entries))
700  iterator=c_get_iterator(field_to_write_information%values_to_write)
701  do while (c_has_next(iterator))
702  map_entry=c_next_mapentry(iterator)
703  value_to_test=conv_to_real(map_entry%key)
704  if (value_to_test .le. time .and. value_to_test .gt. field_to_write_information%previous_write_time) then
705  data_value=>get_data_value_by_field_name(field_to_write_information%values_to_write, map_entry%key)
706  if (size(values_to_write) .ge. next_entry_index+size(data_value%values)-1) then
707  values_to_write(next_entry_index: next_entry_index+size(data_value%values)-1)=data_value%values(:)
708  next_entry_index=next_entry_index+size(data_value%values)
709  deallocate(data_value%values)
710  deallocate(data_value)
711  items_to_remove(included_num)=map_entry%key
712  if (allocated(timeseries_time_to_write)) timeseries_time_to_write(included_num)=value_to_test
713  included_num=included_num+1
714  else
715  call log_log(log_warn, "Omitted time entry of field '"//trim(field_to_write_information%field_name)//&
716  "' as past time dimension length")
717  end if
718  end if
719  end do
720  count_to_write(size(count_to_write))=included_num-1
721  field_id=c_get_integer(file_state%variable_to_id, get_field_key(field_to_write_information))
722  if (included_num-1 .ne. timeseries_diag%num_entries) then
723  call log_log(log_warn, "Miss match of time entries for field '"//trim(field_to_write_information%field_name)//&
724  "', included entries="//trim(conv_to_string(included_num-1))//" but expected entries="//&
725  trim(conv_to_string(timeseries_diag%num_entries)))
726  end if
727  call check_thread_status(forthread_mutex_lock(file_state%mutex))
729  call lock_mpi()
730  call check_netcdf_status(nf90_put_var(file_state%ncid, field_id, values_to_write, count=count_to_write))
731  if (allocated(timeseries_time_to_write)) then
732  call check_netcdf_status(nf90_put_var(file_state%ncid, timeseries_diag%netcdf_var_id, &
733  timeseries_time_to_write, count=(/ timeseries_diag%num_entries /)))
734  timeseries_diag%variable_written=.true.
735  end if
736  call unlock_mpi()
738  call check_thread_status(forthread_mutex_unlock(file_state%mutex))
739  deallocate(values_to_write)
740  if (included_num .gt. 1) then
741  do i=1, included_num-1
742  call c_remove(field_to_write_information%values_to_write, items_to_remove(i))
743  end do
744  end if
745  deallocate(items_to_remove)
746  if (allocated(timeseries_time_to_write)) deallocate(timeseries_time_to_write)
747  end subroutine write_out_number_values
748 
749  subroutine write_out_map(field_to_write_information, timestep, time, file_state)
750  type(writer_field_type), intent(inout) :: field_to_write_information
751  integer, intent(in) :: timestep
752  real, intent(in) :: time
753  type(netcdf_diagnostics_type), intent(inout) :: file_state
754 
755  integer :: i, j, field_id, included_num
756  real :: value_to_test
757  type(iterator_type) :: iterator, map_data_iterator
758  type(mapentry_type) :: map_entry, map_data_entry
759  type(data_values_type), pointer :: data_value
760  character(len=STRING_LENGTH), dimension(:), allocatable :: items_to_remove
761 
762  field_id=c_get_integer(file_state%variable_to_id, get_field_key(field_to_write_information))
763  included_num=1
764  j=1
765  allocate(items_to_remove(c_size(field_to_write_information%values_to_write)))
766  iterator=c_get_iterator(field_to_write_information%values_to_write)
767  do while (c_has_next(iterator))
768  map_entry=c_next_mapentry(iterator)
769  value_to_test=conv_to_real(map_entry%key)
770  if (value_to_test .le. time .and. value_to_test .gt. field_to_write_information%previous_write_time) then
771  items_to_remove(included_num)=map_entry%key
772  included_num=included_num+1
773  data_value=>get_data_value_by_field_name(field_to_write_information%values_to_write, map_entry%key)
774  map_data_iterator=c_get_iterator(data_value%map_values)
775  i=1
776  call check_thread_status(forthread_mutex_lock(file_state%mutex))
778  call lock_mpi()
779  do while (c_has_next(map_data_iterator))
780  map_data_entry=c_next_mapentry(map_data_iterator)
781  call check_netcdf_status(nf90_put_var(file_state%ncid, field_id, trim(map_data_entry%key), (/ 1, 1, i, j /)))
782  call check_netcdf_status(nf90_put_var(file_state%ncid, field_id, trim(c_get_string(map_data_entry)), (/ 1, 2, i, j /)))
783  call c_remove(data_value%map_values, map_data_entry%key)
784  i=i+1
785  end do
786  call unlock_mpi()
788  call check_thread_status(forthread_mutex_unlock(file_state%mutex))
789  call c_free(data_value%map_values)
790  j=j+1
791  end if
792  end do
793  if (included_num .gt. 1) then
794  do i=1, included_num-1
795  call c_remove(field_to_write_information%values_to_write, items_to_remove(i))
796  end do
797  end if
798  deallocate(items_to_remove)
799  end subroutine write_out_map
800 
803  subroutine write_out_options(io_configuration, file_state)
804  type(io_configuration_type), intent(inout) :: io_configuration
805  type(netcdf_diagnostics_type), intent(inout) :: file_state
806 
807  integer :: i
808  character(len=STRING_LENGTH), pointer :: sized_raw_character
809  class(*), pointer :: raw_data, raw_to_string
810 
811  call lock_mpi()
812  do i=1,options_size(io_configuration%options_database)
813  raw_data=> options_value_at(io_configuration%options_database, i)
814  raw_to_string=>raw_data
815  call check_netcdf_status(nf90_put_var(file_state%ncid, nopt_var_id, &
816  trim(options_key_at(io_configuration%options_database, i)), (/ 1, 1, i /)))
817  select type (raw_data)
818  type is(integer)
819  call check_netcdf_status(nf90_put_var(file_state%ncid, nopt_var_id, trim(conv_to_string(raw_data)), (/ 1, 2, i /)))
820  type is(real(kind=single_precision))
821  call check_netcdf_status(nf90_put_var(file_state%ncid, nopt_var_id, trim(conv_to_string(raw_data)), (/ 1, 2, i /)))
822  type is(real(kind=double_precision))
823  call check_netcdf_status(nf90_put_var(file_state%ncid, nopt_var_id, trim(conv_to_string(raw_data)), (/ 1, 2, i /)))
824  type is(logical)
825  call check_netcdf_status(nf90_put_var(file_state%ncid, nopt_var_id, trim(conv_to_string(raw_data)), (/ 1, 2, i /)))
826  type is(character(len=*))
827  ! Done this way to give the character size information and keep the (unsafe) cast in the conversion module
828  sized_raw_character=>conv_to_string(raw_to_string, .false., string_length)
829  call check_netcdf_status(nf90_put_var(file_state%ncid, nopt_var_id, trim(sized_raw_character), (/ 1, 2, i /)))
830  end select
831  end do
832  call unlock_mpi()
833 
834  end subroutine write_out_options
835 
841  subroutine define_time_series_dimensions(file_state, file_writer_information, time, time_points, termination_write)
842  type(netcdf_diagnostics_type), intent(inout) :: file_state
843  type(writer_type), intent(inout) :: file_writer_information
844  real, intent(in) :: time
845  type(map_type), intent(inout) :: time_points
846  logical, intent(in) :: termination_write
847 
848  integer :: i
849  character(len=STRING_LENGTH) :: dim_key
850  type(netcdf_diagnostics_timeseries_type), pointer :: timeseries_diag
851  class(*), pointer :: generic
852 
853  do i=1, size(file_writer_information%contents)
854  if (file_writer_information%contents(i)%output_frequency .lt. 0.0) then
855  dim_key="time_series_"//trim(conv_to_string(file_writer_information%contents(i)%timestep_frequency))
856  else
857  dim_key="time_series_"//trim(conv_to_string(file_writer_information%contents(i)%timestep_frequency))//"_"//&
858  trim(conv_to_string(file_writer_information%contents(i)%output_frequency))
859  end if
860  if (.not. c_contains(file_state%timeseries_dimension, dim_key)) then
861  allocate(timeseries_diag)
862  timeseries_diag%variable_written=.false.
863  timeseries_diag%num_entries=get_number_timeseries_entries(time_points, &
864  file_writer_information%contents(i)%previous_tracked_write_point, &
865  file_writer_information%contents(i)%output_frequency, file_writer_information%contents(i)%timestep_frequency, &
866  termination_write, timeseries_diag%last_write_point)
867  call lock_mpi()
868  call check_netcdf_status(nf90_def_dim(file_state%ncid, dim_key, timeseries_diag%num_entries, &
869  timeseries_diag%netcdf_dim_id))
870  call unlock_mpi()
871  generic=>timeseries_diag
872  call c_put_generic(file_state%timeseries_dimension, dim_key, generic, .false.)
873  end if
874  file_writer_information%contents(i)%previous_tracked_write_point=timeseries_diag%last_write_point
875  end do
876  end subroutine define_time_series_dimensions
877 
883  integer function get_number_timeseries_entries(time_points, previous_write_time, output_frequency, timestep_frequency, &
884  termination_write, last_write_entry)
885  type(map_type), intent(inout) :: time_points
886  real, intent(in) :: output_frequency, previous_write_time
887  integer, intent(in) :: timestep_frequency
888  logical, intent(in) :: termination_write
889  real, intent(out) :: last_write_entry
890 
891  integer :: ts
892  real :: tp_entry, write_point
893  type(iterator_type) :: iterator
894  type(mapentry_type) :: map_entry
895  logical :: include_item
896 
898  write_point=previous_write_time
899  iterator=c_get_iterator(time_points)
900  do while (c_has_next(iterator))
901  map_entry=c_next_mapentry(iterator)
902  ts=conv_to_integer(map_entry%key)
903  if (timestep_frequency .gt. 0) then
904  include_item=mod(ts, timestep_frequency) == 0
905  else
906  include_item=.false.
907  end if
908  if (include_item .or. (.not. c_has_next(iterator) .and. termination_write)) then
909  tp_entry=c_get_real(map_entry)
910  if (tp_entry .ge. write_point+output_frequency) then
912  write_point=tp_entry
913  last_write_entry=tp_entry
914  end if
915  end if
916  end do
917  end function get_number_timeseries_entries
918 
923  integer function define_coordinate_variable(file_state, coord_name)
924  type(netcdf_diagnostics_type), intent(inout) :: file_state
925  character(len=*), intent(in) :: coord_name
926 
927  integer :: field_id, dimension_ids(1)
928 
929  dimension_ids(1)=c_get_integer(file_state%dimension_to_id, trim(coord_name))
930  call lock_mpi()
931  call check_netcdf_status(nf90_def_var(file_state%ncid, trim(coord_name), nf90_double, dimension_ids, field_id))
932  call unlock_mpi()
934  end function define_coordinate_variable
935 
939  integer function define_options_database_variable(file_state)
940  type(netcdf_diagnostics_type), intent(inout) :: file_state
941 
942  integer :: field_id, dimension_ids(3)
943 
944  dimension_ids(1)=file_state%string_dim_id
945  dimension_ids(2)=file_state%key_value_dim_id
946  dimension_ids(3)=nopt_dim_id
947  call lock_mpi()
948  call check_netcdf_status(nf90_def_var(file_state%ncid, "options_database", nf90_char, dimension_ids, field_id))
949  call unlock_mpi()
952 
956  subroutine define_variables(io_configuration, file_state, file_writer_information)
957  type(io_configuration_type), intent(inout) :: io_configuration
958  type(netcdf_diagnostics_type), intent(inout) :: file_state
959  type(writer_type), intent(in) :: file_writer_information
960 
961  integer :: i, j, data_type, field_id, map_dim_id
962  integer, dimension(:), allocatable :: dimension_ids
963  character(len=STRING_LENGTH) :: variable_key
964  type(netcdf_diagnostics_timeseries_type), pointer :: timeseries_diag
965  class(*), pointer :: generic
966  type(iterator_type) :: iterator
967  type(mapentry_type) :: map_entry
968 
969  l_nc_dim = .false.
970  l_nd_dim = .false.
971 
972  iterator=c_get_iterator(file_state%timeseries_dimension)
973  do while (c_has_next(iterator))
974  map_entry=c_next_mapentry(iterator)
975  generic=>c_get_generic(map_entry)
976  select type(generic)
978  timeseries_diag=>generic
979  end select
980  call lock_mpi()
981  call check_netcdf_status(nf90_def_var(file_state%ncid, map_entry%key, &
982  nf90_double, timeseries_diag%netcdf_dim_id, timeseries_diag%netcdf_var_id))
983  call unlock_mpi()
984  end do
985 
986  do i=1, size(file_writer_information%contents)
987  if (.not. file_writer_information%contents(i)%enabled) cycle
988  if (file_writer_information%contents(i)%data_type == double_data_type) then
989  data_type=nf90_double
990  else if (file_writer_information%contents(i)%data_type == integer_data_type) then
991  data_type=nf90_int
992  else if (file_writer_information%contents(i)%data_type == string_data_type) then
993  data_type=nf90_char
994  end if
995  variable_key=get_field_key(file_writer_information%contents(i))
996  if (file_writer_information%contents(i)%field_type == array_field_type) then
997  allocate(dimension_ids(file_writer_information%contents(i)%dimensions+1))
998  do j=1, file_writer_information%contents(i)%dimensions
999  if (c_contains(file_state%dimension_to_id, file_writer_information%contents(i)%dim_size_defns(j))) then
1000  dimension_ids(j)=c_get_integer(file_state%dimension_to_id, file_writer_information%contents(i)%dim_size_defns(j))
1001  else
1002  call log_log(log_error, "Can not find information for dimension named '"//&
1003  trim(file_writer_information%contents(i)%dim_size_defns(j))//"'")
1004  end if
1005  end do
1006  dimension_ids(j)=retrieve_time_series_dimension_id_for_field(file_state, file_writer_information, i)
1007 
1009  ! a data field using its dimensions.
1010  if (any(dimension_ids .eq. nc_dim_id) .or. any(dimension_ids .eq. nd_dim_id)) then
1011  l_nc_dim = .true.
1012  l_nd_dim = .true.
1013  end if
1014 
1015  call lock_mpi()
1016  call check_netcdf_status(nf90_def_var(file_state%ncid, variable_key, &
1017  data_type, dimension_ids, field_id))
1018 
1019  if (file_writer_information%contents(i)%collective_write .and. &
1020  file_writer_information%contents(i)%collective_contiguous_optimisation .and. &
1021  io_configuration%number_of_io_servers .gt. 1) then
1022  call check_netcdf_status(nf90_def_var_fill(file_state%ncid, field_id, 1, 1))
1023  call check_netcdf_status(nf90_var_par_access(file_state%ncid, field_id, nf90_collective))
1024  end if
1025  call unlock_mpi()
1026  deallocate(dimension_ids)
1027  else if (file_writer_information%contents(i)%field_type == scalar_field_type) then
1028  call lock_mpi()
1029  call check_netcdf_status(nf90_def_var(file_state%ncid, variable_key, &
1030  data_type, retrieve_time_series_dimension_id_for_field(file_state, file_writer_information, i), field_id))
1031  call unlock_mpi()
1032  else if (file_writer_information%contents(i)%field_type == map_field_type) then
1033  allocate(dimension_ids(4))
1034  dimension_ids(1)=file_state%string_dim_id
1035  dimension_ids(2)=file_state%key_value_dim_id
1036  dimension_ids(3)=c_get_integer(file_state%dimension_to_id, file_writer_information%contents(i)%dim_size_defns(1))
1037  dimension_ids(4)=retrieve_time_series_dimension_id_for_field(file_state, file_writer_information, i)
1038  call lock_mpi()
1039  call check_netcdf_status(nf90_def_var(file_state%ncid, variable_key, data_type, dimension_ids, field_id))
1040  call unlock_mpi()
1041  deallocate(dimension_ids)
1042  end if
1043  call c_put_integer(file_state%variable_to_id, variable_key, field_id)
1044  if (len_trim(file_writer_information%contents(i)%units) .gt. 0) then
1045  call lock_mpi()
1046  call check_netcdf_status(nf90_put_att(file_state%ncid, field_id, "units", file_writer_information%contents(i)%units))
1047  call unlock_mpi()
1048  end if
1049  end do
1050 
1052  if (l_nc_dim) then
1053  allocate(dimension_ids(2))
1054  dimension_ids(1)=file_state%string_dim_id
1055  dimension_ids(2)=nc_dim_id
1056  call lock_mpi()
1057  call check_netcdf_status(nf90_def_var(file_state%ncid, "conditions_fields_short", &
1058  nf90_char, dimension_ids, nc_var_id_s))
1059  call check_netcdf_status(nf90_def_var(file_state%ncid, "conditions_fields_long", &
1060  nf90_char, dimension_ids, nc_var_id_l))
1061  call unlock_mpi()
1062  deallocate(dimension_ids)
1063  end if
1064  if (l_nd_dim) then
1065  allocate(dimension_ids(2))
1066  dimension_ids(1)=file_state%string_dim_id
1067  dimension_ids(2)=nd_dim_id
1068  call lock_mpi()
1069  call check_netcdf_status(nf90_def_var(file_state%ncid, "diagnostics_fields_short", &
1070  nf90_char, dimension_ids, nd_var_id_s))
1071  call check_netcdf_status(nf90_def_var(file_state%ncid, "diagnostics_fields_long", &
1072  nf90_char, dimension_ids, nd_var_id_l))
1073  call unlock_mpi()
1074  deallocate(dimension_ids)
1075  end if
1076 
1077  end subroutine define_variables
1078 
1079 
1086  integer function retrieve_time_series_dimension_id_for_field(file_state, file_writer_information, field_index)
1087  type(netcdf_diagnostics_type), intent(inout) :: file_state
1088  type(writer_type), intent(in) :: file_writer_information
1089  integer, intent(in) :: field_index
1090 
1091  type(netcdf_diagnostics_timeseries_type), pointer :: timeseries_diag
1092 
1093  timeseries_diag=>get_specific_timeseries_dimension(file_state, &
1094  file_writer_information%contents(field_index)%output_frequency, &
1095  file_writer_information%contents(field_index)%timestep_frequency)
1096  if (associated(timeseries_diag)) then
1097  retrieve_time_series_dimension_id_for_field=timeseries_diag%netcdf_dim_id
1098  else
1099  call log_log(log_error, "Can not find time series dimension with output frequency "//&
1100  trim(conv_to_string(file_writer_information%contents(field_index)%output_frequency)))
1101  end if
1103 
1110  function get_specific_timeseries_dimension(file_state, output_frequency, timestep_frequency)
1111  type(netcdf_diagnostics_type), intent(inout) :: file_state
1112  real, intent(in) :: output_frequency
1113  integer, intent(in) :: timestep_frequency
1115 
1116  character(len=STRING_LENGTH) :: dim_key
1117  class(*), pointer :: generic
1118 
1119  if (output_frequency .lt. 0.0) then
1120  dim_key="time_series_"//trim(conv_to_string(timestep_frequency))
1121  else
1122  dim_key="time_series_"//trim(conv_to_string(timestep_frequency))//"_"// trim(conv_to_string(output_frequency))
1123  end if
1124  generic=>c_get_generic(file_state%timeseries_dimension, dim_key)
1125 
1126  if (associated(generic)) then
1127  select type(generic)
1130  end select
1131  else
1133  end if
1134  end function get_specific_timeseries_dimension
1135 
1139  subroutine define_dimensions(file_state, dimension_sizing)
1140  type(netcdf_diagnostics_type), intent(inout) :: file_state
1141  type(map_type), intent(inout) :: dimension_sizing
1142 
1143  integer :: ncdf_dimid, dim_length
1144  type(iterator_type) :: iterator
1145  type(mapentry_type) :: map_entry
1146 
1147 
1148  iterator=c_get_iterator(dimension_sizing)
1149  call lock_mpi()
1150  do while (c_has_next(iterator))
1151  map_entry=c_next_mapentry(iterator)
1152  dim_length=c_get_integer(map_entry)
1153  if (dim_length .gt. 0) then
1154  call check_netcdf_status(nf90_def_dim(file_state%ncid, map_entry%key, dim_length, ncdf_dimid))
1155  call c_put_integer(file_state%dimension_to_id, map_entry%key, ncdf_dimid)
1156  if (map_entry%key == "nc") then
1157  nc_dim_id=ncdf_dimid
1158  end if
1159  if (map_entry%key == "nd") then
1160  nd_dim_id=ncdf_dimid
1161  end if
1162  if (map_entry%key == "number_options") then
1163  nopt_dim_id=ncdf_dimid
1164  end if
1165  end if
1166  end do
1167  call check_netcdf_status(nf90_def_dim(file_state%ncid, "string", string_length, file_state%string_dim_id))
1168  call check_netcdf_status(nf90_def_dim(file_state%ncid, "kvp", 2, file_state%key_value_dim_id))
1169  call unlock_mpi()
1170  end subroutine define_dimensions
1171 
1177  function get_file_state(filename, timestep, dolock)
1178  character(len=*), intent(in) :: filename
1179  integer, intent(in) :: timestep
1180  logical, intent(in) :: dolock
1181  type(netcdf_diagnostics_type), pointer :: get_file_state
1182 
1183  class(*), pointer :: generic
1184 
1186  generic=>c_get_generic(file_states, trim(filename)//"#"//trim(conv_to_string(timestep)))
1188 
1189  if (associated(generic)) then
1190  select type(generic)
1191  type is (netcdf_diagnostics_type)
1192  get_file_state=>generic
1193  end select
1194  else
1195  get_file_state=>null()
1196  end if
1197  end function get_file_state
1198 
1204  character(len=STRING_LENGTH) function get_field_key(field_to_write_information)
1205  type(writer_field_type), intent(in) :: field_to_write_information
1206 
1207  get_field_key=field_to_write_information%field_name
1208  if (field_to_write_information%duplicate_field_name) then
1209  if (field_to_write_information%time_manipulation_type == instantaneous_type) then
1210  get_field_key=trim(get_field_key)//"_instantaneous"
1211  else if (field_to_write_information%time_manipulation_type == time_averaged_type) then
1212  get_field_key=trim(get_field_key)//"_timeaveraged"
1213  end if
1214  end if
1215  end function get_field_key
1216 
1222  subroutine generate_unique_filename(old_name, new_name, configured_write_time, timestep)
1223  character(len=STRING_LENGTH), intent(in) :: old_name
1224  real, intent(in), optional :: configured_write_time
1225  integer, intent(in), optional :: timestep
1226  character(len=STRING_LENGTH), intent(out) :: new_name
1227 
1228  integer :: dot_posn
1229 
1230  dot_posn=index(old_name, ".")
1231  if (dot_posn .gt. 0) then
1232  new_name = old_name(1:dot_posn-1)
1233  else
1234  new_name=old_name
1235  end if
1236  if (present(configured_write_time)) then
1237  new_name=trim(new_name)//"_"//trim(conv_to_string(configured_write_time))
1238  else if (present(timestep)) then
1239  new_name=trim(new_name)//"_"//trim(conv_to_string(timestep))
1240  end if
1241  if (dot_posn .gt. 0) then
1242  new_name=trim(new_name)//old_name(dot_posn:len(old_name))
1243  end if
1244  end subroutine generate_unique_filename
1245 
1248  subroutine write_out_global_attributes(io_configuration, ncid, file_writer_information, timestep, time)
1249  type(io_configuration_type), intent(inout) :: io_configuration
1250  integer, intent(in) :: ncid, timestep
1251  type(writer_type), intent(inout) :: file_writer_information
1252  real, intent(in) :: time
1253 
1254  integer :: date_values(8), ierr
1255  character(len=50) :: date_time
1256 
1257  call date_and_time(values=date_values)
1258  call lock_mpi()
1259  call mpi_bcast(date_values, 8, mpi_int, 0, io_configuration%io_communicator, ierr)
1260  call unlock_mpi()
1261  date_time=trim(conv_to_string(date_values(3)))//"/"//&
1262  trim(conv_to_string(date_values(2)))//"/"//trim(conv_to_string(date_values(1)))//" "//trim(conv_to_string(&
1263  date_values(5)))// ":"//trim(conv_to_string(date_values(6)))//":"//trim(conv_to_string(date_values(7)))
1264 
1265  call lock_mpi()
1266  call check_netcdf_status(nf90_put_att(ncid, nf90_global, "title", file_writer_information%title))
1267  call check_netcdf_status(nf90_put_att(ncid, nf90_global, "created", date_time))
1268  call check_netcdf_status(nf90_put_att(ncid, nf90_global, "MONC time", trim(conv_to_string(time))))
1269  call check_netcdf_status(nf90_put_att(ncid, nf90_global, "MONC timestep", trim(conv_to_string(timestep))))
1270  call check_netcdf_status(nf90_put_att(ncid, nf90_global, "Diagnostic write frequency", &
1271  trim(conv_to_string(file_writer_information%write_time_frequency))))
1272  call check_netcdf_status(nf90_put_att(ncid, nf90_global, "Previous diagnostic write at", &
1273  trim(conv_to_string(file_writer_information%previous_write_time))))
1274  call unlock_mpi()
1275  end subroutine write_out_global_attributes
1276 end module netcdf_filetype_writer_mod
netcdf_filetype_writer_mod::generate_unique_filename
subroutine generate_unique_filename(old_name, new_name, configured_write_time, timestep)
Generates a unique filename based upon the base one specified and the number of completed timesteps.
Definition: netcdf_filetype.F90:1223
logging_mod::log_error
integer, parameter, public log_error
Only log ERROR messages.
Definition: logging.F90:11
conversions_mod
Conversion between common inbuilt FORTRAN data types.
Definition: conversions.F90:5
collections_mod::map_type
Map data structure that holds string (length 20 maximum) key value pairs.
Definition: collections.F90:86
collections_mod::c_is_empty
Returns whether a collection is empty.
Definition: collections.F90:437
configuration_parser_mod::cond_request
character(len=string_length), dimension(:), allocatable, public cond_request
Definition: configurationparser.F90:147
netcdf_misc_mod
NetCDF misc functionality which can be shared between modules that work with NetCDF files.
Definition: netcdf_misc.F90:2
netcdf_filetype_writer_mod::nc_var_id_s
integer nc_var_id_s
Definition: netcdf_filetype.F90:45
netcdf_filetype_writer_mod::close_netcdf_file
subroutine, public close_netcdf_file(io_configuration, field_name, timestep)
Call back for the inter IO reduction which actually does the NetCDF file closing which is a collectiv...
Definition: netcdf_filetype.F90:194
optionsdatabase_mod::options_key_at
character(len=string_length) function, public options_key_at(options_database, i)
Returns the ith key in the options database.
Definition: optionsdatabase.F90:53
forthread_mod::forthread_mutex_lock
integer function forthread_mutex_lock(mutex_id)
Definition: forthread.F90:284
netcdf_filetype_writer_mod::get_file_state
type(netcdf_diagnostics_type) function, pointer get_file_state(filename, timestep, dolock)
Retrieves a file state based upon its timestep or null if none is found.
Definition: netcdf_filetype.F90:1178
logging_mod::log_warn
integer, parameter, public log_warn
Log WARNING and ERROR messages.
Definition: logging.F90:12
io_server_client_mod::string_data_type
integer, parameter, public string_data_type
Definition: ioclient.F90:40
collections_mod::c_real_at
Retrieves the double precision real value held at the specific map index or null if index > map eleme...
Definition: collections.F90:497
io_server_state_writer_mod
The IO server state module which will write out the current state of the IO server to a NetCDF file.
Definition: io_state_writer.F90:2
configuration_parser_mod::diag_long
character(len=string_length), dimension(:), allocatable, public diag_long
Definition: configurationparser.F90:147
netcdf_filetype_writer_mod::write_independent_variable_to_diagnostics
subroutine write_independent_variable_to_diagnostics(field_to_write_information, timestep, time, file_state)
Writes independent variables to the diagnostics file. This writes the entire variable and works by wr...
Definition: netcdf_filetype.F90:649
collections_mod::c_put_generic
Puts a generic key-value pair into the map.
Definition: collections.F90:305
mpi_communication_mod
Abstraction layer around MPI, this issues and marshals the lower level communication details.
Definition: mpicommunication.F90:2
conversions_mod::conv_to_integer
Converts data types to integers.
Definition: conversions.F90:49
netcdf_filetype_writer_mod::nd_var_id_l
integer nd_var_id_l
Definition: netcdf_filetype.F90:45
netcdf_filetype_writer_mod::retrieve_time_series_dimension_id_for_field
integer function retrieve_time_series_dimension_id_for_field(file_state, file_writer_information, field_index)
For a specific field will retrieve the NetCDF id of the time series dimension most appropriate for th...
Definition: netcdf_filetype.F90:1087
netcdf_filetype_writer_mod::define_options_database_variable
integer function define_options_database_variable(file_state)
Defines the options_database variable in the NetCDF file.
Definition: netcdf_filetype.F90:940
io_server_client_mod::integer_data_type
integer, parameter, public integer_data_type
Definition: ioclient.F90:40
forthread_mod::forthread_mutex_init
integer function forthread_mutex_init(mutex_id, attr_id)
Definition: forthread.F90:274
collections_mod
Collection data structures.
Definition: collections.F90:7
writer_types_mod::writer_field_type
Definition: writer_types.F90:63
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
grids_mod::x_index
integer, parameter, public x_index
Definition: grids.F90:14
netcdf_filetype_writer_mod::write_variable
subroutine, public write_variable(io_configuration, field_to_write_information, filename, timestep, time)
Writes the contents of a variable to the NetCDF file. This also removes the written entries from the ...
Definition: netcdf_filetype.F90:238
io_server_state_writer_mod::define_io_server_state_contributions
subroutine, public define_io_server_state_contributions(io_configuration, writer_entries, time_points, netcdf_file)
Defines the dimensions and variables in a NetCDF file that consitute the IO server current state....
Definition: io_state_writer.F90:214
grids_mod::y_index
integer, parameter, public y_index
Definition: grids.F90:14
collections_mod::c_has_next
Definition: collections.F90:586
configuration_parser_mod::diag_request
character(len=string_length), dimension(:), allocatable, public diag_request
Definition: configurationparser.F90:147
collections_mod::hashmap_type
A hashmap structure, the same as a map but uses hashing for greatly improved performance when storing...
Definition: collections.F90:94
io_server_client_mod::scalar_field_type
integer, parameter, public scalar_field_type
Definition: ioclient.F90:38
io_server_client_mod::map_field_type
integer, parameter, public map_field_type
Field data type identifiers.
Definition: ioclient.F90:38
netcdf_filetype_writer_mod::nd_dim_id
integer nd_dim_id
Definition: netcdf_filetype.F90:44
writer_types_mod
Writer types which are shared across writing functionality. Also includes serialisation functionality...
Definition: writer_types.F90:2
collections_mod::c_size
Returns the number of elements in the collection.
Definition: collections.F90:428
forthread_mod
Definition: forthread.F90:1
netcdf_filetype_writer_mod::nc_dim_id
integer nc_dim_id
Definition: netcdf_filetype.F90:44
configuration_parser_mod::instantaneous_type
integer, parameter, public instantaneous_type
Definition: configurationparser.F90:28
io_server_client_mod::array_field_type
integer, parameter, public array_field_type
Definition: ioclient.F90:38
logging_mod::log_log
subroutine, public log_log(level, message, str)
Logs a message at the specified level. If the level is above the current level then the message is ig...
Definition: logging.F90:75
forthread_mod::forthread_rwlock_destroy
integer function forthread_rwlock_destroy(rwlock_id)
Definition: forthread.F90:495
mpi_communication_mod::lock_mpi
subroutine, public lock_mpi()
If we are explicitly managing MPI thread safety (SERIALIZED mode) then locks MPI.
Definition: mpicommunication.F90:58
netcdf_filetype_writer_mod::nc_var_id_l
integer nc_var_id_l
Definition: netcdf_filetype.F90:45
logging_mod::log_get_logging_level
integer function, public log_get_logging_level()
Retrieves the current logging level.
Definition: logging.F90:122
netcdf_filetype_writer_mod::write_out_options
subroutine write_out_options(io_configuration, file_state)
Writes out the options_database defining this model run.
Definition: netcdf_filetype.F90:804
forthread_mod::forthread_mutex_destroy
integer function forthread_mutex_destroy(mutex_id)
Definition: forthread.F90:265
writer_types_mod::netcdf_diagnostics_timeseries_type
Definition: writer_types.F90:93
logging_mod::log_debug
integer, parameter, public log_debug
Log DEBUG, INFO, WARNING and ERROR messages.
Definition: logging.F90:14
netcdf_filetype_writer_mod::l_nc_dim
logical l_nc_dim
Definition: netcdf_filetype.F90:43
mpi_communication_mod::wait_for_mpi_request
subroutine, public wait_for_mpi_request(request, status)
Waits for a specific MPI request to complete, either by managing thread safety and interleaving or ju...
Definition: mpicommunication.F90:75
netcdf_filetype_writer_mod::get_dimension_identifier
integer function get_dimension_identifier(dim_name, is_auto_dimension)
Translates a dimension name to its numeric corresponding identifier.
Definition: netcdf_filetype.F90:264
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
collections_mod::mapentry_type
Definition: collections.F90:46
writer_types_mod::writer_type
Definition: writer_types.F90:78
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
netcdf_filetype_writer_mod::file_states
type(hashmap_type), volatile file_states
Definition: netcdf_filetype.F90:40
netcdf_filetype_writer_mod::define_netcdf_file
subroutine, public define_netcdf_file(io_configuration, file_writer_information, timestep, time, time_points, termination_write)
Defines a NetCDF file - which creates it, defines all dimensions and variables. This must be called b...
Definition: netcdf_filetype.F90:70
netcdf_filetype_writer_mod::nd_var_id_s
integer nd_var_id_s
Definition: netcdf_filetype.F90:45
collections_mod::c_generic_at
Retrieves the generic value held at the specific map index or null if index > map elements.
Definition: collections.F90:467
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
writer_types_mod::write_field_collective_values_type
Definition: writer_types.F90:46
threadpool_mod
This is a thread pool and the single management "main" thread will spawn out free threads in the pool...
Definition: threadpool.F90:5
netcdf_filetype_writer_mod::store_io_server_state
subroutine, public store_io_server_state(io_configuration, writer_entries, time_points, file_writer_information, timestep)
Stores the IO server state in the NetCDF file.
Definition: netcdf_filetype.F90:152
collections_mod::c_integer_at
Retrieves the integer value held at the specific map index or null if index > map elements.
Definition: collections.F90:477
writer_types_mod::write_field_collective_descriptor_type
Definition: writer_types.F90:51
threadpool_mod::check_thread_status
subroutine, public check_thread_status(ierr)
Checks the error status of any thread operation and reports an error if it failed.
Definition: threadpool.F90:229
netcdf_filetype_writer_mod::netcdf_mutex
integer, volatile netcdf_mutex
Definition: netcdf_filetype.F90:41
datadefn_mod::single_precision
integer, parameter, public single_precision
Single precision (32 bit) kind.
Definition: datadefn.F90:13
writer_types_mod::netcdf_diagnostics_type
Definition: writer_types.F90:100
netcdf_filetype_writer_mod::write_contiguous_collective_variable_to_diagnostics
subroutine write_contiguous_collective_variable_to_diagnostics(io_configuration, field_to_write_information, timestep, time, file_state)
Writes contiguous collective variable blocks into the NetCDF files. These are blocks of data spanning...
Definition: netcdf_filetype.F90:359
netcdf_filetype_writer_mod::write_condition_variable
subroutine write_condition_variable(file_state, c_var_id, field_values)
Writes the conditional diagnostic variable names into the NetCDF file.
Definition: netcdf_filetype.F90:327
netcdf_filetype_writer_mod::get_next_specific_monc_info
type(write_field_collective_monc_info_type) function, pointer get_next_specific_monc_info(iterator)
Retrieves the next specific monc information item from the iterator.
Definition: netcdf_filetype.F90:513
grids_mod::z_index
integer, parameter, public z_index
Grid index parameters.
Definition: grids.F90:14
optionsdatabase_mod::options_size
integer function, public options_size(options_database)
Returns the number of entries in the options database.
Definition: optionsdatabase.F90:43
conversions_mod::conv_to_string
Converts data types to strings.
Definition: conversions.F90:38
netcdf_filetype_writer_mod::get_specific_timeseries_dimension
type(netcdf_diagnostics_timeseries_type) function, pointer get_specific_timeseries_dimension(file_state, output_frequency, timestep_frequency)
Given the file state and the output frequency of a field will retrive the appropriate time series dim...
Definition: netcdf_filetype.F90:1111
collections_mod::iterator_type
Definition: collections.F90:51
netcdf_filetype_writer_mod::finalise_netcdf_filetype
subroutine, public finalise_netcdf_filetype()
Finalises the NetCDF writing functionality.
Definition: netcdf_filetype.F90:59
configuration_parser_mod::time_averaged_type
integer, parameter, public time_averaged_type
Definition: configurationparser.F90:28
forthread_mod::forthread_rwlock_init
integer function forthread_rwlock_init(rwlock_id, attr_id)
Definition: forthread.F90:504
netcdf_filetype_writer_mod
The NetCDF file type writer which performs actual writing of NetCDF files to the parallel filesystem....
Definition: netcdf_filetype.F90:3
configuration_parser_mod::io_configuration_type
Overall IO configuration.
Definition: configurationparser.F90:104
collections_mod::c_get_real
Gets a specific double precision real element out of the list, stack, queue or map with the correspon...
Definition: collections.F90:399
netcdf_filetype_writer_mod::file_states_rwlock
integer, volatile file_states_rwlock
Definition: netcdf_filetype.F90:41
collections_mod::c_put_integer
Puts an integer key-value pair into the map.
Definition: collections.F90:318
collections_mod::c_free
Frees up all the allocatable, heap, memory associated with a list, stack, queue or map.
Definition: collections.F90:577
netcdf_filetype_writer_mod::write_out_map
subroutine write_out_map(field_to_write_information, timestep, time, file_state)
Definition: netcdf_filetype.F90:750
netcdf_filetype_writer_mod::define_time_series_dimensions
subroutine define_time_series_dimensions(file_state, file_writer_information, time, time_points, termination_write)
Defines dimensions for all required dimensions. This is usually the number required plus one,...
Definition: netcdf_filetype.F90:842
netcdf_filetype_writer_mod::nopt_dim_id
integer nopt_dim_id
Definition: netcdf_filetype.F90:44
netcdf_filetype_writer_mod::get_writer_entry_from_netcdf
type(writer_type) function, pointer, public get_writer_entry_from_netcdf(field_name, timestep, terminated)
Looks up and retrieves the writer entry that corresponds to this NetCDF file state.
Definition: netcdf_filetype.F90:176
netcdf_filetype_writer_mod::get_next_collective_descriptor
type(write_field_collective_descriptor_type) function, pointer get_next_collective_descriptor(iterator)
Retrieves the next collective descriptor based upon the iterator.
Definition: netcdf_filetype.F90:497
collections_mod::c_next_generic
Definition: collections.F90:610
configuration_parser_mod::get_data_value_by_field_name
Definition: configurationparser.F90:30
netcdf_filetype_writer_mod::initialise_netcdf_filetype
subroutine, public initialise_netcdf_filetype()
Initialises the NetCDF writing functionality.
Definition: netcdf_filetype.F90:53
writer_types_mod::write_field_collective_monc_info_type
Definition: writer_types.F90:58
netcdf_filetype_writer_mod::nopt_var_id
integer nopt_var_id
Definition: netcdf_filetype.F90:45
logging_mod::log_is_master
logical function, public log_is_master()
Determines whether the process is the master logging process. This might be preferable rather than ca...
Definition: logging.F90:66
logging_mod
Logging utility.
Definition: logging.F90:2
datadefn_mod::double_precision
integer, parameter, public double_precision
Double precision (64 bit) kind.
Definition: datadefn.F90:14
netcdf_filetype_writer_mod::define_variables
subroutine define_variables(io_configuration, file_state, file_writer_information)
Defines all variables in the file writer state.
Definition: netcdf_filetype.F90:957
datadefn_mod
Contains common definitions for the data and datatypes used by MONC.
Definition: datadefn.F90:2
configuration_parser_mod::data_values_type
Definition: configurationparser.F90:34
netcdf_filetype_writer_mod::l_nd_dim
logical l_nd_dim
Definition: netcdf_filetype.F90:43
netcdf_filetype_writer_mod::define_coordinate_variable
integer function define_coordinate_variable(file_state, coord_name)
Defines a coordinate variable in the NetCDF file.
Definition: netcdf_filetype.F90:924
datadefn_mod::string_length
integer, parameter, public string_length
Default length of strings.
Definition: datadefn.F90:10
netcdf_misc_mod::check_netcdf_status
subroutine, public check_netcdf_status(status, found_flag)
Will check a NetCDF status and write to log_log error any decoded statuses. Can be used to decode whe...
Definition: netcdf_misc.F90:19
forthread_mod::forthread_mutex_unlock
integer function forthread_mutex_unlock(mutex_id)
Definition: forthread.F90:302
logging_mod::log_master_log
subroutine, public log_master_log(level, message)
Will log just from the master process.
Definition: logging.F90:47
collections_mod::c_get_iterator
Definition: collections.F90:581
collections_mod::list_type
List data structure which implements a doubly linked list. This list will preserve its order.
Definition: collections.F90:60
netcdf_filetype_writer_mod::write_out_number_values
subroutine write_out_number_values(field_to_write_information, timestep, time, file_state)
Definition: netcdf_filetype.F90:666
io_server_state_writer_mod::write_io_server_state
subroutine, public write_io_server_state(io_configuration, writer_entries, time_points, netcdf_file)
Packags up and writes the actual IO server state into the NetCDF file. The act of serialisation will ...
Definition: io_state_writer.F90:303
netcdf_filetype_writer_mod::get_number_timeseries_entries
integer function get_number_timeseries_entries(time_points, previous_write_time, output_frequency, timestep_frequency, termination_write, last_write_entry)
Retrieves the number of timeseries entries for a specific frequency and previous write time....
Definition: netcdf_filetype.F90:885
optionsdatabase_mod::options_value_at
class(*) function, pointer, public options_value_at(options_database, i)
Returns the value at index in the database.
Definition: optionsdatabase.F90:64
netcdf_filetype_writer_mod::write_out_global_attributes
subroutine write_out_global_attributes(io_configuration, ncid, file_writer_information, timestep, time)
Writes out global attributes into the checkpoint.
Definition: netcdf_filetype.F90:1249
mpi_communication_mod::unlock_mpi
subroutine, public unlock_mpi()
If we are explicitly managing MPI thread safety (SERIALIZED mode) then unlocks MPI.
Definition: mpicommunication.F90:63
collections_mod::c_remove
Removes a specific element from the list or map.
Definition: collections.F90:419
netcdf_filetype_writer_mod::get_field_key
character(len=string_length) function get_field_key(field_to_write_information)
Retrieves the field key, corresponding to the field name in the NetCDF file and what we store against...
Definition: netcdf_filetype.F90:1205
configuration_parser_mod::cond_long
character(len=string_length), dimension(:), allocatable, public cond_long
Definition: configurationparser.F90:147
netcdf_filetype_writer_mod::write_collective_variable_to_diagnostics
subroutine write_collective_variable_to_diagnostics(io_configuration, field_to_write_information, timestep, time, file_state)
Writes collective variables, where we are working with the values from multiple MONCs and storing the...
Definition: netcdf_filetype.F90:532
netcdf_filetype_writer_mod::write_coordinate_variable
subroutine write_coordinate_variable(file_state, coord_var_id, field_values)
Writes a coordinate variable into the NetCDF file.
Definition: netcdf_filetype.F90:310
collections_mod::c_next_string
Definition: collections.F90:594
forthread_mod::forthread_rwlock_wrlock
integer function forthread_rwlock_wrlock(lock_id)
Definition: forthread.F90:532
conversions_mod::conv_to_real
Converts data types to real.
Definition: conversions.F90:60
collections_mod::c_next_mapentry
Definition: collections.F90:606
collections_mod::c_get_integer
Gets a specific integer element out of the list, stack, queue or map with the corresponding key.
Definition: collections.F90:378
forthread_mod::forthread_rwlock_rdlock
integer function forthread_rwlock_rdlock(lock_id)
Definition: forthread.F90:514
grids_mod
Functionality to support the different types of grid and abstraction between global grids and local o...
Definition: grids.F90:5
collections_mod::c_add_string
Adds a string to the end of the list.
Definition: collections.F90:222
optionsdatabase_mod
Manages the options database. Contains administration functions and deduce runtime options from the c...
Definition: optionsdatabase.F90:7
configuration_parser_mod
Parses the XML configuration file to produce the io configuration description which contains the data...
Definition: configurationparser.F90:3
forthread_mod::forthread_rwlock_unlock
integer function forthread_rwlock_unlock(lock_id)
Definition: forthread.F90:550
collections_mod::hashset_type
Hashset structure which will store unique strings. The hashing aspect means that lookup is very fast ...
Definition: collections.F90:102
netcdf_filetype_writer_mod::get_dimension_original_size
integer function get_dimension_original_size(dim_name, dimension_store)
Retrieves the original size of a specific dimension (which is auto)
Definition: netcdf_filetype.F90:293
netcdf_filetype_writer_mod::define_dimensions
subroutine define_dimensions(file_state, dimension_sizing)
Defines spatial dimensions in the diagnostics file.
Definition: netcdf_filetype.F90:1140
datadefn_mod::default_precision
integer, parameter, public default_precision
MPI communication type which we use for the prognostic and calculation data.
Definition: datadefn.F90:17