... | ... |
@@ -98,4 +98,25 @@ setMethod("syntenicDotplot", signature=(x="Axt"), |
98 | 98 |
firstChrs=firstChrs, |
99 | 99 |
secondChrs=secondChrs, |
100 | 100 |
col=col, type=type) |
101 |
- }) |
|
102 | 101 |
\ No newline at end of file |
102 |
+ }) |
|
103 |
+ |
|
104 |
+### ----------------------------------------------------------------- |
|
105 |
+### makeAxtTracks |
|
106 |
+### Exported!! |
|
107 |
+makeAxtTracks <- function(x){ |
|
108 |
+ if(!is(x, "Axt")){ |
|
109 |
+ stop(deparse(substitute(x)), " must be a `Axt`` class!") |
|
110 |
+ } |
|
111 |
+ x <- fixCoordinates(x) |
|
112 |
+ |
|
113 |
+ targetAxt <- targetRanges(x) |
|
114 |
+ queryAxt <- queryRanges(x) |
|
115 |
+ |
|
116 |
+ targetAxt$name <- as.character(queryAxt) |
|
117 |
+ queryAxt$name <- as.character(targetAxt) |
|
118 |
+ |
|
119 |
+ export.bed(targetAxt, "targetAxt.bed") |
|
120 |
+ export.bed(queryAxt, "queryAxt.bed") |
|
121 |
+ |
|
122 |
+ invisible(list(targetAxt, queryAxt)) |
|
123 |
+} |
... | ... |
@@ -375,56 +375,3 @@ blatCNE <- function(cne, blatOptions=NULL, cutIdentity=90){ |
375 | 375 |
as.integer(CNEqNameIndex) <= cutoffs2] |
376 | 376 |
BiocGenerics:::replaceSlots(cne, CNEFinal=cneFinal) |
377 | 377 |
} |
378 |
- |
|
379 |
-# ceScanOneStep <- function(axt1, filter1=NULL, sizes1, assembly1, twoBit1, |
|
380 |
-# axt2, filter2=NULL, sizes2, assembly2, twoBit2, |
|
381 |
-# thresholds=c("49_50"), |
|
382 |
-# blatBinary="blat", |
|
383 |
-# blatCutoff1, blatCutoff2 |
|
384 |
-# ){ |
|
385 |
-# if(grepl("_", assembly1) || grepl("_", assembly2)) |
|
386 |
-# stop("The assembly name must not contain \"_\"") |
|
387 |
-# if(assembly1 < assembly2){ |
|
388 |
-# .ceScanSwap(axt1=axt1, filter1=filter1, sizes1=sizes1, assembly1=assembly1, |
|
389 |
-# twoBit1=twoBit1, axt2=axt2, filter2=filter2, sizes2=sizes2, |
|
390 |
-# assembly2=assembly2, twoBit2=twoBit2, thresholds=thresholds, |
|
391 |
-# blatBinary=blatBinary, blatCutoff1=blatCutoff1, |
|
392 |
-# blatCutoff2=blatCutoff2) |
|
393 |
-# }else{ |
|
394 |
-# .ceScanSwap(axt1=axt2, filter1=filter2, sizes1=sizes2, assembly1=assembly2, |
|
395 |
-# twoBit1=twoBit2, axt2=axt1, filter2=filter1, |
|
396 |
-# sizes2=sizes1, assembly2=assembly1, twoBit2=twoBit1, |
|
397 |
-# thresholds=thresholds, blatBinary=blatBinary, |
|
398 |
-# blatCutoff1=blatCutoff2, blatCutoff2=blatCutoff1) |
|
399 |
-# } |
|
400 |
-# } |
|
401 |
-# |
|
402 |
-# .ceScanSwap <- function(axt1, filter1=NULL, sizes1, assembly1, twoBit1, |
|
403 |
-# axt2, filter2=NULL, sizes2, assembly2, twoBit2, |
|
404 |
-# thresholds=c("49_50"), |
|
405 |
-# blatBinary="blat", |
|
406 |
-# blatCutoff1, blatCutoff2 |
|
407 |
-# ){ |
|
408 |
-# ## In this function, we make sure "assembly1" is smaller than "assembly2". |
|
409 |
-# ## danRer7 is smaller than hg19. |
|
410 |
-# ## This is just for easier database storage table name: "danRer7_hg19_49_50" |
|
411 |
-# CNE1 <- ceScan(axt1, filter1, filter2, sizes2, thresholds) |
|
412 |
-# CNE2 <- ceScan(axt2, filter2, filter1, sizes1, thresholds) |
|
413 |
-# CNEMerged <- mapply(cneMerge, CNE1, CNE2, SIMPLIFY=FALSE) |
|
414 |
-# names(CNEMerged) = paste(assembly1, assembly2, thresholds, sep="_") |
|
415 |
-# CNEBlated <- list() |
|
416 |
-# for(i in 1:length(CNEMerged)){ |
|
417 |
-# CNEBlated[[names(CNEMerged)[i]]] <- |
|
418 |
-# blatCNE(CNEMerged[[i]], as.integer(sub(".+_.+_\\d+_", "", |
|
419 |
-# names(CNEMerged)[i])), |
|
420 |
-# cutoffs1=blatCutoff1, cutoffs2=blatCutoff2, |
|
421 |
-# assembly1Twobit=twoBit1, assembly2Twobit=twoBit2, |
|
422 |
-# blatBinary=blatBinary) |
|
423 |
-# } |
|
424 |
-# ans <- CNE(assembly1=assembly1, assembly2=assembly2, |
|
425 |
-# thresholds=thresholds, |
|
426 |
-# CNE1=CNE1, CNE2=CNE2, CNEMerged=CNEMerged, |
|
427 |
-# CNERepeatsFiltered=CNEBlated, |
|
428 |
-# alignMethod=blatBinary) |
|
429 |
-# return(ans) |
|
430 |
-# } |
100 | 101 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,43 @@ |
1 |
+\name{makeAxtTracks} |
|
2 |
+\alias{makeAxtTracks} |
|
3 |
+\title{ |
|
4 |
+ makeAxtTracks |
|
5 |
+} |
|
6 |
+\description{ |
|
7 |
+ Make the bed tracks for the \sQuote{Axt} alignment. |
|
8 |
+} |
|
9 |
+\usage{ |
|
10 |
+ makeAxtTracks(x) |
|
11 |
+} |
|
12 |
+\arguments{ |
|
13 |
+ \item{x}{ |
|
14 |
+ A \code{Axt} object. |
|
15 |
+ } |
|
16 |
+} |
|
17 |
+\details{ |
|
18 |
+ The coordinates of query \sQuote{Axt} alignment are fixed to be relative to |
|
19 |
+ positive strand before output into \sQuote{bed} file. |
|
20 |
+} |
|
21 |
+\value{ |
|
22 |
+ A list of GRanges for target and query alignments. |
|
23 |
+ The two output \sQuote{bed} files are |
|
24 |
+ \dQuote{targetAxt.bed} and \dQuote{queryAxt.bed}. |
|
25 |
+} |
|
26 |
+\author{ |
|
27 |
+ Ge Tan |
|
28 |
+} |
|
29 |
+\seealso{ |
|
30 |
+ \code{\link{fixCoordinates}} |
|
31 |
+} |
|
32 |
+\examples{ |
|
33 |
+ tAssemblyFn <- file.path(system.file("extdata", |
|
34 |
+ package="BSgenome.Drerio.UCSC.danRer10"), |
|
35 |
+ "single_sequences.2bit") |
|
36 |
+ qAssemblyFn <- file.path(system.file("extdata", |
|
37 |
+ package="BSgenome.Hsapiens.UCSC.hg38"), |
|
38 |
+ "single_sequences.2bit") |
|
39 |
+ axtFn <- file.path(system.file("extdata", package="CNEr"), |
|
40 |
+ "danRer10.hg38.net.axt") |
|
41 |
+ axt <- readAxt(axtFn, tAssemblyFn, qAssemblyFn) |
|
42 |
+ makeAxtTracks(axt) |
|
43 |
+} |
... | ... |
@@ -153,4 +153,21 @@ test_that("test_subAxt", { |
153 | 153 |
ans <- psubAxt(axt, targetSearch, querySearch) |
154 | 154 |
expect_identical(ans, axt[c(1,3,347:350)]) |
155 | 155 |
} |
156 |
-) |
|
157 | 156 |
\ No newline at end of file |
157 |
+) |
|
158 |
+ |
|
159 |
+test_that("test_makeAxtTracks", { |
|
160 |
+ tAssemblyFn <- file.path(system.file("extdata", |
|
161 |
+ package="BSgenome.Drerio.UCSC.danRer10"), |
|
162 |
+ "single_sequences.2bit") |
|
163 |
+ qAssemblyFn <- file.path(system.file("extdata", |
|
164 |
+ package="BSgenome.Hsapiens.UCSC.hg38"), |
|
165 |
+ "single_sequences.2bit") |
|
166 |
+ axtFn <- file.path(system.file("extdata", package="CNEr"), |
|
167 |
+ "danRer10.hg38.net.axt") |
|
168 |
+ axt <- readAxt(axtFn, tAssemblyFn, qAssemblyFn) |
|
169 |
+ ans <- makeAxtTracks(axt) |
|
170 |
+ |
|
171 |
+ ## Make sure the coordinates are right. |
|
172 |
+ expect_identical(ans[[1]]$name[1:2], c("chr7:12578221-12578959:-", |
|
173 |
+ "chr9:121302901-121303067:-")) |
|
174 |
+}) |