Skip to content

Commit

Permalink
Do not send empty value for adequacy patch section in generaldata.ini (
Browse files Browse the repository at this point in the history
…#193)

* Add dicoAdequacySettings() function, clean list of values to send by removing NULL

* Add update_generaldata_by_section() and use it in updateAdequacySettings()

* Use update_generaldata_by_section()

* Treat enable_first_step property as disabled in API and disk mode.

* Set enable_first_step to FALSE if it is in new_params

* Do not export dicoAdequacySettings()
  • Loading branch information
KKamel67 authored Jan 21, 2025
1 parent c5b09f5 commit fd492fe
Show file tree
Hide file tree
Showing 7 changed files with 139 additions and 99 deletions.
3 changes: 3 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -25,6 +25,9 @@ BUGFIXES :

* *[private function]* `api_command_execute()` manage snapshot generation of a variant study with a tempo to wait the end of current task (prevents the order from being ignored).

BUGFIXES :

* `updateAdequacySettings()` : in API mode do not send NULL value


# antaresEditObject 0.7.1
Expand Down
121 changes: 63 additions & 58 deletions R/updateAdequacySettings.R
Original file line number Diff line number Diff line change
Expand Up @@ -46,79 +46,53 @@ updateAdequacySettings <- function(include_adq_patch = NULL,
threshold_csr_variable_bounds_relaxation = NULL,
opts = antaresRead::simOptions()) {

if (opts$antaresVersion < 830) stop("This function is only available for studies v8.3 or higher.")

assertthat::assert_that(inherits(opts, "simOptions"))

# API block
if (is_api_study(opts)) {

writeIni(
listData = list(
`include-adq-patch` = include_adq_patch,
`set-to-null-ntc-from-physical-out-to-physical-in-for-first-step` = set_to_null_ntc_from_physical_out_to_physical_in_for_first_step,
`set-to-null-ntc-between-physical-out-for-first-step` = set_to_null_ntc_between_physical_out_for_first_step,
`price-taking-order` = price_taking_order,
`include-hurdle-cost-csr` = include_hurdle_cost_csr,
`check-csr-cost-function` = check_csr_cost_function,
`threshold-initiate-curtailment-sharing-rule` = threshold_initiate_curtailment_sharing_rule,
`threshold-display-local-matching-rule-violations` = threshold_display_local_matching_rule_violations,
`threshold-csr-variable-bounds-relaxation` = threshold_csr_variable_bounds_relaxation
),
pathIni = "settings/generaldata/adequacy patch",
opts = opts
)

return(update_api_opts(opts))
if (opts[["antaresVersion"]] < 830) {
stop("This function is only available for studies v8.3 or higher.")
}

pathIni <- file.path(opts$studyPath, "settings", "generaldata.ini")
general <- readIniFile(file = pathIni)
new_params <- list(
"include_adq_patch" = include_adq_patch,
"set_to_null_ntc_from_physical_out_to_physical_in_for_first_step" = set_to_null_ntc_from_physical_out_to_physical_in_for_first_step,
"set_to_null_ntc_between_physical_out_for_first_step" = set_to_null_ntc_between_physical_out_for_first_step,
"include_hurdle_cost_csr" = include_hurdle_cost_csr,
"check_csr_cost_function" = check_csr_cost_function,
"enable_first_step" = enable_first_step,
"price_taking_order" = price_taking_order,
"threshold_initiate_curtailment_sharing_rule" = threshold_initiate_curtailment_sharing_rule,
"threshold_display_local_matching_rule_violations" = threshold_display_local_matching_rule_violations,
"threshold_csr_variable_bounds_relaxation" = threshold_csr_variable_bounds_relaxation
)

adequacy <- general$`adequacy patch`
if (!is.null(include_adq_patch))
adequacy$`include-adq-patch` <- include_adq_patch
if (!is.null(set_to_null_ntc_from_physical_out_to_physical_in_for_first_step))
adequacy$`set-to-null-ntc-from-physical-out-to-physical-in-for-first-step` <- set_to_null_ntc_from_physical_out_to_physical_in_for_first_step
if (!is.null(set_to_null_ntc_between_physical_out_for_first_step))
adequacy$`set-to-null-ntc-between-physical-out-for-first-step` <- set_to_null_ntc_between_physical_out_for_first_step
new_params <- dropNulls(x = new_params)

if (opts$antaresVersion >= 850) {
if (!is.null(price_taking_order))
adequacy$`price-taking-order` <- price_taking_order
if (!is.null(include_hurdle_cost_csr))
adequacy$`include-hurdle-cost-csr` <- include_hurdle_cost_csr
if (!is.null(check_csr_cost_function))
adequacy$`check-csr-cost-function` <- check_csr_cost_function
if (!is.null(threshold_initiate_curtailment_sharing_rule))
adequacy$`threshold-initiate-curtailment-sharing-rule` <- threshold_initiate_curtailment_sharing_rule
if (!is.null(threshold_display_local_matching_rule_violations))
adequacy$`threshold-display-local-matching-rule-violations` <- threshold_display_local_matching_rule_violations
if (!is.null(threshold_csr_variable_bounds_relaxation))
adequacy$`threshold-csr-variable-bounds-relaxation` <- threshold_csr_variable_bounds_relaxation
if (opts[["antaresVersion"]] < 850) {
properties_850 <- c("price_taking_order",
"include_hurdle_cost_csr",
"check_csr_cost_function",
"threshold_initiate_curtailment_sharing_rule",
"threshold_display_local_matching_rule_violations",
"threshold_csr_variable_bounds_relaxation")
new_params <- new_params[!names(new_params) %in% properties_850]
}

# Necessary only for desktop application. Not used in API mode.
if (opts$antaresVersion >= 860) {
if (!is.null(enable_first_step)) {
adequacy$`enable-first-step` <- enable_first_step
}
if (opts[["antaresVersion"]] >= 860) {
if ("enable_first_step" %in% names(new_params)) {
message("Property enable_first_step is disabled for the moment. Set to FALSE.\n")
new_params[["enable_first_step"]] <- FALSE
}
}
general$`adequacy patch` <- adequacy

writeIni(listData = general, pathIni = pathIni, overwrite = TRUE)

# Maj simulation
suppressWarnings({
res <- antaresRead::setSimulationPath(path = opts$studyPath, simulation = "input")
})
new_params <- lapply(X = new_params, FUN = .format_ini_rhs)
names(new_params) <- sapply(names(new_params), dicoAdequacySettings, USE.NAMES = FALSE)

res <- update_generaldata_by_section(opts = opts, section = "adequacy patch", new_params = new_params)

invisible(res)
}




#' @title Read adequacy patch config.yml into Antares (v8.5+)
#'
#' @description
Expand Down Expand Up @@ -152,3 +126,34 @@ convertConfigToAdq <- function(opts = simOptions(), path = "default"){
editArea, adequacy = adequacyOptions(adequacy_patch_mode = "inside"))
if (length(pathOut) > 0) setSimulationPath(pathOut)
}


#' Correspondence between arguments of \code{updateAdequacySettings} and actual Antares parameters.
#'
#' @param arg An argument from function \code{updateAdequacySettings}.
#'
#' @return The corresponding Antares general parameter.
#'
dicoAdequacySettings <- function(arg) {

if (length(arg) > 1) {
stop("'arg' must be length one")
}

antares_params <- as.list(c("include-adq-patch", "set-to-null-ntc-from-physical-out-to-physical-in-for-first-step",
"set-to-null-ntc-between-physical-out-for-first-step", "include-hurdle-cost-csr",
"check-csr-cost-function", "enable-first-step",
"price-taking-order", "threshold-initiate-curtailment-sharing-rule",
"threshold-display-local-matching-rule-violations", "threshold-csr-variable-bounds-relaxation"
)
)

names(antares_params) <- c("include_adq_patch", "set_to_null_ntc_from_physical_out_to_physical_in_for_first_step",
"set_to_null_ntc_between_physical_out_for_first_step", "include_hurdle_cost_csr",
"check_csr_cost_function", "enable_first_step",
"price_taking_order", "threshold_initiate_curtailment_sharing_rule",
"threshold_display_local_matching_rule_violations", "threshold_csr_variable_bounds_relaxation"
)

return(antares_params[[arg]])
}
21 changes: 1 addition & 20 deletions R/updateGeneralSettings.R
Original file line number Diff line number Diff line change
Expand Up @@ -158,26 +158,7 @@ updateGeneralSettings <- function(mode = NULL,
new_params <- lapply(X = new_params, FUN = .format_ini_rhs)
names(new_params) <- sapply(names(new_params), dicoGeneralSettings, USE.NAMES = FALSE)

# API block
if (is_api_study(opts)) {

writeIni(listData = new_params, pathIni = "settings/generaldata/general", opts = opts)

return(update_api_opts(opts))
}

generaldatapath <- file.path(opts[["studyPath"]], "settings", "generaldata.ini")
generaldata <- readIniFile(file = generaldatapath)

l_general <- generaldata[["general"]]
l_general <- modifyList(x = l_general, val = new_params)
generaldata[["general"]] <- l_general

writeIni(listData = generaldata, pathIni = generaldatapath, overwrite = TRUE, opts = opts)

suppressWarnings({
res <- setSimulationPath(path = opts[["studyPath"]], simulation = "input")
})
res <- update_generaldata_by_section(opts = opts, section = "general", new_params = new_params)

invisible(res)
}
Expand Down
22 changes: 1 addition & 21 deletions R/updateOutputSettings.R
Original file line number Diff line number Diff line change
Expand Up @@ -51,30 +51,10 @@ updateOutputSettings <- function(synthesis = NULL,
)

new_params <- dropNulls(x = new_params)

new_params <- lapply(X = new_params, FUN = .format_ini_rhs)
names(new_params) <- sapply(names(new_params), dicoOutputSettings, USE.NAMES = FALSE)

# API block
if (is_api_study(opts)) {

writeIni(listData = new_params, pathIni = "settings/generaldata/output", opts = opts)

return(update_api_opts(opts))
}

generaldatapath <- file.path(opts[["studyPath"]], "settings", "generaldata.ini")
generaldata <- readIniFile(file = generaldatapath)

l_output <- generaldata[["output"]]
l_output <- modifyList(x = l_output, val = new_params)
generaldata[["output"]] <- l_output

writeIni(listData = generaldata, pathIni = generaldatapath, overwrite = TRUE, opts = opts)

suppressWarnings({
res <- setSimulationPath(path = opts[["studyPath"]], simulation = "input")
})
res <- update_generaldata_by_section(opts = opts, section = "output", new_params = new_params)

invisible(res)
}
Expand Down
32 changes: 32 additions & 0 deletions R/utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -172,3 +172,35 @@ generate_cluster_name <- function(area, cluster_name, add_prefix) {

return(paste(as.character(value), collapse = ", "))
}

#' @title Update a specific section in generaldata.ini file
#'
#' @template opts
#' @param section The section to update.
#' @param new_params The values to write in the section.
#'
#' @importFrom antaresRead readIniFile
update_generaldata_by_section <- function(opts, section, new_params) {

if (is_api_study(opts = opts)) {

writeIni(listData = new_params, pathIni = sprintf("settings/generaldata/%s", section), opts = opts)

} else {

generaldatapath <- file.path(opts[["studyPath"]], "settings", "generaldata.ini")
generaldata <- readIniFile(file = generaldatapath)

if (section %in% names(generaldata)) {
l_section <- generaldata[[section]]
l_section <- modifyList(x = l_section, val = new_params)
} else {
l_section <- new_params
}
generaldata[[section]] <- l_section

writeIni(listData = generaldata, pathIni = generaldatapath, overwrite = TRUE, opts = opts)
}

return(update_opts(opts = opts))
}
17 changes: 17 additions & 0 deletions man/dicoAdequacySettings.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

22 changes: 22 additions & 0 deletions man/update_generaldata_by_section.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

0 comments on commit fd492fe

Please sign in to comment.