################################################### ### chunk number 1: setup ################################################### library(chipseq) library(GenomicFeatures) library(lattice) ################################################### ### chunk number 2: preprocess eval=FALSE ################################################### ## filter <- compose(chipseqFilter(), alignQualityFilter(15)) ## cstest <- seqapply(sampleFiles, function(file) { ## as(readAligned(file, filter), "GRanges") ## }) ## cstest <- cstest[seqnames(cstest) %in% c("chr10", "chr11", "chr12")] ################################################### ### chunk number 3: ################################################### data(cstest) cstest ################################################### ### chunk number 4: convert-cstest eval=FALSE ################################################### ## ## code used to convert the GenomeDataList to a GRangesList ## cstest <- seqapply(cstest, function(gd) { ## gr <- do.call(c, lapply(names(gd), function(chr) { ## pos <- gd[[chr]] ## starts <- c(pos[["+"]], pos[["-"]] - 23L) ## GRanges(chr, IRanges(starts, width = 24), ## rep(names(pos), elementLengths(pos))) ## })) ## }) ################################################### ### chunk number 5: ################################################### cstest$ctcf ################################################### ### chunk number 6: ################################################### library(BSgenome.Mmusculus.UCSC.mm9) seqlengths(cstest) <- seqlengths(Mmusculus) ################################################### ### chunk number 7: estimate.mean.fraglen ################################################### fraglen <- estimate.mean.fraglen(cstest$ctcf) fraglen[!is.na(fraglen)] ################################################### ### chunk number 8: ################################################### ctcf.ext <- resize(cstest$ctcf, width = 200) ctcf.ext ################################################### ### chunk number 9: ################################################### cov.ctcf <- coverage(ctcf.ext) cov.ctcf ################################################### ### chunk number 10: ################################################### islands <- slice(cov.ctcf, lower = 1) islands ################################################### ### chunk number 11: ################################################### viewSums(islands) viewMaxs(islands) nread.tab <- table(viewSums(islands) / 200) depth.tab <- table(viewMaxs(islands)) nread.tab[,1:10] depth.tab[,1:10] ################################################### ### chunk number 12: ################################################### islandReadSummary <- function(x) { g <- resize(x, 200) s <- slice(coverage(g), lower = 1) tab <- table(viewSums(s) / 200) df <- DataFrame(tab) colnames(df) <- c("chromosome", "nread", "count") df$nread <- as.integer(df$nread) df } ################################################### ### chunk number 13: ################################################### head(islandReadSummary(cstest$ctcf)) ################################################### ### chunk number 14: ################################################### nread.islands <- seqapply(cstest, islandReadSummary) nread.islands <- stack(nread.islands, "sample") nread.islands ################################################### ### chunk number 15: ################################################### xyplot(log(count) ~ nread | sample, as.data.frame(nread.islands), subset = (chromosome == "chr10" & nread <= 40), layout = c(1, 2), pch = 16, type = c("p", "g")) ################################################### ### chunk number 16: ################################################### plot(trellis.last.object()) ################################################### ### chunk number 17: ################################################### xyplot(log(count) ~ nread | sample, as.data.frame(nread.islands), subset = (chromosome == "chr10" & nread <= 40), layout = c(1, 2), pch = 16, type = c("p", "g"), panel = function(x, y, ...) { panel.lmline(x[1:2], y[1:2], col = "black") panel.xyplot(x, y, ...) }) ################################################### ### chunk number 18: ################################################### plot(trellis.last.object()) ################################################### ### chunk number 19: ################################################### islandDepthSummary <- function(x) { g <- resize(x, 200) s <- slice(coverage(g), lower = 1) tab <- table(viewMaxs(s) / 200) df <- DataFrame(tab) colnames(df) <- c("chromosome", "depth", "count") df$depth <- as.integer(df$depth) df } depth.islands <- seqapply(cstest, islandDepthSummary) depth.islands <- stack(depth.islands, "sample") xyplot(log(count) ~ depth | sample, as.data.frame(depth.islands), subset = (chromosome == "chr10" & depth <= 20), layout = c(1, 2), pch = 16, type = c("p", "g"), panel = function(x, y, ...) { lambda <- 2 * exp(y[2]) / exp(y[1]) null.est <- function(xx) { xx * log(lambda) - lambda - lgamma(xx + 1) } log.N.hat <- null.est(1) - y[1] panel.lines(1:10, -log.N.hat + null.est(1:10), col = "black") panel.xyplot(x, y, ...) }) ## depth.islands <- summarizeReads(cstest, summary.fun = islandDepthSummary) ################################################### ### chunk number 20: ################################################### plot(trellis.last.object()) ################################################### ### chunk number 21: islandDepthPlot ################################################### islandDepthPlot(cov.ctcf) ################################################### ### chunk number 22: peakCutoff ################################################### peakCutoff(cov.ctcf, fdr = 0.0001) ################################################### ### chunk number 23: ################################################### peaks.ctcf <- slice(cov.ctcf, lower = 8) peaks.ctcf ################################################### ### chunk number 24: peakSummary ################################################### peaks <- peakSummary(peaks.ctcf) ################################################### ### chunk number 25: ################################################### peak.depths <- viewMaxs(peaks.ctcf) cov.pos <- coverage(ctcf.ext[strand(ctcf.ext) == "+"]) cov.neg <- coverage(ctcf.ext[strand(ctcf.ext) == "-"]) peaks.pos <- Views(cov.pos, peaks.ctcf) peaks.neg <- Views(cov.neg, peaks.ctcf) wpeaks <- tail(order(peak.depths$chr10), 4) wpeaks ################################################### ### chunk number 26: ################################################### coverageplot(peaks.pos$chr10[wpeaks[1]], peaks.neg$chr10[wpeaks[1]]) ################################################### ### chunk number 27: ################################################### plot(trellis.last.object()) ################################################### ### chunk number 28: ################################################### coverageplot(peaks.pos$chr10[wpeaks[2]], peaks.neg$chr10[wpeaks[2]]) ################################################### ### chunk number 29: ################################################### plot(trellis.last.object()) ################################################### ### chunk number 30: ################################################### coverageplot(peaks.pos$chr10[wpeaks[3]], peaks.neg$chr10[wpeaks[3]]) ################################################### ### chunk number 31: ################################################### plot(trellis.last.object()) ################################################### ### chunk number 32: ################################################### coverageplot(peaks.pos$chr10[wpeaks[4]], peaks.neg$chr10[wpeaks[4]]) ################################################### ### chunk number 33: ################################################### plot(trellis.last.object()) ################################################### ### chunk number 34: ################################################### ## find peaks for GFP control cov.gfp <- coverage(resize(cstest$gfp, 200)) peaks.gfp <- slice(cov.gfp, lower = 8) peakSummary <- diffPeakSummary(peaks.gfp, peaks.ctcf) xyplot(asinh(sums2) ~ asinh(sums1) | space, data = as.data.frame(peakSummary), panel = function(x, y, ...) { panel.xyplot(x, y, ...) panel.abline(median(y - x), 1) }, type = c("p", "g"), alpha = 0.5, aspect = "iso") ################################################### ### chunk number 35: ################################################### plot(trellis.last.object()) ################################################### ### chunk number 36: ################################################### peakSummary <- within(peakSummary, { diffs <- asinh(sums2) - asinh(sums1) resids <- (diffs - median(diffs)) / mad(diffs) up <- resids > 2 down <- resids < -2 change <- ifelse(up, "up", ifelse(down, "down", "flat")) }) ################################################### ### chunk number 37: ################################################### db <- makeTranscriptDbFromUCSC("mm9") gregions <- transcripts(db) gregions ################################################### ### chunk number 38: ################################################### promoters <- flank(gregions, 1000, both = TRUE) ################################################### ### chunk number 39: ################################################### peakSummary$inPromoter <- peakSummary %in% promoters xtabs(~ inPromoter + change, peakSummary) ################################################### ### chunk number 40: ################################################### peakSummary$inUpstream <- peakSummary %in% flank(gregions, 20000) peakSummary$inGene <- peakSummary %in% gregions ################################################### ### chunk number 41: ################################################### sumtab <- as.data.frame(rbind(total = xtabs(~ change, peakSummary), promoter = xtabs(~ change, subset(peakSummary, inPromoter)), upstream = xtabs(~ change, subset(peakSummary, inUpstream)), gene = xtabs(~ change, subset(peakSummary, inGene)))) ##cbind(sumtab, ratio = round(sumtab[, "down"] / sumtab[, "up"], 3)) ################################################### ### chunk number 42: rtracklayer-upload eval=FALSE ################################################### ## library(rtracklayer) ## session <- browserSession() ## genome(session) <- "mm9" ## session$gfpCov <- cov.gfp ## session$gfpPeaks <- peaks.gfp ## session$ctcfCov <- cov.ctcf ## session$ctcfPeaks <- peaks.ctcf ################################################### ### chunk number 43: rtracklayer-view eval=FALSE ################################################### ## peak.ord <- order(unlist(peak.depths), decreasing=TRUE) ## peak.sort <- as(peaks.ctcf, "GRanges")[peak.ord] ## view <- browserView(session, peak.sort[1], full = c("gfpCov", "ctcfCov")) ################################################### ### chunk number 44: rtracklayer-view-10 eval=FALSE ################################################### ## top10 <- head(peak.sort, 10) ## for (i in seq(length(top10))) ## browserView(session, top10[i]) ################################################### ### chunk number 45: ################################################### sessionInfo()