Skip to content

Commit

Permalink
add timestamps to rpointer files
Browse files Browse the repository at this point in the history
  • Loading branch information
jedwards4b committed Sep 26, 2024
1 parent 00b9f3a commit 9f07cf9
Show file tree
Hide file tree
Showing 4 changed files with 57 additions and 35 deletions.
5 changes: 4 additions & 1 deletion src/cpl/nuopc/lnd_comp_nuopc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -656,7 +656,10 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
! ---------------------
! Finish initializing ctsm
! ---------------------
call initialize2(ni, nj)
call ESMF_ClockGet(clock, currTime=currtime, rc=rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return

call initialize2(ni, nj, currtime)

!--------------------------------
! Create land export state
Expand Down
6 changes: 5 additions & 1 deletion src/main/clm_initializeMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -124,12 +124,13 @@ subroutine initialize1(dtime)
end subroutine initialize1

!-----------------------------------------------------------------------
subroutine initialize2(ni,nj)
subroutine initialize2(ni,nj, currtime)
!
! !DESCRIPTION:
! CLM initialization second phase
!
! !USES:
use ESMF , only : ESMF_Time
use clm_varcon , only : spval
use clm_varpar , only : natpft_lb, natpft_ub, cft_lb, cft_ub, maxpatch_glc
use clm_varpar , only : surfpft_lb, surfpft_ub
Expand Down Expand Up @@ -185,6 +186,7 @@ subroutine initialize2(ni,nj)
!
! !ARGUMENTS
integer, intent(in) :: ni, nj ! global grid sizes
type(ESMF_Time), intent(in) :: currtime
!
! !LOCAL VARIABLES:
integer :: c,g,i,j,k,l,n,p ! indices
Expand Down Expand Up @@ -344,10 +346,12 @@ subroutine initialize2(ni,nj)
source=create_nutrient_competition_method(bounds_proc))
call readParameters(photosyns_inst)


! Initialize time manager
if (nsrest == nsrStartup) then
call timemgr_init()
else
call timemgr_init(curr_date_in=currtime)
call restFile_getfile(file=fnamer, path=pnamer)
call restFile_open( flag='read', file=fnamer, ncid=ncid )
call timemgr_restart_io( ncid=ncid, flag='read' )
Expand Down
39 changes: 27 additions & 12 deletions src/main/restFileMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -6,13 +6,13 @@ module restFileMod
!
! !USES:
#include "shr_assert.h"
use shr_kind_mod , only : r8 => shr_kind_r8
use shr_kind_mod , only : r8 => shr_kind_r8, CL=>shr_kind_CL
use decompMod , only : bounds_type, get_proc_clumps, get_clump_bounds
use decompMod , only : bounds_level_proc
use spmdMod , only : masterproc, mpicom
use abortutils , only : endrun
use shr_log_mod , only : errMsg => shr_log_errMsg
use clm_time_manager , only : timemgr_restart_io, get_nstep
use clm_time_manager , only : timemgr_restart_io, get_nstep, get_curr_date
use subgridRestMod , only : subgridRestWrite, subgridRestRead, subgridRest_read_cleanup
use accumulMod , only : accumulRest
use clm_instMod , only : clm_instRest
Expand Down Expand Up @@ -340,15 +340,19 @@ subroutine restFile_read_pfile( pnamer )
! !USES:
use fileutils , only : opnfil, getavu, relavu
use clm_varctl, only : rpntfil, rpntdir, inst_suffix
use mpi, only : MPI_CHARACTER
!
! !ARGUMENTS:
character(len=*), intent(out) :: pnamer ! full path of restart file
!
! !LOCAL VARIABLES:
!EOP
integer :: i ! indices
integer :: yr, mon, day, tod
character(len=17) :: timestamp
integer :: nio ! restart unit
integer :: status ! substring check status
logical :: found
character(len=256) :: locfn ! Restart pointer file name
!-----------------------------------------------------------------------

