Browse code

follow renaming of RangesList class -> IntegerRangesList in IRanges 2.13.12

Hervé Pagès authored on 22/01/2018 00:24:43
Showing 1 changed files
... ...
@@ -19,15 +19,15 @@ setMethod("path", "GmapBamReader", function(object) object@path)
19 19
 
20 20
 ## setReplaceMethod("bamWhich", c("GmapBamReader", "ANY"),
21 21
 ##                  function(object, value) {
22
-##                    bamWhich(object) <- as(value, "RangesList")
22
+##                    bamWhich(object) <- as(value, "IntegerRangesList")
23 23
 ##                    object
24 24
 ##                  })
25 25
 
26
-## setReplaceMethod("bamWhich", c("GmapBamReader", "RangesList"),
26
+## setReplaceMethod("bamWhich", c("GmapBamReader", "IntegerRangesList"),
27 27
 ##                  function(object, value) {
28 28
 ##                    if (length(value) != 1L || length(value[[1]]) != 1L)
29
-##                      stop("'value' must be a RangesList with a single, ",
30
-##                           "length-one element")
29
+##                      stop("'value' must be an IntegerRangesList with a ",
30
+##                           "single, length-one element")
31 31
 ##                    .Call(R_Bamread_limit_region, object, names(value),
32 32
 ##                          start(value[[1]]), end(value[[1]]))
33 33
 ##                  })
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 1 changed files
... ...
@@ -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)
Browse code

renaming gmapR2 to gmapR: it lives again

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

Michael Lawrence authored on 02/08/2012 22:24:24
Showing 1 changed files
1 1
new file mode 100644
... ...
@@ -0,0 +1,75 @@
1
+### =========================================================================
2
+### GmapBamReader class
3
+### -------------------------------------------------------------------------
4
+###
5
+### The C-level BAM file iterator used by BAM processors in gmap/gstruct.
6
+###
7
+### This is very similar to BamFile from Rsamtools, but it iterates
8
+### line-by-line, not by chunk.
9
+###
10
+
11
+setClass("GmapBamReader",
12
+         representation(.extptr = "externalptr", path = "character"))
13
+
14
+### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
15
+### Accessors
16
+###
17
+
18
+setMethod("path", "GmapBamReader", function(object) object@path)
19
+
20
+## setReplaceMethod("bamWhich", c("GmapBamReader", "ANY"),
21
+##                  function(object, value) {
22
+##                    bamWhich(object) <- as(value, "RangesList")
23
+##                    object
24
+##                  })
25
+
26
+## setReplaceMethod("bamWhich", c("GmapBamReader", "RangesList"),
27
+##                  function(object, value) {
28
+##                    if (length(value) != 1L || length(value[[1]]) != 1L)
29
+##                      stop("'value' must be a RangesList with a single, ",
30
+##                           "length-one element")
31
+##                    .Call(R_Bamread_limit_region, object, names(value),
32
+##                          start(value[[1]]), end(value[[1]]))
33
+##                  })
34
+
35
+## setReplaceMethod("bamWhich", c("GmapBamReader", "NULL"),
36
+##                  function(object, value) {
37
+##                    .Call(R_Bamread_unlimit_region, object)
38
+##                  })
39
+
40
+### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
41
+### Constructor
42
+###
43
+
44
+GmapBamReader <- function(path, which = NULL) {
45
+  if (is(path, "BamFile"))
46
+    path <- path(path)
47
+  if (!IRanges:::isSingleString(path))
48
+    stop("'path' must be a single, non-NA string")
49
+  path <- path.expand(path)
50
+  obj <- new("GmapBamReader", .extptr = .Call(R_Bamread_new, path), path = path)
51
+### TODO:
52
+  ##  bamWhich(obj) <- which
53
+  obj
54
+}
55
+
56
+### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
57
+### Coercion
58
+###
59
+
60
+setAs("BamFile", "GmapBamReader", function(from) {
61
+  GmapBamReader(from)
62
+})
63
+
64
+setAs("GmapBamReader", "BamFile", function(from) {
65
+  BamFile(path(from))
66
+})
67
+
68
+
69
+### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
70
+### Show
71
+###
72
+
73
+setMethod("show", "GmapBamReader", function(object) {
74
+  cat("GmapBamReader object\npath:", path(object), "\n")
75
+})