+#' standardCV_core
+#'
+#' Cross-validation method, added here as an example.
+#' Parameters are described in ?agghoo and ?AgghooCV
+standardCV_core <- function(data, target, task, gmodel, params, loss, CV) {
+ n <- nrow(data)
+ shuffle_inds <- NULL
+ if (CV$type == "vfold" && CV$shuffle)
+ shuffle_inds <- sample(n, n)
+ list_testinds <- list()
+ for (v in seq_len(CV$V))
+ list_testinds[[v]] <- get_testIndices(n, CV, v, shuffle_inds)
+ gmodel <- agghoo::Model$new(data, target, task, gmodel, params)
+ best_error <- Inf
+ best_p <- NULL
+ for (p in seq_len(gmodel$nmodels)) {
+ error <- Reduce('+', lapply(seq_len(CV$V), function(v) {
+ testIdx <- list_testinds[[v]]
+ d <- splitTrainTest(data, target, testIdx)
+ model_pred <- gmodel$get(d$dataTrain, d$targetTrain, p)
+ prediction <- model_pred(d$dataTest)
+ loss(prediction, d$targetTest)
+ }) )
+ if (error <= best_error) {
+ if (error == best_error)
+ best_p[[length(best_p)+1]] <- p
+ else {
+ best_p <- list(p)
+ best_error <- error
+ }
+ }
+ }
+ chosenP <- best_p[[ sample(length(best_p), 1) ]]
+ list(model=gmodel$get(data, target, chosenP), param=gmodel$getParam(chosenP))
+}
+
#' CVvoting_core
#'
#' "voting" cross-validation method, added here as an example.
shuffle_inds <- NULL
if (CV$type == "vfold" && CV$shuffle)
shuffle_inds <- sample(n, n)
- bestP <- rep(0, gmodel$nmodels)
gmodel <- agghoo::Model$new(data, target, task, gmodel, params)
+ bestP <- rep(0, gmodel$nmodels)
for (v in seq_len(CV$V)) {
test_indices <- get_testIndices(n, CV, v, shuffle_inds)
d <- splitTrainTest(data, target, test_indices)
list(model=gmodel$get(data, target, chosenP), param=gmodel$getParam(chosenP))
}
-#' standardCV_core
-#'
-#' Cross-validation method, added here as an example.
-#' Parameters are described in ?agghoo and ?AgghooCV
-standardCV_core <- function(data, target, task, gmodel, params, loss, CV) {
- n <- nrow(data)
- shuffle_inds <- NULL
- if (CV$type == "vfold" && CV$shuffle)
- shuffle_inds <- sample(n, n)
- list_testinds <- list()
- for (v in seq_len(CV$V))
- list_testinds[[v]] <- get_testIndices(n, CV, v, shuffle_inds)
- gmodel <- agghoo::Model$new(data, target, task, gmodel, params)
- best_error <- Inf
- best_p <- NULL
- for (p in seq_len(gmodel$nmodels)) {
- error <- Reduce('+', lapply(seq_len(CV$V), function(v) {
- testIdx <- list_testinds[[v]]
- d <- splitTrainTest(data, target, testIdx)
- model_pred <- gmodel$get(d$dataTrain, d$targetTrain, p)
- prediction <- model_pred(d$dataTest)
- loss(prediction, d$targetTest)
- }) )
- if (error <= best_error) {
- if (error == best_error)
- best_p[[length(best_p)+1]] <- p
- else {
- best_p <- list(p)
- best_error <- error
- }
- }
- }
- chosenP <- best_p[[ sample(length(best_p), 1) ]]
- list(model=gmodel$get(data, target, chosenP), param=gmodel$getParam(chosenP))
-}
-
#' standardCV_run
#'
#' Run and eval the standard cross-validation procedure.
invisible(err)
}
+#' CVvoting_run
+#'
+#' Run and eval the voting cross-validation procedure.
+#' Parameters are rather explicit except "floss", which corresponds to the
+#' "final" loss function, applied to compute the error on testing dataset.
+#'
+#' @export
+CVvoting_run <- function(
+ dataTrain, dataTest, targetTrain, targetTest, floss, verbose, ...
+) {
+ args <- list(...)
+ task <- checkTask(args$task, targetTrain)
+ modPar <- checkModPar(args$gmodel, args$params)
+ loss <- checkLoss(args$loss, task)
+ CV <- checkCV(args$CV)
+ s <- CVvoting_core(
+ dataTrain, targetTrain, task, modPar$gmodel, modPar$params, loss, CV)
+ if (verbose)
+ print(paste( "Parameter:", s$param ))
+ p <- s$model(dataTest)
+ err <- floss(p, targetTest)
+ if (verbose)
+ print(paste("error CV:", err))
+ invisible(err)
+}
+
#' agghoo_run
#'
#' Run and eval the agghoo procedure.