Commit information:
Commit id: 32762b6bb7445f8b4a96ff02b0edc20c1ef6a1e2
Commit message:
bumped version. Fixed unit test as per changes in SummarizedExperiment. Fixed use of :::
Committed by Kasper Daniel Hansen <kasperdanielhansen at gmail.com>
Commit date: 2014-03-22T22:57:39-04:00
Commit id: 9ddfece19dcb7771cab2136890646b4cb491725e
Commit message:
forgot to stage files in previous commit
Committed by Kasper Daniel Hansen <kasperdanielhansen at gmail.com>
Commit date: 2014-03-22T22:58:11-04:00
Commit id: 3b64624fffff66918dfbcb255ad38a34f63be09f
Commit message:
Merge branch 'master' of github.com:kasperdanielhansen/bsseq
Committed by Kasper Daniel Hansen <kasperdanielhansen at gmail.com>
Commit date: 2014-03-22T23:22:50-04:00
From: Bioconductor Git-SVN Bridge <bioc-sync@bioconductor.org>
git-svn-id: https://hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/bsseq@87756 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,5 +1,5 @@ |
1 | 1 |
Package: bsseq |
2 |
-Version: 0.11.5 |
|
2 |
+Version: 0.99.0 |
|
3 | 3 |
Title: Analyze, manage and store bisulfite sequencing data |
4 | 4 |
Description: Tools for analyzing and visualizing bisulfite sequencing data |
5 | 5 |
Authors@R: c(person(c("Kasper", "Daniel"), "Hansen", role = c("aut", "cre"), |
... | ... |
@@ -10,7 +10,7 @@ Imports: scales, stats, graphics, Biobase, locfit |
10 | 10 |
Suggests: RUnit, bsseqData |
11 | 11 |
Collate: hasGRanges.R BSseq_class.R BSseqTstat_class.R BSseq_utils.R combine.R |
12 | 12 |
utils.R read.bsmooth.R read.bismark.R BSmooth.R BSmooth.tstat.R dmrFinder.R |
13 |
- gof_stats.R plotting.R fisher.R fixes.R |
|
13 |
+ gof_stats.R plotting.R fisher.R |
|
14 | 14 |
License: Artistic-2.0 |
15 | 15 |
LazyData: yes |
16 | 16 |
biocViews: DNAMethylation |
... | ... |
@@ -3,7 +3,7 @@ setClass("BSseq", contains = "SummarizedExperiment", |
3 | 3 |
parameters = "list")) |
4 | 4 |
|
5 | 5 |
setValidity("BSseq", function(object) { |
6 |
- msg <- validMsg(NULL, bsseq:::.checkAssayNames(object, c("Cov", "M"))) |
|
6 |
+ msg <- validMsg(NULL, .checkAssayNames(object, c("Cov", "M"))) |
|
7 | 7 |
if(class(rowData(object)) != "GRanges") |
8 | 8 |
msg <- validMsg(msg, sprintf("object of class '%s' needs to have a 'GRanges' in slot 'rowData'", class(object))) |
9 | 9 |
## benchmarking shows that min(assay()) < 0 is faster than any(assay() < 0) if it is false |
... | ... |
@@ -12,8 +12,8 @@ dmrFinder <- function(BSseqTstat, cutoff = NULL, qcutoff = c(0.025, 0.975), |
12 | 12 |
direction[is.na(direction)] <- 0L |
13 | 13 |
chrs <- as.character(seqnames(BSseqTstat@gr)) |
14 | 14 |
positions <- start(BSseqTstat) |
15 |
- regions <- bsseq:::regionFinder3(direction, chr = chrs, pos = positions, |
|
16 |
- maxGap = maxGap, verbose = subverbose) |
|
15 |
+ regions <- regionFinder3(direction, chr = chrs, positions = positions, |
|
16 |
+ maxGap = maxGap, verbose = subverbose) |
|
17 | 17 |
if(is.null(regions$down) && is.null(regions$up)) |
18 | 18 |
return(NULL) |
19 | 19 |
if(verbose) cat("[dmrFinder] creating dmr data.frame\n") |
20 | 20 |
deleted file mode 100644 |
... | ... |
@@ -1,78 +0,0 @@ |
1 |
-## findOverlaps_mclapply <- function (query, subject, maxgap = 0L, minoverlap = 1L, |
|
2 |
-## type = c("any", "start", "end", "within", "equal"), |
|
3 |
-## select = c("all", "first"), ignore.strand = FALSE, |
|
4 |
-## mc.cores = 1, mc.preschedule = TRUE, verbose = FALSE, ...) { |
|
5 |
-## if(!is(query, "GenomicRanges") || !is(subject, "GenomicRanges")) |
|
6 |
-## stop("findOverlaps_mclapply needs 'query' and 'subject' to be 'GenomicRanges'") |
|
7 |
-## if (!isSingleNumber(maxgap) || maxgap < 0) |
|
8 |
-## stop("'maxgap' must be a non-negative integer") |
|
9 |
-## type <- match.arg(type) |
|
10 |
-## select <- match.arg(select) |
|
11 |
-## seqinfo <- merge(seqinfo(query), seqinfo(subject)) |
|
12 |
-## DIM <- c(length(query), length(subject)) |
|
13 |
-## if (min(DIM) == 0L) { |
|
14 |
-## matchMatrix <- matrix(integer(0), nrow = 0L, ncol = 2L, |
|
15 |
-## dimnames = list(NULL, c("queryHits", "subjectHits"))) |
|
16 |
-## } |
|
17 |
-## else { |
|
18 |
-## querySeqnames <- seqnames(query) |
|
19 |
-## querySplitRanges <- splitRanges(querySeqnames) |
|
20 |
-## uniqueQuerySeqnames <- names(querySplitRanges)[sapply(querySplitRanges, length) > 0] # FIX: only keep seqnames with ranges |
|
21 |
-## subjectSeqnames <- seqnames(subject) |
|
22 |
-## subjectSplitRanges <- splitRanges(subjectSeqnames) |
|
23 |
-## uniqueSubjectSeqnames <- names(subjectSplitRanges)[sapply(subjectSplitRanges, length) > 0] # FIX: only keep seqnames with ranges |
|
24 |
-## commonSeqnames <- intersect(uniqueQuerySeqnames, |
|
25 |
-## uniqueSubjectSeqnames) |
|
26 |
-## if (ignore.strand) { |
|
27 |
-## queryStrand <- rep.int(1L, length(query)) |
|
28 |
-## subjectStrand <- rep.int(1L, length(subject)) |
|
29 |
-## } |
|
30 |
-## else { |
|
31 |
-## queryStrand <- strand(query) |
|
32 |
-## levels(queryStrand) <- c("1", "-1", "0") |
|
33 |
-## queryStrand@values <- as.integer(as.character(runValue(queryStrand))) |
|
34 |
-## queryStrand <- as.vector(queryStrand) |
|
35 |
-## subjectStrand <- strand(subject) |
|
36 |
-## levels(subjectStrand) <- c("1", "-1", "0") |
|
37 |
-## subjectStrand@values <- as.integer(as.character(runValue(subjectStrand))) |
|
38 |
-## subjectStrand <- as.vector(subjectStrand) |
|
39 |
-## } |
|
40 |
-## queryRanges <- unname(ranges(query)) |
|
41 |
-## subjectRanges <- unname(ranges(subject)) |
|
42 |
-## matchMatrix <- do.call(rbind, mclapply(commonSeqnames, |
|
43 |
-## function(seqnm) { |
|
44 |
-## if(verbose) cat(seqnm, "\n") # FIX : added verbosity |
|
45 |
-## if (isCircular(seqinfo)[seqnm] %in% TRUE) |
|
46 |
-## circle.length <- seqlengths(seqinfo)[seqnm] |
|
47 |
-## else circle.length <- NA |
|
48 |
-## qIdxs <- querySplitRanges[[seqnm]] |
|
49 |
-## sIdxs <- subjectSplitRanges[[seqnm]] |
|
50 |
-## ## FIX: added ::: tpo get .findOverlaps.circle |
|
51 |
-## overlaps <- GenomicRanges:::.findOverlaps.circle(circle.length, |
|
52 |
-## seqselect(queryRanges, qIdxs), seqselect(subjectRanges, |
|
53 |
-## sIdxs), maxgap, minoverlap, type) |
|
54 |
-## qHits <- queryHits(overlaps) |
|
55 |
-## sHits <- subjectHits(overlaps) |
|
56 |
-## matches <- cbind(queryHits = as.integer(qIdxs)[qHits], |
|
57 |
-## subjectHits = as.integer(sIdxs)[sHits]) |
|
58 |
-## matches[which(seqselect(queryStrand, qIdxs)[qHits] * |
|
59 |
-## seqselect(subjectStrand, sIdxs)[sHits] != |
|
60 |
-## -1L), , drop = FALSE] |
|
61 |
-## }, mc.cores = mc.cores, mc.preschedule = mc.preschedule)) |
|
62 |
-## if (is.null(matchMatrix)) { |
|
63 |
-## matchMatrix <- matrix(integer(0), nrow = 0L, |
|
64 |
-## ncol = 2L, dimnames = list(NULL, c("queryHits", |
|
65 |
-## "subjectHits"))) |
|
66 |
-## } |
|
67 |
-## matchMatrix <- matchMatrix[IRanges:::orderIntegerPairs(matchMatrix[, |
|
68 |
-## 1L], matchMatrix[, 2L]), , drop = FALSE] |
|
69 |
-## } |
|
70 |
-## if (select == "all") { |
|
71 |
-## new("Hits", queryHits = unname(matchMatrix[, 1L]), |
|
72 |
-## subjectHits = unname(matchMatrix[, 2L]), queryLength = DIM[1], |
|
73 |
-## subjectLength = DIM[2]) |
|
74 |
-## } |
|
75 |
-## else { |
|
76 |
-## IRanges:::.hitsMatrixToVector(matchMatrix, length(query)) |
|
77 |
-## } |
|
78 |
-## } |
... | ... |
@@ -176,7 +176,7 @@ plotManyRegions <- function(BSseq, regions = NULL, extend = 0, main = "", addReg |
176 | 176 |
coverage <- getCoverage(BSseq) |
177 | 177 |
|
178 | 178 |
## get col, lwd, lty |
179 |
- colEtc <- bsseq:::.bsGetCol(object = BSseq, col = col, lty = lty, lwd = lwd) |
|
179 |
+ colEtc <- .bsGetCol(object = BSseq, col = col, lty = lty, lwd = lwd) |
|
180 | 180 |
|
181 | 181 |
## The actual plotting |
182 | 182 |
plot(positions[1], 0.5, type = "n", xaxt = "n", yaxt = "n", |
... | ... |
@@ -224,10 +224,10 @@ plotRegion <- function(BSseq, region = NULL, extend = 0, main = "", addRegions = |
224 | 224 |
else |
225 | 225 |
layout(matrix(1:3, ncol = 1), heights = c(2,2,1)) |
226 | 226 |
|
227 |
- bsseq:::.plotSmoothData(BSseq = BSseq, region = region, extend = extend, addRegions = addRegions, |
|
228 |
- col = col, lty = lty, lwd = lwd, regionCol = regionCol, |
|
229 |
- addTicks = addTicks, addPoints = addPoints, |
|
230 |
- pointsMinCov = pointsMinCov, highlightMain = highlightMain) |
|
227 |
+ .plotSmoothData(BSseq = BSseq, region = region, extend = extend, addRegions = addRegions, |
|
228 |
+ col = col, lty = lty, lwd = lwd, regionCol = regionCol, |
|
229 |
+ addTicks = addTicks, addPoints = addPoints, |
|
230 |
+ pointsMinCov = pointsMinCov, highlightMain = highlightMain) |
|
231 | 231 |
gr <- .bsGetGr(BSseq, region, extend) |
232 | 232 |
|
233 | 233 |
if(!is.null(BSseqTstat)) { |
... | ... |
@@ -237,17 +237,17 @@ plotRegion <- function(BSseq, region = NULL, extend = 0, main = "", addRegions = |
237 | 237 |
axis(side = 2, at = c(-5,0,5)) |
238 | 238 |
abline(h = 0, col = "grey60") |
239 | 239 |
mapply(function(stat, col, lty, lwd) { |
240 |
- bsseq:::.bsPlotLines(start(BSseqTstat), BSseqTstat@stats[, stat], |
|
241 |
- lty = lty, plotRange = c(start(gr), end(gr)), col = col, lwd = lwd) |
|
240 |
+ .bsPlotLines(start(BSseqTstat), BSseqTstat@stats[, stat], |
|
241 |
+ lty = lty, plotRange = c(start(gr), end(gr)), col = col, lwd = lwd) |
|
242 | 242 |
}, stat = stat, col = stat.col, lty = stat.lty, lwd = stat.lwd) |
243 | 243 |
} |
244 | 244 |
|
245 | 245 |
if(!is.null(annoTrack)) |
246 |
- bsseq:::plotAnnoTrack(gr, annoTrack) |
|
246 |
+ plotAnnoTrack(gr, annoTrack) |
|
247 | 247 |
|
248 | 248 |
if(!is.null(main)) { |
249 |
- main <- bsseq:::.bsPlotTitle(gr = region, extend = extend, main = main, |
|
250 |
- mainWithWidth = mainWithWidth) |
|
249 |
+ main <- .bsPlotTitle(gr = region, extend = extend, main = main, |
|
250 |
+ mainWithWidth = mainWithWidth) |
|
251 | 251 |
mtext(side = 3, text = main, outer = TRUE, cex = 1) |
252 | 252 |
} |
253 | 253 |
return(invisible(NULL)) |
... | ... |
@@ -472,9 +472,9 @@ parsingPipeline <- function(dirs, qualityCutoff = 20, outDir, seqnames = NULL, |
472 | 472 |
base <- basename(dir) |
473 | 473 |
cat("parsing, ") |
474 | 474 |
ptime1 <- proc.time() |
475 |
- raw <- bsseq:::read.bsmoothDirRaw(file.path(dir, subdir), |
|
476 |
- keepCycle = TRUE, keepFilt = TRUE, |
|
477 |
- verbose = FALSE) |
|
475 |
+ raw <- read.bsmoothDirRaw(file.path(dir, subdir), |
|
476 |
+ keepCycle = TRUE, keepFilt = TRUE, |
|
477 |
+ verbose = FALSE) |
|
478 | 478 |
assign(paste0(base, ".raw"), raw) |
479 | 479 |
ptime2 <- proc.time() |
480 | 480 |
stime <- (ptime2 - ptime1)[3] |
... | ... |
@@ -487,8 +487,8 @@ parsingPipeline <- function(dirs, qualityCutoff = 20, outDir, seqnames = NULL, |
487 | 487 |
file = file.path(outDir, paste0(base, ".raw.rda"))) |
488 | 488 |
cat("converting, ") |
489 | 489 |
ptime1 <- proc.time() |
490 |
- bsseq <- bsseq:::sampleRawToBSseq(raw, qualityCutoff = qualityCutoff, |
|
491 |
- sampleName = base) |
|
490 |
+ bsseq <- sampleRawToBSseq(raw, qualityCutoff = qualityCutoff, |
|
491 |
+ sampleName = base) |
|
492 | 492 |
seqlevels(bsseq)[seqlevels(bsseq) == "chrgi|9626243|ref|NC_001416.1|"] <- "chrLambda" |
493 | 493 |
ptime2 <- proc.time() |
494 | 494 |
stime <- (ptime2 - ptime1)[3] |
... | ... |
@@ -20,8 +20,8 @@ test_BSseq <- function() { |
20 | 20 |
checkEquals(dim(BStest), c(3,3)) |
21 | 21 |
checkEquals(nrow(BStest), 3) |
22 | 22 |
checkEquals(ncol(BStest), 3) |
23 |
- checkEquals(getCoverage(BStest, type = "M"), unname(M)) |
|
24 |
- checkEquals(getCoverage(BStest, type = "Cov"), unname(M + 2)) |
|
23 |
+ checkEquals(unname(getCoverage(BStest, type = "M")), unname(M)) |
|
24 |
+ checkEquals(unname(getCoverage(BStest, type = "Cov")), unname(M + 2)) |
|
25 | 25 |
checkEquals(sampleNames(BStest), colnames(M)) |
26 | 26 |
|
27 | 27 |
BStest2 <- BSseq(pos = 3:1, chr = rep("chr1", 3), M = M[3:1,], |