Skip to content

Commit

Permalink
Reintroduces the option to flush_nc_files with fms2_io (#826)
Browse files Browse the repository at this point in the history
Adds routine to flush_nc_files via fms2_io if the namelist variable in diag_data.F90 is set.
  • Loading branch information
uramirez8707 authored Oct 7, 2021
1 parent 3876769 commit c057b75
Show file tree
Hide file tree
Showing 4 changed files with 36 additions and 2 deletions.
23 changes: 22 additions & 1 deletion diag_manager/diag_output.F90
Original file line number Diff line number Diff line change
Expand Up @@ -70,7 +70,7 @@ MODULE diag_output_mod
PRIVATE
PUBLIC :: diag_output_init, write_axis_meta_data, write_field_meta_data, done_meta_data,&
& diag_fieldtype, get_diag_global_att, set_diag_global_att
PUBLIC :: diag_field_write, diag_write_time !< use_mpp_io = .false.
PUBLIC :: diag_field_write, diag_write_time, diag_flush
TYPE(diag_global_att_type), SAVE :: diag_global_att

INTEGER, PARAMETER :: NETCDF1 = 1
Expand Down Expand Up @@ -1364,6 +1364,27 @@ SUBROUTINE set_diag_global_att(component, gridType, tileName)
diag_global_att%tile_name = tileName
! endif
END SUBROUTINE set_diag_global_att

!> @brief Flushes the file into disk
subroutine diag_flush(file_num, fileobjU, fileobj, fileobjND, fnum_for_domain)
integer, intent(in) :: file_num !< Index in the fileobj* types array
type(FmsNetcdfUnstructuredDomainFile_t),intent(inout) :: fileobjU(:) !< Array of non domain decomposed fileobj
type(FmsNetcdfDomainFile_t), intent(inout) :: fileobj(:) !< Array of domain decomposed fileobj
type(FmsNetcdfFile_t), intent(inout) :: fileobjND(:) !< Array of unstructured domain fileobj
character(len=2), intent(in) :: fnum_for_domain !< String indicating the type of domain
!! "2d" domain decomposed
!! "ug" unstructured domain decomposed
!! "nd" no domain
if (fnum_for_domain == "2d" ) then
call flush_file (fileobj (file_num))
elseif (fnum_for_domain == "nd") then
call flush_file (fileobjND (file_num))
elseif (fnum_for_domain == "ug") then
call flush_file (fileobjU(file_num))
else
call error_mesg("diag_field_write","No file object is associated with this file number",fatal)
endif
end subroutine diag_flush
END MODULE diag_output_mod
!> @}
! close documentation grouping
3 changes: 2 additions & 1 deletion diag_manager/diag_util.F90
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@ MODULE diag_util_mod
& get_axes_shift, get_diag_axis_name, get_diag_axis_domain_name, get_domainUG, &
& get_axis_reqfld, axis_is_compressed, get_compressed_axes_ids
USE diag_output_mod, ONLY: diag_output_init, write_axis_meta_data,&
& write_field_meta_data, done_meta_data
& write_field_meta_data, done_meta_data, diag_flush
USE diag_output_mod, ONLY: diag_field_write, diag_write_time !<fms2_io use_mpp_io=.false.
USE diag_grid_mod, ONLY: get_local_indexes
USE fms_mod, ONLY: error_mesg, FATAL, WARNING, NOTE, mpp_pe, mpp_root_pe, lowercase, fms_error_handler,&
Expand Down Expand Up @@ -2299,6 +2299,7 @@ SUBROUTINE diag_data_out(file, field, dat, time, final_call_in, static_write_in,
END IF
ELSE
IF ( time > files(file)%last_flush .AND. (flush_nc_files.OR.debug_diag_manager) ) THEN
call diag_flush(file, fileobjU, fileobj, fileobjND, fnum_for_domain(file))
files(file)%last_flush = time
END IF
END IF
Expand Down
1 change: 1 addition & 0 deletions fms2_io/fms2_io.F90
Original file line number Diff line number Diff line change
Expand Up @@ -104,6 +104,7 @@ module fms2_io_mod
public :: get_instance_filename
public :: nullify_filename_appendix
public :: string2
public :: flush_file
!> @}

!> @brief Opens a given netcdf or domain file.
Expand Down
11 changes: 11 additions & 0 deletions fms2_io/netcdf_io.F90
Original file line number Diff line number Diff line change
Expand Up @@ -233,6 +233,7 @@ module netcdf_io_mod
public :: set_fileobj_time_name
public :: write_restart_bc
public :: read_restart_bc
public :: flush_file

!> @ingroup netcdf_io_mod
interface netcdf_add_restart_variable
Expand Down Expand Up @@ -2265,6 +2266,16 @@ subroutine write_restart_bc(fileobj, unlim_dim_level)

end subroutine write_restart_bc

!> @brief flushes the netcdf file into disk
subroutine flush_file(fileobj)
class(FmsNetcdfFile_t), intent(inout) :: fileobj !< FMS2_io fileobj

integer :: err !< Netcdf error code

err = nf90_sync(fileobj%ncid)
call check_netcdf_code(err, "Flush_file: File:"//trim(fileobj%path))
end subroutine flush_file

end module netcdf_io_mod
!> @}
! close documentation grouping

0 comments on commit c057b75

Please sign in to comment.