Skip to content

Commit

Permalink
Merge pull request #482 from nmizukami/cesm-coupling_routed_runoff_name
Browse files Browse the repository at this point in the history
implement generic output name for routing method specific variables
  • Loading branch information
nmizukami authored Sep 20, 2024
2 parents dae5db8 + 37c83ff commit b38a7a0
Show file tree
Hide file tree
Showing 5 changed files with 99 additions and 29 deletions.
1 change: 1 addition & 0 deletions route/build/src/public_var.f90
Original file line number Diff line number Diff line change
Expand Up @@ -96,6 +96,7 @@ MODULE public_var
character(len=strLen),public :: simEnd = '' ! date string defining the end of the simulation
character(len=strLen),public :: newFileFrequency = 'yearly' ! frequency for new output files (daily, monthly, yearly, single)
character(len=strLen),public :: outputFrequency = '1' ! output frequency (integer for multiple of simulation time step or daily, monthly or yearly)
character(len=strLen),public :: outputNameOption = 'specific' ! option for routing method dependent output names (e.g., routedRunoff) - generic or specific (default)
integer(i4b) ,public :: nOutFreq = integerMissing ! integer output frequency
character(len=10) ,public :: routOpt = '0' ! routing scheme options 0: accum runoff, 1:IRF, 2:KWT, 3:KW, 4:MC, 5:DW
integer(i4b) ,public :: doesBasinRoute = 1 ! basin routing options 0-> no, 1->IRF, otherwise error
Expand Down
40 changes: 39 additions & 1 deletion route/build/src/read_control.f90
Original file line number Diff line number Diff line change
Expand Up @@ -58,6 +58,8 @@ SUBROUTINE read_control(ctl_fname, err, message)
character(len=strLen),allocatable :: cLines(:) ! vector of character strings
character(len=strLen) :: cName,cData ! name and data from cLines(iLine)
character(len=strLen) :: cLength,cTime ! length and time units
logical(lgt) :: isGeneric ! temporal logical scalar
logical(lgt) :: onlyOneRouting ! temporal logical scalar
integer(i4b) :: ipos ! index of character string
integer(i4b) :: ibeg_name ! start index of variable name in string cLines(iLine)
integer(i4b) :: iend_name ! end index of variable name in string cLines(iLine)
Expand Down Expand Up @@ -218,6 +220,7 @@ SUBROUTINE read_control(ctl_fname, err, message)
case('<time_units>'); time_units = trim(cData) ! time units used in history file output. format should be <unit> since yyyy-mm-dd (hh:mm:ss). () can be omitted
case('<newFileFrequency>'); newFileFrequency = trim(cData) ! frequency for new history files (daily, monthly, yearly, single)
case('<outputFrequency>'); outputFrequency = trim(cData) ! output frequency (integer for multiple of simulation time step or daily, monthly or yearly)
case('<outputNameOption>'); outputNameOption = trim(cData) ! option for routing method dependent output names (e.g., routedRunoff) - generic or specific (default)
case('<histTimeStamp_offset>'); read(cData,*,iostat=io_error) histTimeStamp_offset ! time stamp offset [second] from a start of time step
case('<basRunoff>'); read(cData,*,iostat=io_error) meta_hflx(ixHFLX%basRunoff )%varFile ! default: true
case('<instRunoff>'); read(cData,*,iostat=io_error) meta_rflx(ixRFLX%instRunoff )%varFile ! default: false
Expand Down Expand Up @@ -509,7 +512,7 @@ SUBROUTINE read_control(ctl_fname, err, message)
! ---- routing methods
! Assign index for each active routing method
! Make sure to turn off write option for routines not used
if (trim(routOpt)=='0')then; write(iulog,'(a)') 'WARNING: routOpt=0 is accumRunoff option now. 12 is previous 0 now'; endif
if (trim(routOpt)=='0')then; write(iulog,'(a)') 'WARNING: routOpt=0 is accumRunoff option now.'; endif
call char2int(trim(routOpt), routeMethods, invalid_value=0)
nRoutes = size(routeMethods)
onRoute = .false.
Expand Down Expand Up @@ -585,6 +588,41 @@ SUBROUTINE read_control(ctl_fname, err, message)
end select
end do

