Browse code

resync with stuff moving from IRanges to S4Vectors

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

Herve Pages authored on 18/04/2014 15:04:25
Showing 3 changed files

... ...
@@ -10,10 +10,10 @@ 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.7.1
13
+Version: 1.7.2
14 14
 Depends: R (>= 2.15.0), methods, GenomicRanges
15
-Imports: IRanges, Rsamtools (>= 1.7.4), rtracklayer (>= 1.17.15),
16
-        GenomicFeatures, Biostrings, VariantAnnotation (>= 1.9.4),
15
+Imports: S4Vectors, IRanges, Rsamtools (>= 1.7.4), rtracklayer (>= 1.17.15),
16
+        GenomicFeatures, Biostrings, VariantAnnotation (>= 1.11.1),
17 17
         tools, Biobase, BSgenome, GenomicAlignments
18 18
 Suggests: RUnit, BSgenome.Dmelanogaster.UCSC.dm3,
19 19
         BSgenome.Scerevisiae.UCSC.sacCer3, org.Hs.eg.db,
... ...
@@ -5,6 +5,7 @@ importFrom(Rsamtools, path, bamPaths, "bamWhich<-", BamFile, BamFileList,
5 5
 importFrom(tools, file_path_as_absolute, file_ext, file_path_sans_ext,
6 6
            list_files_with_exts)
7 7
 importFrom(Biobase, createPackage)
8
+import(S4Vectors)
8 9
 import(IRanges)
9 10
 import(methods)
10 11
 import(GenomicRanges)
... ...
@@ -44,7 +44,7 @@ setMethod("path", "GmapBamReader", function(object) object@path)
44 44
 GmapBamReader <- function(path, which = NULL) {
45 45
   if (is(path, "BamFile"))
46 46
     path <- path(path)
47
-  if (!IRanges:::isSingleString(path))
47
+  if (!isSingleString(path))
48 48
     stop("'path' must be a single, non-NA string")
49 49
   path <- path.expand(path)
50 50
   obj <- new("GmapBamReader", .extptr = .Call(R_Bamread_new, path), path = path)