git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@111240 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -47,7 +47,7 @@ setMethod("gmap", c("character", "GmapParam"), |
47 | 47 |
output_path <- output_dir |
48 | 48 |
} else { |
49 | 49 |
output_path <- paste0(output, ".", |
50 |
- formatToExt(params$format)) |
|
50 |
+ formatToExt(params_list$format)) |
|
51 | 51 |
params_list$.redirect <- paste(">", output_path) |
52 | 52 |
} |
53 | 53 |
|
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@110840 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -6,6 +6,133 @@ |
6 | 6 |
### High-level interface |
7 | 7 |
### |
8 | 8 |
|
9 |
+setGeneric("gmap", function(input, params, ...) standardGeneric("gmap")) |
|
10 |
+ |
|
11 |
+setMethod("gmap", c("ANY", "GmapParam"), |
|
12 |
+ function(input, params, ...) { |
|
13 |
+ tmpfile <- tempfile() |
|
14 |
+ export(input, tmpfile, format="fasta") |
|
15 |
+ input <- tmpfile |
|
16 |
+ callGeneric() |
|
17 |
+ }) |
|
18 |
+ |
|
19 |
+setMethod("gmap", c("FastaFile", "GmapParam"), |
|
20 |
+ function(input, params, ...) { |
|
21 |
+ input <- path(input) |
|
22 |
+ callGeneric() |
|
23 |
+ }) |
|
24 |
+ |
|
25 |
+setMethod("gmap", c("character", "GmapParam"), |
|
26 |
+ function(input, params, |
|
27 |
+ output = file.path(getwd(), |
|
28 |
+ file_path_sans_ext(basename(input), TRUE)), ...) |
|
29 |
+ { |
|
30 |
+ if (any(is.na(input))) |
|
31 |
+ stop("'input' must not contain NA's") |
|
32 |
+ if (length(input) > 1L) { |
|
33 |
+ return(GmapOutputList(mapply(gmap, input, |
|
34 |
+ MoreArgs = |
|
35 |
+ list(params, output, |
|
36 |
+ ...)))) |
|
37 |
+ } |
|
38 |
+ |
|
39 |
+ output_dir <- dirname(output) |
|
40 |
+ if (!file.exists(output_dir)) |
|
41 |
+ dir.create(output_dir, recursive = TRUE) |
|
42 |
+ |
|
43 |
+ params <- initialize(params, ...) |
|
44 |
+ params_list <- as.list(params) |
|
45 |
+ if (gsnap_split_output(params)) { |
|
46 |
+ params_list$split_output <- output |
|
47 |
+ output_path <- output_dir |
|
48 |
+ } else { |
|
49 |
+ output_path <- paste0(output, ".", |
|
50 |
+ formatToExt(params$format)) |
|
51 |
+ params_list$.redirect <- paste(">", output_path) |
|
52 |
+ } |
|
53 |
+ |
|
54 |
+ res <- do.call(.gmap, |
|
55 |
+ c(list(.input = input), params_list)) |
|
56 |
+ gmap_output<- GmapOutput(path = output_path, |
|
57 |
+ version = gmapVersion(), |
|
58 |
+ param = params) |
|
59 |
+ |
|
60 |
+ if (params_list$format %in% c("samse", "sampe")) { |
|
61 |
+ gmap_output <- asBam(gmap_output) |
|
62 |
+ } |
|
63 |
+ gmap_output |
|
64 |
+ }) |
|
65 |
+ |
|
9 | 66 |
### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - |
10 | 67 |
### Low-level interface |
11 | 68 |
### |
69 |
+ |
|
70 |
+.gmap <- function(db = NULL, dir = NULL, |
|
71 |
+ kmer = NULL, basesize = NULL, sampling = NULL, |
|
72 |
+ genomefull = FALSE, gseg = NULL, |
|
73 |
+ selfalign = FALSE, pairalign = FALSE, |
|
74 |
+ part = NULL, input_buffer_size = 1000L, |
|
75 |
+ batch = c("0", "1", "2", "3", "4", "5"), |
|
76 |
+ expand_offsets = FALSE, nosplicing = FALSE, |
|
77 |
+ min_intronlength = 9L, intronlength = 1000000L, |
|
78 |
+ localsplicedist = 2000000L, totallength = 2400000L, |
|
79 |
+ chimera_margin = 40L, no_chimeras = FALSE, |
|
80 |
+ nthreads = NULL, chrsubsetfile = NULL, |
|
81 |
+ direction = c("auto", "sense_force", "antisense_force", |
|
82 |
+ "sense_filter", "antisense_filter"), |
|
83 |
+ trimendexons = 12L, canonical_mode = c("1", "0", "2"), |
|
84 |
+ cross_species = FALSE, allow_close_indels = c("1", "0", "2"), |
|
85 |
+ microexon_spliceprob = 0.90, cmetdir = NULL, atoidir = NULL, |
|
86 |
+ mode = c("standard", "cmet-stranded", "cmet-nonstranded", |
|
87 |
+ "atoi-stranded", "atoi-nonstranded"), |
|
88 |
+ prunelevel = c("0", "1", "2", "3"), |
|
89 |
+ format = NULL, npaths = 5L, quiet_if_excessive = FALSE, |
|
90 |
+ suboptimal_score = NULL, ordered = FALSE, md5 = FALSE, |
|
91 |
+ chimera_overlap = FALSE, failsonly = FALSE, nofails = FALSE, |
|
92 |
+ fails_as_input = FALSE, snpsdir = NULL, use_snps = NULL, |
|
93 |
+ split_output = NULL, append_output = FALSE, |
|
94 |
+ output_buffer_size = 1000L, fulllength = FALSE, |
|
95 |
+ cdsstart = NULL, truncate = FALSE, tolerant = FALSE, |
|
96 |
+ no_sam_headers = FALSE, sam_use_0M = FALSE, |
|
97 |
+ force_xs_dir = FALSE, md_lowercase_snp = FALSE, |
|
98 |
+ read_group_id = NULL, read_group_name = NULL, |
|
99 |
+ read_group_library = NULL, read_group_platform = NULL, |
|
100 |
+ quality_protocol = c("sanger", "illumina"), |
|
101 |
+ quality_print_shift = 0L, mapdir = NULL, map = NULL, |
|
102 |
+ mapexons = FALSE, mapboth = FALSE, version = FALSE, |
|
103 |
+ .input = NULL, .redirect = NULL) |
|
104 |
+{ |
|
105 |
+ formals <- formals(sys.function()) |
|
106 |
+ |
|
107 |
+ expand_offsets <- as.integer(expand_offsets) |
|
108 |
+ batch <- match.arg(batch) |
|
109 |
+ direction <- match.arg(direction) |
|
110 |
+ canonical_mode <- match.arg(canonical_mode) |
|
111 |
+ allow_close_indels <- match.arg(allow_close_indels) |
|
112 |
+ mode <- match.arg(mode) |
|
113 |
+ prunelevel <- match.arg(prunelevel) |
|
114 |
+ quality_protocol <- match.arg(quality_protocol) |
|
115 |
+ |
|
116 |
+ if (version) { |
|
117 |
+ .redirect <- ">/dev/null" |
|
118 |
+ } |
|
119 |
+ |
|
120 |
+### TODO: if input_a is NULL, or split_output and .redirect are NULL: |
|
121 |
+### return a pipe() |
|
122 |
+ .system_gsnap(commandLine("gmap")) |
|
123 |
+} |
|
124 |
+ |
|
125 |
+..gmap <- function(args, path = NULL) { |
|
126 |
+ .system_gsnap(.commandLine("gmap", args, path)) |
|
127 |
+} |
|
128 |
+ |
|
129 |
+### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - |
|
130 |
+### Utilities |
|
131 |
+### |
|
132 |
+ |
|
133 |
+gmapVersion <- function() { |
|
134 |
+ output <- .gmap(version = TRUE) |
|
135 |
+ version_text <- sub("GMAP version (.*?) .*", "\\1", output[1]) |
|
136 |
+ parseGsnapVersion(version_text) |
|
137 |
+} |
|
138 |
+ |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@68172 bc3139a8-67e5-0310-9ffc-ced21a209358
1 | 1 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,11 @@ |
1 |
+### ========================================================================= |
|
2 |
+### gmap command |
|
3 |
+### ------------------------------------------------------------------------- |
|
4 |
+ |
|
5 |
+### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - |
|
6 |
+### High-level interface |
|
7 |
+### |
|
8 |
+ |
|
9 |
+### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - |
|
10 |
+### Low-level interface |
|
11 |
+### |