! Control routing method dependent variable name - routedRunoff, volume, elevation etc.
! use generic name if outputNameOption is set to 'generic' AND only one routing method is activated w or w/o accumRunoff
isGeneric = trim(lower(outputNameOption))=='generic'
onlyOneRouting = ((nRoutes==2 .and. any(routeMethods==accumRunoff) .or. nRoutes==1))
if (onlyOneRouting .and. isGeneric) then
do iRoute = 1, nRoutes
select case(routeMethods(iRoute))
case(accumRunoff)
! nothing to do
case(kinematicWaveTracking)
meta_rflx(ixRFLX%KWTroutedRunoff)%varName='RoutedRunoff'
meta_rflx(ixRFLX%KWTvolume)%varName='volume'
meta_rflx(ixRFLX%KWTinflow)%varName='inflow'
case(impulseResponseFunc)
meta_rflx(ixRFLX%IRFroutedRunoff)%varName='RoutedRunoff'
meta_rflx(ixRFLX%IRFroutedRunoff)%varName='volume'
meta_rflx(ixRFLX%IRFinflow)%varName='inflow'
case(muskingumCunge)
meta_rflx(ixRFLX%MCroutedRunoff)%varName='RoutedRunoff'
meta_rflx(ixRFLX%MCvolume)%varName='volume'
meta_rflx(ixRFLX%MCinflow)%varName='inflow'
case(kinematicWave)
meta_rflx(ixRFLX%KWroutedRunoff)%varName='RoutedRunoff'
meta_rflx(ixRFLX%KWvolume)%varName='volume'
meta_rflx(ixRFLX%KWinflow)%varName='inflow'
case(diffusiveWave)
meta_rflx(ixRFLX%DWroutedRunoff)%varName='RoutedRunoff'
meta_rflx(ixRFLX%DWvolume)%varName='volume'
meta_rflx(ixRFLX%DWinflow)%varName='inflow'
case default
message=trim(message)//'routOpt may include invalid digits; expect digits 0-5 in routOpt'; err=81; return
end select
end do
end if

! basin runoff routing option
if (doesBasinRoute==0) meta_rflx(ixRFLX%instRunoff)%varFile = .false.

Expand Down
34 changes: 20 additions & 14 deletions route/build/src/write_restart_pio.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1235,85 +1235,91 @@ SUBROUTINE write_history_state(ierr, message1)

if (meta_rflx(ixRFLX%KWTroutedRunoff)%varFile) then
array_dp = hVars%discharge(index_write, idxKWT)
call write_pnetcdf(pioFileDesc, 'KWTroutedRunoff', array_dp, ioDesc_hist_rch_double, ierr, cmessage)
call write_pnetcdf(pioFileDesc, meta_rflx(ixRFLX%KWTroutedRunoff)%varName, array_dp, ioDesc_hist_rch_double, ierr, cmessage)
if(ierr/=0)then; message=trim(message)//trim(cmessage); return; endif
endif

if (meta_rflx(ixRFLX%IRFroutedRunoff)%varFile) then
array_dp = hVars%discharge(index_write, idxIRF)
call write_pnetcdf(pioFileDesc, 'IRFroutedRunoff', array_dp, ioDesc_hist_rch_double, ierr, cmessage)
call write_pnetcdf(pioFileDesc, meta_rflx(ixRFLX%IRFroutedRunoff)%varName, array_dp, ioDesc_hist_rch_double, ierr, cmessage)
if(ierr/=0)then; message=trim(message)//trim(cmessage); return; endif
endif

if (meta_rflx(ixRFLX%KWroutedRunoff)%varFile) then
array_dp = hVars%discharge(index_write, idxKW)
call write_pnetcdf(pioFileDesc, 'KWroutedRunoff', array_dp, ioDesc_hist_rch_double, ierr, cmessage)
call write_pnetcdf(pioFileDesc, meta_rflx(ixRFLX%KWroutedRunoff)%varName, array_dp, ioDesc_hist_rch_double, ierr, cmessage)
if(ierr/=0)then; message=trim(message)//trim(cmessage); return; endif
endif

if (meta_rflx(ixRFLX%MCroutedRunoff)%varFile) then
array_dp = hVars%discharge(index_write, idxMC)
call write_pnetcdf(pioFileDesc, 'MCroutedRunoff', array_dp, ioDesc_hist_rch_double, ierr, cmessage)
call write_pnetcdf(pioFileDesc, meta_rflx(ixRFLX%MCroutedRunoff)%varName, array_dp, ioDesc_hist_rch_double, ierr, cmessage)
if(ierr/=0)then; message=trim(message)//trim(cmessage); return; endif
endif