Expand All @@ -359,17 +363,24 @@ subroutine restFile_read_pfile( pnamer )
! New history files are always created for branch runs.

if (masterproc) then
write(iulog,*) 'Reading restart pointer file....'
nio = getavu()
call get_curr_date(yr, mon, day, tod)
write(timestamp,'(".",i4.4,"-",i2.2,"-",i2.2,"-",i5.5)'),yr,mon,day,tod
locfn = trim(rpntdir) //'/'// trim(rpntfil)//trim(inst_suffix)//timestamp
inquire(file=trim(locfn), exist=found)
if(.not. found) then
locfn = trim(rpntdir) //'/'// trim(rpntfil)//trim(inst_suffix)
endif
write(iulog,*) 'Reading restart pointer file: ',trim(locfn)

call opnfil (locfn, nio, 'f')
read (nio,'(a256)') pnamer
call relavu (nio)
endif

nio = getavu()
locfn = trim(rpntdir) //'/'// trim(rpntfil)//trim(inst_suffix)
call opnfil (locfn, nio, 'f')
read (nio,'(a256)') pnamer
call relavu (nio)
call mpi_bcast (pnamer, CL, MPI_CHARACTER, 0, mpicom, status)

if (masterproc) then
write(iulog,*) 'Reading restart data.....'
write(iulog,*) 'Reading restart data: ',trim(pnamer)
write(iulog,'(72a1)') ("-",i=1,60)
end if

Expand Down Expand Up @@ -422,12 +433,16 @@ subroutine restFile_write_pfile( fnamer )
! !LOCAL VARIABLES:
integer :: m ! index
integer :: nio ! restart pointer file
integer :: yr, mon, day, tod
character(len=17) :: timestamp
character(len=256) :: filename ! local file name
!-----------------------------------------------------------------------

if (masterproc) then
call get_curr_date(yr, mon, day, tod)
write(timestamp,'(".",i4.4,"-",i2.2,"-",i2.2,"-",i5.5)') yr, mon, day, tod
nio = getavu()
filename= trim(rpntdir) //'/'// trim(rpntfil)//trim(inst_suffix)
filename= trim(rpntdir) //'/'// trim(rpntfil)//trim(inst_suffix)//timestamp
call opnfil( filename, nio, 'f' )

write(nio,'(a)') fnamer
Expand Down Expand Up @@ -466,7 +481,7 @@ subroutine restFile_open( flag, file, ncid )
! Open netcdf restart file

if (masterproc) then
write(iulog,*) 'Reading restart dataset'
write(iulog,*) 'Reading restart dataset: ', trim(file)
end if
call ncd_pio_openfile (ncid, trim(file), 0)

Expand Down
42 changes: 21 additions & 21 deletions src/utils/clm_time_manager.F90
Original file line number Diff line number Diff line change
Expand Up @@ -177,7 +177,8 @@ end subroutine set_timemgr_init

!=========================================================================================

subroutine timemgr_init( )
subroutine timemgr_init(curr_date_in )
type(ESMF_Time), intent(in), optional :: curr_date_in

!---------------------------------------------------------------------------------
! Initialize the ESMF time manager from the sync clock
Expand All @@ -187,8 +188,8 @@ subroutine timemgr_init( )
character(len=*), parameter :: sub = 'clm::timemgr_init'
integer :: rc ! return code
type(ESMF_Time) :: start_date ! start date for run
type(ESMF_Time) :: curr_date ! temporary date used in logic
type(ESMF_Time) :: ref_date ! reference date for time coordinate
type(ESMF_Time) :: curr_date ! temporary date used in logic
type(ESMF_TimeInterval) :: day_step_size ! day step size
type(ESMF_TimeInterval) :: step_size ! timestep size
!---------------------------------------------------------------------------------
Expand All @@ -211,8 +212,11 @@ subroutine timemgr_init( )
start_date = TimeSetymd( start_ymd, start_tod, "start_date" )

