Skip to content

Commit

Permalink
Merge pull request #336 from nmizukami/cesm-coupling_timestep
Browse files Browse the repository at this point in the history
separate simulation time-step and forcing time-step
  • Loading branch information
nmizukami authored Mar 9, 2023
2 parents 8847342 + ad95b15 commit 44844e8
Show file tree
Hide file tree
Showing 24 changed files with 1,090 additions and 1,092 deletions.
2 changes: 1 addition & 1 deletion route/build/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -138,10 +138,10 @@ EXTINCLUDES =
# data types
DATATYPES = \
nrtype.f90 \
public_var.f90 \
nr_utils.f90 \
pio_utils.f90 \
ascii_utils.f90 \
public_var.f90 \
dataTypes.f90 \
var_lookup.f90 \
time_utils.f90 \
Expand Down
9 changes: 5 additions & 4 deletions route/build/cpl/RtmMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ MODULE RtmMod
USE RunoffMod, ONLY: rtmCTL, RunoffInit ! rof related data objects

! mizuRoute share routines
USE public_var, ONLY: secprday ! second per day
USE public_var, ONLY: dt ! routing time step
USE public_var, ONLY: iulog
USE public_var, ONLY: qgwl_runoff_option
Expand Down Expand Up @@ -120,7 +121,7 @@ SUBROUTINE route_ini(rof_active,flood_active)
if (masterproc) then
write(iulog,*) 'WARNING: Adjust mizuRoute dt to coupling_period'
endif
dt = coupling_period*60.0*60.0*24.0
dt = coupling_period*secprday ! day->sec
endif

! mizuRoute time initialize based on time from coupler
Expand All @@ -130,8 +131,8 @@ SUBROUTINE route_ini(rof_active,flood_active)
if (masterproc) then
write(iulog,*) 'define run:'
write(iulog,*) ' run type = ',runtyp(nsrest+1)
write(iulog,*) ' coupling_period = ',coupling_period, '[day]'
write(iulog,*) ' delt_mizuRoute = ',dt, '[sec]'
write(iulog,*) ' coupling_frequency = ',coupling_period, '[day]'
write(iulog,*) ' mizuRoute timestep = ',dt, '[sec]'
call shr_sys_flush(iulog)
endif

Expand Down Expand Up @@ -384,7 +385,7 @@ SUBROUTINE route_run(rstwr)
call t_startf('mizuRoute_tot')
call shr_sys_flush(iulog)

delt_coupling = coupling_period*60.0*60.0*24.0 ! day -> sec
delt_coupling = coupling_period*secprday ! day -> sec
if (first_call) then
nsub_save = 1
delt_save = dt
Expand Down
14 changes: 3 additions & 11 deletions route/build/cpl/RtmTimeManager.F90
Original file line number Diff line number Diff line change
Expand Up @@ -110,16 +110,8 @@ SUBROUTINE init_time(ierr, message)
! number of time step from reference time to simulation end time
nTime = int(endJulday - begJulday/dt_day) + 1

! Create timeVar array: starting with 0 and increment of model time step in model unit (t_unit)
allocate(timeVar(nTime), stat=ierr)
if(ierr/=0)then; message=trim(message)//trim(cmessage); return; endif

timeVar(1) = (begJulday - refJulday)*timePerDay
if (nTime>1) then
do ix = 2, nTime
timeVar(ix) = timeVar(ix-1) + dt/secPerTime
end do
end if
! Initialize timeVar : starting with 0 and increment of model time step in model time unit (t_unit)
timeVar = (begJulday - refJulday)*timePerDay

