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
32 use mpi,
only : mpi_status_ignore, mpi_request_null, mpi_int
69 subroutine define_netcdf_file(io_configuration, file_writer_information, timestep, time, time_points, termination_write)
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
77 character(len=STRING_LENGTH) :: unique_filename
79 class(*),
pointer :: generic
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
93 generic=>ncdf_writer_state
98 if (file_writer_information%write_on_model_time)
then
100 file_writer_information%defined_write_time)
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))
112 call define_variables(io_configuration, ncdf_writer_state, file_writer_information)
121 if (io_configuration%my_io_rank == 0)
then
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
160 ncdf_writer_state=>
get_file_state(file_writer_information%filename, timestep, .true.)
176 character(len=STRING_LENGTH) :: field_name
178 logical,
intent(out),
optional :: terminated
184 if (
present(terminated)) terminated=file_state%termination_write
195 character(len=STRING_LENGTH) :: field_name
199 class(*),
pointer :: generic
212 call c_free(file_state%dimension_to_id)
213 call c_free(file_state%variable_to_id)
222 call c_free(file_state%timeseries_dimension)
237 subroutine write_variable(io_configuration, field_to_write_information, filename, timestep, time)
240 character(len=*),
intent(in) :: filename
241 integer,
intent(in) :: timestep
242 real,
intent(in) :: time
247 if (field_to_write_information%collective_write)
then
248 if (field_to_write_information%collective_contiguous_optimisation)
then
250 timestep, time, file_state)
264 character(len=*),
intent(in) :: dim_name
265 logical,
intent(out),
optional :: is_auto_dimension
268 logical :: is_modified_size
270 dash_idx=index(dim_name,
"_")
272 is_modified_size=dash_idx .ne. -1
273 if (.not. is_modified_size) dash_idx=len_trim(dim_name)
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
285 if (
present(is_auto_dimension)) is_auto_dimension=is_modified_size
293 character(len=*),
intent(in) :: dim_name
294 type(
map_type),
intent(inout) :: dimension_store
298 dash_idx=index(dim_name,
"_")
300 if (dash_idx .eq. -1) dash_idx=len_trim(dim_name)
311 integer,
intent(in) :: coord_var_id
314 integer :: count_to_write(1)
316 count_to_write(1)=
size(field_values)
318 call check_netcdf_status(nf90_put_var(file_state%ncid, coord_var_id, field_values, count=count_to_write))
328 integer,
intent(in) :: c_var_id
329 character(len=STRING_LENGTH),
dimension(:),
intent(in) :: field_values
331 integer :: count_to_write(2), start_pos(2)
332 integer :: pos, string_size
333 character(len=STRING_LENGTH) :: dum_string
338 do pos=1,
size(field_values)
339 dum_string = trim(field_values(pos))
340 count_to_write(1) = len(trim(field_values(pos)))
343 start=start_pos, count=count_to_write))
361 integer,
intent(in) :: timestep
362 real,
intent(in) :: time
365 real :: value_to_test
366 real(kind=
default_precision),
dimension(:,:,:,:),
allocatable :: contiguous_values
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
371 class(*),
pointer :: generic
377 integer :: number_time_entries, i, start(4), count(4), field_id, ierr
378 character(len=STRING_LENGTH) :: removal_key
381 field_to_write_information%timestep_frequency)
383 if (.not. timeseries_diag%variable_written)
allocate(timeseries_time_to_write(timeseries_diag%num_entries))
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))
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)
396 if (number_time_entries .ne. timeseries_diag%num_entries)
then
399 if (number_time_entries .gt. timeseries_diag%num_entries) number_time_entries=timeseries_diag%num_entries
402 collective_descriptor_iterator=
c_get_iterator(field_to_write_information%collective_descriptors)
403 do while (
c_has_next(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)
410 value_to_write_iterator=
c_get_iterator(field_to_write_information%values_to_write)
412 do while (
c_has_next(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
417 if (
allocated(timeseries_time_to_write)) timeseries_time_to_write(i)=value_to_test
421 multi_monc_entries=>generic
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)/))
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)/))
434 deallocate(data_value%values)
435 deallocate(data_value)
439 count(1:3)=collective_descriptor%count
440 count(4)=number_time_entries
441 start(1:3)=collective_descriptor%absolute_start
446 call check_netcdf_status(nf90_put_var(file_state%ncid, field_id, contiguous_values, start=start, count=count))
450 deallocate(contiguous_values)
451 if (
allocated(timeseries_time_to_write))
then
455 timeseries_time_to_write, count=(/ timeseries_diag%num_entries /)))
458 timeseries_diag%variable_written=.true.
459 deallocate(timeseries_time_to_write)
464 do while (
c_has_next(value_to_remove_iterator))
466 generic=>
c_get_generic(field_to_write_information%values_to_write, removal_key)
469 multi_monc_entries=>generic
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)
475 call c_free(items_to_remove)
477 if (field_to_write_information%max_num_collective_writes_request_handle .ne. mpi_request_null)
then
480 if (
c_size(field_to_write_information%collective_descriptors) .lt. field_to_write_information%max_num_collective_writes)
then
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/)))
500 class(*),
pointer :: generic
516 class(*),
pointer :: generic
534 integer,
intent(in) :: timestep
535 real,
intent(in) :: time
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
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
548 type(
iterator_type) :: value_to_write_iterator, monc_entries_iterator
549 type(
mapentry_type) :: value_to_write_map_entry, monc_entries_map_entry
552 field_to_write_information%timestep_frequency)
553 if (.not. timeseries_diag%variable_written)
allocate(timeseries_time_to_write(timeseries_diag%num_entries))
555 allocate(items_to_remove(timeseries_diag%num_entries))
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))
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
568 multi_monc_entries=>generic
570 monc_entries_iterator=
c_get_iterator(multi_monc_entries%monc_values)
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
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
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
587 dim_start=auto_period - &
588 mod(io_configuration%registered_moncs(monc_location)%local_dim_starts(dim_identifier)-2, auto_period)
590 count(k)=ceiling(real(io_configuration%registered_moncs(monc_location)%local_dim_sizes(dim_identifier) - &
591 (dim_start-1))/auto_period)
594 call log_log(
log_error,
"Can not locate dimension "//trim(field_to_write_information%dim_size_defns(k)))
597 start(field_to_write_information%dimensions+1) = included_num
598 count(field_to_write_information%dimensions+1) = 1
602 call check_netcdf_status(nf90_put_var(file_state%ncid, field_id, data_value%values, start=start, count=count))
606 deallocate(data_value%values)
607 deallocate(data_value)
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)
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))
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="//&
624 if (
allocated(timeseries_time_to_write))
then
628 timeseries_time_to_write, count=(/ timeseries_diag%num_entries /)))
631 timeseries_diag%variable_written=.true.
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))
638 deallocate(items_to_remove)
639 if (
allocated(timeseries_time_to_write))
deallocate(timeseries_time_to_write)
650 integer,
intent(in) :: timestep
651 real,
intent(in) :: time
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)
667 integer,
intent(in) :: timestep
668 real,
intent(in) :: time
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
679 character(len=STRING_LENGTH),
dimension(:),
allocatable :: items_to_remove
683 field_to_write_information%timestep_frequency)
689 if (.not. timeseries_diag%variable_written)
allocate(timeseries_time_to_write(timeseries_diag%num_entries))
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)
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)
704 if (value_to_test .le. time .and. value_to_test .gt. field_to_write_information%previous_write_time)
then
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
715 call log_log(
log_warn,
"Omitted time entry of field '"//trim(field_to_write_information%field_name)//&
716 "' as past time dimension length")
720 count_to_write(
size(count_to_write))=included_num-1
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="//&
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
733 timeseries_time_to_write, count=(/ timeseries_diag%num_entries /)))
734 timeseries_diag%variable_written=.true.
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))
745 deallocate(items_to_remove)
746 if (
allocated(timeseries_time_to_write))
deallocate(timeseries_time_to_write)
749 subroutine write_out_map(field_to_write_information, timestep, time, file_state)
751 integer,
intent(in) :: timestep
752 real,
intent(in) :: time
755 integer :: i, j, field_id, included_num
756 real :: value_to_test
760 character(len=STRING_LENGTH),
dimension(:),
allocatable :: items_to_remove
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)
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
781 call check_netcdf_status(nf90_put_var(file_state%ncid, field_id, trim(map_data_entry%key), (/ 1, 1, i, j /)))
783 call c_remove(data_value%map_values, map_data_entry%key)
789 call c_free(data_value%map_values)
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))
798 deallocate(items_to_remove)
808 character(len=STRING_LENGTH),
pointer :: sized_raw_character
809 class(*),
pointer :: raw_data, raw_to_string
814 raw_to_string=>raw_data
816 trim(
options_key_at(io_configuration%options_database, i)), (/ 1, 1, i /)))
817 select type (raw_data)
826 type is(
character(len=*))
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
849 character(len=STRING_LENGTH) :: dim_key
851 class(*),
pointer :: generic
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))
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))
860 if (.not.
c_contains(file_state%timeseries_dimension, dim_key))
then
861 allocate(timeseries_diag)
862 timeseries_diag%variable_written=.false.
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)
868 call check_netcdf_status(nf90_def_dim(file_state%ncid, dim_key, timeseries_diag%num_entries, &
869 timeseries_diag%netcdf_dim_id))
871 generic=>timeseries_diag
872 call c_put_generic(file_state%timeseries_dimension, dim_key, generic, .false.)
874 file_writer_information%contents(i)%previous_tracked_write_point=timeseries_diag%last_write_point
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
892 real :: tp_entry, write_point
895 logical :: include_item
898 write_point=previous_write_time
903 if (timestep_frequency .gt. 0)
then
904 include_item=mod(ts, timestep_frequency) == 0
908 if (include_item .or. (.not.
c_has_next(iterator) .and. termination_write))
then
910 if (tp_entry .ge. write_point+output_frequency)
then
913 last_write_entry=tp_entry
925 character(len=*),
intent(in) :: coord_name
927 integer :: field_id, dimension_ids(1)
929 dimension_ids(1)=
c_get_integer(file_state%dimension_to_id, trim(coord_name))
931 call check_netcdf_status(nf90_def_var(file_state%ncid, trim(coord_name), nf90_double, dimension_ids, field_id))
942 integer :: field_id, dimension_ids(3)
944 dimension_ids(1)=file_state%string_dim_id
945 dimension_ids(2)=file_state%key_value_dim_id
948 call check_netcdf_status(nf90_def_var(file_state%ncid,
"options_database", nf90_char, dimension_ids, field_id))
959 type(
writer_type),
intent(in) :: file_writer_information
961 integer :: i, j, data_type, field_id, map_dim_id
962 integer,
dimension(:),
allocatable :: dimension_ids
963 character(len=STRING_LENGTH) :: variable_key
965 class(*),
pointer :: generic
978 timeseries_diag=>generic
982 nf90_double, timeseries_diag%netcdf_dim_id, timeseries_diag%netcdf_var_id))
986 do i=1,
size(file_writer_information%contents)
987 if (.not. file_writer_information%contents(i)%enabled) cycle
989 data_type=nf90_double
990 else if (file_writer_information%contents(i)%data_type ==
integer_data_type)
then
992 else if (file_writer_information%contents(i)%data_type ==
string_data_type)
then
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))
1002 call log_log(
log_error,
"Can not find information for dimension named '"//&
1003 trim(file_writer_information%contents(i)%dim_size_defns(j))//
"'")
1017 data_type, dimension_ids, field_id))
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
1026 deallocate(dimension_ids)
1027 else if (file_writer_information%contents(i)%field_type ==
scalar_field_type)
then
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))
1039 call check_netcdf_status(nf90_def_var(file_state%ncid, variable_key, data_type, dimension_ids, field_id))
1041 deallocate(dimension_ids)
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
1046 call check_netcdf_status(nf90_put_att(file_state%ncid, field_id,
"units", file_writer_information%contents(i)%units))
1053 allocate(dimension_ids(2))
1054 dimension_ids(1)=file_state%string_dim_id
1062 deallocate(dimension_ids)
1065 allocate(dimension_ids(2))
1066 dimension_ids(1)=file_state%string_dim_id
1074 deallocate(dimension_ids)
1088 type(
writer_type),
intent(in) :: file_writer_information
1089 integer,
intent(in) :: field_index
1094 file_writer_information%contents(field_index)%output_frequency, &
1095 file_writer_information%contents(field_index)%timestep_frequency)
1096 if (
associated(timeseries_diag))
then
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)))
1112 real,
intent(in) :: output_frequency
1113 integer,
intent(in) :: timestep_frequency
1116 character(len=STRING_LENGTH) :: dim_key
1117 class(*),
pointer :: generic
1119 if (output_frequency .lt. 0.0)
then
1124 generic=>
c_get_generic(file_state%timeseries_dimension, dim_key)
1126 if (
associated(generic))
then
1127 select type(generic)
1141 type(
map_type),
intent(inout) :: dimension_sizing
1143 integer :: ncdf_dimid, dim_length
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
1159 if (map_entry%key ==
"nd")
then
1162 if (map_entry%key ==
"number_options")
then
1168 call check_netcdf_status(nf90_def_dim(file_state%ncid,
"kvp", 2, file_state%key_value_dim_id))
1178 character(len=*),
intent(in) :: filename
1179 integer,
intent(in) :: timestep
1180 logical,
intent(in) :: dolock
1183 class(*),
pointer :: generic
1189 if (
associated(generic))
then
1190 select type(generic)
1208 if (field_to_write_information%duplicate_field_name)
then
1211 else if (field_to_write_information%time_manipulation_type ==
time_averaged_type)
then
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
1230 dot_posn=index(old_name,
".")
1231 if (dot_posn .gt. 0)
then
1232 new_name = old_name(1:dot_posn-1)
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
1241 if (dot_posn .gt. 0)
then
1242 new_name=trim(new_name)//old_name(dot_posn:len(old_name))
1250 integer,
intent(in) :: ncid, timestep
1251 type(
writer_type),
intent(inout) :: file_writer_information
1252 real,
intent(in) :: time
1254 integer :: date_values(8), ierr
1255 character(len=50) :: date_time
1257 call date_and_time(values=date_values)
1259 call mpi_bcast(date_values, 8, mpi_int, 0, io_configuration%io_communicator, ierr)
1266 call check_netcdf_status(nf90_put_att(ncid, nf90_global,
"title", file_writer_information%title))
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))))