From: devijvee Date: Fri, 5 Jun 2020 10:03:08 +0000 (+0200) Subject: plot fonctionne X-Git-Url: https://git.auder.net/?p=valse.git;a=commitdiff_plain;h=206dfd5d377fac6cbb60f3d19e07521749d120e1 plot fonctionne --- diff --git a/pkg/R/main.R b/pkg/R/main.R index aaf5fc7..129aa25 100644 --- a/pkg/R/main.R +++ b/pkg/R/main.R @@ -24,9 +24,8 @@ #' @param plot TRUE to plot the selected models after run #' #' @return -#' The selected model (except if 'DDSE' or 'DJump' is used to select a model and the collection of models -#' has less than 11 models, the function returns the collection as it can not select one - in that case, -#' it is adviced to use 'AIC' or 'BIC' to select a model) +#' The selected model (except if the collection of models +#' has less than 11 models, the function returns the collection as it can not select one using Capushe) #' #' @examples #' n = 50; m = 10; p = 5 @@ -36,7 +35,7 @@ #' data = generateXY(n, c(0.4,0.6), rep(0,p), beta, diag(0.5, p), diag(0.5, m)) #' X = data$X #' Y = data$Y -#' res = runValse(X, Y) +#' res = runValse(X, Y, kmax = 5) #' X <- matrix(runif(100), nrow=50) #' Y <- matrix(runif(100), nrow=50) #' res = runValse(X, Y) diff --git a/pkg/R/plot_valse.R b/pkg/R/plot_valse.R index febc65c..b47c7da 100644 --- a/pkg/R/plot_valse.R +++ b/pkg/R/plot_valse.R @@ -23,7 +23,7 @@ plot_valse <- function(X, Y, model, comp = FALSE, k1 = NA, k2 = NA) for (r in 1:K) { Melt <- melt(t((model$phi[, , r]))) - gReg[[r]] <- ggplot(data = Melt, aes(x = "Var1", y = "Var2", fill = "value")) + + gReg[[r]] <- ggplot(data = Melt, aes(x = Var1, y = Var2, fill = value)) + geom_tile() + scale_fill_gradient2(low = "blue", high = "red", mid = "white", midpoint = 0, space = "Lab") + ggtitle(paste("Regression matrices in cluster", r)) } @@ -35,11 +35,9 @@ plot_valse <- function(X, Y, model, comp = FALSE, k1 = NA, k2 = NA) if (is.na(k1) || is.na(k2)) print("k1 and k2 must be integers, representing the clusters you want to compare") Melt <- melt(t(model$phi[, , k1] - model$phi[, , k2])) - gDiff <- ggplot(data = Melt, aes(x = "Var1", y = "Var2", fill = "value")) - + geom_tile() - + scale_fill_gradient2(low = "blue", high = "red", mid = "white", midpoint = 0, - space = "Lab") - + ggtitle(paste("Difference between regression matrices in cluster", + gDiff <- ggplot(data = Melt, aes(x = Var1, y = Var2, fill = value)) + + geom_tile() + scale_fill_gradient2(low = "blue", high = "red", mid = "white", midpoint = 0, + space = "Lab") + ggtitle(paste("Difference between regression matrices in cluster", k1, "and", k2)) print(gDiff) } @@ -49,10 +47,9 @@ plot_valse <- function(X, Y, model, comp = FALSE, k1 = NA, k2 = NA) for (r in 1:K) matCov[, r] <- diag(model$rho[, , r]) MeltCov <- melt(matCov) - gCov <- ggplot(data = MeltCov, aes(x = "Var1", y = "Var2", fill = "value")) + geom_tile() - + scale_fill_gradient2(low = "blue", high = "red", mid = "white", midpoint = 0, - space = "Lab") - + ggtitle("Covariance matrices") + gCov <- ggplot(data = MeltCov, aes(x = Var1, y = Var2, fill = value)) + geom_tile() + + scale_fill_gradient2(low = "blue", high = "red", mid = "white", midpoint = 0, + space = "Lab") + ggtitle("Covariance matrices (diag., one row per cluster)") print(gCov) ### Proportions @@ -60,28 +57,8 @@ plot_valse <- function(X, Y, model, comp = FALSE, k1 = NA, k2 = NA) for (i in 1:n) gam2[i, ] <- c(model$proba[i, model$affec[i]], model$affec[i]) - bp <- ggplot(data.frame(gam2), aes(x = "X2", y = "X1", color = "X2", group = "X2")) - + geom_boxplot() - + theme(legend.position = "none") - + background_grid(major = "xy", minor = "none") + bp <- ggplot(data.frame(gam2), aes(x = X2, y = X1, color = X2, group = X2)) + geom_boxplot() + + theme(legend.position = "none") + background_grid(major = "xy", minor = "none") + + ggtitle("Assignment boxplot per cluster") print(bp) - - ### Mean in each cluster - XY <- cbind(X, Y) - XY_class <- list() - meanPerClass <- matrix(0, ncol = K, nrow = dim(XY)[2]) - for (r in 1:K) - { - XY_class[[r]] <- XY[model$affec == r, ] - if (sum(model$affec == r) == 1) { - meanPerClass[, r] <- XY_class[[r]] - } else { - meanPerClass[, r] <- apply(XY_class[[r]], 2, mean) - } - } - data <- data.frame(mean = as.vector(meanPerClass), - cluster = as.character(rep(1:K, each = dim(XY)[2])), time = rep(1:dim(XY)[2], K)) - g <- ggplot(data, aes(x = "time", y = "mean", group = "cluster", color = "cluster")) - print(g + geom_line(aes(linetype = "cluster", color = "cluster")) - + geom_point(aes(color = "cluster")) + ggtitle("Mean per cluster")) }