From b534cc90888a798ebfcaa89a5bbd6e3b4bdbbd42 Mon Sep 17 00:00:00 2001 From: "BOITARD Nicolas (Externe)" <123453373+boitardn@users.noreply.github.com> Date: Thu, 6 Jun 2024 09:18:17 +0200 Subject: [PATCH 01/14] Add .importOutputForSTClusters() --- R/importOutput.R | 57 ++++++++++++++++++- tests/testthat/test-importOutputForClusters.R | 21 +++++++ 2 files changed, 77 insertions(+), 1 deletion(-) create mode 100644 tests/testthat/test-importOutputForClusters.R diff --git a/R/importOutput.R b/R/importOutput.R index 2cb25a80..73ad424e 100644 --- a/R/importOutput.R +++ b/R/importOutput.R @@ -304,6 +304,10 @@ # Order is important. There is a correspondance between elements. all_thematic_variables <- c("RES generation by plant") colNames <- c("production") + } else if(type == "details-STstorage") { + # Order is important. There is a correspondance between elements. + all_thematic_variables <- c("STS inj by plant","STS lvl by plant","STS withdrawal by plant") + colNames <- c("injection","level","withdrawal") } # With thematic-trimming enabled if (opts$parameters$general$`thematic-trimming`) { @@ -506,7 +510,7 @@ # To improve greatly the performance we use our knowledge of the position of # the columns instead of using more general functions like dcast. reshapeFun <- function(x) { - + # Get cluster names n <- names(x) idx <- ! n %in% pkgEnv$idVars @@ -540,6 +544,57 @@ } +#' .importOutputForSTClusters +#' +#' Private function used to import the output for the short-term clusters of one area +#' +#' @return +#' a data.table +#' +#' @noRd +#' +.importOutputForSTClusters <- function(areas, timeStep, select = NULL, mcYears = NULL, + showProgress, opts, parallel) { + + # In output files, there is one file per area with the follwing form: + # cluster1-var1 | cluster2-var1 | cluster1-var2 | cluster2-var2 + # the following function reshapes the result to have variable cluster in column. + # To improve greatly the performance we use our knowledge of the position of + # the columns instead of using more general functions like dcast. + reshapeFun <- function(x) { + + # Get cluster names + n <- names(x) + idx <- ! n %in% pkgEnv$idVars + clusterNames <- tolower(unique(n[idx])) + + # Id vars names + idVarsId <- which(!idx) + idVarsNames <- n[idVarsId] + + # Column names of the output table + colNames <- .get_value_columns_details_file(opts, "details-STstorage") + + # Loop over clusters + nclusters <- length(clusterNames) + + res <- llply(1:nclusters, function(i) { + dt <- x[, c(nclusters * 0:(length(colNames) - 1) + i, idVarsId), with = FALSE] + setnames(dt, c(colNames, idVarsNames)) + dt[, cluster := as.factor(clusterNames[i])] + dt + }) + + rbindlist(res) + } + + suppressWarnings( + .importOutput("areas", "details-STstorage", "area", areas, timeStep, NULL, + mcYears, showProgress, opts, reshapeFun, sameNames = FALSE, + objectDisplayName = "clustersRe", parallel = parallel) + ) +} + #' .importOutputForBindingConstraints #' #' Private function used to import the output for binding constraints. diff --git a/tests/testthat/test-importOutputForClusters.R b/tests/testthat/test-importOutputForClusters.R new file mode 100644 index 00000000..caef7428 --- /dev/null +++ b/tests/testthat/test-importOutputForClusters.R @@ -0,0 +1,21 @@ +#Copyright © 2016 RTE Réseau de transport d’électricité + +context("Functions .importOutput") + +path_study_test <- grep(pattern = "87", x = studyPathSV8, value = TRUE) + +opts <- setSimulationPath(path_study_test,simulation="20240105-0934eco") + +test_that(".importOutputForSTClusters is ok", { + + OutputForRESClusters <- .importOutputForSTClusters( + areas="fr", + timeStep="annual", + showProgress=FALSE, + parallel=FALSE, + opts=opts + ) + + expect_true(all(c("injection","level","withdrawal") %in% colnames(OutputForRESClusters))) + expect_equal(nrow(OutputForRESClusters),1) +}) From a08b1bbaf7c658ead32136c93e66facb69f844ab Mon Sep 17 00:00:00 2001 From: "BOITARD Nicolas (Externe)" <123453373+boitardn@users.noreply.github.com> Date: Fri, 7 Jun 2024 12:04:56 +0200 Subject: [PATCH 02/14] Add 'clustersST' argument in readAntares() --- R/importOutput.R | 2 +- R/readAntares.R | 30 +++++++++++++++---- R/setSimulationPath.R | 15 ++++++++++ man/readAntares.Rd | 6 ++++ tests/testthat/test-importOutputForClusters.R | 6 ++-- tests/testthat/test-readAntares_STclusters.R | 19 ++++++++++++ 6 files changed, 69 insertions(+), 9 deletions(-) create mode 100644 tests/testthat/test-readAntares_STclusters.R diff --git a/R/importOutput.R b/R/importOutput.R index 73ad424e..573cd316 100644 --- a/R/importOutput.R +++ b/R/importOutput.R @@ -591,7 +591,7 @@ suppressWarnings( .importOutput("areas", "details-STstorage", "area", areas, timeStep, NULL, mcYears, showProgress, opts, reshapeFun, sameNames = FALSE, - objectDisplayName = "clustersRe", parallel = parallel) + objectDisplayName = "clustersST", parallel = parallel) ) } diff --git a/R/readAntares.R b/R/readAntares.R index fdeb20e2..af518693 100644 --- a/R/readAntares.R +++ b/R/readAntares.R @@ -85,6 +85,11 @@ #' import results at renewable cluster level. If \code{NULL} no cluster is imported. The #' special value \code{"all"} tells the function to import renewable clusters from all #' areas. +#' @param clustersST +#' Vector containing the name of the areas for which you want to +#' import results at short-term cluster level. If \code{NULL} no cluster is imported. The +#' special value \code{"all"} tells the function to import short-term clusters from all +#' areas. #' @param bindingConstraints #' Should binding constraints be imported (v8.4+)? #' @param districts @@ -210,8 +215,8 @@ #' @export #' readAntares <- function(areas = NULL, links = NULL, clusters = NULL, - districts = NULL, clustersRes = NULL, bindingConstraints = FALSE, - misc = FALSE, thermalAvailabilities = FALSE, + districts = NULL, clustersRes = NULL, clustersST = NULL, + bindingConstraints = FALSE, misc = FALSE, thermalAvailabilities = FALSE, hydroStorage = FALSE, hydroStorageMaxPower = FALSE, reserve = FALSE, linkCapacity = FALSE, mustRun = FALSE, thermalModulation = FALSE, @@ -221,7 +226,7 @@ readAntares <- function(areas = NULL, links = NULL, clusters = NULL, mcWeights = NULL, opts = simOptions(), parallel = FALSE, simplify = TRUE, showProgress = TRUE) { - + if((!is.null(opts$parameters$`other preferences`$`renewable-generation-modelling`) && !opts$parameters$`other preferences`$`renewable-generation-modelling` %in% "clusters") || is.null(opts$parameters$`other preferences`$`renewable-generation-modelling`)){ @@ -309,6 +314,7 @@ readAntares <- function(areas = NULL, links = NULL, clusters = NULL, links = links, clusters = clusters, clustersRes = clustersRes, + clustersST = clustersST, districts = districts, mcYears = mcYears) @@ -317,6 +323,7 @@ readAntares <- function(areas = NULL, links = NULL, clusters = NULL, links <- reqInfos$links clusters <- reqInfos$clusters clustersRes <- reqInfos$clustersRes + clustersST <- reqInfos$clustersST districts <- reqInfos$districts mcYears <- reqInfos$mcYears synthesis <- reqInfos$synthesis @@ -328,7 +335,7 @@ readAntares <- function(areas = NULL, links = NULL, clusters = NULL, return(aggregateResult(opts = opts, verbose = showProgress, filtering = TRUE, - selected = list(areas = areas, links = links, clusters = clusters, clustersRes = clustersRes), + selected = list(areas = areas, links = links, clusters = clusters, clustersRes = clustersRes, clustersST = clustersST), timestep = timeStep, writeOutput = FALSE, mcWeights = mcWeights, mcYears = mcYears)) @@ -342,7 +349,7 @@ readAntares <- function(areas = NULL, links = NULL, clusters = NULL, } # If all arguments are NULL, import all areas - if (is.null(areas) & is.null(links) & is.null(clusters) & is.null(clustersRes) & is.null(districts)) { + if (is.null(areas) & is.null(links) & is.null(clusters) & is.null(clustersRes) & is.null(clustersST) & is.null(districts)) { areas <- "all" } @@ -353,6 +360,7 @@ readAntares <- function(areas = NULL, links = NULL, clusters = NULL, links <- .checkArg(links, opts$linkList, "Links %s do not exist in the simulation.") clusters <- .checkArg(clusters, opts$areasWithClusters, "Areas %s do not exist in the simulation or do not have any thermal cluster.") clustersRes <- .checkArg(clustersRes, opts$areasWithResClusters, "Areas %s do not exist in the simulation or do not have any renewable cluster.") + clustersST <- .checkArg(clustersST, opts$areasWithSTClusters, "Areas %s do not exist in the simulation or do not have any short-term cluster.") districts <- .checkArg(districts, opts$districtList, "Districts %s do not exist in the simulation.") mcYears <- .checkArg(mcYears, opts$mcYears, "Monte-Carlo years %s have not been exported.", allowDup = TRUE) @@ -476,6 +484,12 @@ readAntares <- function(areas = NULL, links = NULL, clusters = NULL, opts, parallel = parallel) if(!is.null(res$clustersRes) && nrow(res$clustersRes) == 0) res$clustersRes <- NULL + # Import short-term clusters + res$clustersST <- .importOutputForSTClusters(clustersST, timeStep, NULL, + mcYears, showProgress, + opts, parallel = parallel) + if(!is.null(res$clustersST) && nrow(res$clustersST) == 0) res$clustersST <- NULL + # Import thermal clusters and eventually must run if (!mustRun) { res$clusters <- .importOutputForClusters(clusters, timeStep, NULL, mcYears, @@ -820,6 +834,7 @@ readAntaresAreas <- function(areas, links = TRUE, clusters = TRUE, clustersRes = links, clusters, clustersRes, + clustersST, districts, mcYears){ @@ -873,6 +888,10 @@ readAntaresAreas <- function(areas, links = TRUE, clusters = TRUE, clustersRes = if (!is.null(areas)) clustersRes <- areas else clustersRes <- "all" } + if ("clustersST" %in% unlist(select) & is.null(clustersST)) { + if (!is.null(areas)) clustersST <- areas + else clustersST <- "all" + } if ("mcYears" %in% unlist(select) & is.null(mcYears)) mcYears <- "all" # If all arguments are NULL, import all areas @@ -888,6 +907,7 @@ readAntaresAreas <- function(areas, links = TRUE, clusters = TRUE, clustersRes = links = links, clusters = clusters, clustersRes = clustersRes, + clustersST = clustersST, districts = districts, mcYears = mcYears, synthesis = synthesis, diff --git a/R/setSimulationPath.R b/R/setSimulationPath.R index 5df538e3..cebd1659 100644 --- a/R/setSimulationPath.R +++ b/R/setSimulationPath.R @@ -477,6 +477,20 @@ setSimulationPath <- function(path, simulation = NULL) { areasWithResClusters <- sort(union(areaList_mc_all[hasResClusters_mc_all], areaList_mc_ind[hasResClusters_mc_ind])) + + # Areas containing renewable clusters + hasSTClusters_mc_all <- laply(file.path(dataPath_mc_all, "areas", areaList_mc_all), function(x) { + f <- list.files(x) + any(grepl("details-res-", f)) + }) + hasSTClusters_mc_ind <- laply(file.path(dataPath_mc_ind, "areas", areaList_mc_ind), function(x) { + f <- list.files(x) + any(grepl("details-STstorage-", f)) + }) + + areasWithSTClusters <- sort(union(areaList_mc_all[hasSTClusters_mc_all], + areaList_mc_ind[hasSTClusters_mc_ind])) + # Available variables variables <- list() @@ -518,6 +532,7 @@ setSimulationPath <- function(path, simulation = NULL) { linksDef = linksDef, areasWithClusters = areasWithClusters, areasWithResClusters = areasWithResClusters, + areasWithSTClusters = areasWithSTClusters, variables = variables, parameters = params ) diff --git a/man/readAntares.Rd b/man/readAntares.Rd index 92f153bc..64d8cb68 100644 --- a/man/readAntares.Rd +++ b/man/readAntares.Rd @@ -10,6 +10,7 @@ readAntares( clusters = NULL, districts = NULL, clustersRes = NULL, + clustersST = NULL, bindingConstraints = FALSE, misc = FALSE, thermalAvailabilities = FALSE, @@ -53,6 +54,11 @@ import results at renewable cluster level. If \code{NULL} no cluster is imported special value \code{"all"} tells the function to import renewable clusters from all areas.} +\item{clustersST}{Vector containing the name of the areas for which you want to +import results at short-term cluster level. If \code{NULL} no cluster is imported. The +special value \code{"all"} tells the function to import short-term clusters from all +areas.} + \item{bindingConstraints}{Should binding constraints be imported (v8.4+)?} \item{misc}{Vector containing the name of the areas for which you want to diff --git a/tests/testthat/test-importOutputForClusters.R b/tests/testthat/test-importOutputForClusters.R index caef7428..4464853b 100644 --- a/tests/testthat/test-importOutputForClusters.R +++ b/tests/testthat/test-importOutputForClusters.R @@ -8,7 +8,7 @@ opts <- setSimulationPath(path_study_test,simulation="20240105-0934eco") test_that(".importOutputForSTClusters is ok", { - OutputForRESClusters <- .importOutputForSTClusters( + OutputForSTClusters <- .importOutputForSTClusters( areas="fr", timeStep="annual", showProgress=FALSE, @@ -16,6 +16,6 @@ test_that(".importOutputForSTClusters is ok", { opts=opts ) - expect_true(all(c("injection","level","withdrawal") %in% colnames(OutputForRESClusters))) - expect_equal(nrow(OutputForRESClusters),1) + expect_true(all(c("injection","level","withdrawal") %in% colnames(OutputForSTClusters))) + expect_equal(nrow(OutputForSTClusters),1) }) diff --git a/tests/testthat/test-readAntares_STclusters.R b/tests/testthat/test-readAntares_STclusters.R new file mode 100644 index 00000000..6f94d9ba --- /dev/null +++ b/tests/testthat/test-readAntares_STclusters.R @@ -0,0 +1,19 @@ +#Copyright © 2016 RTE Réseau de transport d’électricité + +context("Function readAntares (ST clusters)") + +path_study_test <- grep(pattern = "87", x = studyPathSV8, value = TRUE) + +opts <- setSimulationPath(path_study_test,simulation="20240105-0934eco") + +test_that("ST clusters importation is ok", { + clustersST <- readAntares(clustersST="all",timeStep="annual",opts = opts)$clustersST + + expect_true(all(c("injection","level","withdrawal") %in% colnames(clustersST))) + expect_true(all(opts$areasWithSTClusters %in% clustersST$area)) + + clustersST_fr <- readAntares(clustersST="fr",timeStep="annual",opts = opts)$clustersST + + expect_true(all(c("injection","level","withdrawal") %in% colnames(clustersST_fr))) + expect_true("fr" %in% clustersST$area) +}) From a462ee662d8ec4cb3a8c9052cd1c668ffa3e1282 Mon Sep 17 00:00:00 2001 From: "BOITARD Nicolas (Externe)" <123453373+boitardn@users.noreply.github.com> Date: Fri, 7 Jun 2024 17:17:29 +0200 Subject: [PATCH 03/14] create a wrapper for calling .reshape_details_file() --- R/importOutput.R | 136 ++++++++++++++++------------------------------- 1 file changed, 47 insertions(+), 89 deletions(-) diff --git a/R/importOutput.R b/R/importOutput.R index 573cd316..f87f8509 100644 --- a/R/importOutput.R +++ b/R/importOutput.R @@ -350,36 +350,8 @@ .importOutputForClusters <- function(areas, timeStep, select = NULL, mcYears = NULL, showProgress, opts, mustRun = FALSE, parallel) { - # In output files, there is one file per area with the follwing form: - # cluster1-var1 | cluster2-var1 | cluster1-var2 | cluster2-var2 - # the following function reshapes the result to have variable cluster in column. - # To improve greatly the performance we use our knowledge of the position of - # the columns instead of using more general functions like dcast. - reshapeFun <- function(x) { - - # Get cluster names - n <- names(x) - idx <- ! n %in% pkgEnv$idVars - clusterNames <- tolower(unique(n[idx])) - - # Id vars names - idVarsId <- which(!idx) - idVarsNames <- n[idVarsId] - - # Column names of the output table - colNames <- .get_value_columns_details_file(opts, "details") - - # Loop over clusters - nclusters <- length(clusterNames) - - res <- llply(1:nclusters, function(i) { - dt <- x[, c(nclusters * 0:(length(colNames) - 1) + i, idVarsId), with = FALSE] - setnames(dt, c(colNames, idVarsNames)) - dt[, cluster := as.factor(clusterNames[i])] - dt - }) - - rbindlist(res) + reshapeFun <- function(x){ + .reshape_details_file(x,"details",opts) } if (!mustRun) { @@ -492,6 +464,47 @@ } +#' .reshape_details_file +#' +#' In output files, there is one file per area with the follwing form: +#' cluster1-var1 | cluster2-var1 | cluster1-var2 | cluster2-var2 +#' the following function reshapes the result to have variable cluster in column. +#' To improve greatly the performance we use our knowledge of the position of +#' the columns instead of using more general functions like dcast. +#' +#' @return +#' a data.table +#' +#' @noRd +#' +.reshape_details_file <- function(x,file_type,opts) { + + # Get cluster names + n <- names(x) + idx <- ! n %in% pkgEnv$idVars + clusterNames <- tolower(unique(n[idx])) + + # Id vars names + idVarsId <- which(!idx) + idVarsNames <- n[idVarsId] + + # Column names of the output table + colNames <- .get_value_columns_details_file(opts,file_type) + + # Loop over clusters + nclusters <- length(clusterNames) + + res <- llply(1:nclusters, function(i) { + dt <- x[, c(nclusters * 0:(length(colNames) - 1) + i, idVarsId), with = FALSE] + setnames(dt, c(colNames, idVarsNames)) + dt[, cluster := as.factor(clusterNames[i])] + dt + }) + + rbindlist(res) +} + + #' .importOutputForResClusters #' #' Private function used to import the output for the renewable clusters of one area @@ -504,38 +517,11 @@ .importOutputForResClusters <- function(areas, timeStep, select = NULL, mcYears = NULL, showProgress, opts, parallel) { - # In output files, there is one file per area with the follwing form: - # cluster1-var1 | cluster2-var1 | cluster1-var2 | cluster2-var2 - # the following function reshapes the result to have variable cluster in column. - # To improve greatly the performance we use our knowledge of the position of - # the columns instead of using more general functions like dcast. - reshapeFun <- function(x) { - # Get cluster names - n <- names(x) - idx <- ! n %in% pkgEnv$idVars - clusterNames <- tolower(unique(n[idx])) - - # Id vars names - idVarsId <- which(!idx) - idVarsNames <- n[idVarsId] - - # Column names of the output table - colNames <- .get_value_columns_details_file(opts, "details-res") - - # Loop over clusters - nclusters <- length(clusterNames) - - res <- llply(1:nclusters, function(i) { - dt <- x[, c(nclusters * 0:(length(colNames) - 1) + i, idVarsId), with = FALSE] - setnames(dt, c(colNames, idVarsNames)) - dt[, cluster := as.factor(clusterNames[i])] - dt - }) - - rbindlist(res) + reshapeFun <- function(x) { + .reshape_details_file(x,"details-res",opts) } - + suppressWarnings( .importOutput("areas", "details-res", "area", areas, timeStep, NULL, mcYears, showProgress, opts, reshapeFun, sameNames = FALSE, @@ -556,36 +542,8 @@ .importOutputForSTClusters <- function(areas, timeStep, select = NULL, mcYears = NULL, showProgress, opts, parallel) { - # In output files, there is one file per area with the follwing form: - # cluster1-var1 | cluster2-var1 | cluster1-var2 | cluster2-var2 - # the following function reshapes the result to have variable cluster in column. - # To improve greatly the performance we use our knowledge of the position of - # the columns instead of using more general functions like dcast. reshapeFun <- function(x) { - - # Get cluster names - n <- names(x) - idx <- ! n %in% pkgEnv$idVars - clusterNames <- tolower(unique(n[idx])) - - # Id vars names - idVarsId <- which(!idx) - idVarsNames <- n[idVarsId] - - # Column names of the output table - colNames <- .get_value_columns_details_file(opts, "details-STstorage") - - # Loop over clusters - nclusters <- length(clusterNames) - - res <- llply(1:nclusters, function(i) { - dt <- x[, c(nclusters * 0:(length(colNames) - 1) + i, idVarsId), with = FALSE] - setnames(dt, c(colNames, idVarsNames)) - dt[, cluster := as.factor(clusterNames[i])] - dt - }) - - rbindlist(res) + .reshape_details_file(x,"details-STstorage",opts) } suppressWarnings( From 227197ca0b43d8952d686b03acabe875b0359ac1 Mon Sep 17 00:00:00 2001 From: "BOITARD Nicolas (Externe)" <123453373+boitardn@users.noreply.github.com> Date: Mon, 10 Jun 2024 17:42:27 +0200 Subject: [PATCH 04/14] Simplify .get_value_columns_details_file() with a reference table --- DESCRIPTION | 3 +- NAMESPACE | 1 + R/importOutput.R | 46 +++++++++++-------- R/zzz.R | 2 +- .../simulation_variables_names_by_support.csv | 9 ++++ tests/testthat/test-importOutputForClusters.R | 43 ++++++++++++++++- tests/testthat/test-readAntares_STclusters.R | 7 +-- 7 files changed, 85 insertions(+), 26 deletions(-) create mode 100644 inst/simulation_variables_names_by_support.csv diff --git a/DESCRIPTION b/DESCRIPTION index 6cbe66ea..33064df3 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -40,7 +40,8 @@ Imports: utils, memuse, purrr, - lifecycle + lifecycle, + assertthat Suggests: rhdf5 (>= 2.24.0), testthat, diff --git a/NAMESPACE b/NAMESPACE index a3692c35..fff146e5 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -79,6 +79,7 @@ import(doParallel) import(jsonlite) import(parallel) import(plyr) +importFrom(assertthat,assert_that) importFrom(doParallel,registerDoParallel) importFrom(grDevices,col2rgb) importFrom(grDevices,rgb) diff --git a/R/importOutput.R b/R/importOutput.R index f87f8509..0eedfcc9 100644 --- a/R/importOutput.R +++ b/R/importOutput.R @@ -287,28 +287,38 @@ #' #' @return #' a vector +#' +#' @importFrom assertthat assert_that #' #' @noRd #' .get_value_columns_details_file <- function(opts, type) { - if(type == "details") { - # Order is important. There is a correspondance between elements. - all_thematic_variables <- c("DTG by plant", "NP Cost by plant", "NODU by plant") - colNames <- c("production", "NP Cost", "NODU") - if (opts$antaresVersion >= 830){ - all_thematic_variables <- c(all_thematic_variables, "Profit by plant") - colNames <- c(colNames, "profit") - } - } else if(type == "details-res") { - # Order is important. There is a correspondance between elements. - all_thematic_variables <- c("RES generation by plant") - colNames <- c("production") - } else if(type == "details-STstorage") { - # Order is important. There is a correspondance between elements. - all_thematic_variables <- c("STS inj by plant","STS lvl by plant","STS withdrawal by plant") - colNames <- c("injection","level","withdrawal") - } + assert_that(type %in% c("details","details-res","details-STstorage")) + + simulation_variables_names_by_support <- data.table(read.table(system.file( + "simulation_variables_names_by_support.csv",package="antaresRead" + ))) + + # Order is important. There is a correspondance between elements + simulation_variables_names_by_support <- simulation_variables_names_by_support[ + order(ORDINAL_POSITION_BY_TOPIC), + ] + + filtering_topic <- switch( + type, + "details"="Generation / Thermal", + "details-res"="Generation / Renewables", + "details-STstorage"="Generation / Short-Term Storages" + ) + + filtered_variables_names <- subset(simulation_variables_names_by_support,TOPIC==filtering_topic) + if (type=="details" && opts$antaresVersion < 830) + filtered_variables_names <- subset(filtered_variables_names,ANTARES_DISPLAYED_NAME!="Profit by plant") + + all_thematic_variables <- filtered_variables_names$ANTARES_DISPLAYED_NAME + colNames <- filtered_variables_names$RPACKAGE_DISPLAYED_NAME + # With thematic-trimming enabled if (opts$parameters$general$`thematic-trimming`) { if ("variables selection" %in% names(opts$parameters)) { @@ -490,7 +500,7 @@ # Column names of the output table colNames <- .get_value_columns_details_file(opts,file_type) - + # Loop over clusters nclusters <- length(clusterNames) diff --git a/R/zzz.R b/R/zzz.R index e1a7f4da..2e0a2c37 100644 --- a/R/zzz.R +++ b/R/zzz.R @@ -104,7 +104,7 @@ utils::globalVariables( "NODU", "min.stable.power", "thermalPmin", "name", "value", "Folder", "Mode", "Stats", "Name", "progNam", "mrgprice", "isLOLD_cum", "...To", "upstream", "downstream", "LOLD", "LOLD_data", "LOLP", "warn_for_status", - "MRG. PRICE", "H. LEV", "V2", "V1") + "MRG. PRICE", "H. LEV", "V2", "V1", "ORDINAL_POSITION_BY_TOPIC", "TOPIC", "ANTARES_DISPLAYED_NAME") ) #----------------------------- HDF5 ------------------------------------# diff --git a/inst/simulation_variables_names_by_support.csv b/inst/simulation_variables_names_by_support.csv new file mode 100644 index 00000000..8aa67005 --- /dev/null +++ b/inst/simulation_variables_names_by_support.csv @@ -0,0 +1,9 @@ +"TOPIC" "ANTARES_DISPLAYED_NAME" "ORDINAL_POSITION_BY_TOPIC" "TITLE" "ALIAS" "MIN_VERSION" "OUTPUT_DISPLAYED_NAME" "RPACKAGE_DISPLAYED_NAME" +"1" "Generation / Thermal" "DTG by plant" 1 "Dispatchable Thermal Generation by Thermal Cluster (MWh)" "dtgByPlant" NA "MWh" "production" +"2" "Generation / Thermal" "NODU by plant" 3 "Number of Dispatched Units by Thermal Cluster" "noduByPlant" NA "NODU" "NODU" +"3" "Generation / Thermal" "NP Cost by plant" 2 "Non-Proportional Costs by Thermal Cluster (€)" "npCostByPlant" NA "NP Cost - Euro" "NP Cost" +"4" "Generation / Thermal" "Profit by plant" 4 "Net Profit by Thermal Cluster (€)" "profitByPlant" 830 "Profit - Euro" "profit" +"5" "Generation / Renewables" "RES generation by plant" 1 "Renewable Energy Generation by Power Plant Cluster (MWh)" "resGenerationByPlant" 810 "MWh" "production" +"6" "Generation / Short-Term Storages" "STS inj by plant" 1 "Short-Term Storage Injection by Power Plant (MWh)" "stsInjByPlant" 860 "P-injection - MW" "P.injection" +"7" "Generation / Short-Term Storages" "STS lvl by plant" 2 "Short-Term Storage Level by Power Plant (MWh)" "stsLvlByPlant" 860 "Levels - MWh" "levels" +"8" "Generation / Short-Term Storages" "STS withdrawal by plant" 3 "Short-Term Storage Withdrawal by Power Plant (MWh)" "stsWithdrawalByPlant" 860 "P-withdrawal - MW" "P.withdrawal" diff --git a/tests/testthat/test-importOutputForClusters.R b/tests/testthat/test-importOutputForClusters.R index 4464853b..c39f574d 100644 --- a/tests/testthat/test-importOutputForClusters.R +++ b/tests/testthat/test-importOutputForClusters.R @@ -5,6 +5,43 @@ context("Functions .importOutput") path_study_test <- grep(pattern = "87", x = studyPathSV8, value = TRUE) opts <- setSimulationPath(path_study_test,simulation="20240105-0934eco") + +test_that(".importOutputForClusters is ok", { + + OutputForClusters <- .importOutputForClusters( + areas="fr", + timeStep="annual", + showProgress=FALSE, + parallel=FALSE, + opts=opts + ) + + required_order_simulation_variables <- c("production","NP Cost","NODU","profit") + + order_simulation_variables <- colnames(OutputForClusters)[colnames(OutputForClusters) %in% required_order_simulation_variables] + + expect_equal(order_simulation_variables,required_order_simulation_variables) + expect_equal(nrow(OutputForClusters),1) +}) + + +test_that(".importOutputForResClusters is ok", { + + OutputForResClusters <- .importOutputForResClusters( + areas="fr", + timeStep="annual", + showProgress=FALSE, + parallel=FALSE, + opts=opts + ) + + required_order_simulation_variables <- c("production") + + order_simulation_variables <- colnames(OutputForResClusters)[colnames(OutputForResClusters) %in% required_order_simulation_variables] + + expect_equal(order_simulation_variables,required_order_simulation_variables) + expect_equal(nrow(OutputForResClusters),1) +}) test_that(".importOutputForSTClusters is ok", { @@ -16,6 +53,10 @@ test_that(".importOutputForSTClusters is ok", { opts=opts ) - expect_true(all(c("injection","level","withdrawal") %in% colnames(OutputForSTClusters))) + required_order_simulation_variables <- c("P.injection","levels","P.withdrawal") + + order_simulation_variables <- colnames(OutputForSTClusters)[colnames(OutputForSTClusters) %in% required_order_simulation_variables] + + expect_equal(order_simulation_variables,required_order_simulation_variables) expect_equal(nrow(OutputForSTClusters),1) }) diff --git a/tests/testthat/test-readAntares_STclusters.R b/tests/testthat/test-readAntares_STclusters.R index 6f94d9ba..e3bade74 100644 --- a/tests/testthat/test-readAntares_STclusters.R +++ b/tests/testthat/test-readAntares_STclusters.R @@ -7,13 +7,10 @@ path_study_test <- grep(pattern = "87", x = studyPathSV8, value = TRUE) opts <- setSimulationPath(path_study_test,simulation="20240105-0934eco") test_that("ST clusters importation is ok", { - clustersST <- readAntares(clustersST="all",timeStep="annual",opts = opts)$clustersST - expect_true(all(c("injection","level","withdrawal") %in% colnames(clustersST))) + clustersST <- readAntares(clustersST="all",timeStep="annual",opts = opts)$clustersST expect_true(all(opts$areasWithSTClusters %in% clustersST$area)) clustersST_fr <- readAntares(clustersST="fr",timeStep="annual",opts = opts)$clustersST - - expect_true(all(c("injection","level","withdrawal") %in% colnames(clustersST_fr))) - expect_true("fr" %in% clustersST$area) + expect_true("fr"==unique(clustersST_fr$area)) }) From c1562f2b64bedfd597a77297a682daf4cc5f7819 Mon Sep 17 00:00:00 2001 From: "BOITARD Nicolas (Externe)" <123453373+boitardn@users.noreply.github.com> Date: Tue, 11 Jun 2024 10:57:22 +0200 Subject: [PATCH 05/14] Correct areasWithSTClusters parameter in .getSimOptions() --- R/setSimulationPath.R | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/R/setSimulationPath.R b/R/setSimulationPath.R index 3a75d5c5..52692979 100644 --- a/R/setSimulationPath.R +++ b/R/setSimulationPath.R @@ -483,10 +483,10 @@ setSimulationPath <- function(path, simulation = NULL) { areaList_mc_ind[hasResClusters_mc_ind])) - # Areas containing renewable clusters + # Areas containing short-term clusters hasSTClusters_mc_all <- laply(file.path(dataPath_mc_all, "areas", areaList_mc_all), function(x) { f <- list.files(x) - any(grepl("details-res-", f)) + any(grepl("details-STstorage-", f)) }) hasSTClusters_mc_ind <- laply(file.path(dataPath_mc_ind, "areas", areaList_mc_ind), function(x) { f <- list.files(x) From 528c6375edee3ad2e04cfb8dcab70e45a3b230e2 Mon Sep 17 00:00:00 2001 From: "BOITARD Nicolas (Externe)" <123453373+boitardn@users.noreply.github.com> Date: Tue, 11 Jun 2024 15:12:07 +0200 Subject: [PATCH 06/14] Add unit tests for 'areasWithSTClusters' parameter --- tests/testthat/test-setSimulationPath.R | 15 +++++++++++++++ 1 file changed, 15 insertions(+) diff --git a/tests/testthat/test-setSimulationPath.R b/tests/testthat/test-setSimulationPath.R index 06cfbf59..eb5e21f1 100644 --- a/tests/testthat/test-setSimulationPath.R +++ b/tests/testthat/test-setSimulationPath.R @@ -178,6 +178,11 @@ test_that("Folder 'maps' is not interpreted as a study (#49)", { } +test_that("No meta info areas with a ST cluster < 860", { + opts <- setSimulationPath(studyPath, "input") + expect_true(length(opts$areasWithSTClusters)==0) +}) + test_that("No meta info binding study < 870", { opts <- setSimulationPath(studyPath, "input") expect_null(opts$binding) @@ -185,6 +190,16 @@ test_that("No meta info binding study < 870", { }) +# v860---- +test_that("New meta data for areas with a ST cluster", { + # read latest version study + path_study_test <- grep(pattern = "87", x = studyPathSV8, value = TRUE) + opts_study_test <- setSimulationPath(path_study_test, simulation = "20240105-0934eco") + + expect_false(is.null(opts_study_test$areasWithSTClusters)) +}) + + # v870---- test_that("New meta data for group dimension of binding constraints", { # read latest version study From 3a3b8ac5e9136ecdd82248d99bd5b1115dd774a7 Mon Sep 17 00:00:00 2001 From: "BOITARD Nicolas (Externe)" <123453373+boitardn@users.noreply.github.com> Date: Tue, 11 Jun 2024 15:13:11 +0200 Subject: [PATCH 07/14] Add DETAILS_FILES_TYPE column in the simulation_variables_names_by_support.csv --- R/importOutput.R | 11 ++--------- R/zzz.R | 4 ++-- .../simulation_variables_names_by_support.csv | 9 +++++++++ inst/simulation_variables_names_by_support.csv | 9 --------- 4 files changed, 13 insertions(+), 20 deletions(-) create mode 100644 inst/format_output/simulation_variables_names_by_support.csv delete mode 100644 inst/simulation_variables_names_by_support.csv diff --git a/R/importOutput.R b/R/importOutput.R index 0eedfcc9..8a3b7b9f 100644 --- a/R/importOutput.R +++ b/R/importOutput.R @@ -297,7 +297,7 @@ assert_that(type %in% c("details","details-res","details-STstorage")) simulation_variables_names_by_support <- data.table(read.table(system.file( - "simulation_variables_names_by_support.csv",package="antaresRead" + "format_output","simulation_variables_names_by_support.csv",package="antaresRead" ))) # Order is important. There is a correspondance between elements @@ -305,14 +305,7 @@ order(ORDINAL_POSITION_BY_TOPIC), ] - filtering_topic <- switch( - type, - "details"="Generation / Thermal", - "details-res"="Generation / Renewables", - "details-STstorage"="Generation / Short-Term Storages" - ) - - filtered_variables_names <- subset(simulation_variables_names_by_support,TOPIC==filtering_topic) + filtered_variables_names <- subset(simulation_variables_names_by_support,DETAILS_FILES_TYPE==type) if (type=="details" && opts$antaresVersion < 830) filtered_variables_names <- subset(filtered_variables_names,ANTARES_DISPLAYED_NAME!="Profit by plant") diff --git a/R/zzz.R b/R/zzz.R index 949ec204..3ebc75fd 100644 --- a/R/zzz.R +++ b/R/zzz.R @@ -104,8 +104,8 @@ utils::globalVariables( "NODU", "min.stable.power", "thermalPmin", "name", "value", "Folder", "Mode", "Stats", "Name", "progNam", "mrgprice", "isLOLD_cum", "...To", "upstream", "downstream", "LOLD", "LOLD_data", "LOLP", "warn_for_status", - "MRG. PRICE", "H. LEV", "V2", "V1", "size", "ORDINAL_POSITION_BY_TOPIC", "TOPIC", - "ANTARES_DISPLAYED_NAME") + "MRG. PRICE", "H. LEV", "V2", "V1", "size", "ORDINAL_POSITION_BY_TOPIC", + "DETAILS_FILES_TYPE","ANTARES_DISPLAYED_NAME") ) #----------------------------- HDF5 ------------------------------------# diff --git a/inst/format_output/simulation_variables_names_by_support.csv b/inst/format_output/simulation_variables_names_by_support.csv new file mode 100644 index 00000000..45cedb42 --- /dev/null +++ b/inst/format_output/simulation_variables_names_by_support.csv @@ -0,0 +1,9 @@ +"TOPIC" "DETAILS_FILES_TYPE" "ANTARES_DISPLAYED_NAME" "ORDINAL_POSITION_BY_TOPIC" "TITLE" "ALIAS" "MIN_VERSION" "OUTPUT_DISPLAYED_NAME" "RPACKAGE_DISPLAYED_NAME" +"1" "Generation / Thermal" "details" "DTG by plant" 1 "Dispatchable Thermal Generation by Thermal Cluster (MWh)" "dtgByPlant" NA "MWh" "production" +"2" "Generation / Thermal" "details" "NODU by plant" 3 "Number of Dispatched Units by Thermal Cluster" "noduByPlant" NA "NODU" "NODU" +"3" "Generation / Thermal" "details" "NP Cost by plant" 2 "Non-Proportional Costs by Thermal Cluster (€)" "npCostByPlant" NA "NP Cost - Euro" "NP Cost" +"4" "Generation / Thermal" "details" "Profit by plant" 4 "Net Profit by Thermal Cluster (€)" "profitByPlant" 830 "Profit - Euro" "profit" +"5" "Generation / Renewables" "details-res" "RES generation by plant" 1 "Renewable Energy Generation by Power Plant Cluster (MWh)" "resGenerationByPlant" 810 "MWh" "production" +"6" "Generation / Short-Term Storages" "details-STstorage" "STS inj by plant" 1 "Short-Term Storage Injection by Power Plant (MWh)" "stsInjByPlant" 860 "P-injection - MW" "P.injection" +"7" "Generation / Short-Term Storages" "details-STstorage" "STS lvl by plant" 2 "Short-Term Storage Level by Power Plant (MWh)" "stsLvlByPlant" 860 "Levels - MWh" "levels" +"8" "Generation / Short-Term Storages" "details-STstorage" "STS withdrawal by plant" 3 "Short-Term Storage Withdrawal by Power Plant (MWh)" "stsWithdrawalByPlant" 860 "P-withdrawal - MW" "P.withdrawal" diff --git a/inst/simulation_variables_names_by_support.csv b/inst/simulation_variables_names_by_support.csv deleted file mode 100644 index 8aa67005..00000000 --- a/inst/simulation_variables_names_by_support.csv +++ /dev/null @@ -1,9 +0,0 @@ -"TOPIC" "ANTARES_DISPLAYED_NAME" "ORDINAL_POSITION_BY_TOPIC" "TITLE" "ALIAS" "MIN_VERSION" "OUTPUT_DISPLAYED_NAME" "RPACKAGE_DISPLAYED_NAME" -"1" "Generation / Thermal" "DTG by plant" 1 "Dispatchable Thermal Generation by Thermal Cluster (MWh)" "dtgByPlant" NA "MWh" "production" -"2" "Generation / Thermal" "NODU by plant" 3 "Number of Dispatched Units by Thermal Cluster" "noduByPlant" NA "NODU" "NODU" -"3" "Generation / Thermal" "NP Cost by plant" 2 "Non-Proportional Costs by Thermal Cluster (€)" "npCostByPlant" NA "NP Cost - Euro" "NP Cost" -"4" "Generation / Thermal" "Profit by plant" 4 "Net Profit by Thermal Cluster (€)" "profitByPlant" 830 "Profit - Euro" "profit" -"5" "Generation / Renewables" "RES generation by plant" 1 "Renewable Energy Generation by Power Plant Cluster (MWh)" "resGenerationByPlant" 810 "MWh" "production" -"6" "Generation / Short-Term Storages" "STS inj by plant" 1 "Short-Term Storage Injection by Power Plant (MWh)" "stsInjByPlant" 860 "P-injection - MW" "P.injection" -"7" "Generation / Short-Term Storages" "STS lvl by plant" 2 "Short-Term Storage Level by Power Plant (MWh)" "stsLvlByPlant" 860 "Levels - MWh" "levels" -"8" "Generation / Short-Term Storages" "STS withdrawal by plant" 3 "Short-Term Storage Withdrawal by Power Plant (MWh)" "stsWithdrawalByPlant" 860 "P-withdrawal - MW" "P.withdrawal" From a35d9837807be60c4c3e8742a2fa106b66c59fb0 Mon Sep 17 00:00:00 2001 From: "BOITARD Nicolas (Externe)" <123453373+boitardn@users.noreply.github.com> Date: Tue, 11 Jun 2024 15:31:00 +0200 Subject: [PATCH 08/14] Update NEWS.md --- DESCRIPTION | 1 + NEWS.md | 2 ++ man/antaresRead-package.Rd | 1 + 3 files changed, 4 insertions(+) diff --git a/DESCRIPTION b/DESCRIPTION index 921e529d..b7369c9a 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -15,6 +15,7 @@ Authors@R: c( person("Clement", "Berthet", role = "ctb"), person("Kamel", "Kemiha", role = "ctb"), person("Abdallah", "Mahoudi", role = "ctb"), + person("Nicolas", "Boitard", role = "ctb"), person("RTE", role = "cph") ) Description: Import, manipulate and explore results generated by 'Antares', a diff --git a/NEWS.md b/NEWS.md index 5bde60e1..46a80865 100644 --- a/NEWS.md +++ b/NEWS.md @@ -10,6 +10,7 @@ NEW FEATURES: * `readInputRES()` new parameter **areas** to get desired clusters from selected areas. * `setSimulationPath()` return a new parameter `binding` (for studies >= v8.7.0). It contains a table with group dimensions of time series for binding constraints. +* `readAntares()` new parameter **clustersST** to read short-term clusters BREAKING CHANGES : @@ -18,6 +19,7 @@ BREAKING CHANGES : BUGFIXES : * `readInputThermal()` return data from file data.txt with `thermalData` parameter +* `setSimulationPath()` has also the parameter **areasWithSTClusters** in 'output' mode # antaresRead 2.7.0 diff --git a/man/antaresRead-package.Rd b/man/antaresRead-package.Rd index 6e14dd10..79f26bc3 100644 --- a/man/antaresRead-package.Rd +++ b/man/antaresRead-package.Rd @@ -37,6 +37,7 @@ Other contributors: \item Clement Berthet [contributor] \item Kamel Kemiha [contributor] \item Abdallah Mahoudi [contributor] + \item Nicolas Boitard [contributor] \item RTE [copyright holder] } From facff5fb2c6545c0e3dda6ea3c14e66e47df05cc Mon Sep 17 00:00:00 2001 From: "BOITARD Nicolas (Externe)" <123453373+boitardn@users.noreply.github.com> Date: Tue, 11 Jun 2024 16:00:14 +0200 Subject: [PATCH 09/14] Make new parameter 'clustersST' API compatible --- R/utils_api.R | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/R/utils_api.R b/R/utils_api.R index 40284089..562e31cd 100644 --- a/R/utils_api.R +++ b/R/utils_api.R @@ -162,6 +162,15 @@ read_secure_json <- function(url, token = NULL, timeout = 60, config = list()) { ) areasWithResClusters <- names(hasResClusters)[hasResClusters] + + hasSTClusters <- unlist( + lapply( + read_secure_json(file.path(dataPath, "areas&depth=2"), ...), + function(x) any(grepl("details-STstorage-", names(x))) + ) + ) + + areasWithSTClusters <- names(hasSTClusters)[hasSTClusters] # Available variables variables <- list() @@ -212,6 +221,7 @@ read_secure_json <- function(url, token = NULL, timeout = 60, config = list()) { linksDef = linksDef, areasWithClusters = intersect(areasWithClusters, areaList), areasWithResClusters = intersect(areasWithResClusters, areaList), + areasWithSTClusters = intersect(areasWithSTClusters, areaList), variables = variables, parameters = params ) From a117df42a5335bf44d62d423bd0825d362d3c56b Mon Sep 17 00:00:00 2001 From: "BOITARD Nicolas (Externe)" <123453373+boitardn@users.noreply.github.com> Date: Wed, 12 Jun 2024 11:37:05 +0200 Subject: [PATCH 10/14] Update documentation with the new function .importOutputForSTClusters() --- R/importOutput.R | 4 ++-- R/readAntares.R | 2 ++ man/readAntares.Rd | 2 ++ 3 files changed, 6 insertions(+), 2 deletions(-) diff --git a/R/importOutput.R b/R/importOutput.R index 8a3b7b9f..ba086a53 100644 --- a/R/importOutput.R +++ b/R/importOutput.R @@ -281,8 +281,8 @@ #' .get_value_columns_details_file #' -#' Private function used to get the column names for the details-timeStep.txt or details-res-timeStep.txt. -#' Used in .importOutputForClusters() and .importOutputForResClusters() +#' Private function used to get the column names for the details-timeStep.txt, details-res-timeStep.txt, or details-STstorage-timeStep.txt. +#' Used in .importOutputForClusters(), .importOutputForResClusters(), and .importOutputForSTClusters() #' From the opts, we detect which outputs the user decides to take #' #' @return diff --git a/R/readAntares.R b/R/readAntares.R index af518693..3cd256a1 100644 --- a/R/readAntares.R +++ b/R/readAntares.R @@ -14,6 +14,8 @@ #' Read the data of an Antares simulation #' #' @description +#' `r antaresRead:::badge_api_ok()` +#' #' \code{readAntares} is a swiss-army-knife function used to read almost every #' possible time series of an antares Project at any desired time resolution #' (hourly, daily, weekly, monthly or annual). diff --git a/man/readAntares.Rd b/man/readAntares.Rd index 64d8cb68..2431cc23 100644 --- a/man/readAntares.Rd +++ b/man/readAntares.Rd @@ -137,6 +137,8 @@ data.tables, each element representing one type of element (areas, links, clusters) } \description{ +\ifelse{html}{\figure{badge_api_ok.svg}{options: alt='Antares API OK'}}{Antares API: \strong{OK}} + \code{readAntares} is a swiss-army-knife function used to read almost every possible time series of an antares Project at any desired time resolution (hourly, daily, weekly, monthly or annual). From caad5bb014f41054b46aa4580eeaef6100b9c836 Mon Sep 17 00:00:00 2001 From: "BOITARD Nicolas (Externe)" <123453373+boitardn@users.noreply.github.com> Date: Wed, 12 Jun 2024 11:51:35 +0200 Subject: [PATCH 11/14] Import simulation_variables_names_by_support.csv in data.frame type rather than data.table --- R/importOutput.R | 18 +++++++++--------- 1 file changed, 9 insertions(+), 9 deletions(-) diff --git a/R/importOutput.R b/R/importOutput.R index ba086a53..851faa95 100644 --- a/R/importOutput.R +++ b/R/importOutput.R @@ -296,21 +296,21 @@ assert_that(type %in% c("details","details-res","details-STstorage")) - simulation_variables_names_by_support <- data.table(read.table(system.file( + simulation_variables_names_by_support <- read.table(system.file( "format_output","simulation_variables_names_by_support.csv",package="antaresRead" - ))) - - # Order is important. There is a correspondance between elements - simulation_variables_names_by_support <- simulation_variables_names_by_support[ - order(ORDINAL_POSITION_BY_TOPIC), - ] + )) filtered_variables_names <- subset(simulation_variables_names_by_support,DETAILS_FILES_TYPE==type) if (type=="details" && opts$antaresVersion < 830) filtered_variables_names <- subset(filtered_variables_names,ANTARES_DISPLAYED_NAME!="Profit by plant") - all_thematic_variables <- filtered_variables_names$ANTARES_DISPLAYED_NAME - colNames <- filtered_variables_names$RPACKAGE_DISPLAYED_NAME + # Order is important. There is a correspondance between elements + ordered_filtered_variables_names <- filtered_variables_names[ + order(filtered_variables_names$ORDINAL_POSITION_BY_TOPIC), + ] + + all_thematic_variables <- ordered_filtered_variables_names$ANTARES_DISPLAYED_NAME + colNames <- ordered_filtered_variables_names$RPACKAGE_DISPLAYED_NAME # With thematic-trimming enabled if (opts$parameters$general$`thematic-trimming`) { From 020198af0c9564df15649196e0788a92fd21c5dd Mon Sep 17 00:00:00 2001 From: "BOITARD Nicolas (Externe)" <123453373+boitardn@users.noreply.github.com> Date: Wed, 12 Jun 2024 15:50:30 +0200 Subject: [PATCH 12/14] Specify the separator for the simulation_variables_names_by_support.csv import --- R/importOutput.R | 11 ++++++----- .../simulation_variables_names_by_support.csv | 18 +++++++++--------- 2 files changed, 15 insertions(+), 14 deletions(-) diff --git a/R/importOutput.R b/R/importOutput.R index 851faa95..95036833 100644 --- a/R/importOutput.R +++ b/R/importOutput.R @@ -47,6 +47,7 @@ #' - "areas", "values" => areas #' - "areas", "details" => clusters #' - "areas", "details-res" => renewables clusters +#' - "areas", "details-STstorage" => short-term clusters #' - "links", "values" => links #' #' @return @@ -298,7 +299,7 @@ simulation_variables_names_by_support <- read.table(system.file( "format_output","simulation_variables_names_by_support.csv",package="antaresRead" - )) + ),sep=";",fileEncoding="UTF-8",header = TRUE) filtered_variables_names <- subset(simulation_variables_names_by_support,DETAILS_FILES_TYPE==type) if (type=="details" && opts$antaresVersion < 830) @@ -354,7 +355,7 @@ showProgress, opts, mustRun = FALSE, parallel) { reshapeFun <- function(x){ - .reshape_details_file(x,"details",opts) + .reshape_details_file(x,file_type="details",opts=opts) } if (!mustRun) { @@ -492,7 +493,7 @@ idVarsNames <- n[idVarsId] # Column names of the output table - colNames <- .get_value_columns_details_file(opts,file_type) + colNames <- .get_value_columns_details_file(opts=opts,type=file_type) # Loop over clusters nclusters <- length(clusterNames) @@ -522,7 +523,7 @@ reshapeFun <- function(x) { - .reshape_details_file(x,"details-res",opts) + .reshape_details_file(x,file_type="details-res",opts=opts) } suppressWarnings( @@ -546,7 +547,7 @@ showProgress, opts, parallel) { reshapeFun <- function(x) { - .reshape_details_file(x,"details-STstorage",opts) + .reshape_details_file(x,file_type="details-STstorage",opts=opts) } suppressWarnings( diff --git a/inst/format_output/simulation_variables_names_by_support.csv b/inst/format_output/simulation_variables_names_by_support.csv index 45cedb42..8e7dc32d 100644 --- a/inst/format_output/simulation_variables_names_by_support.csv +++ b/inst/format_output/simulation_variables_names_by_support.csv @@ -1,9 +1,9 @@ -"TOPIC" "DETAILS_FILES_TYPE" "ANTARES_DISPLAYED_NAME" "ORDINAL_POSITION_BY_TOPIC" "TITLE" "ALIAS" "MIN_VERSION" "OUTPUT_DISPLAYED_NAME" "RPACKAGE_DISPLAYED_NAME" -"1" "Generation / Thermal" "details" "DTG by plant" 1 "Dispatchable Thermal Generation by Thermal Cluster (MWh)" "dtgByPlant" NA "MWh" "production" -"2" "Generation / Thermal" "details" "NODU by plant" 3 "Number of Dispatched Units by Thermal Cluster" "noduByPlant" NA "NODU" "NODU" -"3" "Generation / Thermal" "details" "NP Cost by plant" 2 "Non-Proportional Costs by Thermal Cluster (€)" "npCostByPlant" NA "NP Cost - Euro" "NP Cost" -"4" "Generation / Thermal" "details" "Profit by plant" 4 "Net Profit by Thermal Cluster (€)" "profitByPlant" 830 "Profit - Euro" "profit" -"5" "Generation / Renewables" "details-res" "RES generation by plant" 1 "Renewable Energy Generation by Power Plant Cluster (MWh)" "resGenerationByPlant" 810 "MWh" "production" -"6" "Generation / Short-Term Storages" "details-STstorage" "STS inj by plant" 1 "Short-Term Storage Injection by Power Plant (MWh)" "stsInjByPlant" 860 "P-injection - MW" "P.injection" -"7" "Generation / Short-Term Storages" "details-STstorage" "STS lvl by plant" 2 "Short-Term Storage Level by Power Plant (MWh)" "stsLvlByPlant" 860 "Levels - MWh" "levels" -"8" "Generation / Short-Term Storages" "details-STstorage" "STS withdrawal by plant" 3 "Short-Term Storage Withdrawal by Power Plant (MWh)" "stsWithdrawalByPlant" 860 "P-withdrawal - MW" "P.withdrawal" +"TOPIC";"DETAILS_FILES_TYPE";"ANTARES_DISPLAYED_NAME";"ORDINAL_POSITION_BY_TOPIC";"TITLE";"ALIAS";"MIN_VERSION";"OUTPUT_DISPLAYED_NAME";"RPACKAGE_DISPLAYED_NAME" +"Generation / Thermal";"details";"DTG by plant";1;"Dispatchable Thermal Generation by Thermal Cluster (MWh)";"dtgByPlant";;"MWh";"production" +"Generation / Thermal";"details";"NODU by plant";3;"Number of Dispatched Units by Thermal Cluster";"noduByPlant";;"NODU";"NODU" +"Generation / Thermal";"details";"NP Cost by plant";2;"Non-Proportional Costs by Thermal Cluster (€)";"npCostByPlant";;"NP Cost - Euro";"NP Cost" +"Generation / Thermal";"details";"Profit by plant";4;"Net Profit by Thermal Cluster (€)";"profitByPlant";830;"Profit - Euro";"profit" +"Generation / Renewables";"details-res";"RES generation by plant";1;"Renewable Energy Generation by Power Plant Cluster (MWh)";"resGenerationByPlant";810;"MWh";"production" +"Generation / Short-Term Storages";"details-STstorage";"STS inj by plant";1;"Short-Term Storage Injection by Power Plant (MWh)";"stsInjByPlant";860;"P-injection - MW";"P.injection" +"Generation / Short-Term Storages";"details-STstorage";"STS lvl by plant";2;"Short-Term Storage Level by Power Plant (MWh)";"stsLvlByPlant";860;"Levels - MWh";"levels" +"Generation / Short-Term Storages";"details-STstorage";"STS withdrawal by plant";3;"Short-Term Storage Withdrawal by Power Plant (MWh)";"stsWithdrawalByPlant";860;"P-withdrawal - MW";"P.withdrawal" From 21f3b7c36afe32339981a0de86e427f1a052618d Mon Sep 17 00:00:00 2001 From: "BOITARD Nicolas (Externe)" <123453373+boitardn@users.noreply.github.com> Date: Thu, 13 Jun 2024 11:59:18 +0200 Subject: [PATCH 13/14] Check reverse dependencies --- revdep/README.md | 69 ++++++++++++++++++++++++++++++++++-------------- revdep/cran.md | 2 +- 2 files changed, 50 insertions(+), 21 deletions(-) diff --git a/revdep/README.md b/revdep/README.md index 16a7e2e3..aeb69b06 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -1,28 +1,57 @@ # Platform -|field |value | -|:--------|:-----------------------------------| -|version |R version 4.2.2 (2022-10-31 ucrt) | -|os |Windows 10 x64 (build 19045) | -|system |x86_64, mingw32 | -|ui |RStudio | -|language |(EN) | -|collate |French_France.utf8 | -|ctype |French_France.utf8 | -|tz |Europe/Paris | -|date |2024-05-27 | -|rstudio |2023.12.0+369 Ocean Storm (desktop) | -|pandoc |NA | +|field |value | +|:--------|:------------------------------| +|version |R version 4.1.0 (2021-05-18) | +|os |Windows 10 x64 (build 19045) | +|system |x86_64, mingw32 | +|ui |RStudio | +|language |(EN) | +|collate |French_France.1252 | +|ctype |French_France.1252 | +|tz |Europe/Paris | +|date |2024-06-13 | +|rstudio |1.4.1103 Wax Begonia (desktop) | +|pandoc |NA | # Dependencies -|package |old |new |Δ | -|:-----------|:-----|:-----|:--| -|antaresRead |2.6.1 |2.7.0 |* | -|cachem |NA |1.0.8 |* | -|fastmap |NA |1.1.1 |* | -|openssl |NA |2.1.2 |* | -|stringi |NA |1.8.3 |* | +|package |old |new | | +|:-----------|:-----|:-------|:--| +|antaresRead |2.7.0 |2.7.1 |* | +|askpass |NA |1.1 |* | +|cachem |NA |1.0.7 |* | +|cli |NA |3.6.2 |* | +|commonmark |NA |1.9.1 |* | +|cpp11 |NA |0.4.7 |* | +|curl |NA |5.2.1 |* | +|data.table |NA |1.14.8 |* | +|digest |NA |0.6.35 |* | +|fastmap |NA |1.2.0 |* | +|fontawesome |NA |0.5.2 |* | +|fs |NA |1.6.4 |* | +|glue |NA |1.7.0 |* | +|htmltools |NA |0.5.5 |* | +|httpuv |NA |1.6.9 |* | +|httr |NA |1.4.7 |* | +|jsonlite |NA |1.8.8 |* | +|later |NA |1.3.0 |* | +|lifecycle |NA |1.0.4 |* | +|lubridate |NA |1.9.2 |* | +|openssl |NA |2.0.6 |* | +|plyr |NA |1.8.8 |* | +|promises |NA |1.2.0.1 |* | +|purrr |NA |1.0.1 |* | +|Rcpp |NA |1.0.12 |* | +|rlang |NA |1.1.4 |* | +|sass |NA |0.4.5 |* | +|shiny |NA |1.8.1.1 |* | +|stringi |NA |1.7.12 |* | +|stringr |NA |1.5.1 |* | +|sys |NA |3.4.2 |* | +|timechange |NA |0.2.0 |* | +|vctrs |NA |0.6.1 |* | +|withr |NA |3.0.0 |* | # Revdeps diff --git a/revdep/cran.md b/revdep/cran.md index 29c19611..33114b63 100644 --- a/revdep/cran.md +++ b/revdep/cran.md @@ -1,6 +1,6 @@ ## revdepcheck results -We checked 3 reverse dependencies, comparing R CMD check results across CRAN and dev versions of this package. +We checked 0 reverse dependencies, comparing R CMD check results across CRAN and dev versions of this package. * We saw 0 new problems * We failed to check 0 packages From 2d719472b110e743465193ee83170453f6729f39 Mon Sep 17 00:00:00 2001 From: berthetclement Date: Fri, 14 Jun 2024 09:41:26 +0200 Subject: [PATCH 14/14] revdep check ok --- NEWS.md | 2 +- revdep/README.md | 70 +++++++++++++++--------------------------------- revdep/cran.md | 2 +- 3 files changed, 23 insertions(+), 51 deletions(-) diff --git a/NEWS.md b/NEWS.md index 46a80865..adb88af3 100644 --- a/NEWS.md +++ b/NEWS.md @@ -10,7 +10,7 @@ NEW FEATURES: * `readInputRES()` new parameter **areas** to get desired clusters from selected areas. * `setSimulationPath()` return a new parameter `binding` (for studies >= v8.7.0). It contains a table with group dimensions of time series for binding constraints. -* `readAntares()` new parameter **clustersST** to read short-term clusters +* `readAntares()` new parameter **clustersST** to read (output simulation) short-term clusters BREAKING CHANGES : diff --git a/revdep/README.md b/revdep/README.md index aeb69b06..25ad2f71 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -1,57 +1,29 @@ # Platform -|field |value | -|:--------|:------------------------------| -|version |R version 4.1.0 (2021-05-18) | -|os |Windows 10 x64 (build 19045) | -|system |x86_64, mingw32 | -|ui |RStudio | -|language |(EN) | -|collate |French_France.1252 | -|ctype |French_France.1252 | -|tz |Europe/Paris | -|date |2024-06-13 | -|rstudio |1.4.1103 Wax Begonia (desktop) | -|pandoc |NA | +|field |value | +|:--------|:-----------------------------------| +|version |R version 4.2.2 (2022-10-31 ucrt) | +|os |Windows 10 x64 (build 19045) | +|system |x86_64, mingw32 | +|ui |RStudio | +|language |(EN) | +|collate |French_France.utf8 | +|ctype |French_France.utf8 | +|tz |Europe/Paris | +|date |2024-06-13 | +|rstudio |2023.12.0+369 Ocean Storm (desktop) | +|pandoc |NA | # Dependencies -|package |old |new | | -|:-----------|:-----|:-------|:--| -|antaresRead |2.7.0 |2.7.1 |* | -|askpass |NA |1.1 |* | -|cachem |NA |1.0.7 |* | -|cli |NA |3.6.2 |* | -|commonmark |NA |1.9.1 |* | -|cpp11 |NA |0.4.7 |* | -|curl |NA |5.2.1 |* | -|data.table |NA |1.14.8 |* | -|digest |NA |0.6.35 |* | -|fastmap |NA |1.2.0 |* | -|fontawesome |NA |0.5.2 |* | -|fs |NA |1.6.4 |* | -|glue |NA |1.7.0 |* | -|htmltools |NA |0.5.5 |* | -|httpuv |NA |1.6.9 |* | -|httr |NA |1.4.7 |* | -|jsonlite |NA |1.8.8 |* | -|later |NA |1.3.0 |* | -|lifecycle |NA |1.0.4 |* | -|lubridate |NA |1.9.2 |* | -|openssl |NA |2.0.6 |* | -|plyr |NA |1.8.8 |* | -|promises |NA |1.2.0.1 |* | -|purrr |NA |1.0.1 |* | -|Rcpp |NA |1.0.12 |* | -|rlang |NA |1.1.4 |* | -|sass |NA |0.4.5 |* | -|shiny |NA |1.8.1.1 |* | -|stringi |NA |1.7.12 |* | -|stringr |NA |1.5.1 |* | -|sys |NA |3.4.2 |* | -|timechange |NA |0.2.0 |* | -|vctrs |NA |0.6.1 |* | -|withr |NA |3.0.0 |* | +|package |old |new |Δ | +|:-----------|:-----|:-----|:--| +|antaresRead |2.7.0 |2.7.1 |* | +|cachem |NA |1.0.8 |* | +|fastmap |NA |1.1.1 |* | +|openssl |NA |2.1.2 |* | +|rlang |NA |1.1.3 |* | +|stringi |NA |1.8.3 |* | # Revdeps diff --git a/revdep/cran.md b/revdep/cran.md index 33114b63..29c19611 100644 --- a/revdep/cran.md +++ b/revdep/cran.md @@ -1,6 +1,6 @@ ## revdepcheck results -We checked 0 reverse dependencies, comparing R CMD check results across CRAN and dev versions of this package. +We checked 3 reverse dependencies, comparing R CMD check results across CRAN and dev versions of this package. * We saw 0 new problems * We failed to check 0 packages