R/all_generics.R
60acdef0
 setClass(
     "celdaModel",
     representation(
         params = "list",
75664a2f
         # K, L, model priors, checksum
60acdef0
         names = "list",
         completeLogLik = "numeric",
         finalLogLik = "numeric",
         clusters = "list"
     )
 ) # z and or y
 
 
 #' @title Get parameter values provided for celdaModel creation
75664a2f
 #' @description Retrieves the K/L, model priors (e.g. alpha, beta),
58380509
 #'  and count matrix checksum parameters provided during the creation of the
60acdef0
 #'  provided celdaModel.
 #' @param celdaMod celdaModel. Options available in `celda::availableModels`.
58380509
 #' @return List. Contains the model-specific parameters for the provided celda
60acdef0
 #'  model object depending on its class.
578e7e93
 #' @examples
a49fff03
 #' data(celdaCGMod)
60acdef0
 #' params(celdaCGMod)
578e7e93
 #' @export
3bd8e979
 setGeneric("params",
60acdef0
     function(celdaMod) {
         standardGeneric("params")
     })
 #' @title Get parameter values provided for celdaModel creation
75664a2f
 #' @description Retrieves the K/L, model priors (e.g. alpha, beta),
60acdef0
 #'  and count matrix checksum parameters provided during the creation of the
 #'  provided celdaModel.
 #' @param celdaMod celdaModel. Options available in `celda::availableModels`.
58380509
 #' @return List. Contains the model-specific parameters for the provided celda
60acdef0
 #'  model object depending on its class.
4d840eec
 #' @examples
a49fff03
 #' data(celdaCGMod)
60acdef0
 #' params(celdaCGMod)
4d840eec
 #' @export
3bd8e979
 setMethod("params",
60acdef0
     signature = c(celdaMod = "celdaModel"),
     function(celdaMod) {
         celdaMod@params
     })
 
 
 #' @title Get feature, cell and sample names from a celdaModel
58380509
 #' @description Retrieves the row, column, and sample names used to generate
60acdef0
 #'  a celdaModel.
 #' @param celdaMod celdaModel. Options available in `celda::availableModels`.
58380509
 #' @return List. Contains row, column, and sample character vectors
60acdef0
 #'  corresponding to the values provided when the celdaModel was generated.
578e7e93
 #' @examples
a49fff03
 #' data(celdaCGMod)
60acdef0
 #' matrixNames(celdaCGMod)
578e7e93
 #' @export
2b3c28e3
 setGeneric("matrixNames",
60acdef0
     function(celdaMod) {
         standardGeneric("matrixNames")
     })
 #' @title Get feature, cell and sample names from a celdaModel
58380509
 #' @description Retrieves the row, column, and sample names used to generate a
 #'  celdaModel.
60acdef0
 #' @param celdaMod celdaModel. Options available in `celda::availableModels`.
58380509
 #' @return List. Contains row, column, and sample character vectors
 #'  corresponding to the values provided when the celdaModel was generated.
4d840eec
 #' @examples
a49fff03
 #' data(celdaCGMod)
60acdef0
 #' matrixNames(celdaCGMod)
4d840eec
 #' @export
2b3c28e3
 setMethod("matrixNames",
60acdef0
     signature = c(celdaMod = "celdaModel"),
     function(celdaMod) {
         celdaMod@names
     })
578e7e93
 
 
3bd8e979
 #' @title Get log-likelihood history
58380509
 #' @description Retrieves the complete log-likelihood from all iterations of
60acdef0
 #'  Gibbs sampling used to generate a celdaModel.
 #' @param celdaMod celdaModel. Options available in `celda::availableModels`.
58380509
 #' @return Numeric. The log-likelihood at each step of Gibbs sampling used to
60acdef0
 #'  generate the model.
578e7e93
 #' @examples
a49fff03
 #' data(celdaCGMod)
60acdef0
 #' logLikelihoodHistory(celdaCGMod)
578e7e93
 #' @export