! check that the dates are aligned
if(endDatetime < begDatetime) then; ierr=20; message=trim(message)//'simulation end is before simulation start'; return; endif
Expand All @@ -136,7 +128,7 @@ SUBROUTINE init_time(ierr, message)
write(iulog,*) 'simDatetime = ', simDatetime(1)%year(), simDatetime(1)%month(), simDatetime(1)%day(), simDatetime(1)%hour(), simDatetime(1)%minute(), simDatetime(1)%sec()
write(iulog,*) 'dt [sec] = ', dt
write(iulog,*) 'nTime = ', nTime
write(iulog,*) 'iTime, timeVar(iTime) = ', iTime, timeVar(iTime)
write(iulog,*) 'iTime, timeVar(iTime) = ', iTime, timeVar
call shr_sys_flush(iulog)
end if

Expand Down
89 changes: 43 additions & 46 deletions route/build/src/dataTypes.f90
Original file line number Diff line number Diff line change
Expand Up @@ -72,15 +72,6 @@ MODULE dataTypes
type(reach), allocatable :: branch(:)
end type subbasin_omp

! -- Data structures to hold mainstem and independent tributary reaches separately
! Used for openMP
type,public :: subbasin_omp_tmp
integer(i4b) :: outIndex ! index of outlet segment based on segment array
type(reach), allocatable :: mainstem(:) ! mainstem reach
type(reach), allocatable :: tributary(:) ! tributary reach
end type subbasin_omp_tmp


! ---------- general data structures ----------------------------------------------------------------------

! ** double precision type
Expand Down Expand Up @@ -130,16 +121,15 @@ MODULE dataTypes
! ---------- forcing input file strcuture -----------------------------------------------------------------

! -- input file name and strcuture for nc files
type, public :: infileinfo
type, public :: inFileInfo
integer(i4b) :: nTime ! number of time step in a nc file
integer(i4b) :: iTimebound(1:2) ! time index of start and end of the
real(dp) , allocatable :: timevar(:) ! the time varibale from the netcdf file
real(dp) :: convTime2Days ! the time varibale from the netcdf file
real(dp) , allocatable :: timeVar(:) ! the time varibale [day] from the netcdf file
real(dp) :: ncrefjulday ! the julian day for the reference of the nc file
character(len=strLen) :: infilename ! the name of the input file name
character(len=strLen) :: calendar ! the calendar
character(len=strLen) :: unit ! the unit of time
end type infileinfo
end type inFileInfo


! ---------- mapping data structures ----------------------------------------------------------------------
Expand All @@ -158,32 +148,39 @@ MODULE dataTypes
integer(i4b) , allocatable :: qhru_ix(:) ! Index of hrus associated with runoff simulation (="qhru")
end type remap

! simulated runoff data
type, public :: runoff
integer(i4b) :: nTime ! number of time steps
integer(i4b) :: nSpace(1:2) ! number of spatial dimension
real(dp) :: time ! time variable at one time step
real(dp) , allocatable :: sim(:) ! flux simulation (HM_HRU) at one time step (size: nSpace(1))
real(dp) , allocatable :: sim2D(:,:) ! flux simulation (x,y) at one time step (size: /nSpace(1),nSpace(2)/)
integer(i4b) , allocatable :: hru_id(:) ! id of HM_HRUs or RN_HRUs at which runoff is stored (size: nSpace(1))
integer(i4b) , allocatable :: hru_ix(:) ! Index of RN_HRUs associated with river network (used only if HM_HRUs = RN_HRUs)
real(dp) , allocatable :: basinRunoff(:)! remapped river network catchment runoff (size: number of nHRU)
real(dp) , allocatable :: basinEvapo(:) ! remapped river network catchment runoff (size: number of nHRU)
real(dp) , allocatable :: basinPrecip(:)! remapped river network catchment runoff (size: number of nHRU)
! mapping time step between two time series e.g., simulation time step and runoff time step for one simulation time step
! runoff value used at each simulaition time step is weighted average of runoff(s) across input time step(s)
! (can be one, but several if simulation step is larger than runoff time step)
! This store indices of netCDF files in input file streams and time step weight of input variables from each input timestep
type, public :: map_time
integer(i4b), allocatable :: iFile(:) ! index of input netCDF file
integer(i4b), allocatable :: iTime(:) ! index of time steps within the corresponding netCDF
real(dp), allocatable :: frac(:) ! weight
end type map_time

