Skip to content

Commit

Permalink
fix normalized count extraction (#30)
Browse files Browse the repository at this point in the history
closes #29
  • Loading branch information
c-mertes authored Oct 9, 2020
1 parent 0bff757 commit 3140490
Show file tree
Hide file tree
Showing 5 changed files with 50 additions and 25 deletions.
1 change: 1 addition & 0 deletions NEWS
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@ CHANGES IN VERSION 1.7.1
o Move to S3/S4 methods to be compatible with FRASER
o Due to the S3/S4 changes minor changes in the argument names happend
mainly ods -> object or x
o Bugfixes: #29

CHANGES IN VERSION 1.3.5
-----------------------------
Expand Down
43 changes: 29 additions & 14 deletions R/method-counts.R
Original file line number Diff line number Diff line change
Expand Up @@ -7,8 +7,8 @@ counts.replace.OutriderDataSet <- function(object, ..., value){
object
}

counts.OutriderDataSet <- function(object, normalized=FALSE, minE=0.5){
cnts <- assay(object, "counts")
counts.OutriderDataSet <- function(object, normalized=FALSE, minE=0.5, ...){
cnts <- assay(object, "counts", ...)

# raw counts
if(!normalized) {
Expand All @@ -17,8 +17,16 @@ counts.OutriderDataSet <- function(object, normalized=FALSE, minE=0.5){

# normalized by normalization factors
if(!is.null(normalizationFactors(object))) {
E <- t(apply(normalizationFactors(object), 1, pmax, minE))
return(cnts/E * exp(rowMeans(log(E))))
if(!"expectedLogGeomMean" %in% colnames(mcols(object))){
stop("The expectedLogGeomMean is missing in mcols(ods). ",
"Did you set the normaliationFactors by hand? ",
"Please use normalizationFactors(object) <- values.")
}

# use cached expected log geom mean values
eMat <- pmax(normalizationFactors(object), minE)
eLGM <- mcols(object)[["expectedLogGeomMean"]]
return(cnts/eMat * eLGM)
}

# normalization by sizeFactors
Expand Down Expand Up @@ -49,10 +57,11 @@ counts.OutriderDataSet <- function(object, normalized=FALSE, minE=0.5){
#' @aliases counts counts,OutriderDataSet-method
#' counts<-,OutriderDataSet,matrix-method
#'
#' @param object OutriderDataSet
#' @param object An \code{\link{OutriderDataSet}} object
#' @param normalized TRUE/FALSE whether counts should be normalized
#' @param value An integer matrix containing the counts
#' @param minE minimal expected count.
#' @param minE The minimal expected count, defaults to 0.5, to be used in
#' computing the expected log geom mean.
#' @param ... Further arguments are passed on to the underlying assay function
#' @return A matrix containing the counts
#'
Expand All @@ -76,14 +85,14 @@ setReplaceMethod("counts", signature(object="OutriderDataSet", value="matrix"),
counts.replace.OutriderDataSet)


normalizationFactors.OutriderDataSet <- function(object) {
normalizationFactors.OutriderDataSet <- function(object, ...) {
if (!"normalizationFactors" %in% assayNames(object)){
return(NULL)
}
assay(object, "normalizationFactors")
assay(object, "normalizationFactors", ...)
}

normFactors.replace.OutriderDataSet <- function(object, value) {
normFactors.replace.OutriderDataSet <- function(object, minE=0.5, ..., value) {
# enforce same dimnames and matrix type
if(!is.matrix(value)){
value <- as.matrix(value)
Expand All @@ -96,7 +105,13 @@ normFactors.replace.OutriderDataSet <- function(object, value) {
stopifnot(all(value > 0))

# set the values and check the object
assay(object, "normalizationFactors", withDimnames=FALSE) <- value
assay(object, "normalizationFactors", ..., withDimnames=FALSE) <- value

# compute the expected log geom mean values so we can cache them
mcols(object)[["expectedLogGeomMean"]] <- exp(
rowMeans2(log(pmax(value, minE))))

# validate and return object
validObject(object)
object
}
Expand All @@ -110,22 +125,22 @@ normFactors.replace.OutriderDataSet <- function(object, value) {
#' factors are stored within the OutriderDataset object. This normalization
#' factors are then used to compute the normalized counts.
#'
#' @seealso DESeq2::normalizationFactors
#' @docType methods
#' @name normalizationFactors
#' @rdname normalizationFactors
#' @aliases normalizationFactors normalizationFactors,OutriderDataSet-method
#' normalizationFactors<-,OutriderDataSet,matrix-method
#' normalizationFactors<-,OutriderDataSet,DataFrame-method
#' normalizationFactors<-,OutriderDataSet,NULL-method
#'
#' @param object An \code{OutriderDataSet} object.
#'
#' @inheritParams counts
#' @param value The matrix of normalization factors
#' @return A numeric matrix containing the normalization factors or the
#' OutriderDataSet object with an updated
#' \code{normalizationFactors} assay.
#'
#' @seealso \code{\link{sizeFactors}}
#' @seealso \code{\link{sizeFactors}}
#' \code{\link[DESeq2]{normalizationFactors}}
#'
#' @examples
#'
Expand Down
7 changes: 4 additions & 3 deletions man/counts.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

20 changes: 12 additions & 8 deletions man/normalizationFactors.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

4 changes: 4 additions & 0 deletions tests/testthat/test_generics.R
Original file line number Diff line number Diff line change
Expand Up @@ -31,6 +31,10 @@ test_that("normalization function", {
expect_equal(counts(ord)/E * exp(rowMeans(log(E))),
counts(ord, normalized=TRUE))

# check if subsetting affects the computation of the log geom mean
expect_equal((counts(ord)/E * exp(rowMeans(log(E))))[1:10,1:3],
counts(ord[1:10,1:3], normalized=TRUE))

normalizationFactors(ord) <- NULL
expect_null(normalizationFactors(ord))

Expand Down

0 comments on commit 3140490

Please sign in to comment.