a few fixes
authorBenjamin Auder <benjamin.auder@somewhere>
Mon, 24 Apr 2017 22:12:17 +0000 (00:12 +0200)
committerBenjamin Auder <benjamin.auder@somewhere>
Mon, 24 Apr 2017 22:12:17 +0000 (00:12 +0200)
pkg/R/computeError.R
pkg/R/computeForecast.R
reports/Experiments.gj
reports/PackageR.gj

index 0b1771f..c3bc4f3 100644 (file)
@@ -16,8 +16,8 @@
 computeError = function(data, pred, predict_from, horizon=length(data$getSerie(1)))
 {
        L = pred$getSize()
-       mape_day = rep(0, horizon)
-       abs_day = rep(0, horizon)
+       mape_day = rep(0, horizon-predict_from+1)
+       abs_day = rep(0, horizon-predict_from+1)
        mape_indices = rep(NA, L)
        abs_indices = rep(NA, L)
 
index e967cc7..ca8badd 100644 (file)
@@ -71,27 +71,20 @@ computeForecast = function(data, indices, forecaster, pjump, predict_from,
        forecaster = forecaster_class_name$new( #.pjump =
                getFromNamespace(paste("get",pjump,"JumpPredict",sep=""), "talweg"))
 
-       if (ncores > 1 && requireNamespace("parallel",quietly=TRUE))
+       computeOneForecast <- function(i)
        {
-               p <- parallel::mclapply(seq_along(integer_indices), function(i) {
-                       list(
-                               "forecast" = forecaster$predictSerie(
-                                       data, integer_indices[i], memory, predict_from, horizon, ...),
-                               "params"= forecaster$getParameters(),
-                               "index" = integer_indices[i] )
-                       }, mc.cores=ncores)
-       }
-       else
-       {
-               p <- lapply(seq_along(integer_indices), function(i) {
-                       list(
-                               "forecast" = forecaster$predictSerie(
-                                       data, integer_indices[i], memory, predict_from, horizon, ...),
-                               "params"= forecaster$getParameters(),
-                               "index" = integer_indices[i] )
-                       })
+               list(
+                       "forecast" = forecaster$predictSerie(data,i,memory,predict_from,horizon,...),
+                       "params" = forecaster$getParameters(),
+                       "index" = i )
        }
 
+       p <-
+               if (ncores > 1 && requireNamespace("parallel",quietly=TRUE))
+                       parallel::mclapply(integer_indices, computeOneForecast, mc.cores=ncores)
+               else
+                       lapply(integer_indices, computeOneForecast)
+
        # TODO: find a way to fill pred in //...
        for (i in seq_along(integer_indices))
        {
index 0f102ad..d7ade40 100644 (file)
@@ -2,8 +2,8 @@
 # Résultats numériques
 
 Cette partie montre les résultats obtenus avec des variantes de l'algorithme décrit au
-chapitre , en utilisant le package présenté à la section 3. Cet algorithme est
-systématiquement comparé à deux approches naïves :
+à la section 4, en utilisant le package présenté au chapitre précédent. Cet
+algorithme est systématiquement comparé à deux approches naïves :
 
  * la moyenne des lendemains des jours "similaires" dans tout le passé, c'est-à-dire
 prédiction = moyenne de tous les mardis passés si le jour courant est un lundi.
@@ -35,8 +35,8 @@ list_indices = ['indices_ch', 'indices_ep', 'indices_np']
 -----r
 library(talweg)
 
-P = ${P} #instant de prévision
-H = ${H} #horizon (en heures)
+P = ${P} #première heure de prévision
+H = ${H} #dernière heure de prévision
 
 ts_data = read.csv(system.file("extdata","pm10_mesures_H_loc_report.csv",
        package="talweg"))
@@ -44,8 +44,7 @@ exo_data = read.csv(system.file("extdata","meteo_extra_noNAs.csv",
        package="talweg"))
 # NOTE: 'GMT' because DST gaps are filled and multiple values merged in
 # above dataset. Prediction from P+1 to P+H included.
-data = getData(ts_data, exo_data, input_tz = "GMT", working_tz="GMT",
-       predict_at=P)
+data = getData(ts_data, exo_data)
 
 indices_ch = seq(as.Date("2015-01-18"),as.Date("2015-01-24"),"days")
 indices_ep = seq(as.Date("2015-03-15"),as.Date("2015-03-21"),"days")
@@ -55,21 +54,22 @@ indices_np = seq(as.Date("2015-04-26"),as.Date("2015-05-02"),"days")
 ##<h2 style="color:blue;font-size:2em">${list_titles[i]}</h2>
 ${"##"} ${list_titles[i]}
 -----r
-p1 = computeForecast(data, ${list_indices[i]}, "Neighbors", "Neighbors", horizon=H,
-       simtype="mix", local=FALSE)
-p2 = computeForecast(data, ${list_indices[i]}, "Neighbors", "Neighbors", horizon=H,
-       simtype="endo", local=TRUE)
-p3 = computeForecast(data, ${list_indices[i]}, "Neighbors", "Zero", horizon=H,
-       simtype="none", local=TRUE)
-p4 = computeForecast(data, ${list_indices[i]}, "Average", "Zero", horizon=H)
-p5 = computeForecast(data, ${list_indices[i]}, "Persistence", "Zero", horizon=H,
-       same_day=${'TRUE' if loop.index < 2 else 'FALSE'})
+p1 = computeForecast(data, ${list_indices[i]}, "Neighbors", "Neighbors", predict_from=P,
+       horizon=H, simtype="mix", local=FALSE)
+p2 = computeForecast(data, ${list_indices[i]}, "Neighbors", "Neighbors", predict_from=P,
+       horizon=H, simtype="endo", local=TRUE)
+p3 = computeForecast(data, ${list_indices[i]}, "Neighbors", "Zero", predict_from=P,
+       horizon=H, simtype="none", local=TRUE)
+p4 = computeForecast(data, ${list_indices[i]}, "Average", "Zero", predict_from=P,
+       horizon=H)
+p5 = computeForecast(data, ${list_indices[i]}, "Persistence", "Zero", predict_from=P,
+       horizon=H, same_day=${'TRUE' if loop.index < 2 else 'FALSE'})
 -----r
-e1 = computeError(data, p1, H)
-e2 = computeError(data, p2, H)
-e3 = computeError(data, p3, H)
-e4 = computeError(data, p4, H)
-e5 = computeError(data, p5, H)
+e1 = computeError(data, p1, P, H)
+e2 = computeError(data, p2, P, H)
+e3 = computeError(data, p3, P, H)
+e4 = computeError(data, p4, P, H)
+e5 = computeError(data, p5, P, H)
 options(repr.plot.width=9, repr.plot.height=7)
 plotError(list(e1, e5, e4, e2, e3), cols=c(1,2,colors()[258],4,6))
 
@@ -134,14 +134,14 @@ journée sur la courbes "difficile à prévoir".
 % endif
 -----r
 par(mfrow=c(1,2))
-f_np1 = computeFilaments(data, p1, i_np, plot=TRUE)
+f_np1 = computeFilaments(data, p1, i_np, predict_from=P, plot=TRUE)
        title(paste("Filaments p1 day",i_np))
-f_p1 = computeFilaments(data, p1, i_p, plot=TRUE)
+f_p1 = computeFilaments(data, p1, i_p, predict_from=P, plot=TRUE)
        title(paste("Filaments p1 day",i_p))
 
-f_np2 = computeFilaments(data, p2, i_np, plot=TRUE)
+f_np2 = computeFilaments(data, p2, i_np, predict_from=P, plot=TRUE)
        title(paste("Filaments p2 day",i_np))
-f_p2 = computeFilaments(data, p2, i_p, plot=TRUE)
+f_p2 = computeFilaments(data, p2, i_p, predict_from=P, plot=TRUE)
        title(paste("Filaments p2 day",i_p))
 -----
 % if i == 0:
@@ -161,8 +161,8 @@ de variabilité relative.
 % endif
 -----r
 par(mfrow=c(1,2))
-plotFilamentsBox(data, f_np1); title(paste("FilBox p1 day",i_np))
-plotFilamentsBox(data, f_p1); title(paste("FilBox p1 day",i_p))
+plotFilamentsBox(data, f_np1, predict_from=P); title(paste("FilBox p1 day",i_np))
+plotFilamentsBox(data, f_p1, predict_from=P); title(paste("FilBox p1 day",i_p))
 
 # En pointillés la courbe du jour courant + lendemain (à prédire)
 -----
@@ -185,11 +185,11 @@ lendemains de voisins atypiques, courbe à prévoir elle-même légèrement
 % endif
 -----r
 par(mfrow=c(1,2))
-plotRelVar(data, f_np1); title(paste("StdDev p1 day",i_np))
-plotRelVar(data, f_p1); title(paste("StdDev p1 day",i_p))
+plotRelVar(data, f_np1, predict_from=P); title(paste("StdDev p1 day",i_np))
+plotRelVar(data, f_p1, predict_from=P); title(paste("StdDev p1 day",i_p))
 
-plotRelVar(data, f_np2); title(paste("StdDev p2 day",i_np))
-plotRelVar(data, f_p2); title(paste("StdDev p2 day",i_p))
+plotRelVar(data, f_np2, predict_from=P); title(paste("StdDev p2 day",i_np))
+plotRelVar(data, f_p2, preidct_from=P); title(paste("StdDev p2 day",i_p))
 
 # Variabilité globale en rouge ; sur les voisins (+ lendemains) en noir
 -----
index 567bfd6..29c4822 100644 (file)
@@ -21,17 +21,14 @@ partie suivante.
 library(talweg)
 
 # Acquisition des données (depuis les fichiers CSV)
-ts_data <- read.csv(system.file("extdata","pm10_mesures_H_loc.csv",
-       package="talweg"))
-exo_data <- read.csv(system.file("extdata","meteo_extra_noNAs.csv",
-       package="talweg"))
-data <- getData(ts_data, exo_data,
-       date_format="%d/%m/%Y %H:%M", limit=120)
+ts_data <- read.csv(system.file("extdata","pm10_mesures_H_loc.csv", package="talweg"))
+exo_data <- read.csv(system.file("extdata","meteo_extra_noNAs.csv", package="talweg"))
+data <- getData(ts_data, exo_data, date_format="%d/%m/%Y %H:%M", limit=120)
 # Plus de détails à la section 1 ci-après.
 
 # Prédiction de 10 courbes (jours 102 à 111)
-pred <- computeForecast(data, 101:110, "Persistence", "Zero",
-       predict_from=8, memory=50, horizon=24, ncores=1)
+pred <- computeForecast(data, 101:110, "Persistence", "Zero", predict_from=8, memory=50,
+       horizon=24, ncores=1)
 # Plus de détails à la section 2 ci-après.
 
 # Calcul des erreurs (sur un horizon arbitraire <= horizon de prédiction)