Browse code

elementLengths was renamed -> elementNROWS in S4Vectors (new name reflects TRUE semantic, old name will be deprecated soon)

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

Herve Pages authored on 29/01/2016 01:22:03
Showing 1 changed files
... ...
@@ -31,7 +31,7 @@ setReplaceMethod("snps", c("GmapSnpDirectory", "character", "VCF"),
31 31
                    iitFile <- file.path(iitPath, paste(name, "iit", sep = "."))
32 32
                    alt <- values(gr)$ALT
33 33
                    if (is(alt, "List")) {
34
-                     gr <- rep(gr, elementLengths(alt))
34
+                     gr <- rep(gr, elementNROWS(alt))
35 35
                      alt <- unlist(alt)
36 36
                    }
37 37
                    ref <- values(gr)$REF
Browse code

renamed summarizeVariants to variantSummary the which in GsnapParam is now a GenomicRanges instead of a RangesList refactor the show method of BamTallyParam to rely on showAsCell

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

Michael Lawrence authored on 15/07/2013 23:41:54
Showing 1 changed files
... ...
@@ -52,8 +52,8 @@ setReplaceMethod("snps", c("GmapSnpDirectory", "character", "character"),
52 52
                    }
53 53
 
54 54
                    param <- ScanVcfParam(fixed = "ALT", info = NA, geno = NA)
55
-                   if (!missing(which)) # FIXME: waiting for vcfWhich<-
56
-                     param@which <- as(which, "RangesList")
55
+                   if (!missing(which))
56
+                     vcfWhich(param) <- which
57 57
                    
58 58
                    snps(x, name = name, genome = genome, ...) <-
59 59
                      readVcf(value, genome(genome), param)
Browse code

*drop passing of ... arg to method snps<- eventually dispatches on

*doc'ed ... arg to GmapSnps constructor

*added aliases for snps<- when first arg is a GmapGenomeDirectory

*test case for creating a GmapGenome via a DNAStringSet was
broken. Example sequence was too short for gmap_build to work


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

Cory Barr authored on 12/09/2012 22:29:42
Showing 1 changed files
... ...
@@ -24,7 +24,7 @@ setMethod("length", "GmapSnpDirectory", function(x) {
24 24
 
25 25
 setReplaceMethod("snps", c("GmapSnpDirectory", "character", "VCF"),
26 26
                  function(x, name, genome = GmapGenome(genome(x)),
27
-                          iitPath = tempdir(), ..., value)
27
+                          iitPath = tempdir(), value)
28 28
                  {
29 29
                    gr <- rowData(value)
30 30
                    values(gr) <- values(fixed(value))[c("REF", "ALT")]
Browse code

GmapSnpDirectory replace method now accepts name arg

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

Cory Barr authored on 04/09/2012 22:50:45
Showing 1 changed files
... ...
@@ -22,7 +22,7 @@ setMethod("length", "GmapSnpDirectory", function(x) {
22 22
   length(names(x))
23 23
 })
24 24
 
25
-setReplaceMethod("snps", c("GmapSnpDirectory", "VCF"),
25
+setReplaceMethod("snps", c("GmapSnpDirectory", "character", "VCF"),
26 26
                  function(x, name, genome = GmapGenome(genome(x)),
27 27
                           iitPath = tempdir(), ..., value)
28 28
                  {
... ...
@@ -44,7 +44,7 @@ setReplaceMethod("snps", c("GmapSnpDirectory", "VCF"),
44 44
                    x
45 45
                  })
46 46
 
47
-setReplaceMethod("snps", c("GmapSnpDirectory", "character"),
47
+setReplaceMethod("snps", c("GmapSnpDirectory", "character", "character"),
48 48
                  function(x, name, genome, which, ..., value)
49 49
                  {
50 50
                    if (missing(genome)) {
... ...
@@ -54,6 +54,7 @@ setReplaceMethod("snps", c("GmapSnpDirectory", "character"),
54 54
                    param <- ScanVcfParam(fixed = "ALT", info = NA, geno = NA)
55 55
                    if (!missing(which)) # FIXME: waiting for vcfWhich<-
56 56
                      param@which <- as(which, "RangesList")
57
+                   
57 58
                    snps(x, name = name, genome = genome, ...) <-
58 59
                      readVcf(value, genome(genome), param)
59 60
                    x
Browse code

handled case when GmapSnp obj is created with path to VCF, but no genome specified

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

Cory Barr authored on 21/08/2012 23:49:18
Showing 1 changed files
... ...
@@ -47,6 +47,10 @@ setReplaceMethod("snps", c("GmapSnpDirectory", "VCF"),
47 47
 setReplaceMethod("snps", c("GmapSnpDirectory", "character"),
48 48
                  function(x, name, genome, which, ..., value)
49 49
                  {
50
+                   if (missing(genome)) {
51
+                     stop("Please supply the \"genome\" argument")
52
+                   }
53
+
50 54
                    param <- ScanVcfParam(fixed = "ALT", info = NA, geno = NA)
51 55
                    if (!missing(which)) # FIXME: waiting for vcfWhich<-
52 56
                      param@which <- as(which, "RangesList")
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,92 @@
1
+### =========================================================================
2
+### SnpDirectory class
3
+### -------------------------------------------------------------------------
4
+###
5
+### Database of SNPs used by the GMAP suite.
6
+###
7
+
8
+setClass("GmapSnpDirectory", representation(path = "character"))
9
+
10
+### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
11
+### Accessors
12
+###
13
+
14
+setMethod("path", "GmapSnpDirectory", function(object) object@path)
15
+
16
+setMethod("names", "GmapSnpDirectory", function(x) {
17
+  snp_files <- dir(path(x), ".*genomecomp\\.")
18
+  sub("\\.genomecomp\\.", ":", snp_files)
19
+})
20
+
21
+setMethod("length", "GmapSnpDirectory", function(x) {
22
+  length(names(x))
23
+})
24
+
25
+setReplaceMethod("snps", c("GmapSnpDirectory", "VCF"),
26
+                 function(x, name, genome = GmapGenome(genome(x)),
27
+                          iitPath = tempdir(), ..., value)
28
+                 {
29
+                   gr <- rowData(value)
30
+                   values(gr) <- values(fixed(value))[c("REF", "ALT")]
31
+                   iitFile <- file.path(iitPath, paste(name, "iit", sep = "."))
32
+                   alt <- values(gr)$ALT
33
+                   if (is(alt, "List")) {
34
+                     gr <- rep(gr, elementLengths(alt))
35
+                     alt <- unlist(alt)
36
+                   }
37
+                   ref <- values(gr)$REF
38
+                   single <- nchar(alt) == 1L & nchar(ref) == 1L
39
+                   change <- paste(ref[single], alt[single], sep = "")
40
+                   gr <- gr[single]
41
+                   values(gr) <- DataFrame(change)
42
+                   export.iit(gr, iitFile)
43
+                   snpindex(name, genome, path(x), iitFile)
44
+                   x
45
+                 })
46
+
47
+setReplaceMethod("snps", c("GmapSnpDirectory", "character"),
48
+                 function(x, name, genome, which, ..., value)
49
+                 {
50
+                   param <- ScanVcfParam(fixed = "ALT", info = NA, geno = NA)
51
+                   if (!missing(which)) # FIXME: waiting for vcfWhich<-
52
+                     param@which <- as(which, "RangesList")
53
+                   snps(x, name = name, genome = genome, ...) <-
54
+                     readVcf(value, genome(genome), param)
55
+                   x
56
+                 })
57
+
58
+setMethod("[[<-", c("GmapSnpDirectory", value="ANY"),
59
+          function(x, i, j, ..., value) {
60
+            if (!missing(j))
61
+              warning("argument 'j' ignored")
62
+            snps(x, name = i, ...) <- value
63
+            x
64
+          })
65
+
66
+### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
67
+### Constructor
68
+###
69
+
70
+GmapSnpDirectory <- function(path, create = FALSE) {
71
+  if (is(path, "GmapGenome"))
72
+    path <- path(path)
73
+  if (!isSingleString(path))
74
+    stop("'path' must be a single, non-NA string")
75
+  if (!isTRUEorFALSE(create))
76
+    stop("'create' must be TRUE or FALSE")
77
+  if (create) {
78
+    if (file.exists(path))
79
+      message("NOTE: snp directory '", path, "' already exists, not recreating")
80
+    else dir.create(path, recursive = TRUE)
81
+  }
82
+  new("GmapSnpDirectory", path = path)
83
+}
84
+
85
+### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
86
+### Show
87
+###
88
+
89
+setMethod("show", "GmapSnpDirectory", function(object) {
90
+  cat("GmapSnpDirectory object\n", "path: ", path(object),
91
+      "\nnames: ", names(object), "\n", sep = "")
92
+})