Skip to content

Commit

Permalink
Ignore checksum option and performance with (1,1) io layout (#556)
Browse files Browse the repository at this point in the history
* Update atmos_model and FV3GFS_io read performance when io_layout=1,1 and allow one to override data integrity checks in FMS restart logic

Co-authored-by: Jun Wang <junwang-noaa@users.noreply.github.com>
  • Loading branch information
junwang-noaa and junwang-noaa authored Jun 29, 2022
1 parent 280eeef commit 18bf9b7
Show file tree
Hide file tree
Showing 3 changed files with 29 additions and 21 deletions.
13 changes: 9 additions & 4 deletions atmos_model.F90
Original file line number Diff line number Diff line change
Expand Up @@ -146,6 +146,7 @@ module atmos_model_mod
real(kind=8), pointer, dimension(:,:) :: area
real(kind=8), pointer, dimension(:,:,:) :: layer_hgt, level_hgt
type(domain2d) :: domain ! domain decomposition
type(domain2d) :: domain_for_read ! domain decomposition
type(time_type) :: Time ! current time
type(time_type) :: Time_step ! atmospheric time step.
type(time_type) :: Time_init ! reference time.
Expand Down Expand Up @@ -173,7 +174,9 @@ module atmos_model_mod
!logical :: debug = .true.
logical :: sync = .false.
real :: avg_max_length=3600.
namelist /atmos_model_nml/ blocksize, chksum_debug, dycore_only, debug, sync, ccpp_suite, avg_max_length
logical :: ignore_rst_cksum = .false.
namelist /atmos_model_nml/ blocksize, chksum_debug, dycore_only, debug, sync, ccpp_suite, avg_max_length, &
ignore_rst_cksum

type (time_type) :: diag_time, diag_time_fhzero

Expand Down Expand Up @@ -553,7 +556,8 @@ subroutine atmos_model_init (Atmos, Time_init, Time, Time_step)
!-----------------------------------------------------------------------
call atmosphere_resolution (nlon, nlat, global=.false.)
call atmosphere_resolution (mlon, mlat, global=.true.)
call atmosphere_domain (Atmos%domain, Atmos%layout, Atmos%regional, Atmos%nested, &
call atmosphere_domain (Atmos%domain, Atmos%domain_for_read, Atmos%layout, &
Atmos%regional, Atmos%nested, &
Atmos%moving_nest_parent, Atmos%is_moving_nest, &
Atmos%ngrids, Atmos%mygrid, Atmos%pelist)
call atmosphere_diag_axes (Atmos%axes)
Expand Down Expand Up @@ -718,7 +722,8 @@ subroutine atmos_model_init (Atmos, Time_init, Time, Time_step)
call GFS_restart_populate (GFS_restart_var, GFS_control, GFS_data%Statein, GFS_data%Stateout, GFS_data%Sfcprop, &
GFS_data%Coupling, GFS_data%Grid, GFS_data%Tbd, GFS_data%Cldprop, GFS_data%Radtend, &
GFS_data%IntDiag, Init_parm, GFS_Diag)
call FV3GFS_restart_read (GFS_data, GFS_restart_var, Atm_block, GFS_control, Atmos%domain, Atm(mygrid)%flagstruct%warm_start)
call FV3GFS_restart_read (GFS_data, GFS_restart_var, Atm_block, GFS_control, Atmos%domain_for_read, &
Atm(mygrid)%flagstruct%warm_start, ignore_rst_cksum)
if(GFS_control%do_ca .and. Atm(mygrid)%flagstruct%warm_start)then
call read_ca_restart (Atmos%domain,GFS_control%ncells,GFS_control%nca,GFS_control%ncells_g,GFS_control%nca_g)
endif
Expand Down Expand Up @@ -3190,7 +3195,7 @@ subroutine atmos_model_get_nth_domain_info(n, layout, nx, ny, pelist)
integer, pointer, intent(out) :: pelist(:)

call get_nth_domain_info(n, layout, nx, ny, pelist)

end subroutine atmos_model_get_nth_domain_info

end module atmos_model_mod
35 changes: 19 additions & 16 deletions io/FV3GFS_io.F90
Original file line number Diff line number Diff line change
Expand Up @@ -122,19 +122,20 @@ module FV3GFS_io_mod
!--------------------
! FV3GFS_restart_read
!--------------------
subroutine FV3GFS_restart_read (GFS_Data, GFS_Restart, Atm_block, Model, fv_domain, warm_start)
subroutine FV3GFS_restart_read (GFS_Data, GFS_Restart, Atm_block, Model, fv_domain, warm_start, ignore_rst_cksum)
type(GFS_data_type), intent(inout) :: GFS_Data(:)
type(GFS_restart_type), intent(inout) :: GFS_Restart
type(block_control_type), intent(in) :: Atm_block
type(GFS_control_type), intent(inout) :: Model
type(domain2d), intent(in) :: fv_domain
logical, intent(in) :: warm_start
logical, intent(in) :: ignore_rst_cksum

!--- read in surface data from chgres
call sfc_prop_restart_read (GFS_Data%Sfcprop, Atm_block, Model, fv_domain, warm_start)
call sfc_prop_restart_read (GFS_Data%Sfcprop, Atm_block, Model, fv_domain, warm_start, ignore_rst_cksum)

!--- read in physics restart data
call phys_restart_read (GFS_Restart, Atm_block, Model, fv_domain)
call phys_restart_read (GFS_Restart, Atm_block, Model, fv_domain, ignore_rst_cksum)

end subroutine FV3GFS_restart_read

Expand Down Expand Up @@ -508,13 +509,14 @@ end subroutine FV3GFS_GFS_checksum
! opens: oro_data.tile?.nc, sfc_data.tile?.nc
!
!----------------------------------------------------------------------
subroutine sfc_prop_restart_read (Sfcprop, Atm_block, Model, fv_domain, warm_start)
subroutine sfc_prop_restart_read (Sfcprop, Atm_block, Model, fv_domain, warm_start, ignore_rst_cksum)
!--- interface variable definitions
type(GFS_sfcprop_type), intent(inout) :: Sfcprop(:)
type (block_control_type), intent(in) :: Atm_block
type(GFS_control_type), intent(inout) :: Model
type (domain2d), intent(in) :: fv_domain
logical, intent(in) :: warm_start
logical, intent(in) :: ignore_rst_cksum
!--- local variables
integer :: i, j, k, ix, lsoil, num, nb, i_start, j_start, i_end, j_end
integer :: isc, iec, jsc, jec, npz, nx, ny
Expand All @@ -537,8 +539,8 @@ subroutine sfc_prop_restart_read (Sfcprop, Atm_block, Model, fv_domain, warm_sta
character(37) :: infile
!--- fms2_io file open logic
logical :: amiopen
logical :: is_lsoil
logical :: is_lsoil

nvar_o2 = 19
nvar_oro_ls_ss = 10
nvar_s2o = 18
Expand Down Expand Up @@ -635,7 +637,7 @@ subroutine sfc_prop_restart_read (Sfcprop, Atm_block, Model, fv_domain, warm_sta

!--- read the orography restart/data
call mpp_error(NOTE,'reading topographic/orographic information from INPUT/oro_data.tile*.nc')
call read_restart(Oro_restart)
call read_restart(Oro_restart, ignore_checksum=ignore_rst_cksum)
call close_file(Oro_restart)


Expand Down Expand Up @@ -887,11 +889,11 @@ subroutine sfc_prop_restart_read (Sfcprop, Atm_block, Model, fv_domain, warm_sta
!--- read new GSL created orography restart/data
call mpp_error(NOTE,'reading topographic/orographic information from &
&INPUT/oro_data_ls.tile*.nc')
call read_restart(Oro_ls_restart)
call read_restart(Oro_ls_restart, ignore_checksum=ignore_rst_cksum)
call close_file(Oro_ls_restart)
call mpp_error(NOTE,'reading topographic/orographic information from &
&INPUT/oro_data_ss.tile*.nc')
call read_restart(Oro_ss_restart)
call read_restart(Oro_ss_restart, ignore_checksum=ignore_rst_cksum)
call close_file(Oro_ss_restart)


Expand Down Expand Up @@ -1121,7 +1123,7 @@ subroutine sfc_prop_restart_read (Sfcprop, Atm_block, Model, fv_domain, warm_sta
call register_axis(Sfc_restart, 'xaxis_1', 'X')
call register_axis(Sfc_restart, 'yaxis_1', 'Y')
call register_axis(Sfc_restart, 'zaxis_1', dimension_length=Model%kice)

if (Model%lsm == Model%lsm_noah .or. Model%lsm == Model%lsm_noahmp) then
call register_axis(Sfc_restart, 'zaxis_2', dimension_length=Model%lsoil)
else if(Model%lsm == Model%lsm_ruc) then
Expand Down Expand Up @@ -1247,7 +1249,7 @@ subroutine sfc_prop_restart_read (Sfcprop, Atm_block, Model, fv_domain, warm_sta
end if
end if
enddo

if (Model%lsm == Model%lsm_noahmp) then
mand = .false.
do num = nvar_s3+1,nvar_s3+3
Expand Down Expand Up @@ -1280,7 +1282,7 @@ subroutine sfc_prop_restart_read (Sfcprop, Atm_block, Model, fv_domain, warm_sta

!--- read the surface restart/data
call mpp_error(NOTE,'reading surface properties data from INPUT/sfc_data.tile*.nc')
call read_restart(Sfc_restart)
call read_restart(Sfc_restart, ignore_checksum=ignore_rst_cksum)
call close_file(Sfc_restart)

! write(0,*)' stype read in min,max=',minval(sfc_var2(:,:,35)),maxval(sfc_var2(:,:,35)),' sfc_name2=',sfc_name2(35)
Expand Down Expand Up @@ -2225,11 +2227,11 @@ subroutine sfc_prop_restart_write (Sfcprop, Atm_block, Model, fv_domain, timesta
var3_p2 => sfc_var3eq(:,:,:,7)
call register_restart_field(Sfc_restart, sfc_name3(7), var3_p2, dimensions=(/'xaxis_1', 'yaxis_1', 'zaxis_2', 'Time '/),&
&is_optional=.not.mand)

var3_p3 => sfc_var3zn(:,:,:,8)
call register_restart_field(Sfc_restart, sfc_name3(8), var3_p3, dimensions=(/'xaxis_1', 'yaxis_1', 'zaxis_4', 'Time '/),&
&is_optional=.not.mand)

nullify(var3_p1)
nullify(var3_p2)
nullify(var3_p3)
Expand Down Expand Up @@ -2435,12 +2437,13 @@ end subroutine sfc_prop_restart_write
! opens: phys_data.tile?.nc
!
!----------------------------------------------------------------------
subroutine phys_restart_read (GFS_Restart, Atm_block, Model, fv_domain)
subroutine phys_restart_read (GFS_Restart, Atm_block, Model, fv_domain, ignore_rst_cksum)
!--- interface variable definitions
type(GFS_restart_type), intent(in) :: GFS_Restart
type(block_control_type), intent(in) :: Atm_block
type(GFS_control_type), intent(in) :: Model
type(domain2d), intent(in) :: fv_domain
logical, intent(in) :: ignore_rst_cksum
!--- local variables
integer :: i, j, k, nb, ix, num
integer :: isc, iec, jsc, jec, npz, nx, ny
Expand Down Expand Up @@ -2501,7 +2504,7 @@ subroutine phys_restart_read (GFS_Restart, Atm_block, Model, fv_domain)

!--- read the surface restart/data
call mpp_error(NOTE,'reading physics restart data from INPUT/phy_data.tile*.nc')
call read_restart(Phy_restart)
call read_restart(Phy_restart, ignore_checksum=ignore_rst_cksum)
call close_file(Phy_restart)

!--- place the data into the block GFS containers
Expand Down

0 comments on commit 18bf9b7

Please sign in to comment.