Skip to content

Instantly share code, notes, and snippets.

@kevinrue
Created December 9, 2019 15:51
Show Gist options
  • Save kevinrue/d22c3aeac477d5879f48010c3546625b to your computer and use it in GitHub Desktop.
Save kevinrue/d22c3aeac477d5879f48010c3546625b to your computer and use it in GitHub Desktop.
Proof of concept for creating new panel types in iSEE 2.0
setClass("RedDimHexbinPlot", contains="RedDimPlot")
#' The reduced dimension hexbin plot panel
#'
#' Plots reduced dimensions summarizing points into hexagon bins.
#'
#' @section Constructor:
#' \code{RedDimHexbinPlot()} creates an instance of a RedDimHexbinPlot class.
#'
#' @author Kevin Rue
#'
#' @examples
#' #################
#' # For end-users #
#' #################
#'
#' x <- RedDimHexbinPlot()
#' x[["Type"]]
#' x[["Type"]] <- "TSNE"
#'
#' ##################
#' # For developers #
#' ##################
#'
#'
#' library(scater)
#' sce <- mockSCE()
#' sce <- logNormCounts(sce)
#'
#' # Spits out a NULL and a warning if no reducedDims are available.
#' sce0 <- .cacheCommonInfo(x, sce)
#' .refineParameters(x, sce0)
#'
#' # Replaces the default with something sensible.
#' sce <- runPCA(sce)
#' sce0 <- .cacheCommonInfo(x, sce)
#' .refineParameters(x, sce0)
#'
#' @docType methods
#' @aliases RedDimHexbinPlot RedDimHexbinPlot-class
#' .defineParamInterface,RedDimHexbinPlot-method
#' .createParamObservers,RedDimHexbinPlot-method
#' @name RedDimHexbinPlot
NULL
#' @export
RedDimHexbinPlot <- function() {
new("RedDimHexbinPlot")
}
#' @export
#' @importFrom methods callNextMethod
setMethod("initialize", "RedDimHexbinPlot", function(.Object, ...) {
# TODO: Package `hexbin` required for `stat_binhex`
stopifnot(require(hexbin))
.Object <- callNextMethod(.Object, ...)
.Object
})
#' @export
#' @importFrom SingleCellExperiment reducedDimNames reducedDim
#' @importClassesFrom SingleCellExperiment SingleCellExperiment
#' @importFrom methods callNextMethod
setMethod(".cacheCommonInfo", "RedDimHexbinPlot", function(x, se) {
callNextMethod()
})
#' @export
#' @importFrom SingleCellExperiment reducedDim
#' @importFrom methods callNextMethod
setMethod(".refineParameters", "RedDimHexbinPlot", function(x, se) {
x <- callNextMethod()
x
})
#' @importFrom S4Vectors setValidity2 isSingleString
setValidity2("RedDimHexbinPlot", function(object) {
msg <- character(0)
if (length(msg)>0) {
return(msg)
}
TRUE
})
#' @export
#' @importFrom SingleCellExperiment reducedDim reducedDimNames
#' @importFrom shiny selectInput
#' @importFrom methods callNextMethod
setMethod(".defineParamInterface", "RedDimHexbinPlot", function(x, se, active_panels) {
callNextMethod()
})
#' @export
#' @importFrom SingleCellExperiment reducedDim
#' @importFrom shiny observeEvent updateSelectInput
#' @importFrom methods callNextMethod
setMethod(".createParamObservers", "RedDimHexbinPlot", function(x, se, input, session, pObjects, rObjects) {
callNextMethod()
})
#' @export
setMethod(".getEncodedName", "RedDimHexbinPlot", function(x) "RedDimHexbinPlot")
#' @export
setMethod(".getFullName", "RedDimHexbinPlot", function(x) "Reduced dimension hexbin plot")
#' @export
setMethod(".getCommandsDataXY", "RedDimHexbinPlot", function(x, param_choices) {
callNextMethod()
})
#' @export
setMethod(".getCommandsPlot", "RedDimHexbinPlot", function(x, param_choices, plot_data, plot_type, labs, is_subsetted, is_downsampled) {
plot_cmds <- list()
plot_cmds[["ggplot"]] <- "ggplot() +"
# Adding hexbins to the plot.
new_aes <- .build_aes()
plot_cmds[["hex"]] <- sprintf("geom_hex(%s, plot.data) +", new_aes)
plot_cmds[["theme_base"]] <- "theme_bw()"
return(unlist(plot_cmds))
})
@kevinrue
Copy link
Author

kevinrue commented Dec 9, 2019

image

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment