diff --git a/.Rbuildignore b/.Rbuildignore
index 77d23ee2669ce32c8b6d62fa7b77eeeab4fe4660..7d148441692d2792a23ccbc094b837329e27aeb6 100644
--- a/.Rbuildignore
+++ b/.Rbuildignore
@@ -12,6 +12,7 @@
 ^docs
 ^vignettes/seinebasin
 ^man-roxygen
+^man-examples
 ^dev
 ^CRAN-SUBMISSION$
 ^cran-comments\.md$
diff --git a/.gitlab-ci.yml b/.gitlab-ci.yml
index 716ddcce0dc48bddf21a897eb0d651b22fbf0c20..cd2707ec95b3ada48c86907199b3064418493a3d 100644
--- a/.gitlab-ci.yml
+++ b/.gitlab-ci.yml
@@ -17,12 +17,12 @@ cache:
 before_script:
   - mkdir -p $R_LIBS_USER
   - echo "R_LIBS='$R_LIBS_USER'" > .Renviron
-  - R -e 'devtools::install_deps(dep = T)'
+  - R -e 'remotes::install_deps(dep = T)'
 
 test_all:
   stage: checks
   script:
-  - R -q -e 'devtools::test()'
+  - R -q -e 'testthat::test_local()'
 
 check:
   stage: checks
