From 1e7575f5f2b8964008bdda490cfbab76e29c7690 Mon Sep 17 00:00:00 2001 From: "Rusty.Benson" <rusty.benson@noaa.gov> Date: Thu, 14 Apr 2022 09:33:55 -0400 Subject: [PATCH 1/2] fixes io performance issues by making everyone a reader when io_layout=1,1 adds capability to use FMS feature to ignore data integrity checksums in restarts --- driver/GFDL/atmosphere.F90 | 2 +- driver/SHiELD/atmosphere.F90 | 5 ++-- model/fv_arrays.F90 | 2 ++ model/fv_control.F90 | 7 +++-- tools/external_ic.F90 | 57 ++++++++++++++++-------------------- tools/fv_io.F90 | 28 +++++++++--------- tools/fv_mp_mod.F90 | 18 ++++++++++-- tools/fv_restart.F90 | 6 ++-- 8 files changed, 68 insertions(+), 57 deletions(-) diff --git a/driver/GFDL/atmosphere.F90 b/driver/GFDL/atmosphere.F90 index 756a927f0..8d66688b9 100644 --- a/driver/GFDL/atmosphere.F90 +++ b/driver/GFDL/atmosphere.F90 @@ -372,7 +372,7 @@ subroutine atmosphere_init (Time_init, Time, Time_step, Surf_diff, Grid_box) if ( Atm(mygrid)%flagstruct%nudge ) then call fv_ada_nudge_init( Time, Atm(mygrid)%atmos_axes, npz, zvir, Atm(mygrid)%ak, Atm(mygrid)%bk, & Atm(mygrid)%ts, Atm(mygrid)%phis, Atm(mygrid)%gridstruct, Atm(mygrid)%ks, Atm(mygrid)%npx, & - Atm(mygrid)%neststruct, Atm(mygrid)%bd, Atm(mygrid)%domain) + Atm(mygrid)%neststruct, Atm(mygrid)%bd, Atm(mygrid)%domain_for_read) call mpp_error(NOTE, 'ADA nudging is active') endif #else diff --git a/driver/SHiELD/atmosphere.F90 b/driver/SHiELD/atmosphere.F90 index 0585c959f..8d9e3ceac 100644 --- a/driver/SHiELD/atmosphere.F90 +++ b/driver/SHiELD/atmosphere.F90 @@ -713,8 +713,8 @@ subroutine set_atmosphere_pelist () end subroutine set_atmosphere_pelist - subroutine atmosphere_domain ( fv_domain, layout, regional, bounded_domain ) - type(domain2d), intent(out) :: fv_domain + subroutine atmosphere_domain ( fv_domain, rd_domain, layout, regional, bounded_domain ) + type(domain2d), intent(out) :: fv_domain, rd_domain integer, intent(out) :: layout(2) logical, intent(out) :: regional logical, intent(out) :: bounded_domain @@ -722,6 +722,7 @@ subroutine atmosphere_domain ( fv_domain, layout, regional, bounded_domain ) ! note: coupling is done using the mass/temperature grid with no halos fv_domain = Atm(mygrid)%domain_for_coupler + rd_domain = Atm(mygrid)%domain_for_read layout(1:2) = Atm(mygrid)%layout(1:2) regional = Atm(mygrid)%flagstruct%regional diff --git a/model/fv_arrays.F90 b/model/fv_arrays.F90 index 81edb3299..a953b2965 100644 --- a/model/fv_arrays.F90 +++ b/model/fv_arrays.F90 @@ -511,6 +511,7 @@ module fv_arrays_mod !----------------------------------------------------------------------------------------------- logical :: reset_eta = .false. + logical :: enforce_rst_cksum = .true. !< enfore or override data integrity restart checksums real :: p_fac = 0.05 !< Safety factor for minimum nonhydrostatic pressures, which !< will be limited so the full pressure is no less than p_fac !< times the hydrostatic pressure. This is only of concern in mid-top @@ -1280,6 +1281,7 @@ module fv_arrays_mod #if defined(SPMD) type(domain2D) :: domain_for_coupler !< domain used in coupled model with halo = 1. + type(domain2D) :: domain_for_read !< domain used for reads to increase performance when io_layout=(1,1) !global tile and tile_of_mosaic only have a meaning for the CURRENT pe integer :: num_contact, npes_per_tile, global_tile, tile_of_mosaic, npes_this_grid diff --git a/model/fv_control.F90 b/model/fv_control.F90 index f939b604b..36cf70dd3 100644 --- a/model/fv_control.F90 +++ b/model/fv_control.F90 @@ -188,6 +188,7 @@ subroutine fv_control_init(Atm, dt_atmos, this_grid, grids_on_this_pe, p_split) real(kind=R_GRID) , pointer :: target_lon logical , pointer :: reset_eta + logical , pointer :: enforce_rst_cksum real , pointer :: p_fac real , pointer :: a_imp integer , pointer :: n_split @@ -550,7 +551,8 @@ subroutine fv_control_init(Atm, dt_atmos, this_grid, grids_on_this_pe, p_split) Atm(this_grid)%flagstruct%grid_type,Atm(this_grid)%neststruct%nested, & Atm(this_grid)%layout,Atm(this_grid)%io_layout,Atm(this_grid)%bd,Atm(this_grid)%tile_of_mosaic, & Atm(this_grid)%gridstruct%square_domain,Atm(this_grid)%npes_per_tile,Atm(this_grid)%domain, & - Atm(this_grid)%domain_for_coupler,Atm(this_grid)%num_contact,Atm(this_grid)%pelist) + Atm(this_grid)%domain_for_coupler,Atm(this_grid)%domain_for_read,Atm(this_grid)%num_contact, & + Atm(this_grid)%pelist) call broadcast_domains(Atm,Atm(this_grid)%pelist,size(Atm(this_grid)%pelist)) do n=1,ngrids tile_id = mpp_get_tile_id(Atm(n)%domain) @@ -728,6 +730,7 @@ subroutine set_namelist_pointers(Atm) write_restart_with_bcs => Atm%flagstruct%write_restart_with_bcs regional_bcs_from_gsi => Atm%flagstruct%regional_bcs_from_gsi reset_eta => Atm%flagstruct%reset_eta + enforce_rst_cksum => Atm%flagstruct%enforce_rst_cksum p_fac => Atm%flagstruct%p_fac a_imp => Atm%flagstruct%a_imp n_split => Atm%flagstruct%n_split @@ -940,7 +943,7 @@ subroutine read_namelist_fv_core_nml(Atm) w_limiter, write_coarse_restart_files, write_coarse_diagnostics,& write_only_coarse_intermediate_restarts, & write_coarse_agrid_vel_rst, write_coarse_dgrid_vel_rst, & - pass_full_omega_to_physics_in_non_hydrostatic_mode + pass_full_omega_to_physics_in_non_hydrostatic_mode, enforce_rst_cksum ! Read FVCORE namelist diff --git a/tools/external_ic.F90 b/tools/external_ic.F90 index 9f5eabd65..328e6f1cd 100644 --- a/tools/external_ic.F90 +++ b/tools/external_ic.F90 @@ -87,10 +87,9 @@ module external_ic_mod contains - subroutine get_external_ic( Atm, fv_domain, cold_start, icdir ) + subroutine get_external_ic( Atm, cold_start, icdir ) type(fv_atmos_type), intent(inout), target :: Atm - type(domain2d), intent(inout) :: fv_domain logical, intent(IN) :: cold_start character(len=*), intent(in), optional :: icdir real:: alpha = 0. @@ -139,14 +138,14 @@ subroutine get_external_ic( Atm, fv_domain, cold_start, icdir ) enddo enddo - call mpp_update_domains( f0, fv_domain ) + call mpp_update_domains( f0, Atm%domain ) if ( Atm%gridstruct%cubed_sphere .and. (.not. Atm%gridstruct%bounded_domain))then call fill_corners(f0, Atm%npx, Atm%npy, YDir) endif ! Read in cubed_sphere terrain if ( Atm%flagstruct%mountain ) then - call get_cubed_sphere_terrain(Atm, fv_domain) + call get_cubed_sphere_terrain(Atm) else if (.not. Atm%neststruct%nested) Atm%phis = 0. !TODO: Not sure about this line --- lmh 30 may 18 endif @@ -155,32 +154,32 @@ subroutine get_external_ic( Atm, fv_domain, cold_start, icdir ) if ( Atm%flagstruct%ncep_ic ) then nq = 1 call timing_on('NCEP_IC') - call get_ncep_ic( Atm, fv_domain, nq ) + call get_ncep_ic( Atm, nq ) call timing_off('NCEP_IC') #ifdef FV_TRACERS if (.not. cold_start) then - call fv_io_read_tracers( fv_domain, Atm ) + call fv_io_read_tracers( Atm ) if(is_master()) write(*,*) 'All tracers except sphum replaced by FV IC' endif #endif elseif ( Atm%flagstruct%nggps_ic ) then call timing_on('NGGPS_IC') - call get_nggps_ic( Atm, fv_domain ) + call get_nggps_ic( Atm ) call timing_off('NGGPS_IC') elseif ( Atm%flagstruct%hrrrv3_ic ) then call timing_on('HRRR_IC') - call get_hrrr_ic( Atm, fv_domain ) + call get_hrrr_ic( Atm ) call timing_off('HRRR_IC') elseif ( Atm%flagstruct%ecmwf_ic ) then if( is_master() ) write(*,*) 'Calling get_ecmwf_ic' call timing_on('ECMWF_IC') - call get_ecmwf_ic( Atm, fv_domain ) + call get_ecmwf_ic( Atm ) call timing_off('ECMWF_IC') else ! The following is to read in legacy lat-lon FV core restart file ! is Atm%q defined in all cases? nq = size(Atm%q,4) - call get_fv_ic( Atm, fv_domain, nq ) + call get_fv_ic( Atm, nq ) endif call prt_maxmin('PS', Atm%ps, is, ie, js, je, ng, 1, 0.01) @@ -219,9 +218,8 @@ end subroutine get_external_ic !------------------------------------------------------------------ - subroutine get_cubed_sphere_terrain( Atm, fv_domain ) + subroutine get_cubed_sphere_terrain( Atm ) type(fv_atmos_type), intent(inout), target :: Atm - type(domain2d), intent(inout) :: fv_domain type(FmsNetcdfDomainFile_t) :: Fv_core integer :: tile_id(1) character(len=64) :: fname @@ -244,13 +242,13 @@ subroutine get_cubed_sphere_terrain( Atm, fv_domain ) jed = Atm%bd%jed ng = Atm%bd%ng - tile_id = mpp_get_tile_id( fv_domain ) + tile_id = mpp_get_tile_id( Atm%domain ) fname = 'INPUT/fv_core.res.nc' call mpp_error(NOTE, 'external_ic: looking for '//fname) - if( open_file(Fv_core, fname, "read", fv_domain, is_restart=.true.) ) then + if( open_file(Fv_core, fname, "read", Atm%domain_for_read, is_restart=.true.) ) then call read_data(Fv_core, 'phis', Atm%phis(is:ie,js:je)) call close_file(Fv_core) else @@ -276,7 +274,7 @@ subroutine get_cubed_sphere_terrain( Atm, fv_domain ) end subroutine get_cubed_sphere_terrain - subroutine get_nggps_ic (Atm, fv_domain) + subroutine get_nggps_ic (Atm) ! read in data after it has been preprocessed with ! NCEP/EMC orography maker and global_chgres ! and has been horiztontally interpolated to the @@ -301,7 +299,6 @@ subroutine get_nggps_ic (Atm, fv_domain) type(fv_atmos_type), intent(inout) :: Atm - type(domain2d), intent(inout) :: fv_domain ! local: real, dimension(:), allocatable:: ak, bk real, dimension(:,:), allocatable:: wk2, ps, oro_g @@ -424,7 +421,7 @@ subroutine get_nggps_ic (Atm, fv_domain) !--- read in surface temperature (k) and land-frac ! surface skin temperature - if( open_file(SFC_restart, fn_sfc_ics, "read", Atm%domain, is_restart=.true., dont_add_res_to_filename=.true.) ) then + if( open_file(SFC_restart, fn_sfc_ics, "read", Atm%domain_for_read, is_restart=.true., dont_add_res_to_filename=.true.) ) then naxis_dims = get_variable_num_dimensions(SFC_restart, 'tsea') allocate (dim_names_alloc(naxis_dims)) call get_variable_dimension_names(SFC_restart, 'tsea', dim_names_alloc) @@ -444,7 +441,7 @@ subroutine get_nggps_ic (Atm, fv_domain) dim_names_2d(2) = "lon" ! terrain surface height -- (needs to be transformed into phis = zs*grav) - if( open_file(ORO_restart, fn_oro_ics, "read", Atm%domain, is_restart=.true., dont_add_res_to_filename=.true.) ) then + if( open_file(ORO_restart, fn_oro_ics, "read", Atm%domain_for_read, is_restart=.true., dont_add_res_to_filename=.true.) ) then call register_axis(ORO_restart, "lat", "y") call register_axis(ORO_restart, "lon", "x") if (filtered_terrain) then @@ -757,7 +754,7 @@ subroutine read_gfs_ic() dim_names_3d4(1) = "levp" ! surface pressure (Pa) - if( open_file(GFS_restart, fn_gfs_ics, "read", Atm%domain, is_restart=.true., dont_add_res_to_filename=.true.) ) then + if( open_file(GFS_restart, fn_gfs_ics, "read", Atm%domain_for_read, is_restart=.true., dont_add_res_to_filename=.true.) ) then call register_axis(GFS_restart, "lat", "y") call register_axis(GFS_restart, "lon", "x") call register_axis(GFS_restart, "lonp", "x", domain_position=east) @@ -803,7 +800,7 @@ subroutine read_gfs_ic() end subroutine get_nggps_ic !------------------------------------------------------------------ !------------------------------------------------------------------ - subroutine get_hrrr_ic (Atm, fv_domain) + subroutine get_hrrr_ic (Atm) ! read in data after it has been preprocessed with ! NCEP/EMC orography maker ! @@ -824,7 +821,6 @@ subroutine get_hrrr_ic (Atm, fv_domain) type(fv_atmos_type), intent(inout) :: Atm - type(domain2d), intent(inout) :: fv_domain ! local: real, dimension(:), allocatable:: ak, bk real, dimension(:,:), allocatable:: wk2, ps, oro_g @@ -939,7 +935,7 @@ subroutine get_hrrr_ic (Atm, fv_domain) !--- read in surface temperature (k) and land-frac ! surface skin temperature - if( open_file(SFC_restart, fn_sfc_ics, "read", Atm%domain, is_restart=.true., dont_add_res_to_filename=.true.) ) then + if( open_file(SFC_restart, fn_sfc_ics, "read", Atm%domain_for_read, is_restart=.true., dont_add_res_to_filename=.true.) ) then call get_variable_dimension_names(SFC_restart, 'tsea', dim_names_2d) call register_axis(SFC_restart, dim_names_2d(2), "y") call register_axis(SFC_restart, dim_names_2d(1), "x") @@ -956,7 +952,7 @@ subroutine get_hrrr_ic (Atm, fv_domain) dim_names_2d(2) = "lon" ! terrain surface height -- (needs to be transformed into phis = zs*grav) - if( open_file(ORO_restart, fn_oro_ics, "read", Atm%domain, is_restart=.true., dont_add_res_to_filename=.true.) ) then + if( open_file(ORO_restart, fn_oro_ics, "read", Atm%domain_for_read, is_restart=.true., dont_add_res_to_filename=.true.) ) then call register_axis(ORO_restart, "lat", "y") call register_axis(ORO_restart, "lon", "x") if (filtered_terrain) then @@ -999,7 +995,7 @@ subroutine get_hrrr_ic (Atm, fv_domain) dim_names_3d4(1) = "levp" ! edge pressure (Pa) - if( open_file(HRRR_restart, fn_hrr_ics, "read", Atm%domain,is_restart=.true., dont_add_res_to_filename=.true.) ) then + if( open_file(HRRR_restart, fn_hrr_ics, "read", Atm%domain_for_read, is_restart=.true., dont_add_res_to_filename=.true.) ) then call register_axis(HRRR_restart, "lat", "y") call register_axis(HRRR_restart, "lon", "x") call register_axis(HRRR_restart, "lonp", "x", domain_position=east) @@ -1194,9 +1190,8 @@ subroutine get_hrrr_ic (Atm, fv_domain) end subroutine get_hrrr_ic !------------------------------------------------------------------ !------------------------------------------------------------------ - subroutine get_ncep_ic( Atm, fv_domain, nq ) + subroutine get_ncep_ic( Atm, nq ) type(fv_atmos_type), intent(inout) :: Atm - type(domain2d), intent(inout) :: fv_domain integer, intent(in):: nq ! local: #ifdef HIWPP_ETA @@ -1652,9 +1647,8 @@ subroutine get_ncep_ic( Atm, fv_domain, nq ) end subroutine get_ncep_ic !------------------------------------------------------------------ !------------------------------------------------------------------ - subroutine get_ecmwf_ic( Atm, fv_domain ) + subroutine get_ecmwf_ic( Atm ) type(fv_atmos_type), intent(inout) :: Atm - type(domain2d), intent(inout) :: fv_domain ! local: real :: ak_ec(138), bk_ec(138) data ak_ec/ 0.000000, 2.000365, 3.102241, 4.666084, 6.827977, 9.746966, & @@ -1871,7 +1865,7 @@ subroutine get_ecmwf_ic( Atm, fv_domain ) dim_names_3d4(1) = "levp" !! Read in model terrain from oro_data.tile?.nc - if( open_file(ORO_restart, fn_oro_ics, "read", Atm%domain, is_restart=.true., dont_add_res_to_filename=.true.) ) then + if( open_file(ORO_restart, fn_oro_ics, "read", Atm%domain_for_read, is_restart=.true., dont_add_res_to_filename=.true.) ) then call register_axis(ORO_restart, "lat", "y") call register_axis(ORO_restart, "lon", "x") if (filtered_terrain) then @@ -1891,7 +1885,7 @@ subroutine get_ecmwf_ic( Atm, fv_domain ) allocate (ps_gfs(is:ie,js:je)) allocate (zh_gfs(is:ie,js:je,levp_gfs+1)) - if( open_file(GFS_restart, fn_gfs_ics, "read", Atm%domain, is_restart=.true., dont_add_res_to_filename=.true.) ) then + if( open_file(GFS_restart, fn_gfs_ics, "read", Atm%domain_for_read, is_restart=.true., dont_add_res_to_filename=.true.) ) then call register_axis(GFS_restart, "lat", "y") call register_axis(GFS_restart, "lon", "x") call register_axis(GFS_restart, "lev", size(o3mr_gfs,3)) @@ -2397,9 +2391,8 @@ subroutine get_ecmwf_ic( Atm, fv_domain ) end subroutine get_ecmwf_ic !------------------------------------------------------------------ !------------------------------------------------------------------ - subroutine get_fv_ic( Atm, fv_domain, nq ) + subroutine get_fv_ic( Atm, nq ) type(fv_atmos_type), intent(inout) :: Atm - type(domain2d), intent(inout) :: fv_domain integer, intent(in):: nq type(FmsNetcdfFile_t) :: Latlon_dyn, Latlon_tra diff --git a/tools/fv_io.F90 b/tools/fv_io.F90 index dd03ae3d5..79289ce5b 100644 --- a/tools/fv_io.F90 +++ b/tools/fv_io.F90 @@ -456,7 +456,7 @@ subroutine fv_io_read_restart(fv_domain,Atm,prefix,directory) Atm(1)%Fv_restart_tile_is_open = open_file(Atm(1)%Fv_restart_tile, fname, "read", fv_domain, is_restart=.true.) if (Atm(1)%Fv_restart_tile_is_open) then call fv_io_register_restart(Atm(1)) - call read_restart(Atm(1)%Fv_restart_tile) + call read_restart(Atm(1)%Fv_restart_tile, ignore_checksum=Atm(1)%flagstruct%enforce_rst_cksum) call close_file(Atm(1)%Fv_restart_tile) Atm(1)%Fv_restart_tile_is_open = .false. endif @@ -466,7 +466,7 @@ subroutine fv_io_read_restart(fv_domain,Atm,prefix,directory) Atm(1)%Tra_restart_is_open = open_file(Atm(1)%Tra_restart, fname, "read", fv_domain, is_restart=.true.) if (Atm(1)%Tra_restart_is_open) then call fv_io_register_restart(Atm(1)) - call read_restart(Atm(1)%Tra_restart) + call read_restart(Atm(1)%Tra_restart, ignore_checksum=Atm(1)%flagstruct%enforce_rst_cksum) call close_file(Atm(1)%Tra_restart) Atm(1)%Tra_restart_is_open = .false. else @@ -479,7 +479,7 @@ subroutine fv_io_read_restart(fv_domain,Atm,prefix,directory) if (Atm(1)%Rsf_restart_is_open) then Atm(1)%flagstruct%srf_init = .true. call fv_io_register_restart(Atm(1)) - call read_restart(Atm(1)%Rsf_restart) + call read_restart(Atm(1)%Rsf_restart, ignore_checksum=Atm(1)%flagstruct%enforce_rst_cksum) call close_file(Atm(1)%Rsf_restart) Atm(1)%Rsf_restart_is_open = .false. else @@ -493,7 +493,7 @@ subroutine fv_io_read_restart(fv_domain,Atm,prefix,directory) Atm(1)%Mg_restart_is_open = open_file(Atm(1)%Mg_restart, fname, "read", fv_domain, is_restart=.true.) if (Atm(1)%Mg_restart_is_open) then call fv_io_register_restart(Atm(1)) - call read_restart(Atm(1)%Mg_restart) + call read_restart(Atm(1)%Mg_restart, ignore_checksum=Atm(1)%flagstruct%enforce_rst_cksum) call close_file(Atm(1)%Mg_restart) Atm(1)%Mg_restart_is_open = .false. else @@ -504,7 +504,7 @@ subroutine fv_io_read_restart(fv_domain,Atm,prefix,directory) Atm(1)%Lnd_restart_is_open = open_file(Atm(1)%Lnd_restart, fname, "read", fv_domain, is_restart=.true.) if (Atm(1)%Lnd_restart_is_open) then call fv_io_register_restart(Atm(1)) - call read_restart(Atm(1)%Lnd_restart) + call read_restart(Atm(1)%Lnd_restart, ignore_checksum=Atm(1)%flagstruct%enforce_rst_cksum) call close_file(Atm(1)%Lnd_restart) Atm(1)%Lnd_restart_is_open = .false. else @@ -519,8 +519,7 @@ end subroutine fv_io_read_restart !##################################################################### - subroutine fv_io_read_tracers(fv_domain,Atm) - type(domain2d), intent(inout) :: fv_domain + subroutine fv_io_read_tracers(Atm) type(fv_atmos_type), intent(inout) :: Atm(:) integer :: ntracers, ntprog, nt, isc, iec, jsc, jec character(len=6) :: stile_name @@ -535,7 +534,7 @@ subroutine fv_io_read_tracers(fv_domain,Atm) call get_number_tracers(MODEL_ATMOS, num_tracers=ntracers, num_prog=ntprog) ! fix for single tile runs where you need fv_core.res.nc and fv_core.res.tile1.nc - ntiles = mpp_get_ntile_count(fv_domain) + ntiles = mpp_get_ntile_count(Atm(1)%domain_for_read) if(ntiles == 1 .and. .not. Atm(1)%neststruct%nested) then stile_name = '.tile1' else @@ -544,7 +543,7 @@ subroutine fv_io_read_tracers(fv_domain,Atm) fname = 'INPUT/fv_tracer.res'//trim(stile_name)//'.nc' - if (open_file(Tra_restart_r,fname,"read",fv_domain, is_restart=.true.)) then + if (open_file(Tra_restart_r,fname,"read",Atm(1)%domain_for_read, is_restart=.true.)) then do nt = 2, ntprog call get_tracer_names(MODEL_ATMOS, nt, tracer_name) call set_tracer_profile (MODEL_ATMOS, nt, Atm(1)%q(isc:iec,jsc:jec,:,nt) ) @@ -568,10 +567,9 @@ subroutine fv_io_read_tracers(fv_domain,Atm) end subroutine fv_io_read_tracers - subroutine remap_restart(fv_domain,Atm) + subroutine remap_restart(Atm) use fv_mapz_mod, only: rst_remap - type(domain2d), intent(inout) :: fv_domain type(fv_atmos_type), intent(inout) :: Atm(:) character(len=64) :: fname, tracer_name @@ -580,6 +578,7 @@ subroutine remap_restart(fv_domain,Atm) integer :: isd, ied, jsd, jed integer :: ntiles + type(domain2d) :: fv_domain type(FmsNetcdfDomainFile_t) :: FV_tile_restart_r, Tra_restart_r type(FmsNetcdfFile_t) :: Fv_restart_r integer, allocatable, dimension(:) :: pes !< Array of the pes in the current pelist @@ -594,6 +593,7 @@ subroutine remap_restart(fv_domain,Atm) integer npz, npz_rst, ng integer i,j,k + fv_domain = Atm(1)%domain_for_read npz = Atm(1)%npz ! run time z dimension npz_rst = Atm(1)%flagstruct%npz_rst ! restart z dimension isc = Atm(1)%bd%isc; iec = Atm(1)%bd%iec; jsc = Atm(1)%bd%jsc; jec = Atm(1)%bd%jec @@ -674,7 +674,7 @@ subroutine remap_restart(fv_domain,Atm) if (Atm(1)%Rsf_restart_is_open) then Atm%flagstruct%srf_init = .true. call fv_io_register_restart(Atm(1)) - call read_restart(Atm(1)%Rsf_restart) + call read_restart(Atm(1)%Rsf_restart, ignore_checksum=Atm(1)%flagstruct%enforce_rst_cksum) call close_file(Atm(1)%Rsf_restart) Atm(1)%Rsf_restart_is_open = .false. call mpp_error(NOTE,'==> Warning from remap_restart: Expected file '//trim(fname)//' does not exist') @@ -1435,12 +1435,12 @@ subroutine fv_io_read_BCs(Atm) call fv_io_register_restart_BCs(Atm) if (Atm%neststruct%BCfile_sw_is_open) then - call read_restart_bc(Atm%neststruct%BCfile_sw) + call read_restart_bc(Atm%neststruct%BCfile_sw, ignore_checksum=Atm%flagstruct%enforce_rst_cksum) call close_file(Atm%neststruct%BCfile_sw) endif if (Atm%neststruct%BCfile_ne_is_open) then - call read_restart_bc(Atm%neststruct%BCfile_ne) + call read_restart_bc(Atm%neststruct%BCfile_ne, ignore_checksum=Atm%flagstruct%enforce_rst_cksum) call close_file(Atm%neststruct%BCfile_ne) endif diff --git a/tools/fv_mp_mod.F90 b/tools/fv_mp_mod.F90 index ee081fd1b..96d9a3e2b 100644 --- a/tools/fv_mp_mod.F90 +++ b/tools/fv_mp_mod.F90 @@ -49,7 +49,7 @@ module fv_mp_mod use mpp_domains_mod, only : mpp_group_update_initialized, mpp_do_group_update use mpp_domains_mod, only : mpp_create_group_update,mpp_reset_group_update_field use mpp_domains_mod, only : group_halo_update_type => mpp_group_update_type - use mpp_domains_mod, only: nest_domain_type + use mpp_domains_mod, only : nest_domain_type, mpp_get_io_domain_layout, mpp_get_layout, mpp_copy_domain use mpp_parameter_mod, only : WUPDATE, EUPDATE, SUPDATE, NUPDATE, XUPDATE, YUPDATE use fv_arrays_mod, only: fv_atmos_type, fv_grid_bounds_type use mpp_mod, only : mpp_get_current_pelist, mpp_set_current_pelist @@ -275,7 +275,7 @@ end subroutine mp_stop ! domain_decomp :: Setup domain decomp ! subroutine domain_decomp(grid_num,npx,npy,nregions,grid_type,nested,layout,io_layout,bd,tile,square_domain,& - npes_per_tile,domain,domain_for_coupler,num_contact,pelist) + npes_per_tile,domain,domain_for_coupler,domain_for_read,num_contact,pelist) integer, intent(IN) :: grid_num integer, intent(IN) :: npx,npy,grid_type @@ -297,8 +297,9 @@ subroutine domain_decomp(grid_num,npx,npy,nregions,grid_type,nested,layout,io_la integer, intent(INOUT) :: pelist(:) integer, intent(OUT) :: num_contact, npes_per_tile logical, intent(OUT) :: square_domain - type(domain2D), intent(OUT) :: domain, domain_for_coupler + type(domain2D), intent(OUT) :: domain, domain_for_coupler, domain_for_read type(fv_grid_bounds_type), intent(INOUT) :: bd + integer :: l_layout(2) nx = npx-1 ny = npy-1 @@ -562,6 +563,17 @@ subroutine domain_decomp(grid_num,npx,npy,nregions,grid_type,nested,layout,io_la call mpp_define_io_domain(domain, io_layout) call mpp_define_io_domain(domain_for_coupler, io_layout) + !--- create a read domain that can be used to improve read performance + !--- if io_layout=(1,1) then read io_layout=layout (all read) + !--- if io_layout\=(1,1) then read io_layout=io_layout (no change) + l_layout = mpp_get_io_domain_layout(domain) + call mpp_copy_domain(domain, domain_for_read) + if (ALL(l_layout == 1)) then + call mpp_get_layout(domain, l_layout) + call mpp_define_io_domain(domain_for_read, l_layout) + else + call mpp_define_io_domain(domain_for_read, l_layout) + endif endif deallocate(pe_start,pe_end) diff --git a/tools/fv_restart.F90 b/tools/fv_restart.F90 index a78b65dfc..363d30d26 100644 --- a/tools/fv_restart.F90 +++ b/tools/fv_restart.F90 @@ -260,7 +260,7 @@ subroutine fv_restart(fv_domain, Atm, dt_atmos, seconds, days, cold_start, grid_ !3. External_ic if (Atm(n)%flagstruct%external_ic) then if( is_master() ) write(*,*) 'Calling get_external_ic' - call get_external_ic(Atm(n), Atm(n)%domain, .not. do_read_restart) + call get_external_ic(Atm(n), .not. do_read_restart) if( is_master() ) write(*,*) 'IC generated from the specified external source' !4. Restart @@ -275,11 +275,11 @@ subroutine fv_restart(fv_domain, Atm, dt_atmos, seconds, days, cold_start, grid_ write(*,*) '***** End Note from FV core **************************' write(*,*) ' ' endif - call remap_restart( Atm(n)%domain, Atm(n:n) ) + call remap_restart( Atm(n:n) ) if( is_master() ) write(*,*) 'Done remapping dynamical IC' else if( is_master() ) write(*,*) 'Warm starting, calling fv_io_restart' - call fv_io_read_restart(Atm(n)%domain,Atm(n:n)) + call fv_io_read_restart(Atm(n)%domain_for_read,Atm(n:n)) !====== PJP added DA functionality ====== if (Atm(n)%flagstruct%read_increment) then ! print point in middle of domain for a sanity check From 50d0368026cb1d8acdb8ce9492c0409536b87dd6 Mon Sep 17 00:00:00 2001 From: "Rusty.Benson" <rusty.benson@noaa.gov> Date: Thu, 14 Apr 2022 16:33:29 -0400 Subject: [PATCH 2/2] rename enforce_rst_cksum to ignore_rst_cksum and change the default value for compatibility --- model/fv_arrays.F90 | 2 +- model/fv_control.F90 | 6 +++--- tools/fv_io.F90 | 16 ++++++++-------- 3 files changed, 12 insertions(+), 12 deletions(-) diff --git a/model/fv_arrays.F90 b/model/fv_arrays.F90 index a953b2965..8b1cb3b40 100644 --- a/model/fv_arrays.F90 +++ b/model/fv_arrays.F90 @@ -511,7 +511,7 @@ module fv_arrays_mod !----------------------------------------------------------------------------------------------- logical :: reset_eta = .false. - logical :: enforce_rst_cksum = .true. !< enfore or override data integrity restart checksums + logical :: ignore_rst_cksum = .false. !< enfore (.false.) or override (.true.) data integrity restart checksums real :: p_fac = 0.05 !< Safety factor for minimum nonhydrostatic pressures, which !< will be limited so the full pressure is no less than p_fac !< times the hydrostatic pressure. This is only of concern in mid-top diff --git a/model/fv_control.F90 b/model/fv_control.F90 index 36cf70dd3..7a3d6d47a 100644 --- a/model/fv_control.F90 +++ b/model/fv_control.F90 @@ -188,7 +188,7 @@ subroutine fv_control_init(Atm, dt_atmos, this_grid, grids_on_this_pe, p_split) real(kind=R_GRID) , pointer :: target_lon logical , pointer :: reset_eta - logical , pointer :: enforce_rst_cksum + logical , pointer :: ignore_rst_cksum real , pointer :: p_fac real , pointer :: a_imp integer , pointer :: n_split @@ -730,7 +730,7 @@ subroutine set_namelist_pointers(Atm) write_restart_with_bcs => Atm%flagstruct%write_restart_with_bcs regional_bcs_from_gsi => Atm%flagstruct%regional_bcs_from_gsi reset_eta => Atm%flagstruct%reset_eta - enforce_rst_cksum => Atm%flagstruct%enforce_rst_cksum + ignore_rst_cksum => Atm%flagstruct%ignore_rst_cksum p_fac => Atm%flagstruct%p_fac a_imp => Atm%flagstruct%a_imp n_split => Atm%flagstruct%n_split @@ -943,7 +943,7 @@ subroutine read_namelist_fv_core_nml(Atm) w_limiter, write_coarse_restart_files, write_coarse_diagnostics,& write_only_coarse_intermediate_restarts, & write_coarse_agrid_vel_rst, write_coarse_dgrid_vel_rst, & - pass_full_omega_to_physics_in_non_hydrostatic_mode, enforce_rst_cksum + pass_full_omega_to_physics_in_non_hydrostatic_mode, ignore_rst_cksum ! Read FVCORE namelist diff --git a/tools/fv_io.F90 b/tools/fv_io.F90 index 79289ce5b..1f45d0ac8 100644 --- a/tools/fv_io.F90 +++ b/tools/fv_io.F90 @@ -456,7 +456,7 @@ subroutine fv_io_read_restart(fv_domain,Atm,prefix,directory) Atm(1)%Fv_restart_tile_is_open = open_file(Atm(1)%Fv_restart_tile, fname, "read", fv_domain, is_restart=.true.) if (Atm(1)%Fv_restart_tile_is_open) then call fv_io_register_restart(Atm(1)) - call read_restart(Atm(1)%Fv_restart_tile, ignore_checksum=Atm(1)%flagstruct%enforce_rst_cksum) + call read_restart(Atm(1)%Fv_restart_tile, ignore_checksum=Atm(1)%flagstruct%ignore_rst_cksum) call close_file(Atm(1)%Fv_restart_tile) Atm(1)%Fv_restart_tile_is_open = .false. endif @@ -466,7 +466,7 @@ subroutine fv_io_read_restart(fv_domain,Atm,prefix,directory) Atm(1)%Tra_restart_is_open = open_file(Atm(1)%Tra_restart, fname, "read", fv_domain, is_restart=.true.) if (Atm(1)%Tra_restart_is_open) then call fv_io_register_restart(Atm(1)) - call read_restart(Atm(1)%Tra_restart, ignore_checksum=Atm(1)%flagstruct%enforce_rst_cksum) + call read_restart(Atm(1)%Tra_restart, ignore_checksum=Atm(1)%flagstruct%ignore_rst_cksum) call close_file(Atm(1)%Tra_restart) Atm(1)%Tra_restart_is_open = .false. else @@ -479,7 +479,7 @@ subroutine fv_io_read_restart(fv_domain,Atm,prefix,directory) if (Atm(1)%Rsf_restart_is_open) then Atm(1)%flagstruct%srf_init = .true. call fv_io_register_restart(Atm(1)) - call read_restart(Atm(1)%Rsf_restart, ignore_checksum=Atm(1)%flagstruct%enforce_rst_cksum) + call read_restart(Atm(1)%Rsf_restart, ignore_checksum=Atm(1)%flagstruct%ignore_rst_cksum) call close_file(Atm(1)%Rsf_restart) Atm(1)%Rsf_restart_is_open = .false. else @@ -493,7 +493,7 @@ subroutine fv_io_read_restart(fv_domain,Atm,prefix,directory) Atm(1)%Mg_restart_is_open = open_file(Atm(1)%Mg_restart, fname, "read", fv_domain, is_restart=.true.) if (Atm(1)%Mg_restart_is_open) then call fv_io_register_restart(Atm(1)) - call read_restart(Atm(1)%Mg_restart, ignore_checksum=Atm(1)%flagstruct%enforce_rst_cksum) + call read_restart(Atm(1)%Mg_restart, ignore_checksum=Atm(1)%flagstruct%ignore_rst_cksum) call close_file(Atm(1)%Mg_restart) Atm(1)%Mg_restart_is_open = .false. else @@ -504,7 +504,7 @@ subroutine fv_io_read_restart(fv_domain,Atm,prefix,directory) Atm(1)%Lnd_restart_is_open = open_file(Atm(1)%Lnd_restart, fname, "read", fv_domain, is_restart=.true.) if (Atm(1)%Lnd_restart_is_open) then call fv_io_register_restart(Atm(1)) - call read_restart(Atm(1)%Lnd_restart, ignore_checksum=Atm(1)%flagstruct%enforce_rst_cksum) + call read_restart(Atm(1)%Lnd_restart, ignore_checksum=Atm(1)%flagstruct%ignore_rst_cksum) call close_file(Atm(1)%Lnd_restart) Atm(1)%Lnd_restart_is_open = .false. else @@ -674,7 +674,7 @@ subroutine remap_restart(Atm) if (Atm(1)%Rsf_restart_is_open) then Atm%flagstruct%srf_init = .true. call fv_io_register_restart(Atm(1)) - call read_restart(Atm(1)%Rsf_restart, ignore_checksum=Atm(1)%flagstruct%enforce_rst_cksum) + call read_restart(Atm(1)%Rsf_restart, ignore_checksum=Atm(1)%flagstruct%ignore_rst_cksum) call close_file(Atm(1)%Rsf_restart) Atm(1)%Rsf_restart_is_open = .false. call mpp_error(NOTE,'==> Warning from remap_restart: Expected file '//trim(fname)//' does not exist') @@ -1435,12 +1435,12 @@ subroutine fv_io_read_BCs(Atm) call fv_io_register_restart_BCs(Atm) if (Atm%neststruct%BCfile_sw_is_open) then - call read_restart_bc(Atm%neststruct%BCfile_sw, ignore_checksum=Atm%flagstruct%enforce_rst_cksum) + call read_restart_bc(Atm%neststruct%BCfile_sw, ignore_checksum=Atm%flagstruct%ignore_rst_cksum) call close_file(Atm%neststruct%BCfile_sw) endif if (Atm%neststruct%BCfile_ne_is_open) then - call read_restart_bc(Atm%neststruct%BCfile_ne, ignore_checksum=Atm%flagstruct%enforce_rst_cksum) + call read_restart_bc(Atm%neststruct%BCfile_ne, ignore_checksum=Atm%flagstruct%ignore_rst_cksum) call close_file(Atm%neststruct%BCfile_ne) endif