if (meta_rflx(ixRFLX%DWroutedRunoff)%varFile) then
array_dp = hVars%discharge(index_write, idxDW)
call write_pnetcdf(pioFileDesc, 'DWroutedRunoff', array_dp, ioDesc_hist_rch_double, ierr, cmessage)
call write_pnetcdf(pioFileDesc, meta_rflx(ixRFLX%DWroutedRunoff)%varName, array_dp, ioDesc_hist_rch_double, ierr, cmessage)
if(ierr/=0)then; message=trim(message)//trim(cmessage); return; endif
endif

if (meta_rflx(ixRFLX%KWTvolume)%varFile) then
array_dp = hVars%volume(index_write, idxKWT)
call write_pnetcdf(pioFileDesc, meta_rflx(ixRFLX%KWTvolume)%varName, array_dp, ioDesc_hist_rch_double, ierr, cmessage)
if(ierr/=0)then; message=trim(message)//trim(cmessage); return; endif
endif

if (meta_rflx(ixRFLX%IRFvolume)%varFile) then
array_dp = hVars%volume(index_write, idxIRF)
call write_pnetcdf(pioFileDesc, 'IRFvolume', array_dp, ioDesc_hist_rch_double, ierr, cmessage)
call write_pnetcdf(pioFileDesc, meta_rflx(ixRFLX%IRFvolume)%varName, array_dp, ioDesc_hist_rch_double, ierr, cmessage)
if(ierr/=0)then; message=trim(message)//trim(cmessage); return; endif
endif

if (meta_rflx(ixRFLX%KWvolume)%varFile) then
array_dp = hVars%volume(index_write, idxKW)
call write_pnetcdf(pioFileDesc, 'KWvolume', array_dp, ioDesc_hist_rch_double, ierr, cmessage)
call write_pnetcdf(pioFileDesc, meta_rflx(ixRFLX%KWvolume)%varName, array_dp, ioDesc_hist_rch_double, ierr, cmessage)
if(ierr/=0)then; message=trim(message)//trim(cmessage); return; endif
endif

if (meta_rflx(ixRFLX%MCvolume)%varFile) then
array_dp = hVars%volume(index_write, idxMC)
call write_pnetcdf(pioFileDesc, 'MCvolume', array_dp, ioDesc_hist_rch_double, ierr, cmessage)
call write_pnetcdf(pioFileDesc, meta_rflx(ixRFLX%MCvolume)%varName, array_dp, ioDesc_hist_rch_double, ierr, cmessage)
if(ierr/=0)then; message=trim(message)//trim(cmessage); return; endif
endif

if (meta_rflx(ixRFLX%DWvolume)%varFile) then
array_dp = hVars%volume(index_write, idxDW)
call write_pnetcdf(pioFileDesc, 'DWvolume', array_dp, ioDesc_hist_rch_double, ierr, cmessage)
call write_pnetcdf(pioFileDesc, meta_rflx(ixRFLX%DWvolume)%varName, array_dp, ioDesc_hist_rch_double, ierr, cmessage)
if(ierr/=0)then; message=trim(message)//trim(cmessage); return; endif
endif

if (meta_rflx(ixRFLX%KWTinflow)%varFile) then
array_dp = hVars%inflow(index_write, idxKWT)
if(ierr/=0)then; message=trim(message)//trim(cmessage); return; endif
call write_pnetcdf(pioFileDesc, 'KWTinflow', array_dp, ioDesc_hist_rch_double, ierr, cmessage)
call write_pnetcdf(pioFileDesc, meta_rflx(ixRFLX%KWTinflow)%varName, array_dp, ioDesc_hist_rch_double, ierr, cmessage)
endif

if (meta_rflx(ixRFLX%IRFinflow)%varFile) then
array_dp = hVars%inflow(index_write, idxIRF)
call write_pnetcdf(pioFileDesc, 'IRFinflow', array_dp, ioDesc_hist_rch_double, ierr, cmessage)
call write_pnetcdf(pioFileDesc, meta_rflx(ixRFLX%IRFinflow)%varName, array_dp, ioDesc_hist_rch_double, ierr, cmessage)
if(ierr/=0)then; message=trim(message)//trim(cmessage); return; endif
endif

if (meta_rflx(ixRFLX%KWinflow)%varFile) then
array_dp = hVars%inflow(index_write, idxKW)
call write_pnetcdf(pioFileDesc, 'KWinflow', array_dp, ioDesc_hist_rch_double, ierr, cmessage)
call write_pnetcdf(pioFileDesc, meta_rflx(ixRFLX%KWinflow)%varName, array_dp, ioDesc_hist_rch_double, ierr, cmessage)
if(ierr/=0)then; message=trim(message)//trim(cmessage); return; endif
endif

