Skip to content

Commit

Permalink
[readIniFile] : avoid utils::type.convert on specific cases (ex : 7…
Browse files Browse the repository at this point in the history
…89e or 123i) (#247)

* Add specific case to avoid bad convert

* Add unit test file for readIniFile
  • Loading branch information
KKamel67 authored May 13, 2024
1 parent cb61dbd commit 3801d6e
Show file tree
Hide file tree
Showing 3 changed files with 37 additions and 11 deletions.
11 changes: 2 additions & 9 deletions NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -2,17 +2,10 @@
# antaresRead 2.6.2 (development)

NEW FEATURES :
BUGFIXES :
* `readIniFile()` : avoid `utils::type.convert` on specific cases (ex : 789e or 123i)
* `api_get()` add encoding argument to pass to `httr::content()`

BUGFIXES :

BREAKING CHANGES :

DATA :

PERFORMANCE :


# antaresRead 2.6.1

Expand Down
13 changes: 11 additions & 2 deletions R/readIniFile.R
Original file line number Diff line number Diff line change
Expand Up @@ -58,14 +58,18 @@ readIni <- function(pathIni, opts = antaresRead::simOptions(), default_ext = ".i
#' @export
#' @rdname read-ini
readIniFile <- function(file, stringsAsFactors = FALSE) {

X <- readLines(file)
sections <- grep("^\\[.*\\]$", X)
starts <- sections + 1
ends <- c(sections[-1] - 1, length(X))
L <- vector(mode = "list", length = length(sections))
names(L) <- gsub("\\[|\\]", "", X[sections])

for(i in seq(along = sections)) {

if (starts[i] >= ends[i]) next

pairs <- X[seq(starts[i], ends[i])]
pairs <- pairs[pairs != ""]
pairs <- strsplit(pairs, "=")
Expand All @@ -76,20 +80,25 @@ readIniFile <- function(file, stringsAsFactors = FALSE) {

value <- lapply(pairs, `[`, 2)
value <- as.list(trimws(unlist(value)))
value <- lapply(value, function(x) {
value <- lapply(value, function(x){
if (tolower(x) %in% c("true", "false")) {
tolower(x) == "true"
} else if(!identical(grep(pattern = "^[0-9]+(e|i)$", x = x), integer(0))) {
# Not convert those type of values : 789e or 789i (complex number)
as.character(x)
} else {
utils::type.convert(x, as.is = TRUE)
}
})
}
)

L[[i]] <- value
names(L[[i]]) <- key
}
L
}


#' @param study_id Study's identifier.
#' @param path Path of configuration object to read.
#' @param host Host of AntaREST server API.
Expand Down
24 changes: 24 additions & 0 deletions tests/testthat/test-readIni.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,24 @@
test_that("First test", {

con <- file.path(tempdir(),"testReadIniFile.ini")
file.create(path = con)
cluster_list_ini_content <- c("[zone1_nuclear]", "group = Other", "name = zone1_nuclear", "test = true", "",
"[92i]", "group = Other", "name = 92i", "test = true", "",
"[zone1_gas]", "group = Other", "name = zone1_gas", "test = false", "",
"[7983e]", "group = Other", "name = 7983e", "test = true", "",
"[zone1_coal]", "group = Other", "name = zone1_coal", "test = false", ""
)
writeLines(text = cluster_list_ini_content, con = con)

clusters <- readIniFile(con)

# Specific cases not converted : 92i and 7983e
clusters_name <- sapply(clusters, "[[", "name")
clusters_name <- unname(clusters_name)
expect_identical(clusters_name, c("zone1_nuclear", "92i", "zone1_gas", "7983e", "zone1_coal"))

# Boolean
clusters_test <- sapply(clusters, "[[", "test")
clusters_test <- unname(clusters_test)
expect_true(class(clusters_test) == "logical")
})

0 comments on commit 3801d6e

Please sign in to comment.