Skip to content

Commit

Permalink
add drop=FALSE to all FraserDataSet subsetting in countRNA
Browse files Browse the repository at this point in the history
  • Loading branch information
Drew Behrens committed Feb 5, 2024
1 parent e650af9 commit 4a15970
Show file tree
Hide file tree
Showing 2 changed files with 7 additions and 7 deletions.
6 changes: 3 additions & 3 deletions R/AllGenerics.R
Original file line number Diff line number Diff line change
Expand Up @@ -232,7 +232,7 @@ setReplaceMethod("nonSplicedReads", "FraserDataSet", function(object, value){
#' @param j A integer vector to subset the columns/samples
#' @param by a character (j or ss) defining if we subset by
#' junctions or splice sites
#' @param drop Currently not used
#' @param dropBool Currently not used
#' @return A subsetted \code{FraserDataSet} object
#' @examples
#' fds <- createTestFraserDataSet()
Expand Down Expand Up @@ -289,14 +289,14 @@ subset.FRASER <- function(x, i, j, by=c("j", "ss"), drop = FALSE){
idxNSR <- rowData(x, type="ss")[['spliceSiteID']] %in% ssIdx

# subset it
nsrObj <- nsrObj[idxNSR,j]
nsrObj <- nsrObj[idxNSR,j,drop=FALSE]
}

# subset the inheritate SE object
if(length(x) == 0){
i <- NULL
}
subX <- as(as(x, "RangedSummarizedExperiment")[i,j], "FraserDataSet")
subX <- as(as(x, "RangedSummarizedExperiment")[i,j,drop=FALSE], "FraserDataSet")

# create new FraserDataSet object
newx <- new("FraserDataSet",
Expand Down
8 changes: 4 additions & 4 deletions R/countRNAseqData.R
Original file line number Diff line number Diff line change
Expand Up @@ -459,8 +459,8 @@ getSplitCountCacheFile <- function(sampleID, settings){
#' @export
countSplitReads <- function(sampleID, fds, NcpuPerSample=1, genome=NULL,
recount=FALSE, keepNonStandardChromosomes=TRUE,
bamfile=bamFile(fds[,sampleID]),
pairedend=pairedEnd(fds[,sampleID]),
bamfile=bamFile(fds[,sampleID,drop=FALSE]),
pairedend=pairedEnd(fds[,sampleID,drop=FALSE]),
strandmode=strandSpecific(fds),
cacheFile=getSplitCountCacheFile(sampleID, fds),
scanbamparam=scanBamParam(fds),
Expand Down Expand Up @@ -856,11 +856,11 @@ countNonSplicedReads <- function(sampleID, splitCountRanges, fds,
}


bamFile <- bamFile(fds[,samples(fds) == sampleID])[[1]]
bamFile <- bamFile(fds[,samples(fds) == sampleID,drop=FALSE])[[1]]

# unstranded case: for counting only non spliced reads we
# skip this information
isPairedEnd <- pairedEnd(fds[,samples(fds) == sampleID])[[1]]
isPairedEnd <- pairedEnd(fds[,samples(fds) == sampleID,drop=FALSE])[[1]]
doAutosort <- isPairedEnd

# check cache if available
Expand Down

0 comments on commit 4a15970

Please sign in to comment.