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
 ###