3bd8e979
 setGeneric("logLikelihoodHistory",
60acdef0
     function(celdaMod) {
         standardGeneric("logLikelihoodHistory")
     })
4d840eec
 #' @title Get log-likelihood history
58380509
 #' @description Retrieves the complete log-likelihood from all iterations of
60acdef0
 #'  Gibbs sampling used to generate a celdaModel.
 #' @param celdaMod celdaModel. Options available in `celda::availableModels`.
58380509
 #' @return Numeric. The log-likelihood at each step of Gibbs sampling used to
60acdef0
 #'  generate the model.
4d840eec
 #' @examples
a49fff03
 #' data(celdaCGMod)
60acdef0
 #' logLikelihoodHistory(celdaCGMod)
4d840eec
 #' @export
3bd8e979
 setMethod("logLikelihoodHistory",
60acdef0
     signature = c(celdaMod = "celdaModel"),
     function(celdaMod) {
         celdaMod@completeLogLik
     })
 
 
 #' @title Get the log-likelihood
58380509
 #' @description Retrieves the final log-likelihood from all iterations of Gibbs
60acdef0
 #'  sampling used to generate a celdaModel.
58380509
 #' @return Numeric. The log-likelihood at the final step of Gibbs sampling used
60acdef0
 #'  to generate the model.
 #' @param celdaMod A celdaModel object of class celda_C, celda_G, or celda_CG.
578e7e93
 #' @examples
a49fff03
 #' data(celdaCGMod)
60acdef0
 #' bestLogLikelihood(celdaCGMod)
578e7e93
 #' @export
9b638bd2
 setGeneric("bestLogLikelihood",
60acdef0
     function(celdaMod) {
         standardGeneric("bestLogLikelihood")
     })
 #' @title Get the log-likelihood
58380509
 #' @description Retrieves the final log-likelihood from all iterations of Gibbs
60acdef0
 #'  sampling used to generate a celdaModel.
 #' @param celdaMod A celdaModel object of class celda_C, celda_G, or celda_CG.
58380509
 #' @return Numeric. The log-likelihood at the final step of Gibbs sampling used
60acdef0
 #'  to generate the model.
4d840eec
 #' @examples
a49fff03
 #' data(celdaCGMod)
60acdef0
 #' bestLogLikelihood(celdaCGMod)
4d840eec
 #' @export
9b638bd2
 setMethod("bestLogLikelihood",
60acdef0
     signature = c(celdaMod = "celdaModel"),
     function(celdaMod) {
         celdaMod@finalLogLik
     })
 
 
 #' @title Get clustering outcomes from a celdaModel
58380509
 #' @description Returns the z / y results corresponding to the cell / gene
60acdef0
 #'  cluster labels determined by the provided celdaModel.
 #' @param celdaMod celdaModel. Options available in `celda::availableModels`.
58380509
 #' @return List. Contains z (for celda_C and celdaCGModels) and/or y
60acdef0
 #'  (for celda_G and celdaCGModels)
3bd8e979
 #' @examples
a49fff03
 #' data(celdaCGMod)
60acdef0
 #' clusters(celdaCGMod)
3bd8e979
 #' @export
 setGeneric("clusters",
60acdef0
     function(celdaMod) {
         standardGeneric("clusters")
     })
 #' @title Get clustering outcomes from a celdaModel
58380509
 #' @description Returns the z / y results corresponding to the cell / gene
60acdef0
 #'  cluster labels determined by the provided celdaModel.
 #' @param celdaMod celdaModel. Options available in `celda::availableModels`.
58380509
 #' @return List. Contains z (for celda_C and celdaCGModels) and/or y
60acdef0
 #'  (for celda_G and celdaCGModels)
4d840eec
 #' @examples
a49fff03
 #' data(celdaCGMod)
60acdef0
 #' clusters(celdaCGMod)
4d840eec
 #' @export
60acdef0
 setMethod("clusters",
     signature = c(celdaMod = "celdaModel"),
     function(celdaMod) {
         return(celdaMod@clusters)
     })
