Browse code

replace with lengths for better performance

Ge Tan authored on 12/10/2016 12:08:30
Showing 1 changed files

  • R/GRB.R index 84b3848..8bd2509 100644
... ...
@@ -93,7 +93,7 @@ makeGRBs <- function(x, winSize=NULL, genes=NULL, ratio=1,
93 93
   for(i in 1:length(xList)){
94 94
     hitsCNEs <- findOverlaps(xList[[i]], clusterRanges,
95 95
                              ignore.strand=TRUE, type="within")
96
-    cnes <- sapply(split(queryHits(hitsCNEs), subjectHits(hitsCNEs)), length)
96
+    cnes <- lengths(split(queryHits(hitsCNEs), subjectHits(hitsCNEs)))
97 97
     mcols(clusterRanges)[[names(xList)[i]]] <- 0L
98 98
     mcols(clusterRanges)[[names(xList)[i]]][as.integer(names(cnes))] <- cnes
99 99
   }