diff --git a/R/Calibration.GRiwrmInputsModel.R b/R/Calibration.GRiwrmInputsModel.R
index e53eed89ae4901f042ed96facfde23a26e8310e5..6f16b6bf02eb0c03fc438e21af3681e96682402d 100644
--- a/R/Calibration.GRiwrmInputsModel.R
+++ b/R/Calibration.GRiwrmInputsModel.R
@@ -31,34 +31,74 @@ Calibration.GRiwrmInputsModel <- function(InputsModel,
   OutputsModel <- list()
   class(OutputsModel) <- append("GRiwrmOutputsModel", class(OutputsModel))
 
-  for(IM in InputsModel) {
-    message("Calibration.GRiwrmInputsModel: Treating sub-basin ", IM$id, "...")
+  b <- sapply(InputsModel, function(IM) !IM$isUngauged)
+  gaugedIds <- names(b[b])
 
-    if(useUpstreamQsim && any(IM$UpstreamIsRunoff)) {
-      # Update InputsModel$Qupstream with simulated upstream flows
-      IM <- UpdateQsimUpstream(IM, RunOptions[[IM$id]], OutputsModel)
-    }
+  for(id in gaugedIds) {
+    IM <- InputsModel[[id]]
+    message("Calibration.GRiwrmInputsModel: Treating sub-basin ", id, "...")
 
-    if (inherits(InputsCrit[[IM$id]], "InputsCritLavenneFunction")) {
-      IC <- getInputsCrit_Lavenne(IM$id, OutputsModel, InputsCrit)
+    if (inherits(InputsCrit[[id]], "InputsCritLavenneFunction")) {
+      IC <- getInputsCrit_Lavenne(id, OutputsModel, InputsCrit)
+    } else {
+      IC <- InputsCrit[[id]]
+    }
+    hasUngauged <- IM$hasUngauged
+    if (hasUngauged) {
+      l  <- updateParameters4Ungauged(id,
+                                      InputsModel,
+                                      RunOptions,
+                                      OutputsModel,
+                                      useUpstreamQsim)
+      IM <- l$InputsModel
+      IM$FUN_MOD <- "RunModel_Ungauged"
+      attr(RunOptions[[id]], "GRiwrmRunOptions") <- l$RunOptions
     } else {
-      IC <- InputsCrit[[IM$id]]
+      if(useUpstreamQsim && any(IM$UpstreamIsRunoff)) {
+        # Update InputsModel$Qupstream with simulated upstream flows
+        IM <- UpdateQsimUpstream(IM, RunOptions[[id]], OutputsModel)
+      }
     }
 
-    OutputsCalib[[IM$id]] <- Calibration(
+    OutputsCalib[[id]] <- Calibration(
       InputsModel = IM,
-      RunOptions = RunOptions[[IM$id]],
+      RunOptions = RunOptions[[id]],
       InputsCrit = IC,
-      CalibOptions = CalibOptions[[IM$id]],
+      CalibOptions = CalibOptions[[id]],
       ...
     )
 
+    if (hasUngauged) {
+      # Select nodes with model in the sub-network
+      g <- attr(IM, "GRiwrm")
+      Ids <- g$id[g$donor == id & !is.na(g$model)]
+      # Extract the X4 calibrated for the whole intermediate basin
+      PS <- attr(IM[[id]], "ParamSettings")
+      if(PS$hasX4) {
+        X4 <- OutputsCalib[[id]]$ParamFinalR[PS$iX4] # Global parameter
+        subBasinAreas <- calcSubBasinAreas(IM)
+      }
+      for (uId in Ids) {
+        # Add OutputsCalib for ungauged nodes
+        OutputsCalib[[uId]] <- OutputsCalib[[id]]
+        # Copy parameters and transform X4 relatively to the sub-basin area
+        PS <- attr(IM[[uId]], "ParamSettings")
+        OutputsCalib[[uId]]$ParamFinalR <-
+          OutputsCalib[[uId]]$ParamFinalR[PS$Indexes]
+        if(PS$hasX4) {
+          OutputsCalib[[uId]]$ParamFinalR[PS$iX4] <-
+            X4 * (subBasinAreas[uId] / sum(subBasinAreas)) ^ 0.3
+        }
+      }
+      IM <- IM[[id]]
+    }
+
     if(useUpstreamQsim) {
       # Run the model for the sub-basin
-      OutputsModel[[IM$id]] <- RunModel(
+      OutputsModel[[id]] <- RunModel(
         x = IM,
-        RunOptions = RunOptions[[IM$id]],
-        Param = OutputsCalib[[IM$id]]$ParamFinalR
+        RunOptions = RunOptions[[id]],
+        Param = OutputsCalib[[id]]$ParamFinalR
       )
     }
 
@@ -96,3 +136,135 @@ getInputsCrit_Lavenne <- function(id, OutputsModel, InputsCrit) {
   AprCrit <- ErrorCrit(InputsCrit[[AprioriId]], OutputsModel[[AprioriId]])$CritValue
   return(Lavenne_FUN(AprParamR, AprCrit))
 }
+
+
+#' Reduce a GRiwrm list object (InputsModel, RunOptions...) for a reduced network
+#'
+#' @param griwrm See [CreateGRiwrm])
+#' @param obj Either a *GRiwrmInputsModel*, *GRiwrmOptions*... object
+#'
+#' @return The object containing only nodes of the reduced model
+#' @noRd
+reduceGRiwrmObj4Ungauged <- function(griwrm, obj) {
+  objAttributes <- attributes(obj)
+  obj <- lapply(obj, function(o) {
+    if(o$id %in% griwrm$id && !is.na(griwrm$model[griwrm$id == o$id])) {
+      o
+    } else {
+      NULL
+    }
+  })
+  obj[sapply(obj, is.null)] <- NULL
+  objAttributes$names <- names(obj)
+  attributes(obj) <- objAttributes
+  return(obj)
+}
+
+updateParameters4Ungauged <- function(GaugedId,
+                                      InputsModel,
+                                      RunOptions,
+                                      OutputsModel,
+                                      useUpstreamQsim) {
+
+  ### Set the reduced network of the basin containing ungauged nodes ###
+  # Select nodes identified with the current node as gauged node
+  griwrm <- attr(InputsModel, "GRiwrm")
+  g <- griwrm[griwrm$donor == GaugedId, ]
+  # Add upstream nodes for routing upstream flows
+  upIds <- griwrm$id[griwrm$down %in% g$id & !griwrm$id %in% g$id]
+  g <- rbind(griwrm[griwrm$id %in% upIds, ], g)
+  g$model[g$id %in% upIds] <- NA
+  # Set downstream node
+  g$down[!g$down %in% g$id] <- NA
+
+  ### Modify InputsModel for the reduced network ###
+  # Remove nodes outside of reduced network
+  InputsModel <- reduceGRiwrmObj4Ungauged(g, InputsModel)
+  # Update griwrm
+  attr(InputsModel, "GRiwrm") <- g
+  # Update Qupstream of reduced network upstream nodes
+  g2 <- griwrm[griwrm$donor == GaugedId,]
+  upIds2 <- g2$id[!g2$id %in% g2$down]
+  for (id in upIds2) {
+    if(useUpstreamQsim && any(InputsModel[[id]]$UpstreamIsRunoff)) {
+      # Update InputsModel$Qupstream with simulated upstream flows
+      InputsModel[[id]] <- UpdateQsimUpstream(InputsModel[[id]],
+                                              RunOptions[[id]],
+                                              OutputsModel)
+      InputsModel[[id]]$UpstreamIsRunoff <-
+        rep(FALSE, length(InputsModel[[id]]$UpstreamIsRunoff))
+    }
+  }
+  # Add extra info for Param processing
+  nbParam <- RunOptions[[GaugedId]]$FeatFUN_MOD$NbParam
+  for (id in names(InputsModel)) {
+    attr(InputsModel[[id]], "ParamSettings") <-
+      list(Indexes = ifelse(inherits(InputsModel[[id]], "SD"), 1, 2):nbParam,
+           hasX4 = grepl("RunModel_GR[456][HJ]", InputsModel[[id]]$FUN_MOD),
+           iX4 = ifelse(inherits(InputsModel[[id]], "SD"), 5, 4))
+  }
+  # Add class InputsModel for airGR::Calibration checks
+  class(InputsModel) <- c("InputsModel", class(InputsModel))
+
+  ### Modify RunOptions for the reduced network ###
+  RunOptions <- reduceGRiwrmObj4Ungauged(g, RunOptions)
+  return(list(InputsModel = InputsModel, RunOptions = RunOptions))
+}
+
+
+#' Compute the area of downstream sub-basins
+#'
+#' @param IM *GRiwrmInputsModel* object (See [CreateInputsModel.GRiwrm])
+#'
+#' @return [numeric] named [vector] of the area of the downstream sub-basins
+#' @noRd
+calcSubBasinAreas <- function(IM) {
+  unlist(
+    sapply(IM, function(x) {
+      if(is.list(x)) as.numeric(x$BasinAreas[length(x$BasinAreas)])})
+  )
+}
+
+
+#' RunModel for a sub-network of ungauged nodes
+#'
+#' The function simulates a network with one set of parameters
+#' shared with ungauged nodes inside the basin.
+#'
+#' @details
+#' The network should contains only one gauged station at downstream and other
+#' nodes can be direct injection or ungauged nodes.
+#'
+#' This function works as functions similar to [airGR::RunModel_GR4J] except that
+#' `InputsModel` is a *GRiwrmInputsModel* containing the network of ungauged nodes
+#' and direct injection in the basin.
+#'
+#' `Param` is adjusted for each sub-basin using the method developed by
+#' Lobligeois (2014) for GR models.
+#'
+#' @references Lobligeois, Florent. Mieux connaître la distribution spatiale des
+#' pluies améliore-t-il la modélisation des crues ? Diagnostic sur 181 bassins
+#' versants français. Phdthesis, AgroParisTech, 2014.
+#' <https://pastel.archives-ouvertes.fr/tel-01134990/document>
+#'
+#' @inheritParams airGR::RunModel
+#'
+#' @inherit RunModel.GRiwrmInputsModel return return
+#' @noRd
+RunModel_Ungauged <- function(InputsModel, RunOptions, Param) {
+  InputsModel$FUN_MOD <- NULL
+  SBVI <- sum(calcSubBasinAreas(InputsModel))
+  # Compute Param for each sub-basin
+  P <- lapply(InputsModel, function(IM) {
+    PS <- attr(IM, "ParamSettings")
+    p <- Param[PS$Indexes]
+    if(PS$hasX4) {
+      p[PS$iX4] <- Param[PS$iX4] * (IM$BasinAreas[length(IM$BasinAreas)] / SBVI) ^ 0.3
+    }
+    return(p)
+  })
+  OM <- suppressMessages(
+    RunModel.GRiwrmInputsModel(InputsModel, attr(RunOptions, "GRiwrmRunOptions"), P)
+  )
+  return(OM[[length(OM)]])
+}
diff --git a/R/ConvertMeteoSD.R b/R/ConvertMeteoSD.R
index ea3ed7cdc2a73375912e627ffb59a774116f56c7..6da9fd2719710e53d730c62acbaaa671a7232277 100644
--- a/R/ConvertMeteoSD.R
+++ b/R/ConvertMeteoSD.R
@@ -26,7 +26,7 @@ ConvertMeteoSD.GRiwrm <- function(x, meteo, ...) {
 #' @export
 #' @rdname ConvertMeteoSD
 ConvertMeteoSD.character <- function(x, griwrm, meteo, ...) {
-  upperBasins <- !is.na(griwrm$down) & griwrm$down == x
+  upperBasins <- !is.na(griwrm$down) & griwrm$down == x & !is.na(griwrm$area)
   if(all(!upperBasins)) {
     return(meteo[,x])
   }
diff --git a/R/CreateGRiwrm.R b/R/CreateGRiwrm.R
index f5f9fe3980ab6ee70a317efb876dd83eb76ed2ba..83cf2672d10e128e72558c0440d090f24ea0db4d 100644
--- a/R/CreateGRiwrm.R
+++ b/R/CreateGRiwrm.R
@@ -7,9 +7,21 @@
 #'  * the identifier and the hydraulic distance to the downstream node
 #'  ([character] columns `down` and [numeric] columns `length` in km). The
 #'  last downstream node should have fields `down` and `length` set to `NA`,
-#'  * the area of the basin ([numeric] column `area` in km2)
-#'  * the hydrological model to use or [NA] for using observed flow instead of a
-#'  runoff model output ([character] column `model`)
+#'  * the total area of the basin at the node location ([numeric] column `area` in km2).
+#'  Direct injection node can have a null area defined by `NA`
+#'  * the model to use ([character] column `model`), see section below for details
+#'
+#' ## Available models in airGRiwrm
+#'
+#' The "model" column should be filled by one of the following:
+#'
+#' * One of the hydrological models available in the *airGR* package defined by its
+#' `RunModel` function (i.e.: `RunModel_GR4J`, `RunModel_GR5HCemaneige`...)
+#' * `NA` for injecting (or abstracting) a flow time series at the location of the node
+#' (direct flow injection)
+#' * `Ungauged` for an ungauged node. The sub-basin inherits hydrological model and
+#' parameters from a "donor" sub-basin. By default the donor is the first gauged
+#' node at downstream
 #'
 #' @param db [data.frame] description of the network (See details)
 #' @param cols [list] or [vector] columns of `db`. By default, mandatory column
@@ -31,10 +43,12 @@
 #'  node location in km2
 #'  * `model` ([character]): hydrological model to use ([NA] for using observed
 #'  flow instead of a runoff model output)
+#'  * `donor` ([character]): node used as "donor" for the the model and the
+#'  calibration parameters.
 #'
 #' @aliases GRiwrm
 #' @export
-#' @inherit RunModel.GRiwrmInputsModel return examples
+#' @example man-examples/CreateGRiwrm.R
 #'
 CreateGRiwrm <- function(db,
                    cols = list(
@@ -54,23 +68,24 @@ CreateGRiwrm <- function(db,
       area = "area"
     )
   cols <- utils::modifyList(colsDefault, as.list(cols))
-  db <- dplyr::rename(db, unlist(cols))
+  griwrm <- dplyr::rename(db, unlist(cols))
   if (!keep_all) {
-    db <- dplyr::select(db, names(cols))
+    griwrm <- dplyr::select(griwrm, names(cols))
   }
-  CheckColumnTypes(db,
+  CheckColumnTypes(griwrm,
                    list(id = "character",
                         down = "character",
                         length = "double",
                         model = "character",
                         area = "double"),
                    keep_all)
-  checkNetworkConsistency(db)
-
-  class(db) <- c("GRiwrm", class(db))
-  db
+  checkNetworkConsistency(griwrm)
+  griwrm$donor <- sapply(griwrm$id, getGaugedId, griwrm = griwrm)
+  class(griwrm) <- c("GRiwrm", class(griwrm))
+  griwrm
 }
 
+
 #' Check of the column types of a [data.frame]
 #'
 #' @param df [data.frame] to check
@@ -79,7 +94,7 @@ CreateGRiwrm <- function(db,
 #' @param keep_all [logical] if `df` contains extra columns
 #'
 #' @return [NULL] or error message if a wrong type is detected
-
+#'
 #' @examples
 #' CheckColumnTypes(
 #'   data.frame(string = c("A"), numeric = c(1), stringsAsFactors = FALSE),
@@ -104,6 +119,7 @@ CheckColumnTypes <- function(df, coltypes, keep_all) {
   return(NULL)
 }
 
+
 #' Sorting of the nodes from upstream to downstream
 #'
 #' @param griwrm \[object of class `GRiwrm`\] see [CreateGRiwrm] for details
@@ -131,6 +147,7 @@ getNodeRanking <- function(griwrm) {
   return(ranking)
 }
 
+
 checkNetworkConsistency <- function(db) {
   if(sum(is.na(db$down)) != 1 | sum(is.na(db$length)) != 1) {
     stop("One and only one node must have 'NA' in columns 'down' and 'length")
@@ -144,3 +161,23 @@ checkNetworkConsistency <- function(db) {
     }
   })
 }
+
+
+#' Get the Id of the nearest gauged model at downstream
+#'
+#' @param id [character] Id of the current node
+#' @param griwrm See [CreateGRiwrm])
+#'
+#' @return [character] Id of the first node with a model
+#'
+#' @noRd
+getGaugedId <- function(id, griwrm) {
+  if(!is.na(griwrm$model[griwrm$id == id]) & griwrm$model[griwrm$id == id] != "Ungauged") {
+    return(id)
+  } else if(!is.na(griwrm$down[griwrm$id == id])){
+    return(getGaugedId(griwrm$down[griwrm$id == id], griwrm))
+  } else {
+    stop("The model of the downstream node of a network cannot be `NA` or \"Ungauged\"")
+  }
+}
+
diff --git a/R/CreateInputsCrit.GRiwrmInputsModel.R b/R/CreateInputsCrit.GRiwrmInputsModel.R
index 718938ed6665ca15b2c3a39416ee40689c3d6bfb..1430274b2245739e360102c6eb7ba260c2fb56c8 100644
--- a/R/CreateInputsCrit.GRiwrmInputsModel.R
+++ b/R/CreateInputsCrit.GRiwrmInputsModel.R
@@ -56,6 +56,11 @@ CreateInputsCrit.GRiwrmInputsModel <- function(InputsModel,
         stop("'AprioriIds': the node \"", AprioriIds[id],
              "\" is not upstream the node \"", id,"\"")
       }
+      if (InputsModel[[AprioriIds[id]]]$isUngauged &
+          InputsModel[[AprioriIds[id]]]$gaugedId == id) {
+        stop("'AprioriIds': the node \"", AprioriIds[id],
+             "\" is an ungauged upstream node of the node \"", id,"\"")
+      }
     })
   }
 
diff --git a/R/CreateInputsModel.GRiwrm.R b/R/CreateInputsModel.GRiwrm.R
index 8c374544ce685b18385f353fabe8256a8309270c..e316f7a2242547ea3702083ffefdf3e2a64e0966 100644
--- a/R/CreateInputsModel.GRiwrm.R
+++ b/R/CreateInputsModel.GRiwrm.R
@@ -77,7 +77,6 @@ CreateInputsModel.GRiwrm <- function(x, DatesR,
     if (err) stop(sprintf("'Qobs' column names must at least contain %s", paste(directFlowIds, collapse = ", ")))
   }
 
-
   InputsModel <- CreateEmptyGRiwrmInputsModel(x)
 
   # Qobs completion
@@ -127,6 +126,8 @@ CreateInputsModel.GRiwrm <- function(x, DatesR,
 CreateEmptyGRiwrmInputsModel <- function(griwrm) {
   InputsModel <- list()
   class(InputsModel) <- c("GRiwrmInputsModel", class(InputsModel))
+  # Update griwrm in case of manual change in model column
+  griwrm$donor <- sapply(griwrm$id, getGaugedId, griwrm = griwrm)
   attr(InputsModel, "GRiwrm") <- griwrm
   return(InputsModel)
 }
@@ -146,7 +147,7 @@ CreateEmptyGRiwrmInputsModel <- function(griwrm) {
 #' @noRd
 CreateOneGRiwrmInputsModel <- function(id, griwrm, ..., Qobs) {
   node <- griwrm[griwrm$id == id,]
-  FUN_MOD <- griwrm$model[griwrm$id == id]
+  FUN_MOD <- griwrm$model[griwrm$id == griwrm$donor[griwrm$id == id]]
 
   # Set hydraulic parameters
   UpstreamNodes <- griwrm$id[griwrm$down == id & !is.na(griwrm$down)]
@@ -193,6 +194,9 @@ CreateOneGRiwrmInputsModel <- function(id, griwrm, ..., Qobs) {
 
   # Add the model function
   InputsModel$FUN_MOD <- FUN_MOD
+  InputsModel$isUngauged <- griwrm$model[griwrm$id == id] == "Ungauged"
+  InputsModel$gaugedId <- griwrm$donor[griwrm$id == id]
+  InputsModel$hasUngaugedNodes <- hasUngaugedNodes(id, griwrm)
 
   return(InputsModel)
 }
@@ -250,3 +254,31 @@ getInputBV <- function(x, id, unset = NULL) {
   }
   return(x[, id])
 }
+
+
+#' Check if current node contains ungauged nodes that shares its parameters
+#'
+#' @param id id [character] Id of the current node
+#' @param griwrm See [CreateGRiwrm])
+#'
+#' @return A [logical], `TRUE` if the node `id` contains ungauged nodes.
+#'
+#' @noRd
+hasUngaugedNodes <- function(id, griwrm) {
+  upIds <- griwrm$id[griwrm$down == id]
+  upIds <- upIds[!is.na(upIds)]
+  # No upstream nodes
+  if(length(upIds) == 0) return(FALSE)
+  # At least one upstream node is ungauged
+  UngNodes <- griwrm$model[griwrm$id %in% upIds] == "Ungauged"
+  UngNodes <- UngNodes[!is.na(UngNodes)]
+  if(length(UngNodes) > 0 && any(UngNodes)) return(TRUE)
+  # At least one node's model is NA need to investigate next level
+  if(any(is.na(griwrm$model[griwrm$id %in% upIds]))) {
+    g <- griwrm[griwrm$id %in% upIds, ]
+    NaIds <- g$id[is.na(g$model)]
+    out <- sapply(NaIds, hasUngaugedNodes, griwrm = griwrm)
+    return(any(out))
+  }
+  return(FALSE)
+}
diff --git a/R/CreateRunOptions.GRiwrmInputsModel.R b/R/CreateRunOptions.GRiwrmInputsModel.R
index e7f503c315bfa9655944e418efa559c7389d708a..7b49faeab85ac0d216c7f85612644705449ef0e8 100644
--- a/R/CreateRunOptions.GRiwrmInputsModel.R
+++ b/R/CreateRunOptions.GRiwrmInputsModel.R
@@ -8,6 +8,7 @@ CreateRunOptions.GRiwrmInputsModel <- function(x, IniStates = NULL, ...) {
 
   for(id in names(x)) {
     RunOptions[[id]] <- CreateRunOptions(x[[id]], IniStates = IniStates[[id]], ...)
+    RunOptions[[id]]$id <- id
   }
   return(RunOptions)
 }
diff --git a/R/RunModel.Supervisor.R b/R/RunModel.Supervisor.R
index f266ef0118d5d5b90347f7e9d5f06712acea07d9..937dc40ea1f76bb9173aeea48ac04d8f43ea5501 100644
--- a/R/RunModel.Supervisor.R
+++ b/R/RunModel.Supervisor.R
@@ -36,8 +36,10 @@ RunModel.Supervisor <- function(x, RunOptions, Param, ...) {
   # Copy simulated pure runoff flows (no SD nodes) to Qupstream in downstream SD nodes
   for(id in getNoSD_Ids(x$InputsModel)) {
     downId <- x$InputsModel[[id]]$down
-    x$InputsModel[[downId]]$Qupstream[RunOptions[[downId]]$IndPeriod_Run, id] <-
-      x$OutputsModel[[id]]$Qsim_m3
+    if(!is.null(x$InputsModel[[downId]])) {
+      x$InputsModel[[downId]]$Qupstream[RunOptions[[downId]]$IndPeriod_Run, id] <-
+        x$OutputsModel[[id]]$Qsim_m3
+    }
   }
 
   # Save Qsim for step by step simulation
diff --git a/R/plot.GRiwrm.R b/R/plot.GRiwrm.R
index a35a4226e7871db438bb9b56614730ec300e70e2..1698a13cd3d740783e063e7c8ed1baa354c38109 100644
--- a/R/plot.GRiwrm.R
+++ b/R/plot.GRiwrm.R
@@ -5,6 +5,7 @@
 #' @param orientation [character] orientation of the graph. Possible values are "LR" (left-right), "RL" (right-left), "TB" (top-bottom), or "BT" (bottom-top). "LR" by default
 #' @param width [numeric] width of the resulting graphic in pixels (See [DiagrammeR::mermaid])
 #' @param height [numeric] height of the resulting graphic in pixels (See [DiagrammeR::mermaid])
+#' @param box_colors [list] containing the color used for the different types of nodes
 #' @param ... Other arguments and parameters you would like to send to JavaScript (See [DiagrammeR::mermaid])
 #'
 #' @details This function only works inside RStudio because the HTMLwidget produced by DiagrammeR
@@ -14,30 +15,53 @@
 #'
 #' @export
 #'
-#' @examples
-#' \dontrun{
-#' # Display diagram
-#' plot.GRiwrm(griwrm)
-#' # Is the same as
-#' DiagrammeR::mermaid(plot.GRiwrm(griwrm, display = FALSE), width = "100%", height = "100%")
-#' }
+#' @example man-examples/CreateGRiwrm.R
 #'
-plot.GRiwrm <- function(x, display = TRUE, orientation = "LR", width = "100%", height = "100%", ...) {
+plot.GRiwrm <- function(x,
+                        display = TRUE,
+                        orientation = "LR",
+                        width = "100%",
+                        height = "100%",
+                        box_colors = c(UpstreamUngauged = "#eef",
+                                       UpstreamGauged = "#aaf",
+                                       IntermUngauged = "#efe",
+                                       IntermGauged = "#afa",
+                                       DirectInjection = "#faa"),
+                        ...) {
+
+  stopifnot(inherits(x, "GRiwrm"),
+            is.logical(display),
+            length(display) == 1,
+            is.character(orientation),
+            length(orientation) == 1,
+            is.character(width),
+            length(width) == 1,
+            is.character(height),
+            length(height) == 1,
+            is.character(box_colors),
+            length(setdiff(names(box_colors), c("UpstreamUngauged", "UpstreamGauged",
+                                                "IntermUngauged",   "IntermGauged",
+                                                "DirectInjection"))) == 0)
   g2 <- x[!is.na(x$down),]
   nodes <- paste(
-    g2$id,
+    sprintf("id_%1$s[%1$s]", g2$id),
     "-->|",
     round(g2$length, digits = 0),
     "km|",
-    g2$down
+    sprintf("id_%1$s[%1$s]", g2$down)
   )
-  styleSD <- paste("style", unique(g2$down), "fill:#cfc")
-  if (length(g2$id[is.na(g2$model)]) > 0) {
-    styleDF <- paste("style", unique(g2$id[is.na(g2$model)]), "fill:#fcc")
-  } else {
-    styleDF <- ""
-  }
-  diagram <- paste(c(paste("graph", orientation), nodes, styleSD, styleDF), collapse = "\n")
+  node_class <- list(
+    UpstreamUngauged = x$id[!x$id %in% x$down & x$model == "Ungauged"],
+    UpstreamGauged = x$id[!x$id %in% x$down & x$model != "Ungauged" & !is.na(x$model)],
+    IntermUngauged = x$id[x$id %in% x$down & x$model == "Ungauged"],
+    IntermGauged = x$id[x$id %in% x$down & x$model != "Ungauged" & !is.na(x$model)],
+    DirectInjection = x$id[is.na(x$model)]
+  )
+  node_class <- lapply(node_class, function(x) if(length(x) > 0) paste0("id_", x))
+  node_class[sapply(node_class, is.null)] <- NULL
+  node_class <- paste("class", sapply(node_class, paste, collapse = ","), names(node_class))
+  css <- paste("classDef", names(box_colors), paste0("fill:", box_colors))
+  diagram <- paste(c(paste("graph", orientation), nodes, node_class, css), collapse = "\n\n")
   if (display) {
     DiagrammeR::mermaid(diagram = diagram, width, height, ...)
   } else {
diff --git a/R/utils.R b/R/utils.R
index ed10679196a9f12d402ef33bf5e7c1e72307d817..85fc697e8b8a8d0e337aca4f599e6aa637a82eb5 100644
--- a/R/utils.R
+++ b/R/utils.R
@@ -68,7 +68,10 @@ setDataToLocation <- function(ctrlr, sv) {
     # limit U size to the number of simulation time steps of the current supervision time step
     U <- ctrlr$U[seq.int(length(sv$ts.index)),i]
     # ! Qupstream contains warm up period and run period => the index is shifted
-    sv$InputsModel[[node]]$Qupstream[sv$ts.index0 + sv$ts.index, ctrlr$Unames[i]] <- U
+    if(!is.null(sv$InputsModel[[node]])) {
+      sv$InputsModel[[node]]$Qupstream[sv$ts.index0 + sv$ts.index,
+                                       ctrlr$Unames[i]] <- U
+    }
   })
 }
 
@@ -106,7 +109,7 @@ doSupervision <- function(supervisor) {
 #' @param Param [list] of containing model parameter values of each node of the network
 #' @noRd
 checkRunModelParameters <- function(InputsModel, RunOptions, Param) {
-  if(!inherits(InputsModel, "GRiwrmInputsModel")) stop("`InputsModel` parameter must of class 'GRiwrmRunoptions' (See ?CreateRunOptions.GRiwrmInputsModel)")
+  if(!inherits(InputsModel, "GRiwrmInputsModel")) stop("`InputsModel` parameter must of class 'GRiwrmInputsModel' (See ?CreateRunOptions.GRiwrmInputsModel)")
   if(!inherits(RunOptions, "GRiwrmRunOptions")) stop("Argument `RunOptions` parameter must of class 'GRiwrmRunOptions' (See ?CreateRunOptions.GRiwrmInputsModel)")
   if(!is.list(Param) || !all(names(InputsModel) %in% names(Param))) stop("Argument `Param` must be a list with names equal to nodes IDs")
 }
diff --git a/dev/clean_bibtex.R b/dev/clean_bibtex.R
new file mode 100644
index 0000000000000000000000000000000000000000..0c69fcef4086df99767606a59a657c7bfdce0720
--- /dev/null
+++ b/dev/clean_bibtex.R
@@ -0,0 +1,25 @@
+#' Remove unecessary fields in .bib file
+#'
+#' @param path the path of the .bib file
+#' @param pattern pattern for search files in `path`
+#' @param rm.fields ([character] [vector]) list of fields to remove
+#'
+#' @return Function used for side effect.
+#' @export
+#'
+clean_bibtex <- function(path = "./vignettes",
+                         pattern = "*.bib",
+                         rm.fields = c("abstract", "langid", "file", "keywords", "copyright", "annotation")) {
+  files <- list.files(path = path, pattern = pattern)
+  message("Found files to clean: ", paste(files, collapse = ", "))
+  lapply(files, function(f) {
+    s <- readLines(file.path(path, f))
+    n <- length(s)
+    for (rm.field in rm.fields) {
+      s <- s[!grepl(paste0("^\\s*", rm.field), s)]
+    }
+    writeLines(s, file.path(path, f))
+    message(n - length(s), " lines removed in ", f)
+  })
+  invisible()
+}
diff --git a/inst/vignettes/ParamV02.RDS b/inst/vignettes/ParamV02.RDS
new file mode 100644
index 0000000000000000000000000000000000000000..f97bfd2761f0bc9320c0438e84a6efe82ac99dff
Binary files /dev/null and b/inst/vignettes/ParamV02.RDS differ
diff --git a/inst/vignettes/ParamV03.RDS b/inst/vignettes/ParamV03.RDS
deleted file mode 100644
index 9a694eff5209fd4cef4f78e940a41353bb6e06d2..0000000000000000000000000000000000000000
Binary files a/inst/vignettes/ParamV03.RDS and /dev/null differ
diff --git a/man-examples/CreateGRiwrm.R b/man-examples/CreateGRiwrm.R
new file mode 100644
index 0000000000000000000000000000000000000000..9ef97c074a3acb9b22aba2e8b03e361548e7b3a4
--- /dev/null
+++ b/man-examples/CreateGRiwrm.R
@@ -0,0 +1,37 @@
+# Network of 2 nodes distant of 150 km:
+# - an upstream reservoir modelled as a direct flow injection (no model)
+# - a gauging station downstream a catchment of 360 km² modelled with GR4J
+db <- data.frame(id = c("Reservoir", "GaugingDown"),
+                 length = c(150, NA),
+                 down = c("GaugingDown", NA),
+                 area = c(NA, 360),
+                 model = c(NA, "RunModel_GR4J"),
+                 stringsAsFactors = FALSE)
+griwrm_basic <- CreateGRiwrm(db)
+griwrm_basic
+# Network diagram with direct flow node in red, intermediate sub-basin in green
+plot(griwrm_basic)
+
+# GR4J semi-distributed model of the Severn River
+data(Severn)
+nodes <- Severn$BasinsInfo
+nodes$model <- "RunModel_GR4J"
+str(nodes)
+# Mismatch column names are renamed to stick with GRiwrm requirements
+rename_columns <- list(id = "gauge_id",
+                       down = "downstream_id",
+                       length = "distance_downstream")
+griwrm_severn <- CreateGRiwrm(nodes, rename_columns)
+griwrm_severn
+# Network diagram with upstream basin nodes in blue, intermediate sub-basin in green
+plot(griwrm_severn)
+
+# Same model with an ungauged station at nodes 54029 and 54001
+# By default the first gauged node at downstream is used for parameter calibration (54032)
+nodes_ungauged <- nodes
+nodes_ungauged$model[nodes_ungauged$gauge_id %in% c("54029", "54001")] <- "Ungauged"
+griwrm_ungauged <- CreateGRiwrm(nodes_ungauged, rename_columns)
+# The `donor` column define which node is used for parameter calibration
+griwrm_ungauged
+# Network diagram with gauged nodes of vivid color, and ungauged nodes of dull color
+plot(griwrm_ungauged)
diff --git a/man/CreateGRiwrm.Rd b/man/CreateGRiwrm.Rd
index 012eb41bf2db3c1464698d0f7126425eb954591f..24d40194789be032f734d5425a6b9c16cc052407 100644
--- a/man/CreateGRiwrm.Rd
+++ b/man/CreateGRiwrm.Rd
@@ -37,6 +37,8 @@ node (\link{NA} for the most downstream node)
 node location in km2
 \item \code{model} (\link{character}): hydrological model to use (\link{NA} for using observed
 flow instead of a runoff model output)
+\item \code{donor} (\link{character}): node used as "donor" for the the model and the
+calibration parameters.
 }
 }
 \description{
@@ -50,93 +52,60 @@ description of their connections
 \item the identifier and the hydraulic distance to the downstream node
 (\link{character} columns \code{down} and \link{numeric} columns \code{length} in km). The
 last downstream node should have fields \code{down} and \code{length} set to \code{NA},
-\item the area of the basin (\link{numeric} column \code{area} in km2)
-\item the hydrological model to use or \link{NA} for using observed flow instead of a
-runoff model output (\link{character} column \code{model})
+\item the total area of the basin at the node location (\link{numeric} column \code{area} in km2).
+Direct injection node can have a null area defined by \code{NA}
+\item the model to use (\link{character} column \code{model}), see section below for details
+}
+\subsection{Available models in airGRiwrm}{
+
+The "model" column should be filled by one of the following:
+\itemize{
+\item One of the hydrological models available in the \emph{airGR} package defined by its
+\code{RunModel} function (i.e.: \code{RunModel_GR4J}, \code{RunModel_GR5HCemaneige}...)
+\item \code{NA} for injecting (or abstracting) a flow time series at the location of the node
+(direct flow injection)
+\item \code{Ungauged} for an ungauged node. The sub-basin inherits hydrological model and
+parameters from a "donor" sub-basin. By default the donor is the first gauged
+node at downstream
+}
 }
 }
 \examples{
-###################################################################
-# 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)
-
-## ---- 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:
+# Network of 2 nodes distant of 150 km:
+# - an upstream reservoir modelled as a direct flow injection (no model)
+# - a gauging station downstream a catchment of 360 km² modelled with GR4J
 db <- data.frame(id = c("Reservoir", "GaugingDown"),
-                 length = c(LengthHydro, NA),
+                 length = c(150, NA),
                  down = c("GaugingDown", NA),
-                 area = c(NA, BasinInfo$BasinArea),
+                 area = c(NA, 360),
                  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 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]))
+griwrm_basic <- CreateGRiwrm(db)
+griwrm_basic
+# Network diagram with direct flow node in red, intermediate sub-basin in green
+plot(griwrm_basic)
+
+# GR4J semi-distributed model of the Severn River
+data(Severn)
+nodes <- Severn$BasinsInfo
+nodes$model <- "RunModel_GR4J"
+str(nodes)
+# Mismatch column names are renamed to stick with GRiwrm requirements
+rename_columns <- list(id = "gauge_id",
+                       down = "downstream_id",
+                       length = "distance_downstream")
+griwrm_severn <- CreateGRiwrm(nodes, rename_columns)
+griwrm_severn
+# Network diagram with upstream basin nodes in blue, intermediate sub-basin in green
+plot(griwrm_severn)
+
+# Same model with an ungauged station at nodes 54029 and 54001
+# By default the first gauged node at downstream is used for parameter calibration (54032)
+nodes_ungauged <- nodes
+nodes_ungauged$model[nodes_ungauged$gauge_id \%in\% c("54029", "54001")] <- "Ungauged"
+griwrm_ungauged <- CreateGRiwrm(nodes_ungauged, rename_columns)
+# The `donor` column define which node is used for parameter calibration
+griwrm_ungauged
+# Network diagram with gauged nodes of vivid color, and ungauged nodes of dull color
+plot(griwrm_ungauged)
 }
diff --git a/man/plot.GRiwrm.Rd b/man/plot.GRiwrm.Rd
index d34e84696761155869750f00febc569b4f8ba8fe..280c22d5708d8c29b6db9a4ee4244f40b9d8e16b 100644
--- a/man/plot.GRiwrm.Rd
+++ b/man/plot.GRiwrm.Rd
@@ -10,6 +10,8 @@
   orientation = "LR",
   width = "100\%",
   height = "100\%",
+  box_colors = c(UpstreamUngauged = "#eef", UpstreamGauged = "#aaf", IntermUngauged =
+    "#efe", IntermGauged = "#afa", DirectInjection = "#faa"),
   ...
 )
 }
@@ -24,6 +26,8 @@
 
 \item{height}{\link{numeric} height of the resulting graphic in pixels (See \link[DiagrammeR:mermaid]{DiagrammeR::mermaid})}
 
+\item{box_colors}{\link{list} containing the color used for the different types of nodes}
+
 \item{...}{Other arguments and parameters you would like to send to JavaScript (See \link[DiagrammeR:mermaid]{DiagrammeR::mermaid})}
 }
 \value{
@@ -37,11 +41,41 @@ This function only works inside RStudio because the HTMLwidget produced by Diagr
 is not handled on some platforms
 }
 \examples{
-\dontrun{
-# Display diagram
-plot.GRiwrm(griwrm)
-# Is the same as
-DiagrammeR::mermaid(plot.GRiwrm(griwrm, display = FALSE), width = "100\%", height = "100\%")
-}
+# Network of 2 nodes distant of 150 km:
+# - an upstream reservoir modelled as a direct flow injection (no model)
+# - a gauging station downstream a catchment of 360 km² modelled with GR4J
+db <- data.frame(id = c("Reservoir", "GaugingDown"),
+                 length = c(150, NA),
+                 down = c("GaugingDown", NA),
+                 area = c(NA, 360),
+                 model = c(NA, "RunModel_GR4J"),
+                 stringsAsFactors = FALSE)
+griwrm_basic <- CreateGRiwrm(db)
+griwrm_basic
+# Network diagram with direct flow node in red, intermediate sub-basin in green
+plot(griwrm_basic)
+
+# GR4J semi-distributed model of the Severn River
+data(Severn)
+nodes <- Severn$BasinsInfo
+nodes$model <- "RunModel_GR4J"
+str(nodes)
+# Mismatch column names are renamed to stick with GRiwrm requirements
+rename_columns <- list(id = "gauge_id",
+                       down = "downstream_id",
+                       length = "distance_downstream")
+griwrm_severn <- CreateGRiwrm(nodes, rename_columns)
+griwrm_severn
+# Network diagram with upstream basin nodes in blue, intermediate sub-basin in green
+plot(griwrm_severn)
 
+# Same model with an ungauged station at nodes 54029 and 54001
+# By default the first gauged node at downstream is used for parameter calibration (54032)
+nodes_ungauged <- nodes
+nodes_ungauged$model[nodes_ungauged$gauge_id \%in\% c("54029", "54001")] <- "Ungauged"
+griwrm_ungauged <- CreateGRiwrm(nodes_ungauged, rename_columns)
+# The `donor` column define which node is used for parameter calibration
+griwrm_ungauged
+# Network diagram with gauged nodes of vivid color, and ungauged nodes of dull color
+plot(griwrm_ungauged)
 }
diff --git a/tests/testthat/helper_RunModel.R b/tests/testthat/helper_RunModel.R
index 7c0913f7e21f4ea40715463f180be6272550e65a..2b5b500e8743b67327376ce9b2db44c80d9e6679 100644
--- a/tests/testthat/helper_RunModel.R
+++ b/tests/testthat/helper_RunModel.R
@@ -10,57 +10,119 @@
 # https://stackoverflow.com/questions/9965577/r-copy-move-one-environment-to-another
 #' for(x in ls(e)) assign(x, get(x, e))
 #'
-setupRunModel <- function() {
-  data(Severn)
+setupRunModel <-
+  function(runInputsModel = TRUE,
+           runRunOptions = TRUE,
+           runRunModel = TRUE,
+           griwrm = NULL) {
 
-  # Format observation
-  BasinsObs <- Severn$BasinsObs
-  DatesR <- BasinsObs[[1]]$DatesR
-  PrecipTot <- cbind(sapply(BasinsObs, function(x) {x$precipitation}))
-  PotEvapTot <- cbind(sapply(BasinsObs, function(x) {x$peti}))
-  Qobs <- cbind(sapply(BasinsObs, function(x) {x$discharge_spec}))
+    data(Severn)
 
-  # Set network
-  nodes <- Severn$BasinsInfo[, c("gauge_id", "downstream_id", "distance_downstream", "area")]
-  nodes$distance_downstream <- nodes$distance_downstream
-  nodes$model <- "RunModel_GR4J"
-  griwrm <- CreateGRiwrm(nodes, list(id = "gauge_id", down = "downstream_id", length = "distance_downstream"))
+    # Format observation
+    BasinsObs <- Severn$BasinsObs
+    DatesR <- BasinsObs[[1]]$DatesR
+    PrecipTot <-
+      cbind(sapply(BasinsObs, function(x) {
+        x$precipitation
+      }))
+    PotEvapTot <- cbind(sapply(BasinsObs, function(x) {
+      x$peti
+    }))
+    Qobs <- cbind(sapply(BasinsObs, function(x) {
+      x$discharge_spec
+    }))
 
-  # Convert meteo data to SD (remove upstream areas)
-  Precip <- ConvertMeteoSD(griwrm, PrecipTot)
-  PotEvap <- ConvertMeteoSD(griwrm, PotEvapTot)
+    # Set network
+    if(is.null(griwrm)) {
+      nodes <-
+        Severn$BasinsInfo[, c("gauge_id", "downstream_id", "distance_downstream", "area")]
+      nodes$model <- "RunModel_GR4J"
+      griwrm <-
+        CreateGRiwrm(nodes,
+                     list(
+                       id = "gauge_id",
+                       down = "downstream_id",
+                       length = "distance_downstream"
+                     ))
+    }
 
-  # Calibration parameters
-  ParamMichel <- list(
-    `54057` = c(0.779999999999999, 57.9743110789593, -1.23788116619639, 0.960789439152323, 2.47147147147147),
-    `54032` = c(1.37562057772709, 1151.73462496385, -0.379248293750608, 6.2243898378232, 8.23716221550954),
-    `54001` = c(1.03, 24.7790862245877, -1.90430150145153, 21.7584023961971, 1.37837837837838),
-    `54095` = c(256.844150254651, 0.0650458497009288, 57.523675209819, 2.71809513102128),
-    `54002` = c(419.437754485522, 0.12473266292168, 13.0379482833606, 2.12230907892238),
-    `54029` = c(219.203385553954, 0.389211590110934, 48.4242150713452, 2.00300300300301)
-  )
+    # Convert meteo data to SD (remove upstream areas)
+    Precip <- ConvertMeteoSD(griwrm, PrecipTot)
+    PotEvap <- ConvertMeteoSD(griwrm, PotEvapTot)
+
+    # set up inputs
+    if (!runInputsModel)
+      return(environment())
+    InputsModel <-
+      suppressWarnings(CreateInputsModel(griwrm, DatesR, Precip, PotEvap, Qobs))
+
+    # RunOptions
+    if (!runRunOptions)
+      return(environment())
+    e <- setupRunOptions(InputsModel)
+    for (x in ls(e)) assign(x, get(x, e))
+    rm(e)
 
-  # set up inputs
-  InputsModel <- suppressWarnings(CreateInputsModel(griwrm, DatesR, Precip, PotEvap, Qobs))
+    # RunModel.GRiwrmInputsModel
+    if (!runRunModel)
+      return(environment())
+    OM_GriwrmInputs <- RunModel(InputsModel,
+                                RunOptions = RunOptions,
+                                Param = ParamMichel)
+    return(environment())
+  }
 
-  # RunOptions
+setupRunOptions <- function(InputsModel) {
   nTS <- 365
-  IndPeriod_Run <- seq(
-    length(InputsModel[[1]]$DatesR) - nTS + 1,
-    length(InputsModel[[1]]$DatesR)
-  )
-  IndPeriod_WarmUp = seq(IndPeriod_Run[1]-365,IndPeriod_Run[1]-1)
-  RunOptions <- CreateRunOptions(
-    InputsModel,
-    IndPeriod_WarmUp = IndPeriod_WarmUp,
-    IndPeriod_Run = IndPeriod_Run
-  )
+  IndPeriod_Run <- seq(length(InputsModel[[1]]$DatesR) - nTS + 1,
+                       length(InputsModel[[1]]$DatesR))
+  IndPeriod_WarmUp = seq(IndPeriod_Run[1] - 365, IndPeriod_Run[1] - 1)
+  RunOptions <- CreateRunOptions(InputsModel,
+                                 IndPeriod_WarmUp = IndPeriod_WarmUp,
+                                 IndPeriod_Run = IndPeriod_Run)
 
-  # RunModel.GRiwrmInputsModel
-  OM_GriwrmInputs <- RunModel(
-    InputsModel,
-    RunOptions = RunOptions,
-    Param = ParamMichel
+  # Calibration parameters
+  ParamMichel <- list(
+    `54057` = c(
+      0.779999999999999,
+      57.9743110789593,
+      -1.23788116619639,
+      0.960789439152323,
+      2.47147147147147
+    ),
+    `54032` = c(
+      1.37562057772709,
+      1151.73462496385,
+      -0.379248293750608,
+      6.2243898378232,
+      8.23716221550954
+    ),
+    `54001` = c(
+      1.03,
+      24.7790862245877,
+      -1.90430150145153,
+      21.7584023961971,
+      1.37837837837838
+    ),
+    `54095` = c(
+      256.844150254651,
+      0.0650458497009288,
+      57.523675209819,
+      2.71809513102128
+    ),
+    `54002` = c(
+      419.437754485522,
+      0.12473266292168,
+      13.0379482833606,
+      2.12230907892238
+    ),
+    `54029` = c(
+      219.203385553954,
+      0.389211590110934,
+      48.4242150713452,
+      2.00300300300301
+    )
   )
+
   return(environment())
 }
diff --git a/tests/testthat/test-CreateInputsCrit.R b/tests/testthat/test-CreateInputsCrit.R
index 36b0eef1f4c22cd11f832dcd3543c3c330b8b88c..f5b55d689867bb9269ddbe3f14cd42d8379cc401 100644
--- a/tests/testthat/test-CreateInputsCrit.R
+++ b/tests/testthat/test-CreateInputsCrit.R
@@ -34,6 +34,7 @@ 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))
+rm(e)
 
 context("CreateInputsCrit.GRiwrmInputsModel")
 
@@ -107,3 +108,21 @@ test_that("Lavenne criterion: wrong sub-catchment order should throw error", {
     regexp = "is not upstream the node"
   )
 })
+
+test_that("Ungauged node as Apriori node should throw an error", {
+  nodes$model[nodes$gauge_id == "54001"] <- "Ungauged"
+  griwrm <- CreateGRiwrm(
+    nodes,
+    list(id = "gauge_id", down = "downstream_id", length = "distance_downstream")
+  )
+  InputsModel <-
+    suppressWarnings(CreateInputsModel(griwrm, DatesR, Precip, PotEvap, Qobs))
+  expect_error(
+    CreateInputsCrit(InputsModel = InputsModel,
+                     RunOptions = RunOptions,
+                     Obs = Qobs[IndPeriod_Run,],
+                     AprioriIds = c("54057" = "54032", "54032" = "54001", "54001" = "54029"),
+                     transfo = "sqrt"),
+    regexp = "\"54001\" is an ungauged upstream node of the node \"54032\""
+  )
+})
diff --git a/tests/testthat/test-CreateInputsModel.R b/tests/testthat/test-CreateInputsModel.R
index 45a659b2cd4584f9f8617b51e4b9d258897057b2..4622038f1b169fe6e7352984f92559ebc5f0af0b 100644
--- a/tests/testthat/test-CreateInputsModel.R
+++ b/tests/testthat/test-CreateInputsModel.R
@@ -182,3 +182,22 @@ test_that("negative observed flow on catchment should throw error", {
   ),
   "GRiwrmInputsModel")
 })
+
+# data set up
+e <- setupRunModel(runInputsModel = FALSE)
+# 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))
+
+test_that("Ungauged node should inherits its FUN_MOD from the downstream gauged node", {
+
+  nodes$model[nodes$gauge_id == "54032"] <- "Ungauged"
+  griwrmV05 <- CreateGRiwrm(
+    nodes,
+    list(id = "gauge_id", down = "downstream_id", length = "distance_downstream")
+  )
+  IM <- suppressWarnings(
+    CreateInputsModel(griwrmV05, DatesR, Precip, PotEvap, Qobs)
+  )
+  expect_equal(IM[["54032"]]$FUN_MOD, "RunModel_GR4J")
+})
diff --git a/tests/testthat/test-RunModel.R b/tests/testthat/test-RunModel.R
index f75b408423c85c1fbac1f683efb3b4bfc93bbc64..177afc9e761bdb489f3fb4651bc3ddfe9e80038f 100644
--- a/tests/testthat/test-RunModel.R
+++ b/tests/testthat/test-RunModel.R
@@ -49,14 +49,19 @@ test_that("RunModel.Supervisor with no regulation should returns same results as
 })
 
 # Add 2 nodes to the network