! Initialize current date

curr_date = start_date
if(present(curr_date_in)) then
curr_date = curr_date_in
else
curr_date = start_date
endif

call ESMF_TimeIntervalSet( step_size, s=dtime, rc=rc )
call chkrc(rc, sub//': error return from ESMF_TimeIntervalSet: setting step_size')
Expand Down Expand Up @@ -253,7 +257,7 @@ subroutine init_clock( start_date, ref_date, curr_date )
!---------------------------------------------------------------------------------
! Purpose: Initialize the clock based on the start_date, ref_date and curr_date
!
use ESMF , only : ESMF_ClockCreate, ESMF_ClockAdvance
use ESMF , only : ESMF_ClockCreate, ESMF_ClockAdvance, esmf_clockiscreated

type(ESMF_Time), intent(in) :: start_date ! start date for run
type(ESMF_Time), intent(in) :: ref_date ! reference date for time coordinate
Expand All @@ -277,6 +281,7 @@ subroutine init_clock( start_date, ref_date, curr_date )
! manager included in cime appears to require stopTime.
call ESMF_TimeSet(stop_date, yy=really_big_year, mm=12, dd=31, s=0, &
calendar=tm_cal, rc=rc)
call chkrc(rc, sub//': error return from ESMF_TimeIntervalSet: setting step_size')

! Error check

Expand All @@ -299,9 +304,10 @@ subroutine init_clock( start_date, ref_date, curr_date )

! Initialize the clock


tm_clock = ESMF_ClockCreate(name="CLM Time-manager clock", timeStep=step_size, startTime=start_date, &
stopTime=stop_date, refTime=ref_date, rc=rc)
call chkrc(rc, sub//': error return from ESMF_ClockSetup')
call chkrc(rc, sub//': error return from ESMF_ClockCreate')

! Advance clock to the current time (in case of a restart)

Expand Down Expand Up @@ -496,11 +502,12 @@ end subroutine timemgr_restart_io

!=========================================================================================

subroutine timemgr_restart( )
subroutine timemgr_restart()

!---------------------------------------------------------------------------------
! Restart the ESMF time manager using the synclock for ending date.
!

character(len=*), parameter :: sub = 'clm::timemgr_restart'
integer :: rc ! return code
integer :: yr, mon, day, tod ! Year, month, day, and second as integers
Expand All @@ -520,16 +527,15 @@ subroutine timemgr_restart( )

dtime = rst_step_sec

! Initialize start date from restart info

start_date = TimeSetymd( rst_start_ymd, rst_start_tod, "start_date" )
! Check start date from restart info

! Initialize current date from restart info
if (rst_start_ymd .ne. start_ymd .or. rst_start_tod .ne. start_tod) then
call shr_sys_abort(sub//'ERROR: mismatch in start date with restart file')
endif

curr_date = TimeSetymd( rst_curr_ymd, rst_curr_tod, "curr_date" )

call ESMF_TimeIntervalSet( step_size, s=dtime, rc=rc )
call chkrc(rc, sub//': error return from ESMF_TimeIntervalSet: setting step_size')
if (rst_ref_ymd .ne. ref_ymd .or. rst_ref_tod .ne. ref_tod) then
call shr_sys_abort(sub//'ERROR: mismatch in reference date with restart file')
endif

call ESMF_TimeIntervalSet( day_step_size, d=1, rc=rc )
call chkrc(rc, sub//': error return from ESMF_TimeIntervalSet: setting day_step_size')
Expand All @@ -540,12 +546,6 @@ subroutine timemgr_restart( )

! Initialize ref date from restart info

ref_date = TimeSetymd( rst_ref_ymd, rst_ref_tod, "ref_date" )

! Initialize clock

call init_clock( start_date, ref_date, curr_date)

! Advance the timestep.
! Data from the restart file corresponds to the last timestep of the previous run.

Expand Down

0 comments on commit 9f07cf9

Please sign in to comment.