Commit 0c117fd7 authored by Delaigue Olivier's avatar Delaigue Olivier
Browse files

v1.2.11.2 UPDATE: RunModel_CemaNeige* funs do not present anymore the IsHyst...

v1.2.11.2 UPDATE: RunModel_CemaNeige* funs do not present anymore the IsHyst argument (now in CreatRunOptions and CreatCalibOptions) #5252
Showing with 102 additions and 114 deletions
+102 -114
Package: airGR
Type: Package
Title: Suite of GR Hydrological Models for Precipitation-Runoff Modelling
Version: 1.2.11.1
Version: 1.2.11.2
Date: 2019-03-22
Authors@R: c(
person("Laurent", "Coron", role = c("aut", "trl"), comment = c(ORCID = "0000-0002-1503-6204")),
......
......@@ -13,7 +13,7 @@ output:
### 1.2.11.1 Release Notes (2019-03-22)
### 1.2.11.2 Release Notes (2019-03-22)
......@@ -33,8 +33,6 @@ output:
- Added <code>TransfoParam_CemaNeigeHyst()</code> function in order to take into account transformation of the parameters of the CemaNeige module when the hysteresis is used.
- <code>RunModel_CemaNeige&#42;()</code> functions now presents an <code>IsHyst</code> argument to give the possibility to use the hysteresis with CemaNeige.
- <code>CreateInputsCrit()</code> now can prepare an <code>InputsCrit</code> object in order to compute a single criterion (<code>Single</code> class), multiple criteria (<code>Multi</code> class) with the <code>ErrorCrit()</code> function. So it is now possible to set the following arguments as atomic (as before) or as list: <code>FUN_CRIT</code>, <code>obs</code>, <code>BoolCrit</code>, <code>transfo</code>, <code>weights</code>. If the list format is chosen, all the lists must have the same length.
- <code>CreateInputsCrit()</code> now presents a <code>varObs</code> argument in order to allow to prepare an <code>InputsCrit</code> object in order run a criterion on other variable than observed discharges with the <code>ErrorCrit()</code> function (e.g. SCA, SWE).
......
RunModel_CemaNeige <- function(InputsModel, RunOptions, Param, IsHyst = FALSE) {
## Arguments_check
if (!is.logical(IsHyst) | length(IsHyst) != 1L) {
stop("'IsHyst' must be a 'logical' of length 1")
}
## Initialization of variables
NParam <- ifelse(IsHyst, 4L, 2L)
IsHyst <- inherits(RunOptions, "hysteresis")
NParam <- ifelse(test = IsHyst, yes = 4L, no = 2L)
NStates <- 4L
FortranOutputsCemaNeige <- .FortranOutputs(GR = NULL, isCN = TRUE)$CN
......
RunModel_CemaNeigeGR4J <- function(InputsModel,RunOptions,Param, IsHyst = FALSE){
RunModel_CemaNeigeGR4J <- function(InputsModel,RunOptions,Param){
## Arguments_check
if (!is.logical(IsHyst) | length(IsHyst) != 1L) {
stop("'IsHyst' must be a 'logical' of length 1")
}
NParam <- ifelse(IsHyst, 8L, 6L)
## Initialization of variables
IsHyst <- inherits(RunOptions, "hysteresis")
NParam <- ifelse(test = IsHyst, yes = 8L, no = 6L)
NStates <- 4L
FortranOutputs <- .FortranOutputs(GR = "GR4J", isCN = TRUE)
......@@ -64,21 +61,21 @@ RunModel_CemaNeigeGR4J <- function(InputsModel,RunOptions,Param, IsHyst = FALSE)
StateStartCemaNeige <- RunOptions$IniStates[(7+20+40) + c(iLayer, iLayer+NLayers)]
RESULTS <- .Fortran("frun_CemaNeige",PACKAGE="airGR",
##inputs
LInputs=LInputSeries, ### length of input and output series
InputsPrecip=InputsModel$LayerPrecip[[iLayer]][IndPeriod1], ### input series of total precipitation [mm/d]
InputsFracSolidPrecip=InputsModel$LayerFracSolidPrecip[[iLayer]][IndPeriod1], ### input series of fraction of solid precipitation [0-1]
InputsTemp=InputsModel$LayerTemp[[iLayer]][IndPeriod1], ### input series of air mean temperature [degC]
MeanAnSolidPrecip=RunOptions$MeanAnSolidPrecip[iLayer], ### value of annual mean solid precip [mm/y]
NParam=as.integer(NParam), ### number of model parameter = 2
Param=as.double(ParamCemaNeige), ### parameter set
NStates=as.integer(NStates), ### number of state variables used for model initialising = 2
StateStart=StateStartCemaNeige, ### state variables used when the model run starts
IsHyst = as.integer(IsHyst), ### use of hysteresis
NOutputs=as.integer(length(IndOutputsCemaNeige)), ### number of output series
IndOutputs=IndOutputsCemaNeige, ### indices of output series
LInputs=LInputSeries, ### length of input and output series
InputsPrecip=InputsModel$LayerPrecip[[iLayer]][IndPeriod1], ### input series of total precipitation [mm/d]
InputsFracSolidPrecip=InputsModel$LayerFracSolidPrecip[[iLayer]][IndPeriod1], ### input series of fraction of solid precipitation [0-1]
InputsTemp=InputsModel$LayerTemp[[iLayer]][IndPeriod1], ### input series of air mean temperature [degC]
MeanAnSolidPrecip=RunOptions$MeanAnSolidPrecip[iLayer], ### value of annual mean solid precip [mm/y]
NParam=as.integer(NParam), ### number of model parameter = 2
Param=as.double(ParamCemaNeige), ### parameter set
NStates=as.integer(NStates), ### number of state variables used for model initialising = 2
StateStart=StateStartCemaNeige, ### state variables used when the model run starts
IsHyst = as.integer(IsHyst), ### use of hysteresis
NOutputs=as.integer(length(IndOutputsCemaNeige)), ### number of output series
IndOutputs=IndOutputsCemaNeige, ### indices of output series
##outputs
Outputs=matrix(as.double(-999.999),nrow=LInputSeries,ncol=length(IndOutputsCemaNeige)), ### output series [mm]
StateEnd=rep(as.double(-999.999),as.integer(NStates)) ### state variables at the end of the model run (reservoir levels [mm] and HU)
Outputs=matrix(as.double(-999.999),nrow=LInputSeries,ncol=length(IndOutputsCemaNeige)), ### output series [mm]
StateEnd=rep(as.double(-999.999),as.integer(NStates)) ### state variables at the end of the model run (reservoir levels [mm] and HU)
)
RESULTS$Outputs[ round(RESULTS$Outputs ,3)==(-999.999)] <- NA;
RESULTS$StateEnd[round(RESULTS$StateEnd,3)==(-999.999)] <- NA;
......@@ -113,18 +110,18 @@ RunModel_CemaNeigeGR4J <- function(InputsModel,RunOptions,Param, IsHyst = FALSE)
##Call_fortan
RESULTS <- .Fortran("frun_GR4J",PACKAGE="airGR",
##inputs
LInputs=LInputSeries, ### length of input and output series
InputsPrecip=CatchMeltAndPliq, ### input series of total precipitation [mm/d]
InputsPE=InputsModel$PotEvap[IndPeriod1], ### input series potential evapotranspiration [mm/d]
NParam=NParamMod, ### number of model parameter
Param=ParamMod, ### parameter set
NStates=NStatesMod, ### number of state variables used for model initialising
LInputs=LInputSeries, ### length of input and output series
InputsPrecip=CatchMeltAndPliq, ### input series of total precipitation [mm/d]
InputsPE=InputsModel$PotEvap[IndPeriod1], ### input series potential evapotranspiration [mm/d]
NParam=NParamMod, ### number of model parameter
Param=ParamMod, ### parameter set
NStates=NStatesMod, ### number of state variables used for model initialising
StateStart=RunOptions$IniStates[1:NStatesMod], ### state variables used when the model run starts
NOutputs=as.integer(length(IndOutputsMod)), ### number of output series
IndOutputs=IndOutputsMod, ### indices of output series
NOutputs=as.integer(length(IndOutputsMod)), ### number of output series
IndOutputs=IndOutputsMod, ### indices of output series
##outputs
Outputs=matrix(as.double(-999.999),nrow=LInputSeries,ncol=length(IndOutputsMod)), ### output series [mm]
StateEnd=rep(as.double(-999.999),NStatesMod) ### state variables at the end of the model run
Outputs=matrix(as.double(-999.999),nrow=LInputSeries,ncol=length(IndOutputsMod)), ### output series [mm]
StateEnd=rep(as.double(-999.999),NStatesMod) ### state variables at the end of the model run
)
RESULTS$Outputs[ round(RESULTS$Outputs ,3)==(-999.999)] <- NA;
RESULTS$StateEnd[round(RESULTS$StateEnd,3)==(-999.999)] <- NA;
......@@ -170,6 +167,7 @@ RunModel_CemaNeigeGR4J <- function(InputsModel,RunOptions,Param, IsHyst = FALSE)
##End
rm(RESULTS);
class(OutputsModel) <- c("OutputsModel","daily","GR","CemaNeige");
if(IsHyst) {
class(OutputsModel) <- c(class(OutputsModel), "hysteresis")
......
RunModel_CemaNeigeGR5J <- function(InputsModel,RunOptions,Param, IsHyst = FALSE){
RunModel_CemaNeigeGR5J <- function(InputsModel,RunOptions,Param){
## Arguments_check
if (!is.logical(IsHyst) | length(IsHyst) != 1L) {
stop("'IsHyst' must be a 'logical' of length 1")
}
NParam <- ifelse(IsHyst, 9L, 7L)
IsHyst <- inherits(RunOptions, "hysteresis")
NParam <- ifelse(test = IsHyst, yes = 9L, no = 7L)
NStates <- 4L
FortranOutputs <- .FortranOutputs(GR = "GR5J", isCN = TRUE)
......@@ -63,21 +59,21 @@ RunModel_CemaNeigeGR5J <- function(InputsModel,RunOptions,Param, IsHyst = FALSE)
StateStartCemaNeige <- RunOptions$IniStates[(7+20+40) + c(iLayer, iLayer+NLayers)]
RESULTS <- .Fortran("frun_CemaNeige",PACKAGE="airGR",
##inputs
LInputs=LInputSeries, ### length of input and output series
InputsPrecip=InputsModel$LayerPrecip[[iLayer]][IndPeriod1], ### input series of total precipitation [mm/d]
InputsFracSolidPrecip=InputsModel$LayerFracSolidPrecip[[iLayer]][IndPeriod1], ### input series of fraction of solid precipitation [0-1]
InputsTemp=InputsModel$LayerTemp[[iLayer]][IndPeriod1], ### input series of air mean temperature [degC]
MeanAnSolidPrecip=RunOptions$MeanAnSolidPrecip[iLayer], ### value of annual mean solid precip [mm/y]
NParam=as.integer(NParam), ### number of model parameter = 2
Param=as.double(ParamCemaNeige), ### parameter set
NStates=as.integer(NStates), ### number of state variables used for model initialising = 2
StateStart=StateStartCemaNeige, ### state variables used when the model run starts
IsHyst = as.integer(IsHyst), ### use of hysteresis
NOutputs=as.integer(length(IndOutputsCemaNeige)), ### number of output series
IndOutputs=IndOutputsCemaNeige, ### indices of output series
LInputs=LInputSeries, ### length of input and output series
InputsPrecip=InputsModel$LayerPrecip[[iLayer]][IndPeriod1], ### input series of total precipitation [mm/d]
InputsFracSolidPrecip=InputsModel$LayerFracSolidPrecip[[iLayer]][IndPeriod1], ### input series of fraction of solid precipitation [0-1]
InputsTemp=InputsModel$LayerTemp[[iLayer]][IndPeriod1], ### input series of air mean temperature [degC]
MeanAnSolidPrecip=RunOptions$MeanAnSolidPrecip[iLayer], ### value of annual mean solid precip [mm/y]
NParam=as.integer(NParam), ### number of model parameter = 2
Param=as.double(ParamCemaNeige), ### parameter set
NStates=as.integer(NStates), ### number of state variables used for model initialising = 2
StateStart=StateStartCemaNeige, ### state variables used when the model run starts
IsHyst = as.integer(IsHyst), ### use of hysteresis
NOutputs=as.integer(length(IndOutputsCemaNeige)), ### number of output series
IndOutputs=IndOutputsCemaNeige, ### indices of output series
##outputs
Outputs=matrix(as.double(-999.999),nrow=LInputSeries,ncol=length(IndOutputsCemaNeige)), ### output series [mm]
StateEnd=rep(as.double(-999.999),as.integer(NStates)) ### state variables at the end of the model run (reservoir levels [mm] and HU)
Outputs=matrix(as.double(-999.999),nrow=LInputSeries,ncol=length(IndOutputsCemaNeige)), ### output series [mm]
StateEnd=rep(as.double(-999.999),as.integer(NStates)) ### state variables at the end of the model run (reservoir levels [mm] and HU)
)
RESULTS$Outputs[ round(RESULTS$Outputs ,3)==(-999.999)] <- NA;
RESULTS$StateEnd[round(RESULTS$StateEnd,3)==(-999.999)] <- NA;
......@@ -112,18 +108,18 @@ RunModel_CemaNeigeGR5J <- function(InputsModel,RunOptions,Param, IsHyst = FALSE)
##Call_fortan
RESULTS <- .Fortran("frun_GR5J",PACKAGE="airGR",
##inputs
LInputs=LInputSeries, ### length of input and output series
InputsPrecip=CatchMeltAndPliq, ### input series of total precipitation [mm/d]
InputsPE=InputsModel$PotEvap[IndPeriod1], ### input series potential evapotranspiration [mm/d]
NParam=NParamMod, ### number of model parameter
Param=ParamMod, ### parameter set
NStates=NStatesMod, ### number of state variables used for model initialising
LInputs=LInputSeries, ### length of input and output series
InputsPrecip=CatchMeltAndPliq, ### input series of total precipitation [mm/d]
InputsPE=InputsModel$PotEvap[IndPeriod1], ### input series potential evapotranspiration [mm/d]
NParam=NParamMod, ### number of model parameter
Param=ParamMod, ### parameter set
NStates=NStatesMod, ### number of state variables used for model initialising
StateStart=RunOptions$IniStates[1:NStatesMod], ### state variables used when the model run starts
NOutputs=as.integer(length(IndOutputsMod)), ### number of output series
IndOutputs=IndOutputsMod, ### indices of output series
NOutputs=as.integer(length(IndOutputsMod)), ### number of output series
IndOutputs=IndOutputsMod, ### indices of output series
##outputs
Outputs=matrix(as.double(-999.999),nrow=LInputSeries,ncol=length(IndOutputsMod)), ### output series [mm]
StateEnd=rep(as.double(-999.999),NStatesMod) ### state variables at the end of the model run
Outputs=matrix(as.double(-999.999),nrow=LInputSeries,ncol=length(IndOutputsMod)), ### output series [mm]
StateEnd=rep(as.double(-999.999),NStatesMod) ### state variables at the end of the model run
)
RESULTS$Outputs[ round(RESULTS$Outputs ,3)==(-999.999)] <- NA;
RESULTS$StateEnd[round(RESULTS$StateEnd,3)==(-999.999)] <- NA;
......
RunModel_CemaNeigeGR6J <- function(InputsModel,RunOptions,Param, IsHyst = FALSE){
RunModel_CemaNeigeGR6J <- function(InputsModel,RunOptions,Param){
## Arguments_check
if (!is.logical(IsHyst) | length(IsHyst) != 1L) {
stop("'IsHyst' must be a 'logical' of length 1")
}
NParam <- ifelse(IsHyst, 10L, 8L)
isHyst <- inherits(RunOptions, "hysteresis")
NParam <- ifelse(test = IsHyst, yes = 10L, no = 8L)
NStates <- 4L
FortranOutputs <- .FortranOutputs(GR = "GR6J", isCN = TRUE)
......@@ -72,16 +68,16 @@ RunModel_CemaNeigeGR6J <- function(InputsModel,RunOptions,Param, IsHyst = FALSE)
InputsFracSolidPrecip=InputsModel$LayerFracSolidPrecip[[iLayer]][IndPeriod1], ### input series of fraction of solid precipitation [0-1]
InputsTemp=InputsModel$LayerTemp[[iLayer]][IndPeriod1], ### input series of air mean temperature [degC]
MeanAnSolidPrecip=RunOptions$MeanAnSolidPrecip[iLayer], ### value of annual mean solid precip [mm/y]
NParam=as.integer(NParam), ### number of model parameter = 2
Param=as.double(ParamCemaNeige), ### parameter set
NStates=as.integer(NStates), ### number of state variables used for model initialising = 2
NParam=as.integer(NParam), ### number of model parameter = 2
Param=as.double(ParamCemaNeige), ### parameter set
NStates=as.integer(NStates), ### number of state variables used for model initialising = 2
StateStart=StateStartCemaNeige, ### state variables used when the model run starts
IsHyst = as.integer(IsHyst), ### use of hysteresis
IsHyst = as.integer(IsHyst), ### use of hysteresis
NOutputs=as.integer(length(IndOutputsCemaNeige)), ### number of output series
IndOutputs=IndOutputsCemaNeige, ### indices of output series
##outputs
Outputs=matrix(as.double(-999.999),nrow=LInputSeries,ncol=length(IndOutputsCemaNeige)), ### output series [mm]
StateEnd=rep(as.double(-999.999),as.integer(NStates)) ### state variables at the end of the model run (reservoir levels [mm] and HU)
StateEnd=rep(as.double(-999.999),as.integer(NStates)) ### state variables at the end of the model run (reservoir levels [mm] and HU)
)
RESULTS$Outputs[ round(RESULTS$Outputs ,3)==(-999.999)] <- NA;
RESULTS$StateEnd[round(RESULTS$StateEnd,3)==(-999.999)] <- NA;
......@@ -117,18 +113,18 @@ RunModel_CemaNeigeGR6J <- function(InputsModel,RunOptions,Param, IsHyst = FALSE)
##Call_fortan
RESULTS <- .Fortran("frun_GR6J",PACKAGE="airGR",
##inputs
LInputs=LInputSeries, ### length of input and output series
InputsPrecip=CatchMeltAndPliq, ### input series of total precipitation [mm/d]
InputsPE=InputsModel$PotEvap[IndPeriod1], ### input series potential evapotranspiration [mm/d]
NParam=NParamMod, ### number of model parameter
Param=ParamMod, ### parameter set
NStates=NStatesMod, ### number of state variables used for model initialising
LInputs=LInputSeries, ### length of input and output series
InputsPrecip=CatchMeltAndPliq, ### input series of total precipitation [mm/d]
InputsPE=InputsModel$PotEvap[IndPeriod1], ### input series potential evapotranspiration [mm/d]
NParam=NParamMod, ### number of model parameter
Param=ParamMod, ### parameter set
NStates=NStatesMod, ### number of state variables used for model initialising
StateStart=RunOptions$IniStates[1:NStatesMod], ### state variables used when the model run starts
NOutputs=as.integer(length(IndOutputsMod)), ### number of output series
IndOutputs=IndOutputsMod, ### indices of output series
NOutputs=as.integer(length(IndOutputsMod)), ### number of output series
IndOutputs=IndOutputsMod, ### indices of output series
##outputs
Outputs=matrix(as.double(-999.999),nrow=LInputSeries,ncol=length(IndOutputsMod)), ### output series [mm]
StateEnd=rep(as.double(-999.999),NStatesMod) ### state variables at the end of the model run
Outputs=matrix(as.double(-999.999),nrow=LInputSeries,ncol=length(IndOutputsMod)), ### output series [mm]
StateEnd=rep(as.double(-999.999),NStatesMod) ### state variables at the end of the model run
)
RESULTS$Outputs[ round(RESULTS$Outputs ,3)==(-999.999)] <- NA;
RESULTS$StateEnd[round(RESULTS$StateEnd,3)==(-999.999)] <- NA;
......
......@@ -9,7 +9,7 @@
\usage{
RunModel_CemaNeige(InputsModel, RunOptions, Param, IsHyst = FALSE)
RunModel_CemaNeige(InputsModel, RunOptions, Param)
}
......@@ -25,8 +25,6 @@ CemaNeige X2 \tab degree-day melt coefficient [mm/°C/d]
CemaNeige X3 \tab (optional) accumulation threshold [mm] (needed if \code{IsHyst = TRUE}) \cr
CemaNeige X4 \tab (optional) percentage (between 0 and 1) of annual snowfall defining the melt threshold [-] (needed if \code{IsHyst = TRUE}) \cr
}}
\item{IsHyst}{[boolean] boolean indicating if the hysteresis version of CemaNeige is used. See details}
}
......@@ -58,7 +56,7 @@ Function which performs a single run for the CemaNeige daily snow module.
\details{
The use of the \code{IsHyst} argument is explained in \code{\link{RunModel_CemaNeigeGR4J}}. \cr
The choice of the CemaNeige version is explained in \code{\link{CreateRunOptions}}. \cr
For further details on the model, see the references section. \cr
For further details on the argument structures and initialisation options, see \code{\link{CreateRunOptions}}.
}
......@@ -94,9 +92,12 @@ plot(OutputsModel)
## simulation with the Linear Hysteresis
## preparation of the RunOptions object
RunOptions <- CreateRunOptions(FUN_MOD = RunModel_CemaNeige, InputsModel = InputsModel,
IndPeriod_Run = Ind_Run, IsHyst = TRUE)
Param <- c(0.962, 2.249, 100, 0.4)
OutputsModel <- RunModel_CemaNeige(InputsModel = InputsModel,
RunOptions = RunOptions, Param = Param, IsHyst = TRUE)
RunOptions = RunOptions, Param = Param)
## results preview
plot(OutputsModel)
......
......@@ -9,7 +9,7 @@
\usage{
RunModel_CemaNeigeGR4J(InputsModel, RunOptions, Param, IsHyst = FALSE)
RunModel_CemaNeigeGR4J(InputsModel, RunOptions, Param)
}
......@@ -29,8 +29,6 @@ CemaNeige X2 \tab degree-day melt coefficient [mm/°C/d]
CemaNeige X3 \tab (optional) accumulation threshold [mm] (needed if \code{IsHyst = TRUE}) \cr
CemaNeige X4 \tab (optional) percentage (between 0 and 1) of annual snowfall defining the melt threshold [-] (needed if \code{IsHyst = TRUE}) \cr
}}
\item{IsHyst}{[boolean] boolean indicating if the hysteresis version of CemaNeige is used. See details}
}
......@@ -80,8 +78,7 @@ Function which performs a single run for the CemaNeige-GR4J daily lumped model o
\details{
If \code{IsHyst = FALSE}, the original CemaNeige version from Valéry et al. (2014) is used. \cr
If \code{IsHyst = TRUE}, the CemaNeige version from Riboust et al. (2019) is used. Compared to the original version, this version of CemaNeige needs two more parameters and it includes a representation of the hysteretic relationship between the Snow Cover Area (SCA) and the Snow Water Equivalent (SWE) in the catchment. The hysteresis included in airGR is the Modified Linear hysteresis (LH*); it is represented on panel b) of Fig. 3 in Riboust et al. (2019). Riboust et al. (2019) advise to use the LH* version of CemaNeige with parameters calibrated using an objective function combining 75 \% of KGE calculated on discharge simulated from a rainfall-runoff model compared to observed discharge and 5 \% of KGE calculated on SCA on 5 CemaNeige elevation bands compared to satellite (e.g. MODIS) SCA (see Eq. (18), Table 3 and Fig. 6). Riboust et al. (2019)'s tests were realized with GR4J as the chosen rainfall-runoff model. \cr \cr
The choice of the CemaNeige version is explained in \code{\link{CreateRunOptions}}. \cr
For further details on the model, see the references section. \cr
For further details on the argument structures and initialisation options, see \code{\link{CreateRunOptions}}.
}
......@@ -122,9 +119,12 @@ OutputsCrit <- ErrorCrit_NSE(InputsCrit = InputsCrit, OutputsModel = OutputsMode
## simulation with the Linear Hysteresis
## preparation of the RunOptions object
RunOptions <- CreateRunOptions(FUN_MOD = RunModel_CemaNeigeGR4J, InputsModel = InputsModel,
IndPeriod_Run = Ind_Run, IsHyst = TRUE)
Param <- c(408.774, 2.646, 131.264, 1.174, 0.962, 2.249, 100, 0.4)
OutputsModel <- RunModel_CemaNeigeGR4J(InputsModel = InputsModel,
RunOptions = RunOptions, Param = Param, IsHyst = TRUE)
RunOptions = RunOptions, Param = Param)
## results preview
plot(OutputsModel, Qobs = BasinObs$Qmm[Ind_Run])
......
......@@ -9,7 +9,7 @@
\usage{
RunModel_CemaNeigeGR5J(InputsModel, RunOptions, Param, IsHyst = FALSE)
RunModel_CemaNeigeGR5J(InputsModel, RunOptions, Param)
}
......@@ -30,7 +30,6 @@ CemaNeige X2 \tab degree-day melt coefficient [mm/°C/d]
CemaNeige X3 \tab (optional) accumulation threshold [mm] (needed if \code{IsHyst = TRUE}) \cr
CemaNeige X4 \tab (optional) percentage (between 0 and 1) of annual snowfall defining the melt threshold [-] (needed if \code{IsHyst = TRUE}) \cr
}}
\item{IsHyst}{[boolean] boolean indicating if the hysteresis version of CemaNeige is used. See details}
}
......@@ -80,7 +79,7 @@ Function which performs a single run for the CemaNeige-GR5J daily lumped model.
\details{
The use of the \code{IsHyst} argument is explained in \code{\link{RunModel_CemaNeigeGR4J}}. \cr
The choice of the CemaNeige version is explained in \code{\link{CreateRunOptions}}. \cr
For further details on the model, see the references section. \cr
For further details on the argument structures and initialisation options, see \code{\link{CreateRunOptions}}.
}
......@@ -121,9 +120,12 @@ OutputsCrit <- ErrorCrit_NSE(InputsCrit = InputsCrit, OutputsModel = OutputsMode
## simulation with the Linear Hysteresis
## preparation of the RunOptions object
RunOptions <- CreateRunOptions(FUN_MOD = RunModel_CemaNeigeGR5J, InputsModel = InputsModel,
IndPeriod_Run = Ind_Run, IsHyst = TRUE)
Param <- c(179.139, -0.100, 203.815, 1.174, 2.478, 0.977, 2.774, 100, 0.4)
OutputsModel <- RunModel_CemaNeigeGR5J(InputsModel = InputsModel,
RunOptions = RunOptions, Param = Param, IsHyst = TRUE)
RunOptions = RunOptions, Param = Param)
## results preview
plot(OutputsModel, Qobs = BasinObs$Qmm[Ind_Run])
......
......@@ -9,7 +9,7 @@
\usage{
RunModel_CemaNeigeGR6J(InputsModel, RunOptions, Param, IsHyst = FALSE)
RunModel_CemaNeigeGR6J(InputsModel, RunOptions, Param)
}
......@@ -31,7 +31,6 @@ CemaNeige X2 \tab degree-day melt coefficient [mm/°C/d]
CemaNeige X3 \tab (optional) accumulation threshold [mm] (needed if \code{IsHyst = TRUE}) \cr
CemaNeige X4 \tab (optional) percentage (between 0 and 1) of annual snowfall defining the melt threshold [-] (needed if \code{IsHyst = TRUE})\cr
}}
\item{IsHyst}{[boolean] boolean indicating if the hysteresis version of CemaNeige is used. See details}
}
......@@ -83,7 +82,7 @@ Function which performs a single run for the CemaNeige-GR6J daily lumped model.
\details{
The use of the \code{IsHyst} argument is explained in \code{\link{RunModel_CemaNeigeGR4J}}. \cr
The choice of the CemaNeige version is explained in \code{\link{CreateRunOptions}}. \cr
For further details on the model, see the references section. \cr
For further details on the argument structures and initialisation options, see \code{\link{CreateRunOptions}}.
}
......@@ -126,8 +125,11 @@ OutputsCrit <- ErrorCrit_NSE(InputsCrit = InputsCrit, OutputsModel = OutputsMode
## simulation with the Linear Hysteresis
Param <- c(116.482, 0.500, 72.733, 1.224, 0.278, 30.333, 0.977, 2.774, 100, 0.4)
## preparation of the RunOptions object
RunOptions <- CreateRunOptions(FUN_MOD = RunModel_CemaNeigeGR6J, InputsModel = InputsModel,
IndPeriod_Run = Ind_Run, IsHyst = TRUE)
OutputsModel <- RunModel_CemaNeigeGR6J(InputsModel = InputsModel,
RunOptions = RunOptions, Param = Param, IsHyst = TRUE)
RunOptions = RunOptions, Param = Param)
## results preview
plot(OutputsModel, Qobs = BasinObs$Qmm[Ind_Run])
......
Supports Markdown
0% or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment