Browse code

if GmapGenome constructor is called with a DNAStringSet, now requiring that object to have names set (gmap_build does not like empty names). Test added

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

Cory Barr authored on 12/09/2012 00:06:17
Showing 3 changed files

... ...
@@ -10,7 +10,7 @@ Description: GSNAP and GMAP are a pair of tools to align short-read
10 10
     to work with GMAP and GSNAP from within R. In addition, it provides 
11 11
     methods to tally alignment results on a per-nucleotide basis using 
12 12
     the bam_tally tool.
13
-Version: 0.99.19
13
+Version: 0.99.20
14 14
 Depends: R (>= 2.15.0), methods, GenomicRanges
15 15
 Imports: IRanges, Rsamtools (>= 1.7.4), rtracklayer (>= 1.17.15), GenomicRanges,
16 16
          GenomicFeatures, Biostrings, VariantAnnotation, tools, Biobase
... ...
@@ -58,7 +58,12 @@ GmapGenome <- function(genome,
58 58
   if (is(genome, "DNAStringSet")) {
59 59
     if (missing(name))
60 60
       stop("If the genome argument is a DNAStringSet object",
61
-           "the name argument must be provided") 
61
+           "the name argument must be provided")
62
+    if (is.null(names(genome))) {
63
+      stop("If the genome is provided as a DNAStringSet, ",
64
+           "the genome needs to have names. ",
65
+           "E.g., \"names(genome) <- someSeqNames")
66
+    }
62 67
   }
63 68
   if (!isSingleString(name))
64 69
     stop("'name' must be a single, non-NA string")
... ...
@@ -9,10 +9,12 @@ test_GmapGenome_constructor_DNAStringSet_create <- function() {
9 9
   genomeDir <- file.path(tempdir(), as.integer(runif(1) * 1000000000))
10 10
   if (file.exists(genomeDir)) unlink(genomeDir, recursive=TRUE)
11 11
   dir.create(genomeDir, recursive=TRUE)
12
-  
13 12
   on.exit(unlink(genomeDir, recursive=TRUE))
13
+  checkException(GmapGenome(genome=dna, directory=genomeDir,
14
+                            name="thing", create=TRUE))
15
+  names(dna) <- "sampleDNAStringSet"
14 16
   gmapGenome <- GmapGenome(genome=dna, directory=genomeDir,
15
-                           name="thing", create=TRUE)                           
17
+                           name="thing", create=TRUE)
16 18
   checkTrue(is(gmapGenome, "GmapGenome"))
17 19
 }
18 20