Skip to content

Commit

Permalink
Use is_restart_fh mod in ice_comp_nuopc.F90
Browse files Browse the repository at this point in the history
  • Loading branch information
NickSzapiro-NOAA authored Oct 15, 2024
1 parent 9c98e3f commit 79f56c6
Showing 1 changed file with 14 additions and 55 deletions.
69 changes: 14 additions & 55 deletions cicecore/drivers/nuopc/cmeps/ice_comp_nuopc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -47,6 +47,7 @@ module ice_comp_nuopc
use nuopc_shr_methods , only : set_component_logging
#else
use ice_shr_methods , only : set_component_logging
use shr_is_restart_fh_mod, only : init_is_restart_fh, is_restart_fh, write_restartfh
#endif
use ice_timers
use CICE_InitMod , only : cice_init1, cice_init2
Expand Down Expand Up @@ -96,8 +97,6 @@ module ice_comp_nuopc
logical :: mastertask
logical :: runtimelog = .false.
logical :: restart_eor = .false. !End of run restart flag
logical :: write_restartfh = .false.
type(ESMF_Time), allocatable :: restartFhTimes(:)
integer :: start_ymd ! Start date (YYYYMMDD)
integer :: start_tod ! start time of day (s)
integer :: curr_ymd ! Current date (YYYYMMDD)
Expand Down Expand Up @@ -239,11 +238,6 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
integer :: iblk, jblk ! indices
integer :: ig, jg ! indices
integer :: ilo, ihi, jlo, jhi ! beginning and end of physical domain
integer :: nfh, fh_s
character(len=256) :: timestr
real(kind=ESMF_KIND_R8), allocatable :: restart_fh(:)
type(ESMF_TimeInterval) :: fhInterval
type(ESMF_Config) :: CF_mc
character(len=char_len_long) :: diag_filename = 'unset'
character(len=char_len_long) :: logmsg
character(len=char_len_long) :: single_column_lnd_domainfile
Expand Down Expand Up @@ -532,44 +526,6 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
nu_diag_set = .true.
end if

! Set up times to write non-interval restarts
inquire(FILE='model_configure', EXIST=isPresent)
if (isPresent) then !model_configure exists. this is ufs run
CF_mc = ESMF_ConfigCreate(rc=rc)
call ESMF_ConfigLoadFile(config=CF_mc,filename='model_configure' ,rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return

nfh = ESMF_ConfigGetLen(config=CF_mc, label ='restart_fh:',rc=rc)
if (nfh .gt. 0) then
allocate(restart_fh(1:nfh))
allocate(restartFhTimes(1:nfh)) !not deallocated

call ESMF_ConfigGetAttribute(CF_mc,valueList=restart_fh,label='restart_fh:', rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
! create a list of times at each restart_fh
call ESMF_ClockGet( clock, currTime=currTime, rc=rc )
if (ChkErr(rc,__LINE__,u_FILE_u)) return
do n = 1,nfh
fh_s = NINT(3600*restart_fh(n))
call ESMF_TimeIntervalSet(fhInterval, s=fh_s, rc=rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
restartFhTimes(n) = currTime + fhInterval
call ESMF_TimePrint(restartFhTimes(n), options="string", preString="restart_fh at ", unit=timestr, rc=rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
if (mastertask) then
if (mod(fh_s,dtime) /= 0) then
write(nu_diag,'(A)')trim(subname)//trim(timestr)//' will not be written'
else
write(nu_diag,'(A)')trim(subname)//trim(timestr)//' will be written'
end if
end if
end do
deallocate(restart_fh)
end if !nfh>0
call ESMF_ConfigDestroy(CF_mc, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
end if !model_configure

!----------------------------------------------------------------------------
! First cice initialization phase - before initializing grid info
!----------------------------------------------------------------------------
Expand Down Expand Up @@ -1049,6 +1005,7 @@ subroutine ModelAdvance(gcomp, rc)
integer :: shrlogunit ! original log unit
integer :: k,n ! index
logical :: stop_now ! .true. ==> stop at the end of this run phase
logical, save :: first_time = .true. ! true on first call, false after
integer :: ymd ! Current date (YYYYMMDD)
integer :: tod ! Current time of day (sec)
integer :: curr_ymd ! Current date (YYYYMMDD)
Expand All @@ -1059,6 +1016,7 @@ subroutine ModelAdvance(gcomp, rc)
integer :: mon_sync ! Sync current month
integer :: day_sync ! Sync current day
integer :: tod_sync ! Sync current time of day (sec)
integer :: dtime ! integer time step
character(char_len_long) :: restart_date
character(char_len_long) :: restart_filename
logical :: isPresent, isSet
Expand Down Expand Up @@ -1186,17 +1144,18 @@ subroutine ModelAdvance(gcomp, rc)

force_restart_now = .false.

if (allocated(restartFhTimes)) then
write_restartfh = .false.
! check if next time is == to any restartfhtime
do n = 1,size(restartFhTimes)
call ESMF_ClockGetNextTime(clock, nextTime=nexttime, rc=rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
if (nextTime == restartFhTimes(n)) write_restartfh = .true.
end do
end if

#ifndef CESMCOUPLED
if (first_time) then
call ESMF_TimeIntervalGet(timeStep, s=dtime, rc=rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
call init_is_restart_fh(currTime, dtime,.true.)
first_time = .false.
fi
write_restartfh = is_restart_fh(clock)
if (ESMF_AlarmIsRinging(alarm, rc=rc) .or. write_restartfh) then
#else
if (ESMF_AlarmIsRinging(alarm, rc=rc) then
#endif
if (ChkErr(rc,__LINE__,u_FILE_u)) return
force_restart_now = .true.
call ESMF_AlarmRingerOff( alarm, rc=rc )
Expand Down

0 comments on commit 79f56c6

Please sign in to comment.