bf7859b0
 
37461dae
 
 setClass("celda_C",
60acdef0
     representation(sampleLabel = "factor"),
     contains = "celdaModel")
578e7e93
 
 
60acdef0
 #' @title Get sampleLabels from a celdaModel
58380509
 #' @description Returns the sampleLabels for the count matrix provided for
60acdef0
 #'  generation of a given celdaModel.
 #' @param celdaMod celdaModel. Options available in `celda::availableModels`.
58380509
 #' @return Character. Contains the sampleLabels provided at model creation time,
60acdef0
 #'  or those automatically generated by celda.
578e7e93
 #' @examples
a49fff03
 #' data(celdaCGMod)
60acdef0
 #' sampleLabel(celdaCGMod)
578e7e93
 #' @export
bf7859b0
 setGeneric("sampleLabel",
60acdef0
     function(celdaMod) {
         standardGeneric("sampleLabel")
     })
 #' @title Get sampleLabels from a celdaModel
58380509
 #' @description Returns the sampleLabels for the count matrix provided for
60acdef0
 #'  generation of a given celdaModel.
 #' @param celdaMod celdaModel. Options available in `celda::availableModels`.
58380509
 #' @return Character. Contains the sampleLabels provided at model creation time,
60acdef0
 #'  or those automatically generated by celda.
4d840eec
 #' @examples
a49fff03
 #' data(celdaCGMod)
60acdef0
 #' sampleLabel(celdaCGMod)
4d840eec
 #' @export
bf7859b0
 setMethod("sampleLabel",
60acdef0
     signature = c(celdaMod = "celdaModel"),
     function(celdaMod) {
         celdaMod@sampleLabel
     })
37461dae
 
 
60acdef0
 setClass("celda_G", contains = "celdaModel")
37461dae
 
60acdef0
 setClass("celda_CG", contains = c("celda_C", "celda_G"))
37461dae
 
60acdef0
 setClass(
     "celdaList",
     representation(
         runParams = "data.frame",
         resList = "list",
         countChecksum = "character",
         perplexity = "matrix"
     )
 )
578e7e93
 
3bd8e979
 
578e7e93
 #' @title Get run parameters provided to `celdaGridSearch()`
75664a2f
 #' @description Returns details on the clustering parameters, and model priors
 #'  provided to `celdaGridSearch()` when the provided celdaList was
60acdef0
 #'  created.
06b0c870
 #' @param celdaList An object of class celdaList.
58380509
 #' @return Data Frame. Contains details on the various K/L parameters, chain
 #'  parameters, and final log-likelihoods derived for each model in the provided
60acdef0
 #'  celdaList.
578e7e93
 #' @examples
a49fff03
 #' data(celdaCGGridSearchRes)
60acdef0
 #' runParams(celdaCGGridSearchRes)
578e7e93
 #' @export
bf7859b0
 setGeneric("runParams",
06b0c870
     function(celdaList) {
60acdef0
         standardGeneric("runParams")
     })
4d840eec
 #' @title Get run parameters provided to `celdaGridSearch()`
75664a2f
 #' @description Returns details on the clustering parameters, and model priors
 #'  provided to `celdaGridSearch()` when the provided celdaList was
60acdef0
 #'  created.
06b0c870
 #' @param celdaList An object of class celdaList.
58380509
 #' @return Data Frame. Contains details on the various K/L parameters, chain
 #'  parameters, and final log-likelihoods derived for each model in the provided
60acdef0
 #'  celdaList.
4d840eec
 #' @examples
a49fff03
 #' data(celdaCGGridSearchRes)
60acdef0
 #' runParams(celdaCGGridSearchRes)
4d840eec
 #' @export
bf7859b0
 setMethod("runParams",
06b0c870
     signature = c(celdaList = "celdaList"),
     function(celdaList) {
         celdaList@runParams
60acdef0
     })
3bd8e979
 
578e7e93
 
60acdef0
 #' @title Get final celdaModels from a celdaList
