Browse code

1.5.4. fix for NXX

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

Ge Tan authored on 29/06/2015 20:44:23
Showing 5 changed files

... ...
@@ -1,6 +1,6 @@
1 1
 Package: CNEr 
2
-Version: 1.5.3
3
-Date: 2015-05-11
2
+Version: 1.5.4
3
+Date: 2015-06-29
4 4
 Title: CNE Detection and Visualization
5 5
 Description: Large-scale identification and advanced visualization of sets of conserved noncoding elements.
6 6
 Author: Ge Tan <ge.tan09@imperial.ac.uk> 
... ...
@@ -11,7 +11,7 @@
11 11
 NXX <- function(filepath, XX=50){
12 12
   if(grepl("\\.2bit$", filepath, ignore.case=TRUE)){
13 13
     lengths <- seqlengths(TwoBitFile(filepath))
14
-  }else if(grepl("(\\.fa$ | \\.fasta$)", filepath, ignore.case=TRUE)){
14
+  }else if(grepl("(\\.fa$|\\.fasta$)", filepath, ignore.case=TRUE)){
15 15
     lengths <- fasta.info(filepath)
16 16
   }else{
17 17
     stop("The suffix can only be .2bit, .fa, .fasta!")
18 18
new file mode 100644
... ...
@@ -0,0 +1,184 @@
1
+############################ build package  ######################################
2
+
3
+R_dev CMD build CNEr
4
+R_dev CMD build --no-build-vignettes --no-manual CNEr
5
+R_dev CMD INSTALL CNEr_1.5.4.tar.gz
6
+R_dev CMD check CNEr_1.5.4.tar.gz
7
+
8
+library(devtools)
9
+reload(inst("CNEr"))
10
+
11
+### readAxt
12
+library(CNEr)
13
+axtFileshg19danRer7 = list.files(path="/Users/gtan/CSC/CNEr/axtNet", pattern=".*hg19\\.danRer7\\.*", full.names=TRUE)
14
+axtshg19danRer7 = readAxt(axtFileshg19danRer7)
15
+axtFilesdanRer7hg19 = list.files(path="/Users/gtan/CSC/CNEr/axtNet", pattern=".*danRer7\\.hg19\\.*", full.names=TRUE)
16
+axtsdanRer7hg19 = readAxt(axtFilesdanRer7hg19)
17
+
18
+## subAxt
19
+  dyn.load("/Users/gtan/Repositories/Bitbucket/CNEr/src/alignment.so")
20
+  .Call("subAlignment", c(92822L, 95115L), c(92873L, 95180L),
21
+  c("CAAAACCAGATGCTGTGAGAATACTTTATTAGT----CAAAACCGCATA---CTATAAA", "TGCCAACCTTGGCGCCGATCTGATTCCCGCACTGCCCGATCTGCGTGAGCACGATCTCCCTCATGG"),
22
+  c(1812440L, 47866092L), c(1812495L, 47866157L),
23
+  c("CAAAAC---ATATCATAACTGTACCTTGTTTGTTCCACAAGATTGCATCTTTCCTTAAA",
24
+  "TTCCTACCTTGGCACCAATCTGGTTGCCGCACTGTCCAGCCTGTAAATGCACGATCTCCCTCATTG"),
25
+  c(92863L, 95115L), c(92873L, 95120L),
26
+  c(59L, 66L))
27
+
28
+
29
+subAxt(x, "chr10", 92866L, 92873L, select="target")
30
+mm10ChromSizes <- fetchChromSizes("mm10")
31
+subAxt(x, chr="chr2", start=1812441, end=1812494, select="query", qSize=seqlengths(mm10ChromSizes["chr2"]))
32
+subAxt(x, chr="chr14", start=77037081, end=77039623, select="query", qSize=seqlengths(mm10ChromSizes["chr14"]))
33
+
34
+subAxt(axtHg19DanRer7, chr="chr11", start=31500113, end=31500120, select="target")
35
+
36
+foo2 = .subAxtMultiple(axtHg19DanRer7, chr="chr11", start=31500113, end=31500120, select="target")
37
+
38
+foo3 = .subAxtMultiple(axtHg19DanRer7, chr="chr11", start=c(31082021, 32461267), end=c(31082862,32461581), select="target")
39
+
40
+
41
+## readBedToGRanges
42
+bedhg19 = readBed("/Users/gtan/CSC/CNEr/filters/filter_regions.hg19.bed")
43
+beddanRer7 = readBed("/Users/gtan/CSC/CNEr/filters/filter_regions.danRer7.bed")
44
+library(rtracklayer)
45
+qSizesdanRer7 = seqinfo(TwoBitFile("/Users/gtan/CSC/CNEr/2bit/danRer7.2bit"))
46
+qSizeshg19 = seqinfo(TwoBitFile("/Users/gtan/CSC/CNEr/2bit/hg19.2bit"))
47
+
48
+## ceScan
49
+# debug
50
+axts = axtshg19danRer7
51
+tFilter= bedhg19
52
+qFilter= beddanRer7
53
+qSizes= qSizesdanRer7
54
+winSize=50
55
+minScore=45
56
+resFiles = tempfile(pattern = paste(minScore, winSize, "ceScan", sep="-"), tmpdir = tempdir(), fileext = "")
57
+foo = .Call("myCeScan",  as.character(seqnames(tFilter)), 
58
+      start(tFilter), end(tFilter), 
59
+      as.character(seqnames(qFilter)), start(qFilter), end(qFilter),
60
+              as.character(seqnames(qSizes)), as.integer(seqlengths(qSizes)),
61
+              as.character(seqnames(targetRanges(axts))),
62
+              start(targetRanges(axts)), end(targetRanges(axts)),
63
+              as.character(strand(targetRanges(axts))),
64
+              as.character(targetSeqs(axts)),
65
+              as.character(seqnames(queryRanges(axts))),
66
+              start(queryRanges(axts)), end(queryRanges(axts)),
67
+              as.character(strand(queryRanges(axts))),
68
+              as.character(querySeqs(axts)),
69
+              score(axts), symCount(axts), winSize, minScore,
70
+              as.character(resFiles))
71
+foo = .Call("myCeScan",  NULL, 
72
+      NULL, NULL, 
73
+      as.character(seqnames(qFilter)), start(qFilter), end(qFilter),
74
+              as.character(seqnames(qSizes)), as.integer(seqlengths(qSizes)),
75
+              as.character(seqnames(targetRanges(axts))),
76
+              start(targetRanges(axts)), end(targetRanges(axts)),
77
+              as.character(strand(targetRanges(axts))),
78
+              as.character(targetSeqs(axts)),
79
+              as.character(seqnames(queryRanges(axts))),
80
+              start(queryRanges(axts)), end(queryRanges(axts)),
81
+              as.character(strand(queryRanges(axts))),
82
+              as.character(querySeqs(axts)),
83
+              score(axts), symCount(axts), winSize, minScore,
84
+              as.character(resFiles))
85
+              
86
+# end of debug
87
+CNEhg19_danRer7 = ceScan(axtshg19danRer7, qFilter=beddanRer7, qSizes=qSizesdanRer7, thresholds=c("45,50", "48,50", "49,50"))
88
+CNEhg19_danRer7_2 = ceScan(axtshg19danRer7, bedhg19, beddanRer7, qSizesdanRer7, thresholds=c("45,50", "48,50", "49,50"))
89
+
90
+CNEdanRer7_hg19 = ceScan(axtsdanRer7hg19, beddanRer7, bedhg19, qSizeshg19, thresholds=c("45,50", "48,50", "49,50"))
91
+
92
+## ceScan File
93
+bedhg19File = "/export/data/CNEs/hg19/filters/filter_regions.hg19.bed"
94
+beddanRer7File = "/export/data/CNEs/danRer7/filters/filter_regions.danRer7.bed"
95
+CNEhg19_danRer7 = ceScanFile(axtFileshg19danRer7, bedhg19File, beddanRer7File , qSizesdanRer7, thresholds=c("45,50", "48,50", "49,50"))
96
+CNEdanRer7_hg19 = ceScanFile(axtFilesdanRer7hg19, beddanRer7File, bedhg19File, qSizeshg19, thresholds=c("45,50", "48,50", "49,50"))
97
+
98
+
99
+## ceMerge
100
+data(CNEDanRer7Hg19)
101
+data(CNEHg19DanRer7)
102
+cneMerge(CNEDanRer7Hg19[[1]], CNEHg19DanRer7[[1]])
103
+
104
+## blatCNE
105
+assemblyhg19Twobit = "/export/data/goldenpath/hg19/assembly.2bit"
106
+assemblydanRer7Twobit = "/export/data/goldenpath/danRer7/assembly.2bit"
107
+cneBlateddanRer7_hg19 = list()
108
+for(i in 1:length(cneMergeddanRer7hg19)){
109
+  cneBlateddanRer7_hg19[[names(cneMergeddanRer7_hg19)[i]]] = blatCNE(cneMergeddanRer7_hg19[[i]], sub("\\d+_", "", names(cneMergeddanRer7_hg19)[i]), 8, 4, assemblydanRer7Twobit, assemblyhg19Twobit)
110
+}
111
+
112
+## saveCNE
113
+tableName = "cne_twoWay_danRer7_hg19_len50_id900_v1"
114
+dbName = "/mnt/biggley/home/gtan/work/debug/CNEr-29-07-2013/cne.sqlite"
115
+for(i in 1:length(cneBlateddanRer7_hg19)){
116
+  tableName = paste0("cne_twoWay_danRer7_hg19_len50_id", as.integer(sub("_\\d+$", "", names(cneBlateddanRer7_hg19)[i]))*20, "_v1")
117
+  saveCNEToSQLite(cneBlateddanRer7_hg19[[i]], dbName, tableName, overwrite=TRUE)
118
+}
119
+
120
+# readCNERangesFromSQLite
121
+chr = "chr6"
122
+CNEstart = 19900000
123
+CNEend =  28000000
124
+minLength = 50
125
+dbName = "/Users/gtan/CSC/CNEr/CNESQL/cne.sqlite"
126
+tableName = "cne2wBf_danRer7_hg19_27_30"
127
+fetchedCNERanges = readCNERangesFromSQLite(dbName, tableName, chr, CNEstart, CNEend, whichAssembly="1", minLength)
128
+
129
+##CNEAnnotate
130
+windowSize= 300
131
+cne2wBf_danRer7_hg19_21_30 = CNEAnnotate(dbName, "cne2wBf_danRer7_hg19_21_30", whichAssembly="1", chr, CNEstart, CNEend, windowSize, minLength)
132
+cne2wBf_danRer7_hg19_40_50 = CNEAnnotate(dbName, "cne2wBf_danRer7_hg19_40_50", whichAssembly="1", chr, CNEstart, CNEend, windowSize, minLength)
133
+cne2wBf_danRer7_hg19_49_50 = CNEAnnotate(dbName, "cne2wBf_danRer7_hg19_49_50", whichAssembly="1", chr, CNEstart, CNEend, windowSize, minLength)
134
+
135
+cne2wBf_danRer7_tetNig2_21_30 = CNEAnnotate(dbName, "cne2wBf_danRer7_tetNig2_21_30", whichAssembly="1", chr, CNEstart, CNEend, windowSize, minLength)
136
+cne2wBf_danRer7_tetNig2_40_50 = CNEAnnotate(dbName, "cne2wBf_danRer7_tetNig2_40_50", whichAssembly="1", chr, CNEstart, CNEend, windowSize, minLength)
137
+cne2wBf_danRer7_tetNig2_49_50 = CNEAnnotate(dbName, "cne2wBf_danRer7_tetNig2_49_50", whichAssembly="1", chr, CNEstart, CNEend, windowSize, minLength)
138
+### new Gviz way
139
+genome = "danRer7"
140
+strand = "+"
141
+dataMatrix= cne2wBf_danRer7_hg19_21_30
142
+dTrack1 = DataTrack(start=dataMatrix[ ,1], end=dataMatrix[ ,1], data=dataMatrix[ ,2], chromosome=chr, strand=strand, genome=genome, type="horiz", horizon.scale=1, fill.horizon=c("#B41414", "#E03231", "#F7A99C", "yellow", "orange", "red"), name="hg19 21/30")
143
+dataMatrix = cne2wBf_danRer7_hg19_40_50
144
+dTrack2 = DataTrack(start=dataMatrix[ ,1], end=dataMatrix[ ,1], data=dataMatrix[ ,2], chromosome=chr, strand=strand, genome=genome, type="horiz", horizon.scale=1, fill.horizon=c("#B41414", "#E03231", "#F7A99C", "yellow", "orange", "red"), name="hg19 45/50")
145
+dataMatrix = cne2wBf_danRer7_hg19_49_50
146
+dTrack3 = DataTrack(start=dataMatrix[ ,1], end=dataMatrix[ ,1], data=dataMatrix[ ,2], chromosome=chr, strand=strand, genome=genome, type="horiz", horizon.scale=1, fill.horizon=c("#B41414", "#E03231", "#F7A99C", "yellow", "orange", "red"), name="hg19 49/50")
147
+
148
+dataMatrix= cne2wBf_danRer7_tetNig2_21_30
149
+dTrack4 = DataTrack(start=dataMatrix[ ,1], end=dataMatrix[ ,1], data=dataMatrix[ ,2], chromosome=chr, strand=strand, genome=genome, type="horiz", horizon.scale=2, fill.horizon=c("#B41414", "#E03231", "#F7A99C", "yellow", "orange", "red"), name="tetNig2 21/30")
150
+dataMatrix = cne2wBf_danRer7_tetNig2_40_50
151
+dTrack5 = DataTrack(start=dataMatrix[ ,1], end=dataMatrix[ ,1], data=dataMatrix[ ,2], chromosome=chr, strand=strand, genome=genome, type="horiz", horizon.scale=2, fill.horizon=c("#B41414", "#E03231", "#F7A99C", "yellow", "orange", "red"), name="tetNig2 45/50")
152
+dataMatrix = cne2wBf_danRer7_tetNig2_49_50
153
+dTrack6 = DataTrack(start=dataMatrix[ ,1], end=dataMatrix[ ,1], data=dataMatrix[ ,2], chromosome=chr, strand=strand, genome=genome, type="horiz", horizon.scale=2, fill.horizon=c("#B41414", "#E03231", "#F7A99C", "yellow", "orange", "red"), name="tetNig2 49/50")
154
+
155
+axisTrack <- GenomeAxisTrack()
156
+ideoTrack <- IdeogramTrack(genome = "danRer7", chromosome = chr)
157
+refGeneAnnotation = queryAnnotationSQLite(dbname="/Users/gtan/CSC/CNEr/annotationSQL/geneAnnotation.sqlite", tablename="danRer7_refGene", chr=chr, start= CNEstart, end= CNEend)
158
+refgrtrack <- GeneRegionTrack(refGeneAnnotation, genome = "danRer7", chromosome = chr, name = "refGene")
159
+ensGeneAnnotation = queryAnnotationSQLite(dbname="/Users/gtan/CSC/CNEr/annotationSQL/geneAnnotation.sqlite", tablename="danRer7_ensGene", chr=chr, start= CNEstart, end= CNEend)
160
+ensgrtrack = GeneRegionTrack(ensGeneAnnotation, genome = "danRer7", chromosome = chr, name = "ensGene")
161
+
162
+cpgIslands = UcscTrack(genome = "danRer7", chromosome = chr, track = "cpgIslandExt", from=CNEstart, to=CNEend, trackType = "AnnotationTrack", start = "chromStart",end = "chromEnd", id = "name", shape = "box", fill = "#006400", name = "CpG Islands")
163
+plotTracks(list(axisTrack,ideoTrack,  refgrtrack, cpgIslands, dTrack1, dTrack2, dTrack3, dTrack4, dTrack5, dTrack6), collapseTranscripts = TRUE, shape = "arrow", from= CNEstart, to= CNEend, showId = TRUE, extend.left = 20000)
164
+
165
+### old Gviz way
166
+
167
+
168
+### prepare gene annotation sqlite3
169
+makeGeneDbFromUCSC(genome="danRer7", tablename="refGene", dbnameSQLite="/Users/gtan/CSC/CNEr/annotationSQL/geneAnnotation.sqlite")
170
+makeGeneDbFromUCSC(genome="danRer7", tablename="ensGene", dbnameSQLite="/Users/gtan/CSC/CNEr/annotationSQL/geneAnnotation.sqlite")
171
+
172
+
173
+#############################################   readBinary##############
174
+axtFiles ="/mnt/biggley/data/pairwiseAlignments/ucsc/axtNet/hg19.danRer7.net.axt" 
175
+fn = file(axtFiles, "rb")
176
+foo = readBin(fn, raw(), file.info(axtFiles)$size)
177
+rawToChar(foo[1:16]) 
178
+index = grepRaw("\n", foo, fixed=TRUE)
179
+
180
+targetRanges="GRanges", targetSeqs="DNAStringSet",queryRanges="GRanges", querySeqs="DNAStringSet", score="integer", symCount="integer"
181
+                        )
182
+                        
183
+                        
184
+
0 185
new file mode 100644
... ...
@@ -0,0 +1,75 @@
1
+### Human VS Dog
2
+selfDir = "~/Repos/CSC/CNEr/R"
3
+selfScripts = list.files(path=selfDir, pattern='.*\\.r$', full.names=TRUE, recursive=TRUE)
4
+for(rs in selfScripts){message(rs);source(rs)}
5
+
6
+axtFiles = list.files(path="/export/downloads/ucsc/axtNet/hg19", pattern=".*hg19\\.canFam3\\.*", full.names=TRUE)
7
+axtFiles = axtFiles[1:5]
8
+axts_hg19_canFam3 = readAxt(axtFiles)
9
+axtFiles = list.files(path="/export/downloads/ucsc/axtNet/canFam3", pattern=".*canFam3\\.hg19\\.*", full.names=TRUE)
10
+axts_canFam3_hg19 = readAxt(axtFiles)
11
+
12
+bed_hg19 = readBedToGRanges("/export/data/CNEs/hg19/filters/filter_regions.hg19.bed")
13
+bed_canFam3 = readBedToGRanges("/export/data/CNEs/canFam3/filters/filter_regions.canFam3.bed")
14
+qSizes_canFam3 = seqinfo(TwoBitFile("/export/data/goldenpath/canFam3/assembly.2bit"))
15
+qSizes_hg19 = seqinfo(TwoBitFile("/export/data/goldenpath/hg19/assembly.2bit"))
16
+
17
+CNE_hg19_canFam3 = ceScan(axts_hg19_canFam3, bed_hg19, bed_canFam3, qSizes_canFam3, thresholds=c("29,30", "30,30", "35,50", "40,50", "45,50", "48,50", "49,50"))
18
+CNE_canFam3_hg19 = ceScan(axts_canFam3_hg19, bed_canFam3, bed_hg19, qSizes_hg19, thresholds=c("29,30", "30,30", "35,50", "40,50", "45,50", "48,50", "49,50"))
19
+
20
+cneMerged_canFam3_hg19 = mapply(ceMerge, CNE_canFam3_hg19, CNE_hg19_canFam3, SIMPLIFY=FALSE)
21
+
22
+assembly_hg19_Twobit = "/export/data/goldenpath/hg19/assembly.2bit"
23
+assembly_canFam3_Twobit = "/export/data/goldenpath/canFam3/assembly.2bit"
24
+
25
+cneBlated_canFam3_hg19 = list()
26
+for(i in 1:length(cneMerged_canFam3_hg19)){
27
+  cneBlated_canFam3_hg19[[names(cneMerged_canFam3_hg19)[i]]] = blatCNE(cneMerged_canFam3_hg19[[i]], sub("\\d+_", "", names(cneMerged_canFam3_hg19)[i]), 4, 4, assembly_canFam3_Twobit, assembly_hg19_Twobit)
28
+}
29
+
30
+
31
+# readCNERangesFromSQLite
32
+chr = "chr16"
33
+CNEstart = 45000000
34
+CNEend = 60000000
35
+minLength = 50
36
+fetchedCNERanges = readCNERangesFromSQLite(dbName, tableName, chr, CNEstart, CNEend, whichAssembly="2", minLength)
37
+
38
+##CNEAnnotate
39
+windowSize= 300
40
+dbName = "/Users/gtan/Dropbox/Project/CSC/CNEr/cne.sqlite"
41
+hg19_canFam3_len50_id900_300 = CNEAnnotate(dbName, "cne_twoWay_canFam3_hg19_len50_id900_v1", whichAssembly="2", chr, CNEstart, CNEend, windowSize, minLength)
42
+hg19_canFam3_len50_id960_300 = CNEAnnotate(dbName, "cne_twoWay_canFam3_hg19_len50_id960_v1", whichAssembly="2", chr, CNEstart, CNEend, windowSize, minLength)
43
+hg19_canFam3_len50_id980_300 = CNEAnnotate(dbName, "cne_twoWay_canFam3_hg19_len50_id980_v1", whichAssembly="2", chr, CNEstart, CNEend, windowSize, minLength)
44
+listToPlot = list(hg19_canFam3_len50_id900_300 = hg19_canFam3_len50_id900_300, hg19_canFam3_len50_id960_300 = hg19_canFam3_len50_id960_300, hg19_canFam3_len50_id980_300 = hg19_canFam3_len50_id980_300)
45
+p = plotCNE(listToPlot, horizonscale=4, nbands=5)
46
+zoomLevel = c(45000000, 60000000)
47
+p+xlim(range(zoomLevel))
48
+
49
+## genomic features
50
+library(TxDb.Hsapiens.UCSC.hg19.knownGene)
51
+txdb <- TxDb.Hsapiens.UCSC.hg19.knownGene
52
+aldoa.gr <- GRanges(chr, IRanges(zoomLevel[1], zoomLevel[2]))
53
+library(ggbio)
54
+p1 <- autoplot(txdb, which = aldoa.gr, stat = "reduce")
55
+p2 = tracks(knownGene = p1, CNE = p) + xlim(zoomLevel[1], zoomLevel[2])
56
+
57
+
58
+### Gviz way
59
+genome = "hg19"
60
+strand = "+"
61
+chr = "chr16"
62
+dataMatrix= hg19_canFam3_len50_id900_300
63
+dTrack1 = DataTrack(start=dataMatrix[ ,1], end=dataMatrix[ ,1], data=dataMatrix[ ,2], chromosome=chr, strand=strand, genome=genome, type="horizon", fill.horizonScale=4, ylim=c(0,4), name="hg19_canFam3_len50_id900_300")
64
+dataMatrix = hg19_canFam3_len50_id960_300
65
+dTrack2 = DataTrack(start=dataMatrix[ ,1], end=dataMatrix[ ,1], data=dataMatrix[ ,2], chromosome=chr, strand=strand, genome=genome, type="horizon", fill.horizonScale=4, ylim=c(0,4), name="hg19_canFam3_len50_id960_300")
66
+dataMatrix = hg19_canFam3_len50_id980_300
67
+dTrack3 = DataTrack(start=dataMatrix[ ,1], end=dataMatrix[ ,1], data=dataMatrix[ ,2], chromosome=chr, strand=strand, genome=genome, type="horizon", fill.horizonScale=4, ylim=c(0,4), name="hg19_canFam3_len50_id980_300")
68
+
69
+axisTrack <- GenomeAxisTrack()
70
+ideoTrack <- IdeogramTrack(genome = "hg19", chromosome = chr)
71
+geneAnnotation = queryAnnotationSQLite(dbname="/Users/gtan/Dropbox/Project/CSC/CNEr/geneAnnotation.sqlite", tablename="hg19_refGene", chr="chr16", start= 45000000, end= 60000000)
72
+grtrack <- GeneRegionTrack(geneAnnotation, genome = "hg19", chromosome = chr, name = "refGene")
73
+plotTracks(list(ideoTrack, axisTrack, grtrack, dTrack1, dTrack2, dTrack3), collapseTranscripts = TRUE, shape = "arrow", from= 45000000, to=60000000, showId = TRUE, extend.left = 20000)
74
+
75
+
0 76
new file mode 100644
... ...
@@ -0,0 +1,39 @@
1
+> xyplot(y~x, panel = function(x,y,...){for (i in 0:round(max(y)/2,0)) panel.xyarea(x,y=ifelse(y>0,y,NA)-(scale * i),col="green",border="green", alpha=0.4)})
2
+
3
+fooColors=c("red","blue","yellow")
4
+scale=2
5
+xyplot(y~x, xlab=NULL,ylab=NULL, ylim=c(0, scale),origin=0,
6
+panel = function(x,y,...){for (i in 0:round(max(y)/scale,0)) panel.xyarea(x,y=ifelse(y>0,y,NA)-(scale * i),col=fooColors[i+1],border="green")})
7
+xyplot(y~x, xlab=NULL,ylab=NULL, ylim=c(0, scale),origin=0,
8
+panel = function(x,y,...){for (i in 1:(round(max(y)/scale,0)+1)) panel.xyarea(x,y=ifelse(y>0,y,NA)-(scale * (i-1)),col=fooColors[i],border="green")})
9
+
10
+
11
+rm Gviz_1.4.4.tar.gz
12
+R CMD build  Gviz/
13
+R CMD INSTALL Gviz_1.4.4.tar.gz
14
+remove.packages("Gviz")
15
+library(Gviz)
16
+data(twoGroups)
17
+dTrack <- DataTrack(twoGroups, name = "uniform")
18
+plotTracks(dTrack)
19
+
20
+library(lattice)
21
+library(GenomicRanges)
22
+library(latticeExtra)
23
+set.seed(10)
24
+foo = GRanges(seqnames=seqnames(twoGroups), ranges=ranges(twoGroups), y=runif(25,1,6))
25
+dTrack <- DataTrack(foo, name = "uniform", type="horizon", fill.horizonScale=2, ylim=c(0,2))
26
+plotTracks(dTrack)
27
+
28
+
29
+ans = queryAnnotationSQLite(dbname="/Users/gtan/Dropbox/Project/CSC/CNEr/geneAnnotation.sqlite", tablename="hg19_refGene", chr="chr3", start=158500001, end=160200000)
30
+grtrack <- GeneRegionTrack(ans, genome = "hg19", chromosome = "chr3", name = "foo")
31
+axisTrack <- GenomeAxisTrack()
32
+ideoTrack <- IdeogramTrack(genome = "hg19", chromosome = "chr3")
33
+plotTracks(list(ideoTrack,axisTrack,grtrack), collapseTranscripts = TRUE, shape = "arrow", extend.left = 20000, showId = TRUE)
34
+
35
+
36
+
37
+
38
+
39
+