... | ... |
@@ -50,8 +50,8 @@ setGeneric("genomeName", function(x) standardGeneric("genomeName")) |
50 | 50 |
|
51 | 51 |
setMethod("genomeName", "character", function(x) x) |
52 | 52 |
setMethod("genomeName", "BSgenome", function(x) providerVersion(x)) |
53 |
-setMethods("genomeName", list("RTLFile", "RsamtoolsFile"), |
|
54 |
- function(x) file_path_sans_ext(basename(path(x)), TRUE)) |
|
53 |
+setMethod("genomeName", "BiocFile", |
|
54 |
+ function(x) file_path_sans_ext(basename(path(x)), TRUE)) |
|
55 | 55 |
setMethod("genomeName", "ANY", function(x) { |
56 | 56 |
if (hasMethod("seqinfo", class(x))) { |
57 | 57 |
ans <- unique(genome(x)) |
Needed because we are running it inside a temporary directory. That
logic is now passed down to gmap_build() from referenceSequence<-().
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@129717 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -121,16 +121,7 @@ setReplaceMethod("referenceSequence", |
121 | 121 |
signature(x = "GmapGenome", value = "ANY"), |
122 | 122 |
function(x, name, ..., value) |
123 | 123 |
{ |
124 |
- gmap_db_tmp_dir <- file.path(tempdir(), "gmap_db_tmp_dir") |
|
125 |
- dir.create(gmap_db_tmp_dir, recursive=TRUE) |
|
126 |
- cur_wd <- getwd() |
|
127 |
- on.exit({unlink(gmap_db_tmp_dir, recursive=TRUE) |
|
128 |
- setwd(cur_wd)}) |
|
129 |
- setwd(gmap_db_tmp_dir) |
|
130 |
- |
|
131 |
- db <- gmap_build(value, x, ...) |
|
132 |
- |
|
133 |
- db |
|
124 |
+ gmap_build(value, x, ...) |
|
134 | 125 |
}) |
135 | 126 |
|
136 | 127 |
setGeneric("snps<-", function(x, name, ..., value) standardGeneric("snps<-")) |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@129664 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -178,7 +178,10 @@ setReplaceMethod("spliceSites", c("GmapGenome", "TxDb"), |
178 | 178 |
|
179 | 179 |
setMethod("getSeq", "GmapGenome", function(x, which = seqinfo(x)) { |
180 | 180 |
if (!.gmapGenomeCreated(x)) |
181 |
- stop("Genome index does not exist") |
|
181 |
+ stop("Genome index does not exist") |
|
182 |
+ if (is.character(which)) { |
|
183 |
+ which <- seqinfo(x)[which] |
|
184 |
+ } |
|
182 | 185 |
which <- as(which, "GRanges") |
183 | 186 |
merge(seqinfo(x), seqinfo(which)) # for the checks |
184 | 187 |
ans <- .Call(R_Genome_getSeq, path(directory(x)), genome(x), |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@125152 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -52,6 +52,17 @@ setMethod("genomeName", "character", function(x) x) |
52 | 52 |
setMethod("genomeName", "BSgenome", function(x) providerVersion(x)) |
53 | 53 |
setMethods("genomeName", list("RTLFile", "RsamtoolsFile"), |
54 | 54 |
function(x) file_path_sans_ext(basename(path(x)), TRUE)) |
55 |
+setMethod("genomeName", "ANY", function(x) { |
|
56 |
+ if (hasMethod("seqinfo", class(x))) { |
|
57 |
+ ans <- unique(genome(x)) |
|
58 |
+ if (length(ans) > 1L) { |
|
59 |
+ stop("genome is ambiguous") |
|
60 |
+ } |
|
61 |
+ ans |
|
62 |
+ } else { |
|
63 |
+ stop("cannot derive a genome name") |
|
64 |
+ } |
|
65 |
+}) |
|
55 | 66 |
|
56 | 67 |
file_path_is_absolute <- function(x) { |
57 | 68 |
## hack that is unlikely to work on e.g. Windows |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@110737 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -50,8 +50,8 @@ setGeneric("genomeName", function(x) standardGeneric("genomeName")) |
50 | 50 |
|
51 | 51 |
setMethod("genomeName", "character", function(x) x) |
52 | 52 |
setMethod("genomeName", "BSgenome", function(x) providerVersion(x)) |
53 |
-setMethod("genomeName", "RTLFile", |
|
54 |
- function(x) file_path_sans_ext(basename(path(x)), TRUE)) |
|
53 |
+setMethods("genomeName", list("RTLFile", "RsamtoolsFile"), |
|
54 |
+ function(x) file_path_sans_ext(basename(path(x)), TRUE)) |
|
55 | 55 |
|
56 | 56 |
file_path_is_absolute <- function(x) { |
57 | 57 |
## hack that is unlikely to work on e.g. Windows |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@99428 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -169,6 +169,7 @@ setMethod("getSeq", "GmapGenome", function(x, which = seqinfo(x)) { |
169 | 169 |
if (!.gmapGenomeCreated(x)) |
170 | 170 |
stop("Genome index does not exist") |
171 | 171 |
which <- as(which, "GRanges") |
172 |
+ merge(seqinfo(x), seqinfo(which)) # for the checks |
|
172 | 173 |
ans <- .Call(R_Genome_getSeq, path(directory(x)), genome(x), |
173 | 174 |
as.character(seqnames(which)), start(which), width(which), |
174 | 175 |
as.character(strand(which))) |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@95333 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -50,7 +50,7 @@ setGeneric("genomeName", function(x) standardGeneric("genomeName")) |
50 | 50 |
|
51 | 51 |
setMethod("genomeName", "character", function(x) x) |
52 | 52 |
setMethod("genomeName", "BSgenome", function(x) providerVersion(x)) |
53 |
-setMethod("genomeName", "FastaFile", |
|
53 |
+setMethod("genomeName", "RTLFile", |
|
54 | 54 |
function(x) file_path_sans_ext(basename(path(x)), TRUE)) |
55 | 55 |
|
56 | 56 |
file_path_is_absolute <- function(x) { |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@93316 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -154,6 +154,7 @@ setReplaceMethod("spliceSites", c("GmapGenome", "GRangesList"), |
154 | 154 |
x |
155 | 155 |
}) |
156 | 156 |
|
157 |
+#setReplaceMethod("spliceSites", c("GmapGenome", "TranscriptDb"), |
|
157 | 158 |
setReplaceMethod("spliceSites", c("GmapGenome", "TxDb"), |
158 | 159 |
function(x, name, value) { |
159 | 160 |
spliceSites(x, name) <- exonsBy(value) |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@92976 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -154,7 +154,7 @@ setReplaceMethod("spliceSites", c("GmapGenome", "GRangesList"), |
154 | 154 |
x |
155 | 155 |
}) |
156 | 156 |
|
157 |
-setReplaceMethod("spliceSites", c("GmapGenome", "TranscriptDb"), |
|
157 |
+setReplaceMethod("spliceSites", c("GmapGenome", "TxDb"), |
|
158 | 158 |
function(x, name, value) { |
159 | 159 |
spliceSites(x, name) <- exonsBy(value) |
160 | 160 |
x |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@80610 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -32,10 +32,13 @@ mapsDirectory <- function(x) { |
32 | 32 |
setMethod("seqinfo", "GmapGenome", function(x) { |
33 | 33 |
if (!.gmapGenomeCreated(x)) |
34 | 34 |
stop("GmapGenome index '", genome(x), "' does not exist") |
35 |
- tab <- read.table(.get_genome(path(directory(x)), genome(x), |
|
36 |
- chromosomes = TRUE), |
|
37 |
- colClasses = c("character", "NULL", "integer", "character"), |
|
38 |
- fill = TRUE) |
|
35 |
+ suppressWarnings({ # warning when colClasses is too long, even when fill=TRUE! |
|
36 |
+ tab <- read.table(.get_genome(path(directory(x)), genome(x), |
|
37 |
+ chromosomes = TRUE), |
|
38 |
+ colClasses = c("character", "NULL", "integer", |
|
39 |
+ "character"), |
|
40 |
+ fill = TRUE) |
|
41 |
+ }) |
|
39 | 42 |
Seqinfo(tab[,1], tab[,2], nzchar(tab[,3]), genome = genome(x)) |
40 | 43 |
}) |
41 | 44 |
|
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@80504 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -34,8 +34,9 @@ setMethod("seqinfo", "GmapGenome", function(x) { |
34 | 34 |
stop("GmapGenome index '", genome(x), "' does not exist") |
35 | 35 |
tab <- read.table(.get_genome(path(directory(x)), genome(x), |
36 | 36 |
chromosomes = TRUE), |
37 |
- colClasses = c("character", "NULL", "integer")) |
|
38 |
- Seqinfo(tab[,1], tab[,2], genome = genome(x)) |
|
37 |
+ colClasses = c("character", "NULL", "integer", "character"), |
|
38 |
+ fill = TRUE) |
|
39 |
+ Seqinfo(tab[,1], tab[,2], nzchar(tab[,3]), genome = genome(x)) |
|
39 | 40 |
}) |
40 | 41 |
|
41 | 42 |
### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@79760 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -30,6 +30,8 @@ mapsDirectory <- function(x) { |
30 | 30 |
} |
31 | 31 |
|
32 | 32 |
setMethod("seqinfo", "GmapGenome", function(x) { |
33 |
+ if (!.gmapGenomeCreated(x)) |
|
34 |
+ stop("GmapGenome index '", genome(x), "' does not exist") |
|
33 | 35 |
tab <- read.table(.get_genome(path(directory(x)), genome(x), |
34 | 36 |
chromosomes = TRUE), |
35 | 37 |
colClasses = c("character", "NULL", "integer")) |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@78526 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -189,6 +189,8 @@ setMethod("show", "GmapGenome", function(object) { |
189 | 189 |
path(directory(object)), "\n") |
190 | 190 |
}) |
191 | 191 |
|
192 |
+setMethod("showAsCell", "GmapGenome", function(object) genome(object)) |
|
193 |
+ |
|
192 | 194 |
### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - |
193 | 195 |
### Utilities |
194 | 196 |
### |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@78421 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -47,12 +47,30 @@ setMethod("genomeName", "BSgenome", function(x) providerVersion(x)) |
47 | 47 |
setMethod("genomeName", "FastaFile", |
48 | 48 |
function(x) file_path_sans_ext(basename(path(x)), TRUE)) |
49 | 49 |
|
50 |
+file_path_is_absolute <- function(x) { |
|
51 |
+ ## hack that is unlikely to work on e.g. Windows |
|
52 |
+ identical(substring(x, 1, 1), .Platform$file.sep) |
|
53 |
+} |
|
54 |
+ |
|
55 |
+file_path_is_dir <- function(x) { |
|
56 |
+ isTRUE(file.info(x)[,"isdir"]) |
|
57 |
+} |
|
58 |
+ |
|
50 | 59 |
GmapGenome <- function(genome, |
51 | 60 |
directory = GmapGenomeDirectory(create = create), |
52 | 61 |
name = genomeName(genome), create = FALSE, ...) |
53 | 62 |
{ |
54 | 63 |
if (!isTRUEorFALSE(create)) |
55 | 64 |
stop("'create' must be TRUE or FALSE") |
65 |
+ if (isSingleString(genome) && file_path_is_dir(genome)) { |
|
66 |
+ genome <- path.expand(genome) |
|
67 |
+ if (file_path_is_absolute(genome)) { |
|
68 |
+ if (!missing(directory)) |
|
69 |
+ stop("'directory' should be missing when 'genome' is an absolute path") |
|
70 |
+ directory <- dirname(genome) |
|
71 |
+ genome <- basename(genome) |
|
72 |
+ } |
|
73 |
+ } |
|
56 | 74 |
if (isSingleString(directory)) |
57 | 75 |
directory <- GmapGenomeDirectory(directory, create = create) |
58 | 76 |
if (is(genome, "DNAStringSet")) { |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@75244 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -141,6 +141,8 @@ setReplaceMethod("spliceSites", c("GmapGenome", "TranscriptDb"), |
141 | 141 |
### |
142 | 142 |
|
143 | 143 |
setMethod("getSeq", "GmapGenome", function(x, which = seqinfo(x)) { |
144 |
+ if (!.gmapGenomeCreated(x)) |
|
145 |
+ stop("Genome index does not exist") |
|
144 | 146 |
which <- as(which, "GRanges") |
145 | 147 |
ans <- .Call(R_Genome_getSeq, path(directory(x)), genome(x), |
146 | 148 |
as.character(seqnames(which)), start(which), width(which), |
... | ... |
@@ -179,3 +181,20 @@ setMethod("show", "GmapGenome", function(object) { |
179 | 181 |
db |
180 | 182 |
} |
181 | 183 |
|
184 |
+ |
|
185 |
+.gmapGenomeCreated <- function(genome) { |
|
186 |
+ ##existance means the GENOME_NAME.chromosome exists |
|
187 |
+ |
|
188 |
+ d <- path(directory(genome)) |
|
189 |
+ if (!file.exists(d)) |
|
190 |
+ return(FALSE) |
|
191 |
+ |
|
192 |
+ chromosome.file <- paste(genome(genome), "chromosome", sep=".") |
|
193 |
+ possibleLoc1 <- file.path(d, chromosome.file) |
|
194 |
+ possibleLoc2 <- file.path(d, genome(genome), chromosome.file) |
|
195 |
+ if (!(file.exists(possibleLoc1) || file.exists(possibleLoc2))) |
|
196 |
+ return(FALSE) |
|
197 |
+ |
|
198 |
+ return(TRUE) |
|
199 |
+} |
|
200 |
+ |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@75207 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -145,8 +145,8 @@ setMethod("getSeq", "GmapGenome", function(x, which = seqinfo(x)) { |
145 | 145 |
ans <- .Call(R_Genome_getSeq, path(directory(x)), genome(x), |
146 | 146 |
as.character(seqnames(which)), start(which), width(which), |
147 | 147 |
as.character(strand(which))) |
148 |
- if (!is.null(names(x))) |
|
149 |
- names(ans) <- names(x) |
|
148 |
+ if (!is.null(names(which))) |
|
149 |
+ names(ans) <- names(which) |
|
150 | 150 |
ans |
151 | 151 |
}) |
152 | 152 |
|
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@74945 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -142,9 +142,12 @@ setReplaceMethod("spliceSites", c("GmapGenome", "TranscriptDb"), |
142 | 142 |
|
143 | 143 |
setMethod("getSeq", "GmapGenome", function(x, which = seqinfo(x)) { |
144 | 144 |
which <- as(which, "GRanges") |
145 |
- .Call(R_Genome_getSeq, path(directory(x)), genome(x), |
|
146 |
- as.character(seqnames(which)), start(which), width(which), |
|
147 |
- as.character(strand(which))) |
|
145 |
+ ans <- .Call(R_Genome_getSeq, path(directory(x)), genome(x), |
|
146 |
+ as.character(seqnames(which)), start(which), width(which), |
|
147 |
+ as.character(strand(which))) |
|
148 |
+ if (!is.null(names(x))) |
|
149 |
+ names(ans) <- names(x) |
|
150 |
+ ans |
|
148 | 151 |
}) |
149 | 152 |
|
150 | 153 |
### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - |
... | ... |
@@ -153,6 +156,10 @@ setMethod("getSeq", "GmapGenome", function(x, which = seqinfo(x)) { |
153 | 156 |
|
154 | 157 |
setAs("ANY", "GmapGenome", function(from) GmapGenome(from)) |
155 | 158 |
|
159 |
+setAs("GmapGenome", "DNAStringSet", function(from) { |
|
160 |
+ DNAStringSet(getSeq(from)) |
|
161 |
+}) |
|
162 |
+ |
|
156 | 163 |
### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - |
157 | 164 |
### Show |
158 | 165 |
### |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@74943 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -140,7 +140,7 @@ setReplaceMethod("spliceSites", c("GmapGenome", "TranscriptDb"), |
140 | 140 |
### Sequence access |
141 | 141 |
### |
142 | 142 |
|
143 |
-setMethod("getSeq", "GmapGenome", function(x, which) { |
|
143 |
+setMethod("getSeq", "GmapGenome", function(x, which = seqinfo(x)) { |
|
144 | 144 |
which <- as(which, "GRanges") |
145 | 145 |
.Call(R_Genome_getSeq, path(directory(x)), genome(x), |
146 | 146 |
as.character(seqnames(which)), start(which), width(which), |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@74875 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -136,6 +136,17 @@ setReplaceMethod("spliceSites", c("GmapGenome", "TranscriptDb"), |
136 | 136 |
x |
137 | 137 |
}) |
138 | 138 |
|
139 |
+### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - |
|
140 |
+### Sequence access |
|
141 |
+### |
|
142 |
+ |
|
143 |
+setMethod("getSeq", "GmapGenome", function(x, which) { |
|
144 |
+ which <- as(which, "GRanges") |
|
145 |
+ .Call(R_Genome_getSeq, path(directory(x)), genome(x), |
|
146 |
+ as.character(seqnames(which)), start(which), width(which), |
|
147 |
+ as.character(strand(which))) |
|
148 |
+}) |
|
149 |
+ |
|
139 | 150 |
### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - |
140 | 151 |
### Coerce |
141 | 152 |
### |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@69343 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -58,7 +58,12 @@ GmapGenome <- function(genome, |
58 | 58 |
if (is(genome, "DNAStringSet")) { |
59 | 59 |
if (missing(name)) |
60 | 60 |
stop("If the genome argument is a DNAStringSet object", |
61 |
- "the name argument must be provided") |
|
61 |
+ "the name argument must be provided") |
|
62 |
+ if (is.null(names(genome))) { |
|
63 |
+ stop("If the genome is provided as a DNAStringSet, ", |
|
64 |
+ "the genome needs to have names. ", |
|
65 |
+ "E.g., \"names(genome) <- someSeqNames") |
|
66 |
+ } |
|
62 | 67 |
} |
63 | 68 |
if (!isSingleString(name)) |
64 | 69 |
stop("'name' must be a single, non-NA string") |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@69218 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -109,7 +109,7 @@ setGeneric("spliceSites<-", |
109 | 109 |
setReplaceMethod("spliceSites", c("GmapGenome", "GRangesList"), |
110 | 110 |
function(x, name, value) { |
111 | 111 |
exonsFlat <- unlist(value, use.names=FALSE) |
112 |
- exonsPart <- PartitioningByWidth(exons) |
|
112 |
+ exonsPart <- PartitioningByWidth(value) |
|
113 | 113 |
exonsHead <- exonsFlat[-end(exonsPart)] |
114 | 114 |
donors <- flank(exonsHead, 1L, start = FALSE) |
115 | 115 |
exonsTail <- exonsFlat[-start(exonsPart)] |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@69210 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -118,7 +118,7 @@ setReplaceMethod("spliceSites", c("GmapGenome", "GRangesList"), |
118 | 118 |
resize(acceptors, 2L, fix = "start")) |
119 | 119 |
names(sites) <- values(sites)$exon_id |
120 | 120 |
info <- rep(c("donor", "acceptor"), each = length(donors)) |
121 |
- intronWidths <- abs(acceptors - donors) + 1L |
|
121 |
+ intronWidths <- abs(start(acceptors) - start(donors)) + 1L |
|
122 | 122 |
info <- paste(info, intronWidths) |
123 | 123 |
values(sites) <- DataFrame(info) |
124 | 124 |
iit_store(sites, file.path(mapsDirectory(x), name)) |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@69204 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -108,7 +108,6 @@ setGeneric("spliceSites<-", |
108 | 108 |
|
109 | 109 |
setReplaceMethod("spliceSites", c("GmapGenome", "GRangesList"), |
110 | 110 |
function(x, name, value) { |
111 |
- browser() |
|
112 | 111 |
exonsFlat <- unlist(value, use.names=FALSE) |
113 | 112 |
exonsPart <- PartitioningByWidth(exons) |
114 | 113 |
exonsHead <- exonsFlat[-end(exonsPart)] |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@69198 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -106,25 +106,32 @@ setReplaceMethod("snps", c("GmapGenome", "ANY"), |
106 | 106 |
setGeneric("spliceSites<-", |
107 | 107 |
function(x, ..., value) standardGeneric("spliceSites<-")) |
108 | 108 |
|
109 |
-setReplaceMethod("spliceSites", c("GmapGenome", "TranscriptDb"), |
|
109 |
+setReplaceMethod("spliceSites", c("GmapGenome", "GRangesList"), |
|
110 | 110 |
function(x, name, value) { |
111 |
- exons <- exonsBy(value) |
|
112 |
- exonsFlat <- unlist(exons, use.names=FALSE) |
|
111 |
+ browser() |
|
112 |
+ exonsFlat <- unlist(value, use.names=FALSE) |
|
113 | 113 |
exonsPart <- PartitioningByWidth(exons) |
114 | 114 |
exonsHead <- exonsFlat[-end(exonsPart)] |
115 |
- donors <- flank(exonsHead, 1L, start = FALSE, both = TRUE) |
|
115 |
+ donors <- flank(exonsHead, 1L, start = FALSE) |
|
116 | 116 |
exonsTail <- exonsFlat[-start(exonsPart)] |
117 |
- acceptors <- flank(exonsTail, 1L, start = TRUE, both = TRUE) |
|
118 |
- sites <- c(donors, acceptors) |
|
117 |
+ acceptors <- flank(exonsTail, 1L, start = TRUE) |
|
118 |
+ sites <- c(resize(donors, 2L, fix = "end"), |
|
119 |
+ resize(acceptors, 2L, fix = "start")) |
|
119 | 120 |
names(sites) <- values(sites)$exon_id |
120 | 121 |
info <- rep(c("donor", "acceptor"), each = length(donors)) |
121 |
- info <- paste(info, unlist(width(intronsByTranscript(value)), |
|
122 |
- use.names = FALSE)) |
|
122 |
+ intronWidths <- abs(acceptors - donors) + 1L |
|
123 |
+ info <- paste(info, intronWidths) |
|
123 | 124 |
values(sites) <- DataFrame(info) |
124 | 125 |
iit_store(sites, file.path(mapsDirectory(x), name)) |
125 | 126 |
x |
126 | 127 |
}) |
127 | 128 |
|
129 |
+setReplaceMethod("spliceSites", c("GmapGenome", "TranscriptDb"), |
|
130 |
+ function(x, name, value) { |
|
131 |
+ spliceSites(x, name) <- exonsBy(value) |
|
132 |
+ x |
|
133 |
+ }) |
|
134 |
+ |
|
128 | 135 |
### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - |
129 | 136 |
### Coerce |
130 | 137 |
### |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@69059 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -93,7 +93,7 @@ setReplaceMethod("referenceSequence", |
93 | 93 |
db |
94 | 94 |
}) |
95 | 95 |
|
96 |
-setGeneric("snps<-", function(x, ..., value) standardGeneric("snps<-")) |
|
96 |
+setGeneric("snps<-", function(x, name, ..., value) standardGeneric("snps<-")) |
|
97 | 97 |
|
98 | 98 |
setReplaceMethod("snps", c("GmapGenome", "ANY"), |
99 | 99 |
function(x, name, ..., value) { |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@68691 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -96,7 +96,7 @@ setReplaceMethod("referenceSequence", |
96 | 96 |
setGeneric("snps<-", function(x, ..., value) standardGeneric("snps<-")) |
97 | 97 |
|
98 | 98 |
setReplaceMethod("snps", c("GmapGenome", "ANY"), |
99 |
- function(x, ..., value) { |
|
99 |
+ function(x, name, ..., value) { |
|
100 | 100 |
snpDir <- GmapSnpDirectory(x) |
101 | 101 |
snps(snpDir, name = name, genome = x, |
102 | 102 |
iitPath = mapsDirectory(x), ...) <- value |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/gmapR@68556 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -125,6 +125,12 @@ setReplaceMethod("spliceSites", c("GmapGenome", "TranscriptDb"), |
125 | 125 |
x |
126 | 126 |
}) |
127 | 127 |
|
128 |
+### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - |
|
129 |
+### Coerce |
|
130 |
+### |
|
131 |
+ |
|
132 |
+setAs("ANY", "GmapGenome", function(from) GmapGenome(from)) |
|
133 |
+ |
|
128 | 134 |
### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - |
129 | 135 |
### Show |
130 | 136 |
### |
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,146 @@ |
1 |
+### ========================================================================= |
|
2 |
+### GmapGenome class |
|
3 |
+### ------------------------------------------------------------------------- |
|
4 |
+### |
|
5 |
+### Database of reference sequence used by the GMAP suite. |
|
6 |
+### |
|
7 |
+ |
|
8 |
+setClass("GmapGenome", representation(name = "character", |
|
9 |
+ directory = "GmapGenomeDirectory")) |
|
10 |
+ |
|
11 |
+### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - |
|
12 |
+### Accessors |
|
13 |
+### |
|
14 |
+ |
|
15 |
+directory <- function(x) { |
|
16 |
+ retVal <- NULL |
|
17 |
+ if (!is.null(x)) { |
|
18 |
+ retVal <- x@directory ## 'dir' is already taken |
|
19 |
+ } |
|
20 |
+ return(retVal) |
|
21 |
+} |
|
22 |
+ |
|
23 |
+setMethod("genome", "GmapGenome", function(x) x@name) |
|
24 |
+ |
|
25 |
+setMethod("path", "GmapGenome", |
|
26 |
+ function(object) file.path(path(directory(object)), genome(object))) |
|
27 |
+ |
|
28 |
+mapsDirectory <- function(x) { |
|
29 |
+ file.path(path(x), paste(genome(x), "maps", sep = ".")) |
|
30 |
+} |
|
31 |
+ |
|
32 |
+setMethod("seqinfo", "GmapGenome", function(x) { |
|
33 |
+ tab <- read.table(.get_genome(path(directory(x)), genome(x), |
|
34 |
+ chromosomes = TRUE), |
|
35 |
+ colClasses = c("character", "NULL", "integer")) |
|
36 |
+ Seqinfo(tab[,1], tab[,2], genome = genome(x)) |
|
37 |
+}) |
|
38 |
+ |
|
39 |
+### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - |
|
40 |
+### Constructor |
|
41 |
+### |
|
42 |
+ |
|
43 |
+setGeneric("genomeName", function(x) standardGeneric("genomeName")) |
|
44 |
+ |
|
45 |
+setMethod("genomeName", "character", function(x) x) |
|
46 |
+setMethod("genomeName", "BSgenome", function(x) providerVersion(x)) |
|
47 |
+setMethod("genomeName", "FastaFile", |
|
48 |
+ function(x) file_path_sans_ext(basename(path(x)), TRUE)) |
|
49 |
+ |
|
50 |
+GmapGenome <- function(genome, |
|
51 |
+ directory = GmapGenomeDirectory(create = create), |
|
52 |
+ name = genomeName(genome), create = FALSE, ...) |
|
53 |
+{ |
|
54 |
+ if (!isTRUEorFALSE(create)) |
|
55 |
+ stop("'create' must be TRUE or FALSE") |
|
56 |
+ if (isSingleString(directory)) |
|
57 |
+ directory <- GmapGenomeDirectory(directory, create = create) |
|
58 |
+ if (is(genome, "DNAStringSet")) { |
|
59 |
+ if (missing(name)) |
|
60 |
+ stop("If the genome argument is a DNAStringSet object", |
|
61 |
+ "the name argument must be provided") |
|
62 |
+ } |
|
63 |
+ if (!isSingleString(name)) |
|
64 |
+ stop("'name' must be a single, non-NA string") |
|
65 |
+ if (!is(directory, "GmapGenomeDirectory")) |
|
66 |
+ stop("'directory' must be a GmapGenomeDirectory object or path to one") |
|
67 |
+ db <- new("GmapGenome", name = name, directory = directory) |
|
68 |
+ if (create) { |
|
69 |
+ if (name %in% genome(directory)) |
|
70 |
+ message("NOTE: genome '", name, "' already exists, not overwriting") |
|
71 |
+ else referenceSequence(db, ...) <- genome |
|
72 |
+ } |
|
73 |
+ db |
|
74 |
+} |
|
75 |
+ |
|
76 |
+### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - |
|
77 |
+### Building |
|
78 |
+### |
|
79 |
+ |
|
80 |
+setReplaceMethod("referenceSequence", |
|
81 |
+ signature(x = "GmapGenome", value = "ANY"), |
|
82 |
+ function(x, name, ..., value) |
|
83 |
+ { |
|
84 |
+ gmap_db_tmp_dir <- file.path(tempdir(), "gmap_db_tmp_dir") |
|
85 |
+ dir.create(gmap_db_tmp_dir, recursive=TRUE) |
|
86 |
+ cur_wd <- getwd() |
|
87 |
+ on.exit({unlink(gmap_db_tmp_dir, recursive=TRUE) |
|
88 |
+ setwd(cur_wd)}) |
|
89 |
+ setwd(gmap_db_tmp_dir) |
|
90 |
+ |
|
91 |
+ db <- gmap_build(value, x, ...) |
|
92 |
+ |
|
93 |
+ db |
|
94 |
+ }) |
|
95 |
+ |
|
96 |
+setGeneric("snps<-", function(x, ..., value) standardGeneric("snps<-")) |
|
97 |
+ |
|
98 |
+setReplaceMethod("snps", c("GmapGenome", "ANY"), |
|
99 |
+ function(x, ..., value) { |
|
100 |
+ snpDir <- GmapSnpDirectory(x) |
|
101 |
+ snps(snpDir, name = name, genome = x, |
|
102 |
+ iitPath = mapsDirectory(x), ...) <- value |
|
103 |
+ x |
|
104 |
+ }) |
|
105 |
+ |
|
106 |
+setGeneric("spliceSites<-", |
|
107 |
+ function(x, ..., value) standardGeneric("spliceSites<-")) |
|
108 |
+ |
|
109 |
+setReplaceMethod("spliceSites", c("GmapGenome", "TranscriptDb"), |
|
110 |
+ function(x, name, value) { |
|
111 |
+ exons <- exonsBy(value) |
|
112 |
+ exonsFlat <- unlist(exons, use.names=FALSE) |
|
113 |
+ exonsPart <- PartitioningByWidth(exons) |
|
114 |
+ exonsHead <- exonsFlat[-end(exonsPart)] |
|
115 |
+ donors <- flank(exonsHead, 1L, start = FALSE, both = TRUE) |
|
116 |
+ exonsTail <- exonsFlat[-start(exonsPart)] |
|
117 |
+ acceptors <- flank(exonsTail, 1L, start = TRUE, both = TRUE) |
|
118 |
+ sites <- c(donors, acceptors) |
|
119 |
+ names(sites) <- values(sites)$exon_id |
|
120 |
+ info <- rep(c("donor", "acceptor"), each = length(donors)) |
|
121 |
+ info <- paste(info, unlist(width(intronsByTranscript(value)), |
|
122 |
+ use.names = FALSE)) |
|
123 |
+ values(sites) <- DataFrame(info) |
|
124 |
+ iit_store(sites, file.path(mapsDirectory(x), name)) |
|
125 |
+ x |
|
126 |
+ }) |
|
127 |
+ |
|
128 |
+### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - |
|
129 |
+### Show |
|
130 |
+### |
|
131 |
+ |
|
132 |
+setMethod("show", "GmapGenome", function(object) { |
|
133 |
+ cat("GmapGenome object\ngenome:", genome(object), "\ndirectory:", |
|
134 |
+ path(directory(object)), "\n") |
|
135 |
+}) |
|
136 |
+ |
|
137 |
+### - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - |
|
138 |
+### Utilities |
|
139 |
+### |
|
140 |
+ |
|
141 |
+.normArgDb <- function(db, dir) { |
|
142 |
+ if (!is(db, "GmapGenome")) |
|
143 |
+ db <- GmapGenome(db, dir) |
|
144 |
+ db |
|
145 |
+} |
|
146 |
+ |