### R code from vignette source 'vignettes/GenomicRanges/inst/doc/countGenomicOverlaps.Rnw' ################################################### ### code chunk number 1: firstExample (eval = FALSE) ################################################### ## library(TxDb.Hsapiens.UCSC.hg18.knownGene) ## txdb <- Hsapiens_UCSC_hg18_knownGene_TxDb ## ranges <- exonsBy(txdb, "tx") ## bamFiles <- c("sample1.bam", "sample2.bam") ## ## countsTable <- ## as.data.frame(tx_id=rep(names(ranges), elementLengths(ranges)), ## exon_id=values(unlist(ranges))[["exon_id"]], ## sapply(bamFiles, function(bamFile, ranges) { ## aln <- readGappedAlignments(bamFile) ## countGenomicOverlaps(ranges, aln) ## }, ranges)) ################################################### ### code chunk number 2: data ################################################### library(GenomicFeatures) rng1 <- function(s, w) GRanges(seq="chr1", IRanges(s, width=w), strand="+") rng2 <- function(s, w) GRanges(seq="chr2", IRanges(s, width=w), strand="+") query <- GRangesList(G1=rng1(1000, 500), G2=rng2(2000, 900), G3=rng1(c(3000, 3600), c(500, 300)), G4=rng2(c(7000, 7500), c(600, 300)), G5=rng2(c(9000, 9000), c(300, 600)), G6=rng1(4000, 500), G7=rng1(c(4300, 4500), c(400, 400)), G8=rng2(3000, 500), G9=rng1(c(5000, 5600), c(500, 300)), G10=rng1(6000, 500), G11=rng1(6600, 400)) subj <- GRangesList(read1=rng1(1400, 500), read2=rng2(2700, 100), read3=rng1(3400, 300), read4=rng2(7100, 600), read5=rng2(9000, 200), read6=rng1(4200, 500), read7=rng2(c(3100, 3300), 50), read8=rng1(c(5400, 5600), 50), read9=rng1(c(6400, 6600), 50)) ################################################### ### code chunk number 3: typeAny ################################################### none <- countGenomicOverlaps(query, subj, type="any", resolution="none") divide <- countGenomicOverlaps(query, subj, type="any", resolution="divide") uniqueDisjoint <- countGenomicOverlaps(query, subj, type="any", resolution="uniqueDisjoint") res_any <- data.frame( none = none, divide = divide, uniqueDisjoint = uniqueDisjoint) rownames(res_any) <- paste("F", seq_len(16), sep="") res_any ################################################### ### code chunk number 4: typeWithin ################################################### none <- countGenomicOverlaps(query, subj, type="within", resolution="none") divide <- countGenomicOverlaps(query, subj, type="within", resolution="divide") res_within <- data.frame(none = none, divide = divide) rownames(res_within) <- paste("F", seq_len(16), sep="") res_within