X-Git-Url: https://git.auder.net/?p=agghoo.git;a=blobdiff_plain;f=R%2FcompareTo.R;fp=R%2FcompareTo.R;h=00e90a9ea7ddaac9ea3a24326ceb21d5eb0e01d0;hp=aa3a4e8b7f4bf68004831e598aa8fe561e34a148;hb=afa676609daba103e43d6d4654560ca4c1c9b38b;hpb=43a6578d444f388d72755e74c7eed74f3af638ec diff --git a/R/compareTo.R b/R/compareTo.R index aa3a4e8..00e90a9 100644 --- a/R/compareTo.R +++ b/R/compareTo.R @@ -1,86 +1,25 @@ -standardCV_core <- function(data, target, task = NULL, gmodel = NULL, params = NULL, - loss = NULL, CV = list(type = "MC", V = 10, test_size = 0.2, shuffle = TRUE) -) { - if (!is.null(task)) - task = match.arg(task, c("classification", "regression")) - if (is.character(gmodel)) - gmodel <- match.arg(gmodel, c("knn", "ppr", "rf", "tree")) - if (is.numeric(params) || is.character(params)) - params <- as.list(params) - if (is.null(task)) { - if (is.numeric(target)) - task = "regression" - else - task = "classification" - } - - if (is.null(loss)) { - loss <- function(y1, y2) { - if (task == "classification") { - if (is.null(dim(y1))) - mean(y1 != y2) - else { - if (!is.null(dim(y2))) - mean(rowSums(abs(y1 - y2))) - else { - y2 <- as.character(y2) - names <- colnames(y1) - positions <- list() - for (idx in seq_along(names)) - positions[[ names[idx] ]] <- idx - mean(vapply( - seq_along(y2), - function(idx) sum(abs(y1[idx,] - positions[[ y2[idx] ]])), - 0)) - } - } - } - else - mean(abs(y1 - y2)) - } - } - +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) - get_testIndices <- function(v, shuffle_inds) { - if (CV$type == "vfold") { - first_index = round((v-1) * n / CV$V) + 1 - last_index = round(v * n / CV$V) - test_indices = first_index:last_index - if (!is.null(shuffle_inds)) - test_indices <- shuffle_inds[test_indices] - } - else - test_indices = sample(n, round(n * CV$test_size)) - test_indices - } list_testinds <- list() for (v in seq_len(CV$V)) - list_testinds[[v]] <- get_testIndices(v, shuffle_inds) - + list_testinds[[v]] <- get_testIndices(n, CV, v, shuffle_inds) gmodel <- agghoo::Model$new(data, target, task, gmodel, params) best_error <- Inf best_model <- NULL for (p in seq_len(gmodel$nmodels)) { - error <- 0 - for (v in seq_len(CV$V)) { + error <- Reduce('+', lapply(seq_len(CV$V), function(v) { testIdx <- list_testinds[[v]] - dataHO <- data[-testIdx,] - testX <- data[testIdx,] - targetHO <- target[-testIdx] - testY <- target[testIdx] - if (!is.matrix(dataHO) && !is.data.frame(dataHO)) - dataHO <- as.matrix(dataHO) - if (!is.matrix(testX) && !is.data.frame(testX)) - testX <- as.matrix(testX) - model_pred <- gmodel$get(dataHO, targetHO, p) - prediction <- model_pred(testX) - error <- error + loss(prediction, testY) - } + 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) { - newModel <- list(model=model_pred, param=gmodel$getParam(p)) + newModel <- list(model=gmodel$get(data, target, p), + param=gmodel$getParam(p)) if (error == best_error) best_model[[length(best_model)+1]] <- newModel else { @@ -89,24 +28,30 @@ standardCV_core <- function(data, target, task = NULL, gmodel = NULL, params = N } } } +#browser() best_model[[ sample(length(best_model), 1) ]] } standardCV_run <- function( - dataTrain, dataTest, targetTrain, targetTest, verbose, CV, floss, ... + dataTrain, dataTest, targetTrain, targetTest, CV, floss, verbose, ... ) { - s <- standardCV_core(dataTrain, targetTrain, ...) + args <- list(...) + task <- checkTask(args$task, targetTrain) + modPar <- checkModPar(args$gmodel, args$params) + loss <- checkLoss(args$loss, task) + s <- standardCV_core( + dataTrain, targetTrain, task, modPar$gmodel, modPar$params, loss, CV) if (verbose) print(paste( "Parameter:", s$param )) - ps <- s$model(test) - err_s <- floss(ps, targetTest) + p <- s$model(dataTest) + err <- floss(p, targetTest) if (verbose) - print(paste("error CV:", err_s)) - invisible(c(errors, err_s)) + print(paste("error CV:", err)) + invisible(err) } agghoo_run <- function( - dataTrain, dataTest, targetTrain, targetTest, verbose, CV, floss, ... + dataTrain, dataTest, targetTrain, targetTest, CV, floss, verbose, ... ) { a <- agghoo(dataTrain, targetTrain, ...) a$fit(CV) @@ -118,27 +63,22 @@ agghoo_run <- function( err <- floss(pa, targetTest) if (verbose) print(paste("error agghoo:", err)) + invisible(err) } -# ... arguments passed to agghoo or any other procedure +# ... arguments passed to method_s (agghoo, standard CV or else) compareTo <- function( - data, target, rseed=-1, verbose=TRUE, floss=NULL, - CV = list(type = "MC", - V = 10, - test_size = 0.2, - shuffle = TRUE), - method_s=NULL, ... + data, target, method_s, rseed=-1, floss=NULL, verbose=TRUE, ... ) { if (rseed >= 0) set.seed(rseed) n <- nrow(data) test_indices <- sample( n, round(n / ifelse(n >= 500, 10, 5)) ) - trainData <- as.matrix(data[-test_indices,]) - trainTarget <- target[-test_indices] - testData <- as.matrix(data[test_indices,]) - testTarget <- target[test_indices] + d <- splitTrainTest(data, target, test_indices) + CV <- checkCV(list(...)$CV) # Set error function to be used on model outputs (not in core method) + task <- checkTask(list(...)$task, target) if (is.null(floss)) { floss <- function(y1, y2) { ifelse(task == "classification", mean(y1 != y2), mean(abs(y1 - y2))) @@ -147,34 +87,33 @@ compareTo <- function( # Run (and compare) all methods: runOne <- function(o) { - o(dataTrain, dataTest, targetTrain, targetTest, verbose, CV, floss, ...) + o(d$dataTrain, d$dataTest, d$targetTrain, d$targetTest, + CV, floss, verbose, ...) } + errors <- c() if (is.list(method_s)) errors <- sapply(method_s, runOne) else if (is.function(method_s)) errors <- runOne(method_s) - else - errors <- c() invisible(errors) } # Run compareTo N times in parallel +# ... : additional args to be passed to method_s compareMulti <- function( - data, target, N = 100, nc = NA, - CV = list(type = "MC", - V = 10, - test_size = 0.2, - shuffle = TRUE), - method_s=NULL, ... + data, target, method_s, N=100, nc=NA, floss=NULL, ... ) { + require(parallel) if (is.na(nc)) nc <- parallel::detectCores() + + # "One" comparison for each method in method_s (list) compareOne <- function(n) { print(n) - compareTo(data, target, n, verbose=FALSE, CV, method_s, ...) + compareTo(data, target, method_s, n, floss, verbose=FALSE, ...) } + errors <- if (nc >= 2) { - require(parallel) parallel::mclapply(1:N, compareOne, mc.cores = nc) } else { lapply(1:N, compareOne) @@ -182,5 +121,3 @@ compareMulti <- function( print("Errors:") Reduce('+', errors) / N } - -# TODO: unfinished !