Browse code

allow omitting gmap arg suboptimal_score, and make that the default

Michael Lawrence authored on 29/08/2017 22:10:50
Showing 1 changed files
... ...
@@ -8,8 +8,6 @@
8 8
 ### list.
9 9
 ###
10 10
 
11
-setClassUnion("integer_OR_NULL", c("integer", "NULL"))
12
-
13 11
 setClass("GsnapParam",
14 12
          representation(max_mismatches = "integer_OR_NULL",
15 13
                         suboptimal_levels = "integer",
Browse code

follow renaming of union classes in S4Vectors

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

Herve Pages authored on 01/02/2017 13:23:02
Showing 1 changed files
... ...
@@ -8,13 +8,13 @@
8 8
 ### list.
9 9
 ###
10 10
 
11
-setClassUnion("integerORNULL", c("integer", "NULL"))
11
+setClassUnion("integer_OR_NULL", c("integer", "NULL"))
12 12
 
13 13
 setClass("GsnapParam",
14
-         representation(max_mismatches = "integerORNULL",
14
+         representation(max_mismatches = "integer_OR_NULL",
15 15
                         suboptimal_levels = "integer",
16 16
                         novelsplicing = "logical",
17
-                        splicing = "characterORNULL",
17
+                        splicing = "character_OR_NULL",
18 18
                         terminal_threshold = "integer",
19 19
                         gmap_mode = "character",
20 20
                         clip_overlap = "logical"),
... ...
@@ -205,12 +205,12 @@ setAs("GsnapParam", "list", function(from) {
205 205
 
206 206
 as.list.GmapAlignerParam <- function(x, ...) as(x, "list")
207 207
 
208
-setAs("ANY", "characterORNULL", function(from) {
208
+setAs("ANY", "character_OR_NULL", function(from) {
209 209
   if (is.null(from))
210 210
     NULL
211 211
   else as.character(from)
212 212
 })
213
-setAs("ANY", "integerORNULL", function(from) {
213
+setAs("ANY", "integer_OR_NULL", function(from) {
214 214
   if (is.null(from))
215 215
     NULL
216 216
   else as.integer(from)
Browse code

general cleanup and fixes, doc updates

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

Michael Lawrence authored on 03/12/2015 21:11:09
Showing 1 changed files
... ...
@@ -203,7 +203,7 @@ setAs("GsnapParam", "list", function(from) {
203 203
           to
204 204
       })
205 205
 
206
-as.list.GmapAlignerParam <- function(x) as(x, "list")
206
+as.list.GmapAlignerParam <- function(x, ...) as(x, "list")
207 207
 
208 208
 setAs("ANY", "characterORNULL", function(from) {
209 209
   if (is.null(from))
Browse code

add ability to call GMAP

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

Michael Lawrence authored on 23/11/2015 23:25:34
Showing 1 changed files
... ...
@@ -9,27 +9,16 @@
9 9
 ###
10 10
 
11 11
 setClassUnion("integerORNULL", c("integer", "NULL"))
12
-setClassUnion("GmapSnpsORNULL", c("GmapSnps", "NULL"))
13 12
 
14 13
 setClass("GsnapParam",
15
-         representation(genome = "GmapGenome",
16
-                        part = "characterORNULL", # used by parallelized_gsnap
17
-                        batch = "character", # weird "0", "1", ... 
18
-                        max_mismatches = "integerORNULL",
14
+         representation(max_mismatches = "integerORNULL",
19 15
                         suboptimal_levels = "integer",
20
-                        snps = "GmapSnpsORNULL",
21
-                        mode = "character",
22
-                        nthreads = "integer",
23 16
                         novelsplicing = "logical",
24 17
                         splicing = "characterORNULL",
25
-                        npaths = "integer",
26
-                        quiet_if_excessive = "logical",
27
-                        nofails = "logical", 
28
-                        split_output = "logical",
29 18
                         terminal_threshold = "integer",
30 19
                         gmap_mode = "character",
31
-                        clip_overlap = "logical",
32
-                        extra = "list"))
20
+                        clip_overlap = "logical"),
21
+         contains="GmapAlignerParam")
33 22
 
34 23
 ### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
35 24
 ### Accessors
... ...
@@ -148,6 +137,27 @@ gsnap_extra <- function(x) {
148 137
 ### Constructor
149 138
 ###
150 139
 
140
+newGmapAlignerParam <- function(Class, genome, snps) {
141
+    if (missing(genome))
142
+        stop("The 'genome' must be specified (and coercible to GmapGenome)")
143
+    args <- formals(sys.function(sys.parent(1L)))
144
+    params <- mget(names(args), parent.frame())
145
+    params$unique_only <- NULL
146
+    paramClasses <- getSlots(Class)
147
+    paramClasses <- paramClasses[setdiff(names(paramClasses),
148
+                                         c("extra", "snps"))]
149
+    params <- mapply(as, params[names(paramClasses)], paramClasses,
150
+                     SIMPLIFY = FALSE)
151
+    if (!is.null(snps)) {
152
+        if (!is(snps, "GmapSnps")) {
153
+            snps <- GmapSnps(snps, genome)
154
+        }
155
+        params$snps <- snps
156
+    }
157
+    params$extra <- evalq(list(...), parent.frame())
158
+    do.call(new, c(Class, params))
159
+}
160
+
151 161
 GsnapParam <- function(genome, unique_only = FALSE, molecule = c("RNA", "DNA"),
152 162
                        max_mismatches = NULL,
153 163
                        suboptimal_levels = 0L, mode = "standard",
... ...
@@ -157,54 +167,43 @@ GsnapParam <- function(genome, unique_only = FALSE, molecule = c("RNA", "DNA"),
157 167
                        split_output = !unique_only,
158 168
                        novelsplicing = FALSE, splicing = NULL, 
159 169
                        nthreads = 1L, part = NULL, batch = "2",
160
-                       terminal_threshold = if (molecule == "DNA") 1000L else 2L,
161
-                       gmap_mode = if (molecule == "DNA") "none" else
162
-                       "pairsearch,terminal,improve",
170
+                       terminal_threshold =
171
+                           if (molecule == "DNA") 1000L else 2L,
172
+                       gmap_mode = if (molecule == "DNA") "none"
173
+                                   else "pairsearch,terminal,improve",
163 174
                        clip_overlap = FALSE, ...)
164 175
 {
165
-  if (missing(genome))
166
-    stop("The 'genome' must be specified (should be coercible to GmapGenome)")
167 176
   molecule <- match.arg(molecule)
168
-  args <- formals(sys.function())
169
-  params <- mget(names(args), environment())
170
-  params$unique_only <- NULL
171
-  paramClasses <- getSlots("GsnapParam")
172
-  paramClasses <- paramClasses[setdiff(names(paramClasses), c("extra", "snps"))]
173
-  params <- mapply(as, params[names(paramClasses)], paramClasses,
174
-                   SIMPLIFY = FALSE)
175
-  if (!is.null(snps)) {
176
-    if (!is(snps, "GmapSnps")) {
177
-      snps <- GmapSnps(snps, genome)
178
-    }
179
-    params$snps <- snps
180
-  }
181
-  params$extra <- list(...)
182
-  do.call(new, c("GsnapParam", params))
177
+  newGmapAlignerParam("GsnapParam", genome, snps)
183 178
 }
184 179
 
185 180
 ### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
186 181
 ### Coercion
187 182
 ###
188 183
 
189
-setAs("GsnapParam", "list", function(from) {
184
+GmapAlignerParam_asList <- function(from) {
190 185
   to <- lapply(slotNames(from), slot, object = from)
191 186
   names(to) <- slotNames(from)
192
-  to$split_output <- if (to$split_output) "gsnap" else NULL
187
+  to$split_output <- if (to$split_output) tolower(sub("Param", "", class(from)))
193 188
   to$db <- genome(to$genome)
194 189
   to$dir <- path(directory(to$genome))
195 190
   to$genome <- NULL
196 191
   to$use_snps <- name(to$snps)
197 192
   to$snpsdir <- path(directory(to$snps))
198
-  to$novelsplicing <- as.integer(to$novelsplicing)
199
-  to <- rename(to, splicing = "use_splicing")
200 193
   extras <- to$extra
201 194
   to <- c(to, extras)
202
-  to$extra <- NULL
203
-  
195
+  to$extra <- NULL  
204 196
   to
205
-})
197
+}
198
+
199
+setAs("GsnapParam", "list", function(from) {
200
+          to <- GmapAlignerParam_asList(from)
201
+          to$novelsplicing <- as.integer(to$novelsplicing)
202
+          to <- rename(to, splicing = "use_splicing")
203
+          to
204
+      })
206 205
 
207
-setMethod("as.list", "GsnapParam", function(x) as(x, "list"))
206
+as.list.GmapAlignerParam <- function(x) as(x, "list")
208 207
 
209 208
 setAs("ANY", "characterORNULL", function(from) {
210 209
   if (is.null(from))
... ...
@@ -222,7 +221,7 @@ setAs("ANY", "integerORNULL", function(from) {
222 221
 ### Show
223 222
 ###
224 223
 
225
-setMethod("show", "GsnapParam", function(object) {
224
+setMethod("show", "GmapAlignerParam", function(object) {
226 225
   slots <- lapply(slotNames(object), slot, object = object)
227 226
   names(slots) <- slotNames(object)
228 227
   slots$genome <- paste0(slots$genome@name,
... ...
@@ -231,6 +230,6 @@ setMethod("show", "GsnapParam", function(object) {
231 230
     slots$snps <- paste0(name(slots$snps),
232 231
                          " (", path(directory(slots$snps)), ")")
233 232
   }
234
-  cat("A GsnapParams object\n",
233
+  cat("A ", class(object), " object\n",
235 234
       paste0(names(slots), ": ", slots, collapse = "\n"), "\n", sep = "")
236 235
 })
Browse code

clip_overlaps should be clip_overlap

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

Michael Lawrence authored on 12/02/2014 17:13:58
Showing 1 changed files
... ...
@@ -28,7 +28,7 @@ setClass("GsnapParam",
28 28
                         split_output = "logical",
29 29
                         terminal_threshold = "integer",
30 30
                         gmap_mode = "character",
31
-                        clip_overlaps = "logical",
31
+                        clip_overlap = "logical",
32 32
                         extra = "list"))
33 33
 
34 34
 ### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
... ...
@@ -160,7 +160,7 @@ GsnapParam <- function(genome, unique_only = FALSE, molecule = c("RNA", "DNA"),
160 160
                        terminal_threshold = if (molecule == "DNA") 1000L else 2L,
161 161
                        gmap_mode = if (molecule == "DNA") "none" else
162 162
                        "pairsearch,terminal,improve",
163
-                       clip_overlaps = FALSE, ...)
163
+                       clip_overlap = FALSE, ...)
164 164
 {
165 165
   if (missing(genome))
166 166
     stop("The 'genome' must be specified (should be coercible to GmapGenome)")
Browse code

clip_overlaps added to GsnapParam

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

Michael Lawrence authored on 14/01/2014 19:12:55
Showing 1 changed files
... ...
@@ -28,6 +28,7 @@ setClass("GsnapParam",
28 28
                         split_output = "logical",
29 29
                         terminal_threshold = "integer",
30 30
                         gmap_mode = "character",
31
+                        clip_overlaps = "logical",
31 32
                         extra = "list"))
32 33
 
33 34
 ### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
... ...
@@ -158,7 +159,8 @@ GsnapParam <- function(genome, unique_only = FALSE, molecule = c("RNA", "DNA"),
158 159
                        nthreads = 1L, part = NULL, batch = "2",
159 160
                        terminal_threshold = if (molecule == "DNA") 1000L else 2L,
160 161
                        gmap_mode = if (molecule == "DNA") "none" else
161
-                       "pairsearch,terminal,improve", ...)
162
+                       "pairsearch,terminal,improve",
163
+                       clip_overlaps = FALSE, ...)
162 164
 {
163 165
   if (missing(genome))
164 166
     stop("The 'genome' must be specified (should be coercible to GmapGenome)")
Browse code

actually check in the gmap-mode fix

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

Michael Lawrence authored on 10/09/2013 03:42:15
Showing 1 changed files
... ...
@@ -27,7 +27,7 @@ setClass("GsnapParam",
27 27
                         nofails = "logical", 
28 28
                         split_output = "logical",
29 29
                         terminal_threshold = "integer",
30
-                        gmap_mode = "characterORNULL",
30
+                        gmap_mode = "character",
31 31
                         extra = "list"))
32 32
 
33 33
 ### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
... ...
@@ -157,7 +157,9 @@ GsnapParam <- function(genome, unique_only = FALSE, molecule = c("RNA", "DNA"),
157 157
                        novelsplicing = FALSE, splicing = NULL, 
158 158
                        nthreads = 1L, part = NULL, batch = "2",
159 159
                        terminal_threshold = if (molecule == "DNA") 1000L else 2L,
160
-                       gmap_mode = if (molecule == "DNA") "none", ...) {
160
+                       gmap_mode = if (molecule == "DNA") "none" else
161
+                       "pairsearch,terminal,improve", ...)
162
+{
161 163
   if (missing(genome))
162 164
     stop("The 'genome' must be specified (should be coercible to GmapGenome)")
163 165
   molecule <- match.arg(molecule)
Browse code

fix default (NULL) for gmap-mode argument to gsnap

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

Michael Lawrence authored on 09/09/2013 21:59:47
Showing 1 changed files
... ...
@@ -27,7 +27,7 @@ setClass("GsnapParam",
27 27
                         nofails = "logical", 
28 28
                         split_output = "logical",
29 29
                         terminal_threshold = "integer",
30
-                        gmap_mode = "character",
30
+                        gmap_mode = "characterORNULL",
31 31
                         extra = "list"))
32 32
 
33 33
 ### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
Browse code

Support terminal_threshold parameter, and use different defaults for DNA vs. RNA. This means a big improvement in alignment quality for DNA.

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

Michael Lawrence authored on 14/07/2013 00:37:00
Showing 1 changed files
... ...
@@ -26,6 +26,8 @@ setClass("GsnapParam",
26 26
                         quiet_if_excessive = "logical",
27 27
                         nofails = "logical", 
28 28
                         split_output = "logical",
29
+                        terminal_threshold = "integer",
30
+                        gmap_mode = "character",
29 31
                         extra = "list"))
30 32
 
31 33
 ### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
... ...
@@ -145,7 +147,7 @@ gsnap_extra <- function(x) {
145 147
 ### Constructor
146 148
 ###
147 149
 
148
-GsnapParam <- function(genome, unique_only = FALSE,
150
+GsnapParam <- function(genome, unique_only = FALSE, molecule = c("RNA", "DNA"),
149 151
                        max_mismatches = NULL,
150 152
                        suboptimal_levels = 0L, mode = "standard",
151 153
                        snps = NULL,
... ...
@@ -153,9 +155,12 @@ GsnapParam <- function(genome, unique_only = FALSE,
153 155
                        quiet_if_excessive = unique_only, nofails = unique_only,
154 156
                        split_output = !unique_only,
155 157
                        novelsplicing = FALSE, splicing = NULL, 
156
-                       nthreads = 1L, part = NULL, batch = "2", ...) {
158
+                       nthreads = 1L, part = NULL, batch = "2",
159
+                       terminal_threshold = if (molecule == "DNA") 1000L else 2L,
160
+                       gmap_mode = if (molecule == "DNA") "none", ...) {
157 161
   if (missing(genome))
158 162
     stop("The 'genome' must be specified (should be coercible to GmapGenome)")
163
+  molecule <- match.arg(molecule)
159 164
   args <- formals(sys.function())
160 165
   params <- mget(names(args), environment())
161 166
   params$unique_only <- NULL
Browse code

Check that genome argument is provided in GsnapParam. No way to get a safe default for this one.

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

Michael Lawrence authored on 09/11/2012 12:54:49
Showing 1 changed files
... ...
@@ -154,6 +154,8 @@ GsnapParam <- function(genome, unique_only = FALSE,
154 154
                        split_output = !unique_only,
155 155
                        novelsplicing = FALSE, splicing = NULL, 
156 156
                        nthreads = 1L, part = NULL, batch = "2", ...) {
157
+  if (missing(genome))
158
+    stop("The 'genome' must be specified (should be coercible to GmapGenome)")
157 159
   args <- formals(sys.function())
158 160
   params <- mget(names(args), environment())
159 161
   params$unique_only <- NULL
Browse code

Match up GsnapParams@splicing with new use_splicing gsnap parameter

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

Michael Lawrence authored on 07/09/2012 17:37:14
Showing 1 changed files
... ...
@@ -182,15 +182,10 @@ setAs("GsnapParam", "list", function(from) {
182 182
   to$db <- genome(to$genome)
183 183
   to$dir <- path(directory(to$genome))
184 184
   to$genome <- NULL
185
-  if(!is.null(to$snps)) {
186
-    to$use_snps <- name(to$snps)
187
-  } else {
188
-    to$use_snps <- NULL
189
-  }
185
+  to$use_snps <- name(to$snps)
190 186
   to$snpsdir <- path(directory(to$snps))
191
-  to$snps <- NULL
192 187
   to$novelsplicing <- as.integer(to$novelsplicing)
193
-
188
+  to <- rename(to, splicing = "use_splicing")
194 189
   extras <- to$extra
195 190
   to <- c(to, extras)
196 191
   to$extra <- NULL
Browse code

Fix novelsplicing coercion so that it specifies the 0/1 flag (Greg's second issue).

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

Michael Lawrence authored on 06/09/2012 23:15:38
Showing 1 changed files
... ...
@@ -189,6 +189,7 @@ setAs("GsnapParam", "list", function(from) {
189 189
   }
190 190
   to$snpsdir <- path(directory(to$snps))
191 191
   to$snps <- NULL
192
+  to$novelsplicing <- as.integer(to$novelsplicing)
192 193
 
193 194
   extras <- to$extra
194 195
   to <- c(to, extras)
Browse code

Rewrite the GsnapParam constructor to coerce its arguments to the slot types.

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

Michael Lawrence authored on 06/09/2012 12:01:42
Showing 1 changed files
... ...
@@ -154,21 +154,20 @@ GsnapParam <- function(genome, unique_only = FALSE,
154 154
                        split_output = !unique_only,
155 155
                        novelsplicing = FALSE, splicing = NULL, 
156 156
                        nthreads = 1L, part = NULL, batch = "2", ...) {
157
-  params <- formals(sys.function())
158
-  mc <- as.list(match.call(expand.dots = FALSE))[-1L]
159
-  params[names(mc)] <- mc
157
+  args <- formals(sys.function())
158
+  params <- mget(names(args), environment())
160 159
   params$unique_only <- NULL
160
+  paramClasses <- getSlots("GsnapParam")
161
+  paramClasses <- paramClasses[setdiff(names(paramClasses), c("extra", "snps"))]
162
+  params <- mapply(as, params[names(paramClasses)], paramClasses,
163
+                   SIMPLIFY = FALSE)
161 164
   if (!is.null(snps)) {
162 165
     if (!is(snps, "GmapSnps")) {
163
-      params$snps <- GmapSnps(snps, genome)
166
+      snps <- GmapSnps(snps, genome)
164 167
     }
168
+    params$snps <- snps
165 169
   }
166
-  dots <- list(...)
167
-  ##TODO: this breaks if ... has anything in it
168
-  if (length(dots) > 0) {
169
-    params$extra <- params$...
170
-  }
171
-  params$... <- NULL
170
+  params$extra <- list(...)
172 171
   do.call(new, c("GsnapParam", params))
173 172
 }
174 173
 
... ...
@@ -200,6 +199,18 @@ setAs("GsnapParam", "list", function(from) {
200 199
 
201 200
 setMethod("as.list", "GsnapParam", function(x) as(x, "list"))
202 201
 
202
+setAs("ANY", "characterORNULL", function(from) {
203
+  if (is.null(from))
204
+    NULL
205
+  else as.character(from)
206
+})
207
+setAs("ANY", "integerORNULL", function(from) {
208
+  if (is.null(from))
209
+    NULL
210
+  else as.integer(from)
211
+})
212
+
213
+
203 214
 ### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
204 215
 ### Show
205 216
 ###
Browse code

fixed bug in handling 'errors' slot of GsnapParams objects

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

Cory Barr authored on 22/08/2012 22:25:34
Showing 1 changed files
... ...
@@ -163,9 +163,9 @@ GsnapParam <- function(genome, unique_only = FALSE,
163 163
       params$snps <- GmapSnps(snps, genome)
164 164
     }
165 165
   }
166
-  extra <- params$...
166
+  dots <- list(...)
167 167
   ##TODO: this breaks if ... has anything in it
168
-  if (!missing(extra) && !is.null(names(extra))) {
168
+  if (length(dots) > 0) {
169 169
     params$extra <- params$...
170 170
   }
171 171
   params$... <- NULL
... ...
@@ -190,6 +190,11 @@ setAs("GsnapParam", "list", function(from) {
190 190
   }
191 191
   to$snpsdir <- path(directory(to$snps))
192 192
   to$snps <- NULL
193
+
194
+  extras <- to$extra
195
+  to <- c(to, extras)
196
+  to$extra <- NULL
197
+  
193 198
   to
194 199
 })
195 200
 
Browse code

novel_splicing GSNAP param should default to FALSE (not 0) in GsnapParams()

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

Michael Lawrence authored on 17/08/2012 20:18:15
Showing 1 changed files
... ...
@@ -152,7 +152,7 @@ GsnapParam <- function(genome, unique_only = FALSE,
152 152
                        npaths = if (unique_only) 1L else 100L,
153 153
                        quiet_if_excessive = unique_only, nofails = unique_only,
154 154
                        split_output = !unique_only,
155
-                       novelsplicing = 0L, splicing = NULL, 
155
+                       novelsplicing = FALSE, splicing = NULL, 
156 156
                        nthreads = 1L, part = NULL, batch = "2", ...) {
157 157
   params <- formals(sys.function())
158 158
   mc <- as.list(match.call(expand.dots = FALSE))[-1L]
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,213 @@
1
+### =========================================================================
2
+### GsnapParam class
3
+### -------------------------------------------------------------------------
4
+###
5
+### High-level interface to gsnap. As a complex operation, we need a
6
+### formal parameter object. It should only formally represent the
7
+### most commonly used parameters. The rest fall into the 'extra'
8
+### list.
9
+###
10
+
11
+setClassUnion("integerORNULL", c("integer", "NULL"))
12
+setClassUnion("GmapSnpsORNULL", c("GmapSnps", "NULL"))
13
+
14
+setClass("GsnapParam",
15
+         representation(genome = "GmapGenome",
16
+                        part = "characterORNULL", # used by parallelized_gsnap
17
+                        batch = "character", # weird "0", "1", ... 
18
+                        max_mismatches = "integerORNULL",
19
+                        suboptimal_levels = "integer",
20
+                        snps = "GmapSnpsORNULL",
21
+                        mode = "character",
22
+                        nthreads = "integer",
23
+                        novelsplicing = "logical",
24
+                        splicing = "characterORNULL",
25
+                        npaths = "integer",
26
+                        quiet_if_excessive = "logical",
27
+                        nofails = "logical", 
28
+                        split_output = "logical",
29
+                        extra = "list"))
30
+
31
+### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
32
+### Accessors
33
+###
34
+
35
+gsnap_part <- function(x) {
36
+  x@part
37
+}
38
+gsnap_batch <- function(x) {
39
+  x@batch
40
+}
41
+gsnap_max_mismatches <- function(x) {
42
+  x@max_mismatches
43
+}
44
+gsnap_suboptimal_levels <- function(x) {
45
+  x@suboptimal_levels
46
+}
47
+gsnap_use_snps <- function(x) {
48
+  x@use_snps
49
+}
50
+gsnap_snpsdir <- function(x) {
51
+  x@snpsdir
52
+}
53
+gsnap_mode <- function(x) {
54
+  x@mode
55
+}
56
+gsnap_nthreads <- function(x) {
57
+  x@nthreads
58
+}
59
+gsnap_novelsplicing <- function(x) {
60
+  x@novelsplicing
61
+}
62
+gsnap_splicing <- function(x) {
63
+  x@splicing
64
+}
65
+gsnap_npaths <- function(x) {
66
+  x@npaths
67
+}
68
+gsnap_quiet_if_excessive <- function(x) {
69
+  x@quiet_if_excessive
70
+}
71
+gsnap_nofails <- function(x) {
72
+  x@nofails
73
+}
74
+gsnap_split_output <- function(x) {
75
+  x@split_output
76
+}
77
+gsnap_extra <- function(x) {
78
+  x@extra
79
+}
80
+
81
+`gsnap_part<-` <- function(x, value) {
82
+  x@part <- value
83
+  x
84
+}
85
+`gsnap_batch<-` <- function(x, value) {
86
+  x@batch <- value
87
+  x
88
+}
89
+`gsnap_max_mismatches<-` <- function(x, value) {
90
+  x@max_mismatches <- value
91
+  x
92
+}
93
+`gsnap_suboptimal_levels<-` <- function(x, value) {
94
+  x@suboptimal_levels <- value
95
+  x
96
+}
97
+`gsnap_use_snps<-` <- function(x, value) {
98
+  x@use_snps <- value
99
+  x
100
+}
101
+`gsnap_snpsdir<-` <- function(x, value) {
102
+  x@snpsdir <- value
103
+  x
104
+}
105
+`gsnap_mode<-` <- function(x, value) {
106
+  x@mode <- value
107
+  x
108
+}
109
+`gsnap_nthreads<-` <- function(x, value) {
110
+  x@nthreads <- value
111
+  x
112
+}
113
+`gsnap_novelsplicing<-` <- function(x, value) {
114
+  x@novelsplicing <- value
115
+  x
116
+}
117
+`gsnap_splicing<-` <- function(x, value) {
118
+  x@splicing <- value
119
+  x
120
+}
121
+`gsnap_npaths<-` <- function(x, value) {
122
+  x@npaths <- value
123
+  x
124
+}
125
+`gsnap_quiet_if_excessive<-` <- function(x, value) {
126
+  x@quiet_if_excessive <- value
127
+  x
128
+}
129
+`gsnap_nofails<-` <- function(x, value) {
130
+  x@nofails <- value
131
+  x
132
+}
133
+`gsnap_split_output<-` <- function(x, value) {
134
+  x@split_output <- value
135
+  x
136
+}
137
+`gsnap_extra<-` <- function(x, value) {
138
+  x@extra <- value
139
+  x
140
+}
141
+
142
+## etc..
143
+
144
+### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
145
+### Constructor
146
+###
147
+
148
+GsnapParam <- function(genome, unique_only = FALSE,
149
+                       max_mismatches = NULL,
150
+                       suboptimal_levels = 0L, mode = "standard",
151
+                       snps = NULL,
152
+                       npaths = if (unique_only) 1L else 100L,
153
+                       quiet_if_excessive = unique_only, nofails = unique_only,
154
+                       split_output = !unique_only,
155
+                       novelsplicing = 0L, splicing = NULL, 
156
+                       nthreads = 1L, part = NULL, batch = "2", ...) {
157
+  params <- formals(sys.function())
158
+  mc <- as.list(match.call(expand.dots = FALSE))[-1L]
159
+  params[names(mc)] <- mc
160
+  params$unique_only <- NULL
161
+  if (!is.null(snps)) {
162
+    if (!is(snps, "GmapSnps")) {
163
+      params$snps <- GmapSnps(snps, genome)
164
+    }
165
+  }
166
+  extra <- params$...
167
+  ##TODO: this breaks if ... has anything in it
168
+  if (!missing(extra) && !is.null(names(extra))) {
169
+    params$extra <- params$...
170
+  }
171
+  params$... <- NULL
172
+  do.call(new, c("GsnapParam", params))
173
+}
174
+
175
+### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
176
+### Coercion
177
+###
178
+
179
+setAs("GsnapParam", "list", function(from) {
180
+  to <- lapply(slotNames(from), slot, object = from)
181
+  names(to) <- slotNames(from)
182
+  to$split_output <- if (to$split_output) "gsnap" else NULL
183
+  to$db <- genome(to$genome)
184
+  to$dir <- path(directory(to$genome))
185
+  to$genome <- NULL
186
+  if(!is.null(to$snps)) {
187
+    to$use_snps <- name(to$snps)
188
+  } else {
189
+    to$use_snps <- NULL
190
+  }
191
+  to$snpsdir <- path(directory(to$snps))
192
+  to$snps <- NULL
193
+  to
194
+})
195
+
196
+setMethod("as.list", "GsnapParam", function(x) as(x, "list"))
197
+
198
+### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
199
+### Show
200
+###
201
+
202
+setMethod("show", "GsnapParam", function(object) {
203
+  slots <- lapply(slotNames(object), slot, object = object)
204
+  names(slots) <- slotNames(object)
205
+  slots$genome <- paste0(slots$genome@name,
206
+                         " (", path(directory(slots$genome)), ")")
207
+  if (!is.null(slots$snps)) {
208
+    slots$snps <- paste0(name(slots$snps),
209
+                         " (", path(directory(slots$snps)), ")")
210
+  }
211
+  cat("A GsnapParams object\n",
212
+      paste0(names(slots), ": ", slots, collapse = "\n"), "\n", sep = "")
213
+})