! ---------- input forcing data ----------------------------------------------------------------------

type, public :: inputData
integer(i4b) :: nSpace(1:2) ! number of spatial dimension
real(dp) , allocatable :: sim(:) ! flux simulation (HM_HRU) at one time step (size: nSpace(1))
real(dp) , allocatable :: sim2d(:,:) ! flux simulation (x,y) at one time step (size: /nSpace(1),nSpace(2)/)
real(dp) :: fillvalue ! fillvalue
end type inputData

type, public, extends(inputData) :: runoff ! runoff data
integer(i4b) , allocatable :: hru_id(:) ! id of HM_HRUs or RN_HRUs at which runoff is stored (size: nSpace(1))
integer(i4b) , allocatable :: hru_ix(:) ! Index of RN_HRUs associated with river network (used only if HM_HRUs = RN_HRUs)
real(dp) , allocatable :: basinRunoff(:) ! remapped river network catchment runoff [depth/time] (size: number of nHRU)
real(dp) , allocatable :: basinEvapo(:) ! remapped river network catchment evaporation [depth/time] (size: number of nHRU)
real(dp) , allocatable :: basinPrecip(:) ! remapped river network catchment precipitation [depth/time] (size: number of nHRU)
end type runoff

! water management data; fluxes to/from reaches or target volume
type, public :: wm
integer(i4b) :: nTime ! number of time steps
integer(i4b) :: nSpace(1:2) ! number of spatial dimension, in this case only one dimentonal
real(dp) :: time ! time variable at one time step
real(dp) , allocatable :: sim(:) ! user specified flux add/subtract, or volume at one time step (size: nSpace)
real(dp) , allocatable :: sim2D(:,:) ! to provide modularity for reading data
type, public, extends(inputData) :: wm ! water-management
integer(i4b) , allocatable :: seg_id(:) ! id of reach in data (size: nSpace)
integer(i4b) , allocatable :: seg_ix(:) ! Index of river network reach IDs corresponding reach ID in data
real(dp) , allocatable :: flux_wm(:) ! allocated flux to existing river network using sort_flux (size: number of nRCH)
real(dp) , allocatable :: vol_wm(:) ! allocated target vol to existing river network using sort_flux (size: number of nRCH)
end type
real(dp) , allocatable :: flux_wm(:) ! allocated flux to existing river network using sort_flux [m3/s] (size: number of nRCH)
real(dp) , allocatable :: vol_wm(:) ! allocated target vol to existing river network using sort_flux [m3/s] (size: number of nRCH)
end type wm

! ---------- reach parameters ----------------------------------------------------------------------------

Expand Down Expand Up @@ -299,18 +296,18 @@ MODULE dataTypes

! - Lagrangian kinematic wave states (collection of particles)
! Individual flow particles
TYPE, public :: FPOINT
type, public :: FPOINT
real(dp) :: QF ! Flow
real(dp) :: QM ! Modified flow
real(dp) :: TI ! initial time of point in reach
real(dp) :: TR ! time point expected to exit reach
logical(lgt) :: RF ! routing flag (T if point has exited)
END TYPE FPOINT
end type FPOINT

! Collection of flow points within a given reach
TYPE, public :: kwtRCH
type, public :: kwtRCH
type(FPOINT),allocatable :: KWAVE(:)
END TYPE kwtRCH
end type kwtRCH

! ---------- irf states (future flow series ) ---------------------------------
! Future flow series
Expand Down Expand Up @@ -339,16 +336,16 @@ MODULE dataTypes
type(SUBRCH) :: molecule
end type mcRCH

type, public :: dwRch
type, public :: dwRch
type(SUBRCH) :: molecule
end type dwRCH

