From d5943d287ae04df4e827b379e81b3cc1fa39808c Mon Sep 17 00:00:00 2001 From: Dorchies David <david.dorchies@inrae.fr> Date: Sun, 12 Dec 2021 14:02:46 +0100 Subject: [PATCH] feat: seemless integration of airGR into airGRiwrm - import airGR with "Depends" - remove all library(airGR) and airGR::FUN Closes #63 --- .Rbuildignore | 1 + DESCRIPTION | 6 +- NAMESPACE | 4 + R/Calibration.GRiwrmInputsModel.R | 1 + R/Calibration.InputsModel.R | 6 +- R/CreateCalibOptions.GRiwrmInputsModel.R | 8 +- R/CreateCalibOptions.InputsModel.R | 10 --- R/CreateCalibOptions.R | 43 +++++++++- R/CreateGRiwrm.R | 23 +---- R/CreateInputsCrit.GRiwrmInputsModel.R | 3 +- R/CreateInputsModel.GRiwrm.R | 42 +--------- R/CreateInputsModel.R | 10 +++ R/CreateInputsModel.default.R | 12 --- R/CreateRunOptions.GRiwrmInputsModel.R | 6 +- R/CreateRunOptions.InputsModel.R | 8 -- R/CreateRunOptions.R | 35 +++++++- R/CreateSupervisor.R | 1 - R/RunModel.GR.R | 4 +- R/RunModel.GRiwrmInputsModel.R | 65 ++++++++++----- man-roxygen/param_x.R | 2 + man/CreateCalibOptions.Rd | 18 ++-- man/CreateGRiwrm.Rd | 73 ++++++++++++++-- man/CreateInputsCrit.Rd | 2 +- man/CreateInputsModel.GRiwrm.Rd | 66 ++++++++++++--- man/CreateInputsModel.Rd | 3 + man/CreateInputsModel.default.Rd | 16 ---- man/CreateRunOptions.Rd | 83 +++++++++++++------ man/CreateSupervisor.Rd | 1 - man/RunModel.GR.Rd | 43 +--------- man/RunModel.GRiwrmInputsModel.Rd | 65 ++++++++++----- man/plot.GRiwrmOutputsModel.Rd | 65 ++++++++++----- tests/testthat/helper_RunModel.R | 2 +- tests/testthat/helper_cemaneige.R | 2 - tests/testthat/test-Calibration.R | 40 ++++++++- tests/testthat/test-CreateCalibOptions.R | 6 ++ tests/testthat/test-CreateInputsCrit.R | 31 +++++++ tests/testthat/test-CreateInputsModel.R | 21 ++++- tests/testthat/test-CreateRunOptions.R | 52 ++++++++++++ tests/testthat/test-RunModel.R | 28 ++++--- vignettes/V02_Calibration_SD_model.Rmd | 4 +- vignettes/V03_Open-loop_influenced_flow.Rmd | 2 +- .../V04_Closed-loop_regulated_withdrawal.Rmd | 2 +- vignettes/seinebasin/V02_First_run.Rmd | 2 +- .../seinebasin/V03_First_Calibration.Rmd | 2 +- .../V04_Open-loop_influenced_flow.Rmd | 2 +- ..._Open-loop_influenced_flow_calibration.Rmd | 4 +- ...-loop_influenced_flow_calibration_GR6J.Rmd | 4 +- .../V06_Naturalised_flow_simulation.Rmd | 2 +- 48 files changed, 615 insertions(+), 316 deletions(-) delete mode 100644 R/CreateCalibOptions.InputsModel.R delete mode 100644 R/CreateInputsModel.default.R delete mode 100644 R/CreateRunOptions.InputsModel.R create mode 100644 man-roxygen/param_x.R delete mode 100644 man/CreateInputsModel.default.Rd create mode 100644 tests/testthat/test-CreateCalibOptions.R create mode 100644 tests/testthat/test-CreateRunOptions.R diff --git a/.Rbuildignore b/.Rbuildignore index 911f877..03fd9b3 100644 --- a/.Rbuildignore +++ b/.Rbuildignore @@ -11,3 +11,4 @@ ^pkgdown ^docs ^vignettes/seinebasin$ +^man-roxygen$ diff --git a/DESCRIPTION b/DESCRIPTION index 437b90a..bb1ee74 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -16,8 +16,7 @@ Imports: dplyr, utils, grDevices, - graphics, - airGR (>= 1.6.12.9001) + graphics Suggests: knitr, rmarkdown, @@ -29,6 +28,7 @@ VignetteBuilder: knitr URL: https://airgriwrm.g-eau.fr/ BugReports: https://gitlab.irstea.fr/in-wop/airGRiwrm/-/issues/ Depends: - R (>= 2.10) + R (>= 2.10), + airGR (>= 1.6.12.9001) Remotes: url::https://gitlab.irstea.fr/HYCAR-Hydro/airgr/-/archive/dev/airgr-dev.zip diff --git a/NAMESPACE b/NAMESPACE index ac8670f..2117129 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -5,14 +5,18 @@ S3method(Calibration,InputsModel) S3method(ConvertMeteoSD,GRiwrm) S3method(ConvertMeteoSD,character) S3method(ConvertMeteoSD,matrix) +S3method(CreateCalibOptions,"function") S3method(CreateCalibOptions,GRiwrmInputsModel) S3method(CreateCalibOptions,InputsModel) +S3method(CreateCalibOptions,character) S3method(CreateInputsCrit,GRiwrmInputsModel) S3method(CreateInputsCrit,InputsModel) S3method(CreateInputsModel,GRiwrm) S3method(CreateInputsModel,default) +S3method(CreateRunOptions,"function") S3method(CreateRunOptions,GRiwrmInputsModel) S3method(CreateRunOptions,InputsModel) +S3method(CreateRunOptions,character) S3method(RunModel,GR) S3method(RunModel,GRiwrmInputsModel) S3method(RunModel,InputsModel) diff --git a/R/Calibration.GRiwrmInputsModel.R b/R/Calibration.GRiwrmInputsModel.R index af28833..1199a98 100644 --- a/R/Calibration.GRiwrmInputsModel.R +++ b/R/Calibration.GRiwrmInputsModel.R @@ -78,6 +78,7 @@ Calibration.GRiwrmInputsModel <- function(InputsModel, #' @param InputsCrit \[InputsCritLavenneFunction\] object internally created by [CreateInputsCrit.GRiwrmInputsModel] #' #' @return \[InputsCrit\] object with De Lavenne regularisation +#' @import airGR #' @noRd #' getInputsCrit_Lavenne <- function(id, OutputsModel, InputsCrit) { diff --git a/R/Calibration.InputsModel.R b/R/Calibration.InputsModel.R index e030148..1b5fba1 100644 --- a/R/Calibration.InputsModel.R +++ b/R/Calibration.InputsModel.R @@ -1,5 +1,9 @@ #' @rdname Calibration #' @export Calibration.InputsModel <- function(InputsModel, ...) { - airGR::Calibration(InputsModel, FUN_MOD = InputsModel$FUN_MOD, ...) + if (!exists("FUN_MOD") && !is.null(InputsModel$FUN_MOD)) { + airGR::Calibration(InputsModel, FUN_MOD = InputsModel$FUN_MOD, ...) + } else { + airGR::Calibration(InputsModel, ...) + } } diff --git a/R/CreateCalibOptions.GRiwrmInputsModel.R b/R/CreateCalibOptions.GRiwrmInputsModel.R index ffadd50..8abb580 100644 --- a/R/CreateCalibOptions.GRiwrmInputsModel.R +++ b/R/CreateCalibOptions.GRiwrmInputsModel.R @@ -1,13 +1,13 @@ #' @rdname CreateCalibOptions #' @export -CreateCalibOptions.GRiwrmInputsModel <- function(InputsModel, ...) { +CreateCalibOptions.GRiwrmInputsModel <- function(x, ...) { CalibOptions <- list() class(CalibOptions) <- c("GRiwrmCalibOptions", class(CalibOptions)) - for(IM in InputsModel) { - CalibOptions[[IM$id]] <- CreateCalibOptions.InputsModel( - InputsModel = IM, + for(IM in x) { + CalibOptions[[IM$id]] <- CreateCalibOptions( + IM, ... ) } diff --git a/R/CreateCalibOptions.InputsModel.R b/R/CreateCalibOptions.InputsModel.R deleted file mode 100644 index e1f139e..0000000 --- a/R/CreateCalibOptions.InputsModel.R +++ /dev/null @@ -1,10 +0,0 @@ -#' @rdname CreateCalibOptions -#' @export -CreateCalibOptions.InputsModel <- function(InputsModel, - ...) { - airGR::CreateCalibOptions( - FUN_MOD = InputsModel$FUN_MOD, - IsSD = !is.null(InputsModel$Qupstream), - ... - ) -} diff --git a/R/CreateCalibOptions.R b/R/CreateCalibOptions.R index ddef1e8..8c65ecf 100644 --- a/R/CreateCalibOptions.R +++ b/R/CreateCalibOptions.R @@ -2,7 +2,7 @@ #' #' This function can be used either for a catchment (with an \emph{InputsModel} object) or for a network (with a \emph{GRiwrmInputsModel} object) #' -#' @param InputsModel object of class \emph{InputsModel} or \emph{GRiwrmInputsModel}. See [CreateInputsModel] for details +#' @template param_x #' @param ... arguments passed to [airGR::CreateCalibOptions], see details #' #' @details See [airGR::CreateCalibOptions] documentation for a complete list of arguments. @@ -15,6 +15,43 @@ #' #' @rdname CreateCalibOptions #' @export -CreateCalibOptions <- function(InputsModel, ...) { - UseMethod("CreateCalibOptions", InputsModel) +CreateCalibOptions <- function(x, ...) { + UseMethod("CreateCalibOptions", x) +} + +#' @rdname CreateCalibOptions +#' @export +CreateCalibOptions.InputsModel <- function(x, + ...) { + if (!exists("FUN_MOD") && !is.null(x$FUN_MOD)) { + airGR::CreateCalibOptions( + FUN_MOD = x$FUN_MOD, + IsSD = !is.null(x$Qupstream), + ... + ) + } else { + airGR::CreateCalibOptions( + ... + ) + } +} + +#' @rdname CreateCalibOptions +#' @export +CreateCalibOptions.character <- function(x, + ...) { + airGR::CreateCalibOptions( + FUN_MOD = x, + ... + ) +} + +#' @rdname CreateCalibOptions +#' @export +CreateCalibOptions.function <- function(x, + ...) { + airGR::CreateCalibOptions( + FUN_MOD = x, + ... + ) } diff --git a/R/CreateGRiwrm.R b/R/CreateGRiwrm.R index 6386b07..69f704b 100644 --- a/R/CreateGRiwrm.R +++ b/R/CreateGRiwrm.R @@ -21,28 +21,7 @@ #' #' @aliases GRiwrm #' @export -#' @examples -#' ################################################################### -#' # Run the `airGR::RunModel_Lag` example in the GRiwrm fashion way # -#' ################################################################### -#' -#' # Run the airGR RunModel_Lag example for harvesting the necessary data -#' library(airGR) -#' example(RunModel_Lag) -#' # detach the package because otherwise airGR overwrites the airGRiwrm functions -#' detach("package:airGR") -#' -#' # This example is a network of 2 nodes which can be described like this: -#' db <- data.frame(id = c("Reservoir", "GaugingDown"), -#' length = c(LengthHydro, NA), -#' down = c("GaugingDown", NA), -#' area = c(NA, BasinInfo$BasinArea), -#' model = c(NA, "RunModel_GR4J"), -#' stringsAsFactors = FALSE) -#' -#' # Create GRiwrm object from the data.frame -#' griwrm <- CreateGRiwrm(db) -#' str(griwrm) +#' @inherit RunModel.GRiwrmInputsModel return examples #' CreateGRiwrm <- function(db, cols = list( diff --git a/R/CreateInputsCrit.GRiwrmInputsModel.R b/R/CreateInputsCrit.GRiwrmInputsModel.R index d91ac39..e27db7b 100644 --- a/R/CreateInputsCrit.GRiwrmInputsModel.R +++ b/R/CreateInputsCrit.GRiwrmInputsModel.R @@ -1,7 +1,8 @@ #' @rdname CreateInputsCrit +#' @import airGR #' @export CreateInputsCrit.GRiwrmInputsModel <- function(InputsModel, - FUN_CRIT = airGR::ErrorCrit_NSE, + FUN_CRIT = ErrorCrit_NSE, RunOptions, Obs, AprioriIds = NULL, diff --git a/R/CreateInputsModel.GRiwrm.R b/R/CreateInputsModel.GRiwrm.R index d780b6b..17bb6d1 100644 --- a/R/CreateInputsModel.GRiwrm.R +++ b/R/CreateInputsModel.GRiwrm.R @@ -20,47 +20,7 @@ #' #' @return A \emph{GRiwrmInputsModel} object which is a list of \emph{InputsModel} objects created by [airGR::CreateInputsModel] with one item per modelled sub-catchment. #' @export -#' @examples -#' ################################################################## -#' # Run the `airGR RunModel_Lag` example in the GRiwrm fashion way # -#' ################################################################## -#' -#' # Run the airGR RunModel_Lag example for harvesting necessary data -#' library(airGR) -#' example(RunModel_Lag) -#' # detach the package because otherwise airGR overwrites the airGRiwrm functions -#' detach("package:airGR") -#' -#' # This example is a network of 2 nodes which can be described like this: -#' db <- data.frame(id = c("Reservoir", "GaugingDown"), -#' length = c(LengthHydro, NA), -#' down = c("GaugingDown", NA), -#' area = c(NA, BasinInfo$BasinArea), -#' model = c(NA, "RunModel_GR4J"), -#' stringsAsFactors = FALSE) -#' -#' # Create GRiwrm object from the data.frame -#' griwrm <- CreateGRiwrm(db) -#' str(griwrm) -#' -#' # Formatting observations for the hydrological models -#' # Each input data should be a matrix or a data.frame with the correct id as the column name -#' Precip <- matrix(BasinObs$P, ncol = 1) -#' colnames(Precip) <- "GaugingDown" -#' PotEvap <- matrix(BasinObs$E, ncol = 1) -#' colnames(PotEvap) <- "GaugingDown" -#' -#' # Observed flows should at least contains flows that are directly injected in the model -#' Qobs = matrix(Qupstream, ncol = 1) -#' colnames(Qobs) <- "Reservoir" -#' str(Qobs) -#' -#' InputsModels <- CreateInputsModel(griwrm, -#' DatesR = BasinObs$DatesR, -#' Precip = Precip, -#' PotEvap = PotEvap, -#' Qobs = Qobs) -#' str(InputsModels) +#' @inherit RunModel.GRiwrmInputsModel return examples #' CreateInputsModel.GRiwrm <- function(x, DatesR, Precip = NULL, diff --git a/R/CreateInputsModel.R b/R/CreateInputsModel.R index 6d17dda..f034cc1 100644 --- a/R/CreateInputsModel.R +++ b/R/CreateInputsModel.R @@ -6,7 +6,17 @@ #' @param ... further arguments passed to or from other methods. #' #' @return InputsModel or GRiwrmInputsObject object +#' @rdname CreateInputsModel +#' @import airGR #' @export CreateInputsModel <- function(x, ...) { UseMethod("CreateInputsModel", x) } + +#' @rdname CreateInputsModel +#' @export +CreateInputsModel.default <- function(x, + ...) { + + airGR::CreateInputsModel(FUN_MOD = x, ...) +} diff --git a/R/CreateInputsModel.default.R b/R/CreateInputsModel.default.R deleted file mode 100644 index eaca56b..0000000 --- a/R/CreateInputsModel.default.R +++ /dev/null @@ -1,12 +0,0 @@ -#' Wrapper for [airGR::CreateInputsModel] for one sub-basin -#' -#' @param x [function] hydrological model function (e.g. [airGR::RunModel_GR4J]...) -#' @param ... arguments passed to [airGR::CreateInputsModel] -#' @import airGR -#' @export -#' -CreateInputsModel.default <- function(x, - ...) { - - airGR::CreateInputsModel(FUN_MOD = x, ...) -} diff --git a/R/CreateRunOptions.GRiwrmInputsModel.R b/R/CreateRunOptions.GRiwrmInputsModel.R index 637b58f..e7f503c 100644 --- a/R/CreateRunOptions.GRiwrmInputsModel.R +++ b/R/CreateRunOptions.GRiwrmInputsModel.R @@ -1,13 +1,13 @@ #' @param IniStates (optional) [numeric] object or [list] of [numeric] object of class \emph{IniStates}, see [airGR::CreateIniStates] for details #' @rdname CreateRunOptions #' @export -CreateRunOptions.GRiwrmInputsModel <- function(InputsModel, IniStates = NULL, ...) { +CreateRunOptions.GRiwrmInputsModel <- function(x, IniStates = NULL, ...) { RunOptions <- list() class(RunOptions) <- append(class(RunOptions), "GRiwrmRunOptions") - for(id in names(InputsModel)) { - RunOptions[[id]] <- CreateRunOptions(InputsModel = InputsModel[[id]], IniStates = IniStates[[id]], ...) + for(id in names(x)) { + RunOptions[[id]] <- CreateRunOptions(x[[id]], IniStates = IniStates[[id]], ...) } return(RunOptions) } diff --git a/R/CreateRunOptions.InputsModel.R b/R/CreateRunOptions.InputsModel.R deleted file mode 100644 index bb0f2e7..0000000 --- a/R/CreateRunOptions.InputsModel.R +++ /dev/null @@ -1,8 +0,0 @@ -#' @rdname CreateRunOptions -#' @export -CreateRunOptions.InputsModel <- function(InputsModel, ...) { - - airGR::CreateRunOptions(FUN_MOD = InputsModel$FUN_MOD, - InputsModel = InputsModel, - ...) -} diff --git a/R/CreateRunOptions.R b/R/CreateRunOptions.R index a0d4753..21d47a7 100644 --- a/R/CreateRunOptions.R +++ b/R/CreateRunOptions.R @@ -2,7 +2,7 @@ #' #' This function can be used either for a catchment (with an \emph{InputsModel} object) or for a network (with a \emph{GRiwrmInputsModel} object) #' -#' @param InputsModel object of class \emph{InputsModel} or \emph{GRiwrmInputsModel}. See [CreateInputsModel] for details +#' @template param_x #' @param ... arguments passed to [airGR::CreateRunOptions], see details #' #' @details See [airGR::CreateRunOptions] documentation for a complete list of arguments. @@ -18,6 +18,35 @@ #' @rdname CreateRunOptions #' @export #' @inherit RunModel.GRiwrmInputsModel return examples -CreateRunOptions <- function(InputsModel, ...) { - UseMethod("CreateRunOptions", InputsModel) +CreateRunOptions <- function(x, ...) { + UseMethod("CreateRunOptions", x) +} + +#' @rdname CreateRunOptions +#' @export +CreateRunOptions.InputsModel <- function(x, ...) { + if (!exists("FUN_MOD") && !is.null(x$FUN_MOD)) { + airGR::CreateRunOptions(FUN_MOD = x$FUN_MOD, + InputsModel = x, + ...) + } else { + airGR::CreateRunOptions(InputsModel = x, + ...) + } +} + +#' @rdname CreateRunOptions +#' @export +CreateRunOptions.character <- function(x, ...) { + + airGR::CreateRunOptions(FUN_MOD = x, + ...) +} + +#' @rdname CreateRunOptions +#' @export +CreateRunOptions.function <- function(x, ...) { + + airGR::CreateRunOptions(FUN_MOD = x, + ...) } diff --git a/R/CreateSupervisor.R b/R/CreateSupervisor.R index 06de63a..3a6b109 100644 --- a/R/CreateSupervisor.R +++ b/R/CreateSupervisor.R @@ -14,7 +14,6 @@ #' @examples #' data(Severn) #' nodes <- Severn$BasinsInfo[, c("gauge_id", "downstream_id", "distance_downstream", "area")] -#' nodes$distance_downstream <- nodes$distance_downstream * 1000 # Conversion km -> m #' nodes$model <- "RunModel_GR4J" #' griwrm <- CreateGRiwrm(nodes, #' list(id = "gauge_id", diff --git a/R/RunModel.GR.R b/R/RunModel.GR.R index 7f708e8..b34a7ba 100644 --- a/R/RunModel.GR.R +++ b/R/RunModel.GR.R @@ -1,9 +1,11 @@ #' Run of a rainfall-runoff model on a sub-basin #' -#' @inherit airGR::RunModel #' @param x \[object of class `InputsModel`\] `InputsModel` for [airGR::RunModel] +#' @param RunOptions \[object of class *RunOptions*\] see [airGR::CreateRunOptions] for details +#' @param Param [numeric] vector of model parameters (See details for SD lag model) #' @param ... further arguments passed to or from other methods #' +#' @inherit airGR::RunModel description details return #' @export #' RunModel.GR <- function(x, RunOptions, Param, ...) { diff --git a/R/RunModel.GRiwrmInputsModel.R b/R/RunModel.GRiwrmInputsModel.R index 0b3df93..01d7f3d 100644 --- a/R/RunModel.GRiwrmInputsModel.R +++ b/R/RunModel.GRiwrmInputsModel.R @@ -8,15 +8,36 @@ #' @return [[list] of class \emph{GRiwrmOutputsModel}] list of \emph{OutputsModel} objects (See \[airGR::RunModel]) for each node of the semi-distributed model #' @export #' @examples -#' ################################################################# -#' # Run the `airGRRunModel_Lag` example in the GRiwrm fashion way # -#' ################################################################# +#' ################################################################### +#' # Run the `airGR::RunModel_Lag` example in the GRiwrm fashion way # +#' # Simulation of a reservoir with a purpose of low-flow mitigation # +#' ################################################################### #' -#' # Run the airGR RunModel_Lag example for harvesting necessary data -#' library(airGR) -#' example(RunModel_Lag) -#' # detach the package because otherwise airGR overwrites the airGRiwrm functions -#' detach("package:airGR") +#' ## ---- preparation of the InputsModel object +#' +#' ## loading package and catchment data +#' library(airGRiwrm) +#' data(L0123001) +#' +#' ## ---- specifications of the reservoir +#' +#' ## the reservoir withdraws 1 m3/s when it's possible considering the flow observed in the basin +#' Qupstream <- matrix(-sapply(BasinObs$Qls / 1000 - 1, function(x) { +#' min(1, max(0, x, na.rm = TRUE)) +#' }), ncol = 1) +#' +#' ## except between July and September when the reservoir releases 3 m3/s for low-flow mitigation +#' month <- as.numeric(format(BasinObs$DatesR, "%m")) +#' Qupstream[month >= 7 & month <= 9] <- 3 +#' Qupstream <- Qupstream * 86400 ## Conversion in m3/day +#' +#' ## the reservoir is not an upstream subcachment: its areas is NA +#' BasinAreas <- c(NA, BasinInfo$BasinArea) +#' +#' ## delay time between the reservoir and the catchment outlet is 2 days and the distance is 150 km +#' LengthHydro <- 150 +#' ## with a delay of 2 days for 150 km, the flow velocity is 75 km per day +#' Velocity <- (LengthHydro * 1e3 / 2) / (24 * 60 * 60) ## Conversion km/day -> m/s #' #' # This example is a network of 2 nodes which can be describe like this: #' db <- data.frame(id = c("Reservoir", "GaugingDown"), @@ -37,12 +58,9 @@ #' PotEvap <- matrix(BasinObs$E, ncol = 1) #' colnames(PotEvap) <- "GaugingDown" #' -#' # Observed flows are integrated now because we mix: -#' # - flows that are directly injected in the model -#' # - flows that could be used for the calibration of the hydrological models -#' Qobs = matrix(c(Qupstream, BasinObs$Qmm), ncol = 2) -#' colnames(Qobs) <- griwrm$id -#' str(Qobs) +#' # Observed flows contain flows that are directly injected in the model +#' Qobs = matrix(Qupstream, ncol = 1) +#' colnames(Qobs) <- "Reservoir" #' #' # Creation of the GRiwrmInputsModel object (= a named list of InputsModel objects) #' InputsModels <- CreateInputsModel(griwrm, @@ -52,22 +70,27 @@ #' Qobs = Qobs) #' str(InputsModels) #' +#' ## run period selection +#' Ind_Run <- seq(which(format(BasinObs$DatesR, format = "%Y-%m-%d")=="1990-01-01"), +#' which(format(BasinObs$DatesR, format = "%Y-%m-%d")=="1999-12-31")) +#' #' # Creation of the GriwmRunOptions object -#' RunOptions2 <- CreateRunOptions(InputsModels, +#' RunOptions <- CreateRunOptions(InputsModels, #' IndPeriod_Run = Ind_Run) -#' str(RunOptions2) +#' str(RunOptions) #' #' # Parameters of the SD models should be encapsulated in a named list -#' Param2 <- list(`GaugingDown` = c(Velocity, Param)) +#' ParamGR4J <- c(X1 = 257.238, X2 = 1.012, X3 = 88.235, X4 = 2.208) +#' Param <- list(`GaugingDown` = c(Velocity, ParamGR4J)) #' #' # RunModel for the whole network #' OutputsModels <- RunModel(InputsModels, -#' RunOptions = RunOptions2, -#' Param = Param2) +#' RunOptions = RunOptions, +#' Param = Param) #' str(OutputsModels) #' -#' # Comparison between GRiwrm simulation and airGR simulation -#' plot(OutputsModels, Qobs = data.frame(`GaugingDown` = OutputsModel$Qsim)) +#' # Compare Simulation with reservoir and observation of natural flow +#' plot(OutputsModels, data.frame(GaugingDown = BasinObs$Qmm[Ind_Run])) RunModel.GRiwrmInputsModel <- function(x, RunOptions, Param, ...) { checkRunModelParameters(x, RunOptions, Param) diff --git a/man-roxygen/param_x.R b/man-roxygen/param_x.R new file mode 100644 index 0000000..0e25a80 --- /dev/null +++ b/man-roxygen/param_x.R @@ -0,0 +1,2 @@ +#' @param x [function], [character], or object of class \emph{InputsModel} runs [airGR::CreateRunOptions]for a catchment. Use object of class \emph{GRiwrmInputsModel} for a network. See [CreateInputsModel] for details +#' diff --git a/man/CreateCalibOptions.Rd b/man/CreateCalibOptions.Rd index c2a2e13..74b6eb7 100644 --- a/man/CreateCalibOptions.Rd +++ b/man/CreateCalibOptions.Rd @@ -1,20 +1,26 @@ % Generated by roxygen2: do not edit by hand % Please edit documentation in R/CreateCalibOptions.GRiwrmInputsModel.R, -% R/CreateCalibOptions.InputsModel.R, R/CreateCalibOptions.R +% R/CreateCalibOptions.R \name{CreateCalibOptions.GRiwrmInputsModel} \alias{CreateCalibOptions.GRiwrmInputsModel} -\alias{CreateCalibOptions.InputsModel} \alias{CreateCalibOptions} +\alias{CreateCalibOptions.InputsModel} +\alias{CreateCalibOptions.character} +\alias{CreateCalibOptions.function} \title{Creation of the CalibOptions object} \usage{ -\method{CreateCalibOptions}{GRiwrmInputsModel}(InputsModel, ...) +\method{CreateCalibOptions}{GRiwrmInputsModel}(x, ...) + +CreateCalibOptions(x, ...) + +\method{CreateCalibOptions}{InputsModel}(x, ...) -\method{CreateCalibOptions}{InputsModel}(InputsModel, ...) +\method{CreateCalibOptions}{character}(x, ...) -CreateCalibOptions(InputsModel, ...) +\method{CreateCalibOptions}{`function`}(x, ...) } \arguments{ -\item{InputsModel}{object of class \emph{InputsModel} or \emph{GRiwrmInputsModel}. See \link{CreateInputsModel} for details} +\item{x}{\link{function}, \link{character}, or object of class \emph{InputsModel} runs \link[airGR:CreateRunOptions]{airGR::CreateRunOptions}for a catchment. Use object of class \emph{GRiwrmInputsModel} for a network. See \link{CreateInputsModel} for details} \item{...}{arguments passed to \link[airGR:CreateCalibOptions]{airGR::CreateCalibOptions}, see details} } diff --git a/man/CreateGRiwrm.Rd b/man/CreateGRiwrm.Rd index f962ec2..ab1ad35 100644 --- a/man/CreateGRiwrm.Rd +++ b/man/CreateGRiwrm.Rd @@ -46,15 +46,36 @@ of their connections \examples{ ################################################################### # Run the `airGR::RunModel_Lag` example in the GRiwrm fashion way # +# Simulation of a reservoir with a purpose of low-flow mitigation # ################################################################### -# Run the airGR RunModel_Lag example for harvesting the necessary data -library(airGR) -example(RunModel_Lag) -# detach the package because otherwise airGR overwrites the airGRiwrm functions -detach("package:airGR") +## ---- preparation of the InputsModel object -# This example is a network of 2 nodes which can be described like this: +## loading package and catchment data +library(airGRiwrm) +data(L0123001) + +## ---- specifications of the reservoir + +## the reservoir withdraws 1 m3/s when it's possible considering the flow observed in the basin +Qupstream <- matrix(-sapply(BasinObs$Qls / 1000 - 1, function(x) { + min(1, max(0, x, na.rm = TRUE)) +}), ncol = 1) + +## except between July and September when the reservoir releases 3 m3/s for low-flow mitigation +month <- as.numeric(format(BasinObs$DatesR, "\%m")) +Qupstream[month >= 7 & month <= 9] <- 3 +Qupstream <- Qupstream * 86400 ## Conversion in m3/day + +## the reservoir is not an upstream subcachment: its areas is NA +BasinAreas <- c(NA, BasinInfo$BasinArea) + +## delay time between the reservoir and the catchment outlet is 2 days and the distance is 150 km +LengthHydro <- 150 +## with a delay of 2 days for 150 km, the flow velocity is 75 km per day +Velocity <- (LengthHydro * 1e3 / 2) / (24 * 60 * 60) ## Conversion km/day -> m/s + +# This example is a network of 2 nodes which can be describe like this: db <- data.frame(id = c("Reservoir", "GaugingDown"), length = c(LengthHydro, NA), down = c("GaugingDown", NA), @@ -66,4 +87,44 @@ db <- data.frame(id = c("Reservoir", "GaugingDown"), griwrm <- CreateGRiwrm(db) str(griwrm) +# Formatting observations for the hydrological models +# Each input data should be a matrix or a data.frame with the good id in the name of the column +Precip <- matrix(BasinObs$P, ncol = 1) +colnames(Precip) <- "GaugingDown" +PotEvap <- matrix(BasinObs$E, ncol = 1) +colnames(PotEvap) <- "GaugingDown" + +# Observed flows contain flows that are directly injected in the model +Qobs = matrix(Qupstream, ncol = 1) +colnames(Qobs) <- "Reservoir" + +# Creation of the GRiwrmInputsModel object (= a named list of InputsModel objects) +InputsModels <- CreateInputsModel(griwrm, + DatesR = BasinObs$DatesR, + Precip = Precip, + PotEvap = PotEvap, + Qobs = Qobs) +str(InputsModels) + +## run period selection +Ind_Run <- seq(which(format(BasinObs$DatesR, format = "\%Y-\%m-\%d")=="1990-01-01"), + which(format(BasinObs$DatesR, format = "\%Y-\%m-\%d")=="1999-12-31")) + +# Creation of the GriwmRunOptions object +RunOptions <- CreateRunOptions(InputsModels, + IndPeriod_Run = Ind_Run) +str(RunOptions) + +# Parameters of the SD models should be encapsulated in a named list +ParamGR4J <- c(X1 = 257.238, X2 = 1.012, X3 = 88.235, X4 = 2.208) +Param <- list(`GaugingDown` = c(Velocity, ParamGR4J)) + +# RunModel for the whole network +OutputsModels <- RunModel(InputsModels, + RunOptions = RunOptions, + Param = Param) +str(OutputsModels) + +# Compare Simulation with reservoir and observation of natural flow +plot(OutputsModels, data.frame(GaugingDown = BasinObs$Qmm[Ind_Run])) } diff --git a/man/CreateInputsCrit.Rd b/man/CreateInputsCrit.Rd index dcfdeee..3ec30d5 100644 --- a/man/CreateInputsCrit.Rd +++ b/man/CreateInputsCrit.Rd @@ -9,7 +9,7 @@ \usage{ \method{CreateInputsCrit}{GRiwrmInputsModel}( InputsModel, - FUN_CRIT = airGR::ErrorCrit_NSE, + FUN_CRIT = ErrorCrit_NSE, RunOptions, Obs, AprioriIds = NULL, diff --git a/man/CreateInputsModel.GRiwrm.Rd b/man/CreateInputsModel.GRiwrm.Rd index c442d6d..fe944a4 100644 --- a/man/CreateInputsModel.GRiwrm.Rd +++ b/man/CreateInputsModel.GRiwrm.Rd @@ -59,17 +59,38 @@ Meteorological data are needed for the nodes of the network that represent a cat See \link[airGR:CreateInputsModel]{airGR::CreateInputsModel} documentation for details concerning each input. } \examples{ -################################################################## -# Run the `airGR RunModel_Lag` example in the GRiwrm fashion way # -################################################################## +################################################################### +# Run the `airGR::RunModel_Lag` example in the GRiwrm fashion way # +# Simulation of a reservoir with a purpose of low-flow mitigation # +################################################################### -# Run the airGR RunModel_Lag example for harvesting necessary data -library(airGR) -example(RunModel_Lag) -# detach the package because otherwise airGR overwrites the airGRiwrm functions -detach("package:airGR") +## ---- preparation of the InputsModel object -# This example is a network of 2 nodes which can be described like this: +## loading package and catchment data +library(airGRiwrm) +data(L0123001) + +## ---- specifications of the reservoir + +## the reservoir withdraws 1 m3/s when it's possible considering the flow observed in the basin +Qupstream <- matrix(-sapply(BasinObs$Qls / 1000 - 1, function(x) { + min(1, max(0, x, na.rm = TRUE)) +}), ncol = 1) + +## except between July and September when the reservoir releases 3 m3/s for low-flow mitigation +month <- as.numeric(format(BasinObs$DatesR, "\%m")) +Qupstream[month >= 7 & month <= 9] <- 3 +Qupstream <- Qupstream * 86400 ## Conversion in m3/day + +## the reservoir is not an upstream subcachment: its areas is NA +BasinAreas <- c(NA, BasinInfo$BasinArea) + +## delay time between the reservoir and the catchment outlet is 2 days and the distance is 150 km +LengthHydro <- 150 +## with a delay of 2 days for 150 km, the flow velocity is 75 km per day +Velocity <- (LengthHydro * 1e3 / 2) / (24 * 60 * 60) ## Conversion km/day -> m/s + +# This example is a network of 2 nodes which can be describe like this: db <- data.frame(id = c("Reservoir", "GaugingDown"), length = c(LengthHydro, NA), down = c("GaugingDown", NA), @@ -82,17 +103,17 @@ griwrm <- CreateGRiwrm(db) str(griwrm) # Formatting observations for the hydrological models -# Each input data should be a matrix or a data.frame with the correct id as the column name +# Each input data should be a matrix or a data.frame with the good id in the name of the column Precip <- matrix(BasinObs$P, ncol = 1) colnames(Precip) <- "GaugingDown" PotEvap <- matrix(BasinObs$E, ncol = 1) colnames(PotEvap) <- "GaugingDown" -# Observed flows should at least contains flows that are directly injected in the model +# Observed flows contain flows that are directly injected in the model Qobs = matrix(Qupstream, ncol = 1) colnames(Qobs) <- "Reservoir" -str(Qobs) +# Creation of the GRiwrmInputsModel object (= a named list of InputsModel objects) InputsModels <- CreateInputsModel(griwrm, DatesR = BasinObs$DatesR, Precip = Precip, @@ -100,4 +121,25 @@ InputsModels <- CreateInputsModel(griwrm, Qobs = Qobs) str(InputsModels) +## run period selection +Ind_Run <- seq(which(format(BasinObs$DatesR, format = "\%Y-\%m-\%d")=="1990-01-01"), + which(format(BasinObs$DatesR, format = "\%Y-\%m-\%d")=="1999-12-31")) + +# Creation of the GriwmRunOptions object +RunOptions <- CreateRunOptions(InputsModels, + IndPeriod_Run = Ind_Run) +str(RunOptions) + +# Parameters of the SD models should be encapsulated in a named list +ParamGR4J <- c(X1 = 257.238, X2 = 1.012, X3 = 88.235, X4 = 2.208) +Param <- list(`GaugingDown` = c(Velocity, ParamGR4J)) + +# RunModel for the whole network +OutputsModels <- RunModel(InputsModels, + RunOptions = RunOptions, + Param = Param) +str(OutputsModels) + +# Compare Simulation with reservoir and observation of natural flow +plot(OutputsModels, data.frame(GaugingDown = BasinObs$Qmm[Ind_Run])) } diff --git a/man/CreateInputsModel.Rd b/man/CreateInputsModel.Rd index 213f986..39521c8 100644 --- a/man/CreateInputsModel.Rd +++ b/man/CreateInputsModel.Rd @@ -2,9 +2,12 @@ % Please edit documentation in R/CreateInputsModel.R \name{CreateInputsModel} \alias{CreateInputsModel} +\alias{CreateInputsModel.default} \title{Generic function for creating \code{InputsModel} object for either \strong{airGR} or \strong{airGRiwrm}} \usage{ CreateInputsModel(x, ...) + +\method{CreateInputsModel}{default}(x, ...) } \arguments{ \item{x}{First parameter determining which InputsModel object is created} diff --git a/man/CreateInputsModel.default.Rd b/man/CreateInputsModel.default.Rd deleted file mode 100644 index ea83bb7..0000000 --- a/man/CreateInputsModel.default.Rd +++ /dev/null @@ -1,16 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/CreateInputsModel.default.R -\name{CreateInputsModel.default} -\alias{CreateInputsModel.default} -\title{Wrapper for \link[airGR:CreateInputsModel]{airGR::CreateInputsModel} for one sub-basin} -\usage{ -\method{CreateInputsModel}{default}(x, ...) -} -\arguments{ -\item{x}{\link{function} hydrological model function (e.g. \link[airGR:RunModel_GR4J]{airGR::RunModel_GR4J}...)} - -\item{...}{arguments passed to \link[airGR:CreateInputsModel]{airGR::CreateInputsModel}} -} -\description{ -Wrapper for \link[airGR:CreateInputsModel]{airGR::CreateInputsModel} for one sub-basin -} diff --git a/man/CreateRunOptions.Rd b/man/CreateRunOptions.Rd index 36e6665..8f6bda1 100644 --- a/man/CreateRunOptions.Rd +++ b/man/CreateRunOptions.Rd @@ -1,20 +1,26 @@ % Generated by roxygen2: do not edit by hand % Please edit documentation in R/CreateRunOptions.GRiwrmInputsModel.R, -% R/CreateRunOptions.InputsModel.R, R/CreateRunOptions.R +% R/CreateRunOptions.R \name{CreateRunOptions.GRiwrmInputsModel} \alias{CreateRunOptions.GRiwrmInputsModel} -\alias{CreateRunOptions.InputsModel} \alias{CreateRunOptions} +\alias{CreateRunOptions.InputsModel} +\alias{CreateRunOptions.character} +\alias{CreateRunOptions.function} \title{Creation of the CalibOptions object} \usage{ -\method{CreateRunOptions}{GRiwrmInputsModel}(InputsModel, IniStates = NULL, ...) +\method{CreateRunOptions}{GRiwrmInputsModel}(x, IniStates = NULL, ...) + +CreateRunOptions(x, ...) -\method{CreateRunOptions}{InputsModel}(InputsModel, ...) +\method{CreateRunOptions}{InputsModel}(x, ...) -CreateRunOptions(InputsModel, ...) +\method{CreateRunOptions}{character}(x, ...) + +\method{CreateRunOptions}{`function`}(x, ...) } \arguments{ -\item{InputsModel}{object of class \emph{InputsModel} or \emph{GRiwrmInputsModel}. See \link{CreateInputsModel} for details} +\item{x}{\link{function}, \link{character}, or object of class \emph{InputsModel} runs \link[airGR:CreateRunOptions]{airGR::CreateRunOptions}for a catchment. Use object of class \emph{GRiwrmInputsModel} for a network. See \link{CreateInputsModel} for details} \item{IniStates}{(optional) \link{numeric} object or \link{list} of \link{numeric} object of class \emph{IniStates}, see \link[airGR:CreateIniStates]{airGR::CreateIniStates} for details} @@ -38,15 +44,36 @@ If \code{InputsModel} argument is a \emph{GRiwrmInputsModel} object, \code{IniSt With a \emph{GRiwrmInputsModel} object, all arguments are applied on each sub-catchments of the network. } \examples{ -################################################################# -# Run the `airGRRunModel_Lag` example in the GRiwrm fashion way # -################################################################# +################################################################### +# Run the `airGR::RunModel_Lag` example in the GRiwrm fashion way # +# Simulation of a reservoir with a purpose of low-flow mitigation # +################################################################### + +## ---- preparation of the InputsModel object + +## loading package and catchment data +library(airGRiwrm) +data(L0123001) -# Run the airGR RunModel_Lag example for harvesting necessary data -library(airGR) -example(RunModel_Lag) -# detach the package because otherwise airGR overwrites the airGRiwrm functions -detach("package:airGR") +## ---- specifications of the reservoir + +## the reservoir withdraws 1 m3/s when it's possible considering the flow observed in the basin +Qupstream <- matrix(-sapply(BasinObs$Qls / 1000 - 1, function(x) { + min(1, max(0, x, na.rm = TRUE)) +}), ncol = 1) + +## except between July and September when the reservoir releases 3 m3/s for low-flow mitigation +month <- as.numeric(format(BasinObs$DatesR, "\%m")) +Qupstream[month >= 7 & month <= 9] <- 3 +Qupstream <- Qupstream * 86400 ## Conversion in m3/day + +## the reservoir is not an upstream subcachment: its areas is NA +BasinAreas <- c(NA, BasinInfo$BasinArea) + +## delay time between the reservoir and the catchment outlet is 2 days and the distance is 150 km +LengthHydro <- 150 +## with a delay of 2 days for 150 km, the flow velocity is 75 km per day +Velocity <- (LengthHydro * 1e3 / 2) / (24 * 60 * 60) ## Conversion km/day -> m/s # This example is a network of 2 nodes which can be describe like this: db <- data.frame(id = c("Reservoir", "GaugingDown"), @@ -67,12 +94,9 @@ colnames(Precip) <- "GaugingDown" PotEvap <- matrix(BasinObs$E, ncol = 1) colnames(PotEvap) <- "GaugingDown" -# Observed flows are integrated now because we mix: -# - flows that are directly injected in the model -# - flows that could be used for the calibration of the hydrological models -Qobs = matrix(c(Qupstream, BasinObs$Qmm), ncol = 2) -colnames(Qobs) <- griwrm$id -str(Qobs) +# Observed flows contain flows that are directly injected in the model +Qobs = matrix(Qupstream, ncol = 1) +colnames(Qobs) <- "Reservoir" # Creation of the GRiwrmInputsModel object (= a named list of InputsModel objects) InputsModels <- CreateInputsModel(griwrm, @@ -82,20 +106,25 @@ InputsModels <- CreateInputsModel(griwrm, Qobs = Qobs) str(InputsModels) +## run period selection +Ind_Run <- seq(which(format(BasinObs$DatesR, format = "\%Y-\%m-\%d")=="1990-01-01"), + which(format(BasinObs$DatesR, format = "\%Y-\%m-\%d")=="1999-12-31")) + # Creation of the GriwmRunOptions object -RunOptions2 <- CreateRunOptions(InputsModels, +RunOptions <- CreateRunOptions(InputsModels, IndPeriod_Run = Ind_Run) -str(RunOptions2) +str(RunOptions) # Parameters of the SD models should be encapsulated in a named list -Param2 <- list(`GaugingDown` = c(Velocity, Param)) +ParamGR4J <- c(X1 = 257.238, X2 = 1.012, X3 = 88.235, X4 = 2.208) +Param <- list(`GaugingDown` = c(Velocity, ParamGR4J)) # RunModel for the whole network OutputsModels <- RunModel(InputsModels, - RunOptions = RunOptions2, - Param = Param2) + RunOptions = RunOptions, + Param = Param) str(OutputsModels) -# Comparison between GRiwrm simulation and airGR simulation -plot(OutputsModels, Qobs = data.frame(`GaugingDown` = OutputsModel$Qsim)) +# Compare Simulation with reservoir and observation of natural flow +plot(OutputsModels, data.frame(GaugingDown = BasinObs$Qmm[Ind_Run])) } diff --git a/man/CreateSupervisor.Rd b/man/CreateSupervisor.Rd index 6ada44b..e3c95b7 100644 --- a/man/CreateSupervisor.Rd +++ b/man/CreateSupervisor.Rd @@ -27,7 +27,6 @@ Creation of a Supervisor for handling regulation in a model \examples{ data(Severn) nodes <- Severn$BasinsInfo[, c("gauge_id", "downstream_id", "distance_downstream", "area")] -nodes$distance_downstream <- nodes$distance_downstream * 1000 # Conversion km -> m nodes$model <- "RunModel_GR4J" griwrm <- CreateGRiwrm(nodes, list(id = "gauge_id", diff --git a/man/RunModel.GR.Rd b/man/RunModel.GR.Rd index 1b76564..963391a 100644 --- a/man/RunModel.GR.Rd +++ b/man/RunModel.GR.Rd @@ -9,9 +9,9 @@ \arguments{ \item{x}{[object of class \code{InputsModel}] \code{InputsModel} for \link[airGR:RunModel]{airGR::RunModel}} -\item{RunOptions}{[object of class \emph{RunOptions}] see \code{\link[airGR]{CreateRunOptions}} for details} +\item{RunOptions}{[object of class \emph{RunOptions}] see \link[airGR:CreateRunOptions]{airGR::CreateRunOptions} for details} -\item{Param}{[numeric] vector of model parameters (See details for SD lag model)} +\item{Param}{\link{numeric} vector of model parameters (See details for SD lag model)} \item{...}{further arguments passed to or from other methods} } @@ -26,42 +26,3 @@ Function which performs a single model run with the provided function over the s \details{ If \code{InputsModel} parameter has been created for using a semi-distributed (SD) lag model (See \code{\link[airGR]{CreateInputsModel}}), the first item of \code{Param} parameter should contain a constant lag parameter expressed as a velocity in m/s, parameters for the hydrological model are then shift one position to the right. } -\examples{ -library(airGR) - -## loading catchment data -data(L0123001) - -## preparation of the InputsModel object -InputsModel <- CreateInputsModel(FUN_MOD = RunModel_GR4J, DatesR = BasinObs$DatesR, - Precip = BasinObs$P, PotEvap = BasinObs$E) - -## run period selection -Ind_Run <- seq(which(format(BasinObs$DatesR, format = "\%Y-\%m-\%d")=="1990-01-01"), - which(format(BasinObs$DatesR, format = "\%Y-\%m-\%d")=="1999-12-31")) - -## preparation of the RunOptions object -RunOptions <- CreateRunOptions(FUN_MOD = RunModel_GR4J, - InputsModel = InputsModel, IndPeriod_Run = Ind_Run) - -## simulation -Param <- c(X1 = 734.568, X2 = -0.840, X3 = 109.809, X4 = 1.971) -OutputsModel <- RunModel(InputsModel = InputsModel, - RunOptions = RunOptions, Param = Param, - FUN_MOD = RunModel_GR4J) - -## results preview -plot(OutputsModel, Qobs = BasinObs$Qmm[Ind_Run]) - -## efficiency criterion: Nash-Sutcliffe Efficiency -InputsCrit <- CreateInputsCrit(FUN_CRIT = ErrorCrit_NSE, InputsModel = InputsModel, - RunOptions = RunOptions, Obs = BasinObs$Qmm[Ind_Run]) -OutputsCrit <- ErrorCrit_NSE(InputsCrit = InputsCrit, OutputsModel = OutputsModel) -} -\seealso{ -\code{\link[airGR]{RunModel_GR4J}}, \code{\link[airGR]{RunModel_CemaNeigeGR4J}}, \code{\link[airGR]{CreateInputsModel}}, -\code{\link[airGR]{CreateRunOptions}}, \code{\link[airGR]{CreateIniStates}}. -} -\author{ -Laurent Coron, Olivier Delaigue -} diff --git a/man/RunModel.GRiwrmInputsModel.Rd b/man/RunModel.GRiwrmInputsModel.Rd index f5f614a..629450e 100644 --- a/man/RunModel.GRiwrmInputsModel.Rd +++ b/man/RunModel.GRiwrmInputsModel.Rd @@ -22,15 +22,36 @@ RunModel function for \emph{GRiwrmInputsModel} object } \examples{ -################################################################# -# Run the `airGRRunModel_Lag` example in the GRiwrm fashion way # -################################################################# +################################################################### +# Run the `airGR::RunModel_Lag` example in the GRiwrm fashion way # +# Simulation of a reservoir with a purpose of low-flow mitigation # +################################################################### -# Run the airGR RunModel_Lag example for harvesting necessary data -library(airGR) -example(RunModel_Lag) -# detach the package because otherwise airGR overwrites the airGRiwrm functions -detach("package:airGR") +## ---- preparation of the InputsModel object + +## loading package and catchment data +library(airGRiwrm) +data(L0123001) + +## ---- specifications of the reservoir + +## the reservoir withdraws 1 m3/s when it's possible considering the flow observed in the basin +Qupstream <- matrix(-sapply(BasinObs$Qls / 1000 - 1, function(x) { + min(1, max(0, x, na.rm = TRUE)) +}), ncol = 1) + +## except between July and September when the reservoir releases 3 m3/s for low-flow mitigation +month <- as.numeric(format(BasinObs$DatesR, "\%m")) +Qupstream[month >= 7 & month <= 9] <- 3 +Qupstream <- Qupstream * 86400 ## Conversion in m3/day + +## the reservoir is not an upstream subcachment: its areas is NA +BasinAreas <- c(NA, BasinInfo$BasinArea) + +## delay time between the reservoir and the catchment outlet is 2 days and the distance is 150 km +LengthHydro <- 150 +## with a delay of 2 days for 150 km, the flow velocity is 75 km per day +Velocity <- (LengthHydro * 1e3 / 2) / (24 * 60 * 60) ## Conversion km/day -> m/s # This example is a network of 2 nodes which can be describe like this: db <- data.frame(id = c("Reservoir", "GaugingDown"), @@ -51,12 +72,9 @@ colnames(Precip) <- "GaugingDown" PotEvap <- matrix(BasinObs$E, ncol = 1) colnames(PotEvap) <- "GaugingDown" -# Observed flows are integrated now because we mix: -# - flows that are directly injected in the model -# - flows that could be used for the calibration of the hydrological models -Qobs = matrix(c(Qupstream, BasinObs$Qmm), ncol = 2) -colnames(Qobs) <- griwrm$id -str(Qobs) +# Observed flows contain flows that are directly injected in the model +Qobs = matrix(Qupstream, ncol = 1) +colnames(Qobs) <- "Reservoir" # Creation of the GRiwrmInputsModel object (= a named list of InputsModel objects) InputsModels <- CreateInputsModel(griwrm, @@ -66,20 +84,25 @@ InputsModels <- CreateInputsModel(griwrm, Qobs = Qobs) str(InputsModels) +## run period selection +Ind_Run <- seq(which(format(BasinObs$DatesR, format = "\%Y-\%m-\%d")=="1990-01-01"), + which(format(BasinObs$DatesR, format = "\%Y-\%m-\%d")=="1999-12-31")) + # Creation of the GriwmRunOptions object -RunOptions2 <- CreateRunOptions(InputsModels, +RunOptions <- CreateRunOptions(InputsModels, IndPeriod_Run = Ind_Run) -str(RunOptions2) +str(RunOptions) # Parameters of the SD models should be encapsulated in a named list -Param2 <- list(`GaugingDown` = c(Velocity, Param)) +ParamGR4J <- c(X1 = 257.238, X2 = 1.012, X3 = 88.235, X4 = 2.208) +Param <- list(`GaugingDown` = c(Velocity, ParamGR4J)) # RunModel for the whole network OutputsModels <- RunModel(InputsModels, - RunOptions = RunOptions2, - Param = Param2) + RunOptions = RunOptions, + Param = Param) str(OutputsModels) -# Comparison between GRiwrm simulation and airGR simulation -plot(OutputsModels, Qobs = data.frame(`GaugingDown` = OutputsModel$Qsim)) +# Compare Simulation with reservoir and observation of natural flow +plot(OutputsModels, data.frame(GaugingDown = BasinObs$Qmm[Ind_Run])) } diff --git a/man/plot.GRiwrmOutputsModel.Rd b/man/plot.GRiwrmOutputsModel.Rd index 79d874a..42a99bf 100644 --- a/man/plot.GRiwrmOutputsModel.Rd +++ b/man/plot.GRiwrmOutputsModel.Rd @@ -22,15 +22,36 @@ by hydrological model output named with the node ID (See \link{CreateGRiwrm} for Function which creates screen plots giving an overview of the model outputs in the GRiwrm network } \examples{ -################################################################# -# Run the `airGRRunModel_Lag` example in the GRiwrm fashion way # -################################################################# +################################################################### +# Run the `airGR::RunModel_Lag` example in the GRiwrm fashion way # +# Simulation of a reservoir with a purpose of low-flow mitigation # +################################################################### -# Run the airGR RunModel_Lag example for harvesting necessary data -library(airGR) -example(RunModel_Lag) -# detach the package because otherwise airGR overwrites the airGRiwrm functions -detach("package:airGR") +## ---- preparation of the InputsModel object + +## loading package and catchment data +library(airGRiwrm) +data(L0123001) + +## ---- specifications of the reservoir + +## the reservoir withdraws 1 m3/s when it's possible considering the flow observed in the basin +Qupstream <- matrix(-sapply(BasinObs$Qls / 1000 - 1, function(x) { + min(1, max(0, x, na.rm = TRUE)) +}), ncol = 1) + +## except between July and September when the reservoir releases 3 m3/s for low-flow mitigation +month <- as.numeric(format(BasinObs$DatesR, "\%m")) +Qupstream[month >= 7 & month <= 9] <- 3 +Qupstream <- Qupstream * 86400 ## Conversion in m3/day + +## the reservoir is not an upstream subcachment: its areas is NA +BasinAreas <- c(NA, BasinInfo$BasinArea) + +## delay time between the reservoir and the catchment outlet is 2 days and the distance is 150 km +LengthHydro <- 150 +## with a delay of 2 days for 150 km, the flow velocity is 75 km per day +Velocity <- (LengthHydro * 1e3 / 2) / (24 * 60 * 60) ## Conversion km/day -> m/s # This example is a network of 2 nodes which can be describe like this: db <- data.frame(id = c("Reservoir", "GaugingDown"), @@ -51,12 +72,9 @@ colnames(Precip) <- "GaugingDown" PotEvap <- matrix(BasinObs$E, ncol = 1) colnames(PotEvap) <- "GaugingDown" -# Observed flows are integrated now because we mix: -# - flows that are directly injected in the model -# - flows that could be used for the calibration of the hydrological models -Qobs = matrix(c(Qupstream, BasinObs$Qmm), ncol = 2) -colnames(Qobs) <- griwrm$id -str(Qobs) +# Observed flows contain flows that are directly injected in the model +Qobs = matrix(Qupstream, ncol = 1) +colnames(Qobs) <- "Reservoir" # Creation of the GRiwrmInputsModel object (= a named list of InputsModel objects) InputsModels <- CreateInputsModel(griwrm, @@ -66,20 +84,25 @@ InputsModels <- CreateInputsModel(griwrm, Qobs = Qobs) str(InputsModels) +## run period selection +Ind_Run <- seq(which(format(BasinObs$DatesR, format = "\%Y-\%m-\%d")=="1990-01-01"), + which(format(BasinObs$DatesR, format = "\%Y-\%m-\%d")=="1999-12-31")) + # Creation of the GriwmRunOptions object -RunOptions2 <- CreateRunOptions(InputsModels, +RunOptions <- CreateRunOptions(InputsModels, IndPeriod_Run = Ind_Run) -str(RunOptions2) +str(RunOptions) # Parameters of the SD models should be encapsulated in a named list -Param2 <- list(`GaugingDown` = c(Velocity, Param)) +ParamGR4J <- c(X1 = 257.238, X2 = 1.012, X3 = 88.235, X4 = 2.208) +Param <- list(`GaugingDown` = c(Velocity, ParamGR4J)) # RunModel for the whole network OutputsModels <- RunModel(InputsModels, - RunOptions = RunOptions2, - Param = Param2) + RunOptions = RunOptions, + Param = Param) str(OutputsModels) -# Comparison between GRiwrm simulation and airGR simulation -plot(OutputsModels, Qobs = data.frame(`GaugingDown` = OutputsModel$Qsim)) +# Compare Simulation with reservoir and observation of natural flow +plot(OutputsModels, data.frame(GaugingDown = BasinObs$Qmm[Ind_Run])) } diff --git a/tests/testthat/helper_RunModel.R b/tests/testthat/helper_RunModel.R index aeb7ec8..7c0913f 100644 --- a/tests/testthat/helper_RunModel.R +++ b/tests/testthat/helper_RunModel.R @@ -51,7 +51,7 @@ setupRunModel <- function() { ) IndPeriod_WarmUp = seq(IndPeriod_Run[1]-365,IndPeriod_Run[1]-1) RunOptions <- CreateRunOptions( - InputsModel = InputsModel, + InputsModel, IndPeriod_WarmUp = IndPeriod_WarmUp, IndPeriod_Run = IndPeriod_Run ) diff --git a/tests/testthat/helper_cemaneige.R b/tests/testthat/helper_cemaneige.R index c62c66a..919312e 100644 --- a/tests/testthat/helper_cemaneige.R +++ b/tests/testthat/helper_cemaneige.R @@ -15,9 +15,7 @@ #' @examples setUpCemaNeigeData <- function() { - library(airGR) data(L0123001) - detach("package:airGR") # Formatting observations for the hydrological models # Each input data should be a matrix or a data.frame with the good id in the name of the column diff --git a/tests/testthat/test-Calibration.R b/tests/testthat/test-Calibration.R index a9e49ec..ecb3b98 100644 --- a/tests/testthat/test-Calibration.R +++ b/tests/testthat/test-Calibration.R @@ -1,12 +1,46 @@ +test_that("airGR::Calibration should work", { + ## loading catchment data + data(L0123001) + + ## preparation of InputsModel object + InputsModel <- CreateInputsModel(RunModel_GR4J, DatesR = BasinObs$DatesR, + Precip = BasinObs$P, PotEvap = BasinObs$E) + + ## calibration period selection + Ind_Run <- seq(which(format(BasinObs$DatesR, format = "%Y-%m-%d")=="1990-01-01"), + which(format(BasinObs$DatesR, format = "%Y-%m-%d")=="1999-12-31")) + Ind_WarmUp <- seq(which(format(BasinObs$DatesR, format = "%Y-%m-%d")=="1989-01-01"), + which(format(BasinObs$DatesR, format = "%Y-%m-%d")=="1989-12-31")) + + ## preparation of RunOptions object + RunOptions <- CreateRunOptions(RunModel_GR4J, + InputsModel = InputsModel, + IndPeriod_Run = Ind_Run, + IndPeriod_WarmUp = Ind_WarmUp) + + ## calibration criterion: preparation of the InputsCrit object + InputsCrit <- CreateInputsCrit(ErrorCrit_NSE, InputsModel = InputsModel, + RunOptions = RunOptions, Obs = BasinObs$Qmm[Ind_Run]) + + ## preparation of CalibOptions object + CalibOptions <- CreateCalibOptions(RunModel_GR4J, FUN_CALIB = Calibration_Michel) + + ## calibration + OutputsCalib <- Calibration(InputsModel = InputsModel, RunOptions = RunOptions, + InputsCrit = InputsCrit, CalibOptions = CalibOptions, + FUN_MOD = RunModel_GR4J, + FUN_CALIB = Calibration_Michel) + + expect_length(OutputsCalib$ParamFinalR, 4) +}) + # data set up e <- setupRunModel() # variables are copied from environment 'e' to the current environment # https://stackoverflow.com/questions/9965577/r-copy-move-one-environment-to-another for(x in ls(e)) assign(x, get(x, e)) -context("Calibration.GRiwrmInputsModel") - -CalibOptions <- CreateCalibOptions(InputsModel = InputsModel) +CalibOptions <- CreateCalibOptions(InputsModel) test_that("Calibrated parameters remains unchanged", { InputsCrit <- CreateInputsCrit( diff --git a/tests/testthat/test-CreateCalibOptions.R b/tests/testthat/test-CreateCalibOptions.R new file mode 100644 index 0000000..4661409 --- /dev/null +++ b/tests/testthat/test-CreateCalibOptions.R @@ -0,0 +1,6 @@ +test_that("airGR::CreateCalibOptions should works", { + ## preparation of CalibOptions object + CalibOptions <- airGR::CreateCalibOptions(RunModel_GR4J, FUN_CALIB = Calibration_Michel) + expect_equal(CreateCalibOptions(RunModel_GR4J, FUN_CALIB = Calibration_Michel), CalibOptions) + expect_equal(CreateCalibOptions("RunModel_GR4J", FUN_CALIB = Calibration_Michel), CalibOptions) +}) diff --git a/tests/testthat/test-CreateInputsCrit.R b/tests/testthat/test-CreateInputsCrit.R index 99f00de..36b0eef 100644 --- a/tests/testthat/test-CreateInputsCrit.R +++ b/tests/testthat/test-CreateInputsCrit.R @@ -1,3 +1,34 @@ +test_that("airGR::CreateInputsCrit should works", { + ## loading catchment data + data(L0123001) + + ## preparation of InputsModel object + InputsModel <- CreateInputsModel(RunModel_GR4J, DatesR = BasinObs$DatesR, + Precip = BasinObs$P, PotEvap = BasinObs$E) + + ## calibration period selection + Ind_Run <- seq(which(format(BasinObs$DatesR, format = "%Y-%m-%d")=="1990-01-01"), + which(format(BasinObs$DatesR, format = "%Y-%m-%d")=="1999-12-31")) + Ind_WarmUp <- seq(which(format(BasinObs$DatesR, format = "%Y-%m-%d")=="1989-01-01"), + which(format(BasinObs$DatesR, format = "%Y-%m-%d")=="1989-12-31")) + + ## preparation of RunOptions object + RunOptions <- CreateRunOptions(RunModel_GR4J, + InputsModel = InputsModel, + IndPeriod_Run = Ind_Run, + IndPeriod_WarmUp = Ind_WarmUp) + + ## calibration criterion: preparation of the InputsCrit object + InputsCrit <- airGR::CreateInputsCrit(ErrorCrit_NSE, InputsModel = InputsModel, + RunOptions = RunOptions, Obs = BasinObs$Qmm[Ind_Run]) + expect_equal(CreateInputsCrit(ErrorCrit_NSE, InputsModel = InputsModel, + RunOptions = RunOptions, Obs = BasinObs$Qmm[Ind_Run]), + InputsCrit) + expect_equal(CreateInputsCrit("ErrorCrit_NSE", InputsModel = InputsModel, + RunOptions = RunOptions, Obs = BasinObs$Qmm[Ind_Run]), + InputsCrit) +}) + # data set up e <- setupRunModel() # variables are copied from environment 'e' to the current environment diff --git a/tests/testthat/test-CreateInputsModel.R b/tests/testthat/test-CreateInputsModel.R index bc2d6d7..eb106bd 100644 --- a/tests/testthat/test-CreateInputsModel.R +++ b/tests/testthat/test-CreateInputsModel.R @@ -1,4 +1,23 @@ -context("CreateInputsModel") +test_that("airGR::CreateInputsModel should work", { + ## loading catchment data + data(L0123001) + + ## preparation of InputsModel object + InputsModel <- airGR::CreateInputsModel(FUN_MOD = RunModel_GR4J, DatesR = BasinObs$DatesR, + Precip = BasinObs$P, PotEvap = BasinObs$E) + + expect_equal(CreateInputsModel(RunModel_GR4J, + DatesR = BasinObs$DatesR, + Precip = BasinObs$P, + PotEvap = BasinObs$E), + InputsModel) + expect_equal(CreateInputsModel("RunModel_GR4J", + DatesR = BasinObs$DatesR, + Precip = BasinObs$P, + PotEvap = BasinObs$E), + InputsModel) +}) + l <- setUpCemaNeigeData() diff --git a/tests/testthat/test-CreateRunOptions.R b/tests/testthat/test-CreateRunOptions.R new file mode 100644 index 0000000..ed3e224 --- /dev/null +++ b/tests/testthat/test-CreateRunOptions.R @@ -0,0 +1,52 @@ +## loading catchment data +data(L0123001) + +## preparation of InputsModel object +InputsModel <- CreateInputsModel(RunModel_GR4J, DatesR = BasinObs$DatesR, + Precip = BasinObs$P, PotEvap = BasinObs$E) + +## calibration period selection +Ind_Run <- seq(which(format(BasinObs$DatesR, format = "%Y-%m-%d")=="1990-01-01"), + which(format(BasinObs$DatesR, format = "%Y-%m-%d")=="1999-12-31")) +Ind_WarmUp <- seq(which(format(BasinObs$DatesR, format = "%Y-%m-%d")=="1989-01-01"), + which(format(BasinObs$DatesR, format = "%Y-%m-%d")=="1989-12-31")) + +## preparation of RunOptions object +RunOptions <- airGR::CreateRunOptions(RunModel_GR4J, + InputsModel = InputsModel, + IndPeriod_Run = Ind_Run, + IndPeriod_WarmUp = Ind_WarmUp) + +test_that("CreateRunOptions.InputsModel works", { + expect_equal( + CreateRunOptions(InputsModel, + FUN_MOD = RunModel_GR4J, + IndPeriod_Run = Ind_Run, + IndPeriod_WarmUp = Ind_WarmUp), + RunOptions) + InputsModel$FUN_MOD = RunModel_GR4J + expect_equal( + CreateRunOptions(InputsModel, + IndPeriod_Run = Ind_Run, + IndPeriod_WarmUp = Ind_WarmUp), + RunOptions) +}) + +test_that("CreateRunOptions.character works", { + expect_equal( + CreateRunOptions("RunModel_GR4J", + InputsModel = InputsModel, + IndPeriod_Run = Ind_Run, + IndPeriod_WarmUp = Ind_WarmUp), + RunOptions) +}) + +test_that("CreateRunOptions.function works", { + expect_equal( + CreateRunOptions(RunModel_GR4J, + InputsModel = InputsModel, + IndPeriod_Run = Ind_Run, + IndPeriod_WarmUp = Ind_WarmUp), + RunOptions) +}) + diff --git a/tests/testthat/test-RunModel.R b/tests/testthat/test-RunModel.R index e20038a..f75b408 100644 --- a/tests/testthat/test-RunModel.R +++ b/tests/testthat/test-RunModel.R @@ -8,7 +8,7 @@ context("RunModel.GRiwrmInputsModel") test_that("RunModel.GRiwrmInputsModel should return same result with separated warm-up", { RO_WarmUp <- CreateRunOptions( - InputsModel = InputsModel, + InputsModel, IndPeriod_WarmUp = 0L, IndPeriod_Run = IndPeriod_WarmUp ) @@ -18,7 +18,7 @@ test_that("RunModel.GRiwrmInputsModel should return same result with separated w Param = ParamMichel ) RO_Run <- CreateRunOptions( - InputsModel = InputsModel, + InputsModel, IndPeriod_WarmUp = 0L, IndPeriod_Run = IndPeriod_Run, IniStates = lapply(OM_WarmUp, "[[", "StateEnd") @@ -60,7 +60,9 @@ griwrm2 <- rbind(griwrm, # Add Qobs for the 2 new nodes and create InputsModel Qobs2 <- cbind(Qobs, matrix(data = rep(0, 2*nrow(Qobs)), ncol = 2)) colnames(Qobs2) <- c(colnames(Qobs2)[1:6], "R1", "R2") -InputsModel <- CreateInputsModel(griwrm2, DatesR, Precip, PotEvap, Qobs2) +InputsModel <- suppressWarnings( + CreateInputsModel(griwrm2, DatesR, Precip, PotEvap, Qobs2) +) test_that("RunModel.Supervisor with two regulations that cancel each other out should returns same results as RunModel.GRiwrmInputsModel", { # Create Supervisor @@ -103,14 +105,18 @@ test_that("RunModel.GRiwrmInputsModel handles CemaNeige", { l$ZInputs <- l$ZInputs[1:2] l$TempMean <- l$TempMean[,1:2] l$HypsoData <- l$HypsoData[,1:2] - InputsModels <- CreateInputsModel(l$griwrm, - DatesR = l$DatesR, - Precip = l$Precip, - PotEvap = l$PotEvap, - TempMean = l$TempMean, - ZInputs = l$ZInputs, - HypsoData = l$HypsoData, - Qobs = l$Qobs) + InputsModels <- suppressWarnings( + CreateInputsModel( + l$griwrm, + DatesR = l$DatesR, + Precip = l$Precip, + PotEvap = l$PotEvap, + TempMean = l$TempMean, + ZInputs = l$ZInputs, + HypsoData = l$HypsoData, + Qobs = l$Qobs + ) + ) ## run period selection Ind_Run <- seq(which(format(BasinObs$DatesR, format = "%Y-%m-%d")=="1990-01-01"), which(format(BasinObs$DatesR, format = "%Y-%m-%d")=="1999-12-31")) diff --git a/vignettes/V02_Calibration_SD_model.Rmd b/vignettes/V02_Calibration_SD_model.Rmd index 074d7cd..19e4c96 100644 --- a/vignettes/V02_Calibration_SD_model.Rmd +++ b/vignettes/V02_Calibration_SD_model.Rmd @@ -74,7 +74,7 @@ Arguments of the `CreateRunOptions` function for **airGRiwrm** are the same as f ```{r} RunOptions <- CreateRunOptions( - InputsModel = InputsModel, + InputsModel, IndPeriod_WarmUp = IndPeriod_WarmUp, IndPeriod_Run = IndPeriod_Run ) @@ -98,7 +98,7 @@ It needs the following arguments: ```{r InputsCrit} InputsCrit <- CreateInputsCrit( InputsModel = InputsModel, - FUN_CRIT = airGR::ErrorCrit_KGE2, + FUN_CRIT = ErrorCrit_KGE2, RunOptions = RunOptions, Obs = Qobs[IndPeriod_Run, ], AprioriIds = c( diff --git a/vignettes/V03_Open-loop_influenced_flow.Rmd b/vignettes/V03_Open-loop_influenced_flow.Rmd index 2895ee9..35bb05f 100644 --- a/vignettes/V03_Open-loop_influenced_flow.Rmd +++ b/vignettes/V03_Open-loop_influenced_flow.Rmd @@ -103,7 +103,7 @@ RunOptions <- CreateRunOptions(IM_OL, IndPeriod_WarmUp = IndPeriod_WarmUp, IndPeriod_Run = IndPeriod_Run) InputsCrit <- CreateInputsCrit(IM_OL, - FUN_CRIT = airGR::ErrorCrit_KGE2, + FUN_CRIT = ErrorCrit_KGE2, RunOptions = RunOptions, Obs = Qobs[IndPeriod_Run,], AprioriIds = c("54057" = "54032", "54032" = "54001"), transfo = "sqrt", k = 0.15 diff --git a/vignettes/V04_Closed-loop_regulated_withdrawal.Rmd b/vignettes/V04_Closed-loop_regulated_withdrawal.Rmd index dd39ea6..50a606b 100644 --- a/vignettes/V04_Closed-loop_regulated_withdrawal.Rmd +++ b/vignettes/V04_Closed-loop_regulated_withdrawal.Rmd @@ -87,7 +87,7 @@ PotEvap <- ConvertMeteoSD(griwrm, PotEvapTot) # Calculation of the water need at the sub-basin scale dailyWaterNeed <- PotEvap - Precip dailyWaterNeed <- cbind(as.data.frame(DatesR), dailyWaterNeed[,c("54001", "54032")]) -monthlyWaterNeed <- airGR::SeriesAggreg(dailyWaterNeed, "%m", rep("q80",2)) +monthlyWaterNeed <- SeriesAggreg(dailyWaterNeed, "%m", rep("q80",2)) monthlyWaterNeed$DatesR <- as.numeric(format(monthlyWaterNeed$DatesR,"%m")) names(monthlyWaterNeed)[1] <- "month" monthlyWaterNeed diff --git a/vignettes/seinebasin/V02_First_run.Rmd b/vignettes/seinebasin/V02_First_run.Rmd index 151b953..19d5976 100644 --- a/vignettes/seinebasin/V02_First_run.Rmd +++ b/vignettes/seinebasin/V02_First_run.Rmd @@ -95,7 +95,7 @@ IndPeriod_WarmUp <- seq(1, IndPeriod_Run[1] - 1) ```{r CreateRunOptions} RunOptions <- CreateRunOptions( - InputsModel = InputsModel, + InputsModel, IndPeriod_WarmUp = IndPeriod_WarmUp, IndPeriod_Run = IndPeriod_Run ) diff --git a/vignettes/seinebasin/V03_First_Calibration.Rmd b/vignettes/seinebasin/V03_First_Calibration.Rmd index b98734e..438e2ae 100644 --- a/vignettes/seinebasin/V03_First_Calibration.Rmd +++ b/vignettes/seinebasin/V03_First_Calibration.Rmd @@ -32,7 +32,7 @@ We need then to prepare the InputsCrit object that is necessary to define the ca ```{r CreateInputsCrit} InputsCrit <- CreateInputsCrit( InputsModel = InputsModel, - FUN_CRIT = airGR::ErrorCrit_KGE2, + FUN_CRIT = ErrorCrit_KGE2, RunOptions = RunOptions, Obs = Qnat[IndPeriod_Run,] ) diff --git a/vignettes/seinebasin/V04_Open-loop_influenced_flow.Rmd b/vignettes/seinebasin/V04_Open-loop_influenced_flow.Rmd index b95efee..3e800de 100644 --- a/vignettes/seinebasin/V04_Open-loop_influenced_flow.Rmd +++ b/vignettes/seinebasin/V04_Open-loop_influenced_flow.Rmd @@ -249,7 +249,7 @@ We can now run the model, using the parameters previously obtained: ```{r RunModel} RunOptions <- CreateRunOptions( - InputsModel = InputsModel2, + InputsModel2, IndPeriod_Run = IndPeriod_Run ) OutputsModels2 <- RunModel( diff --git a/vignettes/seinebasin/V05_Open-loop_influenced_flow_calibration.Rmd b/vignettes/seinebasin/V05_Open-loop_influenced_flow_calibration.Rmd index 164f551..3005233 100644 --- a/vignettes/seinebasin/V05_Open-loop_influenced_flow_calibration.Rmd +++ b/vignettes/seinebasin/V05_Open-loop_influenced_flow_calibration.Rmd @@ -75,7 +75,7 @@ IndPeriod_WarmUp <- seq.int(1, IndPeriod_Run[1] - 1) ```{r CreateRunOptions} RunOptions <- CreateRunOptions( - InputsModel = InputsModel3, + InputsModel3, IndPeriod_WarmUp = IndPeriod_WarmUp, IndPeriod_Run = IndPeriod_Run ) @@ -88,7 +88,7 @@ We define the objective function for the calibration: ```{r CreateInputsCrit} InputsCrit <- CreateInputsCrit( InputsModel = InputsModel3, - FUN_CRIT = airGR::ErrorCrit_KGE2, + FUN_CRIT = ErrorCrit_KGE2, RunOptions = RunOptions, Obs = Qobs[IndPeriod_Run,] ) ``` diff --git a/vignettes/seinebasin/V05b_Open-loop_influenced_flow_calibration_GR6J.Rmd b/vignettes/seinebasin/V05b_Open-loop_influenced_flow_calibration_GR6J.Rmd index b132e5a..f5aa8fb 100644 --- a/vignettes/seinebasin/V05b_Open-loop_influenced_flow_calibration_GR6J.Rmd +++ b/vignettes/seinebasin/V05b_Open-loop_influenced_flow_calibration_GR6J.Rmd @@ -77,7 +77,7 @@ IndPeriod_WarmUp <- seq.int(1,IndPeriod_Run[1] - 1) ```{r CreateRunOptions} RunOptions <- CreateRunOptions( - InputsModel = InputsModel3, + InputsModel3, IndPeriod_WarmUp = IndPeriod_WarmUp, IndPeriod_Run = IndPeriod_Run ) @@ -90,7 +90,7 @@ We define the objective function for the calibration: ```{r CreateInputsCrit} InputsCrit <- CreateInputsCrit( InputsModel = InputsModel3, - FUN_CRIT = airGR::ErrorCrit_KGE2, + FUN_CRIT = ErrorCrit_KGE2, RunOptions = RunOptions, Obs = Qobs[IndPeriod_Run,] ) ``` diff --git a/vignettes/seinebasin/V06_Naturalised_flow_simulation.Rmd b/vignettes/seinebasin/V06_Naturalised_flow_simulation.Rmd index 20a52b5..4b0a8f2 100644 --- a/vignettes/seinebasin/V06_Naturalised_flow_simulation.Rmd +++ b/vignettes/seinebasin/V06_Naturalised_flow_simulation.Rmd @@ -77,7 +77,7 @@ IndPeriod_WarmUp <- seq(1, IndPeriod_Run[1] - 1) ```{r CreateRunOptions} RunOptions <- CreateRunOptions( - InputsModel = InputsModel4, + InputsModel4, IndPeriod_WarmUp = IndPeriod_WarmUp, IndPeriod_Run = IndPeriod_Run ) -- GitLab