... | ... |
@@ -50,6 +50,7 @@ export(plotDimReduceFeature) |
50 | 50 |
export(plotDimReduceGrid) |
51 | 51 |
export(plotDimReduceModule) |
52 | 52 |
export(plotGridSearchPerplexity) |
53 |
+export(plotGridSearchPerplexityDiff) |
|
53 | 54 |
export(plotHeatmap) |
54 | 55 |
export(plotMarkerDendro) |
55 | 56 |
export(plotMarkerHeatmap) |
... | ... |
@@ -106,6 +107,7 @@ exportMethods(plotDimReduceFeature) |
106 | 107 |
exportMethods(plotDimReduceGrid) |
107 | 108 |
exportMethods(plotDimReduceModule) |
108 | 109 |
exportMethods(plotGridSearchPerplexity) |
110 |
+exportMethods(plotGridSearchPerplexityDiff) |
|
109 | 111 |
exportMethods(recursiveSplitCell) |
110 | 112 |
exportMethods(recursiveSplitModule) |
111 | 113 |
exportMethods(resList) |
... | ... |
@@ -413,14 +413,15 @@ setMethod("celdaGridSearch", |
413 | 413 |
#' @param x Can be one of |
414 | 414 |
#' \itemize{ |
415 | 415 |
#' \item A \linkS4class{SingleCellExperiment} object returned from |
416 |
-#' \code{celdaGridSearch}. Must contain a list named |
|
416 |
+#' \code{celdaGridSearch}, \code{recursiveSplitModule}, |
|
417 |
+#' or \code{recursiveSplitCell}. Must contain a list named |
|
417 | 418 |
#' \code{"celda_grid_search"} in \code{metadata(x)}. |
418 | 419 |
#' \item celdaList object.} |
419 | 420 |
#' @param params List. List of parameters used to subset the matching celda |
420 | 421 |
#' models in list \code{"celda_grid_search"} in \code{metadata(x)}. |
421 | 422 |
#' @param useAssay A string specifying which \code{assay} |
422 | 423 |
#' slot to use if \code{x} is a |
423 |
-#' \link[SingleCellExperiment]{SingleCellExperiment} object. Default "counts". |
|
424 |
+#' \linkS4class{SingleCellExperiment} object. Default "counts". |
|
424 | 425 |
#' @return One of |
425 | 426 |
#' \itemize{ |
426 | 427 |
#' \item A new \linkS4class{SingleCellExperiment} object containing |
... | ... |
@@ -472,19 +473,16 @@ setMethod("subsetCeldaList", |
472 | 473 |
subset(newRunParams, newRunParams[, i] %in% params[[i]]) |
473 | 474 |
|
474 | 475 |
if (nrow(newRunParams) == 0) { |
475 |
- stop( |
|
476 |
- "No runs matched the criteria given in 'params'. Check", |
|
476 |
+ stop("No runs matched the criteria given in 'params'. Check", |
|
477 | 477 |
" 'runParams(x)' for complete list of parameters used", |
478 |
- " to generate 'x'." |
|
479 |
- ) |
|
478 |
+ " to generate 'x'.") |
|
480 | 479 |
} |
481 | 480 |
} |
482 | 481 |
|
483 | 482 |
## Get index of selected models, subset celdaList, and return |
484 | 483 |
ix <- match(newRunParams$index, runParams(x)$index) |
485 | 484 |
if (length(ix) == 1) { |
486 |
- x <- celdatosce(resList(x)[[ix]], |
|
487 |
- SummarizedExperiment::assay(x, i = useAssay)) |
|
485 |
+ x <- .subsetCeldaListSCE(x, ix) |
|
488 | 486 |
} else { |
489 | 487 |
x@metadata$celda_grid_search@runParams <- |
490 | 488 |
as.data.frame(newRunParams) |
... | ... |
@@ -543,9 +541,13 @@ setMethod("subsetCeldaList", |
543 | 541 |
#' @description Select the chain with the best log likelihood for each |
544 | 542 |
#' combination of tested parameters from a \code{SCE} object gererated by |
545 | 543 |
#' \link{celdaGridSearch} or from a \code{celdaList} object. |
546 |
-#' @param x Object of class \linkS4class{SingleCellExperiment} or |
|
547 |
-#' \code{celdaList}. An object containing celda |
|
548 |
-#' models returned from \link{celdaGridSearch}. |
|
544 |
+#' @param x Can be one of |
|
545 |
+#' \itemize{ |
|
546 |
+#' \item A \linkS4class{SingleCellExperiment} object returned from |
|
547 |
+#' \code{celdaGridSearch}, \code{recursiveSplitModule}, |
|
548 |
+#' or \code{recursiveSplitCell}. Must contain a list named |
|
549 |
+#' \code{"celda_grid_search"} in \code{metadata(x)}. |
|
550 |
+#' \item celdaList object.} |
|
549 | 551 |
#' @param asList \code{TRUE} or \code{FALSE}. Whether to return the |
550 | 552 |
#' best model as a |
551 | 553 |
#' \code{celdaList} object or not. If \code{FALSE}, return the best model as a |
... | ... |
@@ -595,8 +597,7 @@ setMethod("selectBestModel", signature(x = "SingleCellExperiment"), |
595 | 597 |
|
596 | 598 |
ix <- match(newRunParams$index, runParams$index) |
597 | 599 |
if (nrow(newRunParams) == 1 & !asList) { |
598 |
- x <- celdatosce(resList(x)[[ix]], |
|
599 |
- SummarizedExperiment::assay(x, i = useAssay)) |
|
600 |
+ x <- .subsetCeldaListSCE(x, ix) |
|
600 | 601 |
} else { |
601 | 602 |
x@metadata$celda_grid_search@runParams <- |
602 | 603 |
as.data.frame(newRunParams) |
... | ... |
@@ -670,3 +671,60 @@ setMethod("selectBestModel", signature(x = "celdaList"), |
670 | 671 |
logfilePrefix = logfilePrefix) |
671 | 672 |
return(sce) |
672 | 673 |
} |
674 |
+ |
|
675 |
+ |
|
676 |
+.subsetCeldaListSCE <- function (x, ix) { |
|
677 |
+ cgsparam <- x@metadata$celda_grid_search@celdaGridSearchParameters |
|
678 |
+ if (cgsparam$model == "celda_c") { |
|
679 |
+ x <- .createSCEceldaC(celdaCMod = resList(x)[[ix]], |
|
680 |
+ sce = x, |
|
681 |
+ xClass = cgsparam$xClass, |
|
682 |
+ useAssay = cgsparam$useAssay, |
|
683 |
+ algorithm = cgsparam$algorithm, |
|
684 |
+ stopIter = cgsparam$stopIter, |
|
685 |
+ maxIter = cgsparam$maxIter, |
|
686 |
+ splitOnIter = cgsparam$splitOnIter, |
|
687 |
+ splitOnLast = cgsparam$splitOnLast, |
|
688 |
+ nchains = cgsparam$nchains, |
|
689 |
+ zInitialize = cgsparamp[["zInitialize"]], |
|
690 |
+ zInit = cgsparamp[["zInit"]], |
|
691 |
+ logfile = cgsparamp$logfile, |
|
692 |
+ verbose = cgsparamp$verbose) |
|
693 |
+ } else if (cgsparam$model == "celda_G") { |
|
694 |
+ x <- .createSCEceldaG(celdaGMod = resList(x)[[ix]], |
|
695 |
+ sce = x, |
|
696 |
+ xClass = cgsparam$xClass, |
|
697 |
+ useAssay = cgsparam$useAssay, |
|
698 |
+ stopIter = cgsparam$stopIter, |
|
699 |
+ maxIter = cgsparam$maxIter, |
|
700 |
+ splitOnIter = cgsparam$splitOnIter, |
|
701 |
+ splitOnLast = cgsparam$splitOnLast, |
|
702 |
+ nchains = cgsparam$nchains, |
|
703 |
+ yInitialize = cgsparam[["yInitialize"]], |
|
704 |
+ yInit = cgsparam[["yInit"]], |
|
705 |
+ logfile = cgsparam$logfile, |
|
706 |
+ verbose = cgsparam$verbose) |
|
707 |
+ } else if (cgsparam$model == "celda_CG") { |
|
708 |
+ x <- .createSCEceldaCG(celdaCGMod = resList(x)[[ix]], |
|
709 |
+ sce = x, |
|
710 |
+ xClass = cgsparam$xClass, |
|
711 |
+ useAssay = cgsparam$useAssay, |
|
712 |
+ algorithm = cgsparam$algorithm, |
|
713 |
+ stopIter = cgsparam$stopIter, |
|
714 |
+ maxIter = cgsparam$maxIter, |
|
715 |
+ splitOnIter = cgsparam$splitOnIter, |
|
716 |
+ splitOnLast = cgsparam$splitOnLast, |
|
717 |
+ nchains = cgsparam$nchains, |
|
718 |
+ zInitialize = cgsparam[["zInitialize"]], |
|
719 |
+ yInitialize = cgsparam[["yInitialize"]], |
|
720 |
+ zInit = cgsparam[["zInit"]], |
|
721 |
+ yInit = cgsparam[["yInit"]], |
|
722 |
+ logfile = cgsparam$logfile, |
|
723 |
+ verbose = cgsparam$verbose) |
|
724 |
+ } else { |
|
725 |
+ stop("S4Vectors::metadata(X)$celda_grid_search@", |
|
726 |
+ "celdaGridSearchParameters$model must be", |
|
727 |
+ " one of 'celda_C', 'celda_G', or 'celda_CG'") |
|
728 |
+ } |
|
729 |
+ return(x) |
|
730 |
+} |
... | ... |
@@ -132,8 +132,13 @@ setMethod("resamplePerplexity", |
132 | 132 |
#' @title Visualize perplexity of a list of celda models |
133 | 133 |
#' @description Visualize perplexity of every model in a celdaList, by unique |
134 | 134 |
#' K/L combinations |
135 |
-#' @param x A \linkS4class{SingleCellExperiment} object returned from |
|
136 |
-#' \link{celdaGridSearch} or an object of class \code{celdaList}. |
|
135 |
+#' @param x Can be one of |
|
136 |
+#' \itemize{ |
|
137 |
+#' \item A \linkS4class{SingleCellExperiment} object returned from |
|
138 |
+#' \code{celdaGridSearch}, \code{recursiveSplitModule}, |
|
139 |
+#' or \code{recursiveSplitCell}. Must contain a list named |
|
140 |
+#' \code{"celda_grid_search"} in \code{metadata(x)}. |
|
141 |
+#' \item celdaList object.} |
|
137 | 142 |
#' @param sep Numeric. Breaks in the x axis of the resulting plot. |
138 | 143 |
#' @return A ggplot plot object showing perplexity as a function of clustering |
139 | 144 |
#' parameters. |
... | ... |
@@ -379,3 +384,266 @@ setMethod("plotGridSearchPerplexity", |
379 | 384 |
}, integer(nrow(countMatrix))) |
380 | 385 |
return(resample) |
381 | 386 |
} |
387 |
+ |
|
388 |
+ |
|
389 |
+#' @title Visualize perplexity differences of a list of celda models |
|
390 |
+#' @description Visualize perplexity differences of every model in a celdaList, |
|
391 |
+#' by unique K/L combinations. |
|
392 |
+#' @param x Can be one of |
|
393 |
+#' \itemize{ |
|
394 |
+#' \item A \linkS4class{SingleCellExperiment} object returned from |
|
395 |
+#' \code{celdaGridSearch}, \code{recursiveSplitModule}, |
|
396 |
+#' or \code{recursiveSplitCell}. Must contain a list named |
|
397 |
+#' \code{"celda_grid_search"} in \code{metadata(x)}. |
|
398 |
+#' \item celdaList object.} |
|
399 |
+#' @param sep Numeric. Breaks in the x axis of the resulting plot. |
|
400 |
+#' @return A ggplot plot object showing perplexity diferences as a function of |
|
401 |
+#' clustering parameters. |
|
402 |
+#' @export |
|
403 |
+setGeneric("plotGridSearchPerplexityDiff", function(x, ...) { |
|
404 |
+ standardGeneric("plotGridSearchPerplexityDiff")}) |
|
405 |
+ |
|
406 |
+ |
|
407 |
+#' @rdname plotGridSearchPerplexityDiff |
|
408 |
+#' @examples |
|
409 |
+#' data(sceCeldaCGGridSearch) |
|
410 |
+#' sce <- resamplePerplexity(sceCeldaCGGridSearch) |
|
411 |
+#' plotGridSearchPerplexityDiff(sce) |
|
412 |
+#' @export |
|
413 |
+setMethod("plotGridSearchPerplexityDiff", |
|
414 |
+ signature(x = "SingleCellExperiment"), |
|
415 |
+ function(x, sep = 1) { |
|
416 |
+ model <- x@metadata$celda_grid_search@celdaGridSearchParameters$model |
|
417 |
+ celdaList <- S4Vectors::metadata(x)$celda_grid_search |
|
418 |
+ |
|
419 |
+ if (model == "celda_c") { |
|
420 |
+ g <- .plotGridSearchPerplexityDiffC(celdaList, sep) |
|
421 |
+ } else if (model == "celda_G") { |
|
422 |
+ g <- .plotGridSearchPerplexityDiffG(celdaList, sep) |
|
423 |
+ } else if (model == "celda_CG") { |
|
424 |
+ g <- .plotGridSearchPerplexityDiffCG(celdaList, sep) |
|
425 |
+ } else { |
|
426 |
+ stop("S4Vectors::metadata(X)$celda_grid_search@", |
|
427 |
+ "celdaGridSearchParameters$model must be", |
|
428 |
+ " one of 'celda_C', 'celda_G', or 'celda_CG'") |
|
429 |
+ } |
|
430 |
+ return(g) |
|
431 |
+ } |
|
432 |
+) |
|
433 |
+ |
|
434 |
+ |
|
435 |
+#' @rdname plotGridSearchPerplexityDiff |
|
436 |
+#' @examples |
|
437 |
+#' data(celdaCGSim, celdaCGGridSearchRes) |
|
438 |
+#' ## Run various combinations of parameters with 'celdaGridSearch' |
|
439 |
+#' celdaCGGridSearchRes <- resamplePerplexity( |
|
440 |
+#' celdaCGSim$counts, |
|
441 |
+#' celdaCGGridSearchRes) |
|
442 |
+#' plotGridSearchPerplexityDiff(celdaCGGridSearchRes) |
|
443 |
+#' @export |
|
444 |
+setMethod("plotGridSearchPerplexityDiff", |
|
445 |
+ signature(x = "celdaList"), |
|
446 |
+ function(x, sep = 1) { |
|
447 |
+ g <- do.call(paste0(".plotGridSearchPerplexityDiff", |
|
448 |
+ unlist(strsplit(as.character(class(resList(x)[[1]])), "_"))[[2]]), |
|
449 |
+ args = list(x, sep)) |
|
450 |
+ return(g) |
|
451 |
+ } |
|
452 |
+) |
|
453 |
+ |
|
454 |
+ |
|
455 |
+.plotGridSearchPerplexityDiffCG <- function(celdaList, sep) { |
|
456 |
+ if (!all(c("K", "L") %in% colnames(runParams(celdaList)))) { |
|
457 |
+ stop("runParams(celdaList) needs K and L columns.") |
|
458 |
+ } |
|
459 |
+ if (is.null(celdaPerplexity(celdaList))) { |
|
460 |
+ stop("No perplexity measurements available. First run", |
|
461 |
+ " 'resamplePerplexity' with celdaList object.") |
|
462 |
+ } |
|
463 |
+ |
|
464 |
+ ix1 <- rep(seq(nrow(celdaPerplexity(celdaList))), |
|
465 |
+ each = ncol(celdaPerplexity(celdaList))) |
|
466 |
+ ix2 <- rep(seq(ncol(celdaPerplexity(celdaList))), |
|
467 |
+ nrow(celdaPerplexity(celdaList))) |
|
468 |
+ dt <- data.table::data.table(runParams(celdaList)[ix1, ], |
|
469 |
+ perplexity = celdaPerplexity(celdaList)[cbind(ix1, ix2)]) |
|
470 |
+ dt$K <- as.factor(dt$K) |
|
471 |
+ dt$L <- as.factor(dt$L) |
|
472 |
+ |
|
473 |
+ if (nlevels(dt$K) > 1) { |
|
474 |
+ for (i in seq(nlevels(dt$L))) { |
|
475 |
+ for (j in seq(2, nlevels(dt$K))) { |
|
476 |
+ p1 <- dt[K == levels(dt$K)[j - 1] & L == levels(dt$L)[i], |
|
477 |
+ perplexity] |
|
478 |
+ p2 <- dt[K == levels(dt$K)[j] & L == levels(dt$L)[i], |
|
479 |
+ perplexity] |
|
480 |
+ dt[K == levels(dt$K)[j] & L == levels(dt$L)[i], |
|
481 |
+ perpdiffK := p2 - p1] |
|
482 |
+ } |
|
483 |
+ } |
|
484 |
+ |
|
485 |
+ diffMeansByK <- data.table::data.table(stats::aggregate(dt$perpdiffK, |
|
486 |
+ by = list(dt$K, dt$L), |
|
487 |
+ FUN = mean)) |
|
488 |
+ colnames(diffMeansByK) <- c("K", "L", "meanperpdiffK") |
|
489 |
+ diffMeansByK$K <- as.factor(diffMeansByK$K) |
|
490 |
+ diffMeansByK$L <- as.factor(diffMeansByK$L) |
|
491 |
+ |
|
492 |
+ plot <- ggplot2::ggplot(dt[!is.na(perpdiffK), ], |
|
493 |
+ ggplot2::aes_string(x = "K", |
|
494 |
+ y = "perpdiffK")) + |
|
495 |
+ ggplot2::geom_jitter(height = 0, width = 0.1, |
|
496 |
+ ggplot2::aes_string(color = "L")) + |
|
497 |
+ ggplot2::scale_color_discrete(name = "L") + |
|
498 |
+ ggplot2::geom_path(data = diffMeansByK[!is.na(meanperpdiffK), ], |
|
499 |
+ ggplot2::aes_string( |
|
500 |
+ x = "K", |
|
501 |
+ y = "meanperpdiffK", group = "L", color = "L")) + |
|
502 |
+ ggplot2::ylab("Perplexity difference compared to previous K") + |
|
503 |
+ ggplot2::xlab("K") + |
|
504 |
+ ggplot2::scale_x_discrete(breaks = seq(as.integer(levels(dt$K))[2], |
|
505 |
+ max(as.integer(levels(dt$K))), sep)) + |
|
506 |
+ ggplot2::theme_bw() |
|
507 |
+ } else if (nlevels(dt$L) > 1) { |
|
508 |
+ for (i in seq(nlevels(dt$K))) { |
|
509 |
+ for (j in seq(2, nlevels(dt$L))) { |
|
510 |
+ p1 <- dt[K == levels(dt$K)[i] & L == levels(dt$L)[j - 1], |
|
511 |
+ perplexity] |
|
512 |
+ p2 <- dt[K == levels(dt$K)[i] & L == levels(dt$L)[j], |
|
513 |
+ perplexity] |
|
514 |
+ dt[K == levels(dt$K)[i] & L == levels(dt$L)[j], |
|
515 |
+ perpdiffL := p2 - p1] |
|
516 |
+ } |
|
517 |
+ } |
|
518 |
+ |
|
519 |
+ diffMeansByL <- data.table::data.table(stats::aggregate(dt$perpdiffL, |
|
520 |
+ by = list(dt$K, dt$L), |
|
521 |
+ FUN = mean)) |
|
522 |
+ colnames(diffMeansByL) <- c("K", "L", "meanperpdiffL") |
|
523 |
+ diffMeansByL$K <- as.factor(diffMeansByL$K) |
|
524 |
+ diffMeansByK$L <- as.factor(diffMeansByL$L) |
|
525 |
+ |
|
526 |
+ plot <- ggplot2::ggplot(dt[!is.na(perpdiffL), ], |
|
527 |
+ ggplot2::aes_string(x = "L", y = "perpdiffL")) + |
|
528 |
+ ggplot2::geom_jitter(height = 0, width = 0.1, |
|
529 |
+ ggplot2::aes_string(color = "K")) + |
|
530 |
+ ggplot2::scale_color_discrete(name = "K") + |
|
531 |
+ ggplot2::geom_path( |
|
532 |
+ data = diffMeansByL[!is.na(meanperpdiffL), ], |
|
533 |
+ ggplot2::aes_string( |
|
534 |
+ x = "L", y = "meanperpdiffL", group = "K", color = "K")) + |
|
535 |
+ ggplot2::ylab("Perplexity difference compared to previous L") + |
|
536 |
+ ggplot2::xlab("L") + |
|
537 |
+ ggplot2::scale_x_discrete(breaks = seq(as.integer(levels(dt$L))[2], |
|
538 |
+ max(as.integer(levels(dt$L))), sep)) + |
|
539 |
+ ggplot2::theme_bw() |
|
540 |
+ } else { |
|
541 |
+ stop("Only one combination of K and L available! Unable to calculate", |
|
542 |
+ " perplexity differences.") |
|
543 |
+ } |
|
544 |
+ |
|
545 |
+ return(plot) |
|
546 |
+} |
|
547 |
+ |
|
548 |
+ |
|
549 |
+.plotGridSearchPerplexityceldaC <- function(celdaList, sep) { |
|
550 |
+ if (!all(c("K") %in% colnames(runParams(celdaList)))) { |
|
551 |
+ stop("runParams(celdaList) needs the column K.") |
|
552 |
+ } |
|
553 |
+ if (is.null(celdaPerplexity(celdaList))) { |
|
554 |
+ stop( |
|
555 |
+ "No perplexity measurements available. First run", |
|
556 |
+ " 'resamplePerplexity' with celdaList object." |
|
557 |
+ ) |
|
558 |
+ } |
|
559 |
+ |
|
560 |
+ ix1 <- rep(seq(nrow(celdaPerplexity(celdaList))), |
|
561 |
+ each = ncol(celdaPerplexity(celdaList))) |
|
562 |
+ ix2 <- rep(seq(ncol(celdaPerplexity(celdaList))), |
|
563 |
+ nrow(celdaPerplexity(celdaList))) |
|
564 |
+ dt <- data.table::data.table(runParams(celdaList)[ix1, ], |
|
565 |
+ perplexity = celdaPerplexity(celdaList)[cbind(ix1, ix2)]) |
|
566 |
+ dt$K <- as.factor(dt$K) |
|
567 |
+ |
|
568 |
+ if (nlevels(dt$K) > 1) { |
|
569 |
+ for (i in seq(2, nlevels(dt$K))) { |
|
570 |
+ p1 <- dt[K == levels(dt$K)[i - 1], perplexity] |
|
571 |
+ p2 <- dt[K == levels(dt$K)[i], perplexity] |
|
572 |
+ dt[K == levels(dt$K)[i], perpdiffK := p2 - p1] |
|
573 |
+ } |
|
574 |
+ |
|
575 |
+ diffMeansByK <- data.table::data.table(stats::aggregate(dt$perpdiffK, |
|
576 |
+ by = list(dt$K), |
|
577 |
+ FUN = mean)) |
|
578 |
+ colnames(diffMeansByK) <- c("K", "meanperpdiffK") |
|
579 |
+ diffMeansByK$K <- as.factor(diffMeansByK$K) |
|
580 |
+ |
|
581 |
+ plot <- ggplot2::ggplot(dt[!is.na(perpdiffK), ], |
|
582 |
+ ggplot2::aes_string(x = "K", |
|
583 |
+ y = "perpdiffK")) + |
|
584 |
+ ggplot2::geom_jitter(height = 0, width = 0.1) + |
|
585 |
+ ggplot2::geom_path(data = diffMeansByK[!is.na(meanperpdiffK), ], |
|
586 |
+ ggplot2::aes_string(x = "K", y = "meanperpdiffK", group = 1)) + |
|
587 |
+ ggplot2::ylab("Perplexity difference compared to previous K") + |
|
588 |
+ ggplot2::xlab("K") + |
|
589 |
+ ggplot2::scale_x_discrete(breaks = seq(as.integer(levels(dt$K))[2], |
|
590 |
+ max(as.integer(levels(dt$K))), sep)) + |
|
591 |
+ ggplot2::theme_bw() |
|
592 |
+ } else { |
|
593 |
+ stop("Only one unique K value available! Unable to calculate", |
|
594 |
+ " perplexity differences.") |
|
595 |
+ } |
|
596 |
+ return(plot) |
|
597 |
+} |
|
598 |
+ |
|
599 |
+ |
|
600 |
+.plotGridSearchPerplexityceldaG <- function(celdaList, sep) { |
|
601 |
+ if (!all(c("L") %in% colnames(runParams(celdaList)))) { |
|
602 |
+ stop("runParams(celdaList) needs the column L.") |
|
603 |
+ } |
|
604 |
+ if (length(celdaPerplexity(celdaList)) == 0) { |
|
605 |
+ stop( |
|
606 |
+ "No perplexity measurements available. First run", |
|
607 |
+ " 'resamplePerplexity' with celdaList object." |
|
608 |
+ ) |
|
609 |
+ } |
|
610 |
+ |
|
611 |
+ ix1 <- rep(seq(nrow(celdaPerplexity(celdaList))), |
|
612 |
+ each = ncol(celdaPerplexity(celdaList))) |
|
613 |
+ ix2 <- rep(seq(ncol(celdaPerplexity(celdaList))), |
|
614 |
+ nrow(celdaPerplexity(celdaList))) |
|
615 |
+ dt <- data.table::data.table(runParams(celdaList)[ix1, ], |
|
616 |
+ perplexity = celdaPerplexity(celdaList)[cbind(ix1, ix2)]) |
|
617 |
+ dt$L <- as.factor(dt$L) |
|
618 |
+ |
|
619 |
+ if (nlevels(dt$L) > 1) { |
|
620 |
+ for (i in seq(2, nlevels(dt$L))) { |
|
621 |
+ p1 <- dt[L == levels(dt$L)[i - 1], perplexity] |
|
622 |
+ p2 <- dt[L == levels(dt$L)[i], perplexity] |
|
623 |
+ dt[L == levels(dt$L)[i], perpdiffL := p2 - p1] |
|
624 |
+ } |
|
625 |
+ |
|
626 |
+ diffMeansByL <- data.table::data.table(stats::aggregate(dt$perpdiffL, |
|
627 |
+ by = list(dt$L), |
|
628 |
+ FUN = mean)) |
|
629 |
+ colnames(diffMeansByL) <- c("L", "meanperpdiffL") |
|
630 |
+ diffMeansByL$L <- as.factor(diffMeansByL$L) |
|
631 |
+ |
|
632 |
+ plot <- ggplot2::ggplot(dt[!is.na(perpdiffL), ], |
|
633 |
+ ggplot2::aes_string(x = "L", |
|
634 |
+ y = "perpdiffL")) + |
|
635 |
+ ggplot2::geom_jitter(height = 0, width = 0.1) + |
|
636 |
+ ggplot2::geom_path(data = diffMeansByL[!is.na(meanperpdiffL), ], |
|
637 |
+ ggplot2::aes_string(x = "L", y = "meanperpdiffL", group = 1)) + |
|
638 |
+ ggplot2::ylab("Perplexity difference compared to previous L") + |
|
639 |
+ ggplot2::xlab("L") + |
|
640 |
+ ggplot2::scale_x_discrete(breaks = seq(as.integer(levels(dt$L))[2], |
|
641 |
+ max(as.integer(levels(dt$L))), sep)) + |
|
642 |
+ ggplot2::theme_bw() |
|
643 |
+ } else { |
|
644 |
+ stop("Only one unique L value available! Unable to calculate", |
|
645 |
+ " perplexity differences.") |
|
646 |
+ } |
|
647 |
+ return(plot) |
|
648 |
+} |
|
649 |
+ |
... | ... |
@@ -13,8 +13,13 @@ plotGridSearchPerplexity(x, ...) |
13 | 13 |
\S4method{plotGridSearchPerplexity}{celdaList}(x, sep = 1) |
14 | 14 |
} |
15 | 15 |
\arguments{ |
16 |
-\item{x}{A \linkS4class{SingleCellExperiment} object returned from |
|
17 |
-\link{celdaGridSearch} or an object of class \code{celdaList}.} |
|
16 |
+\item{x}{Can be one of |
|
17 |
+\itemize{ |
|
18 |
+ \item A \linkS4class{SingleCellExperiment} object returned from |
|
19 |
+ \code{celdaGridSearch}, \code{recursiveSplitModule}, |
|
20 |
+ or \code{recursiveSplitCell}. Must contain a list named |
|
21 |
+ \code{"celda_grid_search"} in \code{metadata(x)}. |
|
22 |
+ \item celdaList object.}} |
|
18 | 23 |
|
19 | 24 |
\item{sep}{Numeric. Breaks in the x axis of the resulting plot.} |
20 | 25 |
} |
21 | 26 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,44 @@ |
1 |
+% Generated by roxygen2: do not edit by hand |
|
2 |
+% Please edit documentation in R/model_performance.R |
|
3 |
+\name{plotGridSearchPerplexityDiff} |
|
4 |
+\alias{plotGridSearchPerplexityDiff} |
|
5 |
+\alias{plotGridSearchPerplexityDiff,SingleCellExperiment-method} |
|
6 |
+\alias{plotGridSearchPerplexityDiff,celdaList-method} |
|
7 |
+\title{Visualize perplexity differences of a list of celda models} |
|
8 |
+\usage{ |
|
9 |
+plotGridSearchPerplexityDiff(x, ...) |
|
10 |
+ |
|
11 |
+\S4method{plotGridSearchPerplexityDiff}{SingleCellExperiment}(x, sep = 1) |
|
12 |
+ |
|
13 |
+\S4method{plotGridSearchPerplexityDiff}{celdaList}(x, sep = 1) |
|
14 |
+} |
|
15 |
+\arguments{ |
|
16 |
+\item{x}{Can be one of |
|
17 |
+\itemize{ |
|
18 |
+ \item A \linkS4class{SingleCellExperiment} object returned from |
|
19 |
+ \code{celdaGridSearch}, \code{recursiveSplitModule}, |
|
20 |
+ or \code{recursiveSplitCell}. Must contain a list named |
|
21 |
+ \code{"celda_grid_search"} in \code{metadata(x)}. |
|
22 |
+ \item celdaList object.}} |
|
23 |
+ |
|
24 |
+\item{sep}{Numeric. Breaks in the x axis of the resulting plot.} |
|
25 |
+} |
|
26 |
+\value{ |
|
27 |
+A ggplot plot object showing perplexity diferences as a function of |
|
28 |
+ clustering parameters. |
|
29 |
+} |
|
30 |
+\description{ |
|
31 |
+Visualize perplexity differences of every model in a celdaList, |
|
32 |
+ by unique K/L combinations. |
|
33 |
+} |
|
34 |
+\examples{ |
|
35 |
+data(sceCeldaCGGridSearch) |
|
36 |
+sce <- resamplePerplexity(sceCeldaCGGridSearch) |
|
37 |
+plotGridSearchPerplexityDiff(sce) |
|
38 |
+data(celdaCGSim, celdaCGGridSearchRes) |
|
39 |
+## Run various combinations of parameters with 'celdaGridSearch' |
|
40 |
+celdaCGGridSearchRes <- resamplePerplexity( |
|
41 |
+ celdaCGSim$counts, |
|
42 |
+ celdaCGGridSearchRes) |
|
43 |
+plotGridSearchPerplexityDiff(celdaCGGridSearchRes) |
|
44 |
+} |
... | ... |
@@ -13,9 +13,13 @@ selectBestModel(x, ...) |
13 | 13 |
\S4method{selectBestModel}{celdaList}(x, asList = FALSE) |
14 | 14 |
} |
15 | 15 |
\arguments{ |
16 |
-\item{x}{Object of class \linkS4class{SingleCellExperiment} or |
|
17 |
-\code{celdaList}. An object containing celda |
|
18 |
-models returned from \link{celdaGridSearch}.} |
|
16 |
+\item{x}{Can be one of |
|
17 |
+\itemize{ |
|
18 |
+ \item A \linkS4class{SingleCellExperiment} object returned from |
|
19 |
+ \code{celdaGridSearch}, \code{recursiveSplitModule}, |
|
20 |
+ or \code{recursiveSplitCell}. Must contain a list named |
|
21 |
+ \code{"celda_grid_search"} in \code{metadata(x)}. |
|
22 |
+ \item celdaList object.}} |
|
19 | 23 |
|
20 | 24 |
\item{asList}{\code{TRUE} or \code{FALSE}. Whether to return the |
21 | 25 |
best model as a |
... | ... |
@@ -17,7 +17,8 @@ subsetCeldaList(x, ...) |
17 | 17 |
\item{x}{Can be one of |
18 | 18 |
\itemize{ |
19 | 19 |
\item A \linkS4class{SingleCellExperiment} object returned from |
20 |
- \code{celdaGridSearch}. Must contain a list named |
|
20 |
+ \code{celdaGridSearch}, \code{recursiveSplitModule}, |
|
21 |
+ or \code{recursiveSplitCell}. Must contain a list named |
|
21 | 22 |
\code{"celda_grid_search"} in \code{metadata(x)}. |
22 | 23 |
\item celdaList object.}} |
23 | 24 |
|
... | ... |
@@ -26,7 +27,7 @@ models in list \code{"celda_grid_search"} in \code{metadata(x)}.} |
26 | 27 |
|
27 | 28 |
\item{useAssay}{A string specifying which \code{assay} |
28 | 29 |
slot to use if \code{x} is a |
29 |
-\link[SingleCellExperiment]{SingleCellExperiment} object. Default "counts".} |
|
30 |
+\linkS4class{SingleCellExperiment} object. Default "counts".} |
|
30 | 31 |
} |
31 | 32 |
\value{ |
32 | 33 |
One of |