|
34 | 34 | #'
|
35 | 35 | .importInputTS <- function(area, timeStep, opts, fileNamePattern, colnames,
|
36 | 36 | inputTimeStep, fun = "sum", type = "simple", colSelect = NULL, ...) {
|
37 |
| - |
| 37 | + |
38 | 38 | path <- file.path(opts$inputPath, sprintf(fileNamePattern, area))
|
39 | 39 |
|
40 | 40 | # if(!is.null(colSelect)){
|
|
48 | 48 | daily=range(.getTimeId(opts$timeIdMin:opts$timeIdMax, "daily", opts)),
|
49 | 49 | monthly=range(.getTimeId(opts$timeIdMin:opts$timeIdMax, "monthly", opts)))
|
50 | 50 |
|
51 |
| - if(opts$typeLoad == "api"){ |
52 |
| - path <- .changeNameInput(path, opts) |
53 |
| - } |
54 |
| - |
55 | 51 |
|
56 |
| - |
57 |
| - |
58 | 52 | if (opts$typeLoad == 'api' || (file.exists(path) && !file.size(path) == 0)) {
|
59 | 53 | if(is.null(colSelect))
|
60 | 54 | {
|
61 |
| - inputTS <- fread(path, integer64 = "numeric", header = FALSE, showProgress = FALSE) |
62 |
| - }else{ |
63 |
| - inputTS <- fread(path, integer64 = "numeric", header = FALSE, select = colSelect, showProgress = FALSE) |
| 55 | + # inputTS <- fread(path, integer64 = "numeric", header = FALSE, showProgress = FALSE) |
| 56 | + inputTS <- fread_antares(opts = opts, file = path, integer64 = "numeric", header = FALSE, showProgress = FALSE) |
| 57 | + } else { |
| 58 | + # inputTS <- fread(path, integer64 = "numeric", header = FALSE, select = colSelect, showProgress = FALSE) |
| 59 | + inputTS <- fread_antares(opts = opts, file = path, integer64 = "numeric", header = FALSE, select = colSelect, showProgress = FALSE) |
64 | 60 | }
|
65 | 61 |
|
66 |
| - if (opts$typeLoad == 'api' || opts$antaresVersion < 650) { |
67 |
| - |
68 |
| - inputTS <- .reorderInputTSHydroStorage(inputTS, path, opts) |
| 62 | + # browser() |
| 63 | + if (opts$antaresVersion < 650) { |
| 64 | + if(!is.null(inputTS)){ |
| 65 | + inputTS <- .reorderInputTSHydroStorage(inputTS, path, opts) |
| 66 | + } |
69 | 67 | }
|
70 | 68 |
|
71 |
| - inputTS <- inputTS[timeRange[1]:timeRange[2]] |
| 69 | + if(!is.null(inputTS)){ |
| 70 | + inputTS <- inputTS[timeRange[1]:timeRange[2]] |
| 71 | + } else { |
| 72 | + if (type == "matrix") return(NULL) |
| 73 | + inputTS <- data.table(matrix(0L, timeRange[2] - timeRange[1] + 1,length(colnames))) |
| 74 | + } |
72 | 75 | } else {
|
73 | 76 | if (type == "matrix") return(NULL)
|
74 | 77 | inputTS <- data.table(matrix(0L, timeRange[2] - timeRange[1] + 1,length(colnames)))
|
75 | 78 | }
|
76 | 79 |
|
77 |
| - # Add area and timeId columns and put it at the begining of the table |
78 |
| - inputTS$area <- area |
79 |
| - inputTS$timeId <- timeRange[1]:timeRange[2] |
80 |
| - .reorderCols(inputTS) |
81 |
| - |
82 |
| - inputTS <- changeTimeStep(inputTS, timeStep, inputTimeStep, fun = fun, opts = opts) |
83 |
| - |
84 |
| - # If the data is a matrix of time series melt the data |
85 |
| - if (type == "matrix") { |
86 |
| - colnames <- c("tsId", colnames) |
87 |
| - inputTS <- melt(inputTS, id.vars = c("area", "timeId")) |
88 |
| - inputTS$variable <- as.integer(substring(inputTS$variable, 2)) |
| 80 | + if(!is.null(inputTS)){ |
| 81 | + # Add area and timeId columns and put it at the begining of the table |
| 82 | + inputTS$area <- area |
| 83 | + inputTS$timeId <- timeRange[1]:timeRange[2] |
| 84 | + .reorderCols(inputTS) |
| 85 | + |
| 86 | + inputTS <- changeTimeStep(inputTS, timeStep, inputTimeStep, fun = fun, opts = opts) |
| 87 | + |
| 88 | + # If the data is a matrix of time series melt the data |
| 89 | + if (type == "matrix") { |
| 90 | + colnames <- c("tsId", colnames) |
| 91 | + inputTS <- melt(inputTS, id.vars = c("area", "timeId")) |
| 92 | + inputTS$variable <- as.integer(substring(inputTS$variable, 2)) |
| 93 | + } |
| 94 | + |
| 95 | + setnames(inputTS, names(inputTS), c("area", "timeId", colnames)) |
89 | 96 | }
|
90 |
| - |
91 |
| - setnames(inputTS, names(inputTS), c("area", "timeId", colnames)) |
92 |
| - |
93 | 97 | inputTS
|
94 | 98 | }
|
95 | 99 |
|
|
101 | 105 | .importThermalAvailabilities <- function(area, timeStep, opts, ...) {
|
102 | 106 | if (!area %in% opts$areasWithClusters) return(NULL)
|
103 | 107 |
|
104 |
| - clusters <- list.files(file.path(opts$inputPath, "thermal/series", area)) |
105 |
| - |
| 108 | + if(!"api" %in% opts$typeLoad){ |
| 109 | + clusters <- list.files(file.path(opts$inputPath, "thermal/series", area)) |
| 110 | + } else { |
| 111 | + clusters <- names(read_secure_json(file.path(opts$inputPath, "thermal/series", area), |
| 112 | + token = opts$token, timeout = opts$timeout)) |
| 113 | + } |
| 114 | + |
106 | 115 | ldply(clusters, function(cl) {
|
107 | 116 | filePattern <- sprintf("%s/%s/%%s/series.txt", "thermal/series", area)
|
108 | 117 | res <- .importInputTS(cl, timeStep, opts, filePattern, "ThermalAvailabilities",
|
|
119 | 128 | }
|
120 | 129 |
|
121 | 130 | .importResProduction <- function(area, timeStep, opts, ...) {
|
| 131 | + |
122 | 132 | if (!area %in% opts$areasWithResClusters) return(NULL)
|
123 | 133 |
|
124 |
| - clusters <- list.files(file.path(opts$inputPath, "renewables/series", area)) |
125 |
| - |
| 134 | + if(!"api" %in% opts$typeLoad){ |
| 135 | + clusters <- list.files(file.path(opts$inputPath, "renewables/series", area)) |
| 136 | + } else { |
| 137 | + clusters <- names(read_secure_json(file.path(opts$inputPath, "renewables/series", area), |
| 138 | + token = opts$token, timeout = opts$timeout)) |
| 139 | + } |
| 140 | + |
126 | 141 | ldply(clusters, function(cl) {
|
127 | 142 | filePattern <- sprintf("%s/%s/%%s/series.txt", "renewables/series", area)
|
128 | 143 | res <- .importInputTS(cl, timeStep, opts, filePattern, "production",
|
|
147 | 162 | .importInputTS(area, timeStep, opts, "hydro/series/%s/mod.txt", "hydroStorage",
|
148 | 163 | inputTimeStep = inputTimeStepV, type = "matrix")
|
149 | 164 | }
|
150 |
| - |
| 165 | + |
151 | 166 | .importHydroStorageMaxPower <- function(area, timeStep, opts, unselect = NULL, ...) {
|
152 | 167 |
|
153 | 168 | unselect = unselect$areas
|
|
267 | 282 | unselect <- unselect$areas
|
268 | 283 | path <- file.path(opts$inputPath, "thermal/prepro", area)
|
269 | 284 |
|
270 |
| - clusters <- list.files(path) |
| 285 | + if(!"api" %in% opts$typeLoad){ |
| 286 | + clusters <- list.files(path) |
| 287 | + } else { |
| 288 | + clusters <- names(read_secure_json(path, token = opts$token, timeout = opts$timeout)) |
| 289 | + } |
271 | 290 |
|
272 | 291 | beginName <- c("marginalCostModulation", "marketBidModulation",
|
273 |
| - "capacityModulation", "minGenModulation") |
| 292 | + "capacityModulation", "minGenModulation") |
274 | 293 | if(!is.null(unselect)){
|
275 | 294 | colSelect <- which(!beginName%in%unselect)
|
276 | 295 | names <- beginName[colSelect]
|
|
283 | 302 | res <- ldply(clusters, function(cl) {
|
284 | 303 | if(is.null(colSelect))
|
285 | 304 | {
|
286 |
| - modulation <- fread(file.path(path, cl, "modulation.txt"), colClasses = "numeric") |
| 305 | + # modulation <- fread(file.path(path, cl, "modulation.txt"), colClasses = "numeric") |
| 306 | + modulation <- fread_antares(opts = opts, file = file.path(path, cl, "modulation.txt"), colClasses = "numeric") |
287 | 307 | }else{
|
288 |
| - modulation <- fread(file.path(path, cl, "modulation.txt"), select = colSelect, colClasses = "numeric") |
| 308 | + # modulation <- fread(file.path(path, cl, "modulation.txt"), select = colSelect, colClasses = "numeric") |
| 309 | + modulation <- fread_antares(opts = opts, file = file.path(path, cl, "modulation.txt"), select = colSelect, colClasses = "numeric") |
289 | 310 | }
|
290 | 311 |
|
291 | 312 | setnames(modulation,
|
|
305 | 326 | })
|
306 | 327 | }
|
307 | 328 |
|
308 |
| -.changeNameInput <- function(path, opts){ |
309 |
| - out <- sub(pattern = "studies", "file", path) |
310 |
| - out <- gsub(" ", "%20", out) |
311 |
| -} |
| 329 | +# .changeNameInput <- function(path, opts){ |
| 330 | +# out <- sub(pattern = "studies", "file", path) |
| 331 | +# out <- gsub(" ", "%20", out) |
| 332 | +# } |
0 commit comments