From d3f3aa84d2a1bff5b232badeaeae53557099421e Mon Sep 17 00:00:00 2001 From: Nekmek7 Date: Tue, 4 Jun 2024 10:59:16 +0200 Subject: [PATCH 01/14] change columns name, first try of endpoint table_mode, dynamic endpoint --- R/readClusterDesc.R | 114 ++++++++++++++++++++++---------------------- 1 file changed, 57 insertions(+), 57 deletions(-) diff --git a/R/readClusterDesc.R b/R/readClusterDesc.R index dad0515e..686a13a1 100644 --- a/R/readClusterDesc.R +++ b/R/readClusterDesc.R @@ -105,77 +105,77 @@ readClusterSTDesc <- function(opts = simOptions()) { } path <- file.path(opts$inputPath, dir) - columns <- .generate_columns_by_type(dir = dir) api_study <- is_api_study(opts) if(api_study){ - jsoncld <- read_secure_json(paste0(path, "&depth=4"), token = opts$token, timeout = opts$timeout, config = opts$httr_config) - res <- rbindlist(mapply(function(X1, Y1){ - clusters <- rbindlist( - mapply(function(X, Y){ - out <- as.data.frame(X) - if(nrow(out) == 0)return(NULL) - out$area = Y - out - }, X1$list, names(X1$list), SIMPLIFY = FALSE), fill = TRUE) - if(is.null(clusters))return(NULL) - if(nrow(clusters)==0)return(NULL) - clusters$area <- Y1 - clusters[, .SD, .SDcols = order(names(clusters))] - },jsoncld, names(jsoncld), SIMPLIFY = FALSE), fill = TRUE) - - - }else{ - - areas <- list.files(path) + table_type <- switch( + dir, + "thermal/clusters" = "thermals", + "renewables/clusters" = "renewables", + "st-storage/clusters" = "st-storages" + ) - res <- ldply(areas, function(x) { - clusters <- readIniFile(file.path(path, x, "list.ini")) + list_clusters = api_get( + opts = opts, + endpoint = paste0(opts$study_id, "/table-mode/",table_type), + query = list( + columns = "" + ) + ) + if(length(list_clusters) == 0){ + mandatory_cols <- c("area","cluster") + warning("No cluster description available.", call. = FALSE) + res <- setNames(data.table(matrix(nrow = 0, ncol = length(mandatory_cols) + length(columns))), c(mandatory_cols, columns)) + }else{ + clusters <- rbindlist(list_clusters, idcol = "cluster") + newcol <- data.table() + newcol <- newcol[, c("area", "cluster") := tstrsplit(clusters$cluster, " / ", fixed = TRUE, keep = 1:2)] + res <- data.table(newcol,clusters[,-"cluster"]) - if (length(clusters) == 0) return(NULL) - - clusters <- ldply(clusters, as.data.frame) - clusters$.id <- NULL - clusters$area <- x - - clusters[, c(ncol(clusters), 1:(ncol(clusters) - 1))] - }) - - } - - if(length(res) == 0){ - mandatory_cols <- c("area","cluster") - warning("No cluster description available.", call. = FALSE) - res <- setNames(data.table(matrix(nrow = 0, ncol = length(mandatory_cols) + length(columns))), c(mandatory_cols, columns)) - }else{ - if(api_study){ - mandatory_cols <- c("area", "name", "group") - additional_cols <- setdiff(colnames(res),mandatory_cols) - res <- res[, .SD, .SDcols = c(mandatory_cols, additional_cols)] + }else{ + areas <- list.files(path) + res <- ldply(areas, function(x) { + clusters <- readIniFile(file.path(path, x, "list.ini")) + if (length(clusters) == 0) return(NULL) + clusters <- ldply(clusters, as.data.frame) + clusters$.id <- NULL + clusters$area <- x + clusters[, c(ncol(clusters), 1:(ncol(clusters) - 1))] + }) + } + if(length(res) == 0){ + mandatory_cols <- c("area","cluster") + warning("No cluster description available.", call. = FALSE) + res <- setNames(data.table(matrix(nrow = 0, ncol = length(mandatory_cols) + length(columns))), c(mandatory_cols, columns)) + }else{ + if(api_study){ + mandatory_cols <- c("area", "name", "group") + additional_cols <- setdiff(colnames(res),mandatory_cols) + res <- res[, .SD, .SDcols = c(mandatory_cols, additional_cols)] + } + res <- as.data.table(res) + setnames(res, "name", "cluster") + res$cluster <- as.factor(tolower(res$cluster)) } - res <- as.data.table(res) - setnames(res, "name", "cluster") - res$cluster <- as.factor(tolower(res$cluster)) + res } - - res } - .generate_columns_by_type <- function(dir = c("thermal/clusters", "renewables/clusters", "st-storage/clusters")) { - columns <- switch( dir, - "thermal/clusters" = c("group","enabled","must_run","unit_count","nominal_capacity", - "min_stable_power","spinning","min_up_time","min_down_time", - "co2","marginal_cost","fixed_cost","startup_cost","market_bid_cost", - "spread_cost","ts_gen","volatility_forced","volatility_planned", - "law_forced","law_planned"), + "thermal/clusters" = c("name","group","enabled","mustRun","unitCount","nominalCapacity", + "minStablePower","spinning","minUpTime","minDownTime", + "co2","marginalCost","fixedCost","startupCost","marketBidCost", + "spreadCost","tsGen","volatilityForced","volatilityPlanned", + "lawForced","lawPlanned"), - "renewables/clusters" = c("group","ts_interpretation","enabled","unit_count","nominal_capacity") - #"st-storage/clusters" = #ATTENTE DEV COTé API + "renewables/clusters" = c("name","group","ts-interpretation","enabled","unitCount","nominalCapacity"), + + "st-storage/clusters" = c("name","group","enabled","injection_nominal_capacity","withdrawal_nominal_capacity", + "reservoir_capacity","efficiency","initial_level","initial_level_optim") ) return(columns) -} +} \ No newline at end of file From d7d9d45d24d8e51a4e086d3db82fda30947f2234 Mon Sep 17 00:00:00 2001 From: Nekmek7 Date: Tue, 4 Jun 2024 11:19:20 +0200 Subject: [PATCH 02/14] typo --- R/readClusterDesc.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/readClusterDesc.R b/R/readClusterDesc.R index 686a13a1..41329559 100644 --- a/R/readClusterDesc.R +++ b/R/readClusterDesc.R @@ -134,6 +134,7 @@ readClusterSTDesc <- function(opts = simOptions()) { newcol <- newcol[, c("area", "cluster") := tstrsplit(clusters$cluster, " / ", fixed = TRUE, keep = 1:2)] res <- data.table(newcol,clusters[,-"cluster"]) + } }else{ areas <- list.files(path) res <- ldply(areas, function(x) { @@ -160,7 +161,6 @@ readClusterSTDesc <- function(opts = simOptions()) { res$cluster <- as.factor(tolower(res$cluster)) } res - } } .generate_columns_by_type <- function(dir = c("thermal/clusters", "renewables/clusters", "st-storage/clusters")) { From 909d0b72235420029d7fda62048a51e828c1f8de Mon Sep 17 00:00:00 2001 From: Nekmek7 Date: Tue, 4 Jun 2024 11:46:27 +0200 Subject: [PATCH 03/14] change "cluster" by "name", conversion of "name" in "cluster" common for each case --- R/readClusterDesc.R | 58 ++++++++++++++++++++++----------------------- 1 file changed, 29 insertions(+), 29 deletions(-) diff --git a/R/readClusterDesc.R b/R/readClusterDesc.R index 41329559..04cfee07 100644 --- a/R/readClusterDesc.R +++ b/R/readClusterDesc.R @@ -125,42 +125,42 @@ readClusterSTDesc <- function(opts = simOptions()) { ) ) if(length(list_clusters) == 0){ - mandatory_cols <- c("area","cluster") + mandatory_cols <- c("area","name") warning("No cluster description available.", call. = FALSE) res <- setNames(data.table(matrix(nrow = 0, ncol = length(mandatory_cols) + length(columns))), c(mandatory_cols, columns)) }else{ - clusters <- rbindlist(list_clusters, idcol = "cluster") + clusters <- rbindlist(list_clusters, idcol = "name") newcol <- data.table() - newcol <- newcol[, c("area", "cluster") := tstrsplit(clusters$cluster, " / ", fixed = TRUE, keep = 1:2)] - res <- data.table(newcol,clusters[,-"cluster"]) + newcol <- newcol[, c("area", "name") := tstrsplit(clusters$name, " / ", fixed = TRUE, keep = 1:2)] + res <- data.table(newcol,clusters[,-"name"]) } - }else{ - areas <- list.files(path) - res <- ldply(areas, function(x) { - clusters <- readIniFile(file.path(path, x, "list.ini")) - if (length(clusters) == 0) return(NULL) - clusters <- ldply(clusters, as.data.frame) - clusters$.id <- NULL - clusters$area <- x - clusters[, c(ncol(clusters), 1:(ncol(clusters) - 1))] - }) - } - if(length(res) == 0){ - mandatory_cols <- c("area","cluster") - warning("No cluster description available.", call. = FALSE) - res <- setNames(data.table(matrix(nrow = 0, ncol = length(mandatory_cols) + length(columns))), c(mandatory_cols, columns)) - }else{ - if(api_study){ - mandatory_cols <- c("area", "name", "group") - additional_cols <- setdiff(colnames(res),mandatory_cols) - res <- res[, .SD, .SDcols = c(mandatory_cols, additional_cols)] - } - res <- as.data.table(res) - setnames(res, "name", "cluster") - res$cluster <- as.factor(tolower(res$cluster)) + }else{ + areas <- list.files(path) + res <- ldply(areas, function(x) { + clusters <- readIniFile(file.path(path, x, "list.ini")) + if (length(clusters) == 0) return(NULL) + clusters <- ldply(clusters, as.data.frame) + clusters$.id <- NULL + clusters$area <- x + clusters[, c(ncol(clusters), 1:(ncol(clusters) - 1))] + }) + } + if(length(res) == 0){ + mandatory_cols <- c("area","name") + warning("No cluster description available.", call. = FALSE) + res <- setNames(data.table(matrix(nrow = 0, ncol = length(mandatory_cols) + length(columns))), c(mandatory_cols, columns)) + }else{ + if(api_study){ + mandatory_cols <- c("area", "name", "group") + additional_cols <- setdiff(colnames(res),mandatory_cols) + res <- res[, .SD, .SDcols = c(mandatory_cols, additional_cols)] } - res + } + res <- as.data.table(res) + setnames(res, "name", "cluster") + res$cluster <- as.factor(tolower(res$cluster)) + res } .generate_columns_by_type <- function(dir = c("thermal/clusters", "renewables/clusters", "st-storage/clusters")) { From 757be3b2aba1dd76df582b43d843ca5346d1cc83 Mon Sep 17 00:00:00 2001 From: berthetclement Date: Thu, 13 Jun 2024 16:31:30 +0200 Subject: [PATCH 04/14] add 3 referential for input properties clusters + manage package --- DESCRIPTION | 1 + R/readClusterDesc.R | 8 +- R/utils.R | 1 + R/zzz.R | 104 +++++++++++------- .../properties_input_renewable.csv | 7 ++ .../properties_input_storage.csv | 11 ++ .../properties_input_thermal.csv | 37 +++++++ tests/testthat/test-readClusterDesc.R | 8 ++ 8 files changed, 136 insertions(+), 41 deletions(-) create mode 100644 inst/referential_properties/properties_input_renewable.csv create mode 100644 inst/referential_properties/properties_input_storage.csv create mode 100644 inst/referential_properties/properties_input_thermal.csv diff --git a/DESCRIPTION b/DESCRIPTION index 6cbe66ea..1a1ed819 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -23,6 +23,7 @@ Description: Import, manipulate and explore results generated by 'Antares', a URL: https://github.com/rte-antares-rpackage/antaresRead, https://rte-antares-rpackage.github.io/antaresRead/ BugReports: https://github.com/rte-antares-rpackage/antaresRead/issues License: GPL (>= 2) | file LICENSE +StagedInstall: no Imports: data.table (>= 1.9.6), bit64, diff --git a/R/readClusterDesc.R b/R/readClusterDesc.R index 04cfee07..64d76b5b 100644 --- a/R/readClusterDesc.R +++ b/R/readClusterDesc.R @@ -127,11 +127,15 @@ readClusterSTDesc <- function(opts = simOptions()) { if(length(list_clusters) == 0){ mandatory_cols <- c("area","name") warning("No cluster description available.", call. = FALSE) - res <- setNames(data.table(matrix(nrow = 0, ncol = length(mandatory_cols) + length(columns))), c(mandatory_cols, columns)) + res <- setNames(data.table(matrix(nrow = 0, + ncol = length(mandatory_cols) + length(columns))), + c(mandatory_cols, columns)) }else{ clusters <- rbindlist(list_clusters, idcol = "name") newcol <- data.table() - newcol <- newcol[, c("area", "name") := tstrsplit(clusters$name, " / ", fixed = TRUE, keep = 1:2)] + newcol <- newcol[, c("area", "name") := tstrsplit(clusters$name, " / ", + fixed = TRUE, + keep = 1:2)] res <- data.table(newcol,clusters[,-"name"]) } diff --git a/R/utils.R b/R/utils.R index 4ac4d8b5..c26aa91e 100644 --- a/R/utils.R +++ b/R/utils.R @@ -1,3 +1,4 @@ +# badge doc ---- badge_api_ok <- function() { "\\ifelse{html}{\\figure{badge_api_ok.svg}{options: alt='Antares API OK'}}{Antares API: \\strong{OK}}" } diff --git a/R/zzz.R b/R/zzz.R index e1a7f4da..23bdb6d9 100644 --- a/R/zzz.R +++ b/R/zzz.R @@ -11,11 +11,14 @@ #' @importFrom utils untar #' @importFrom stringr str_match str_replace + +# private variables ---- # Private variables accessible only by functions from the package pkgEnv <- new.env() +## output variables ---- pkgEnv$formatName <- read.table(system.file("format_output/tableOutput.csv", package = "antaresRead"), sep = ";", header = TRUE) @@ -86,6 +89,7 @@ setAlias("nostat", "All variables except summary variable (MIN, MAX and STD)", "FLOW QUAD.", "CONG. FEE (ALG.)", "CONG. FEE (ABS.)", "MARG. COST", "CONG. PROB +", "CONG. PROB -", "HURDLE COST")) +## global vars package ---- # The goal of the following lines is only to remove many useless warnings in # R CMD CHECK: "no visible binding for global variable 'XXX'". # They come from the use of the data.table syntax. @@ -107,51 +111,29 @@ utils::globalVariables( "MRG. PRICE", "H. LEV", "V2", "V1") ) -#----------------------------- HDF5 ------------------------------------# +## INPUT Properties REF ---- +ref_input_properties_path <- file.path(system.file(package = "antaresRead"), + "referential_properties") +all_ref_properties_path <- list.files(ref_input_properties_path, + full.names = TRUE) +names_files <- gsub(pattern = ".csv", + replacement = "", + x = list.files(ref_input_properties_path)) -is.installed <- function(mypkg) is.element(mypkg, utils::installed.packages()[,1]) +list_files_ref <- lapply(all_ref_properties_path, + data.table::fread, + encoding="UTF-8", + strip.white=FALSE) -rhdf5_version <- "2.24.0" -rhdf5_message <- "This function require 'rhdf5' (>= 2.24.0) package. - This is a bioconductor package. You can install it with : - source('https://bioconductor.org/biocLite.R') - biocLite('rhdf5')" - -# !! parameter versionCheck of requireNamespace does not work correctly, use utils::package_version instead -.requireRhdf5_Antares <- function(stopP = TRUE){ - if(.check_rhdf5(stopP = stopP)){ - if(.check_rhdf5_version(stopP = stopP)){ - return(TRUE) - } - } - return(FALSE) -} - -.stop_rhdf5_version <- function(stopP = TRUE) { - if(stopP){ - stop(rhdf5_message) - }else{ - return(FALSE) - } -} +names(list_files_ref) <- names_files -.check_rhdf5 <- function(stopP = TRUE){ - if(requireNamespace("rhdf5", quietly = TRUE)){ - return(TRUE) - }else{ - .stop_rhdf5_version(stopP) - } -} +df_files_ref <- do.call("rbind", list_files_ref) +pkgEnv$inputProperties <- df_files_ref -.check_rhdf5_version <- function(stopP = TRUE){ - if(utils::packageVersion("rhdf5") >= rhdf5_version){ - return(TRUE) - }else{ - .stop_rhdf5_version(stopP) - } -} +#----------------------------- HDF5 ------------------------------------# +# HDF5 ---- # .addClassAndAttributes <- antaresRead:::.addClassAndAttributes pkgEnvAntareasH5 <- new.env() @@ -257,7 +239,50 @@ integerVariable <- as.character(unique(pkgEnv$formatName$Name[which(pkgEnv$forma integerVariable <- unlist(apply(expand.grid(integerVariable, c("", "_std", "_min", "_max")), 1, function(X){paste0(X, collapse = "")})) +# rhfd5 functions ---- +is.installed <- function(mypkg) is.element(mypkg, utils::installed.packages()[,1]) +rhdf5_version <- "2.24.0" +rhdf5_message <- "This function require 'rhdf5' (>= 2.24.0) package. + This is a bioconductor package. You can install it with : + source('https://bioconductor.org/biocLite.R') + biocLite('rhdf5')" + +# !! parameter versionCheck of requireNamespace does not work correctly, use utils::package_version instead +.requireRhdf5_Antares <- function(stopP = TRUE){ + if(.check_rhdf5(stopP = stopP)){ + if(.check_rhdf5_version(stopP = stopP)){ + return(TRUE) + } + } + return(FALSE) +} + +.stop_rhdf5_version <- function(stopP = TRUE) { + if(stopP){ + stop(rhdf5_message) + }else{ + return(FALSE) + } +} + +.check_rhdf5 <- function(stopP = TRUE){ + if(requireNamespace("rhdf5", quietly = TRUE)){ + return(TRUE) + }else{ + .stop_rhdf5_version(stopP) + } +} + +.check_rhdf5_version <- function(stopP = TRUE){ + if(utils::packageVersion("rhdf5") >= rhdf5_version){ + return(TRUE) + }else{ + .stop_rhdf5_version(stopP) + } +} + +# some tools functions ---- .tidymess <- function(..., prefix = " ", initial = ""){ as.character(strwrap(..., prefix = prefix, initial = initial)) } @@ -286,3 +311,4 @@ integerVariable <- unlist(apply(expand.grid(integerVariable, c("", "_std", "_min bydistrict <- c("district", .get_by(x)) return(bydistrict) } + diff --git a/inst/referential_properties/properties_input_renewable.csv b/inst/referential_properties/properties_input_renewable.csv new file mode 100644 index 00000000..4fa409b9 --- /dev/null +++ b/inst/referential_properties/properties_input_renewable.csv @@ -0,0 +1,7 @@ +Topic;INI Name;Tech Name;Type;Default;Version;Category +General;name;name;str;;8.1;renewable +General;group;group;str;;8.1;renewable +General;ts-interpretation;ts-interpretation;str;power-generation;8.1;renewable +Operating parameters;enabled;enabled;;True;8.1;renewable +Operating parameters;unitcount;unitCount;int;1;8.1;renewable +Operating parameters;nominalcapacity;nominalCapacity;float;0.0;8.1;renewable diff --git a/inst/referential_properties/properties_input_storage.csv b/inst/referential_properties/properties_input_storage.csv new file mode 100644 index 00000000..a135d55a --- /dev/null +++ b/inst/referential_properties/properties_input_storage.csv @@ -0,0 +1,11 @@ +Topic;INI Name;Tech Name;Type;Default;Version;Category +General;name;name;str;;8.6;storage +General;group;group;str;;8.6;storage +General;enabled;enabled;bool;True;8.8;storage +General;injectionnominalcapacity;injection_nominal_capacity;float;0.0;8.6;storage +General;withdrawalnominalcapacity;withdrawal_nominal_capacity;float;0.0;8.6;storage +General;reservoircapacity;reservoir_capacity;float;0.0;8.6;storage +General;efficiency;efficiency;float;0.0;8.6;storage +General;initiallevel;initial_level;float;0.5;8.8;storage +General;initiallevel;initial_level;float;0;8.6;storage +General;initialleveloptim;initial_level_optim;bool;False;8.6;storage diff --git a/inst/referential_properties/properties_input_thermal.csv b/inst/referential_properties/properties_input_thermal.csv new file mode 100644 index 00000000..3e389ae6 --- /dev/null +++ b/inst/referential_properties/properties_input_thermal.csv @@ -0,0 +1,37 @@ +Topic;INI Name;Tech Name;Type;Default;Version;Category +General;name;name;str;;;thermal +General;group;group;str;Other 1;;thermal +Operating parameters;unitcount;unitCount;int;1;;thermal +Operating parameters;enabled;enabled;bool;True;;thermal +Operating parameters;nominalcapacity;nominalCapacity;float;0.0;;thermal +Operating parameters;min-stable-power;minStablePower;float;0.0;;thermal +Operating parameters;min-up-time;minUpTime;int;1;;thermal +Operating parameters;min-down-time;minDownTime;int;1;;thermal +Operating parameters;must-run;mustRun;bool;False;;thermal +Operating parameters;spinning;spinning;float;0.0;;thermal +Operating costs;costgeneration;costGeneration;str;SetManually;8.7;thermal +Operating costs;efficiency;efficiency;float;100.0;8.7;thermal +Operating costs;variableomcost;variableOMCost;float;0.0;8.7;thermal +Operating costs;marginal-cost;marginalCost;float;0.0;;thermal +Operating costs;spread-cost;spreadCost;float;0.0;;thermal +Operating costs;fixed-cost;fixedCost;float;0.0;;thermal +Operating costs;startup-cost;startupCost;float;0.0;;thermal +Operating costs;market-bid-cost;marketBidCost;float;0.0;;thermal +Pollutant emission rates;co2;co2;float;0.0;;thermal +Pollutant emission rates;nh3;nh3;float;0.0;8.6;thermal +Pollutant emission rates;so2;so2;float;0.0;8.6;thermal +Pollutant emission rates;nox;nox;float;0.0;8.6;thermal +Pollutant emission rates;pm2_5;pm25;float;0.0;8.6;thermal +Pollutant emission rates;pm5;pm5;float;0.0;8.6;thermal +Pollutant emission rates;pm10;pm10;float;0.0;8.6;thermal +Pollutant emission rates;nmvoc;nmvoc;float;0.0;8.6;thermal +Pollutant emission rates;op1;op1;float;0.0;8.6;thermal +Pollutant emission rates;op2;op2;float;0.0;8.6;thermal +Pollutant emission rates;op3;op3;float;0.0;8.6;thermal +Pollutant emission rates;op4;op4;float;0.0;8.6;thermal +Pollutant emission rates;op5;op5;float;0.0;8.6;thermal +Timeseries generation;gen-ts;genTs;str;Use Global;;thermal +Timeseries generation;volatility.forced;volatilityForced;float;0.0;;thermal +Timeseries generation;volatility.planned;volatilityPlanned;float;0.0;;thermal +Timeseries generation;law.forced;lawForced;str;Uniform;;thermal +Timeseries generation;law.planned;lawPlanned;str;Uniform;;thermal diff --git a/tests/testthat/test-readClusterDesc.R b/tests/testthat/test-readClusterDesc.R index 3b938df7..c505edb4 100644 --- a/tests/testthat/test-readClusterDesc.R +++ b/tests/testthat/test-readClusterDesc.R @@ -54,3 +54,11 @@ test_that("test read cluster st-storage v860", { testthat::expect_true(all(mandatory_cols %in% colnames(input_st))) testthat::expect_true(nrow(input_st) == length(input_st$cluster)) }) + +# read empty study ---- +path_empty_study <- setup_study_empty(sourcedir_empty_study) +opts_study_test <- setSimulationPath(path_empty_study, simulation = "input") + +test_that("test when study has no cluster (empty)", { + readClusterDesc() +}) From e80d1cd6edfd4e22bcbe52661f84f67bc31f47cb Mon Sep 17 00:00:00 2001 From: berthetclement Date: Wed, 19 Jun 2024 08:44:31 +0200 Subject: [PATCH 05/14] update referentiel + resolve problem with build package (stage Install conflict) delete StageInstall causing NOTE check --- DESCRIPTION | 1 - R/zzz.R | 35 ++++----- .../properties_input_renewable.csv | 14 ++-- .../properties_input_storage.csv | 22 +++--- .../properties_input_thermal.csv | 74 +++++++++---------- 5 files changed, 73 insertions(+), 73 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 1a1ed819..6cbe66ea 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -23,7 +23,6 @@ Description: Import, manipulate and explore results generated by 'Antares', a URL: https://github.com/rte-antares-rpackage/antaresRead, https://rte-antares-rpackage.github.io/antaresRead/ BugReports: https://github.com/rte-antares-rpackage/antaresRead/issues License: GPL (>= 2) | file LICENSE -StagedInstall: no Imports: data.table (>= 1.9.6), bit64, diff --git a/R/zzz.R b/R/zzz.R index 23bdb6d9..f9eaf4ba 100644 --- a/R/zzz.R +++ b/R/zzz.R @@ -112,25 +112,26 @@ utils::globalVariables( ) ## INPUT Properties REF ---- -ref_input_properties_path <- file.path(system.file(package = "antaresRead"), - "referential_properties") - -all_ref_properties_path <- list.files(ref_input_properties_path, - full.names = TRUE) -names_files <- gsub(pattern = ".csv", - replacement = "", - x = list.files(ref_input_properties_path)) - -list_files_ref <- lapply(all_ref_properties_path, - data.table::fread, - encoding="UTF-8", - strip.white=FALSE) - -names(list_files_ref) <- names_files - -df_files_ref <- do.call("rbind", list_files_ref) +res_prop_ref <- data.table::fread(system.file("referential_properties/properties_input_renewable.csv", + package = "antaresRead"), + sep = ";", + header = TRUE) + +res_prop_therm <- data.table::fread(system.file("referential_properties/properties_input_thermal.csv", + package = "antaresRead"), + sep = ";", + header = TRUE) + +res_prop_st <- data.table::fread(system.file("referential_properties/properties_input_storage.csv", + package = "antaresRead"), + sep = ";", + header = TRUE) + +df_files_ref <- do.call("rbind", + list(res_prop_ref, res_prop_therm, res_prop_st)) pkgEnv$inputProperties <- df_files_ref + #----------------------------- HDF5 ------------------------------------# # HDF5 ---- diff --git a/inst/referential_properties/properties_input_renewable.csv b/inst/referential_properties/properties_input_renewable.csv index 4fa409b9..44061018 100644 --- a/inst/referential_properties/properties_input_renewable.csv +++ b/inst/referential_properties/properties_input_renewable.csv @@ -1,7 +1,7 @@ -Topic;INI Name;Tech Name;Type;Default;Version;Category -General;name;name;str;;8.1;renewable -General;group;group;str;;8.1;renewable -General;ts-interpretation;ts-interpretation;str;power-generation;8.1;renewable -Operating parameters;enabled;enabled;;True;8.1;renewable -Operating parameters;unitcount;unitCount;int;1;8.1;renewable -Operating parameters;nominalcapacity;nominalCapacity;float;0.0;8.1;renewable +Topic;INI Name;Tech Name;Type;Default;Version;Category;Version Antares +General;name;name;str;;8.1;renewable;810 +General;group;group;str;;8.1;renewable;810 +General;ts-interpretation;ts-interpretation;str;power-generation;8.1;renewable;810 +Operating parameters;enabled;enabled;;True;8.1;renewable;810 +Operating parameters;unitcount;unitCount;int;1;8.1;renewable;810 +Operating parameters;nominalcapacity;nominalCapacity;float;0.0;8.1;renewable;810 diff --git a/inst/referential_properties/properties_input_storage.csv b/inst/referential_properties/properties_input_storage.csv index a135d55a..e4b464cf 100644 --- a/inst/referential_properties/properties_input_storage.csv +++ b/inst/referential_properties/properties_input_storage.csv @@ -1,11 +1,11 @@ -Topic;INI Name;Tech Name;Type;Default;Version;Category -General;name;name;str;;8.6;storage -General;group;group;str;;8.6;storage -General;enabled;enabled;bool;True;8.8;storage -General;injectionnominalcapacity;injection_nominal_capacity;float;0.0;8.6;storage -General;withdrawalnominalcapacity;withdrawal_nominal_capacity;float;0.0;8.6;storage -General;reservoircapacity;reservoir_capacity;float;0.0;8.6;storage -General;efficiency;efficiency;float;0.0;8.6;storage -General;initiallevel;initial_level;float;0.5;8.8;storage -General;initiallevel;initial_level;float;0;8.6;storage -General;initialleveloptim;initial_level_optim;bool;False;8.6;storage +Topic;INI Name;Tech Name;Type;Default;Version;Category;Version Antares +General;name;name;str;;8.6;storage;860 +General;group;group;str;;8.6;storage;860 +General;injectionnominalcapacity;injection_nominal_capacity;float;0.0;8.6;storage;860 +General;withdrawalnominalcapacity;withdrawal_nominal_capacity;float;0.0;8.6;storage;860 +General;reservoircapacity;reservoir_capacity;float;0.0;8.6;storage;860 +General;efficiency;efficiency;float;0.0;8.6;storage;860 +General;initiallevel;initial_level;float;0;8.6;storage;860 +General;initialleveloptim;initial_level_optim;bool;False;8.6;storage;860 +General;enabled;enabled;bool;True;8.8;storage;880 +General;initiallevel;initial_level;float;0.5;8.8;storage;880 diff --git a/inst/referential_properties/properties_input_thermal.csv b/inst/referential_properties/properties_input_thermal.csv index 3e389ae6..22768cd3 100644 --- a/inst/referential_properties/properties_input_thermal.csv +++ b/inst/referential_properties/properties_input_thermal.csv @@ -1,37 +1,37 @@ -Topic;INI Name;Tech Name;Type;Default;Version;Category -General;name;name;str;;;thermal -General;group;group;str;Other 1;;thermal -Operating parameters;unitcount;unitCount;int;1;;thermal -Operating parameters;enabled;enabled;bool;True;;thermal -Operating parameters;nominalcapacity;nominalCapacity;float;0.0;;thermal -Operating parameters;min-stable-power;minStablePower;float;0.0;;thermal -Operating parameters;min-up-time;minUpTime;int;1;;thermal -Operating parameters;min-down-time;minDownTime;int;1;;thermal -Operating parameters;must-run;mustRun;bool;False;;thermal -Operating parameters;spinning;spinning;float;0.0;;thermal -Operating costs;costgeneration;costGeneration;str;SetManually;8.7;thermal -Operating costs;efficiency;efficiency;float;100.0;8.7;thermal -Operating costs;variableomcost;variableOMCost;float;0.0;8.7;thermal -Operating costs;marginal-cost;marginalCost;float;0.0;;thermal -Operating costs;spread-cost;spreadCost;float;0.0;;thermal -Operating costs;fixed-cost;fixedCost;float;0.0;;thermal -Operating costs;startup-cost;startupCost;float;0.0;;thermal -Operating costs;market-bid-cost;marketBidCost;float;0.0;;thermal -Pollutant emission rates;co2;co2;float;0.0;;thermal -Pollutant emission rates;nh3;nh3;float;0.0;8.6;thermal -Pollutant emission rates;so2;so2;float;0.0;8.6;thermal -Pollutant emission rates;nox;nox;float;0.0;8.6;thermal -Pollutant emission rates;pm2_5;pm25;float;0.0;8.6;thermal -Pollutant emission rates;pm5;pm5;float;0.0;8.6;thermal -Pollutant emission rates;pm10;pm10;float;0.0;8.6;thermal -Pollutant emission rates;nmvoc;nmvoc;float;0.0;8.6;thermal -Pollutant emission rates;op1;op1;float;0.0;8.6;thermal -Pollutant emission rates;op2;op2;float;0.0;8.6;thermal -Pollutant emission rates;op3;op3;float;0.0;8.6;thermal -Pollutant emission rates;op4;op4;float;0.0;8.6;thermal -Pollutant emission rates;op5;op5;float;0.0;8.6;thermal -Timeseries generation;gen-ts;genTs;str;Use Global;;thermal -Timeseries generation;volatility.forced;volatilityForced;float;0.0;;thermal -Timeseries generation;volatility.planned;volatilityPlanned;float;0.0;;thermal -Timeseries generation;law.forced;lawForced;str;Uniform;;thermal -Timeseries generation;law.planned;lawPlanned;str;Uniform;;thermal +Topic;INI Name;Tech Name;Type;Default;Version;Category;Version Antares +Pollutant emission rates;nh3;nh3;float;0.0;8.6;thermal;860 +Pollutant emission rates;so2;so2;float;0.0;8.6;thermal;860 +Pollutant emission rates;nox;nox;float;0.0;8.6;thermal;860 +Pollutant emission rates;pm2_5;pm25;float;0.0;8.6;thermal;860 +Pollutant emission rates;pm5;pm5;float;0.0;8.6;thermal;860 +Pollutant emission rates;pm10;pm10;float;0.0;8.6;thermal;860 +Pollutant emission rates;nmvoc;nmvoc;float;0.0;8.6;thermal;860 +Pollutant emission rates;op1;op1;float;0.0;8.6;thermal;860 +Pollutant emission rates;op2;op2;float;0.0;8.6;thermal;860 +Pollutant emission rates;op3;op3;float;0.0;8.6;thermal;860 +Pollutant emission rates;op4;op4;float;0.0;8.6;thermal;860 +Pollutant emission rates;op5;op5;float;0.0;8.6;thermal;860 +Operating costs;costgeneration;costGeneration;str;SetManually;8.7;thermal;870 +Operating costs;efficiency;efficiency;float;100.0;8.7;thermal;870 +Operating costs;variableomcost;variableOMCost;float;0.0;8.7;thermal;870 +General;name;name;str;;;thermal; +General;group;group;str;Other 1;;thermal; +Operating parameters;unitcount;unitCount;int;1;;thermal; +Operating parameters;enabled;enabled;bool;True;;thermal; +Operating parameters;nominalcapacity;nominalCapacity;float;0.0;;thermal; +Operating parameters;min-stable-power;minStablePower;float;0.0;;thermal; +Operating parameters;min-up-time;minUpTime;int;1;;thermal; +Operating parameters;min-down-time;minDownTime;int;1;;thermal; +Operating parameters;must-run;mustRun;bool;False;;thermal; +Operating parameters;spinning;spinning;float;0.0;;thermal; +Operating costs;marginal-cost;marginalCost;float;0.0;;thermal; +Operating costs;spread-cost;spreadCost;float;0.0;;thermal; +Operating costs;fixed-cost;fixedCost;float;0.0;;thermal; +Operating costs;startup-cost;startupCost;float;0.0;;thermal; +Operating costs;market-bid-cost;marketBidCost;float;0.0;;thermal; +Pollutant emission rates;co2;co2;float;0.0;;thermal; +Timeseries generation;gen-ts;genTs;str;Use Global;;thermal; +Timeseries generation;volatility.forced;volatilityForced;float;0.0;;thermal; +Timeseries generation;volatility.planned;volatilityPlanned;float;0.0;;thermal; +Timeseries generation;law.forced;lawForced;str;Uniform;;thermal; +Timeseries generation;law.planned;lawPlanned;str;Uniform;;thermal; From 183d1716f8642afaa165e3ecae2cd94aac8dd352 Mon Sep 17 00:00:00 2001 From: berthetclement Date: Wed, 19 Jun 2024 08:46:27 +0200 Subject: [PATCH 06/14] readClusterSTDesc() reforge return function and api part + conversion list to date.frame changing columns names + test --- R/readClusterDesc.R | 75 ++++++++++----------------- tests/testthat/test-readClusterDesc.R | 35 ++++++++----- 2 files changed, 50 insertions(+), 60 deletions(-) diff --git a/R/readClusterDesc.R b/R/readClusterDesc.R index 64d76b5b..21a89522 100644 --- a/R/readClusterDesc.R +++ b/R/readClusterDesc.R @@ -92,18 +92,6 @@ readClusterSTDesc <- function(opts = simOptions()) { .readClusterDesc <- function(opts = simOptions(), dir = "thermal/clusters") { - if(isH5Opts(opts)){ - if(dir %in% "thermal/clusters"){ - if(.requireRhdf5_Antares(stopP = FALSE)){ - return(h5ReadClusterDesc(opts)) - } else { - stop(rhdf5_message, call. = FALSE) - } - } else { - stop("Read cluster Description from '", dir, "' not available using .h5", call. = FALSE) - } - } - path <- file.path(opts$inputPath, dir) columns <- .generate_columns_by_type(dir = dir) api_study <- is_api_study(opts) @@ -117,55 +105,46 @@ readClusterSTDesc <- function(opts = simOptions()) { "st-storage/clusters" = "st-storages" ) + # api request with all columns list_clusters = api_get( opts = opts, - endpoint = paste0(opts$study_id, "/table-mode/",table_type), + endpoint = paste0(opts$study_id, "/table-mode/", table_type), query = list( columns = "" ) ) - if(length(list_clusters) == 0){ - mandatory_cols <- c("area","name") - warning("No cluster description available.", call. = FALSE) - res <- setNames(data.table(matrix(nrow = 0, - ncol = length(mandatory_cols) + length(columns))), - c(mandatory_cols, columns)) - }else{ - clusters <- rbindlist(list_clusters, idcol = "name") - newcol <- data.table() - newcol <- newcol[, c("area", "name") := tstrsplit(clusters$name, " / ", - fixed = TRUE, - keep = 1:2)] - res <- data.table(newcol,clusters[,-"name"]) - - } - }else{ - areas <- list.files(path) - res <- ldply(areas, function(x) { - clusters <- readIniFile(file.path(path, x, "list.ini")) - if (length(clusters) == 0) return(NULL) - clusters <- ldply(clusters, as.data.frame) - clusters$.id <- NULL - clusters$area <- x - clusters[, c(ncol(clusters), 1:(ncol(clusters) - 1))] - }) + + return(list_clusters) } + + # "text" mode + areas <- list.files(path) + + # read properties for each area + res <- llply(areas, function(x) { + clusters <- readIniFile(file.path(path, x, "list.ini")) + if (length(clusters) == 0) + return(NULL) + clusters <- ldply(clusters, data.frame) # check.names = FALSE (too many side effects) + clusters$.id <- NULL + clusters$area <- x + clusters[, c(ncol(clusters), 1:(ncol(clusters) - 1))] + }) + + res <- rbindlist(l = res, fill = TRUE) + if(length(res) == 0){ - mandatory_cols <- c("area","name") - warning("No cluster description available.", call. = FALSE) - res <- setNames(data.table(matrix(nrow = 0, ncol = length(mandatory_cols) + length(columns))), c(mandatory_cols, columns)) - }else{ - if(api_study){ - mandatory_cols <- c("area", "name", "group") - additional_cols <- setdiff(colnames(res),mandatory_cols) - res <- res[, .SD, .SDcols = c(mandatory_cols, additional_cols)] - } - } + warning("No properties found", + call. = FALSE) + return(NULL) + } + res <- as.data.table(res) setnames(res, "name", "cluster") res$cluster <- as.factor(tolower(res$cluster)) res } + .generate_columns_by_type <- function(dir = c("thermal/clusters", "renewables/clusters", "st-storage/clusters")) { columns <- switch( diff --git a/tests/testthat/test-readClusterDesc.R b/tests/testthat/test-readClusterDesc.R index c505edb4..8e41471c 100644 --- a/tests/testthat/test-readClusterDesc.R +++ b/tests/testthat/test-readClusterDesc.R @@ -1,14 +1,13 @@ -# read study ---- - # latest version -path_study_test <- grep(pattern = "87", x = studyPathSV8, value = TRUE) -opts_study_test <- setSimulationPath(path_study_test, simulation = "input") - -# all version ---- -#minimal columns -mandatory_cols <- c("area","cluster") +# v710---- ## Thermal ---- test_that("test read cluster", { + path_study_test <- studyPathS + opts_study_test <- setSimulationPath(path_study_test, simulation = "input") + + #minimal columns + mandatory_cols <- c("area","cluster") + # function setSimulationPath() provide areas names with st-storage clusters areas <- opts_study_test$areasWithClusters @@ -17,13 +16,19 @@ test_that("test read cluster", { # tests testthat::expect_true("data.table" %in% class(input)) - testthat::expect_true(all(areas %in% unique(readClusterDesc()$area))) + testthat::expect_true(all(areas %in% unique(input$area))) testthat::expect_true(all(mandatory_cols %in% colnames(input))) testthat::expect_true(nrow(input) == length(input$cluster)) }) ## Renewables ---- test_that("test read cluster renewables", { + path_study_test <- grep(pattern = "87", x = studyPathSV8, value = TRUE) + opts_study_test <- setSimulationPath(path_study_test, simulation = "input") + + #minimal columns + mandatory_cols <- c("area","cluster") + # function setSimulationPath() provide areas names with st-storage clusters areas_res <- opts_study_test$areasWithResClusters @@ -40,6 +45,12 @@ test_that("test read cluster renewables", { # v860 ---- ## st-storage ---- test_that("test read cluster st-storage v860", { + path_study_test <- grep(pattern = "87", x = studyPathSV8, value = TRUE) + opts_study_test <- setSimulationPath(path_study_test, simulation = "input") + + #minimal columns + mandatory_cols <- c("area","cluster") + # function setSimulationPath() provide areas names with st-storage clusters areas_st <- opts_study_test$areasWithSTClusters @@ -56,9 +67,9 @@ test_that("test read cluster st-storage v860", { }) # read empty study ---- -path_empty_study <- setup_study_empty(sourcedir_empty_study) -opts_study_test <- setSimulationPath(path_empty_study, simulation = "input") - test_that("test when study has no cluster (empty)", { + path_empty_study <- setup_study_empty(sourcedir_empty_study) + opts_study_test <- setSimulationPath(path_empty_study, simulation = "input") + readClusterDesc() }) From eea31e500ca194a9c9cdeb9c3a8d688eb8fedc18 Mon Sep 17 00:00:00 2001 From: berthetclement Date: Fri, 21 Jun 2024 17:05:22 +0200 Subject: [PATCH 07/14] trivial join ref to cluster properties + delete dote in colnames --- R/readClusterDesc.R | 64 ++++++++++++++++++++++++++++++++++++--------- 1 file changed, 52 insertions(+), 12 deletions(-) diff --git a/R/readClusterDesc.R b/R/readClusterDesc.R index 21a89522..9c317af3 100644 --- a/R/readClusterDesc.R +++ b/R/readClusterDesc.R @@ -96,15 +96,15 @@ readClusterSTDesc <- function(opts = simOptions()) { columns <- .generate_columns_by_type(dir = dir) api_study <- is_api_study(opts) + table_type <- switch( + dir, + "thermal/clusters" = "thermals", + "renewables/clusters" = "renewables", + "st-storage/clusters" = "st-storages" + ) + if(api_study){ - table_type <- switch( - dir, - "thermal/clusters" = "thermals", - "renewables/clusters" = "renewables", - "st-storage/clusters" = "st-storages" - ) - # api request with all columns list_clusters = api_get( opts = opts, @@ -121,26 +121,66 @@ readClusterSTDesc <- function(opts = simOptions()) { areas <- list.files(path) # read properties for each area - res <- llply(areas, function(x) { + res <- plyr::llply(areas, function(x) { clusters <- readIniFile(file.path(path, x, "list.ini")) if (length(clusters) == 0) return(NULL) - clusters <- ldply(clusters, data.frame) # check.names = FALSE (too many side effects) + clusters <- plyr::ldply(clusters, + data.frame, + check.names = FALSE) # check.names = FALSE (too many side effects) clusters$.id <- NULL clusters$area <- x clusters[, c(ncol(clusters), 1:(ncol(clusters) - 1))] }) - res <- rbindlist(l = res, fill = TRUE) + res <- data.table::rbindlist(l = res, fill = TRUE) + # NO PROPERTIES CLUSTER FOUND if(length(res) == 0){ warning("No properties found", call. = FALSE) return(NULL) } + + # merge with referential cluster properties + full_ref_properties <- pkgEnv[["inputProperties"]] + + category_ref_cluster <- switch( + table_type, + "thermals" = "thermal", + "renewables" = "renewable", + "st-storages" = "storage" + ) + + # filter by category + ref_filter_by_cat <- full_ref_properties[`Category` %in% + category_ref_cluster] + # filter by study version + ref_filter_by_vers <- ref_filter_by_cat[`Version Antares` <= + opts$antaresVersion | + `Version Antares` %in% NA] + + # select key colums and put wide format + ref_filter_by_vers <- ref_filter_by_vers[ , + .SD, + .SDcols = c("INI Name", "Default", "Type")] + + wide_ref <- data.table::dcast(data = ref_filter_by_vers, + formula = .~`INI Name`, + value.var = "Default")[ + , + .SD, + .SDcols = -c(".", "name")] + + wide_ref <- wide_ref[, .SD, .SDcols = -intersect(names(res), names(wide_ref))] + + # merge(wide_ref, res, allow.cartesian = TRUE, no.dups = FALSE, all = TRUE) + + restable <- cbind(res, wide_ref) - res <- as.data.table(res) - setnames(res, "name", "cluster") + # output format conversion + res <- data.table::as.data.table(res) + data.table::setnames(res, "name", "cluster") res$cluster <- as.factor(tolower(res$cluster)) res } From e56707787f211f346372ba8b5043951f950ad8b7 Mon Sep 17 00:00:00 2001 From: berthetclement Date: Thu, 27 Jun 2024 15:34:16 +0200 Subject: [PATCH 08/14] updated with default values addded keep bad check with side effect in package --- R/readClusterDesc.R | 84 ++++++++++++++++++++------------------------- 1 file changed, 37 insertions(+), 47 deletions(-) diff --git a/R/readClusterDesc.R b/R/readClusterDesc.R index 9c317af3..89fd0240 100644 --- a/R/readClusterDesc.R +++ b/R/readClusterDesc.R @@ -93,7 +93,6 @@ readClusterSTDesc <- function(opts = simOptions()) { dir = "thermal/clusters") { path <- file.path(opts$inputPath, dir) - columns <- .generate_columns_by_type(dir = dir) api_study <- is_api_study(opts) table_type <- switch( @@ -120,29 +119,7 @@ readClusterSTDesc <- function(opts = simOptions()) { # "text" mode areas <- list.files(path) - # read properties for each area - res <- plyr::llply(areas, function(x) { - clusters <- readIniFile(file.path(path, x, "list.ini")) - if (length(clusters) == 0) - return(NULL) - clusters <- plyr::ldply(clusters, - data.frame, - check.names = FALSE) # check.names = FALSE (too many side effects) - clusters$.id <- NULL - clusters$area <- x - clusters[, c(ncol(clusters), 1:(ncol(clusters) - 1))] - }) - - res <- data.table::rbindlist(l = res, fill = TRUE) - - # NO PROPERTIES CLUSTER FOUND - if(length(res) == 0){ - warning("No properties found", - call. = FALSE) - return(NULL) - } - - # merge with referential cluster properties + # READ cluster properties full_ref_properties <- pkgEnv[["inputProperties"]] category_ref_cluster <- switch( @@ -163,7 +140,12 @@ readClusterSTDesc <- function(opts = simOptions()) { # select key colums and put wide format ref_filter_by_vers <- ref_filter_by_vers[ , .SD, - .SDcols = c("INI Name", "Default", "Type")] + .SDcols = c("INI Name", + "Default", + "Type")] + + # select names columns to convert to logical + logical_col_names <- ref_filter_by_vers[Type%in%"bool"][["INI Name"]] wide_ref <- data.table::dcast(data = ref_filter_by_vers, formula = .~`INI Name`, @@ -171,34 +153,42 @@ readClusterSTDesc <- function(opts = simOptions()) { , .SD, .SDcols = -c(".", "name")] + # /!\ column type conversion on + wide_ref[, + (logical_col_names):= lapply(.SD, as.logical), + .SDcols = logical_col_names] + + # read properties for each area + res <- plyr::llply(areas, function(x) { + clusters <- readIniFile(file.path(path, x, "list.ini")) + if (length(clusters) == 0) + return(NULL) + # conversion list to data.frame + clusters <- plyr::ldply(clusters, function(x){ + df_clust <- data.frame(x, check.names = FALSE) + colnames_to_add <- setdiff(names(wide_ref), names(df_clust)) + if(!identical(colnames_to_add, character(0))) + df_clust <- cbind(df_clust, wide_ref[, .SD, .SDcols = colnames_to_add]) + df_clust + }) # check.names = FALSE (too many side effects) + clusters$.id <- NULL + clusters$area <- x + # re order columns + clusters[, c("area", setdiff(colnames(clusters), "area"))] + }) - wide_ref <- wide_ref[, .SD, .SDcols = -intersect(names(res), names(wide_ref))] + res <- data.table::rbindlist(l = res, fill = TRUE) - # merge(wide_ref, res, allow.cartesian = TRUE, no.dups = FALSE, all = TRUE) + # NO PROPERTIES CLUSTER FOUND + if(length(res) == 0){ + warning("No properties found", + call. = FALSE) + return(NULL) + } - restable <- cbind(res, wide_ref) - # output format conversion res <- data.table::as.data.table(res) data.table::setnames(res, "name", "cluster") res$cluster <- as.factor(tolower(res$cluster)) res } - -.generate_columns_by_type <- function(dir = c("thermal/clusters", "renewables/clusters", "st-storage/clusters")) { - - columns <- switch( - dir, - "thermal/clusters" = c("name","group","enabled","mustRun","unitCount","nominalCapacity", - "minStablePower","spinning","minUpTime","minDownTime", - "co2","marginalCost","fixedCost","startupCost","marketBidCost", - "spreadCost","tsGen","volatilityForced","volatilityPlanned", - "lawForced","lawPlanned"), - - "renewables/clusters" = c("name","group","ts-interpretation","enabled","unitCount","nominalCapacity"), - - "st-storage/clusters" = c("name","group","enabled","injection_nominal_capacity","withdrawal_nominal_capacity", - "reservoir_capacity","efficiency","initial_level","initial_level_optim") - ) - return(columns) -} \ No newline at end of file From 91ec8c2289413c43c835fa92f3ef950ea2cb0c4f Mon Sep 17 00:00:00 2001 From: berthetclement Date: Tue, 2 Jul 2024 15:10:47 +0200 Subject: [PATCH 09/14] updated with type "bool" for RES referential --- inst/referential_properties/properties_input_renewable.csv | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/inst/referential_properties/properties_input_renewable.csv b/inst/referential_properties/properties_input_renewable.csv index 44061018..2b20fe44 100644 --- a/inst/referential_properties/properties_input_renewable.csv +++ b/inst/referential_properties/properties_input_renewable.csv @@ -2,6 +2,6 @@ Topic;INI Name;Tech Name;Type;Default;Version;Category;Version Antares General;name;name;str;;8.1;renewable;810 General;group;group;str;;8.1;renewable;810 General;ts-interpretation;ts-interpretation;str;power-generation;8.1;renewable;810 -Operating parameters;enabled;enabled;;True;8.1;renewable;810 +Operating parameters;enabled;enabled;bool;True;8.1;renewable;810 Operating parameters;unitcount;unitCount;int;1;8.1;renewable;810 Operating parameters;nominalcapacity;nominalCapacity;float;0.0;8.1;renewable;810 From 99d6dd4f65bd7fcd5ff5eb61da9ae6217b775361 Mon Sep 17 00:00:00 2001 From: berthetclement Date: Wed, 3 Jul 2024 09:12:12 +0200 Subject: [PATCH 10/14] correction of edge effects on variable names with "dots". --- R/importOutput.R | 26 ++++++++++++++------------ R/readAntares.R | 2 +- R/zzz.R | 5 +++-- man/readAntares.Rd | 2 +- 4 files changed, 19 insertions(+), 16 deletions(-) diff --git a/R/importOutput.R b/R/importOutput.R index 2cb25a80..524782d9 100644 --- a/R/importOutput.R +++ b/R/importOutput.R @@ -397,14 +397,16 @@ # Get cluster capacity and must run mode clusterDesc <- readClusterDesc(opts) - if(is.null(clusterDesc$must.run)) clusterDesc$must.run <- FALSE - clusterDesc[is.na(must.run), must.run := FALSE] - if (is.null(clusterDesc$min.stable.power)) clusterDesc$min.stable.power <- 0 - clusterDesc[is.na(min.stable.power), min.stable.power := 0] + if(is.null(clusterDesc[["must-run"]])) + clusterDesc[["must-run"]] <- FALSE + clusterDesc[is.na(`must-run`), `must-run` := FALSE] + if (is.null(clusterDesc[["min-stable-power"]])) + clusterDesc[["min-stable-power"]] <- 0 + clusterDesc[is.na(`min-stable-power`), `min-stable-power` := 0] clusterDesc <- clusterDesc[, .(area, cluster, capacity = nominalcapacity * unitcount, - min.stable.power, - must.run)] + `min-stable-power`, + `must-run`)] # Are clusters in partial must run mode ? mod <- llply(areas, .importThermalModulation, opts = opts, timeStep = "hourly") @@ -469,16 +471,16 @@ } - .mergeByRef(res, clusterDesc[,.(area, cluster, must.run, min.stable.power)]) + .mergeByRef(res, clusterDesc[,.(area, cluster, `must-run`, `min-stable-power`)]) if (is.null(res$NODU)) res[, thermalPmin := 0] - else res[, thermalPmin := min.stable.power * NODU] + else res[, thermalPmin := `min-stable-power` * NODU] res[, `:=`( - mustRun = production * must.run, - mustRunTotal = production * must.run + mustRunPartial, - must.run = NULL, - min.stable.power = NULL + mustRun = production * `must-run`, + mustRunTotal = production * `must-run` + mustRunPartial, + `must-run` = NULL, + `min-stable-power` = NULL )] res[, thermalPmin := pmax(thermalPmin, mustRunTotal)] diff --git a/R/readAntares.R b/R/readAntares.R index fdeb20e2..4a9ac46f 100644 --- a/R/readAntares.R +++ b/R/readAntares.R @@ -116,7 +116,7 @@ #' similar to mustRunTotal except it also takes into account the production #' induced by the minimum stable power of the units of a cluster. More #' precisely, for a given cluster and a given time step, it is equal to -#' \code{min(NODU x min.stable.power, mustRunTotal)}. +#' \code{min(NODU x min-stable-power, mustRunTotal)}. #' @param select #' Character vector containing the name of the columns to import. If this #' argument is \code{NULL}, all variables are imported. Special names diff --git a/R/zzz.R b/R/zzz.R index f9eaf4ba..0c290891 100644 --- a/R/zzz.R +++ b/R/zzz.R @@ -97,7 +97,7 @@ utils::globalVariables( c("timeId", "tsId", "area", "hydroStorage", "thermalAvailability", "cluster", "FLOW LIN.", "FLOW QUAD.", "direction", "flow", "BALANCE", "totalFlow", "prop", "to", "link", "change", - "district", "must.run", ".txt", "detailsLength", + "district", "must-run", ".txt", "detailsLength", "linkLength", "connectedToVirtualArea", "from", "correction", "nominalcapacity", "unitcount", "capacity", "minGenModulation", "production", "mustRunPartial", "mustRunTotal", "mcYear", @@ -105,7 +105,8 @@ utils::globalVariables( "pumpingCapacity", "pumpingCapacity.x", "pumpingCapacity.y", "rarea", "storageCapacity", "storageCapacity.x", "storageCapacity.y", "toDistrict", "transCapacityDirect", "transCapacityIndirect", "varea", "x", "y", - "NODU", "min.stable.power", "thermalPmin", "name", "value", + "NODU", "min-stable-power", 'Category', 'Version Antares', 'Type', + "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") diff --git a/man/readAntares.Rd b/man/readAntares.Rd index 92f153bc..78019479 100644 --- a/man/readAntares.Rd +++ b/man/readAntares.Rd @@ -79,7 +79,7 @@ is the sum of the two previous columns. Finally \code{thermalPmin} is similar to mustRunTotal except it also takes into account the production induced by the minimum stable power of the units of a cluster. More precisely, for a given cluster and a given time step, it is equal to -\code{min(NODU x min.stable.power, mustRunTotal)}.} +\code{min(NODU x min-stable-power, mustRunTotal)}.} \item{thermalModulation}{Should thermal modulation time series be imported ? If \code{TRUE}, the columns "marginalCostModulation", "marketBidModulation", "capacityModulation" From 415565d2823325c2e3747b6e007dfafc5b49d825 Mon Sep 17 00:00:00 2001 From: berthetclement Date: Wed, 3 Jul 2024 09:14:06 +0200 Subject: [PATCH 11/14] converting repository variables to numerical --- R/readClusterDesc.R | 9 +++++++-- 1 file changed, 7 insertions(+), 2 deletions(-) diff --git a/R/readClusterDesc.R b/R/readClusterDesc.R index 89fd0240..f63afeb2 100644 --- a/R/readClusterDesc.R +++ b/R/readClusterDesc.R @@ -144,8 +144,9 @@ readClusterSTDesc <- function(opts = simOptions()) { "Default", "Type")] - # select names columns to convert to logical + # select names columns to convert to logical + numerical logical_col_names <- ref_filter_by_vers[Type%in%"bool"][["INI Name"]] + numerical_col_names <- ref_filter_by_vers[Type%in%c("int", "float")][["INI Name"]] wide_ref <- data.table::dcast(data = ref_filter_by_vers, formula = .~`INI Name`, @@ -156,7 +157,11 @@ readClusterSTDesc <- function(opts = simOptions()) { # /!\ column type conversion on wide_ref[, (logical_col_names):= lapply(.SD, as.logical), - .SDcols = logical_col_names] + .SDcols = logical_col_names][ + , + (numerical_col_names):= lapply(.SD, as.numeric), + .SDcols = numerical_col_names + ] # read properties for each area res <- plyr::llply(areas, function(x) { From 82438dd7444ca74fa881417b855add7315b46afc Mon Sep 17 00:00:00 2001 From: berthetclement Date: Wed, 10 Jul 2024 15:09:34 +0200 Subject: [PATCH 12/14] update function to return empty data.table + doc + tests (using new ref properties) --- R/readClusterDesc.R | 9 ++-- man/readClusterDesc.Rd | 2 + tests/testthat/test-readClusterDesc.R | 70 +++++++++++++++++++-------- 3 files changed, 57 insertions(+), 24 deletions(-) diff --git a/R/readClusterDesc.R b/R/readClusterDesc.R index f63afeb2..89e6507e 100644 --- a/R/readClusterDesc.R +++ b/R/readClusterDesc.R @@ -34,6 +34,8 @@ #' \code{readClusterResDesc} : read renewable clusters (Antares >= V8.1) #' #' \code{readClusterSTDesc} : read st-storage clusters (Antares >= V8.6) +#' +#' If you have no clusters properties, `Null data.table (0 rows and 0 cols)` is returned. #' #' @examples #' @@ -185,11 +187,8 @@ readClusterSTDesc <- function(opts = simOptions()) { res <- data.table::rbindlist(l = res, fill = TRUE) # NO PROPERTIES CLUSTER FOUND - if(length(res) == 0){ - warning("No properties found", - call. = FALSE) - return(NULL) - } + if(length(res) == 0) + return(data.table()) # output format conversion res <- data.table::as.data.table(res) diff --git a/man/readClusterDesc.Rd b/man/readClusterDesc.Rd index fe3bcd15..8ed4337e 100644 --- a/man/readClusterDesc.Rd +++ b/man/readClusterDesc.Rd @@ -39,6 +39,8 @@ study. You can use the argument \code{opts} to specify another study. \code{readClusterResDesc} : read renewable clusters (Antares >= V8.1) \code{readClusterSTDesc} : read st-storage clusters (Antares >= V8.6) + +If you have no clusters properties, \verb{Null data.table (0 rows and 0 cols)} is returned. } \description{ This function reads in the input files of an antares study the diff --git a/tests/testthat/test-readClusterDesc.R b/tests/testthat/test-readClusterDesc.R index 8e41471c..42dd1204 100644 --- a/tests/testthat/test-readClusterDesc.R +++ b/tests/testthat/test-readClusterDesc.R @@ -5,9 +5,6 @@ test_that("test read cluster", { path_study_test <- studyPathS opts_study_test <- setSimulationPath(path_study_test, simulation = "input") - #minimal columns - mandatory_cols <- c("area","cluster") - # function setSimulationPath() provide areas names with st-storage clusters areas <- opts_study_test$areasWithClusters @@ -17,18 +14,29 @@ test_that("test read cluster", { # tests testthat::expect_true("data.table" %in% class(input)) testthat::expect_true(all(areas %in% unique(input$area))) - testthat::expect_true(all(mandatory_cols %in% colnames(input))) - testthat::expect_true(nrow(input) == length(input$cluster)) + + # tests if all colnames are returned according to ref + ref_thermal <- antaresRead:::pkgEnv$inputProperties[ + Category%in%"thermal"] + ref_thermal <- ref_thermal[`Version Antares` <= + opts_study_test$antaresVersion | + `Version Antares` %in% NA] + + # "name" in INI file corresponding "cluster" in output + testthat::expect_true(all( + setdiff(ref_thermal$`INI Name`, "name")%in% + setdiff(colnames(input), c("area", "cluster")))) + + # object returned is one line per area/cluster + testthat::expect_equal(nrow(input), nrow(unique(input))) }) ## Renewables ---- test_that("test read cluster renewables", { - path_study_test <- grep(pattern = "87", x = studyPathSV8, value = TRUE) + path_study_test <- grep(pattern = "test_case_study_v870", + x = studyPathSV8, value = TRUE) opts_study_test <- setSimulationPath(path_study_test, simulation = "input") - #minimal columns - mandatory_cols <- c("area","cluster") - # function setSimulationPath() provide areas names with st-storage clusters areas_res <- opts_study_test$areasWithResClusters @@ -38,19 +46,30 @@ test_that("test read cluster renewables", { # tests testthat::expect_true("data.table" %in% class(input)) testthat::expect_true(all(areas_res %in% unique(input$area))) - testthat::expect_true(all(mandatory_cols %in% colnames(input))) - testthat::expect_true(nrow(input) == length(input$cluster)) + + # tests if all colnames are returned according to ref + ref_res <- antaresRead:::pkgEnv$inputProperties[ + Category%in%"renewable"] + ref_res <- ref_res[`Version Antares` <= + opts_study_test$antaresVersion | + `Version Antares` %in% NA] + + # "name" in INI file corresponding "cluster" in output + testthat::expect_true(all( + setdiff(ref_res$`INI Name`, "name")%in% + setdiff(colnames(input), c("area", "cluster")))) + + # object returned is one line per area/cluster + testthat::expect_equal(nrow(input), nrow(unique(input))) }) # v860 ---- ## st-storage ---- test_that("test read cluster st-storage v860", { - path_study_test <- grep(pattern = "87", x = studyPathSV8, value = TRUE) + path_study_test <- grep(pattern = "test_case_study_v870", + x = studyPathSV8, value = TRUE) opts_study_test <- setSimulationPath(path_study_test, simulation = "input") - #minimal columns - mandatory_cols <- c("area","cluster") - # function setSimulationPath() provide areas names with st-storage clusters areas_st <- opts_study_test$areasWithSTClusters @@ -61,9 +80,21 @@ test_that("test read cluster st-storage v860", { testthat::expect_true("data.table" %in% class(input_st)) testthat::expect_true(all( areas_st %in% unique(readClusterSTDesc()$area))) - testthat::expect_true(all(areas_st %in% unique(readClusterSTDesc()$area))) - testthat::expect_true(all(mandatory_cols %in% colnames(input_st))) - testthat::expect_true(nrow(input_st) == length(input_st$cluster)) + + # tests if all colnames are returned according to ref + ref_st <- antaresRead:::pkgEnv$inputProperties[ + Category%in%"storage"] + ref_st <- ref_st[`Version Antares` <= + opts_study_test$antaresVersion | + `Version Antares` %in% NA] + + # "name" in INI file corresponding "cluster" in output + testthat::expect_true(all( + setdiff(ref_st$`INI Name`, "name")%in% + setdiff(colnames(input_st), c("area", "cluster")))) + + # object returned is one line per area/cluster + testthat::expect_equal(nrow(input_st), nrow(unique(input_st))) }) # read empty study ---- @@ -71,5 +102,6 @@ test_that("test when study has no cluster (empty)", { path_empty_study <- setup_study_empty(sourcedir_empty_study) opts_study_test <- setSimulationPath(path_empty_study, simulation = "input") - readClusterDesc() + testthat::expect_equal(readClusterDesc(), + data.table::data.table()) }) From c23a980ffe88af7d3dee8cd772121233cafc7a69 Mon Sep 17 00:00:00 2001 From: berthetclement Date: Wed, 10 Jul 2024 15:42:16 +0200 Subject: [PATCH 13/14] update newsmd --- NEWS.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/NEWS.md b/NEWS.md index 4d5fcb5e..d6b4a45e 100644 --- a/NEWS.md +++ b/NEWS.md @@ -17,6 +17,8 @@ It contains a table with group dimensions of time series for binding constraints BREAKING CHANGES : * `readInputThermal()` / `readInputRES()` default value when no time series in the selected clusters. +* `readClusterDesc()` / `readClusterResDesc()` / `readClusterSTDesc()` are updated with new endpoint "table mode". + - In "text" mode, functions return all properties (with default properties) according to study version. BUGFIXES : From 4b2b161f8d1c0aaa623c4d38376e0609ff538469 Mon Sep 17 00:00:00 2001 From: berthetclement Date: Thu, 11 Jul 2024 15:39:39 +0200 Subject: [PATCH 14/14] update readClusterDesc() with sub function to return properties according to version + test referential properties --- R/readClusterDesc.R | 89 ++++++++++++------- .../properties_input_storage_test.csv | 13 +++ 2 files changed, 72 insertions(+), 30 deletions(-) create mode 100644 inst/referential_properties/properties_input_storage_test.csv diff --git a/R/readClusterDesc.R b/R/readClusterDesc.R index 89e6507e..f9f75032 100644 --- a/R/readClusterDesc.R +++ b/R/readClusterDesc.R @@ -121,6 +121,46 @@ readClusterSTDesc <- function(opts = simOptions()) { # "text" mode areas <- list.files(path) + # READ cluster properties + properties <- get_input_cluster_properties(table_type = table_type, + opts = opts) + + # read properties for each area + res <- plyr::llply(areas, function(x, prop_ref=properties) { + clusters <- readIniFile(file.path(path, x, "list.ini")) + if (length(clusters) == 0) + return(NULL) + # conversion list to data.frame + clusters <- plyr::ldply(clusters, function(x){ + df_clust <- data.frame(x, check.names = FALSE) + colnames_to_add <- setdiff(names(prop_ref), names(df_clust)) + if(!identical(colnames_to_add, character(0))) + df_clust <- cbind(df_clust, prop_ref[, .SD, .SDcols = colnames_to_add]) + df_clust + }) # check.names = FALSE (too many side effects) + clusters$.id <- NULL + clusters$area <- x + # re order columns + clusters[, c("area", setdiff(colnames(clusters), "area"))] + }) + + res <- data.table::rbindlist(l = res, fill = TRUE) + + # NO PROPERTIES CLUSTER FOUND + if(length(res) == 0) + return(data.table()) + + # output format conversion + res <- data.table::as.data.table(res) + data.table::setnames(res, "name", "cluster") + res$cluster <- as.factor(tolower(res$cluster)) + res +} + + +# read and manage referential properties + # return referential according to type and study version +get_input_cluster_properties <- function(table_type, opts){ # READ cluster properties full_ref_properties <- pkgEnv[["inputProperties"]] @@ -139,6 +179,24 @@ readClusterSTDesc <- function(opts = simOptions()) { opts$antaresVersion | `Version Antares` %in% NA] + # detect evolution on parameter ? (new value according to study version) + # filter on value according to study version + df_multi_params <- ref_filter_by_vers[, + count := .N, + by = c("INI Name"), + keyby = TRUE][ + count>1][, + .SD[which.max(`Version Antares`)], + by="INI Name"] + + df_unique_params <- ref_filter_by_vers[, + count := .N, + by = c("INI Name"), + keyby = TRUE][ + count==1] + + ref_filter_by_vers <- rbind(df_unique_params, df_multi_params) + # select key colums and put wide format ref_filter_by_vers <- ref_filter_by_vers[ , .SD, @@ -165,34 +223,5 @@ readClusterSTDesc <- function(opts = simOptions()) { .SDcols = numerical_col_names ] - # read properties for each area - res <- plyr::llply(areas, function(x) { - clusters <- readIniFile(file.path(path, x, "list.ini")) - if (length(clusters) == 0) - return(NULL) - # conversion list to data.frame - clusters <- plyr::ldply(clusters, function(x){ - df_clust <- data.frame(x, check.names = FALSE) - colnames_to_add <- setdiff(names(wide_ref), names(df_clust)) - if(!identical(colnames_to_add, character(0))) - df_clust <- cbind(df_clust, wide_ref[, .SD, .SDcols = colnames_to_add]) - df_clust - }) # check.names = FALSE (too many side effects) - clusters$.id <- NULL - clusters$area <- x - # re order columns - clusters[, c("area", setdiff(colnames(clusters), "area"))] - }) - - res <- data.table::rbindlist(l = res, fill = TRUE) - - # NO PROPERTIES CLUSTER FOUND - if(length(res) == 0) - return(data.table()) - - # output format conversion - res <- data.table::as.data.table(res) - data.table::setnames(res, "name", "cluster") - res$cluster <- as.factor(tolower(res$cluster)) - res + return(wide_ref) } diff --git a/inst/referential_properties/properties_input_storage_test.csv b/inst/referential_properties/properties_input_storage_test.csv new file mode 100644 index 00000000..ed9c8918 --- /dev/null +++ b/inst/referential_properties/properties_input_storage_test.csv @@ -0,0 +1,13 @@ +Topic;INI Name;Tech Name;Type;Default;Version;Category;Version Antares +General;efficiency;efficiency;float;0.0;8.6;storage;860 +General;enabled;enabled;bool;True;8.8;storage;880 +General;group;group;str;;8.6;storage;860 +General;initiallevel;initial_level;float;0;8.6;storage;860 +General;initiallevel;initial_level;float;0.5;8.8;storage;880 +General;initialleveloptim;initial_level_optim;bool;False;8.6;storage;860 +General;injectionnominalcapacity;injection_nominal_capacity;float;0.2;8.4;storage;840 +General;injectionnominalcapacity;injection_nominal_capacity;float;0.1;8.5;storage;850 +General;injectionnominalcapacity;injection_nominal_capacity;float;0.0;8.6;storage;860 +General;name;name;str;;8.6;storage;860 +General;reservoircapacity;reservoir_capacity;float;0.0;8.6;storage;860 +General;withdrawalnominalcapacity;withdrawal_nominal_capacity;float;0.0;8.6;storage;860