578e7e93
 #' @description Returns all models generated during a `celdaGridSearch()` run.
06b0c870
 #' @param celdaList An object of class celdaList.
58380509
 #' @return List. Contains one celdaModel object for each of the parameters
60acdef0
 #'  specified in the `runParams()` of the provided celda list.
578e7e93
 #' @examples
a49fff03
 #' data(celdaCGGridSearchRes)
60acdef0
 #' celdaCGGridModels <- resList(celdaCGGridSearchRes)
578e7e93
 #' @export
bf7859b0
 setGeneric("resList",
06b0c870
     function(celdaList) {
60acdef0
         standardGeneric("resList")
     })
 #' @title Get final celdaModels from a celdaList
4d840eec
 #' @description Returns all models generated during a `celdaGridSearch()` run.
06b0c870
 #' @param celdaList An object of class celdaList.
58380509
 #' @return List. Contains one celdaModel object for each of the parameters
60acdef0
 #'  specified in the `runParams()` of the provided celda list.
4d840eec
 #' @examples
a49fff03
 #' data(celdaCGGridSearchRes)
60acdef0
 #' celdaCGGridModels <- resList(celdaCGGridSearchRes)
4d840eec
 #' @export
bf7859b0
 setMethod("resList",
06b0c870
     signature = c(celdaList = "celdaList"),
     function(celdaList) {
         celdaList@resList
60acdef0
     })
578e7e93
 
 
 #' @title Get perplexity for every model in a celdaList
58380509
 #' @description Returns perplexity for each model in a celdaList as calculated
60acdef0
 #'  by `perplexity().`
06b0c870
 #' @param celdaList An object of class celdaList.
58380509
 #' @return List. Contains one celdaModel object for each of the parameters
60acdef0
 #'  specified in the `runParams()` of the provided celda list.
578e7e93
 #' @examples
a49fff03
 #' data(celdaCGGridSearchRes)
60acdef0
 #' celdaCGGridModelPerplexities <- celdaPerplexity(celdaCGGridSearchRes)
578e7e93
 #' @export
3bd8e979
 setGeneric("celdaPerplexity",
06b0c870
     function(celdaList) {
60acdef0
         standardGeneric("celdaPerplexity")
     })
4d840eec
 #' @title Get perplexity for every model in a celdaList
58380509
 #' @description Returns perplexity for each model in a celdaList as calculated
60acdef0
 #'  by `perplexity().`
06b0c870
 #' @param celdaList An object of class celdaList.
58380509
 #' @return List. Contains one celdaModel object for each of the parameters
60acdef0
 #'  specified in the `runParams()` of the provided celda list.
4d840eec
 #' @examples
a49fff03
 #' data(celdaCGGridSearchRes)
60acdef0
 #' celdaCGGridModelPerplexities <- celdaPerplexity(celdaCGGridSearchRes)
4d840eec
 #' @export
3bd8e979
 setMethod("celdaPerplexity",
06b0c870
     signature = c(celdaList = "celdaList"),
     function(celdaList) {
         celdaList@perplexity
60acdef0
     })
37461dae
 
 
c2e3064e
 #' @title Append two celdaList objects
58380509
 #' @description Returns a single celdaList representing the combination of two
60acdef0
 #'  provided celdaList objects.
58380509
 #' @return A celdaList object. This object contains all resList entries and
60acdef0
 #'  runParam records from both lists.
4d840eec
 #' @param list1 A celda_list object
 #' @param list2 A celda_list object to be joined with list_1
c2e3064e
 #' @examples
a49fff03
 #' data(celdaCGGridSearchRes)
58380509
 #' appendedList <- appendCeldaList(celdaCGGridSearchRes,
60acdef0
 #'     celdaCGGridSearchRes)
d7196f24
 #' @importFrom methods new
c2e3064e
 #' @export