-griwrm2 <- rbind(griwrm,
-                 data.frame(
-                   id = c("R1", "R2"),
-                   down = "54057",
-                   length = 100,
-                   area = NA,
-                   model = NA
-                 ))
+nodes2 <- rbind(nodes,
+                data.frame(
+                  gauge_id = c("R1", "R2"),
+                  downstream_id = "54057",
+                  distance_downstream = 100,
+                  area = NA,
+                  model = NA
+                ))
+griwrm2 <- CreateGRiwrm(nodes2,
+                        list(id = "gauge_id",
+                             down = "downstream_id",
+                             length = "distance_downstream"))
+
 # 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")
diff --git a/tests/testthat/test-createGRiwrm.R b/tests/testthat/test-createGRiwrm.R
index 653898b711c921ed086fb818023ae9074182fba9..5b0e896fc0cb48171ec88138cfbfb973802402a2 100644
--- a/tests/testthat/test-createGRiwrm.R
+++ b/tests/testthat/test-createGRiwrm.R
@@ -18,3 +18,30 @@ H5920010	602213	2427449	43824.66	La Seine à Paris [Austerlitz après création
   "GRiwrm")
 
 })
+
+test_that("NA or Ungauged nodes at downstream should throw an error", {
+  data(Severn)
+  nodes <-
+    Severn$BasinsInfo[, c("gauge_id", "downstream_id", "distance_downstream", "area")]
+  nodes$model <- "RunModel_GR4J"
+  nodes$model[nodes$gauge_id == "54057"] <- "Ungauged"
+  expect_error(CreateGRiwrm(
+    nodes,
+    list(
+      id = "gauge_id",
+      down = "downstream_id",
+      length = "distance_downstream"
+    )
+  ),
+  regexp = "downstream node")
+  nodes$model[nodes$gauge_id == "54057"] <- NA
+  expect_error(CreateGRiwrm(
+    nodes,
+    list(
+      id = "gauge_id",
+      down = "downstream_id",
+      length = "distance_downstream"
+    )
+  ),
+  regexp = "downstream node")
+})
diff --git a/tests/testthat/test-plot.R b/tests/testthat/test-plot.R
deleted file mode 100644
index 3466b0828cd73868ac9e3dea3e6f0972d4956a63..0000000000000000000000000000000000000000
--- a/tests/testthat/test-plot.R
+++ /dev/null
@@ -1,9 +0,0 @@
-test_that("plot.GRiwrm should have all styles correctly filled (#73)", {
-  data(Severn)
-  nodes <- Severn$BasinsInfo[, c("gauge_id", "downstream_id", "distance_downstream", "area")]
-  nodes$distance_downstream <- nodes$distance_downstream #je ne comprends pas cette ligne, elle semble inutile
-  nodes$model <- "RunModel_GR4J"
-  griwrm <- CreateGRiwrm(nodes, list(id = "gauge_id", down = "downstream_id", length = "distance_downstream"))
-  code_mermaid <-plot(griwrm, display = FALSE)
-  expect_length(grep("style  fill", code_mermaid), 0)
-})
diff --git a/vignettes/V02_Calibration_SD_model.Rmd b/vignettes/V02_Calibration_SD_model.Rmd
index 739edbabdbf0a7221086ceb4bc751e285d5883ac..5146c631e9daa99a9d0460e76f8a4c6699233301 100644
--- a/vignettes/V02_Calibration_SD_model.Rmd
+++ b/vignettes/V02_Calibration_SD_model.Rmd
@@ -44,7 +44,6 @@ The method used for producing the `GRiwrmInputsModel` object is detailed in the
 ```{r}
 data(Severn)
 nodes <- Severn$BasinsInfo[, c("gauge_id", "downstream_id", "distance_downstream", "area")]
-nodes$distance_downstream <- nodes$distance_downstream
 nodes$model <- "RunModel_GR4J"
 griwrm <- CreateGRiwrm(nodes, list(id = "gauge_id", down = "downstream_id", length = "distance_downstream"))
 BasinsObs <- Severn$BasinsObs
@@ -128,10 +127,6 @@ Before using the automatic calibration tool, the user needs to prepare the calib
 CalibOptions <- CreateCalibOptions(InputsModel)
 ```
 