type, public :: STRSTA
type(irfRCH) :: IRF_ROUTE
type(kwtRCH) :: LKW_ROUTE
type(kwRCH) :: KW_ROUTE
type(mcRCH) :: MC_ROUTE
type(dwRCH) :: DW_ROUTE
type(irfRCH) :: IRF_ROUTE
type(kwtRCH) :: LKW_ROUTE
type(kwRCH) :: KW_ROUTE
type(mcRCH) :: MC_ROUTE
type(dwRCH) :: DW_ROUTE
end type STRSTA


Expand Down Expand Up @@ -457,7 +454,7 @@ SUBROUTINE init(this, vName, vDesc, vUnit, vType, vDim, vFile)
this%varDesc = vDesc
this%varUnit = vUnit
this%varType = vType
this%varDim(1:n) = vDim(1:n)
this%varDim(1:n) = vDim(1:n)
this%varFile = vFile
END SUBROUTINE init

Expand Down
11 changes: 7 additions & 4 deletions route/build/src/globalData.f90
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ MODULE globalData
USE dataTypes, ONLY: var_info ! metadata type - variable
USE objTypes, ONLY: var_info_new ! metadata type - variable

USE dataTypes, ONLY: infileinfo ! data strture - information of input files
USE dataTypes, ONLY: inFileInfo ! data strture - information of input files
USE dataTypes, ONLY: gage ! data structure - gauge metadata

USE dataTypes, ONLY: RCHPRP ! data structure - Reach parameters (properties)
Expand All @@ -25,6 +25,7 @@ MODULE globalData
USE dataTypes, ONLY: LKFLX ! data structure - lake fluxes

USE dataTypes, ONLY: remap ! data structure - remapping data type

USE dataTypes, ONLY: runoff ! data structure - runoff data type
USE dataTypes, ONLY: wm ! data structure - water management (flux to/from segment, target volume) data type

Expand Down Expand Up @@ -86,18 +87,20 @@ MODULE globalData
! ---------- Date/Time data -------------------------------------------------------------------------

integer(i4b), public :: iTime ! time index at simulation time step
real(dp), allocatable, public :: timeVar(:) ! time variables (unit given by runoff data)
real(dp), public :: timeVar ! time variables (unit given by time variable)
real(dp), public :: TSEC(0:1) ! begning and end of time step since simulation started (sec)
type(datetime), public :: simDatetime(0:1) ! previous and current simulation time (yyyy:mm:dd:hh:mm:ss)
type(datetime), public :: begDatetime ! simulation start date/time (yyyy:mm:dd:hh:mm:ss)
type(datetime), public :: endDatetime ! simulation end date/time (yyyy:mm:dd:hh:mm:ss)
type(datetime), public :: restDatetime ! desired restart date/time (yyyy:mm:dd:hh:mm:ss)
type(datetime), public :: dropDatetime ! restart dropoff date/time (yyyy:mm:dd:hh:mm:ss)
type(datetime), public :: roBegDatetime ! forcing data start date/time (yyyy:mm:dd:hh:mm:ss)
type(datetime), public :: wmBegDatetime ! water management data start date/time (yyyy:mm:dd:hh:mm:ss)

! ---------- input file information -------------------------------------------------------------------

type(infileinfo), allocatable, public :: infileinfo_data(:) ! input runoff file information
type(infileinfo), allocatable, public :: infileinfo_data_wm(:) ! input water management (abstaction/injection) file information
type(infileinfo), allocatable, public :: inFileInfo_ro(:) ! input runoff/evapo/precipi file information
type(infileinfo), allocatable, public :: inFileInfo_wm(:) ! input water management (abstaction/injection) file information

! ---------- Misc. data -------------------------------------------------------------------------
character(len=strLen), public :: runMode='standalone' ! run options: standalone or cesm-coupling
Expand Down
Loading

0 comments on commit 44844e8

Please sign in to comment.