60acdef0
 appendCeldaList <- function(list1, list2) {
     if (!is.element("celdaList", class(list1)) |
22ad839c
             !is.element("celdaList", class(list2))) {
60acdef0
         stop("Both parameters to appendCeldaList must be of class celdaList.")
     }
06b0c870
     if (!(countChecksum(list1) == countChecksum(list2))) {
22ad839c
         warning("Provided lists have different countChecksums and may have",
             " been generated from different count matrices. Using checksum",
             " from first list...")
60acdef0
     }
     newList <- methods::new(
         "celdaList",
06b0c870
         runParams = rbind(runParams(list1), runParams(list2)),
         resList = c(resList(list1), resList(list2)),
         countChecksum = countChecksum(list1),
60acdef0
         perplexity = matrix(nrow = 0, ncol = 0))
     return(newList)
c2e3064e
 }
 
06b0c870
 
 #' @title Get the MD5 hash of the count matrix from the celdaList
 #' @description Returns the MD5 hash of the count matrix used to generate the
 #'  celdaList.
 #' @param celdaList An object of class celdaList.
 #' @return A character string of length 32 containing the MD5 digest of
 #'  the count matrix.
 #' @examples
 #' data(celdaCGGridSearchRes)
 #' countChecksum <- countChecksum(celdaCGGridSearchRes)
 #' @export
 setGeneric("countChecksum",
     function(celdaList) {
         standardGeneric("countChecksum")
     })
 #' @title Get the MD5 hash of the count matrix from the celdaList
 #' @description Returns the MD5 hash of the count matrix used to generate the
 #'  celdaList.
 #' @param celdaList An object of class celdaList.
 #' @return A character string of length 32 containing the MD5 digest of
 #'  the count matrix.
 #' @examples
 #' data(celdaCGGridSearchRes)
 #' countChecksum <- countChecksum(celdaCGGridSearchRes)
 #' @export
 setMethod("countChecksum",
     signature = c(celdaList = "celdaList"),
     function(celdaList) {
         celdaList@countChecksum
     })
 
37461dae
 ################################################################################
 # Generics
 ################################################################################
 
 
58380509
 #' @title Plot celda Heatmap
 #' @description Render a stylable heatmap of count data based on celda
 #'  clustering results.
 #' @param counts Integer matrix. Rows represent features and columns represent
 #'  cells. This matrix should be the same as the one used to generate
60acdef0
 #'  `celdaMod`.
58380509
 #' @param celdaMod A celdaModel object of class "celda_C", "celda_G", or
60acdef0
 #'  "celda_CG".
58380509
 #' @param featureIx Integer vector. Select features for display in heatmap. If
60acdef0
 #'  NULL, no subsetting will be performed. Default NULL.
37461dae
 #' @param ... Additional parameters.
60acdef0
 #' @examples
a49fff03
 #' data(celdaCGSim, celdaCGMod)
60acdef0
 #' celdaHeatmap(celdaCGSim$counts, celdaCGMod)
37461dae
 #' @return list A list containing dendrogram information and the heatmap grob
60acdef0
 #' @export
 setGeneric("celdaHeatmap",
     signature = "celdaMod",
     function(counts, celdaMod, featureIx, ...) {
         standardGeneric("celdaHeatmap")
     })
 
58380509
 #' @title Calculate LogLikelihood
 #' @description Calculate a log-likelihood for a user-provided cluster
60acdef0
 #'  assignment and count matrix, per the desired celdaModel.
58380509
 #' @param counts The counts matrix used to generate the provided cluster
60acdef0
 #'  assignments.
 #' @param model celdaModel. Options available in `celda::availableModels`.
37461dae
 #' @param ... Additional parameters.
58380509
 #' @return The log-likelihood of the provided cluster assignment for the
60acdef0
 #'  provided counts matrix.
37461dae
 #' @examples
a49fff03
 #' data(celdaCGSim)
60acdef0
 #' loglik <- logLikelihood(celdaCGSim$counts,
 #'     model = "celda_CG",
 #'     sampleLabel = celdaCGSim$sampleLabel,
 #'     z = celdaCGSim$z, y = celdaCGSim$y,
 #'     K = celdaCGSim$K, L = celdaCGSim$L,
 #'     alpha = celdaCGSim$alpha, beta = celdaCGSim$beta,
 #'     gamma = celdaCGSim$gamma, delta = celdaCGSim$delta
 #' )