-```{r, echo=FALSE}
-save(RunOptions, InputsCrit, CalibOptions, IndPeriod_Run, file = file.path(tempdir(), "V02.RData"))
-```
-
 ## Calibration
 
 The **airGR** calibration process is applied on each node of the `GRiwrm` network from upstream nodes to downstream nodes.
@@ -139,7 +134,7 @@ The **airGR** calibration process is applied on each node of the `GRiwrm` networ
 ```{r Calibration}
 OutputsCalib <- suppressWarnings(
   Calibration(InputsModel, RunOptions, InputsCrit, CalibOptions))
-ParamMichel <- sapply(OutputsCalib, "[[", "ParamFinalR")
+ParamV02 <- sapply(OutputsCalib, "[[", "ParamFinalR")
 ```
 
 ## Run the model with the optimized model parameters
@@ -148,7 +143,7 @@ ParamMichel <- sapply(OutputsCalib, "[[", "ParamFinalR")
 OutputsModels <- RunModel(
   InputsModel,
   RunOptions = RunOptions,
-  Param = ParamMichel
+  Param = ParamV02
 )
 ```
 
diff --git a/vignettes/V03_Open-loop_influenced_flow.Rmd b/vignettes/V03_Open-loop_influenced_flow.Rmd
index a68b78faacac587911e25e5669b47cd23b9dba23..21e069058a359bb0d0cff09797d7d2a0c74d22c0 100644
--- a/vignettes/V03_Open-loop_influenced_flow.Rmd
+++ b/vignettes/V03_Open-loop_influenced_flow.Rmd
@@ -26,20 +26,20 @@ library(airGRiwrm)
 
 ## Presentation of the study case
 
-The calibration results shown in vignette 'V02_Calibration_SD_model' for the 
-flows simulated on the Avon at Evesham (Gauging station '54002') and on the 
-Severn at Buildwas (Gauging station '54095') are not fully satisfactory, 
-especially regarding low flows. These upper basins are actually heavily 
+The calibration results shown in vignette 'V02_Calibration_SD_model' for the
+flows simulated on the Avon at Evesham (Gauging station '54002') and on the
+Severn at Buildwas (Gauging station '54095') are not fully satisfactory,
+especially regarding low flows. These upper basins are actually heavily
 influenced by impoundments and inter-basin transfers [@higgsHydrologicalChangesRiver1988].
 
-So, to cope with these influences, in this vignette, we use direct injection of 
-observed influenced flows instead of modelling natural flow with an hydrological model. 
+So, to cope with these influences, in this vignette, we use direct injection of
+observed influenced flows instead of modelling natural flow with an hydrological model.
 
 We use observation on the Avon at Evesham (Gauging station '54002') and we
 choose to do the same on the Severn at Bewdley (Gauging station '54001') as if
-the observed flow at these locations would be the observed release of a dam. 
+the observed flow at these locations would be the observed release of a dam.
 
-Please note that the flow on the Severn at Buildwas (Gauging station '54095') is 
+Please note that the flow on the Severn at Buildwas (Gauging station '54095') is
 still simulated but its flows is no longer routed to downstream.
 
 ## Conversion of a gauging station into a release spot
@@ -51,17 +51,15 @@ The creation of the `GRiwrm` object is detailed in the vignette "V01_Structure_S
 ```{r}
 data(Severn)
 nodes <- Severn$BasinsInfo[, c("gauge_id", "downstream_id", "distance_downstream", "area")]
-nodes$distance_downstream <- nodes$distance_downstream
 nodes$model <- "RunModel_GR4J"
-griwrm <- CreateGRiwrm(nodes, list(id = "gauge_id", down = "downstream_id", length = "distance_downstream"))
 ```
 
 To notify the SD model that the provided flows on a node should be directly used instead of an hydrological model, one only needs to declare its model as `NA`:
 
 ```{r}