if (meta_rflx(ixRFLX%MCinflow)%varFile) then
array_dp = hVars%inflow(index_write, idxMC)
call write_pnetcdf(pioFileDesc, 'MCinflow', array_dp, ioDesc_hist_rch_double, ierr, cmessage)
call write_pnetcdf(pioFileDesc, meta_rflx(ixRFLX%MCinflow)%varName, array_dp, ioDesc_hist_rch_double, ierr, cmessage)
if(ierr/=0)then; message=trim(message)//trim(cmessage); return; endif
endif

if (meta_rflx(ixRFLX%DWinflow)%varFile) then
array_dp = hVars%inflow(index_write, idxDW)
call write_pnetcdf(pioFileDesc, 'DWinflow', array_dp, ioDesc_hist_rch_double, ierr, cmessage)
call write_pnetcdf(pioFileDesc, meta_rflx(ixRFLX%DWinflow)%varName, array_dp, ioDesc_hist_rch_double, ierr, cmessage)
if(ierr/=0)then; message=trim(message)//trim(cmessage); return; endif
endif

Expand Down
18 changes: 11 additions & 7 deletions route/settings/SAMPLE-coupled.control
Original file line number Diff line number Diff line change
Expand Up @@ -7,15 +7,18 @@
! lines starting with <xxx> are read till "!"
! Do not inclue empty line without !
!
! Followings are example of control options. if valid variables are inserted, they are default values.
! Please see route/build/src/read_control.f90 for complete options
!
! Any control variables not in this example use default values defined in public_var.f90.
!
! ****************************************************************************************************************************
! RUN CONTROL
! --------------------------------------------
<case_name> CASE_NAME ! name of simulation
<route_opt> 1 ! option for routing schemes (only one-option allowed) 1->IRF, 2->KWT, 3-> KW, 4->MC, 5->DW
<route_opt> 5 ! option for routing schemes (only one-option allowed) 1->IRF, 2->KWT, 3-> KW, 4->MC, 5->DW
<doesBasinRoute> 1 ! basin routing options 0-> no, 1->IRF, otherwise error
<is_flux_wm> T ! switch for water abstraction/injection
<hw_drain_point> 2 ! how lateral flow is put into a headwater reach 1-> top of headwater, 2-> bottom of headwater
<fname_state_in> STATE_IN_NC ! input restart netCDF name. remove for run without any particular initial channel states
<newFileFrequency> monthly ! frequency for new output files (daily, monthly, yearly, single)
<outputFrequency> monthly ! time frequency used for temporal aggregation of output variables - numeric or daily, monthyly, or yearly
Expand Down Expand Up @@ -70,6 +73,7 @@
! NOTE: discharge and volume output options
! Routing options not chosen (see <route_opt>) will be ignored.
! ---------------------------
<outputNameOption> generic ! "generic": routing method dependet output does not include routing schem name
<basRunoff> T ! HRU average runoff depth at HRU [L/T]
<instRunoff> F ! intantaneou runoff volume from Local HRUs at reach [L3/T]
<dlayRunoff> F ! delayed runoff voluem (discharge) from local HRUsi at reach [L3/T]
Expand All @@ -79,11 +83,11 @@
<MCroutedRunoff> T ! kinematic wave routed discharge at reach [L3/T]
<KWroutedRunoff> T ! muskingum-cunge routed discharge at reach [L3/T]
<DWroutedRunoff> T ! diffusive wave routed discharge at reach [L3/T]
<KWTvolume> F ! kinematic wave tracking volume at the end of time step at reach [L3]
<IRFvolume> F ! impulse response function volume at the end of time step at reach [L3]
<KWvolume> F ! Euler kinematic wave volume at the end of time step at reach [L3]
<MCvolume> F ! muskingum-cunge volume at the end of time step at reach [L3]
<DWvolume> F ! diffusive wave volume at the end of time step at reach [L3]
<KWTvolume> T ! kinematic wave tracking volume at the end of time step at reach [L3]
<IRFvolume> T ! impulse response function volume at the end of time step at reach [L3]
<KWvolume> T ! Euler kinematic wave volume at the end of time step at reach [L3]
<MCvolume> T ! muskingum-cunge volume at the end of time step at reach [L3]
<DWvolume> T ! diffusive wave volume at the end of time step at reach [L3]
! ****************************************************************************************************************************
! cesm-coupler: negative flow (qgwl and excess irrigation demand) handling option
! ---------------------------
Expand Down
Loading

0 comments on commit b38a7a0

Please sign in to comment.