37461dae
 #' @export
60acdef0
 #'
 #'
 logLikelihood <- function(counts, model, ...) {
804d499b
     do.call(paste0("logLikelihood", model),
22ad839c
         args = list(counts = counts, ...))
edef7bb1
 }
2b3c28e3
 
 
58380509
 #' @title Get cluster probability
 #' @description Get the probability of the cluster assignments generated during
 #'  a celda run.
 #' @param counts Integer matrix. Rows represent features and columns represent
60acdef0
 #' cells. This matrix should be the same as the one used to generate `celdaMod`.
 #' @param celdaMod celdaModel. Options available in `celda::availableModels`.
58380509
 #' @param log Logical. If FALSE, then the normalized conditional probabilities
 #'  will be returned. If TRUE, then the unnormalized log probabilities will be
60acdef0
 #'  returned. Default FALSE.
4d840eec
 #' @param ... Additional parameters.
2b3c28e3
 #' @examples
a49fff03
 #' data(celdaCGSim, celdaCGMod)
60acdef0
 #' clusterProb <- clusterProbability(celdaCGSim$counts, celdaCGMod)
2b3c28e3
 #' @return A numeric vector of the cluster assignment probabilties
 #' @export
60acdef0
 setGeneric("clusterProbability",
     signature = "celdaMod",
     function(counts, celdaMod, log = FALSE, ...) {
         standardGeneric("clusterProbability")
     })
 
 
 #' @title Calculate the perplexity from a single celdaModel
58380509
 #' @description Perplexity can be seen as a measure of how well a provided set
60acdef0
 #'  of cluster assignments fit the data being clustered.
58380509
 #' @param counts Integer matrix. Rows represent features and columns represent
 #'  cells. This matrix should be the same as the one used to generate
60acdef0
 #'  `celdaMod`.
 #' @param celdaMod celdaModel. Options available in `celda::availableModels`.
58380509
 #' @param newCounts A newCounts matrix used to calculate perplexity. If NULL,
60acdef0
 #'  perplexity will be calculated for the 'counts' matrix. Default NULL.
2b3c28e3
 #' @return Numeric. The perplexity for the provided count data and model.
 #' @examples
a49fff03
 #' data(celdaCGSim, celdaCGMod)
60acdef0
 #' perplexity <- perplexity(celdaCGSim$counts, celdaCGMod)
2b3c28e3
 #' @export
 setGeneric("perplexity",
60acdef0
     signature = "celdaMod",
     function(counts, celdaMod, newCounts = NULL) {
         standardGeneric("perplexity")
     })
 
 
 #' @title Simulate count data from the celda generative models.
58380509
 #' @description This function generates a list containing a simulated counts
 #'  matrix, as well as various parameters used in the simulation which can be
60acdef0
 #'  useful for running celda. The user must provide the desired model
 #'  (one of celda_C, celda_G, celda_CG) as well as any desired tuning parameters
 #'  for those model's simulation functions as detailed below.
 #' @param model Character. Options available in `celda::availableModels`.
37461dae
 #' @param ... Additional parameters.
58380509
 #' @return List. Contains the simulated counts matrix, derived cell cluster
 #'  assignments, the provided parameters, and estimated Dirichlet distribution
60acdef0
 #'  parameters for the model.
37461dae
 #' @examples
a49fff03
 #' data(celdaCGSim)
60acdef0
 #' dim(celdaCGSim$counts)
37461dae
 #' @export
60acdef0
 simulateCells <- function(model, ...) {
804d499b
     do.call(paste0("simulateCells", model), args = list(...))
37461dae
 }
 
 
58380509
 #' @title Generate factorized matrices showing each feature's influence on cell
60acdef0
 #'  / gene clustering
58380509
 #' @param counts Integer matrix. Rows represent features and columns represent
 #'  cells. This matrix should be the same as the one used to generate
