git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@69874 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -55,3 +55,37 @@ test_GmapGenome_accessors <- function() { |
55 | 55 |
checkTrue(is(directory(gmapGenome), "GmapGenomeDirectory")) |
56 | 56 |
checkIdentical(genome(gmapGenome), genomeName) |
57 | 57 |
} |
58 |
+ |
|
59 |
+test_GmapGenome_spliceSites_replacement <- function() { |
|
60 |
+ library("TxDb.Hsapiens.UCSC.hg19.knownGene") |
|
61 |
+ txdb <- TxDb.Hsapiens.UCSC.hg19.knownGene |
|
62 |
+ getTP53Range <- function() { |
|
63 |
+ library(org.Hs.eg.db) |
|
64 |
+ eg <- org.Hs.egSYMBOL2EG[["TP53"]] |
|
65 |
+ txTP53 <- transcripts(TxDb.Hsapiens.UCSC.hg19.knownGene, |
|
66 |
+ vals = list(gene_id = eg)) |
|
67 |
+ rngs <- GRanges(ranges=IRanges(start(range(tx)), end(range(tx))), |
|
68 |
+ seqnames="chr17") |
|
69 |
+ rngs + 1e6 |
|
70 |
+ } |
|
71 |
+ rngTP53 <- getTP53Range() |
|
72 |
+ |
|
73 |
+ exonsByTx <- exonsBy(txdb, by="tx") |
|
74 |
+ exonsInRegion <- exonsByTx[exonsByTx %in% rngTP53] |
|
75 |
+ |
|
76 |
+ ##shift coords of retrieved exons so the ranges match the |
|
77 |
+ ##region of the genome used for this example |
|
78 |
+ shiftCoords <- function(x) { |
|
79 |
+ x <- exonsInRegion |
|
80 |
+ w <- width(x) |
|
81 |
+ r <- ranges(x) |
|
82 |
+ r <- r + start(rngTP53) |
|
83 |
+ width(r) <- w |
|
84 |
+ ranges(x) <- r |
|
85 |
+ return(x) |
|
86 |
+ } |
|
87 |
+ shiftedExons <- shiftCoords(exonsInRegion) |
|
88 |
+ genome <- TP53Genome() |
|
89 |
+ x <- spliceSites(genome, name="dbSnp") <- shiftedExons |
|
90 |
+ checkIdentical(class(x), class(GRangesList())) |
|
91 |
+} |