Skip to content

Commit

Permalink
reforge function .transform_antares_version() + tests + integration i…
Browse files Browse the repository at this point in the history
…n setsimulationPath + tests
  • Loading branch information
berthetclement committed Oct 14, 2024
1 parent 3d3a4d1 commit a402ebb
Show file tree
Hide file tree
Showing 7 changed files with 109 additions and 89 deletions.
3 changes: 0 additions & 3 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -67,7 +67,6 @@ export(setSimulationPathAPI)
export(setTimeoutAPI)
export(showAliases)
export(simOptions)
export(transform_antares_version)
export(viewAntares)
export(writeDigest)
import(bit64)
Expand Down Expand Up @@ -106,8 +105,6 @@ importFrom(stats,as.formula)
importFrom(stats,setNames)
importFrom(stats,weighted.mean)
importFrom(stringi,stri_replace_last_fixed)
importFrom(stringr,str_count)
importFrom(stringr,str_detect)
importFrom(stringr,str_match)
importFrom(stringr,str_replace)
importFrom(stringr,str_split)
Expand Down
71 changes: 26 additions & 45 deletions R/setSimulationPath.R
Original file line number Diff line number Diff line change
Expand Up @@ -350,7 +350,10 @@ setSimulationPath <- function(path, simulation = NULL) {
linksDef <- data.table(linksDef)

antaresVersion <- readIniFile(file.path(studyPath, "study.antares"))$antares$version
# TODO gestion des version >= 9.0
# Convert the Antares number version (from 9.0)
if(antaresVersion<600 & antaresVersion>=9)
antaresVersion <- .transform_antares_version(antares_version = antaresVersion)

params <- readIniFile(file.path(studyPath, "settings/generaldata.ini"))

# Areas with thermal clusters
Expand Down Expand Up @@ -682,53 +685,31 @@ setSimulationPath <- function(path, simulation = NULL) {
}

#' @title Convert the Antares number version
#' @description From V9.0, system version is 9.0 (1 digit for minor) instead of 900
#'
#' @param antares_version ``numeric` Antares number version.
#'
#' @param antares_version Antares number version.
#'
#' @importFrom stringr str_count str_detect
#'
#' @export
transform_antares_version <- function(antares_version) {
antares_version <- as.character(antares_version)
#' @return `numeric` value according to study version
#'
#' @keywords internal
.transform_antares_version <- function(antares_version) {
antares_version <- format(antares_version, nsmall = 1)

# Handle single numeric version (e.g., "860", "890")
if (str_count(antares_version, "\\.") == 0) {
to_write <- antares_version
to_read <- as.numeric(antares_version) # Keep it numeric if no decimal
} else {
# Split major and minor parts
antares_version_splitted <- strsplit(antares_version, split = "\\.")[[1]]

# Ensure valid version format
if (length(antares_version_splitted) != 2 || any(!str_detect(antares_version_splitted, "^\\d+$"))) {
stop("Invalid antares_version format")
}

# Extract major and minor parts as numbers
major_version <- as.numeric(antares_version_splitted[1])
minor_version_str <- antares_version_splitted[2] # Keep minor version as string

# Check if minor version exceeds 2 digits
if (nchar(minor_version_str) > 2) {
stop("Minor version exceeds 2 digits limit.")
}

# Convert minor version to numeric for calculation
minor_version <- as.numeric(minor_version_str)

# Convert major version starting from 9.0 to 900, 10.0 to 1000, etc.
if (major_version >= 9) {
major_version_converted <- major_version * 100
} else {
stop("Major version must be 9 or higher.")
}

# Create a numeric value for comparison by treating the version as major.minor
to_write <- paste(major_version, minor_version_str, sep = ".")
to_read <- major_version_converted + minor_version # Major * 100, add minor
}
# Split major and minor parts
antares_version_splitted <- unlist(strsplit(antares_version, split = "\\."))

major <- antares_version_splitted[1]
minor <- antares_version_splitted[2]

# max 1 digit for minor
if (nchar(minor) > 1)
stop("Invalid antares_version format, good format is like '9.0'",
call. = FALSE)

# convert to numeric for package understanding
num_version <- as.numeric(antares_version)*100

return(list("w" = to_write, "r" = to_read))
return(num_version)
}


Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
[antares]
version = 9.0
caption = study_name
created = 1702567142
lastsave = 1702634579
author = Unknown
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
[antares]
version = 9.9
caption = study_name
created = 1702567142
lastsave = 1702634579
author = Unknown
18 changes: 18 additions & 0 deletions man/dot-transform_antares_version.Rd

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

14 changes: 0 additions & 14 deletions man/transform_antares_version.Rd

This file was deleted.

80 changes: 53 additions & 27 deletions tests/testthat/test-setSimulationPath.R
Original file line number Diff line number Diff line change
Expand Up @@ -208,33 +208,59 @@ test_that("New meta data for group dimension of binding constraints", {
expect_is(opts_study_test$binding, "data.table")
})

# v900---
test_that("valid versions are transformed correctly", {
expect_equal(transform_antares_version("9.0")$r, 900)
expect_equal(transform_antares_version("9.45")$r, 945)
expect_equal(transform_antares_version("10.10")$r, 1010)
expect_equal(transform_antares_version("10.45")$r, 1045)
expect_equal(transform_antares_version("12.12")$r, 1212)
})

test_that("invalid minor versions with more than 2 digits raise an error", {
expect_error(transform_antares_version("10.113400000"), "Minor version exceeds 2 digits limit.")
expect_error(transform_antares_version("9.1234"), "Minor version exceeds 2 digits limit.")
})

test_that("invalid major versions less than 9 raise an error", {
expect_error(transform_antares_version("8.99"), "Major version must be 9 or higher.")
expect_error(transform_antares_version("7.10"), "Major version must be 9 or higher.")
})

test_that("single numeric versions work correctly", {
expect_equal(transform_antares_version("860")$r, 860)
expect_equal(transform_antares_version("890")$r, 890)
# v900----
## test private ----
test_that("read new format version from .antares file", {
test_path_files <- system.file("test_files", package = "antaresRead")

# "readIniFile" conversion problem (9.0 => 9)
antares_file <- file.path(test_path_files,
"antares_version_files",
"antares_version_float.antares")

file_to_read <- readIniFile(file = antares_file, stringsAsFactors = TRUE)

version_value <- file_to_read$antares$version

# test right conversion for package
expect_equal(.transform_antares_version(version_value), 900)

# exception max digit minor
expect_error(.transform_antares_version(9.01),
regexp = "Invalid antares_version format")

# read right format file
antares_file <- file.path(test_path_files,
"antares_version_files",
"antares_version_float_2digit.antares")

file_to_read <- readIniFile(file = antares_file, stringsAsFactors = TRUE)

version_value <- file_to_read$antares$version

# test right conversion for package
expect_equal(.transform_antares_version(version_value), 990)
})

test_that("correct output for to_write field", {
expect_equal(transform_antares_version("9.0")$w, "9.0")
expect_equal(transform_antares_version("9.45")$w, "9.45")
expect_equal(transform_antares_version("10.10")$w, "10.10")
expect_equal(transform_antares_version("12.12")$w, "12.12")
## study ----
test_that("read new format version from study", {
path <- setup_study_empty(dir_path = sourcedir_empty_study)
opts_study_test <- setSimulationPath(path)

# "hack" study and paste test file with version "9.0"
test_path_files <- system.file("test_files", package = "antaresRead")
antares_file <- file.path(test_path_files,
"antares_version_files",
"antares_version_float.antares")

# delete "study.antares"
file_to_remove <- file.path(opts_study_test$studyPath, "study.antares")
file.remove(file_to_remove)
file.copy(from = antares_file, to = file_to_remove)

# read study
study <- setSimulationPath(path)

# test right conversion for package
expect_equal(study$antaresVersion, 900)
})

0 comments on commit a402ebb

Please sign in to comment.