-griwrmV03 <- griwrm
-griwrmV03$model[griwrm$id == "54002"] <- NA
-griwrmV03$model[griwrm$id == "54001"] <- NA
+nodes$model[nodes$gauge_id == "54002"] <- NA
+nodes$model[nodes$gauge_id == "54001"] <- NA
+griwrmV03 <- CreateGRiwrm(nodes, list(id = "gauge_id", down = "downstream_id", length = "distance_downstream"))
 griwrmV03
 ```
 
@@ -86,8 +84,8 @@ BasinsObs <- Severn$BasinsObs
 DatesR <- BasinsObs[[1]]$DatesR
 PrecipTot <- cbind(sapply(BasinsObs, function(x) {x$precipitation}))
 PotEvapTot <- cbind(sapply(BasinsObs, function(x) {x$peti}))
-Precip <- ConvertMeteoSD(griwrm, PrecipTot)
-PotEvap <- ConvertMeteoSD(griwrm, PotEvapTot)
+Precip <- ConvertMeteoSD(griwrmV03, PrecipTot)
+PotEvap <- ConvertMeteoSD(griwrmV03, PotEvapTot)
 Qobs <- cbind(sapply(BasinsObs, function(x) {x$discharge_spec}))
 ```
 
@@ -133,7 +131,7 @@ The **airGR** calibration process is applied on each hydrological node of the `G
 ```{r Calibration}
 OC_OL <- suppressWarnings(
   Calibration(IM_OL, RunOptions, InputsCrit, CalibOptions))
-ParamV03 <- sapply(griwrm$id, function(x) {OC_OL[[x]]$Param})
+ParamV03 <- sapply(griwrmV03$id, function(x) {OC_OL[[x]]$Param})
 ```
 
 ## Run of the model with this newly calibrated parameters
diff --git a/vignettes/V04_Closed-loop_regulated_withdrawal.Rmd b/vignettes/V04_Closed-loop_regulated_withdrawal.Rmd
index 0c0ae44cc95dcbb09c8a947e311b452ebf55daa5..e2e46c119142e3a9758df053890563b0bfeaf4f6 100644
--- a/vignettes/V04_Closed-loop_regulated_withdrawal.Rmd
+++ b/vignettes/V04_Closed-loop_regulated_withdrawal.Rmd
@@ -29,54 +29,71 @@ library(airGRiwrm)
 
 # Presentation of the case study
 
-Starting from the network and the calibration set in the vignette "V03_Open-loop_influenced_flow", we add 2 intake points for irrigation.
+Starting from the network and the calibration set in the vignette
+"V02_Calibration_SD_model", we add 2 intake points for irrigation.
 
-The following code chunk resumes the procedure of the vignette "V03_Open-loop_influenced_flow":
+## Network configuration
+
+The following code chunk resumes the procedure of the vignette
+"V02_Calibration_SD_model":
 
 ```{r load_cache}
 data(Severn)
 nodes <- Severn$BasinsInfo[, c("gauge_id", "downstream_id", "distance_downstream", "area")]
-nodes$distance_downstream <- nodes$distance_downstream
 nodes$model <- "RunModel_GR4J"
