Skip to content

Commit

Permalink
Create 'coupler.res' log file in write grid comp. Explicitly specify …
Browse files Browse the repository at this point in the history
…chunk sizes in restart files (#726)

* Write coupler.res log files from the write grid comp if quilting_restart is .true.

* Explicitly specify chunk sizes in write_restart_netcdf
  • Loading branch information
DusanJovic-NOAA authored Dec 5, 2023
1 parent ba6e8ea commit a82381c
Show file tree
Hide file tree
Showing 3 changed files with 59 additions and 14 deletions.
9 changes: 8 additions & 1 deletion io/module_write_restart_netcdf.F90
Original file line number Diff line number Diff line change
Expand Up @@ -79,7 +79,7 @@ subroutine write_restart_netcdf(wrtfb, filename, &
integer :: dimid, dimtype
integer :: im_dimid, im_p1_dimid, jm_dimid, jm_p1_dimid, time_dimid
integer :: im_varid, im_p1_varid, jm_varid, jm_p1_varid, time_varid
integer, dimension(:), allocatable :: dimids_2d, dimids_3d
integer, dimension(:), allocatable :: dimids_2d, dimids_3d, chunksizes
integer, dimension(:), allocatable :: varids, zaxis_dimids
logical shuffle

Expand Down Expand Up @@ -335,6 +335,7 @@ subroutine write_restart_netcdf(wrtfb, filename, &
! define variables
if (rank == 2) then
dimids_2d = [im_dimid,jm_dimid, time_dimid]
chunksizes = [im, jm, 1]
if (typekind == ESMF_TYPEKIND_R4) then
ncerr = nf90_def_var(ncid, trim(fldName), NF90_FLOAT, dimids_2d, varids(i)); NC_ERR_STOP(ncerr)
else if (typekind == ESMF_TYPEKIND_R8) then
Expand All @@ -346,13 +347,17 @@ subroutine write_restart_netcdf(wrtfb, filename, &
else if (rank == 3) then
if ( .not.is_restart_core ) then
dimids_3d = [im_dimid,jm_dimid,zaxis_dimids(i),time_dimid]
chunksizes = [im, jm, 1, 1]
else
if (staggerloc == ESMF_STAGGERLOC_CENTER) then
dimids_3d = [im_dimid,jm_dimid,zaxis_dimids(i),time_dimid]
chunksizes = [im, jm, 1, 1]
else if (staggerloc == ESMF_STAGGERLOC_EDGE1) then ! east
dimids_3d = [im_p1_dimid,jm_dimid,zaxis_dimids(i),time_dimid]
chunksizes = [im+1, jm, 1, 1]
else if (staggerloc == ESMF_STAGGERLOC_EDGE2) then ! south
dimids_3d = [im_dimid,jm_p1_dimid,zaxis_dimids(i),time_dimid]
chunksizes = [im, jm+1, 1, 1]
else
if (mype==0) write(0,*)'Unsupported staggerloc ', staggerloc
call ESMF_Finalize(endflag=ESMF_END_ABORT)
Expand All @@ -374,6 +379,8 @@ subroutine write_restart_netcdf(wrtfb, filename, &
ncerr = nf90_var_par_access(ncid, varids(i), par_access); NC_ERR_STOP(ncerr)
end if

ncerr = nf90_def_var_chunking(ncid, varids(i), NF90_CHUNKED, chunksizes) ; NC_ERR_STOP(ncerr)

if (zstandard_level(1) > 0) then
ncerr = nf90_def_var_zstandard(ncid, varids(i), zstandard_level(1))
if (ncerr /= nf90_noerr) then
Expand Down
50 changes: 44 additions & 6 deletions io/module_wrt_grid_comp.F90
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ module module_wrt_grid_comp
stdlat1, stdlat2, dx, dy, iau_offset, &
ideflate, zstandard_level, lflname_fulltime
use module_write_netcdf, only : write_netcdf
use module_write_restart_netcdf
use module_write_restart_netcdf, only : write_restart_netcdf
use physcons, only : pi => con_pi
#ifdef INLINE_POST
use post_fv3, only : post_run_fv3
Expand All @@ -68,10 +68,11 @@ module module_wrt_grid_comp
integer,save :: ngrids

integer,save :: wrt_mpi_comm !<-- the mpi communicator in the write comp
integer,save :: idate(7)
integer,save :: idate(7), start_time(7)
logical,save :: write_nsflip
logical,save :: change_wrtidate=.false.
integer,save :: frestart(999) = -1
integer,save :: calendar_type = 3
logical :: lprnt
!
!-----------------------------------------------------------------------
Expand Down Expand Up @@ -840,6 +841,7 @@ subroutine wrt_initialize_p1(wrt_comp, imp_state_write, exp_state_write, clock,
h=idate(4), m=idate(5), s=idate(6),rc=rc)
! if (lprnt) write(0,*) 'in wrt initial, io_baseline time=',idate,'rc=',rc
idate(7) = 1
start_time = idate
wrt_int_state%idate = idate
wrt_int_state%fdate = idate
! update IO-BASETIME and idate on write grid comp when IAU is enabled
Expand Down Expand Up @@ -1333,8 +1335,27 @@ subroutine wrt_initialize_p1(wrt_comp, imp_state_write, exp_state_write, clock,

if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return

! save calendar_type (as integer) for use in 'coupler.res'
if (index(trim(attNameList(i)),'time:calendar') > 0) then
select case( uppercase(trim(valueS)) )
case( 'JULIAN' )
calendar_type = JULIAN
case( 'GREGORIAN' )
calendar_type = GREGORIAN
case( 'NOLEAP' )
calendar_type = NOLEAP
case( 'THIRTY_DAY' )
calendar_type = THIRTY_DAY_MONTHS
case( 'NO_CALENDAR' )
calendar_type = NO_CALENDAR
case default
call mpp_error ( FATAL, 'fcst_initialize: calendar must be one of '// &
'JULIAN|GREGORIAN|NOLEAP|THIRTY_DAY|NO_CALENDAR.' )
end select
endif

! update the time:units when idate on write grid component is changed
if ( index(trim(attNameList(i)),'time:units')>0) then
if (index(trim(attNameList(i)),'time:units') > 0) then
if ( change_wrtidate ) then
idx = index(trim(valueS),' since ')
if(lprnt) print *,'in write grid comp, time:unit=',trim(valueS)
Expand Down Expand Up @@ -1795,7 +1816,7 @@ subroutine wrt_run(wrt_comp, imp_state_write, exp_state_write,clock,rc)

logical :: use_parallel_netcdf
real, allocatable :: output_fh(:)
logical :: is_restart_bundle
logical :: is_restart_bundle, restart_written
integer :: tileCount
!
!-----------------------------------------------------------------------
Expand Down Expand Up @@ -2151,6 +2172,8 @@ subroutine wrt_run(wrt_comp, imp_state_write, exp_state_write,clock,rc)

! if (lprnt) write(0,*)'wrt_run: loop over wrt_int_state%FBCount ',wrt_int_state%FBCount, ' nfhour ', nfhour, ' cdate ', cdate(1:6)
two_phase_loop: do out_phase = 1, 2

restart_written = .false.
file_loop_all: do nbdl=1, wrt_int_state%FBCount

call ESMF_FieldBundleGet(wrt_int_state%wrtFB(nbdl), name=wrtFBName, rc=rc)
Expand Down Expand Up @@ -2349,6 +2372,8 @@ subroutine wrt_run(wrt_comp, imp_state_write, exp_state_write,clock,rc)
rc)
endif ! cubed sphere vs. regional/nest write grid

restart_written = .true.

else ! history bundle
if (trim(output_grid(grid_id)) == 'cubed_sphere_grid') then

Expand Down Expand Up @@ -2413,13 +2438,26 @@ subroutine wrt_run(wrt_comp, imp_state_write, exp_state_write,clock,rc)
enddo file_loop_all

if (out_phase == 1 .and. mype == lead_write_task) then
!** write out log file
open(newunit=nolog,file='log.atm.f'//trim(cfhour),form='FORMATTED')
!** write history log file
open(newunit=nolog, file='log.atm.f'//trim(cfhour))
write(nolog,"('completed: fv3atm')")
write(nolog,"('forecast hour: ',f10.3)") nfhour
write(nolog,"('valid time: ',6(i4,2x))") wrt_int_state%fdate(1:6)
close(nolog)
endif

if (out_phase == 2 .and. restart_written .and. mype == lead_write_task) then
!** write coupler.res log file
open(newunit=nolog, file='RESTART/'//trim(time_restart)//'.coupler.res', status='new')
write(nolog,"(i6,8x,a)") calendar_type , &
'(Calendar: no_calendar=0, thirty_day_months=1, julian=2, gregorian=3, noleap=4)'
write(nolog,"(6i6,8x,a)") start_time(1:6), &
'Model start time: year, month, day, hour, minute, second'
write(nolog,"(6i6,8x,a)") wrt_int_state%fdate(1:6), &
'Current model time: year, month, day, hour, minute, second'
close(nolog)
endif

enddo two_phase_loop
endif ! if ( wrt_int_state%output_history )

Expand Down
14 changes: 7 additions & 7 deletions module_fcst_grid_comp.F90
Original file line number Diff line number Diff line change
Expand Up @@ -921,11 +921,11 @@ subroutine fcst_initialize(fcst_comp, importState, exportState, clock, rc)
! Add time Attribute to the exportState
call ESMF_AttributeAdd(exportState, convention="NetCDF", purpose="FV3", &
attrList=(/ "time ", &
"time:long_name ", &
"time:units ", &
"time:cartesian_axis", &
"time:calendar_type ", &
"time:calendar " /), rc=rc)
"time:long_name ", &
"time:units ", &
"time:cartesian_axis", &
"time:calendar_type ", &
"time:calendar " /), rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return

call ESMF_AttributeSet(exportState, convention="NetCDF", purpose="FV3", &
Expand Down Expand Up @@ -1366,8 +1366,8 @@ subroutine fcst_run_phase_2(fcst_comp, importState, exportState,clock,rc)
call atmos_model_restart(Atmos, timestamp)
call write_stoch_restart_atm('RESTART/'//trim(timestamp)//'.atm_stoch.res.nc')

!----- write restart file ------
if (mpp_pe() == mpp_root_pe())then
!----- write coupler.res file ------
if (.not. quilting_restart .and. mpp_pe() == mpp_root_pe()) then
call get_date (Atmos%Time, date(1), date(2), date(3), date(4), date(5), date(6))
open( newunit=unit, file='RESTART/'//trim(timestamp)//'.coupler.res' )
write( unit, '(i6,8x,a)' )calendar_type, &
Expand Down

0 comments on commit a82381c

Please sign in to comment.