Browse code

gsnap will now output a GsnapOutputList when there are multiple input files; this means that the return value is more dependent on the input than we may like; perhaps we want a FastqFile and FastqFileList to make this more consistent?

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

Michael Lawrence authored on 23/08/2013 14:22:00
Showing 2 changed files

... ...
@@ -173,6 +173,18 @@ setClass("GsnapOutputList",
173 173
 setClass("SimpleGsnapOutputList",
174 174
          contains = c("GsnapOutputList", "SimpleList"))
175 175
 
176
+GsnapOutputList <- function(...) {
177
+  args <- list(...)
178
+  if (length(args) == 1 && is.list(args[[1]])) 
179
+    args <- args[[1]]
180
+  IRanges:::newList("SimpleGsnapOutputList", args)
181
+}
182
+
183
+setAs("GsnapOutputList", "BamFileList", function(from) {
184
+  BamFileList(lapply(from, as, "BamFile"))
185
+})
186
+
187
+
176 188
 ### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
177 189
 ### Show
178 190
 ###
... ...
@@ -14,6 +14,15 @@ setMethod("gsnap", c("character", "characterORNULL", "GsnapParam"),
14 14
                    output = file_path_sans_ext(input_a, TRUE),
15 15
                    consolidate = TRUE, ...)
16 16
           {
17
+            if (!is.null(input_b) && length(input_a) != length(input_b))
18
+              stop("If 'input_b' is non-NULL, it must have the same length",
19
+                   " as 'input_a'")
20
+            if (length(input_a) > 1L) {
21
+              return(GsnapOutputList(mapply(gsnap, input_a, input_b,
22
+                                            MoreArgs = list(params, output,
23
+                                              consolidate, ...))))
24
+            }
25
+            
17 26
             output_dir <- dirname(output)
18 27
             if (!file.exists(output_dir))
19 28
               dir.create(output_dir, recursive = TRUE)