-griwrm <- CreateGRiwrm(nodes, list(id = "gauge_id", down = "downstream_id", length = "distance_downstream"))
-griwrmV03 <- griwrm
-griwrmV03$model[griwrm$id == "54002"] <- NA
-griwrmV03$model[griwrm$id == "54095"] <- NA
-griwrmV03
 ```
 
-## Network configuration
-
 The intake points are located:
 
 - on the Severn at 35 km upstream Bewdley (Gauging station '54001');
 - on the Severn at 10 km upstream Saxons Lode (Gauging station '54032').
 
-We have to add this 2 nodes in the `GRiwrm` object that describes the network:
+We have to add this 2 nodes in the network:
 
-```{r griwrm}
-griwrmV04 <- rbind(
-  griwrmV03,
+```{r updated_nodes}
+nodes <- rbind(
+  nodes,
   data.frame(
-    id = c("Irrigation1", "Irrigation2"),
-    down = c("54001", "54032"),
-    length = c(35, 10),
+    gauge_id = c("Irrigation1", "Irrigation2"),
+    downstream_id = c("54001", "54032"),
+    distance_downstream = c(35, 10),
     model = NA,
     area = NA
   )
 )
+
+nodes
+
+```
+
+And we create the `GRiwrm` object from this new network:
+
+```{r griwm}
+griwrmV04 <- CreateGRiwrm(nodes, list(id = "gauge_id", down = "downstream_id", length = "distance_downstream"))
 plot(griwrmV04)
 ```
-Blue-grey nodes figure upstream basins (rainfall-runoff modeling only) and green nodes figure intermediate basins, coupling rainfall-runoff and hydraulic routing modeling.
+
+Blue nodes figure upstream basins (rainfall-runoff modeling only) and green
+nodes figure intermediate basins, coupling rainfall-runoff and hydraulic routing modeling.
 Nodes in red color are direct injection points (positive or negative flow) in the model.
 
-It's important to notice that even if the points "Irrigation1" and "Irrigation2" are physically located on a single branch of the Severn river as well as gauging stations "54095", "54001" and "54032", nodes "Irrigation1" and "Irrigation2" are not represented on the same branch in this conceptual model. Consequently, with this network configuration, it is not possible to know the value of the flow in the Severn river at the "Irrigation1" or "Irrigation2" nodes. These values are only available in nodes "54095", "54001" and "54032" where rainfall-runoff and hydraulic routing are actually modeled.
+It's important to notice that even if the points "Irrigation1" and "Irrigation2"
+are physically located on a single branch of the Severn river as well as gauging
+stations "54095", "54001" and "54032", nodes "Irrigation1" and "Irrigation2" are
+not represented on the same branch in this conceptual model. Consequently, with
+this network configuration, it is not possible to know the value of the flow in
+the Severn river at the "Irrigation1" or "Irrigation2" nodes. These values are
+only available in nodes "54095", "54001" and "54032" where rainfall-runoff and
+hydraulic routing are actually modeled.
 
 ## Irrigation objectives and flow demand at intakes
 
 Irrigation1 covers an area of 15 km² and Irrigation2 covers an area of 30 km².
 
-The objective of these irrigation systems is to cover the rainfall deficit [@burtIrrigationPerformanceMeasures1997] with 80% of success. Below is the calculation of the 8<sup>th</sup> decile of monthly water needed given meteorological data of catchments "54001" and "54032" (unit mm/day) :
+The objective of these irrigation systems is to cover the rainfall deficit
+[@burtIrrigationPerformanceMeasures1997] with 80% of success. Below is the
+calculation of the 8<sup>th</sup> decile of monthly water needed given
+meteorological data of catchments "54001" and "54032" (unit mm/day) :
 
 ```{r monthly_water_need}
 # Formatting climatic data for CreateInputsModel (See vignette V01_Structure_SD_model for details)
@@ -85,8 +102,8 @@ DatesR <- BasinsObs[[1]]$DatesR
 PrecipTot <- cbind(sapply(BasinsObs, function(x) {x$precipitation}))
 PotEvapTot <- cbind(sapply(BasinsObs, function(x) {x$peti}))
 Qobs <- cbind(sapply(BasinsObs, function(x) {x$discharge_spec}))
-Precip <- ConvertMeteoSD(griwrm, PrecipTot)
-PotEvap <- ConvertMeteoSD(griwrm, PotEvapTot)
+Precip <- ConvertMeteoSD(griwrmV04, PrecipTot)
+PotEvap <- ConvertMeteoSD(griwrmV04, PotEvapTot)
 
 # Calculation of the water need at the sub-basin scale
 dailyWaterNeed <- PotEvap - Precip
@@ -241,7 +258,7 @@ As for the previous model, we need to set up an `GRiwrmInputsModel` object conta
 # A flow is needed for all direct injection nodes in the network
 # even if they may be overwritten after by a controller
 # The Qobs matrix is completed with 2 new columns for the new nodes
-QobsIrrig <- cbind(Qobs[, c("54002", "54095")], Irrigation1 = 0, Irrigation2 = 0)
+QobsIrrig <- cbind(Qobs, Irrigation1 = 0, Irrigation2 = 0)
 
 # Creation of the GRiwrmInputsModel object
 IM_Irrig <- CreateInputsModel(griwrmV04, DatesR, Precip, PotEvap, QobsIrrig)
@@ -346,7 +363,7 @@ CreateController(sv,
 
 # Running the simulation
 
-First we need to create a `GRiwrmRunOptions` object and load the parameters calibrated in the vignette "V03_Open-loop_influenced_flow":
+First we need to create a `GRiwrmRunOptions` object and load the parameters calibrated in the vignette "V02_Calibration_SD_model":
 
 ```{r}
 IndPeriod_Run <- seq(
@@ -357,23 +374,23 @@ IndPeriod_WarmUp = seq(1,IndPeriod_Run[1]-1)
 RunOptions <- CreateRunOptions(IM_Irrig,
                                IndPeriod_WarmUp = IndPeriod_WarmUp,
                                IndPeriod_Run = IndPeriod_Run)
-ParamV03 <- readRDS(system.file("vignettes", "ParamV03.RDS", package = "airGRiwrm"))
+ParamV02 <- readRDS(system.file("vignettes", "ParamV02.RDS", package = "airGRiwrm"))
 ```
 
 
 For running a model with a supervision, you only need to substitute `InputsModel` by a `Supervisor` in the `RunModel` function call.
 
 ```{r}
-OM_Irrig <- RunModel(sv, RunOptions = RunOptions, Param = ParamV03)
+OM_Irrig <- RunModel(sv, RunOptions = RunOptions, Param = ParamV02)
 ```
 
-Simulated flows can be extracted and plot as follows:
+Simulated flows during irrigation season can be extracted and plot as follows:
 
 ```{r}
 Qm3s <- attr(OM_Irrig, "Qm3s")
-Qm3s <- Qm3s[Qm3s$DatesR > "2003-05-25" & Qm3s$DatesR < "2003-10-05",]
+Qm3s <- Qm3s[Qm3s$DatesR > "2003-02-25" & Qm3s$DatesR < "2003-10-05",]
 oldpar <- par(mfrow=c(2,1), mar = c(2.5,4,1,1))
-plot(Qm3s[, c("DatesR", "54095", "54001", "54032")], main = "", xlab = "", ylim = c(0,40))
+plot(Qm3s[, c("DatesR", "54095", "54001", "54032")], main = "", xlab = "")
 plot(Qm3s[, c("DatesR", "Irrigation1", "Irrigation2")], main = "", xlab = "", legend.x = "bottomright")
 par(oldpar)
 ```
diff --git a/vignettes/V05_Modelling_ungauged_nodes.Rmd b/vignettes/V05_Modelling_ungauged_nodes.Rmd
new file mode 100644
index 0000000000000000000000000000000000000000..4aace25a8d5a3d82db4a3c42a14f2593b6f7c2cd
--- /dev/null
+++ b/vignettes/V05_Modelling_ungauged_nodes.Rmd
@@ -0,0 +1,194 @@
+---
+title: "Severn_05: Modelling ungauged stations"
+output: rmarkdown::html_vignette
+vignette: >
+  %\VignetteIndexEntry{Severn_05: Modelling ungauged stations}
+  %\VignetteEngine{knitr::rmarkdown}
+  %\VignetteEncoding{UTF-8}
+bibliography: airGRiwrm.bib
+---
+
+```{r, include = FALSE}
+knitr::opts_chunk$set(
+  collapse = TRUE,
+  comment = "#>",
+  fig.width = 6,
+  fig.asp = 0.68,
+  out.width = "70%",
+  fig.align = "center"
+)
+```
+
+```{r setup}
+library(airGRiwrm)
+```
+
+## Why modelling ungauged station in the semi-distributed model?
+
+Ungauged nodes in the semi-distributed model can be used to reach two different goals:
+
+- increase spatial resolution of the rain fall to improve streamflow simulation [@lobligeoisWhenDoesHigher2014].
+- simulate streamflows in location of interest for management purpose
+
+This vignette introduces the implementation in airGRiwrm of the method developped by @lobligeoisMieuxConnaitreDistribution2014 for calibrating ungauged nodes in a 
+semi-distributed model.
+
+## Presentation of the study case
+
+Using the study case of the vignette #1 and #2, we considere this time that nodes `54001` and 
+`54029` are ungauged. We simulate the streamflow at these locations by sharing 
+hydrological parameters of the gauged node `54032`.
+
+```{r network, echo = FALSE}
+mmd <- function(x, ...) {
+  # For avoiding crash of R CMD build in console mode
+  if(Sys.getenv("RSTUDIO") == "1") {
+    DiagrammeR::mermaid(x, ...)
+  }
+}
+
+mmd("
+graph LR
+id95[54095]
+id01[54001]
+id29[54029]
+
+id95 -->| 42 km| id01
+
+subgraph Shared parameters from node 54032
+id01 -->| 45 km| 54032
+id29 -->| 32 km| 54032
+end
+
+54032 -->| 15 km| 54057
+54002 -->| 43 km| 54057
+
+classDef UpUng fill:#eef
+classDef UpGau fill:#aaf
+classDef IntUng fill:#efe
+classDef IntGau fill:#afa
+classDef DirInj fill:#faa
+
+class id29 UpUng
+class 54057,54032 IntGau
+class id01 IntUng
+class id95,54002 UpGau
+")
+```
+
+Hydrological parameters at the ungauged nodes will be the same as the one at the gauged node `54032` except for the unit hydrogram parameter which depend on the area of the sub-basin. @lobligeoisMieuxConnaitreDistribution2014 provides the following conversion formula for this parameter:
+
+$$
+x_{4i} = \left( \dfrac{S_i}{S_{BV}} \right) ^ {0.3} X_4
+$$
+With $X_4$ the unit hydrogram parameter for the entire basin at `54032` which as an area of $S_{BV}$; $S_i$ the area and $x_{4i}$ the parameter for the sub-basin $i$.
+
+## Using ungauged stations in the airGRiwrm model
+
+Ungauged stations are specified by using the model "Ungauged" in the `model` column provided in the `CreateGRiwrm` function:
+
+```{r griwrm}
+data(Severn)
+nodes <- Severn$BasinsInfo[, c("gauge_id", "downstream_id", "distance_downstream", "area")]
+nodes$model <- "RunModel_GR4J"
+nodes$model[nodes$gauge_id %in% c("54029", "54001")] <- "Ungauged"
+griwrmV05 <- CreateGRiwrm(
+  nodes,
+  list(id = "gauge_id", down = "downstream_id", length = "distance_downstream")
+)
+griwrmV05
+```
+
+On the following network scheme, the ungauged nodes are cleared than gauged ones with the same color (blue for upstream nodes and green for intermediate and downstream nodes)
+
+```{r plot_network}
+plot(griwrmV05)
+```
+
+
+## Generation of the GRiwrmInputsModel object
+
+The formatting of the input data is described in the vignette "V01_Structure_SD_model". The following code chunk resumes this formatting procedure:
+
+```{r obs}
+BasinsObs <- Severn$BasinsObs
+DatesR <- BasinsObs[[1]]$DatesR
+PrecipTot <- cbind(sapply(BasinsObs, function(x) {x$precipitation}))
+PotEvapTot <- cbind(sapply(BasinsObs, function(x) {x$peti}))
+Precip <- ConvertMeteoSD(griwrmV05, PrecipTot)
+PotEvap <- ConvertMeteoSD(griwrmV05, PotEvapTot)
+Qobs <- cbind(sapply(BasinsObs, function(x) {x$discharge_spec}))
+```
+
+Then, the `GRiwrmInputsModel` object can be generated taking into account the new `GRiwrm` object:
+
+```{r InputsModel}
+IM_U <- CreateInputsModel(griwrmV05, DatesR, Precip, PotEvap, Qobs)
+```
+## Calibration of the model integrating ungauged nodes
+
+Calibration options is detailed in vignette "V02_Calibration_SD_model".
+We also apply a parameter regularization here but only where an upstream simulated catchment is available.
+
+The following code chunk resumes this procedure:
+
+```{r RunOptions}
+IndPeriod_Run <- seq(
+  which(DatesR == (DatesR[1] + 365*24*60*60)), # Set aside warm-up period
+  length(DatesR) # Until the end of the time series
+)
+IndPeriod_WarmUp = seq(1,IndPeriod_Run[1]-1)
+RunOptions <- CreateRunOptions(IM_U,
+                               IndPeriod_WarmUp = IndPeriod_WarmUp,
+                               IndPeriod_Run = IndPeriod_Run)
+InputsCrit <- CreateInputsCrit(IM_U,
+                               FUN_CRIT = ErrorCrit_KGE2,
+                               RunOptions = RunOptions, Obs = Qobs[IndPeriod_Run,],
+                               AprioriIds = c("54057" = "54032", "54032" = "54095"),
+                               transfo = "sqrt", k = 0.15
+)
+CalibOptions <- CreateCalibOptions(IM_U)
+```
+
+The **airGR** calibration process is applied on each hydrological node of the `GRiwrm` network from upstream nodes to downstream nodes but this time the calibration of the sub-basin `54032` invokes a semi-distributed model composed of the nodes `54029`, `54001` and `54032`.
+
+```{r Calibration}
+OC_U <- suppressWarnings(
+  Calibration(IM_U, RunOptions, InputsCrit, CalibOptions))
+```
+
+Hydrological parameters for sub-basins 
+
+## Run the model with the optimized model parameters
+
+The hydrologic model uses parameters herited from the calibration of the gauged sub-basin `54032` for the ungauged nodes `54001` and `54029`:
+
+```{r param}
+ParamV05 <- sapply(griwrmV05$id, function(x) {OC_U[[x]]$Param})
+dfParam <- do.call(
+  rbind, 
+  lapply(ParamV05, function(x) 
+    if(length(x)==4) {return(c(NA, x))} else return(x))
+)
+colnames(dfParam) <- c("velocity", paste0("X", 1:4))
+knitr::kable(round(dfParam, 3))
+```
+
+We can run the model with these calibrated parameters:
+
+```{r RunModel}
+OutputsModels <- RunModel(
+  IM_U,
+  RunOptions = RunOptions,
+  Param = ParamV05
+)
+```
+
+and plot the comparison of the modelled and the observed flows including on the so-called "ungauged" stations :
+
+```{r plot, fig.height = 5, fig.width = 8}
+plot(OutputsModels, Qobs = Qobs[IndPeriod_Run,], which = c("Regime", "CumFreq"))
+```
+
+
+# References
diff --git a/vignettes/airGRiwrm.bib b/vignettes/airGRiwrm.bib
index 1cde68fa214982d85147728da770a5a8f5054cb6..5b36ed23c5de349a91f7239f85b1d64d9d94dc8d 100644
--- a/vignettes/airGRiwrm.bib
+++ b/vignettes/airGRiwrm.bib
@@ -3,8 +3,9 @@
   title = {Irrigation {{Performance Measures}}: {{Efficiency}} and {{Uniformity}}},
   shorttitle = {Irrigation {{Performance Measures}}},
   author = {Burt, C. M. and Clemmens, A. J. and Strelkoff, T. S. and Solomon, K. H. and Bliesner, R. D. and Hardy, L. A. and Howell, T. A. and Eisenhauer, D. E.},
-  date = {1997-11-01},
-  journaltitle = {Journal of Irrigation and Drainage Engineering},
+  year = {1997},
+  month = nov,
+  journal = {Journal of Irrigation and Drainage Engineering},
   volume = {123},
   number = {6},
   pages = {423--442},
@@ -13,65 +14,50 @@
   doi = {10.1061/(ASCE)0733-9437(1997)123:6(423)},
   url = {https://ascelibrary.org/doi/abs/10.1061/%28ASCE%290733-9437%281997%29123%3A6%28423%29},
   urldate = {2021-03-04},
-  abstract = {It is essential to standardize the definitions and approaches to quantifying various irrigation performance measures. The ASCE Task Committee on Defining Irrigation Efficiency and Uniformity provides a comprehensive examination of various performance indices such as irrigation efficiency, application efficiency, irrigation sagacity, distribution uniformity, and others. Consistency is provided among different irrigation methods and different scales. Clarification of common points of confusion is provided, and methods are proposed whereby the accuracy of numerical values of the performance indicators can be assessed. This issue has two companion papers that provide more detailed information on statistical distribution uniformity and the accuracy of irrigation efficiency estimates.},
-  langid = {english},
-  file = {C\:\\Users\\david.dorchies\\Zotero\\storage\\D9Q9VV6J\\Burt et al. - 1997 - Irrigation Performance Measures Efficiency and Un.pdf;C\:\\Users\\david.dorchies\\Zotero\\storage\\5NLYUVSN\\(ASCE)0733-9437(1997)1236(423).html}
 }
 
 @article{coronSuiteLumpedGR2017,
   title = {The Suite of Lumped {{GR}} Hydrological Models in an {{R}} Package},
-  author = {Coron, L. and Thirel, G. and Delaigue, O. and Perrin, C. and Andréassian, V.},
-  date = {2017-08-01},
-  journaltitle = {Environmental Modelling \& Software},
-  shortjournal = {Environmental Modelling \& Software},
+  author = {Coron, L. and Thirel, G. and Delaigue, O. and Perrin, C. and Andr{\'e}assian, V.},
+  year = {2017},
+  month = aug,
+  journal = {Environmental Modelling \& Software},
   volume = {94},
   pages = {166--171},
   issn = {1364-8152},
   doi = {10.1016/j.envsoft.2017.05.002},
   url = {http://www.sciencedirect.com/science/article/pii/S1364815217300208},
   urldate = {2021-01-07},
-  abstract = {Lumped hydrological models are catchment-scale representations of the transformation of precipitation into discharge. They are widely-used tools for real-time flow forecasting, flood design and climate change impact assessment, and they are often used for training and educational purposes. This article presents an R-package, airGR, to facilitate the implementation of the GR lumped hydrological models (including GR4J) and a snow-accumulation and melt model. The package allows users to calibrate and run hourly to annual models on catchment sets and to analyse their outputs. While the core of the models is implemented in Fortran, the user can manage the input/output data within R. A number of options and plotting functions are proposed to ease automate tests and analyses of the results. The codes are flexible enough to include external models, other calibration routines or efficiency criteria. To illustrate the features of airGR, we present one application example for a French mountainous catchment.},
-  langid = {english},
-  keywords = {Calibration,Flow simulation,Hydrological modelling,Lumped models,Parsimony,R package},
-  file = {C\:\\Users\\david.dorchies\\Zotero\\storage\\J94F6IEJ\\Coron et al. - 2017 - The suite of lumped GR hydrological models in an R.pdf;C\:\\Users\\david.dorchies\\Zotero\\storage\\47JDT6WA\\S1364815217300208.html}
 }
 
-@dataset{coxonCatchmentAttributesHydrometeorological2020,
-  title = {Catchment Attributes and Hydro-Meteorological Timeseries for 671 Catchments across {{Great Britain}} ({{CAMELS}}-{{GB}})},
+@misc{coxonCatchmentAttributesHydrometeorological2020,
+  title = {Catchment Attributes and Hydro-Meteorological Timeseries for 671 Catchments across {{Great Britain}} ({{CAMELS-GB}})},
   author = {Coxon, G. and Addor, N. and Bloomfield, J.P. and Freer, J. and Fry, M. and Hannaford, J. and Howden, N.J.K. and Lane, R. and Lewis, M. and Robinson, E.L. and Wagener, T. and Woods, R.},
-  date = {2020},
+  year = {2020},
   publisher = {{NERC Environmental Information Data Centre}},
   doi = {10.5285/8344E4F3-D2EA-44F5-8AFA-86D2987543A9},
   url = {https://catalogue.ceh.ac.uk/id/8344e4f3-d2ea-44f5-8afa-86d2987543a9},
   urldate = {2020-12-18},
-  abstract = {This dataset provides hydro-meteorological timeseries and landscape attributes for 671 catchments across Great Britain. It collates river flows, catchment attributes and catchment boundaries from the UK National River Flow Archive together with a suite of new meteorological timeseries and catchment attributes. Daily timeseries for the time period 1st October 1970 to the 30th September 2015 are provided for a range of hydro-meteorological data (including rainfall, potential evapotranspiration, temperature, radiation, humidity and flow). A comprehensive set of catchment attributes are quantified describing a range of catchment characteristics including topography, climate, hydrology, land cover, soils, hydrogeology, human influences and discharge uncertainty. This dataset is intended for the community as a freely available, easily accessible dataset to use in a wide range of environmental data and modelling analyses. A research paper (Coxon et al, CAMELS-GB: Hydrometeorological time series and landscape attributes for 671 catchments in Great Britain) describing the dataset in detail will be made available in Earth System Science Data (https://www.earth-system-science-data.net/).},
-  editora = {Coxon, Gemma and Environmental Information Data Centre},
-  editoratype = {collaborator},
-  langid = {english},
-  keywords = {Hydrology}
+  collaborator = {Coxon, Gemma and Environmental Information Data Centre},
 }
 
-@thesis{dehayEtudeImpactChangement2012,
-  type = {other},
-  title = {Etude de l'impact du changement climatique sur la gestion des lacs-réservoirs de la Seine},
+@phdthesis{dehayEtudeImpactChangement2012,
+  type = {{other}},
+  title = {{Etude de l'impact du changement climatique sur la gestion des lacs-r\'eservoirs de la Seine}},
   author = {Dehay, F.},
-  date = {2012},
+  year = {2012},
   pages = {74},
-  institution = {{Diplôme d'ingénieur de l'ENGEES ,Strasbourg}},
   url = {https://hal.inrae.fr/hal-02597326},
   urldate = {2021-02-12},
-  abstract = {Dans le cadre du projet européen Climaware, une modélisation du bassin versant de la Seine avec pour exutoire Paris a été réalisée afin d’étudier l’effet du changement climatique sur les règles de gestion des quatre lacs-réservoirs de la Seine (lac Aube, lac Marne, lac Seine, lac Pannecière). Il s’agit du modèle TGR de type GR, dans un premier temps réalisé et calé sans prendre en compte les quatre lacs-réservoirs. Suivant certaines conditions, telles que la courbe de gestion de ces lacs et leurs volumes maximum et minimum admissibles, il a fallu les intégrer au modèle. Différents cas ont dû être déterminés auparavant, selon les particularités des lacs. Il faut reproduire au mieux les effets des lacs, leur courbe de volume et les débits dans les rivières, afin d’avoir un modèle le plus exact possible. Les chroniques de débits utilisées pour son calage sont celles des débits naturalisés, débits mesurés desquels l’influence des lacs a été effacée. Les autres actions anthropiques (prélèvements AEP…) sont présentes. Les indicateurs de performance indiquant que le modèle était suffisamment proche de la réalité, il a alors été possible de passer à la phase suivante, c'est-à-dire la modélisation avec les forçages des modèles climatiques du GIEC (Groupe d’experts Intergouvernemental sur l’Evolution du Climat). Ces simulations doivent permettre d’établir une tendance de l’effet des lacs en temps futur par rapport au temps présent. Pour cela, quatorze ensembles de données fournies par le GIEC (sept en temps présent et sept en temps futur) ont été utilisées dans les simulations. De ces simulations, il semble apparaitre que le futur sera plus sec que le présent, avec des crues mieux absorbées et des étiages plus sévères, que les dépassements du débit de référence diminuent sur les rivières Aube et Marne, et que, si leurs causes restent inchangées pour la Marne, elles évoluent pour les autres lacs.},
-  langid = {french},
-  file = {C\:\\Users\\david.dorchies\\Zotero\\storage\\ZV8PCCIB\\Dehay - 2012 - Etude de l'impact du changement climatique sur la .pdf;C\:\\Users\\david.dorchies\\Zotero\\storage\\4NWNXZKR\\hal-02597326.html}
+  school = {Dipl\^ome d'ing\'enieur de l'ENGEES ,Strasbourg},
 }
 
 @article{delavenneRegularizationApproachImprove2019,
   ids = {lavenneRegularizationApproachImprove2019a},
   title = {A {{Regularization Approach}} to {{Improve}} the {{Sequential Calibration}} of a {{Semidistributed Hydrological Model}}},
-  author = {de Lavenne, Alban and Andréassian, Vazken and Thirel, Guillaume and Ramos, Maria-Helena and Perrin, Charles},
-  options = {useprefix=true},
-  date = {2019},
-  journaltitle = {Water Resources Research},
+  author = {{de Lavenne}, Alban and Andr{\'e}assian, Vazken and Thirel, Guillaume and Ramos, Maria-Helena and Perrin, Charles},
+  year = {2019},
+  journal = {Water Resources Research},
   volume = {55},
   number = {11},
   pages = {8821--8839},
@@ -79,19 +65,15 @@
   doi = {10.1029/2018WR024266},
   url = {https://agupubs.onlinelibrary.wiley.com/doi/abs/10.1029/2018WR024266},
   urldate = {2021-06-07},
-  abstract = {In semidistributed hydrological modeling, sequential calibration usually refers to the calibration of a model by considering not only the flows observed at the outlet of a catchment but also the different gauging points inside the catchment from upstream to downstream. While sequential calibration aims to optimize the performance at these interior gauged points, we show that it generally fails to improve performance at ungauged points. In this paper, we propose a regularization approach for the sequential calibration of semidistributed hydrological models. It consists in adding a priori information on optimal parameter sets for each modeling unit of the semidistributed model. Calibration iterations are then performed by jointly maximizing simulation performance and minimizing drifts from the a priori parameter sets. The combination of these two sources of information is handled by a parameter k to which the method is quite sensitive. The method is applied to 1,305 catchments in France over 30 years. The leave-one-out validation shows that, at locations considered as ungauged, model simulations are significantly improved (over all the catchments, the median KGE criterion is increased from 0.75 to 0.83 and the first quartile from 0.35 to 0.66), while model performance at gauged points is not significantly impacted by the use of the regularization approach. Small catchments benefit most from this calibration strategy. These performances are, however, very similar to the performances obtained with a lumped model based on similar conceptualization.},
-  langid = {english},
-  keywords = {regularization,semidistributed model,stepwise calibration,ungauged basins},
-  annotation = {\_eprint: https://agupubs.onlinelibrary.wiley.com/doi/pdf/10.1029/2018WR024266},
-  file = {C\:\\Users\\david.dorchies\\Zotero\\storage\\6V6ZZUH4\\Lavenne et al. - 2019 - A Regularization Approach to Improve the Sequentia.pdf;C\:\\Users\\david.dorchies\\Zotero\\storage\\ZDCSQPXK\\2018WR024266.html}
 }
 
 @article{dorchiesClimateChangeImpacts2014,
   title = {Climate Change Impacts on Multi-Objective Reservoir Management: Case Study on the {{Seine River}} Basin, {{France}}},
   shorttitle = {Climate Change Impacts on Multi-Objective Reservoir Management},
-  author = {Dorchies, David and Thirel, Guillaume and Jay-Allemand, Maxime and Chauveau, Mathilde and Dehay, Florine and Bourgin, Pierre-Yves and Perrin, Charles and Jost, Claudine and Rizzoli, Jean-Louis and Demerliac, Stéphane and Thépot, Régis},
-  date = {2014-07-03},
-  journaltitle = {International Journal of River Basin Management},
+  author = {Dorchies, David and Thirel, Guillaume and {Jay-Allemand}, Maxime and Chauveau, Mathilde and Dehay, Florine and Bourgin, Pierre-Yves and Perrin, Charles and Jost, Claudine and Rizzoli, Jean-Louis and Demerliac, St{\'e}phane and Th{\'e}pot, R{\'e}gis},
+  year = {2014},
+  month = jul,
+  journal = {International Journal of River Basin Management},
   volume = {12},
   number = {3},
   pages = {265--283},
@@ -99,59 +81,54 @@
   doi = {10.1080/15715124.2013.865636},
   url = {http://dx.doi.org/10.1080/15715124.2013.865636},
   urldate = {2015-04-15},
-  abstract = {Adaptation strategies will be needed to cope with the hydrological consequences of projected climate change. In this perspective, the management of many artificial reservoirs will have to be adapted to continue to fulfil downstream objectives (e.g. flow regulation). This study evaluates the sustainability of the management rules of the artificial reservoirs on the Seine River basin, France, under climate change scenarios. The Seine River basin at Paris (43,800 km2) has major socio-economic stakes for France, and the consequences of droughts and floods may be dramatic. In this context, four large multi-purpose reservoirs were built on the basin during the twentieth century for low-flow augmentation and flood alleviation. A hydrological modelling chain was designed to explicitly account for reservoir management rules. It was calibrated in current conditions and then fed by the outputs of seven climate models in present and future conditions, forced by the A1B IPCC scenario, downscaled using a weather-type method and statistically bias-corrected. The results show that the hydrological model performs quite well in current conditions. The simulations made in present and future conditions indicate a decrease in water availability and summer low flows, but no significant trends in high flows. Simulations also indicate that there is room for progress in the current multi-purpose management of reservoirs and that it would be useful to define proper adaptation strategies.},
-  annotation = {00002},
-  file = {C\:\\Users\\david.dorchies\\Zotero\\storage\\IXAF3NWQ\\Dorchies et al. - 2014 - Climate change impacts on multi-objective reservoi.pdf;C\:\\Users\\david.dorchies\\Zotero\\storage\\9TFDSBU5\\15715124.2013.html}
 }
 
 @article{dorchiesClimateChangeImpacts2016,
   title = {Climate Change Impacts on Water Resources and Reservoir Management in the {{Seine}} River Basin ({{France}})},
-  author = {Dorchies, David and Thirel, Guillaume and Perrin, Charles and Bader, Jean-Claude and Thepot, Régis and Rizzoli, Jean-Louis and Jost, Claudine and Demerliac, Stéphane},
-  date = {2016-10},
-  journaltitle = {La Houille Blanche},
+  author = {Dorchies, David and Thirel, Guillaume and Perrin, Charles and Bader, Jean-Claude and Thepot, R{\'e}gis and Rizzoli, Jean-Louis and Jost, Claudine and Demerliac, St{\'e}phane},
+  year = {2016},
+  month = oct,
+  journal = {La Houille Blanche},
   number = {5},
   pages = {32--37},
   issn = {0018-6368, 1958-5551},
   doi = {10.1051/lhb/2016047},
   url = {http://www.shf-lhb.org/10.1051/lhb/2016047},
   urldate = {2018-01-04},
-  file = {C\:\\Users\\david.dorchies\\Zotero\\storage\\M2MAKRGI\\Dorchies et al. - 2016 - Climate change impacts on water resources and rese.pdf}
 }
 
 @article{graftonParadoxIrrigationEfficiency2018,
   title = {The Paradox of Irrigation Efficiency},
   author = {Grafton, R. Q. and Williams, J. and Perry, C. J. and Molle, F. and Ringler, C. and Steduto, P. and Udall, B. and Wheeler, S. A. and Wang, Y. and Garrick, D. and Allen, R. G.},
-  date = {2018-08-24},
-  journaltitle = {Science},
+  year = {2018},
+  month = aug,
+  journal = {Science},
   volume = {361},
   number = {6404},
-  eprint = {30139857},
-  eprinttype = {pmid},
   pages = {748--750},
   publisher = {{American Association for the Advancement of Science}},
   issn = {0036-8075, 1095-9203},
   doi = {10.1126/science.aat9314},
   url = {https://science.sciencemag.org/content/361/6404/748},
   urldate = {2021-03-04},
-  abstract = {Higher efficiency rarely reduces water consumption Higher efficiency rarely reduces water consumption},
-  langid = {english},
-  file = {C\:\\Users\\david.dorchies\\Zotero\\storage\\VIHQIB84\\Grafton et al. - 2018 - The paradox of irrigation efficiency.pdf;C\:\\Users\\david.dorchies\\Zotero\\storage\\XDKSCJIX\\748.html}
+  chapter = {Policy Forum},
+  pmid = {30139857},
 }
 
-@report{gustardStudyCompensationFlows1987,
+@techreport{gustardStudyCompensationFlows1987,
   title = {A Study of Compensation Flows in the {{UK}}},
   author = {Gustard, Alan and Cole, Gwyneth and Marshall, David and Bayliss, Adrian},
-  date = {1987-11},
+  year = {1987},
+  month = nov,
   pages = {170},
   institution = {{Institute of Hydrology}},
-  file = {C\:\\Users\\david.dorchies\\Zotero\\storage\\Z3VSBM2Y\\Gustard et al. - 1987 - A study of compensation flows in the UK.pdf}
 }
 
 @article{higgsHydrologicalChangesRiver1988,
   title = {Hydrological Changes and River Regulation in the {{UK}}},
   author = {Higgs, Gary and Petts, Geoff},
-  date = {1988},
-  journaltitle = {Regulated Rivers: Research \& Management},
+  year = {1988},
+  journal = {Regulated Rivers: Research \& Management},
   volume = {2},
   number = {3},
   pages = {349--368},
@@ -159,26 +136,21 @@
   doi = {10.1002/rrr.3450020312},
   url = {https://onlinelibrary.wiley.com/doi/abs/10.1002/rrr.3450020312},
   urldate = {2020-12-26},
-  abstract = {Water levels of streams and rivers in the United Kingdom have been regulated by weirs for more than one thousand years, but regulation of the flow regime by impoundments began in the latter half on the 19th Century. Organized river flow measurements were not undertaken until 1935, and today the average record length is about 20 years. Only three gauging stations have provided data suitable for pre- and post-impoundment comparisons. Other studies have relied on the comparison of regulated and naturalized discharges. In either case climate and land-use changes make evaluation of the hydrological effect of impoundments problematic. This paper reviews research on hydrological changes due to river regulation in the UK, and presents a case study of the River Severn to evaluate the influence of Clywedog Reservoir on flood magnitude and frequency. Consequent upon dam completion, on average, median flows have been reduced by about 50per cent; mean annual floods have been reduced by about 30per cent; and low flows have been maintained at about 22 per cent higher than the natural Q95 discharge. However, marked differences exist between rivers. The direct effect of reservoir compensation flows and the indirect effect of inter basin transfers for supply have significantly increased minimum flows in most rivers, although in the case of the latter this involves the discharge of treated effluents. In contrast, the effects of impoundments on flood magnitude and frequency is less clear and on the River Severn, at least, changes in flood hydrology during the past two decades are shown to be more related to climate change than to river regulation.},
-  langid = {english},
-  keywords = {Dry weather flow,Floods,Flow regime},
-  annotation = {\_eprint: https://onlinelibrary.wiley.com/doi/pdf/10.1002/rrr.3450020312},
-  file = {C\:\\Users\\david.dorchies\\Zotero\\storage\\Q4EWWR7A\\Higgs et Petts - 1988 - Hydrological changes and river regulation in the U.pdf;C\:\\Users\\david.dorchies\\Zotero\\storage\\CI9TWW3V\\rrr.html}
 }
 
-@report{hydratecActualisationBaseDonnees2011a,
-  title = {Actualisation de La Base de Données Des Débits Journaliers ‘Naturalisés’ - {{Phase}} 2.},
+@techreport{hydratecActualisationBaseDonnees2011,
+  title = {Actualisation de La Base de Donn\'ees Des D\'ebits Journaliers `Naturalis\'es' - {{Phase}} 2.},
   author = {Hydratec},
-  date = {2011},
+  year = {2011},
   number = {26895 - LME/TL},
   pages = {31}
 }
 
 @article{jolleyLargeScaleGridBasedHydrological1996,
-  title = {A {{Large}}-{{Scale Grid}}-{{Based Hydrological Model}} of the {{Severn}} and {{Thames Catchments}}},
+  title = {A {{Large-Scale Grid-Based Hydrological Model}} of the {{Severn}} and {{Thames Catchments}}},
   author = {Jolley, T. J. and Wheater, H. S.},
-  date = {1996},
-  journaltitle = {Water and Environment Journal},
+  year = {1996},
+  journal = {Water and Environment Journal},
   volume = {10},
   number = {4},
   pages = {253--262},
@@ -186,19 +158,14 @@
   doi = {10.1111/j.1747-6593.1996.tb00043.x},
   url = {https://onlinelibrary.wiley.com/doi/abs/10.1111/j.1747-6593.1996.tb00043.x},
   urldate = {2020-12-26},
-  abstract = {This paper addresses the issues of scale and appropriate model complexity for large-scale hydrological models. A grid-based hydrological model, which employs the UK Meteorological Office Rainfall and Evaporation Calculation System, is applied to the Severn and Thames catchments using a grid scale of 40 km, and is shown to reproduce the observed mean annual runoff over a 10-year period to within 6\% with no prior calibration. The variation in the model performance is strongly correlated with the linearity of the annual rainfall/runoff relationship and a climate index. At the monthly scale, runoff routing becomes significant, and the introduction of a two-parameter routeing algorithm significantly improves the monthly runoff simulations giving efficiencies of 90\% and 88\% for the Severn and Thames respectively. The results provide guidance to climate modellers looking for efficient and robust land-surface parameterizations, and indicate the potential application of such a modelling scheme to water resource managers.},
-  langid = {english},
-  keywords = {Climate models,runoff,Severn,Thames,water resources,water-balance model},
-  annotation = {\_eprint: https://onlinelibrary.wiley.com/doi/pdf/10.1111/j.1747-6593.1996.tb00043.x},
-  file = {C\:\\Users\\david.dorchies\\Zotero\\storage\\NIH9WIPD\\Jolley et Wheater - 1996 - A Large-Scale Grid-Based Hydrological Model of the.pdf;C\:\\Users\\david.dorchies\\Zotero\\storage\\2T597AZG\\j.1747-6593.1996.tb00043.html}
 }
 
 @article{klaarDevelopingHydroecologicalModels2014,
   title = {Developing Hydroecological Models to Inform Environmental Flow Standards: A Case Study from {{England}}},
   shorttitle = {Developing Hydroecological Models to Inform Environmental Flow Standards},
   author = {Klaar, Megan J. and Dunbar, Michael J. and Warren, Mark and Soley, Rob},
-  date = {2014},
-  journaltitle = {WIREs Water},
+  year = {2014},
+  journal = {WIREs Water},
   volume = {1},
   number = {2},
   pages = {207--217},
@@ -206,17 +173,30 @@
   doi = {10.1002/wat2.1012},
   url = {https://onlinelibrary.wiley.com/doi/abs/10.1002/wat2.1012},
   urldate = {2021-03-04},
-  abstract = {The concept of defining environmental flow regimes to balance the provision of water resources for both human and environmental needs has gained wide recognition. As the authority responsible for water resource management within England, the Environment Agency (EA) uses the Environmental Flow Indicator (EFI), which represents an allowable percentage deviation from the natural flow to determine where water may be available for new abstractions. In a simplified form, the EFI has been used as the hydrological supporting component of Water Framework Directive classification, to flag where hydrological alteration may be contributing to failure to achieve good ecological status, and to guide further ecological investigation. As the primary information source for the EFI was expert opinion, the EA aims to improve the evidence base linking flow alteration and ecological response, and to use this evidence to develop improved environmental flow criteria and implementation tools. Such tools will be required to make predictions at locations with no or limited ecological monitoring data. Hence empirical statistical models are required that provide a means to describe observed variation in ecological sensitivity to flow change. Models must also strike a balance between generic and local relationships. Multilevel (mixed effects) regression models provide a rich set of capabilities suitable for this purpose. Three brief examples of the application of these techniques in defining empirical relationships between flow alteration and ecological response are provided. Establishment of testable hydrological–ecological relationships provides the framework for improving data collection, analysis, and ultimately water resources management models. This article is categorized under: Water and Life {$>$} Conservation, Management, and Awareness},
-  langid = {english},
-  annotation = {\_eprint: https://onlinelibrary.wiley.com/doi/pdf/10.1002/wat2.1012},
-  file = {C\:\\Users\\david.dorchies\\Zotero\\storage\\RNDY5IW9\\wat2.html}
+}
+
+@article{laganierCouplingHydrologicHydraulic2014,
+  title = {A Coupling of Hydrologic and Hydraulic Models Appropriate for the Fast Floods of the {{Gardon River}} Basin ({{France}})},
+  author = {Laganier, O. and Ayral, P. A. and Salze, D. and Sauvagnargues, S.},
+  year = {2014},
+  month = nov,
+  journal = {Natural Hazards and Earth System Sciences},
+  volume = {14},
+  number = {11},
+  pages = {2899--2920},
+  publisher = {{Copernicus GmbH}},
+  issn = {1561-8633},
+  doi = {10.5194/nhess-14-2899-2014},
+  url = {https://nhess.copernicus.org/articles/14/2899/2014/},
+  urldate = {2022-06-10},
 }
 
 @article{leleuRefoundingNationalInformation2014,
   title = {Re-Founding the National Information System Designed to Manage and Give Access to Hydrometric Data},
   author = {Leleu, Isabelle and Tonnelier, Isabelle and Puechberty, Rachel and Gouin, Philippe and Viquendi, Isabelle and Cobos, Laurent and Foray, Anouck and Baillon, Martine and Ndima, Pierre-Olivier},
-  date = {2014-02-01},
-  journaltitle = {La Houille Blanche},
+  year = {2014},
+  month = feb,
+  journal = {La Houille Blanche},
   volume = {100},
   number = {1},
   pages = {25--32},
@@ -225,18 +205,43 @@
   doi = {10.1051/lhb/2014004},
   url = {https://doi.org/10.1051/lhb/2014004},
   urldate = {2021-05-31},
-  keywords = {banque Hydro,base de données,data base,eau,hydrologie,hydrology,hydrométrie,hydrometry,information system,système d'information,water},
-  annotation = {\_eprint: https://doi.org/10.1051/lhb/2014004},
-  file = {C\:\\Users\\david.dorchies\\Zotero\\storage\\M5PLGR49\\Leleu et al. - 2014 - Re-founding the national information system design.pdf;C\:\\Users\\david.dorchies\\Zotero\\storage\\SWI2NVWP\\2014004.html}
+}
+
+@phdthesis{lobligeoisMieuxConnaitreDistribution2014,
+  title = {{Mieux conna\^itre la distribution spatiale des pluies am\'eliore-t-il la mod\'elisation des crues ? Diagnostic sur 181 bassins versants fran\c{c}ais}},
+  shorttitle = {{Mieux conna\^itre la distribution spatiale des pluies am\'eliore-t-il la mod\'elisation des crues ?}},
+  author = {Lobligeois, Florent},
+  year = {2014},
+  month = mar,
+  url = {https://pastel.archives-ouvertes.fr/tel-01134990/document},
+  urldate = {2017-04-06},
+  school = {AgroParisTech},
+}
+
+@article{lobligeoisWhenDoesHigher2014,
+  title = {When Does Higher Spatial Resolution Rainfall Information Improve Streamflow Simulation? {{An}} Evaluation Using 3620 Flood Events},
+  shorttitle = {When Does Higher Spatial Resolution Rainfall Information Improve Streamflow Simulation?},
+  author = {Lobligeois, F. and Andr{\'e}assian, V. and Perrin, C. and Tabary, P. and Loumagne, C.},
+  year = {2014},
+  month = feb,
+  journal = {Hydrology and Earth System Sciences},
+  volume = {18},
+  number = {2},
+  pages = {575--594},
+  publisher = {{Copernicus GmbH}},
+  issn = {1027-5606},
+  doi = {10.5194/hess-18-575-2014},
+  url = {https://hess.copernicus.org/articles/18/575/2014/},
+  urldate = {2022-07-19},
 }
 
 @article{reynardFloodCharacteristicsLarge2001,
   title = {The {{Flood Characteristics}} of {{Large U}}.{{K}}. {{Rivers}}: {{Potential Effects}} of {{Changing Climate}} and {{Land Use}}},
   shorttitle = {The {{Flood Characteristics}} of {{Large U}}.{{K}}. {{Rivers}}},
   author = {Reynard, N. S. and Prudhomme, C. and Crooks, S. M.},
-  date = {2001-02-01},
-  journaltitle = {Climatic Change},
-  shortjournal = {Climatic Change},
+  year = {2001},
+  month = feb,
+  journal = {Climatic Change},
   volume = {48},
   number = {2},
   pages = {343--359},
@@ -244,9 +249,6 @@
   doi = {10.1023/A:1010735726818},
   url = {https://doi.org/10.1023/A:1010735726818},
   urldate = {2020-12-26},
-  abstract = {A continuous flow simulation model(CLASSIC) has been used to assess the potential impactof climate and land use changes on the flood regimesof large U.K. catchments. Climate change scenarios,based on the HadCM2 experiments from the HadleyCentre, are applied to the Severn and Thames rivers.The analysis shows that, for the 2050s, the climatechange scenarios result in an increase in both thefrequency and magnitude of flooding events in theserivers. The various ways of applying the rainfallscenario can have a significant effect on thesegeneral conclusions, although generally do not affecteither the direction or consistency of the changes.While ‘best guess’ land use changes show little impacton flood response, a 50\% increase in forest covercould counter-act the impact of climate change. Aswould be expected, a large change in the urban coverof the catchments does have a large effect on theflood regimes, increasing both the frequency andmagnitude of floods significantly beyond the changesdue to climate alone. Further research is requiredinto the potential impacts of seasonal changes in thedaily rainfall and potential evaporation regimes, landuse changes and the interaction between the two.},
-  langid = {english},
-  file = {C\:\\Users\\david.dorchies\\Zotero\\storage\\PZTI9ZQE\\Reynard et al. - 2001 - The Flood Characteristics of Large U.K. Rivers Po.pdf}
 }
 
 @incollection{secklerConceptEfficiencyWaterresources2003,
@@ -254,50 +256,43 @@
   booktitle = {Water Productivity in Agriculture: Limits and Opportunities for Improvement},
   author = {Seckler, D. and Molden, D. and Sakthivadivel, R.},
   editor = {Kijne, J. W. and Barker, R. and Molden, D.},
-  date = {2003},
+  year = {2003},
   pages = {37--51},
   publisher = {{CABI}},
-  location = {{Wallingford}},
+  address = {{Wallingford}},
   doi = {10.1079/9780851996691.0037},
   url = {http://www.cabi.org/cabebooks/ebook/20033158279},
   urldate = {2021-03-04},
   isbn = {978-0-85199-669-1},
-  langid = {english},
-  file = {C\:\\Users\\david.dorchies\\Zotero\\storage\\FM69CIK3\\Seckler et al. - 2003 - The concept of efficiency in water-resources manag.pdf}
 }
 
 @article{terrierStreamflowNaturalizationMethods2020,
   title = {Streamflow Naturalization Methods: A Review},
   shorttitle = {Streamflow Naturalization Methods},
-  author = {Terrier, Morgane and Perrin, Charles and de Lavenne, Alban and Andréassian, Vazken and Lerat, Julien and Vaze, Jai},
-  options = {useprefix=true},
-  date = {2020-11-26},
-  journaltitle = {Hydrological Sciences Journal},
-  shortjournal = {Hydrological Sciences Journal},
+  author = {Terrier, Morgane and Perrin, Charles and {de Lavenne}, Alban and Andr{\'e}assian, Vazken and Lerat, Julien and Vaze, Jai},
+  year = {2020},
+  month = nov,
+  journal = {Hydrological Sciences Journal},
   pages = {1--25},
   issn = {0262-6667, 2150-3435},
   doi = {10.1080/02626667.2020.1839080},
   url = {https://www.tandfonline.com/doi/full/10.1080/02626667.2020.1839080},
   urldate = {2021-01-06},
-  abstract = {Over the past few decades, several naturalization methods have been developed for removing anthropogenic influences from streamflow time series, to the point that naturalized flows are often considered true natural flows in many studies. However, such trust in a particular naturalization method does not expose the assumptions underlying the method, nor does it quantifies the associated uncertainty. This review provides an overview of streamflow naturalization approaches. The terminology associated with naturalization is discussed, and a classification of naturalization methods according to their data requirements and main assumptions is proposed. A large set of studies developing or applying naturalization methods are reviewed, and the main challenges associated with the methods applied are assessed. To give a more concrete example, a focus is made on studies conducted in France over the last decade, which applied naturalization methods to estimate water extraction limits in rivers.},
-  langid = {english},
-  file = {C\:\\Users\\david.dorchies\\Zotero\\storage\\6KKQ9H7A\\Terrier et al. - 2020 - Streamflow naturalization methods a review.pdf}
 }
 
-@report{theobaldClimAwareImpactsClimate2014a,
+@techreport{theobaldClimAwareImpactsClimate2014a,
   title = {{{ClimAware}}: Impacts of Climate Change on Water Resources Management. {{Regional}} Strategies and European View. {{Final Report}}},
-  author = {Theobald, S. and Träbing, K. and Kehr, K. and Aufenanger, V. and Flörke, M. and Schneider, C. and Perrin, C. and Thirel, G. and Chauveau, M. and Dehay, F. and Dorchies, D. and Ficchì, A. and Jay-Allemand, M. and Thépot, R. and Démerliac, S and Jost, C. and Lamaddalena, N. and D'Agostino, D. and Scardigno, A.},
-  date = {2014},
+  author = {Theobald, S. and Tr{\"a}bing, K. and Kehr, K. and Aufenanger, V. and Fl{\"o}rke, M. and Schneider, C. and Perrin, C. and Thirel, G. and Chauveau, M. and Dehay, F. and Dorchies, D. and Ficch{\`i}, A. and {Jay-Allemand}, M. and Th{\'e}pot, R. and D{\'e}merliac, S and Jost, C. and Lamaddalena, N. and D'Agostino, D. and Scardigno, A.},
+  year = {2014},
   pages = {208},
   url = {http://irsteadoc.irstea.fr/cemoa/PUB00040932},
-  abstract = {The main objectives of the project have been addressed by combining a European modelling approach with case study analysis and regional (local) knowledge of water demand and water availability considering climate change as well as socio-economic developments. An integrated assessment for entire Europe was performed under the consideration of different scenarios and cli-mate change projections. This large-scale perspective allows indicating regions which are po¬ten-tially vulnerable to climate change and furthermore to identify regional adaptation measures which could be promoted at the EU level. Additionally three case studies were selected across Europe to in¬vestigate changes in hydrologic regimes, water availability and sectoral water use. These case stu¬dies are focusing on three different water management issues in three different regions. In the first case study, the influence of climate change on the hydromorphological conditions according to the WFD were evaluated for a section of the Eder River (Germany). The objective of this case study was to examine whether the environmental WFD objectives can be achieved in a typical river section considering climate change impacts. The second case study investigated water management, especially drinking water provision, and flood alleviation in the Seine river basin (France), which is partly based on the operation of artificial reservoirs. Scenarios were developed linking the impact of climate change on water resources and changes in water demand and its management. The third case study assesses the quantitative effects of climate change on water balance components and water use in the agricultural sector of the Italian Apulia region, in order to support the adoption of adaptation measures. Actually, in the Apulia region agriculture still remains the primary user of water and the primary economical resource. / Les principaux objectifs du projet ont été adressés en combinant une approche de modélisation européenne avec une analyse de cas d\&\#8217;études et la connaissance régionale (locale) des demandes et disponibilités en eau en considérant le changement climatique ainsi que les développements socio-économiques. Une estimation intégrée pour l\&\#8217;Europe entière a été entreprise en considérant différents scénarios et projections de changement climatique. Cette perspective à large échelle permet d\&\#8217;identifier des régions qui sont potentiellement vulnérables au changement climatique mais aussi d\&\#8217;identifier les mesures d\&\#8217;adaptation qui pourraient être développées au niveau européen. De plus, trois cas d\&\#8217;étude ont été sélectionnés à travers l\&\#8217;Europe pour étudier les changements dans les régimes hydrologiques, la disponibilité en eau, et les usages de l\&\#8217;eau. Ces cas d\&\#8217;étude concernent trois différents problèmes de gestion de l\&\#8217;eau dans trois régions différentes. Dans le premier cas d\&\#8217;étude, l\&\#8217;influence du changement climatique sur les conditions hydromorphologiques selon la DCE ont été évaluées pour une section de la rivière Eder (Allemagne). L\&\#8217;objectif de ce cas d\&\#8217;étude était d\&\#8217;examiner si l\&\#8217;objectif environnemental de la DCE peut être rempli dans une section typique de la rivière en considérant le changement climatique. Le second cas d\&\#8217;étude s\&\#8217;est penché sur la gestion de l\&\#8217;eau, plus spécialement de la fourniture en eau potable, et sur la mitigation des crues sur le bassin de la Seine (France), qui est partiellement basée sur l\&\#8217;exploitation de réservoirs artificiels. Des scénarios ont été développés pour évaluer l\&\#8217;impact du changement climatique sur les ressources en eau en testant différents modes de gestion des réservoirs. Le troisième cas d\&\#8217;étude a évalué les effets quantitatifs du changement climatique sur les composantes du bilan en eau et sur l\&\#8217;utilisation de l\&\#8217;eau sur le secteur agricole de la région des Pouilles en Italie, afin de soutenir l\&\#8217;adoption de mesures d\&\#8217;adaptation. En fait, la région des Pouilles l\&\#8217;agriculture reste le principal utilisateur d\&\#8217;eau et la principale ressource économique.}
 }
 
 @article{vidal50yearHighresolutionAtmospheric2010,
   title = {A 50-Year High-Resolution Atmospheric Reanalysis over {{France}} with the {{Safran}} System},
-  author = {Vidal, Jean-Philippe and Martin, Eric and Franchistéguy, Laurent and Baillon, Martine and Soubeyroux, Jean-Michel},
-  date = {2010},
-  journaltitle = {International Journal of Climatology},
+  author = {Vidal, Jean-Philippe and Martin, Eric and Franchist{\'e}guy, Laurent and Baillon, Martine and Soubeyroux, Jean-Michel},
+  year = {2010},
+  journal = {International Journal of Climatology},
   volume = {30},
   number = {11},
   pages = {1627--1644},
@@ -305,11 +300,6 @@
   doi = {10.1002/joc.2003},
   url = {https://rmets.onlinelibrary.wiley.com/doi/abs/10.1002/joc.2003},
   urldate = {2021-05-20},
-  abstract = {The assessment of regional climate change requires the development of reference long-term retrospective meteorological datasets. This article presents an 8-km-resolution atmospheric reanalysis over France performed with the the Safran-gauge-based analysis system for the period 1958–2008. Climatological features of the Safran 50-year analysis—long-term mean values, inter-annual and seasonal variability—are first presented for all computed variables: rainfall, snowfall, mean air temperature, specific humidity, wind speed and solar and infrared radiation. The spatial patterns of precipitation, minimum and maximum temperature are compared with another spatialization method, and the temporal consistency of the reanalysis is assessed through various validation experiments with both dependent and independent data. These experiments demonstrate the overall robustness of the Safran reanalysis and the improvement of its quality with time, in connection with the sharp increase in the observation network density that occurred in the 1990s. They also show the differentiated sensitivity of variables to the number of available ground observations, with precipitation and air temperature being the more robust ones. The comparison of trends from the reanalysis with those from homogenized series finally shows that if spatial patterns are globally consistent with both approaches, care must be taken when using literal values from the reanalysis and corresponding statistical significance in climate change detection studies. The Safran 50-year atmospheric reanalysis constitutes a long-term forcing datasets for land surface schemes and thus enables the simulation of the past 50 years of water resources over France. Copyright © 2009 Royal Meteorological Society},
-  langid = {english},
-  keywords = {atmospheric reanalysis,climatology,France,high resolution,trends,validation},
-  annotation = {\_eprint: https://rmets.onlinelibrary.wiley.com/doi/pdf/10.1002/joc.2003},
-  file = {C\:\\Users\\david.dorchies\\Zotero\\storage\\54M9KGRN\\Vidal et al. - 2010 - A 50-year high-resolution atmospheric reanalysis o.pdf;C\:\\Users\\david.dorchies\\Zotero\\storage\\R88PXXHQ\\joc.html}
 }