Commit | Line | Data |
---|---|---|
64cceb2e | 1 | utils::globalVariables(c("Var1","Var2","X1","X2","value")) #, package="valse") |
6382130f | 2 | |
0ba1b11c | 3 | #' Plot |
3453829e | 4 | #' |
6382130f | 5 | #' A function which plots relevant parameters. |
3453829e BA |
6 | #' |
7 | #' @param X matrix of covariates (of size n*p) | |
8 | #' @param Y matrix of responses (of size n*m) | |
9 | #' @param model the model constructed by valse procedure | |
1196a43d BA |
10 | #' @param comp TRUE to enable pairwise clusters comparison |
11 | #' @param k1 index of the first cluster to be compared | |
12 | #' @param k2 index of the second cluster to be compared | |
13 | #' | |
64cceb2e | 14 | #' @importFrom ggplot2 ggplot aes ggtitle geom_tile geom_line scale_fill_gradient2 geom_boxplot theme |
1196a43d BA |
15 | #' @importFrom cowplot background_grid |
16 | #' @importFrom reshape2 melt | |
3453829e | 17 | #' |
6382130f BA |
18 | #' @return No return value (only plotting). |
19 | #' | |
3453829e | 20 | #' @export |
3921ba9b | 21 | plot_valse <- function(X, Y, model, comp = FALSE, k1 = NA, k2 = NA) |
3453829e | 22 | { |
3921ba9b | 23 | n <- nrow(X) |
3453829e BA |
24 | K <- length(model$pi) |
25 | ## regression matrices | |
26 | gReg <- list() | |
64cceb2e BA |
27 | for (r in 1:K) { |
28 | Melt <- reshape2::melt(t((model$phi[, , r]))) | |
29 | gReg[[r]] <- ggplot2::ggplot(data = Melt, ggplot2::aes(x = Var1, y = Var2, fill = value)) + | |
30 | ggplot2::geom_tile() + ggplot2::scale_fill_gradient2(low = "blue", high = "red", mid = "white", | |
31 | midpoint = 0, space = "Lab") + ggplot2::ggtitle(paste("Regression matrices in cluster", r)) | |
3453829e BA |
32 | } |
33 | print(gReg) | |
34 | ||
35 | ## Differences between two clusters | |
64cceb2e | 36 | if (comp) { |
1196a43d | 37 | if (is.na(k1) || is.na(k2)) |
3453829e | 38 | print("k1 and k2 must be integers, representing the clusters you want to compare") |
64cceb2e BA |
39 | Melt <- reshape2::melt(t(model$phi[, , k1] - model$phi[, , k2])) |
40 | gDiff <- ggplot2::ggplot(data = Melt, ggplot2::aes(x = Var1, y = Var2, fill = value)) + | |
41 | ggplot2::geom_tile() + ggplot2::scale_fill_gradient2(low = "blue", high = "red", mid = "white", midpoint = 0, | |
42 | space = "Lab") + ggplot2::ggtitle(paste("Difference between regression matrices in cluster", | |
3453829e BA |
43 | k1, "and", k2)) |
44 | print(gDiff) | |
45 | } | |
46 | ||
47 | ### Covariance matrices | |
48 | matCov <- matrix(NA, nrow = dim(model$rho[, , 1])[1], ncol = K) | |
49 | for (r in 1:K) | |
50 | matCov[, r] <- diag(model$rho[, , r]) | |
64cceb2e BA |
51 | MeltCov <- reshape2::melt(matCov) |
52 | gCov <- ggplot2::ggplot(data = MeltCov, ggplot2::aes(x = Var1, y = Var2, fill = value)) + ggplot2::geom_tile() + | |
53 | ggplot2::scale_fill_gradient2(low = "blue", high = "red", mid = "white", midpoint = 0, | |
54 | space = "Lab") + ggplot2::ggtitle("Covariance matrices (diag., one row per cluster)") | |
3453829e BA |
55 | print(gCov) |
56 | ||
57 | ### Proportions | |
64cceb2e | 58 | gam2 <- matrix(NA, ncol = 2, nrow = n) |
3453829e BA |
59 | for (i in 1:n) |
60 | gam2[i, ] <- c(model$proba[i, model$affec[i]], model$affec[i]) | |
61 | ||
64cceb2e BA |
62 | bp <- ggplot2::ggplot(data.frame(gam2), ggplot2::aes(x = X2, y = X1, color = X2, group = X2)) + ggplot2::geom_boxplot() + |
63 | ggplot2::theme(legend.position = "none") + cowplot::background_grid(major = "xy", minor = "none") + | |
64 | ggplot2::ggtitle("Assignment boxplot per cluster") | |
3453829e | 65 | print(bp) |
3453829e | 66 | } |