... | ... |
@@ -7,7 +7,7 @@ strands: + - |
7 | 7 |
Background letter frequencies |
8 | 8 |
A 0.250 C 0.250 G 0.250 T 0.250 |
9 | 9 |
|
10 |
-MOTIF Mmusculus-cispb_1.02-M0082_1.02 |
|
10 |
+MOTIF Mmusculus-cisbp_1.02-M0082_1.02 |
|
11 | 11 |
letter-probability matrix: alength= 4 w= 10 nsites= 45 E=8.1e-020 |
12 | 12 |
0.2203768432 0.3354050831 0.1020373584 0.3421807153 |
13 | 13 |
0.1117838556 0.1937497051 0.6695240896 0.0249423496 |
... | ... |
@@ -20,7 +20,7 @@ letter-probability matrix: alength= 4 w= 10 nsites= 45 E=8.1e-020 |
20 | 20 |
0.0551007724 0.0004313497 0.9430919013 0.0013759766 |
21 | 21 |
0.0952369898 0.3494527694 0.4354449644 0.1198652764 |
22 | 22 |
|
23 |
-MOTIF Mmusculus-cispb_1.02-M0083_1.02 |
|
23 |
+MOTIF Mmusculus-cisbp_1.02-M0083_1.02 |
|
24 | 24 |
letter-probability matrix: alength= 4 w= 10 nsites= 45 E=8.1e-020 |
25 | 25 |
0.1631992133 0.1296672588 0.1083071987 0.5988263292 |
26 | 26 |
0.2034461212 0.3491149401 0.2460171402 0.2014217985 |
... | ... |
@@ -33,7 +33,7 @@ letter-probability matrix: alength= 4 w= 10 nsites= 45 E=8.1e-020 |
33 | 33 |
0.1006336198 0.0000926882 0.8991828391 0.0000908529 |
34 | 34 |
0.0001197413 0.0000375373 0.9998233202 0.0000194012 |
35 | 35 |
|
36 |
-MOTIF Mmusculus-cispb_1.02-M0084_1.02 |
|
36 |
+MOTIF Mmusculus-cisbp_1.02-M0084_1.02 |
|
37 | 37 |
letter-probability matrix: alength= 4 w= 10 nsites= 45 E=8.1e-020 |
38 | 38 |
0.1947249309 0.4000493650 0.1501429668 0.2550827372 |
39 | 39 |
0.0896002212 0.3254984788 0.5260297596 0.0588715404 |
40 | 40 |
deleted file mode 100644 |
... | ... |
@@ -1,221 +0,0 @@ |
1 |
-library (MotifDb) |
|
2 |
-library (RUnit) |
|
3 |
-library (MotIV) |
|
4 |
-library (seqLogo) |
|
5 |
-#---------------------------------------------------------------------------------------------------- |
|
6 |
-printf <- function(...) print(noquote(sprintf(...))) |
|
7 |
-#---------------------------------------------------------------------------------------------------- |
|
8 |
-# Note: all matrix numbers were chosen randomly using "sample()" |
|
9 |
-runTests = function () |
|
10 |
-{ |
|
11 |
- |
|
12 |
-} # runTests |
|
13 |
-#---------------------------------------------------------------------------------------------------- |
|
14 |
-test_cisbp <- function(){ |
|
15 |
- |
|
16 |
- # Load the cisbp matrix as "cisbp" |
|
17 |
- load("./single_matrices/cisbp_matrix.Rdata") |
|
18 |
- |
|
19 |
- # Matrix name |
|
20 |
- mtx.name <- "M0308_1.02" |
|
21 |
- |
|
22 |
- # Query for the same matrix |
|
23 |
- queried <- query(MotifDb, mtx.name)[[1]] |
|
24 |
- |
|
25 |
- # Check that they're the same |
|
26 |
- checkTrue(all(cisbp == queried)) |
|
27 |
- |
|
28 |
-} # test_cisbp |
|
29 |
-#---------------------------------------------------------------------------------------------------- |
|
30 |
-test_FlyFactorSurvey <- function(){ |
|
31 |
- |
|
32 |
- # Load the cisbp matrix as "cisbp" |
|
33 |
- load("./single_matrices/FlyFactorSurvey.Rdata") |
|
34 |
- |
|
35 |
- # Matrix name |
|
36 |
- mtx.name <- "M0308_1.02" |
|
37 |
- |
|
38 |
- # Query for the same matrix |
|
39 |
- queried <- query(MotifDb, mtx.name)[[1]] |
|
40 |
- |
|
41 |
- # Check that they're the same |
|
42 |
- checkTrue(all(cisbp == queried)) |
|
43 |
- |
|
44 |
-} # test_FlyFactorSurvey |
|
45 |
-#---------------------------------------------------------------------------------------------------- |
|
46 |
-test_HOCOMOCOv10 <- function(){ |
|
47 |
- |
|
48 |
- # Load the cisbp matrix as "cisbp" |
|
49 |
- load("./single_matrices/HOCOMOCOv10.Rdata") |
|
50 |
- |
|
51 |
- # Matrix name |
|
52 |
- mtx.name <- "M0308_1.02" |
|
53 |
- |
|
54 |
- # Query for the same matrix |
|
55 |
- queried <- query(MotifDb, mtx.name)[[1]] |
|
56 |
- |
|
57 |
- # Check that they're the same |
|
58 |
- checkTrue(all(cisbp == queried)) |
|
59 |
- |
|
60 |
-} # test_HOCOMOCOv10 |
|
61 |
-#---------------------------------------------------------------------------------------------------- |
|
62 |
-test_HOMER <- function(){ |
|
63 |
- |
|
64 |
- # Load the cisbp matrix as "cisbp" |
|
65 |
- load("./single_matrices/HOMER.Rdata") |
|
66 |
- |
|
67 |
- # Matrix name |
|
68 |
- mtx.name <- "M0308_1.02" |
|
69 |
- |
|
70 |
- # Query for the same matrix |
|
71 |
- queried <- query(MotifDb, mtx.name)[[1]] |
|
72 |
- |
|
73 |
- # Check that they're the same |
|
74 |
- checkTrue(all(cisbp == queried)) |
|
75 |
- |
|
76 |
-} # test_HOMER |
|
77 |
-#---------------------------------------------------------------------------------------------------- |
|
78 |
-test_hPDI <- function(){ |
|
79 |
- |
|
80 |
- # Load the cisbp matrix as "cisbp" |
|
81 |
- load("./single_matrices/hPDI.Rdata") |
|
82 |
- |
|
83 |
- # Matrix name |
|
84 |
- mtx.name <- "M0308_1.02" |
|
85 |
- |
|
86 |
- # Query for the same matrix |
|
87 |
- queried <- query(MotifDb, mtx.name)[[1]] |
|
88 |
- |
|
89 |
- # Check that they're the same |
|
90 |
- checkTrue(all(cisbp == queried)) |
|
91 |
- |
|
92 |
-} # test_hPDI |
|
93 |
-#---------------------------------------------------------------------------------------------------- |
|
94 |
-test_JASPAR_2014 <- function(){ |
|
95 |
- |
|
96 |
- # Load the cisbp matrix as "cisbp" |
|
97 |
- load("./single_matrices/JASPAR_2014.Rdata") |
|
98 |
- |
|
99 |
- # Matrix name |
|
100 |
- mtx.name <- "M0308_1.02" |
|
101 |
- |
|
102 |
- # Query for the same matrix |
|
103 |
- queried <- query(MotifDb, mtx.name)[[1]] |
|
104 |
- |
|
105 |
- # Check that they're the same |
|
106 |
- checkTrue(all(cisbp == queried)) |
|
107 |
- |
|
108 |
-} # test_JASPAR_2014 |
|
109 |
-#---------------------------------------------------------------------------------------------------- |
|
110 |
-test_JASPAR_CORE<- function(){ |
|
111 |
- |
|
112 |
- # Load the cisbp matrix as "cisbp" |
|
113 |
- load("./single_matrices/JASPAR_CORE.Rdata") |
|
114 |
- |
|
115 |
- # Matrix name |
|
116 |
- mtx.name <- "M0308_1.02" |
|
117 |
- |
|
118 |
- # Query for the same matrix |
|
119 |
- queried <- query(MotifDb, mtx.name)[[1]] |
|
120 |
- |
|
121 |
- # Check that they're the same |
|
122 |
- checkTrue(all(cisbp == queried)) |
|
123 |
- |
|
124 |
-} # test_JASPAR_CORE |
|
125 |
-#---------------------------------------------------------------------------------------------------- |
|
126 |
-test_jaspar2016 <- function(){ |
|
127 |
- |
|
128 |
- # Load the cisbp matrix as "cisbp" |
|
129 |
- load("./single_matrices/jaspar2016.Rdata") |
|
130 |
- |
|
131 |
- # Matrix name |
|
132 |
- mtx.name <- "M0308_1.02" |
|
133 |
- |
|
134 |
- # Query for the same matrix |
|
135 |
- queried <- query(MotifDb, mtx.name)[[1]] |
|
136 |
- |
|
137 |
- # Check that they're the same |
|
138 |
- checkTrue(all(cisbp == queried)) |
|
139 |
- |
|
140 |
-} # test_jaspar2016 |
|
141 |
-#---------------------------------------------------------------------------------------------------- |
|
142 |
-test_jolma2013 <- function(){ |
|
143 |
- |
|
144 |
- # Load the cisbp matrix as "cisbp" |
|
145 |
- load("./single_matrices/jolma2013.Rdata") |
|
146 |
- |
|
147 |
- # Matrix name |
|
148 |
- mtx.name <- "M0308_1.02" |
|
149 |
- |
|
150 |
- # Query for the same matrix |
|
151 |
- queried <- query(MotifDb, mtx.name)[[1]] |
|
152 |
- |
|
153 |
- # Check that they're the same |
|
154 |
- checkTrue(all(cisbp == queried)) |
|
155 |
- |
|
156 |
-} # test_jolma2013 |
|
157 |
-#---------------------------------------------------------------------------------------------------- |
|
158 |
-test_ScerTF <- function(){ |
|
159 |
- |
|
160 |
- # Load the cisbp matrix as "cisbp" |
|
161 |
- load("./single_matrices/ScerTF.Rdata") |
|
162 |
- |
|
163 |
- # Matrix name |
|
164 |
- mtx.name <- "M0308_1.02" |
|
165 |
- |
|
166 |
- # Query for the same matrix |
|
167 |
- queried <- query(MotifDb, mtx.name)[[1]] |
|
168 |
- |
|
169 |
- # Check that they're the same |
|
170 |
- checkTrue(all(cisbp == queried)) |
|
171 |
- |
|
172 |
-} # test_ScerTF |
|
173 |
-#---------------------------------------------------------------------------------------------------- |
|
174 |
-test_stamlab <- function(){ |
|
175 |
- |
|
176 |
- # Load the cisbp matrix as "cisbp" |
|
177 |
- load("./single_matrices/stamlab.Rdata") |
|
178 |
- |
|
179 |
- # Matrix name |
|
180 |
- mtx.name <- "M0308_1.02" |
|
181 |
- |
|
182 |
- # Query for the same matrix |
|
183 |
- queried <- query(MotifDb, mtx.name)[[1]] |
|
184 |
- |
|
185 |
- # Check that they're the same |
|
186 |
- checkTrue(all(cisbp == queried)) |
|
187 |
- |
|
188 |
-} # test_stamlab |
|
189 |
-#---------------------------------------------------------------------------------------------------- |
|
190 |
-test_SwissRegulon <- function(){ |
|
191 |
- |
|
192 |
- # Load the cisbp matrix as "cisbp" |
|
193 |
- load("./single_matrices/SR_matrix.Rdata") |
|
194 |
- |
|
195 |
- # Matrix name |
|
196 |
- mtx.name <- "M0308_1.02" |
|
197 |
- |
|
198 |
- # Query for the same matrix |
|
199 |
- queried <- query(MotifDb, mtx.name)[[1]] |
|
200 |
- |
|
201 |
- # Check that they're the same |
|
202 |
- checkTrue(all(cisbp == queried)) |
|
203 |
- |
|
204 |
-} # test_SwissRegulon |
|
205 |
-#---------------------------------------------------------------------------------------------------- |
|
206 |
-test_UniPROBE <- function(){ |
|
207 |
- |
|
208 |
- # Load the uniprobe matrix as "uniprobe" |
|
209 |
- load("./single_matrices/UniPROBE_matrix.Rdata") |
|
210 |
- |
|
211 |
- # Matrix name |
|
212 |
- mtx.name <- "UP00230" |
|
213 |
- |
|
214 |
- # Query for the same matrix |
|
215 |
- queried <- query(MotifDb, mtx.name)[[1]] |
|
216 |
- |
|
217 |
- # Check that they're the same |
|
218 |
- checkTrue(all(uniprobe == queried)) |
|
219 |
- |
|
220 |
-} # test_UniPROBE |
|
221 |
- |
... | ... |
@@ -42,9 +42,10 @@ runTests = function () |
42 | 42 |
test.export_jasparFormatToFile() |
43 | 43 |
|
44 | 44 |
test.geneToMotif() |
45 |
+ test.geneToMotif.ignore.jasparSuffixes() |
|
45 | 46 |
test.motifToGene() |
46 |
- test.associateTranscriptionFactors() |
|
47 | 47 |
|
48 |
+ test.associateTranscriptionFactors() |
|
48 | 49 |
} # runTests |
49 | 50 |
#------------------------------------------------------------------------------------------------------------------------ |
50 | 51 |
test.emptyCtor = function () |
... | ... |
@@ -288,10 +289,10 @@ test.flyBindingDomains = function () |
288 | 289 |
|
289 | 290 |
# these counts will likely change with a fresh load of data from FlyFactorSurvey. |
290 | 291 |
|
291 |
- checkEquals (tmp$Homeobox, 212) |
|
292 |
- checkEquals (tmp[['zf-C2H2']], 160) |
|
293 |
- checkEquals (tmp[["Helix-Turn-Helix"]], 182) |
|
294 |
- checkEquals (length (which (is.na (subset (x, organism=='Dmelanogaster')$bindingDomain))), 301) # lots of cisbp |
|
292 |
+ checkEquals(tmp$Homeobox, 212) |
|
293 |
+ checkEquals(tmp[['zf-C2H2']], 160) |
|
294 |
+ checkEquals(tmp[["Helix-Turn-Helix"]], 182) |
|
295 |
+ checkTrue(length(which(is.na(subset(x, organism=='Dmelanogaster')$bindingDomain))) > 300) # lots of cisbp |
|
295 | 296 |
|
296 | 297 |
} # test.flyBindingDomains |
297 | 298 |
#------------------------------------------------------------------------------------------------------------------------ |
... | ... |
@@ -563,7 +564,7 @@ test.export_memeFormatToFileDuplication = function () |
563 | 564 |
print ('--- test.export_memeFormatToFileDuplication') |
564 | 565 |
mdb = MotifDb # () |
565 | 566 |
mdb.mouse = subset (mdb, organism=='Mmusculus') |
566 |
- checkEquals (length (mdb.mouse), 1251) |
|
567 |
+ checkTrue(length(mdb.mouse) > 1300) |
|
567 | 568 |
output.file = 'mouse.txt' # tempfile () |
568 | 569 |
max = 3 |
569 | 570 |
meme.text = export (mdb.mouse [1:max], output.file, 'meme') |
... | ... |
@@ -771,7 +772,7 @@ test.geneToMotif <- function() |
771 | 772 |
|
772 | 773 |
# MotifDb mode uses the MotifDb metadata, pulled from many sources |
773 | 774 |
tbl.mdb <- geneToMotif(mdb, genes, source="mOtifdb") # intentional mis-capitalization |
774 |
- checkEquals(dim(tbl.mdb), c(12, 6)) |
|
775 |
+ checkEquals(dim(tbl.mdb), c(13, 6)) |
|
775 | 776 |
checkEquals(subset(tbl.mdb, dataSource=="jaspar2016" & geneSymbol== "FOS")$motif, "MA0476.1") |
776 | 777 |
# no recognizable (i.e., jaspar standard) motif name returned by MotifDb metadata |
777 | 778 |
# MotifDb for ATF5 |
... | ... |
@@ -809,9 +810,11 @@ test.geneToMotif.ignore.jasparSuffixes <- function() |
809 | 810 |
# this establishes the need for careful scrutiny as one winnows a geneToMotif result into |
810 | 811 |
# useful non-reduplicative sequence analysis |
811 | 812 |
|
812 |
- checkEquals(as.list(query(mdb, "MA0110599")), as.list(query(query(mdb, "MA0476.1"), "jaspar2018"))) |
|
813 |
+ pfm.ma0110599 <- as.list(query(mdb, "MA0110599"))[[1]] |
|
814 |
+ pfm.ma0476.1 <- as.list(query(query(mdb, "MA0476.1"), "jaspar2018"))[[1]] |
|
815 |
+ checkEquals(pfm.ma0110599, pfm.ma0476.1) |
|
813 | 816 |
|
814 |
-} # test.geneToMotif |
|
817 |
+} # test.geneToMotif.ignore.jasparSuffixes |
|
815 | 818 |
#------------------------------------------------------------------------------------------------------------------------ |
816 | 819 |
test.motifToGene <- function() |
817 | 820 |
{ |
... | ... |
@@ -822,14 +825,15 @@ test.motifToGene <- function() |
822 | 825 |
|
823 | 826 |
# MotifDb mode uses the MotifDb metadata "providerId", |
824 | 827 |
tbl.mdb <- motifToGene(MotifDb, motifs, source="MotifDb") |
825 |
- checkEquals(dim(tbl.mdb), c(3, 6)) |
|
826 |
- expected <- sort(c("MA0592.2", "ELF1.SwissRegulon", "UP00022")) |
|
828 |
+ checkEquals(dim(tbl.mdb), c(4, 6)) |
|
829 |
+ expected <- sort(c("MA0592.2", "MA0592.2", "ELF1.SwissRegulon", "UP00022")) |
|
827 | 830 |
actual <- sort(tbl.mdb$motif) |
828 | 831 |
checkEquals(actual, expected) |
829 |
- checkEquals(sort(tbl.mdb$geneSymbol), sort(c("Esrra", "ELF1", "Zfp740"))) |
|
830 |
- checkEquals(sort(tbl.mdb$dataSource), sort(c("jaspar2016", "SwissRegulon", "UniPROBE"))) |
|
831 |
- checkEquals(sort(tbl.mdb$organism), sort(c("Mmusculus", "Hsapiens", "Mmusculus"))) |
|
832 |
- checkEquals(sort(tbl.mdb$source), rep("MotifDb", 3)) |
|
832 |
+ checkEquals(sort(tbl.mdb$geneSymbol), sort(c("ELF1", "Esrra", "Esrra", "Zfp740"))) |
|
833 |
+ checkEquals(sort(tbl.mdb$dataSource), sort(c("jaspar2016", "jaspar2018", "SwissRegulon", "UniPROBE"))) |
|
834 |
+ |
|
835 |
+ checkEquals(sort(tbl.mdb$organism), sort(c("Hsapiens", "Mmusculus", "Mmusculus", "Mmusculus"))) |
|
836 |
+ checkEquals(tbl.mdb$source, rep("MotifDb", 4)) |
|
833 | 837 |
|
834 | 838 |
# TFClass mode uses TF family classifcation |
835 | 839 |
tbl.tfClass <- motifToGene(MotifDb, motifs, source="TFClass") |