60acdef0
 #'  `celdaMod`.
 #' @param celdaMod Celda object of class "celda_C", "celda_G", or "celda_CG".
58380509
 #' @param type A character vector containing one or more of "counts",
60acdef0
 #'  "proportions", or "posterior". "counts" returns the raw number of counts for
58380509
 #'  each entry in each matrix. "proportions" returns the counts matrix where
60acdef0
 #'  each vector is normalized to a probability distribution. "posterior" returns
58380509
 #'  the posterior estimates which include the addition of the Dirichlet
60acdef0
 #'  concentration parameter (essentially as a pseudocount).
 #' @examples
a49fff03
 #' data(celdaCGSim, celdaCGMod)
60acdef0
 #' factorizedMatrices <- factorizeMatrix(
 #'     celdaCGSim$counts, celdaCGMod,
 #'     "posterior"
 #' )
37461dae
 #' @return A list of lists of the types of factorized matrices specified
 #' @export
2b3c28e3
 setGeneric("factorizeMatrix",
60acdef0
     signature = "celdaMod",
     function(counts,
         celdaMod,
         type = c("counts", "proportion", "posterior")) {
         standardGeneric("factorizeMatrix")
     })
 
58380509
 #' @title Renders probability and relative expression heatmaps to visualize the
60acdef0
 #'  relationship between feature modules and cell populations.
58380509
 #' @description It is often useful to visualize to what degree each feature
 #' influences each cell cluster. This can also be useful for identifying
60acdef0
 #' features which may be redundant or unassociated with cell clustering.
58380509
 #' @param counts Integer matrix. Rows represent features and columns represent
 #'  cells. This matrix should be the same as the one used to generate
60acdef0
 #'  `celdaMod`.
 #' @param celdaMod Celda object of class "celda_C" or "celda_CG".
37461dae
 #' @param ... Additional parameters.
 #' @examples
a49fff03
 #' data(celdaCGSim, celdaCGMod)
60acdef0
 #' celdaProbabilityMap(celdaCGSim$counts, celdaCGMod)
37461dae
 #' @return A grob containing the specified plots
 #' @export
2b3c28e3
 setGeneric("celdaProbabilityMap",
60acdef0
     signature = "celdaMod",
     function(counts, celdaMod, ...) {
         standardGeneric("celdaProbabilityMap")
     })
 
 
 #' @title Embeds cells in two dimensions using tSNE based on celda_CG results.
58380509
 #' @param counts Integer matrix. Rows represent features and columns represent
 #'  cells. This matrix should be the same as the one used to generate
60acdef0
 #'  `celdaMod`.
 #' @param celdaMod Celda object of class `celda_CG`.
58380509
 #' @param maxCells Integer. Maximum number of cells to plot. Cells will be
 #'  randomly subsampled if ncol(counts) > maxCells. Larger numbers of cells
60acdef0
 #'  requires more memory. Default 25000.
58380509
 #' @param minClusterSize Integer. Do not subsample cell clusters below this
60acdef0
 #'  threshold. Default 100.
 #' @param initialDims integer. The number of dimensions that should be retained
 #'  in the initial PCA step. Default 20.
58380509
 #' @param modules Integer vector. Determines which features modules to use for
60acdef0
 #'  tSNE. If NULL, all modules will be used. Default NULL.
8b60a355
 #' @param perplexity Numeric. Perplexity parameter for tSNE. Default 20.
58380509
 #' @param maxIter Integer. Maximum number of iterations in tSNE generation.
60acdef0
 #'  Default 2500.
8b60a355
 #' @param ... Additional parameters.
58380509
 #' @return Numeric Matrix of dimension `ncol(counts)` x 2, colums representing
60acdef0
 #'  the "X" and "Y" coordinates in the data's t-SNE represetation.
 #' @examples
a49fff03
 #' data(celdaCGSim, celdaCGMod)
60acdef0
 #' tsneRes <- celdaTsne(celdaCGSim$counts, celdaCGMod)
