Commit b8d429a1 authored by Dorchies David's avatar Dorchies David
Browse files

Merge branch 'dev' into 'newSeriesAggreg'

# Conflicts:
#   DESCRIPTION
#   NAMESPACE
#   R/Utils.R
Showing with 427 additions and 190 deletions
+427 -190
...@@ -3,6 +3,7 @@ ...@@ -3,6 +3,7 @@
^\.Rprofile$ ^\.Rprofile$
^packrat/ ^packrat/
^tests/tmp/ ^tests/tmp/
^\.gitlab-ci.yml$
^\.regressionignore$ ^\.regressionignore$
^\.gitlab-ci\.yml$ ^\.gitlab-ci\.yml$
^\.vscode$ ^\.vscode$
...@@ -33,17 +33,11 @@ default: ...@@ -33,17 +33,11 @@ default:
.regression: .regression:
stage: regression stage: regression
only:
refs:
- schedules
script: script:
- Rscript -e 'source("tests/testthat/store_examples.R"); StoreRefExampleResults("airGR");' - Rscript tests/testthat/regression_tests.R stable
- R CMD INSTALL . - R CMD INSTALL .
- Rscript -e 'source("tests/testthat/store_examples.R"); StoreTestExampleResults("airGR");' - Rscript tests/testthat/regression_tests.R dev
artifacts: - Rscript tests/testthat/regression_tests.R compare
paths:
- tests/tmp/
expire_in: 1 week
.check_not_cran: .check_not_cran:
stage: tests stage: tests
...@@ -73,11 +67,17 @@ regression_patched: ...@@ -73,11 +67,17 @@ regression_patched:
extends: .regression extends: .regression
regression_devel: regression_devel:
only:
refs:
- schedules
variables: variables:
R_VERSION: "devel" R_VERSION: "devel"
extends: .regression extends: .regression
regression_oldrel: regression_oldrel:
only:
refs:
- schedules
variables: variables:
R_VERSION: "oldrel" R_VERSION: "oldrel"
extends: .regression extends: .regression
......
...@@ -5,3 +5,4 @@ ...@@ -5,3 +5,4 @@
# Example for ignoring OutputsModel variable produced by example("RunModel_GR2M"): RunModel_GR2M OutputsModel # Example for ignoring OutputsModel variable produced by example("RunModel_GR2M"): RunModel_GR2M OutputsModel
RunModel_GR2M OutputsModel RunModel_GR2M OutputsModel
RunModel_GR2M RunOptions RunModel_GR2M RunOptions
RunModel_GR1A OutputsModel
...@@ -63,8 +63,8 @@ export(TransfoParam_GR5J) ...@@ -63,8 +63,8 @@ export(TransfoParam_GR5J)
export(TransfoParam_GR6J) export(TransfoParam_GR6J)
export(TransfoParam_Lag) export(TransfoParam_Lag)
export(plot) export(plot)
exportPattern(".FortranOutputs") export(plot.OutputsModel)
exportPattern(".ErrorCrit") export(.ErrorCrit)
......
...@@ -16,7 +16,7 @@ ...@@ -16,7 +16,7 @@
____________________________________________________________________________________ ____________________________________________________________________________________
### 1.6.3.65 Release Notes (2020-11-17) ### 1.6.3.73 Release Notes (2020-11-24)
#### New features #### New features
...@@ -46,7 +46,11 @@ ________________________________________________________________________________ ...@@ -46,7 +46,11 @@ ________________________________________________________________________________
#### Minor user-visible changes #### Minor user-visible changes
- <code>RunModel_GR1A()</code> now uses the Fortran version of the model code. This code is no longer duplicated: the R version which was used is removed. - The <code>.FortranOutputs()</code> function is no longer exported in the namespace.
- <code>RunModel_GR1A()</code> now uses the Fortran version of the model code. This code is no longer duplicated: the R version which was used is removed. ([#65](https://gitlab.irstea.fr/HYCAR-Hydro/airgr/-/issues/65))
- Character argument verification now use partial matching in <code>PE_Oudin()</code> and <code>SeriesAggreg()</code> functions. ([#37](https://gitlab.irstea.fr/HYCAR-Hydro/airgr/-/issues/37)) - Character argument verification now use partial matching in <code>PE_Oudin()</code> and <code>SeriesAggreg()</code> functions. ([#37](https://gitlab.irstea.fr/HYCAR-Hydro/airgr/-/issues/37))
......
...@@ -28,10 +28,10 @@ PE_Oudin <- function(JD, Temp, ...@@ -28,10 +28,10 @@ PE_Oudin <- function(JD, Temp,
if (LatUnit[1L] == "deg" & (all(Lat >= 90) | all(Lat <= -90))) { if (LatUnit[1L] == "deg" & (all(Lat >= 90) | all(Lat <= -90))) {
stop("'Lat' must be comprised between -90 and +90 degrees") stop("'Lat' must be comprised between -90 and +90 degrees")
} }
if (!RunFortran & LatUnit[1L] == "rad") { if (LatUnit[1L] == "rad") {
FI <- Lat FI <- Lat
} }
if (!RunFortran & LatUnit[1L] == "deg") { if (LatUnit[1L] == "deg") {
FI <- Lat / (180 / pi) FI <- Lat / (180 / pi)
} }
if (any(JD < 0) | any(JD > 366)) { if (any(JD < 0) | any(JD > 366)) {
...@@ -61,9 +61,6 @@ PE_Oudin <- function(JD, Temp, ...@@ -61,9 +61,6 @@ PE_Oudin <- function(JD, Temp,
## ---------- Oudin's formula ## ---------- Oudin's formula
if (RunFortran) { if (RunFortran) {
if (LatUnit[1L] == "rad") {
Lat = Lat * 180 / pi
}
LInputs = as.integer(length(Temp)) LInputs = as.integer(length(Temp))
...@@ -71,7 +68,7 @@ PE_Oudin <- function(JD, Temp, ...@@ -71,7 +68,7 @@ PE_Oudin <- function(JD, Temp,
Lat = rep(Lat, LInputs) Lat = rep(Lat, LInputs)
} }
RESULTS <- .Fortran("frun_etp_oudin", PACKAGE = "airGR", RESULTS <- .Fortran("frun_pe_oudin", PACKAGE = "airGR",
##inputs ##inputs
LInputs = LInputs, LInputs = LInputs,
InputsLAT = as.double(Lat), InputsLAT = as.double(Lat),
...@@ -86,7 +83,6 @@ PE_Oudin <- function(JD, Temp, ...@@ -86,7 +83,6 @@ PE_Oudin <- function(JD, Temp,
PE_Oudin_D <- rep(NA, length(Temp)) PE_Oudin_D <- rep(NA, length(Temp))
COSFI <- cos(FI) COSFI <- cos(FI)
AFI <- abs(FI / 42)
for (k in seq_along(Temp)) { for (k in seq_along(Temp)) {
......
...@@ -100,154 +100,3 @@ ...@@ -100,154 +100,3 @@
res <- list(GR = outGR, CN = outCN) res <- list(GR = outGR, CN = outCN)
} }
## =================================================================================
## function to manage inputs of specific ErrorCrit_*() functions
## =================================================================================
.ErrorCrit <- function(InputsCrit, Crit, OutputsModel, warnings) {
## Arguments check
if (!inherits(InputsCrit, "InputsCrit")) {
stop("'InputsCrit' must be of class 'InputsCrit'", call. = FALSE)
}
if (inherits(InputsCrit, "Multi") | inherits(InputsCrit, "Compo")) {
if (Crit == "RMSE") {
stop("'InputsCrit' must be of class 'Single'. Use the 'ErrorCrit' function on objects of class 'Multi' with RMSE", call. = FALSE)
} else {
stop(paste0("'InputsCrit' must be of class 'Single'. Use the 'ErrorCrit' function on objects of class 'Multi' or 'Compo' with ", Crit), call. = FALSE)
}
}
## Initialisation
CritName <- NA
CritVar <- InputsCrit$VarObs
if (InputsCrit$transfo == "") {
CritName <- paste0(Crit, "[CritVar]")
}
if (InputsCrit$transfo %in% c("sqrt", "log", "sort", "boxcox")) {
CritName <- paste0(Crit, "[", InputsCrit$transfo, "(CritVar)]")
}
if (InputsCrit$transfo == "inv") {
CritName <- paste0(Crit, "[1/CritVar]")
}
if (grepl("\\^", InputsCrit$transfo)) {
transfoPow <- suppressWarnings(as.numeric(gsub("\\^", "", InputsCrit$transfo)))
CritName <- paste0(Crit, "[CritVar^", transfoPow, "]")
}
CritName <- gsub(pattern = "CritVar", replacement = CritVar, x = CritName)
CritValue <- NA
if (Crit %in% c("RMSE")) {
CritBestValue <- +1
Multiplier <- +1
}
if (Crit %in% c("NSE", "KGE", "KGE2")) {
CritBestValue <- +1
Multiplier <- -1
}
## Data preparation
VarObs <- InputsCrit$Obs
VarObs[!InputsCrit$BoolCrit] <- NA
if (InputsCrit$VarObs == "Q") {
VarSim <- OutputsModel$Qsim
}
if (InputsCrit$VarObs == "SCA") {
VarSim <- rowMeans(sapply(OutputsModel$CemaNeigeLayers[InputsCrit$idLayer], FUN = "[[", "Gratio"))
}
if (InputsCrit$VarObs == "SWE") {
VarSim <- rowMeans(sapply(OutputsModel$CemaNeigeLayers[InputsCrit$idLayer], FUN = "[[", "SnowPack"))
}
VarSim[!InputsCrit$BoolCrit] <- NA
## Data transformation
if (InputsCrit$transfo %in% c("log", "inv") & is.null(InputsCrit$epsilon) & warnings) {
if (any(VarObs %in% 0)) {
warning("zeroes detected in 'Qobs': the corresponding time-steps will be excluded from the criteria computation if the epsilon argument of 'CreateInputsCrit' = NULL", call. = FALSE)
}
if (any(VarSim %in% 0)) {
warning("zeroes detected in 'Qsim': the corresponding time-steps will be excluded from the criteria computation if the epsilon argument of 'CreateInputsCrit' = NULL", call. = FALSE)
}
}
if ("epsilon" %in% names(InputsCrit) & !is.null(InputsCrit$epsilon) & !(InputsCrit$transfo == "boxcox")) {
VarObs <- VarObs + InputsCrit$epsilon
VarSim <- VarSim + InputsCrit$epsilon
}
if (InputsCrit$transfo == "sqrt") {
VarObs <- sqrt(VarObs)
VarSim <- sqrt(VarSim)
}
if (InputsCrit$transfo == "log") {
VarObs <- log(VarObs)
VarSim <- log(VarSim)
VarSim[VarSim < -1e100] <- NA
}
if (InputsCrit$transfo == "inv") {
VarObs <- 1 / VarObs
VarSim <- 1 / VarSim
VarSim[abs(VarSim) > 1e+100] <- NA
}
if (InputsCrit$transfo == "sort") {
VarSim[is.na(VarObs)] <- NA
VarSim <- sort(VarSim, na.last = TRUE)
VarObs <- sort(VarObs, na.last = TRUE)
InputsCrit$BoolCrit <- sort(InputsCrit$BoolCrit, decreasing = TRUE)
}
if (InputsCrit$transfo == "boxcox") {
muTransfoVarObs <- (0.01 * mean(VarObs, na.rm = TRUE))^0.25
VarSim <- (VarSim^0.25 - muTransfoVarObs) / 0.25
VarObs <- (VarObs^0.25 - muTransfoVarObs) / 0.25
}
if (grepl("\\^", InputsCrit$transfo)) {
VarObs <- VarObs^transfoPow
VarSim <- VarSim^transfoPow
}
## TS_ignore
TS_ignore <- !is.finite(VarObs) | !is.finite(VarSim) | !InputsCrit$BoolCrit
Ind_TS_ignore <- which(TS_ignore)
if (length(Ind_TS_ignore) == 0) {
Ind_TS_ignore <- NULL
}
if (sum(!TS_ignore) == 0 | (sum(!TS_ignore) == 1 & Crit %in% c("KGE", "KGE2"))) {
CritCompute <- FALSE
} else {
CritCompute <- TRUE
}
if (inherits(OutputsModel, "hourly")) {
WarningTS <- 365
}
if (inherits(OutputsModel, "daily")) {
WarningTS <- 365
}
if (inherits(OutputsModel, "monthly")) {
WarningTS <- 12
}
if (inherits(OutputsModel, "yearly")) {
WarningTS <- 3
}
if (sum(!TS_ignore) < WarningTS & warnings) {
warning("\t criterion computed on less than ", WarningTS, " time-steps", call. = FALSE)
}
## Outputs
OutputsCritCheck <- list(WarningTS = WarningTS,
VarObs = VarObs,
VarSim = VarSim,
CritBestValue = CritBestValue,
Multiplier = Multiplier,
CritName = CritName,
CritVar = CritVar,
CritCompute = CritCompute,
TS_ignore = TS_ignore,
Ind_TS_ignore = Ind_TS_ignore)
}
## =================================================================================
## function to manage inputs of specific ErrorCrit_*() functions
## =================================================================================
.ErrorCrit <- function(InputsCrit, Crit, OutputsModel, warnings) {
## Arguments check
if (!inherits(InputsCrit, "InputsCrit")) {
stop("'InputsCrit' must be of class 'InputsCrit'", call. = FALSE)
}
if (inherits(InputsCrit, "Multi") | inherits(InputsCrit, "Compo")) {
if (Crit == "RMSE") {
stop("'InputsCrit' must be of class 'Single'. Use the 'ErrorCrit' function on objects of class 'Multi' with RMSE", call. = FALSE)
} else {
stop(paste0("'InputsCrit' must be of class 'Single'. Use the 'ErrorCrit' function on objects of class 'Multi' or 'Compo' with ", Crit), call. = FALSE)
}
}
## Initialisation
CritName <- NA
CritVar <- InputsCrit$VarObs
if (InputsCrit$transfo == "") {
CritName <- paste0(Crit, "[CritVar]")
}
if (InputsCrit$transfo %in% c("sqrt", "log", "sort", "boxcox")) {
CritName <- paste0(Crit, "[", InputsCrit$transfo, "(CritVar)]")
}
if (InputsCrit$transfo == "inv") {
CritName <- paste0(Crit, "[1/CritVar]")
}
if (grepl("\\^", InputsCrit$transfo)) {
transfoPow <- suppressWarnings(as.numeric(gsub("\\^", "", InputsCrit$transfo)))
CritName <- paste0(Crit, "[CritVar^", transfoPow, "]")
}
CritName <- gsub(pattern = "CritVar", replacement = CritVar, x = CritName)
CritValue <- NA
if (Crit %in% c("RMSE")) {
CritBestValue <- +1
Multiplier <- +1
}
if (Crit %in% c("NSE", "KGE", "KGE2")) {
CritBestValue <- +1
Multiplier <- -1
}
## Data preparation
VarObs <- InputsCrit$Obs
VarObs[!InputsCrit$BoolCrit] <- NA
if (InputsCrit$VarObs == "Q") {
VarSim <- OutputsModel$Qsim
}
if (InputsCrit$VarObs == "SCA") {
VarSim <- rowMeans(sapply(OutputsModel$CemaNeigeLayers[InputsCrit$idLayer], FUN = "[[", "Gratio"))
}
if (InputsCrit$VarObs == "SWE") {
VarSim <- rowMeans(sapply(OutputsModel$CemaNeigeLayers[InputsCrit$idLayer], FUN = "[[", "SnowPack"))
}
VarSim[!InputsCrit$BoolCrit] <- NA
## Data transformation
if (InputsCrit$transfo %in% c("log", "inv") & is.null(InputsCrit$epsilon) & warnings) {
if (any(VarObs %in% 0)) {
warning("zeroes detected in 'Qobs': the corresponding time-steps will be excluded from the criteria computation if the epsilon argument of 'CreateInputsCrit' = NULL", call. = FALSE)
}
if (any(VarSim %in% 0)) {
warning("zeroes detected in 'Qsim': the corresponding time-steps will be excluded from the criteria computation if the epsilon argument of 'CreateInputsCrit' = NULL", call. = FALSE)
}
}
if ("epsilon" %in% names(InputsCrit) & !is.null(InputsCrit$epsilon) & !(InputsCrit$transfo == "boxcox")) {
VarObs <- VarObs + InputsCrit$epsilon
VarSim <- VarSim + InputsCrit$epsilon
}
if (InputsCrit$transfo == "sqrt") {
VarObs <- sqrt(VarObs)
VarSim <- sqrt(VarSim)
}
if (InputsCrit$transfo == "log") {
VarObs <- log(VarObs)
VarSim <- log(VarSim)
VarSim[VarSim < -1e100] <- NA
}
if (InputsCrit$transfo == "inv") {
VarObs <- 1 / VarObs
VarSim <- 1 / VarSim
VarSim[abs(VarSim) > 1e+100] <- NA
}
if (InputsCrit$transfo == "sort") {
VarSim[is.na(VarObs)] <- NA
VarSim <- sort(VarSim, na.last = TRUE)
VarObs <- sort(VarObs, na.last = TRUE)
InputsCrit$BoolCrit <- sort(InputsCrit$BoolCrit, decreasing = TRUE)
}
if (InputsCrit$transfo == "boxcox") {
muTransfoVarObs <- (0.01 * mean(VarObs, na.rm = TRUE))^0.25
VarSim <- (VarSim^0.25 - muTransfoVarObs) / 0.25
VarObs <- (VarObs^0.25 - muTransfoVarObs) / 0.25
}
if (grepl("\\^", InputsCrit$transfo)) {
VarObs <- VarObs^transfoPow
VarSim <- VarSim^transfoPow
}
## TS_ignore
TS_ignore <- !is.finite(VarObs) | !is.finite(VarSim) | !InputsCrit$BoolCrit
Ind_TS_ignore <- which(TS_ignore)
if (length(Ind_TS_ignore) == 0) {
Ind_TS_ignore <- NULL
}
if (sum(!TS_ignore) == 0 | (sum(!TS_ignore) == 1 & Crit %in% c("KGE", "KGE2"))) {
CritCompute <- FALSE
} else {
CritCompute <- TRUE
}
if (inherits(OutputsModel, "hourly")) {
WarningTS <- 365
}
if (inherits(OutputsModel, "daily")) {
WarningTS <- 365
}
if (inherits(OutputsModel, "monthly")) {
WarningTS <- 12
}
if (inherits(OutputsModel, "yearly")) {
WarningTS <- 3
}
if (sum(!TS_ignore) < WarningTS & warnings) {
warning("\t criterion computed on less than ", WarningTS, " time-steps", call. = FALSE)
}
## Outputs
OutputsCritCheck <- list(WarningTS = WarningTS,
VarObs = VarObs,
VarSim = VarSim,
CritBestValue = CritBestValue,
Multiplier = Multiplier,
CritName = CritName,
CritVar = CritVar,
CritCompute = CritCompute,
TS_ignore = TS_ignore,
Ind_TS_ignore = Ind_TS_ignore)
}
...@@ -15,7 +15,7 @@ extern void F77_NAME(frun_gr5h)(int *, double *, double *, int *, double *, int ...@@ -15,7 +15,7 @@ extern void F77_NAME(frun_gr5h)(int *, double *, double *, int *, double *, int
extern void F77_NAME(frun_gr4j)(int *, double *, double *, int *, double *, int *, double *, int *, int *, double *, double *); extern void F77_NAME(frun_gr4j)(int *, double *, double *, int *, double *, int *, double *, int *, int *, double *, double *);
extern void F77_NAME(frun_gr5j)(int *, double *, double *, int *, double *, int *, double *, int *, int *, double *, double *); extern void F77_NAME(frun_gr5j)(int *, double *, double *, int *, double *, int *, double *, int *, int *, double *, double *);
extern void F77_NAME(frun_gr6j)(int *, double *, double *, int *, double *, int *, double *, int *, int *, double *, double *); extern void F77_NAME(frun_gr6j)(int *, double *, double *, int *, double *, int *, double *, int *, int *, double *, double *);
extern void F77_NAME(frun_etp_oudin)(int *, double *, double *, double *, double *); extern void F77_NAME(frun_pe_oudin)(int *, double *, double *, double *, double *);
static const R_FortranMethodDef FortranEntries[] = { static const R_FortranMethodDef FortranEntries[] = {
{"frun_cemaneige", (DL_FUNC) &F77_NAME(frun_cemaneige), 14}, {"frun_cemaneige", (DL_FUNC) &F77_NAME(frun_cemaneige), 14},
...@@ -26,7 +26,7 @@ static const R_FortranMethodDef FortranEntries[] = { ...@@ -26,7 +26,7 @@ static const R_FortranMethodDef FortranEntries[] = {
{"frun_gr4j", (DL_FUNC) &F77_NAME(frun_gr4j), 11}, {"frun_gr4j", (DL_FUNC) &F77_NAME(frun_gr4j), 11},
{"frun_gr5j", (DL_FUNC) &F77_NAME(frun_gr5j), 11}, {"frun_gr5j", (DL_FUNC) &F77_NAME(frun_gr5j), 11},
{"frun_gr6j", (DL_FUNC) &F77_NAME(frun_gr6j), 11}, {"frun_gr6j", (DL_FUNC) &F77_NAME(frun_gr6j), 11},
{"frun_etp_oudin", (DL_FUNC) &F77_NAME(frun_etp_oudin), 5}, {"frun_pe_oudin", (DL_FUNC) &F77_NAME(frun_pe_oudin), 5},
{NULL, NULL, 0} {NULL, NULL, 0}
}; };
......
...@@ -296,19 +296,14 @@ ...@@ -296,19 +296,14 @@
IF(AR.GT.33.) AR=33. IF(AR.GT.33.) AR=33.
IF(AR.LT.-33.) AR=-33. IF(AR.LT.-33.) AR=-33.
IF(AR.GT.7.)THEN IF(AR.GT.7.) THEN
QRExp=St(3)+Param(6)/EXP(AR) QRExp=St(3)+Param(6)/EXP(AR)
GOTO 3 ELSEIF(AR.LT.-7.) THEN
ENDIF
IF(AR.LT.-7.)THEN
QRExp=Param(6)*EXP(AR) QRExp=Param(6)*EXP(AR)
GOTO 3 ELSE
QRExp=Param(6)*LOG(EXP(AR)+1.)
ENDIF ENDIF
QRExp=Param(6)*LOG(EXP(AR)+1.)
3 CONTINUE
St(3)=St(3)-QRExp St(3)=St(3)-QRExp
! Runoff from direct branch QD ! Runoff from direct branch QD
......
!------------------------------------------------------------------------------
! Subroutines relative to the Oudin potential evapotranspiration (PE) formula
!------------------------------------------------------------------------------
! TITLE : airGR
! PROJECT : airGR
! FILE : frun_PE.f90
!------------------------------------------------------------------------------
! AUTHORS
! Original code: L. Oudin
! Cleaning and formatting for airGR: Fr. Bourgin
! Further cleaning: O. Delaigue, G. Thirel
!------------------------------------------------------------------------------
! Creation date: 2004
! Last modified: 20/10/2020
!------------------------------------------------------------------------------
! REFERENCES
! Oudin, L., Hervieu, F., Michel, C., Perrin, C., Andréassian, V.,
! Anctil, F. and Loumagne, C., 2005. Which potential evapotranspiration
! input for a rainfall-runoff model? Part 2 - Towards a simple and
! efficient PE model for rainfall-runoff modelling. Journal of Hydrology
! 303(1-4), 290-306.
!------------------------------------------------------------------------------
! Quick description of public procedures:
! 1. frun_pe_oudin
! 2. PE_OUDIN
!------------------------------------------------------------------------------
!******************************************************************************* !*******************************************************************************
SUBROUTINE frun_etp_oudin(LInputs,InputsLAT,InputsTT,InputsJJ,OutputsETP) SUBROUTINE frun_pe_oudin(LInputs,InputsLAT,InputsTemp,InputsJJ,OutputsPE)
!******************************************************************************* !*******************************************************************************
! Subroutine that performs the call to the PE_OUDIN subroutine at each time step,
! and stores the final values
! Inputs
! LInputs ! Integer, length of input and output series
! InputsLAT ! Vector of real, input series of latitude [rad]
! InputsTemp ! Vector of real, input series of air mean temperature [degC]
! InputsJJ ! Vector of real, input series of Julian day [-]
! Outputs
! OutputsPE ! Vector of real, output series of potential evapotranspiration (PE) [mm/time step]
!DEC$ ATTRIBUTES DLLEXPORT :: frun_etp_oudin !DEC$ ATTRIBUTES DLLEXPORT :: frun_pe_oudin
Implicit None Implicit None
...@@ -10,27 +49,27 @@ ...@@ -10,27 +49,27 @@
! in ! in
integer, intent(in) :: LInputs integer, intent(in) :: LInputs
doubleprecision, dimension(LInputs), intent(in) :: InputsLAT doubleprecision, dimension(LInputs), intent(in) :: InputsLAT
doubleprecision, dimension(LInputs), intent(in) :: InputsTT doubleprecision, dimension(LInputs), intent(in) :: InputsTemp
doubleprecision, dimension(LInputs), intent(in) :: InputsJJ doubleprecision, dimension(LInputs), intent(in) :: InputsJJ
! out ! out
doubleprecision, dimension(LInputs), intent(out) :: OutputsETP doubleprecision, dimension(LInputs), intent(out) :: OutputsPE
!! locals !! locals
integer :: k integer :: k
real :: FI, tt, jj, ETPoud doubleprecision :: FI, tt, jj, PEoud
!-------------------------------------------------------------- !--------------------------------------------------------------
! Time loop ! Time loop
!-------------------------------------------------------------- !--------------------------------------------------------------
DO k=1,LInputs DO k = 1, LInputs
tt = InputsTT(k) tt = InputsTemp(k)
jj = InputsJJ(k) jj = InputsJJ(k)
FI = InputsLAT(k) / 57.296 FI = InputsLAT(k)!
!model run on one time step !model run on one time step
CALL ETP_OUDIN(FI,tt,jj,ETPoud) CALL PE_OUDIN(FI, tt, jj, PEoud)
!storage of outputs !storage of outputs
OutputsETP(k) = ETPoud OutputsPE(k) = PEoud
ENDDO ENDDO
RETURN RETURN
...@@ -38,14 +77,22 @@ ...@@ -38,14 +77,22 @@
ENDSUBROUTINE ENDSUBROUTINE
!################################################################################################################################
!******************************************************************************* !*******************************************************************************
SUBROUTINE ETP_OUDIN(FI,DT,JD,DPE) SUBROUTINE PE_OUDIN(FI,DT,JD,DPE)
!******************************************************************************* !*******************************************************************************
! This subroutine calculates daily potential evapotranspiration (DPE) ! Calculation of potential evapotranspiration (DPE) on a single time step
! using daily temperature and daily extra-atmospheric global radiation ! using air temperature and daily extra-atmospheric global radiation
! (that depends only on Julian day) ! (that depends only on Julian day)
! !
! The PE formula is is that described in: ! The PE formula is described in:
! Oudin, L., Hervieu, F., Michel, C., Perrin, C., Andréassian, V., ! Oudin, L., Hervieu, F., Michel, C., Perrin, C., Andréassian, V.,
! Anctil, F. and Loumagne, C., 2005. Which potential evapotranspiration ! Anctil, F. and Loumagne, C., 2005. Which potential evapotranspiration
! input for a rainfall-runoff model? Part 2 - Towards a simple and ! input for a rainfall-runoff model? Part 2 - Towards a simple and
...@@ -58,67 +105,68 @@ ...@@ -58,67 +105,68 @@
! of hydrology. Journal of Hydrology 66 (1/4), 1-76. ! of hydrology. Journal of Hydrology 66 (1/4), 1-76.
! !
!*************************************************************** !***************************************************************
! Inputs: ! Inputs
! xLAT: Latitude in decimal degrees ! FI ! Latitude [rad]
! DT: Temperature in degree C ! DT ! Air Temperature [degC]
! JD: Julian day ! JD ! Julian day [-]
! !
! Output: ! Outputs
! DPE: Daily potential evapotranspiration in mm ! DPE ! Potential evapotranspiration [mm/time step]
!*************************************************************** !***************************************************************
IMPLICIT NONE IMPLICIT NONE
REAL :: xLAT, FI, COSFI, TETA, COSTETA, COSGZ, GZ, COSGZ2 !! dummies
REAL :: SINGZ, COSOM, COSOM2, SINOM, COSPZ, OM, GE ! in
REAL :: ETA, DPE, DT, JD, RD doubleprecision, intent(in) :: FI, DT, JD
! out
! DATA RD/57.296/ doubleprecision, intent(out) :: DPE
!! locals
doubleprecision :: COSFI, TETA, COSTETA, COSGZ, GZ, COSGZ2
doubleprecision :: SINGZ, COSOM, COSOM2, SINOM, COSPZ, OM, GE
doubleprecision :: ETA
! Calculation of extra-atmospheric global radiation (Appendix C in Morton ! Calculation of extra-atmospheric global radiation (Appendix C in Morton
! (1983), Eq. C-6 to C-11, p.60-61) ! (1983), Eq. C-6 to C-11, p.60-61)
! Converts latitude in radians
! FI=xLAT/RD
COSFI=COS(FI) COSFI=COS(FI)
! AFI=ABS(xLAT/42.)
! TETA: Declination of the sun in radians ! TETA: Declination of the sun in radians
TETA=0.4093*SIN(JD/58.1-1.405) TETA=0.4093*SIN(JD/58.1-1.405)
COSTETA=COS(TETA) COSTETA=COS(TETA)
COSGZ=MAX(0.001,COS(FI-TETA)) COSGZ=MAX(0.001d0,COS(FI-TETA))
! GZ: Noon angular zenith distance of the sun ! GZ: Noon angular zenith distance of the sun
GZ=ACOS(COSGZ) GZ=ACOS(COSGZ)
COSGZ2=COSGZ*COSGZ COSGZ2=COSGZ*COSGZ
IF(COSGZ2.GE.1.)THEN IF(COSGZ2.GE.1.) THEN
SINGZ=0. SINGZ=0.
ELSE ELSE
SINGZ=SQRT(1.-COSGZ2) SINGZ=SQRT(1.-COSGZ2)
ENDIF ENDIF
COSOM=1.-COSGZ/COSFI/COSTETA COSOM=1.-COSGZ/COSFI/COSTETA
IF(COSOM.LT.-1.)COSOM=-1. IF(COSOM.LT.-1.) COSOM=-1.
IF(COSOM.GT.1.)COSOM=1. IF(COSOM.GT.1.) COSOM=1.
COSOM2=COSOM*COSOM COSOM2=COSOM*COSOM
IF(COSOM2.GE.1.)THEN IF(COSOM2.GE.1.) THEN
SINOM=0. SINOM=0.
ELSE ELSE
SINOM=SQRT(1.-COSOM2) SINOM=SQRT(1.-COSOM2)
ENDIF ENDIF
OM=ACOS(COSOM) OM=ACOS(COSOM)
! PZ: Average angular zenith distance of the sun ! PZ: Average angular zenith distance of the sun
COSPZ=COSGZ+COSFI*COSTETA*(SINOM/OM-1.) COSPZ=COSGZ+COSFI*COSTETA*(SINOM/OM-1.)
IF(COSPZ.LT.0.001)COSPZ=0.001 IF(COSPZ.LT.0.001) COSPZ=0.001
! ETA: Radius vector of the sun ! ETA: Radius vector of the sun
ETA=1.+COS(JD/58.1)/30. ETA=1.+COS(JD/58.1)/30.
! GE: extra-atmospheric global radiation ! GE: extra-atmospheric global radiation
GE=446.*OM*COSPZ*ETA GE=446.*OM*COSPZ*ETA
! Daily PE by Oudin et al. (2006) formula: ! Daily PE by Oudin et al. (2006) formula:
DPE=MAX(0.,GE*(DT+5.)/100./28.5) DPE=MAX(0.d0,GE*(DT+5.)/100./28.5)
RETURN RETURN
END SUBROUTINE ETP_OUDIN END SUBROUTINE PE_OUDIN
!******************************************************************************* !*******************************************************************************
StoreRefExampleResults <- function(package, ...) { StoreStableExampleResults <- function(
package = "airGR",
path = file.path("tests/tmp", Sys.getenv("R_VERSION"), "stable"),
...) {
install.packages(package, repos = "http://cran.r-project.org") install.packages(package, repos = "http://cran.r-project.org")
StoreExampleResults(package = package, path = "tests/tmp/ref", ...) StoreExampleResults(package = package, path = path, ...)
} }
StoreTestExampleResults <- function(package, ...) { StoreDevExampleResults <- function(
StoreExampleResults( package = "airGR",
package = package, path = file.path("tests/tmp", Sys.getenv("R_VERSION"), "dev"),
path = file.path("tests/tmp", Sys.getenv("R_VERSION", "test")), ...) {
... StoreExampleResults(package = package, path = path, ...)
)
} }
#' Run examples of a package and store the output variables in RDS files for further testing. #' Run examples of a package and store the output variables in RDS files for further testing.
...@@ -72,3 +74,8 @@ StoreTopicResults <- function(topic, package, path, run.dontrun = TRUE, run.dont ...@@ -72,3 +74,8 @@ StoreTopicResults <- function(topic, package, path, run.dontrun = TRUE, run.dont
} }
CompareStableDev <- function() {
res = testthat::test_file("tests/testthat/regression.R")
dRes = as.data.frame(res)
if(any(dRes[,"failed"]>0) | any(dRes[,"error"])) quit(status = 1)
}
context("Compare example outputs with CRAN") context("Compare example outputs with CRAN")
CompareWithRef <- function(refVarFile, testDir, regIgnore) { CompareWithStable <- function(refVarFile, testDir, regIgnore) {
v <- data.frame(topic = basename(dirname(refVarFile)), v <- data.frame(topic = basename(dirname(refVarFile)),
var = gsub("\\.rds$", "", basename(refVarFile))) var = gsub("\\.rds$", "", basename(refVarFile)))
if (is.null(regIgnore) || all(apply(regIgnore, 1, function(x) !all(x == v)))) { if (is.null(regIgnore) || all(apply(regIgnore, 1, function(x) !all(x == v)))) {
test_that(paste("Compare", v$topic, v$var), { test_that(paste("Compare", v$topic, v$var), {
skip_on_cran()
testVarFile <- paste0( testVarFile <- paste0(
file.path("../tmp", Sys.getenv("R_VERSION", "test"), v$topic, v$var), file.path(testDir, v$topic, v$var),
".rds" ".rds"
) )
expect_true(file.exists(testVarFile)) expect_true(file.exists(testVarFile))
...@@ -20,23 +19,26 @@ CompareWithRef <- function(refVarFile, testDir, regIgnore) { ...@@ -20,23 +19,26 @@ CompareWithRef <- function(refVarFile, testDir, regIgnore) {
} }
} }
if (dir.exists("../tmp/ref") & dir.exists("../tmp/test")) { tmp_path <- file.path("../tmp", Sys.getenv("R_VERSION"));
refVarFiles <- list.files("../tmp/ref", recursive = TRUE, full.names = TRUE)
regIgnoreFile <- "../../.regressionignore2" if (dir.exists(file.path(tmp_path, "stable")) & dir.exists(file.path(tmp_path, "dev"))) {
refVarFiles <- list.files(file.path(tmp_path, "stable"), recursive = TRUE, full.names = TRUE)
regIgnoreFile <- "../../.regressionignore"
if (file.exists(regIgnoreFile)) { if (file.exists(regIgnoreFile)) {
message("Using .regressionignore file. The following variables are going to be skipped:")
regIgnore <- read.table(file = regIgnoreFile, regIgnore <- read.table(file = regIgnoreFile,
sep = " ", header = FALSE, skip = 5, sep = " ", header = FALSE, skip = 5,
col.names = c("topic", "var"), col.names = c("topic", "var"),
stringsAsFactors = FALSE) stringsAsFactors = FALSE)
apply(regIgnore, 1, function(x) message(x[1], ": ", x[2]))
} else { } else {
message("File ", file.path(getwd(), regIgnoreFile), " not found")
regIgnore <- NULL regIgnore <- NULL
} }
lapply(X = refVarFiles, CompareWithRef, testDir = "../tmp/test", regIgnore = regIgnore) lapply(X = refVarFiles, CompareWithStable, testDir = file.path(tmp_path, "dev"), regIgnore = regIgnore)
} else { } else {
warning("Regression tests compared to released version needs that you run the following instructions first:\n", stop("Regression tests compared to released version needs that you run the following instructions first:\n",
"Rscript -e 'source(\"tests/testthat/store_examples.R\"); StoreRefExampleResults(\"airGR\");'\n", "Rscript tests/testthat/regression_tests.R stable\n",
"R CMD INSTALL .\n", "R CMD INSTALL .\n",
"Rscript -e 'source(\"tests/testthat/store_examples.R\"); StoreTestExampleResults(\"airGR\");'\n") "Rscript tests/testthat/regression_tests.R dev")
} }
# Execute Regression test by comparing RD files stored in folders /tests/tmp/ref and /tests/tmp/test
Args = commandArgs(trailingOnly=TRUE)
source("tests/testthat/helper_regression.R")
lActions = list(
stable = StoreStableExampleResults,
dev = StoreDevExampleResults,
compare = CompareStableDev
)
if(Args %in% names(lActions)) {
lActions[[Args]]()
} else {
stop("This script should be run with one argument in the command line:\n",
"`Rscript tests/regression_tests.R [stable|dev|compare]`.\n",
"Available arguments are:\n",
"- stable: install stable version from CRAN, run and store examples\n",
"- dev: install dev version from current directory, run and store examples\n",
"- compare: stored results of both versions")
}
Supports Markdown
0% or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment