Add CV-voting, remove random forests
[agghoo.git] / R / compareTo.R
CommitLineData
a7ec4f8a
BA
1#' CVvoting_core
2#'
3#' "voting" cross-validation method, added here as an example.
4#' Parameters are described in ?agghoo and ?AgghooCV
5CVvoting_core <- function(data, target, task, gmodel, params, loss, CV) {
6 CV <- checkCV(CV)
7 n <- nrow(data)
8 shuffle_inds <- NULL
9 if (CV$type == "vfold" && CV$shuffle)
10 shuffle_inds <- sample(n, n)
11 bestP <- rep(0, gmodel$nmodels)
12 gmodel <- agghoo::Model$new(data, target, task, gmodel, params)
13 for (v in seq_len(CV$V)) {
14 test_indices <- get_testIndices(n, CV, v, shuffle_inds)
15 d <- splitTrainTest(data, target, test_indices)
16 best_p <- NULL
17 best_error <- Inf
18 for (p in seq_len(gmodel$nmodels)) {
19 model_pred <- gmodel$get(d$dataTrain, d$targetTrain, p)
20 prediction <- model_pred(d$dataTest)
21 error <- loss(prediction, d$targetTest)
22 if (error <= best_error) {
23 if (error == best_error)
24 best_p[[length(best_p)+1]] <- p
25 else {
26 best_p <- list(p)
27 best_error <- error
28 }
29 }
30 }
31 for (p in best_p)
32 bestP[p] <- bestP[p] + 1
33 }
34 # Choose a param at random in case of ex-aequos:
35 maxP <- max(bestP)
36 chosenP <- sample(which(bestP == maxP), 1)
37 list(model=gmodel$get(data, target, chosenP), param=gmodel$getParam(chosenP))
38}
39
17ea2f13
BA
40#' standardCV_core
41#'
42#' Cross-validation method, added here as an example.
43#' Parameters are described in ?agghoo and ?AgghooCV
afa67660 44standardCV_core <- function(data, target, task, gmodel, params, loss, CV) {
43a6578d
BA
45 n <- nrow(data)
46 shuffle_inds <- NULL
47 if (CV$type == "vfold" && CV$shuffle)
48 shuffle_inds <- sample(n, n)
43a6578d
BA
49 list_testinds <- list()
50 for (v in seq_len(CV$V))
afa67660 51 list_testinds[[v]] <- get_testIndices(n, CV, v, shuffle_inds)
43a6578d
BA
52 gmodel <- agghoo::Model$new(data, target, task, gmodel, params)
53 best_error <- Inf
a7ec4f8a 54 best_p <- NULL
43a6578d 55 for (p in seq_len(gmodel$nmodels)) {
afa67660 56 error <- Reduce('+', lapply(seq_len(CV$V), function(v) {
43a6578d 57 testIdx <- list_testinds[[v]]
afa67660
BA
58 d <- splitTrainTest(data, target, testIdx)
59 model_pred <- gmodel$get(d$dataTrain, d$targetTrain, p)
60 prediction <- model_pred(d$dataTest)
61 loss(prediction, d$targetTest)
62 }) )
43a6578d 63 if (error <= best_error) {
43a6578d 64 if (error == best_error)
a7ec4f8a 65 best_p[[length(best_p)+1]] <- p
43a6578d 66 else {
a7ec4f8a 67 best_p <- list(p)
43a6578d
BA
68 best_error <- error
69 }
70 }
71 }
a7ec4f8a
BA
72 chosenP <- best_p[[ sample(length(best_p), 1) ]]
73 list(model=gmodel$get(data, target, chosenP), param=gmodel$getParam(chosenP))
43a6578d
BA
74}
75
17ea2f13
BA
76#' standardCV_run
77#'
78#' Run and eval the standard cross-validation procedure.
79#' Parameters are rather explicit except "floss", which corresponds to the
80#' "final" loss function, applied to compute the error on testing dataset.
81#'
82#' @export
43a6578d 83standardCV_run <- function(
17ea2f13 84 dataTrain, dataTest, targetTrain, targetTest, floss, verbose, ...
43a6578d 85) {
afa67660
BA
86 args <- list(...)
87 task <- checkTask(args$task, targetTrain)
88 modPar <- checkModPar(args$gmodel, args$params)
89 loss <- checkLoss(args$loss, task)
17ea2f13 90 CV <- checkCV(args$CV)
afa67660
BA
91 s <- standardCV_core(
92 dataTrain, targetTrain, task, modPar$gmodel, modPar$params, loss, CV)
43a6578d
BA
93 if (verbose)
94 print(paste( "Parameter:", s$param ))
afa67660
BA
95 p <- s$model(dataTest)
96 err <- floss(p, targetTest)
43a6578d 97 if (verbose)
afa67660
BA
98 print(paste("error CV:", err))
99 invisible(err)
43a6578d
BA
100}
101
17ea2f13
BA
102#' agghoo_run
103#'
104#' Run and eval the agghoo procedure.
105#' Parameters are rather explicit except "floss", which corresponds to the
106#' "final" loss function, applied to compute the error on testing dataset.
107#'
108#' @export
43a6578d 109agghoo_run <- function(
17ea2f13 110 dataTrain, dataTest, targetTrain, targetTest, floss, verbose, ...
43a6578d 111) {
17ea2f13
BA
112 args <- list(...)
113 CV <- checkCV(args$CV)
114 # Must remove CV arg, or agghoo will complain "error: unused arg"
115 args$CV <- NULL
116 a <- do.call(agghoo, c(list(data=dataTrain, target=targetTrain), args))
43a6578d
BA
117 a$fit(CV)
118 if (verbose) {
119 print("Parameters:")
120 print(unlist(a$getParams()))
121 }
122 pa <- a$predict(dataTest)
123 err <- floss(pa, targetTest)
124 if (verbose)
125 print(paste("error agghoo:", err))
afa67660 126 invisible(err)
43a6578d
BA
127}
128
17ea2f13
BA
129#' compareTo
130#'
131#' Compare a list of learning methods (or run only one), on data/target.
132#'
133#' @param data Data matrix or data.frame
134#' @param target Target vector (generally)
135#' @param method_s Either a single function, or a list
136#' (examples: agghoo_run, standardCV_run)
137#' @param rseed Seed of the random generator (-1 means "random seed")
138#' @param floss Loss function to compute the error on testing dataset.
139#' @param verbose TRUE to request methods to be verbose.
140#' @param ... arguments passed to method_s function(s)
141#'
142#' @export
43a6578d 143compareTo <- function(
afa67660 144 data, target, method_s, rseed=-1, floss=NULL, verbose=TRUE, ...
43a6578d
BA
145) {
146 if (rseed >= 0)
147 set.seed(rseed)
148 n <- nrow(data)
149 test_indices <- sample( n, round(n / ifelse(n >= 500, 10, 5)) )
afa67660 150 d <- splitTrainTest(data, target, test_indices)
43a6578d
BA
151
152 # Set error function to be used on model outputs (not in core method)
afa67660 153 task <- checkTask(list(...)$task, target)
43a6578d
BA
154 if (is.null(floss)) {
155 floss <- function(y1, y2) {
156 ifelse(task == "classification", mean(y1 != y2), mean(abs(y1 - y2)))
157 }
158 }
159
160 # Run (and compare) all methods:
161 runOne <- function(o) {
17ea2f13 162 o(d$dataTrain, d$dataTest, d$targetTrain, d$targetTest, floss, verbose, ...)
43a6578d 163 }
afa67660 164 errors <- c()
43a6578d
BA
165 if (is.list(method_s))
166 errors <- sapply(method_s, runOne)
167 else if (is.function(method_s))
168 errors <- runOne(method_s)
43a6578d
BA
169 invisible(errors)
170}
171
17ea2f13
BA
172#' compareMulti
173#'
174#' Run compareTo N times in parallel.
175#'
176#' @inheritParams compareTo
177#' @param N Number of calls to method(s)
178#' @param nc Number of cores. Set to parallel::detectCores() if undefined.
179#' Set it to any value <=1 to say "no parallelism".
180#' @param verbose TRUE to print task numbers and "Errors:" in the end.
181#'
182#' @export
43a6578d 183compareMulti <- function(
17ea2f13 184 data, target, method_s, N=100, nc=NA, floss=NULL, verbose=TRUE, ...
43a6578d 185) {
afa67660 186 require(parallel)
43a6578d
BA
187 if (is.na(nc))
188 nc <- parallel::detectCores()
afa67660
BA
189
190 # "One" comparison for each method in method_s (list)
43a6578d 191 compareOne <- function(n) {
17ea2f13
BA
192 if (verbose)
193 print(n)
afa67660 194 compareTo(data, target, method_s, n, floss, verbose=FALSE, ...)
43a6578d 195 }
afa67660 196
43a6578d 197 errors <- if (nc >= 2) {
43a6578d
BA
198 parallel::mclapply(1:N, compareOne, mc.cores = nc)
199 } else {
200 lapply(1:N, compareOne)
201 }
17ea2f13
BA
202 if (verbose)
203 print("Errors:")
43a6578d
BA
204 Reduce('+', errors) / N
205}
17ea2f13
BA
206
207#' compareRange
208#'
209#' Run compareMulti on several values of the parameter V.
210#'
211#' @inheritParams compareMulti
212#' @param V_range Values of V to be tested.
213#'
214#' @export
215compareRange <- function(
a78bd1c0 216 data, target, method_s, N=100, nc=NA, floss=NULL, V_range=c(10,15,20), ...
17ea2f13
BA
217) {
218 args <- list(...)
219 # Avoid warnings if V is left unspecified:
220 CV <- suppressWarnings( checkCV(args$CV) )
221 errors <- lapply(V_range, function(V) {
222 args$CV$V <- V
223 do.call(compareMulti, c(list(data=data, target=target, method_s=method_s,
224 N=N, nc=nc, floss=floss, verbose=F), args))
225 })
226 print(paste(V_range, errors))
227}