37461dae
 #' @export
2b3c28e3
 setGeneric("celdaTsne",
60acdef0
     signature = "celdaMod",
     function(counts,
         celdaMod,
         maxCells = 25000,
         minClusterSize = 100,
         initialDims = 20,
         modules = NULL,
         perplexity = 20,
         maxIter = 2500,
         ...) {
         # counts = processCounts(counts)
         # compareCountMatrix(counts, celdaMod)
         standardGeneric("celdaTsne")
     })
 
 
 #' @title Embeds cells in two dimensions using umap.
58380509
 #' @param counts Integer matrix. Rows represent features and columns represent
 #'  cells. This matrix should be the same as the one used to generate
60acdef0
 #'  `celdaMod`.
 #' @param celdaMod Celda object of class `celda_CG`.
58380509
 #' @param maxCells Integer. Maximum number of cells to plot. Cells will be
 #'  randomly subsampled if ncol(counts) > maxCells. Larger numbers of cells
60acdef0
 #'  requires more memory. Default 25000.
58380509
 #' @param minClusterSize Integer. Do not subsample cell clusters below this
60acdef0
 #'  threshold. Default 100.
2e877ffe
 #' @param initialDims Integer. PCA will be used to reduce the dimentionality
 #'  of the dataset. The top 'initialDims' principal components will be used
 #'  for umap. Default 20.
58380509
 #' @param modules Integer vector. Determines which features modules to use for
60acdef0
 #'  tSNE. If NULL, all modules will be used. Default NULL.
fd95d0e3
 #' @param seed Integer. Passed to \link[withr]{with_seed}. For reproducibility,
 #'  a default value of 12345 is used. If NULL, no calls to
 #'  \link[withr]{with_seed} are made.
60acdef0
 #' @param umapConfig An object of class "umapConfig" specifying parameters to
 #'  the UMAP algorithm.
58380509
 #' @return Numeric Matrix of dimension `ncol(counts)` x 2, colums representing
60acdef0
 #'  the "X" and "Y" coordinates in the data's t-SNE represetation.
 #' @examples
a49fff03
 #' data(celdaCGSim, celdaCGMod)
60acdef0
 #' tsneRes <- celdaUmap(celdaCGSim$counts, celdaCGMod)
d7196f24
 #' @importFrom umap umap.defaults
8b60a355
 #' @export
 setGeneric("celdaUmap",
60acdef0
     signature = "celdaMod",
     function(counts,
         celdaMod,
         maxCells = 25000,
         minClusterSize = 100,
2e877ffe
         initialDims = 20,
60acdef0
         modules = NULL,
fd95d0e3
         seed = 12345,
60acdef0
         umapConfig = umap::umap.defaults) {
         standardGeneric("celdaUmap")
     })
 
 
 #' @title Obtain the gene module of a gene of interest
 #' @description This function will output the corresponding feature module for a
 #'  specified list of genes from a celdaModel.
 #' @param counts Integer matrix. Rows represent features and columns represent
58380509
 #'  cells. This matrix should be the same as the one used to generate
60acdef0
 #'  `celdaMod`.
 #' @param celdaMod Model of class "celda_G" or "celda_CG".
 #' @param feature Character vector. Identify feature modules for the specified
 #'  feature names.
 #' @param exactMatch Logical. Whether to look for exactMatch of the gene name
 #'  within counts matrix. Default TRUE.
 #' @return List. Each entry corresponds to the feature module determined for the
 #'  provided features
 #' @examples
a49fff03
 #' data(celdaCGSim, celdaCGMod)
60acdef0
 #' featureModuleLookup(
 #'     counts = celdaCGSim$counts,
 #'     celdaMod = celdaCGMod, "Gene_1")
37461dae
 #' @export
2b3c28e3
 setGeneric("featureModuleLookup",
60acdef0
     signature = "celdaMod",
     function(counts, celdaMod, feature, exactMatch = TRUE) {
         standardGeneric("featureModuleLookup")
     })