git-svn-id: https://hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/bsseq@81150 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,4 +1,4 @@ |
1 |
-makeClusters <- function(hasGRanges, maxGap = 10^8, mc.cores = 1) { |
|
1 |
+makeClusters <- function(hasGRanges, maxGap = 10^8) { |
|
2 | 2 |
chrOrder <- as.character(runValue(seqnames(hasGRanges))) |
3 | 3 |
if(anyDuplicated(chrOrder)) |
4 | 4 |
stop("argument 'hasGRanges' is not properly order") |
... | ... |
@@ -12,7 +12,7 @@ makeClusters <- function(hasGRanges, maxGap = 10^8, mc.cores = 1) { |
12 | 12 |
}))) # are the clusters ordered within the chromosome? This is probably guranteed |
13 | 13 |
clusters <- Reduce(c, clusters.sp[chrOrder]) |
14 | 14 |
stopifnot(all(chrOrder == runValue(seqnames(clusters)))) |
15 |
- ov <- bsseq:::findOverlaps_mclapply(grBase, clusters, mc.cores = mc.cores) |
|
15 |
+ ov <- findOverlaps(grBase, clusters) |
|
16 | 16 |
clusterIdx <- split(as.matrix(ov)[,1], as.matrix(ov)[,2]) |
17 | 17 |
names(clusterIdx) <- NULL |
18 | 18 |
clusterIdx |
... | ... |
@@ -66,7 +66,7 @@ BSmooth <- function(BSseq, ns = 70, h = 1000, maxGap = 10^8, parallelBy = c("sam |
66 | 66 |
parallelBy <- match.arg(parallelBy) |
67 | 67 |
if(verbose) cat("[BSmooth] preprocessing ... ") |
68 | 68 |
ptime1 <- proc.time() |
69 |
- clusterIdx <- makeClusters(BSseq, maxGap = maxGap, mc.cores = mc.cores) |
|
69 |
+ clusterIdx <- makeClusters(BSseq, maxGap = maxGap) |
|
70 | 70 |
ptime2 <- proc.time() |
71 | 71 |
stime <- (ptime2 - ptime1)[3] |
72 | 72 |
if(verbose) cat(sprintf("done in %.1f sec\n", stime)) |
... | ... |
@@ -59,7 +59,7 @@ BSmooth.tstat <- function(BSseq, group1, group2, estimate.var = c("same", "paire |
59 | 59 |
|
60 | 60 |
if(verbose) cat("[BSmooth.tstat] preprocessing ... ") |
61 | 61 |
ptime1 <- proc.time() |
62 |
- clusterIdx <- makeClusters(BSseq, maxGap = maxGap, mc.cores = mc.cores) |
|
62 |
+ clusterIdx <- makeClusters(BSseq, maxGap = maxGap) |
|
63 | 63 |
ptime2 <- proc.time() |
64 | 64 |
stime <- (ptime2 - ptime1)[3] |
65 | 65 |
if(verbose) cat(sprintf("done in %.1f sec\n", stime)) |
... | ... |
@@ -20,11 +20,7 @@ collapseBSseq <- function(BSseq, columns) { |
20 | 20 |
} |
21 | 21 |
|
22 | 22 |
chrSelectBSseq <- function(BSseq, seqnames = NULL, order = FALSE) { |
23 |
- gr <- GRanges(seqnames = seqnames, |
|
24 |
- ranges = IRanges(start = rep(1, length(seqnames)), |
|
25 |
- end = rep(10^9, length(seqnames)))) |
|
26 |
- BSseq <- subsetByOverlaps(BSseq, gr) |
|
27 |
- seqlevels(BSseq) <- seqlevels(BSseq)[seqlevels(BSseq) %in% seqnames] |
|
23 |
+ seqlevels(BSseq, force = TRUE) <- seqnames |
|
28 | 24 |
if(order) |
29 | 25 |
BSseq <- orderBSseq(BSseq, seqOrder = seqnames) |
30 | 26 |
BSseq |
... | ... |
@@ -32,18 +28,9 @@ chrSelectBSseq <- function(BSseq, seqnames = NULL, order = FALSE) { |
32 | 28 |
|
33 | 29 |
|
34 | 30 |
orderBSseq <- function(BSseq, seqOrder = NULL) { |
35 |
- splitNames <- splitRanges(seqnames(BSseq)) |
|
36 |
- if(is.null(seqOrder)) |
|
37 |
- seqOrder <- names(splitNames) |
|
38 |
- else |
|
39 |
- seqOrder <- seqOrder[seqOrder %in% names(splitNames)] |
|
40 |
- splitOd <- lapply(seqOrder, function(nam) { |
|
41 |
- seqRanges <- seqselect(ranges(granges(BSseq)), splitNames[[nam]]) |
|
42 |
- as.integer(unlist(splitNames[[nam]])[order(start(seqRanges))]) |
|
43 |
- }) |
|
44 |
- BSseq <- BSseq[do.call(c, splitOd)] |
|
45 |
- seqlevels(BSseq) <- seqOrder |
|
46 |
- BSseq |
|
31 |
+ if(!is.null(seqOrder)) |
|
32 |
+ seqlevels(BSseq, force = TRUE) <- seqOrder |
|
33 |
+ BSseq[order(granges(BSseq))] |
|
47 | 34 |
} |
48 | 35 |
|
49 | 36 |
|
... | ... |
@@ -1,78 +1,78 @@ |
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 (!IRanges:::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 |
-} |
|
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 |
+## } |
... | ... |
@@ -86,10 +86,10 @@ setMethod("subsetByOverlaps", |
86 | 86 |
function(query, subject, maxgap = 0L, minoverlap = 1L, |
87 | 87 |
type = c("any", "start", "end", "within", "equal"), |
88 | 88 |
ignore.strand = FALSE, ...) { |
89 |
- ov <- findOverlaps_mclapply(query = granges(query), subject = subject, |
|
90 |
- maxgap = maxgap, minoverlap = minoverlap, |
|
91 |
- type = match.arg(type), select = "first", |
|
92 |
- ignore.strand = ignore.strand, ... ) |
|
89 |
+ ov <- findOverlaps(query = granges(query), subject = subject, |
|
90 |
+ maxgap = maxgap, minoverlap = minoverlap, |
|
91 |
+ type = match.arg(type), select = "first", |
|
92 |
+ ignore.strand = ignore.strand, ... ) |
|
93 | 93 |
query[!is.na(ov)] |
94 | 94 |
}) |
95 | 95 |
|
... | ... |
@@ -98,10 +98,10 @@ setMethod("subsetByOverlaps", |
98 | 98 |
function(query, subject, maxgap = 0L, minoverlap = 1L, |
99 | 99 |
type = c("any", "start", "end", "within", "equal"), |
100 | 100 |
ignore.strand = FALSE, ...) { |
101 |
- ov <- findOverlaps_mclapply(query = granges(query), subject = granges(subject), |
|
102 |
- maxgap = maxgap, minoverlap = minoverlap, |
|
103 |
- type = match.arg(type), select = "first", |
|
104 |
- ignore.strand = ignore.strand, ... ) |
|
101 |
+ ov <- findOverlaps(query = granges(query), subject = granges(subject), |
|
102 |
+ maxgap = maxgap, minoverlap = minoverlap, |
|
103 |
+ type = match.arg(type), select = "first", |
|
104 |
+ ignore.strand = ignore.strand, ... ) |
|
105 | 105 |
query[!is.na(ov)] |
106 | 106 |
}) |
107 | 107 |
|
... | ... |
@@ -110,10 +110,10 @@ setMethod("subsetByOverlaps", |
110 | 110 |
function(query, subject, maxgap = 0L, minoverlap = 1L, |
111 | 111 |
type = c("any", "start", "end", "within", "equal"), |
112 | 112 |
ignore.strand = FALSE, ...) { |
113 |
- ov <- findOverlaps_mclapply(query = query, subject = granges(subject), |
|
114 |
- maxgap = maxgap, minoverlap = minoverlap, |
|
115 |
- type = match.arg(type), select = "first", |
|
116 |
- ignore.strand = ignore.strand, ... ) |
|
113 |
+ ov <- findOverlaps(query = query, subject = granges(subject), |
|
114 |
+ maxgap = maxgap, minoverlap = minoverlap, |
|
115 |
+ type = match.arg(type), select = "first", |
|
116 |
+ ignore.strand = ignore.strand, ... ) |
|
117 | 117 |
query[!is.na(ov)] |
118 | 118 |
}) |
119 | 119 |
|
... | ... |
@@ -122,10 +122,10 @@ setMethod("findOverlaps", |
122 | 122 |
function (query, subject, maxgap = 0L, minoverlap = 1L, |
123 | 123 |
type = c("any", "start", "end", "within", "equal"), |
124 | 124 |
select = c("all", "first"), ignore.strand = FALSE, ...) { |
125 |
- findOverlaps_mclapply(query = granges(query), subject = subject, |
|
126 |
- maxgap = maxgap, minoverlap = minoverlap, |
|
127 |
- type = match.arg(type), select = match.arg(select), |
|
128 |
- ignore.strand = ignore.strand, ...) |
|
125 |
+ findOverlaps(query = granges(query), subject = subject, |
|
126 |
+ maxgap = maxgap, minoverlap = minoverlap, |
|
127 |
+ type = match.arg(type), select = match.arg(select), |
|
128 |
+ ignore.strand = ignore.strand, ...) |
|
129 | 129 |
}) |
130 | 130 |
|
131 | 131 |
setMethod("findOverlaps", |
... | ... |
@@ -133,10 +133,10 @@ setMethod("findOverlaps", |
133 | 133 |
function (query, subject, maxgap = 0L, minoverlap = 1L, |
134 | 134 |
type = c("any", "start", "end", "within", "equal"), |
135 | 135 |
select = c("all", "first"), ignore.strand = FALSE, ...) { |
136 |
- findOverlaps_mclapply(query = granges(query), subject = granges(subject), |
|
137 |
- maxgap = maxgap, minoverlap = minoverlap, |
|
138 |
- type = match.arg(type), select = match.arg(select), |
|
139 |
- ignore.strand = ignore.strand, ...) |
|
136 |
+ findOverlaps(query = granges(query), subject = granges(subject), |
|
137 |
+ maxgap = maxgap, minoverlap = minoverlap, |
|
138 |
+ type = match.arg(type), select = match.arg(select), |
|
139 |
+ ignore.strand = ignore.strand, ...) |
|
140 | 140 |
}) |
141 | 141 |
|
142 | 142 |
setMethod("findOverlaps", |
... | ... |
@@ -144,10 +144,10 @@ setMethod("findOverlaps", |
144 | 144 |
function (query, subject, maxgap = 0L, minoverlap = 1L, |
145 | 145 |
type = c("any", "start", "end", "within", "equal"), |
146 | 146 |
select = c("all", "first"), ignore.strand = FALSE, ...) { |
147 |
- findOverlaps_mclapply(query = query, subject = granges(subject), |
|
148 |
- maxgap = maxgap, minoverlap = minoverlap, |
|
149 |
- type = match.arg(type), select = match.arg(select), |
|
150 |
- ignore.strand = ignore.strand, ...) |
|
147 |
+ findOverlaps(query = query, subject = granges(subject), |
|
148 |
+ maxgap = maxgap, minoverlap = minoverlap, |
|
149 |
+ type = match.arg(type), select = match.arg(select), |
|
150 |
+ ignore.strand = ignore.strand, ...) |
|
151 | 151 |
}) |
152 | 152 |
|
153 | 153 |
setMethod("[", "hasGRanges", function(x, i, ...) { |
... | ... |
@@ -12,6 +12,8 @@ |
12 | 12 |
\alias{sampleNames,BSseq-method} |
13 | 13 |
\alias{sampleNames<-,BSseq,ANY-method} |
14 | 14 |
\alias{updateObject,BSseq-method} |
15 |
+\alias{assays,BSseq-method} |
|
16 |
+\alias{assayNames} |
|
15 | 17 |
\alias{show,BSseq-method} |
16 | 18 |
\alias{getBSseq} |
17 | 19 |
\alias{collapseBSseq} |
... | ... |
@@ -133,6 +135,15 @@ slots for representing smoothed data. This class is an extension of |
133 | 135 |
\sQuote{BSseq} objects. You can update old serialized (saved) |
134 | 136 |
objects by invoking \code{x <- udateObject(x)}. |
135 | 137 |
} |
138 |
+\section{Assays}{ |
|
139 |
+ This class overrides the default implementation of \code{assays} to |
|
140 |
+ make it faster. Per default, no names are added to the returned data |
|
141 |
+ matrices. |
|
142 |
+ |
|
143 |
+ Assay names can conveniently be obtained by the function |
|
144 |
+ \code{assayNames} |
|
145 |
+} |
|
146 |
+ |
|
136 | 147 |
\author{ |
137 | 148 |
Kasper Daniel Hansen \email{khansen@jhsph.edu} |
138 | 149 |
} |
... | ... |
@@ -8,14 +8,14 @@ |
8 | 8 |
object. |
9 | 9 |
} |
10 | 10 |
\usage{ |
11 |
-getStats(BSseqTstat, regions = NULL, column = "tstat.corrected") |
|
11 |
+getStats(BSseqTstat, regions = NULL, stat = "tstat.corrected") |
|
12 | 12 |
} |
13 | 13 |
\arguments{ |
14 | 14 |
\item{BSseqTstat}{An object of class \code{BSseqTstat}.} |
15 | 15 |
\item{regions}{An optional \code{data.frame} or |
16 | 16 |
\code{GenomicRanges} object specifying a number of genomic |
17 | 17 |
regions.} |
18 |
- \item{column}{Which statistics column should be obtained.} |
|
18 |
+ \item{stat}{Which statistics column should be obtained.} |
|
19 | 19 |
} |
20 | 20 |
\value{ |
21 | 21 |
An object of class \code{data.frame} possible restricted to the |
... | ... |
@@ -11,14 +11,16 @@ |
11 | 11 |
\usage{ |
12 | 12 |
plotRegion(BSseq, region = NULL, extend = 0, main = "", |
13 | 13 |
addRegions = NULL, annoTrack = NULL, col = NULL, lty = NULL, |
14 |
- lwd = NULL, BSseqTstat = NULL, mainWithWidth = TRUE, |
|
15 |
- regionCol = alpha("red", 0.1), addTicks = TRUE, |
|
14 |
+ lwd = NULL, BSseqTstat = NULL, stat = "tstat.corrected", |
|
15 |
+ stat.col = "black", stat.lwd = 1, stat.lty = 1, stat.ylim = c(-8, 8), |
|
16 |
+ mainWithWidth = TRUE, regionCol = alpha("red", 0.1), addTicks = TRUE, |
|
16 | 17 |
addPoints = FALSE, pointsMinCov = 5, highlightMain = FALSE) |
17 | 18 |
|
18 | 19 |
plotManyRegions(BSseq, regions = NULL, extend = 0, main = "", |
19 | 20 |
addRegions = NULL, annoTrack = NULL, col = NULL, lty = NULL, |
20 |
- lwd = NULL, BSseqTstat = NULL, mainWithWidth = TRUE, |
|
21 |
- regionCol = alpha("red", 0.1), addTicks = TRUE, |
|
21 |
+ lwd = NULL, BSseqTstat = NULL, stat = "tstat.corrected", |
|
22 |
+ stat.col = "black", stat.lwd = 1, stat.lty = 1, stat.ylim = c(-8, 8), |
|
23 |
+ mainWithWidth = TRUE, regionCol = alpha("red", 0.1), addTicks = TRUE, |
|
22 | 24 |
addPoints = FALSE, pointsMinCov = 5, highlightMain = FALSE, |
23 | 25 |
verbose = TRUE) |
24 | 26 |
} |
... | ... |
@@ -44,7 +46,13 @@ plotManyRegions(BSseq, regions = NULL, extend = 0, main = "", |
44 | 46 |
\item{lty}{The line type of the methylation estimates, see details.} |
45 | 47 |
\item{lwd}{The line width of the methylation estimates, see details.} |
46 | 48 |
\item{BSseqTstat}{An object of class \code{BSseqTstat}. If present, |
47 |
- a new panel will be shown with the t-statistics.} |
|
49 |
+ a new panel will be shown with the t-statistics.} |
|
50 |
+ \item{stat}{Which statistics will be plotted (only used is |
|
51 |
+ \code{BSseqTstat} is not \code{NULL}.)} |
|
52 |
+ \item{stat.col}{color for the statistics plot.} |
|
53 |
+ \item{stat.lwd}{line width for the statistics plot.} |
|
54 |
+ \item{stat.lty}{line type for the statistics plot.} |
|
55 |
+ \item{stat.ylim}{y-limits for the statistics plot.} |
|
48 | 56 |
\item{mainWithWidth}{Should the default title include information |
49 | 57 |
about width of the plot region.} |
50 | 58 |
\item{regionCol}{The color used for highlighting the region.} |