Browse code

TP53 genome is now named by the TxDb package from which the TP53 region was retrieved, so that it is automatically refreshed with annotation changes, and devel and release can coexist.

git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@87282 bc3139a8-67e5-0310-9ffc-ced21a209358

Michael Lawrence authored on 10/03/2014 23:10:51
Showing 5 changed files

... ...
@@ -10,7 +10,7 @@ Description: GSNAP and GMAP are a pair of tools to align short-read
10 10
         methods to work with GMAP and GSNAP from within R. In addition,
11 11
         it provides methods to tally alignment results on a
12 12
         per-nucleotide basis using the bam_tally tool.
13
-Version: 1.5.11
13
+Version: 1.5.12
14 14
 Depends: R (>= 2.15.0), methods, GenomicRanges
15 15
 Imports: IRanges, Rsamtools (>= 1.7.4), rtracklayer (>= 1.17.15),
16 16
         GenomicFeatures, Biostrings, VariantAnnotation (>= 1.9.4),
... ...
@@ -7,6 +7,7 @@ importFrom(Biobase, createPackage)
7 7
 import(IRanges)
8 8
 import(methods)
9 9
 import(GenomicRanges)
10
+importFrom(utils, packageVersion)
10 11
 importFrom(Biostrings, getSeq, readDNAStringSet, DNAStringSet)
11 12
 importFrom(GenomicRanges, genome, seqinfo)
12 13
 importMethodsFrom(GenomicRanges, seqnames, strand)
... ...
@@ -1,6 +1,10 @@
1
+geneGenomeName <- function(gene) {
2
+  paste0(gene, "_demo_", packageVersion("TxDb.Hsapiens.UCSC.hg19.knownGene"))
3
+}
4
+
1 5
 TP53Genome <- function() {
2 6
   gene <- "TP53"
3
-  genomeName <- paste0(gene, "_demo")
7
+  genomeName <- geneGenomeName(gene)
4 8
   
5 9
   if (genomeName %in% genome(GmapGenomeDirectory(create=TRUE))) {
6 10
     GmapGenome(genomeName)
... ...
@@ -58,7 +62,7 @@ translateToP53Genome <- function(x) {
58 62
   orgdb <- org.Hs.eg.db::org.Hs.eg.db
59 63
   roi <- getGeneRoi(txdb, orgdb, "TP53")
60 64
   subregion <- subsetRegion(x, roi, gene)
61
-  genome(subregion) <- "TP53_demo"
65
+  genome(subregion) <- geneGenomeName("TP53")
62 66
   subregion
63 67
 }
64 68
 
... ...
@@ -19,7 +19,9 @@ TP53Which()
19 19
   For \code{TP53Genome}, a \code{GmapGenome} object. If this is the
20 20
   first time the user has run this function, a side-effect will be the
21 21
   generation of an on-disk genome index, under the name
22
-  \dQuote{TP53_demo} in the default genome directory.
22
+  \dQuote{TP53_demo_VERSION} in the default genome directory, where
23
+  \code{VERSION} is the version of the TxDb package providing the bounds
24
+  of the P53 gene.
23 25
 
24 26
   For \code{TP53Which}, a \code{GRanges} of the extents of the TP53
25 27
   gene, translated to the space of \code{TP53Genome}.
... ...
@@ -182,9 +182,12 @@ library("gmapR")
182 182
 p53Seq <- getSeq(BSgenome.Hsapiens.UCSC.hg19::Hsapiens, roi,
183 183
                  as.character = FALSE) 
184 184
 names(p53Seq) <- "TP53"
185
-gmapGenome <- GmapGenome(genome = p53Seq, name = "TP53_demo", create = TRUE, 
185
+gmapGenome <- GmapGenome(genome = p53Seq, 
186
+                         name = paste0("TP53_demo_", 
187
+                           packageVersion("TxDb.Hsapiens.UCSC.hg19.knownGene")), 
188
+                         create = TRUE, 
186 189
                          k = 12L)
187
-@ 
190
+@
188 191
 
189 192
 We add the known transcripts (splice sites) to the genome index:
190 193
 <<set_TP53_splicesites>>=
... ...
@@ -294,11 +297,8 @@ summarizing these data into R data structures. For now, there is one:
294 297
 \Rfunction{variantSummary}, which returns a \Rcode{VRanges} object
295 298
 describing putative genetic variants in the sample.
296 299
 <<run_bamtally, eval=FALSE>>=
297
-library(gmapR)
298
-
299 300
 bam_file <- system.file("extdata/H1993.analyzed.bam", 
300 301
                         package="LungCancerLines", mustWork=TRUE)
301
-
302 302
 breaks <- c(0L, 15L, 60L, 75L)
303 303
 bqual <- 56L
304 304
 mapq <- 13L