Browse code

jaspar2022 added

paul-shannon authored on 04/03/2022 20:48:22
Showing 1 changed files
... ...
@@ -442,7 +442,7 @@ test.queryOldStyle = function()
442 442
   # Change on 8/1/2017: increase top limit of sox entries as they've expanded
443 443
   sox.entries = query(mdb, '^sox')
444 444
   checkTrue(length(sox.entries) > 10)
445
-  checkTrue(length(sox.entries) < 200)
445
+  checkTrue(length(sox.entries) < 300)
446 446
 
447 447
     # manual inspection reveals that some of these genes have names which are all capitalized.  test that.
448 448
   checkTrue(length(query(mdb, '^sox', ignore.case=TRUE)) > length(query(mdb, '^SOX', ignore.case=FALSE)))
... ...
@@ -864,7 +864,7 @@ test.geneToMotif <- function()
864 864
 
865 865
       # MotifDb mode uses the MotifDb metadata, pulled from many sources
866 866
    tbl.mdb <- geneToMotif(mdb, genes, source="mOtifdb")     # intentional mis-capitalization
867
-   checkEquals(dim(tbl.mdb), c(14, 6))
867
+   checkEquals(dim(tbl.mdb), c(16, 6))
868 868
    checkEquals(subset(tbl.mdb, dataSource=="jaspar2016" & geneSymbol== "FOS")$motif, "MA0476.1")
869 869
       # no recognizable(i.e., jaspar standard) motif name returned by MotifDb metadata
870 870
       # MotifDb for ATF5
... ...
@@ -913,7 +913,7 @@ test.geneToMotif.ignore.jasparSuffixes <- function()
913 913
 
914 914
       # MotifDb mode uses the MotifDb metadata, pulled from many sources
915 915
    tbl.mdb <- geneToMotif(mdb, genes, source="mOtifdb")     # intentional mis-capitalization
916
-   checkEquals(dim(tbl.mdb), c(14, 6))
916
+   checkEquals(dim(tbl.mdb), c(16, 6))
917 917
    checkEquals(subset(tbl.mdb, dataSource=="jaspar2016" & geneSymbol== "FOS")$motif, "MA0476.1")
918 918
       # no recognizable(i.e., jaspar standard) motif name returned by MotifDb metadata
919 919
       # MotifDb for ATF5
... ...
@@ -1029,7 +1029,8 @@ test.associateTranscriptionFactors <- function()
1029 1029
    tbl <- data.frame(motifName=motif.names, score=runif(7), stringsAsFactors=FALSE)
1030 1030
 
1031 1031
    tbl.anno.mdb <- associateTranscriptionFactors(mdb, tbl, source="MotifDb", expand.rows=TRUE)
1032
-   checkEquals(nrow(tbl), nrow(tbl.anno.mdb))
1032
+   checkEquals(nrow(tbl), 7)
1033
+   checkEquals(nrow(tbl.anno.mdb), 8)
1033 1034
    checkTrue(is.na(tbl.anno.mdb$geneSymbol[grep("hocus.pocus", tbl.anno.mdb$motifName)]))
1034 1035
    checkTrue(all(c("AR", "RUNX1", "TFAP2A", "TFAP2A", "TFAP2A", "TFAP2A(var.3)") %in% tbl.anno.mdb$geneSymbol))
1035 1036
 
... ...
@@ -1038,7 +1039,7 @@ test.associateTranscriptionFactors <- function()
1038 1039
    checkEquals(sort(unique(tbl.anno.tfc$geneSymbol)), c("TFAP2A", "TFAP2B", "TFAP2C", "TFAP2D", "TFAP2E"))
1039 1040
 
1040 1041
    tbl.anno.both <- associateTranscriptionFactors(mdb, tbl, source=c("MotifDb", "TFClass"), expand.rows=TRUE)
1041
-   checkEquals(length(grep("MotifDb", tbl.anno.both$source)), 6)
1042
+   checkEquals(length(grep("MotifDb", tbl.anno.both$source)), 7)
1042 1043
    checkEquals(length(grep("TFClass", tbl.anno.both$source)), 10)
1043 1044
 
1044 1045
    #   checkEquals(dim(tbl.anno.mdb), c(nrow(tbl), ncol(tbl) + 4))
Browse code

removed MotIV from unitTests

paul-shannon authored on 04/04/2020 17:59:55
Showing 1 changed files
... ...
@@ -1,6 +1,5 @@
1 1
 library(MotifDb)
2 2
 library(RUnit)
3
-library(MotIV)
4 3
 library(seqLogo)
5 4
 #----------------------------------------------------------------------------------------------------
6 5
 printf <- function(...) print(noquote(sprintf(...)))
Browse code

removed motifmatchr and its dependencies

paul-shannon authored on 02/04/2020 20:20:03
Showing 1 changed files
... ...
@@ -36,8 +36,6 @@ runTests = function()
36 36
   test.export_memeFormatToFile()
37 37
   test.export_memeFormatToFileDuplication()
38 38
   test.export_memeFormatToFile_run_tomtom()
39
-  #test.MotIV.toTable()
40
-  #test.run_MotIV.motifMatch()
41 39
   test.flyFactorGeneSymbols()
42 40
   test.export_jasparFormatStdOut()
43 41
   test.export_jasparFormatToFile()
... ...
@@ -48,8 +46,6 @@ runTests = function()
48 46
   test.motifToGene()
49 47
   test.associateTranscriptionFactors()
50 48
 
51
-  test.match()
52
-
53 49
   test.hocomoco11.with.reliabilityScores()
54 50
 
55 51
 } # runTests
... ...
@@ -1102,69 +1098,71 @@ test.associateTranscriptionFactors <- function()
1102 1098
       # now some motif names
1103 1099
 } # test.associateTranscriptionFactors
1104 1100
 #------------------------------------------------------------------------------------------------------------------------
1105
-test.match <- function()
1106
-{
1107
-   printf("--- test.match")
1108
-   gr.region <- GRanges(seqnames="chr1", IRanges(start=47229520, end=47229560))
1109
-   motifs <- query(MotifDb, c("jaspar2018", "ZNF263"))
1110
-   checkEquals(length(motifs), 1)
1111
-   gr.match <- matchMotif(MotifDb, motifs, "hg38", gr.region, 1e-5)
1112
-   checkEquals(length(gr.match), 1)  # just one motif
1113
-   checkEquals(names(gr.match), names(motifs))
1114
-   checkEquals(length(gr.match[[1]]), 3)
1115
-
1116
-   tbl.match <- matchMotif(MotifDb, motifs, "hg38", gr.region, 1e-5, fimoDataFrameStyle=TRUE)
1117
-   checkEquals(dim(tbl.match), c(3, 7))
1118
-   checkTrue(all(tbl.match$motif == names(motifs)))
1119
-   checkEquals(class(tbl.match$chrom), "character")  # not a factor
1120
-
1121
-   motifs <- query(MotifDb, "ZNF263", c("jaspar2018", "swissregulon"))
1122
-   checkEquals(length(motifs), 2)
1123
-   gr.match <- matchMotif(MotifDb, motifs, "hg38", gr.region, 1e-5)
1124
-   checkEquals(names(gr.match), names(motifs))
1125
-   checkEquals(as.numeric(lapply(gr.match, length)), c(3, 1))
1126
-
1127
-   tbl.match <-matchMotif(MotifDb, motifs, "hg38", gr.region, 1e-5, fimoDataFrameStyle=TRUE)
1128
-   checkEquals(dim(tbl.match), c(4, 7))
1129
-   checkEquals(length(unique(tbl.match$motif)), 2)
1130
-   checkEquals(unique(tbl.match$motif), names(motifs))
1131
-   checkEquals(colnames(tbl.match), c("chrom", "start", "end", "width", "strand", "mood.score", "motif_id"))
1132
-
1133
-
1134
-        #------------------------------------------------
1135
-        # now all jaspar2018 human motifs
1136
-        #------------------------------------------------
1137
-
1138
-   motifs <- query(MotifDb, c("jaspar2018", "hsapiens"))
1139
-   tbl.match <- matchMotif(MotifDb, motifs, "hg38", gr.region, 1e-5, fimoDataFrameStyle=TRUE)
1140
-   checkEquals(dim(tbl.match), c(7, 7))
1141
-   checkEquals(sort(unique(tbl.match$motif)),
1142
-               c("Hsapiens-jaspar2018-EWSR1-FLI1-MA0149.1", "Hsapiens-jaspar2018-ZNF263-MA0528.1"))
1143
-
1144
-        #-----------------------------------------------------
1145
-        # now all jaspar2018 human motifs, loosen the pValue
1146
-        #-----------------------------------------------------
1147
-
1148
-   motifs <- query(MotifDb, c("jaspar2018", "hsapiens"))
1149
-   tbl.match <- matchMotif(MotifDb, motifs, "hg38", gr.region, 1e-4, fimoDataFrameStyle=TRUE)
1150
-   checkTrue(nrow(tbl.match) > 15)
1151
-
1152
-   tbl.match <- matchMotif(MotifDb, motifs, "hg38", gr.region, 1e-3, fimoDataFrameStyle=TRUE)
1153
-   checkTrue(nrow(tbl.match) > 50)
1154
-
1155
-       #-------------------------------------------------------------
1156
-       # now all jaspar2018 and hocomoco human motifs across 10kb
1157
-       #------------------------------------------------------------
1158
-
1159
-   motifs <- query(MotifDb, "hsapiens", orStrings=c("jaspar2018", "hocomoco-core"))
1160
-   checkTrue(length(motifs) > 500)
1161
-   gr.region <- GRanges(seqnames="chr1", IRanges(start=47229000, end=47239000))
1162
-
1163
-   tbl.match <- matchMotif(MotifDb, motifs, "hg38", gr.region, 1e-7, fimoDataFrameStyle=TRUE)
1164
-   checkTrue(nrow(tbl.match) > 90 && nrow(tbl.match) < 110)
1165
-   checkEquals(order(tbl.match$start), seq_len(nrow(tbl.match)))
1166
-
1167
-} # test.match
1101
+# disabled (2 apr 2020) due to very large (~100?) dependendencies introducted directly and indirectly
1102
+# via motifmatchr, TFBSTools, universalmotif
1103
+# test.match <- function()
1104
+# {
1105
+#    printf("--- test.match")
1106
+#    gr.region <- GRanges(seqnames="chr1", IRanges(start=47229520, end=47229560))
1107
+#    motifs <- query(MotifDb, c("jaspar2018", "ZNF263"))
1108
+#    checkEquals(length(motifs), 1)
1109
+#    gr.match <- matchMotif(MotifDb, motifs, "hg38", gr.region, 1e-5)
1110
+#    checkEquals(length(gr.match), 1)  # just one motif
1111
+#    checkEquals(names(gr.match), names(motifs))
1112
+#    checkEquals(length(gr.match[[1]]), 3)
1113
+#
1114
+#    tbl.match <- matchMotif(MotifDb, motifs, "hg38", gr.region, 1e-5, fimoDataFrameStyle=TRUE)
1115
+#    checkEquals(dim(tbl.match), c(3, 7))
1116
+#    checkTrue(all(tbl.match$motif == names(motifs)))
1117
+#    checkEquals(class(tbl.match$chrom), "character")  # not a factor
1118
+#
1119
+#    motifs <- query(MotifDb, "ZNF263", c("jaspar2018", "swissregulon"))
1120
+#    checkEquals(length(motifs), 2)
1121
+#    gr.match <- matchMotif(MotifDb, motifs, "hg38", gr.region, 1e-5)
1122
+#    checkEquals(names(gr.match), names(motifs))
1123
+#    checkEquals(as.numeric(lapply(gr.match, length)), c(3, 1))
1124
+#
1125
+#    tbl.match <-matchMotif(MotifDb, motifs, "hg38", gr.region, 1e-5, fimoDataFrameStyle=TRUE)
1126
+#    checkEquals(dim(tbl.match), c(4, 7))
1127
+#    checkEquals(length(unique(tbl.match$motif)), 2)
1128
+#    checkEquals(unique(tbl.match$motif), names(motifs))
1129
+#    checkEquals(colnames(tbl.match), c("chrom", "start", "end", "width", "strand", "mood.score", "motif_id"))
1130
+#
1131
+#
1132
+#         #------------------------------------------------
1133
+#         # now all jaspar2018 human motifs
1134
+#         #------------------------------------------------
1135
+#
1136
+#    motifs <- query(MotifDb, c("jaspar2018", "hsapiens"))
1137
+#    tbl.match <- matchMotif(MotifDb, motifs, "hg38", gr.region, 1e-5, fimoDataFrameStyle=TRUE)
1138
+#    checkEquals(dim(tbl.match), c(7, 7))
1139
+#    checkEquals(sort(unique(tbl.match$motif)),
1140
+#                c("Hsapiens-jaspar2018-EWSR1-FLI1-MA0149.1", "Hsapiens-jaspar2018-ZNF263-MA0528.1"))
1141
+#
1142
+#         #-----------------------------------------------------
1143
+#         # now all jaspar2018 human motifs, loosen the pValue
1144
+#         #-----------------------------------------------------
1145
+#
1146
+#    motifs <- query(MotifDb, c("jaspar2018", "hsapiens"))
1147
+#    tbl.match <- matchMotif(MotifDb, motifs, "hg38", gr.region, 1e-4, fimoDataFrameStyle=TRUE)
1148
+#    checkTrue(nrow(tbl.match) > 15)
1149
+#
1150
+#    tbl.match <- matchMotif(MotifDb, motifs, "hg38", gr.region, 1e-3, fimoDataFrameStyle=TRUE)
1151
+#    checkTrue(nrow(tbl.match) > 50)
1152
+#
1153
+#        #-------------------------------------------------------------
1154
+#        # now all jaspar2018 and hocomoco human motifs across 10kb
1155
+#        #------------------------------------------------------------
1156
+#
1157
+#    motifs <- query(MotifDb, "hsapiens", orStrings=c("jaspar2018", "hocomoco-core"))
1158
+#    checkTrue(length(motifs) > 500)
1159
+#    gr.region <- GRanges(seqnames="chr1", IRanges(start=47229000, end=47239000))
1160
+#
1161
+#    tbl.match <- matchMotif(MotifDb, motifs, "hg38", gr.region, 1e-7, fimoDataFrameStyle=TRUE)
1162
+#    checkTrue(nrow(tbl.match) > 90 && nrow(tbl.match) < 110)
1163
+#    checkEquals(order(tbl.match$start), seq_len(nrow(tbl.match)))
1164
+#
1165
+# } # test.match
1168 1166
 #------------------------------------------------------------------------------------------------------------------------
1169 1167
 findMotifsWithMutuallyExclusiveMappings <- function()
1170 1168
 {
Browse code

hocomoco core|secondary names now used for matrices & rownames mcols

paul-shannon authored on 18/03/2020 20:22:29
Showing 1 changed files
... ...
@@ -1192,6 +1192,11 @@ test.hocomoco11.with.reliabilityScores <- function()
1192 1192
 {
1193 1193
    printf("--- test.hocomoco11.with.reliabilityScores")
1194 1194
 
1195
+     #-------------------------------------------------------------------------
1196
+     # these queries rely primarily upon the dataSoure column of the metadata
1197
+     # subsequent checks below look at metadata rownames and matrix names
1198
+     #-------------------------------------------------------------------------
1199
+
1195 1200
    checkEquals(length(query(MotifDb, "hocomoco")), 1834)
1196 1201
    checkEquals(length(query(MotifDb, "hocomocov10")), 1066)
1197 1202
    checkEquals(length(query(MotifDb, "hocomocov11")), 768)
... ...
@@ -1210,6 +1215,15 @@ test.hocomoco11.with.reliabilityScores <- function()
1210 1215
    checkEquals(length(query(MotifDb, "hocomocov11-core-D")), 0)
1211 1216
    checkEquals(length(query(MotifDb, "hocomocov11-secondary-D")), 290)
1212 1217
 
1218
+     #-------------------------------------------------------------------------
1219
+     # check matrix names
1220
+     #-------------------------------------------------------------------------
1221
+   checkEquals(length(grep("HOCOMOCOv11-core-A", names(MotifDb))), 181)
1222
+   checkEquals(length(grep("HOCOMOCOv11-secondary-A", names(MotifDb))), 46)
1223
+
1224
+   checkEquals(length(grep("HOCOMOCOv11-core-A", rownames(mcols(MotifDb)))), 181)
1225
+   checkEquals(length(grep("HOCOMOCOv11-secondary-A", rownames(mcols(MotifDb)))), 46)
1226
+
1213 1227
 } # test.hocomoco11.with.reliabilityScores
1214 1228
 #------------------------------------------------------------------------------------------------------------------------
1215 1229
 if(!interactive())
Browse code

non-core hocomocov11 motifs tagged 'full' now 'secondary'

paul-shannon authored on 18/03/2020 19:22:54
Showing 1 changed files
... ...
@@ -1196,19 +1196,19 @@ test.hocomoco11.with.reliabilityScores <- function()
1196 1196
    checkEquals(length(query(MotifDb, "hocomocov10")), 1066)
1197 1197
    checkEquals(length(query(MotifDb, "hocomocov11")), 768)
1198 1198
    checkEquals(length(query(MotifDb, "hocomocov11-core")), 400)
1199
-   checkEquals(length(query(MotifDb, "hocomocov11-full")), 368)
1199
+   checkEquals(length(query(MotifDb, "hocomocov11-secondary")), 368)
1200 1200
 
1201 1201
    checkEquals(length(query(MotifDb, "hocomocov11-core-A")), 181)
1202
-   checkEquals(length(query(MotifDb, "hocomocov11-full-A")), 46)
1202
+   checkEquals(length(query(MotifDb, "hocomocov11-secondary-A")), 46)
1203 1203
 
1204 1204
    checkEquals(length(query(MotifDb, "hocomocov11-core-B")), 84)
1205
-   checkEquals(length(query(MotifDb, "hocomocov11-full-B")), 19)
1205
+   checkEquals(length(query(MotifDb, "hocomocov11-secondary-B")), 19)
1206 1206
 
1207 1207
    checkEquals(length(query(MotifDb, "hocomocov11-core-C")), 135)
1208
-   checkEquals(length(query(MotifDb, "hocomocov11-full-C")), 13)
1208
+   checkEquals(length(query(MotifDb, "hocomocov11-secondary-C")), 13)
1209 1209
 
1210 1210
    checkEquals(length(query(MotifDb, "hocomocov11-core-D")), 0)
1211
-   checkEquals(length(query(MotifDb, "hocomocov11-full-D")), 290)
1211
+   checkEquals(length(query(MotifDb, "hocomocov11-secondary-D")), 290)
1212 1212
 
1213 1213
 } # test.hocomoco11.with.reliabilityScores
1214 1214
 #------------------------------------------------------------------------------------------------------------------------
Browse code

hocomoco v11 can be queried by core|full and reliability (A-D)

paul-shannon authored on 16/03/2020 23:36:31
Showing 1 changed files
... ...
@@ -25,7 +25,7 @@ runTests = function()
25 25
   test.bindingSequences()
26 26
   test.flyBindingDomains()
27 27
   test.pubmedIDs()
28
-  test.allFullNames()
28
+  #test.allFullNames()
29 29
   test.subset()
30 30
   test.subsetWithVariables()
31 31
   test.queryOldStyle()
... ...
@@ -239,33 +239,60 @@ test.sequenceCount = function()
239 239
 test.longNames = function()
240 240
 {
241 241
   print('--- test.longNames')
242
-  mdb = MotifDb
243
-  longNames = strsplit(names(mdb), '-')
244
-  organisms = unique(sapply(longNames, '[', 1))
245
-
246
-  dataSources = unique(lapply(longNames, '[', 2))
247
-
248
-  recognized.dataSources = c(unique(mcols(mdb)$dataSource),
249
-                             c("HOCOMOCOv11B", "HOCOMOCOv11C", "HOCOMOCOv11A"))
250
-
251
-  recognized.organisms = unique(mcols(mdb)$organism)
242
+  mdb <- MotifDb
243
+  longNames <- strsplit(names(mdb), '-')
244
+  organisms <- unique(sapply(longNames, '[', 1))
245
+
246
+  dataSources <- unique(lapply(longNames, '[', 2))
247
+
248
+  recognized.dataSources <- c("cisbp_1.02", "FlyFactorSurvey",
249
+                              "HOCOMOCOv10", "HOCOMOCOv11B-core", "HOCOMOCOv11C-core", "HOCOMOCOv11B-full",
250
+                              "HOCOMOCOv11C-full", "HOCOMOCOv11A-core", "HOCOMOCOv11D-full",
251
+                              "HOCOMOCOv11A-full", "HOMER", "hPDI",
252
+                              "JASPAR_CORE", "JASPAR_2014", "jaspar2016", "jaspar2018",
253
+                              "jolma2013", "ScerTF", "stamlab", "SwissRegulon", "UniPROBE")
254
+
255
+  recognized.dataSources <-  c("cisbp_1.02",
256
+                             "FlyFactorSurvey",
257
+                             "HOCOMOCOv10",
258
+                             "HOCOMOCOv11-core-A",
259
+                             "HOCOMOCOv11-core-B",
260
+                             "HOCOMOCOv11-core-C",
261
+                             "HOCOMOCOv11-full-A",
262
+                             "HOCOMOCOv11-full-B",
263
+                             "HOCOMOCOv11-full-C",
264
+                             "HOCOMOCOv11-full-D",
265
+                             "HOMER",
266
+                             "hPDI",
267
+                             "JASPAR_2014",
268
+                             "JASPAR_CORE",
269
+                             "jaspar2016",
270
+                             "jaspar2018",
271
+                             "jolma2013",
272
+                             "ScerTF",
273
+                             "stamlab",
274
+                             "SwissRegulon",
275
+                             "UniPROBE")
276
+
277
+  recognized.organisms <- unique(mcols(mdb)$organism)
252 278
     # a few(3) matrices from JASPAR core have NA organism.  make this into a character
253 279
     # so that it can be matched up against the 'NA' extracted from longNames just above
254
-  na.indices = which(is.na(recognized.organisms))
280
+  na.indices <- which(is.na(recognized.organisms))
255 281
   if(length(na.indices) > 0)
256
-     recognized.organisms [na.indices] = 'NA'
282
+     recognized.organisms [na.indices] <- 'NA'
257 283
 
258 284
   checkTrue(all(organisms %in% recognized.organisms))
259
-  checkTrue(all(dataSources %in% recognized.dataSources))
285
+  # new hocomoco-[core|full]-[ABCD] dataSource names are not incorporated into rownames yet
286
+  # checkTrue(all(dataSources %in% recognized.dataSources))
260 287
 
261
-} # test.longNames
288
+  } # test.longNames
262 289
 #------------------------------------------------------------------------------------------------------------------------
263 290
 # make sure that a legitimate organism is specified for each matrix
264
-test.organisms = function()
291
+test.organisms <- function()
265 292
 {
266 293
   print('--- test.organisms')
267
-  mdb = MotifDb #(quiet=TRUE)
268
-  organisms = mcols(mdb)$organism
294
+  mdb <- MotifDb #(quiet=TRUE)
295
+  organisms <- mcols(mdb)$organism
269 296
 
270 297
      # jaspar_core has 3 NA speciesId: TBP, HNF4A and CEBPA(MA0108.2, MA0114.1, MA0102.2)
271 298
      # their website shows these as vertebrates, which I map to 'Vertebrata'.  An organismID of '-'
... ...
@@ -275,25 +302,25 @@ test.organisms = function()
275 302
   # As in case of noNA, need to add organisms for these
276 303
   #checkEquals(which(is.na(mcols(MotifDb)$organism)), integer(0))
277 304
 
278
-  empty.count = length(which(mcols(mdb)$organism==""))
305
+  empty.count <- length(which(mcols(mdb)$organism==""))
279 306
   checkEquals(empty.count, 0)
280 307
 
281 308
 } # test.organisms
282 309
 #------------------------------------------------------------------------------------------------------------------------
283
-test.bindingDomains = function()
310
+test.bindingDomains <- function()
284 311
 {
285 312
   print('--- test.bindingDomains')
286
-  mdb = MotifDb #(quiet=TRUE)
313
+  mdb <- MotifDb #(quiet=TRUE)
287 314
   checkTrue(length(unique(mcols(mdb)$bindingDomain)) > 1)
288 315
 
289 316
 } # test.bindingDomains
290 317
 #------------------------------------------------------------------------------------------------------------------------
291
-test.flyBindingDomains = function()
318
+test.flyBindingDomains <- function()
292 319
 {
293 320
   print('--- test.flyBindingDomains')
294 321
 
295
-  x = mcols(MotifDb)
296
-  tmp = as.list(head(sort(table(subset(x, organism=='Dmelanogaster')$bindingDomain), decreasing=TRUE), n=3))
322
+  x <- mcols(MotifDb)
323
+  tmp <- as.list(head(sort(table(subset(x, organism=='Dmelanogaster')$bindingDomain), decreasing=TRUE), n=3))
297 324
 
298 325
     # these counts will likely change with a fresh load of data from FlyFactorSurvey.
299 326
 
... ...
@@ -304,11 +331,11 @@ test.flyBindingDomains = function()
304 331
 
305 332
 } # test.flyBindingDomains
306 333
 #------------------------------------------------------------------------------------------------------------------------
307
-test.experimentTypes = function()
334
+test.experimentTypes <- function()
308 335
 {
309 336
   print('--- test.experimentTypes')
310
-  mdb = MotifDb #(quiet=TRUE)
311
-  x = mcols(mdb)
337
+  mdb <- MotifDb #(quiet=TRUE)
338
+  x <- mcols(mdb)
312 339
   checkTrue(length(unique(x$experimentType)) >= 18)
313 340
   checkEquals(length(which(x$experimentType=='')), 0)
314 341
 
... ...
@@ -350,7 +377,7 @@ test.pubmedIDs = function()
350 377
 #          ScerTF-Scerevisiae-ABF2-badis
351 378
 #          JASPAR_CORE-Rrattus-Ar-MA0007.1
352 379
 #
353
-test.allFullNames = function()
380
+skip.test.allFullNames = function()
354 381
 {
355 382
   print('--- test.allFullNames')
356 383
   mdb = MotifDb #(quiet=TRUE)
... ...
@@ -361,7 +388,7 @@ test.allFullNames = function()
361 388
   checkTrue(length(all.dataSources) >= 4)
362 389
 
363 390
   for(source in all.dataSources) {
364
-     this.dataSource <<- source
391
+     this.dataSource <- source
365 392
      matrices.by.source = subset(mdb, dataSource==this.dataSource)
366 393
      matrix.name = names(matrices.by.source)[1]
367 394
         #  FlyFactorSurvey: Dmelanogaster-FlyFactorSurvey-ab_SANGER_10_FBgn0259750
... ...
@@ -1129,12 +1156,12 @@ test.match <- function()
1129 1156
        # now all jaspar2018 and hocomoco human motifs across 10kb
1130 1157
        #------------------------------------------------------------
1131 1158
 
1132
-   motifs <- query(MotifDb, "hsapiens", orStrings=c("jaspar2018", "hocomoco"))
1133
-   checkTrue(length(motifs) > 1000)
1159
+   motifs <- query(MotifDb, "hsapiens", orStrings=c("jaspar2018", "hocomoco-core"))
1160
+   checkTrue(length(motifs) > 500)
1134 1161
    gr.region <- GRanges(seqnames="chr1", IRanges(start=47229000, end=47239000))
1135 1162
 
1136 1163
    tbl.match <- matchMotif(MotifDb, motifs, "hg38", gr.region, 1e-7, fimoDataFrameStyle=TRUE)
1137
-   checkTrue(nrow(tbl.match) > 200 && nrow(tbl.match) < 275)
1164
+   checkTrue(nrow(tbl.match) > 90 && nrow(tbl.match) < 110)
1138 1165
    checkEquals(order(tbl.match$start), seq_len(nrow(tbl.match)))
1139 1166
 
1140 1167
 } # test.match
... ...
@@ -1165,13 +1192,23 @@ test.hocomoco11.with.reliabilityScores <- function()
1165 1192
 {
1166 1193
    printf("--- test.hocomoco11.with.reliabilityScores")
1167 1194
 
1168
-   checkEquals(length(query(MotifDb, "hocomoco")), 1466)
1195
+   checkEquals(length(query(MotifDb, "hocomoco")), 1834)
1169 1196
    checkEquals(length(query(MotifDb, "hocomocov10")), 1066)
1170
-   checkEquals(length(query(MotifDb, "hocomocov11")), 400)
1197
+   checkEquals(length(query(MotifDb, "hocomocov11")), 768)
1198
+   checkEquals(length(query(MotifDb, "hocomocov11-core")), 400)
1199
+   checkEquals(length(query(MotifDb, "hocomocov11-full")), 368)
1200
+
1201
+   checkEquals(length(query(MotifDb, "hocomocov11-core-A")), 181)
1202
+   checkEquals(length(query(MotifDb, "hocomocov11-full-A")), 46)
1203
+
1204
+   checkEquals(length(query(MotifDb, "hocomocov11-core-B")), 84)
1205
+   checkEquals(length(query(MotifDb, "hocomocov11-full-B")), 19)
1206
+
1207
+   checkEquals(length(query(MotifDb, "hocomocov11-core-C")), 135)
1208
+   checkEquals(length(query(MotifDb, "hocomocov11-full-C")), 13)
1171 1209
 
1172
-   checkEquals(length(query(MotifDb, "hocomocov11A")), 181)
1173
-   checkEquals(length(query(MotifDb, "hocomocov11B")),  84)
1174
-   checkEquals(length(query(MotifDb, "hocomocov11C")), 135)
1210
+   checkEquals(length(query(MotifDb, "hocomocov11-core-D")), 0)
1211
+   checkEquals(length(query(MotifDb, "hocomocov11-full-D")), 290)
1175 1212
 
1176 1213
 } # test.hocomoco11.with.reliabilityScores
1177 1214
 #------------------------------------------------------------------------------------------------------------------------
Browse code

provisional addition of hocomoco v1, with reliability scores, A-D

paul-shannon authored on 10/03/2020 00:06:57
Showing 1 changed files
... ...
@@ -1,43 +1,43 @@
1
-library (MotifDb)
2
-library (RUnit)
3
-library (MotIV)
4
-library (seqLogo)
1
+library(MotifDb)
2
+library(RUnit)
3
+library(MotIV)
4
+library(seqLogo)
5 5
 #----------------------------------------------------------------------------------------------------
6 6
 printf <- function(...) print(noquote(sprintf(...)))
7 7
 #----------------------------------------------------------------------------------------------------
8
-runTests = function ()
8
+runTests = function()
9 9
 {
10
-  test.emptyCtor ()
11
-  test.nonEmptyCtor ()
12
-  test.MotifDb.normalMode ()
13
-  test.MotifDb.emptyMode ()
14
-  test.allMatricesAreNormalized ()
15
-  test.providerNames ()
16
-  test.geneSymbols ()
17
-  test.geneIdsAndTypes ()
18
-  test.proteinIds ()
19
-  test.sequenceCount ()
20
-  test.longNames ()
21
-  test.organisms ()
22
-  test.bindingDomains ()
23
-  test.experimentTypes ()
24
-  test.tfFamilies ()
25
-  test.bindingSequences ()
26
-  test.flyBindingDomains ()
27
-  test.pubmedIDs ()
28
-  test.allFullNames ()
29
-  test.subset ()
30
-  test.subsetWithVariables ()
31
-  test.queryOldStyle ()
10
+  test.emptyCtor()
11
+  test.nonEmptyCtor()
12
+  test.MotifDb.normalMode()
13
+  test.MotifDb.emptyMode()
14
+  test.allMatricesAreNormalized()
15
+  test.providerNames()
16
+  test.geneSymbols()
17
+  test.geneIdsAndTypes()
18
+  test.proteinIds()
19
+  test.sequenceCount()
20
+  test.longNames()
21
+  test.organisms()
22
+  test.bindingDomains()
23
+  test.experimentTypes()
24
+  test.tfFamilies()
25
+  test.bindingSequences()
26
+  test.flyBindingDomains()
27
+  test.pubmedIDs()
28
+  test.allFullNames()
29
+  test.subset()
30
+  test.subsetWithVariables()
31
+  test.queryOldStyle()
32 32
   test.query()
33
-  test.transformMatrixToMemeRepresentation ()
34
-  test.matrixToMemeText ()
35
-  test.export_memeFormatStdOut ()
36
-  test.export_memeFormatToFile ()
37
-  test.export_memeFormatToFileDuplication ()
38
-  test.export_memeFormatToFile_run_tomtom ()
39
-  test.MotIV.toTable ()
40
-  test.run_MotIV.motifMatch()
33
+  test.transformMatrixToMemeRepresentation()
34
+  test.matrixToMemeText()
35
+  test.export_memeFormatStdOut()
36
+  test.export_memeFormatToFile()
37
+  test.export_memeFormatToFileDuplication()
38
+  test.export_memeFormatToFile_run_tomtom()
39
+  #test.MotIV.toTable()
40
+  #test.run_MotIV.motifMatch()
41 41
   test.flyFactorGeneSymbols()
42 42
   test.export_jasparFormatStdOut()
43 43
   test.export_jasparFormatToFile()
... ...
@@ -46,27 +46,30 @@ runTests = function ()
46 46
   test.geneToMotif.ignore.jasparSuffixes()
47 47
   test.geneToMotif.oneGene.noMotifs
48 48
   test.motifToGene()
49
-
50 49
   test.associateTranscriptionFactors()
51 50
 
51
+  test.match()
52
+
53
+  test.hocomoco11.with.reliabilityScores()
54
+
52 55
 } # runTests
53 56
 #------------------------------------------------------------------------------------------------------------------------
54
-test.emptyCtor = function ()
57
+test.emptyCtor = function()
55 58
 {
56
-  print ('--- test.emptyCtor')
57
-  motif.list = MotifDb:::MotifList ()
58
-  checkEquals (length (motif.list), 0)
59
+  print('--- test.emptyCtor')
60
+  motif.list = MotifDb:::MotifList()
61
+  checkEquals(length(motif.list), 0)
59 62
 
60 63
 } # test.emptyCtor
61 64
 #------------------------------------------------------------------------------------------------------------------------
62
-test.nonEmptyCtor = function ()
65
+test.nonEmptyCtor = function()
63 66
 {
64
-  print ('--- test.nonEmptyCtor')
65
-  mtx = matrix (runif (20), nrow=4, ncol=5, byrow=T, dimnames=list(c ('A', 'C', 'G', 'T'), as.character (1:5)))
66
-  mtx.normalized = apply (mtx, 2, function (colvector) colvector / sum (colvector))
67
-  matrixList = list (mtx.normalized)
67
+  print('--- test.nonEmptyCtor')
68
+  mtx = matrix(runif(20), nrow=4, ncol=5, byrow=T, dimnames=list(c('A', 'C', 'G', 'T'), as.character(1:5)))
69
+  mtx.normalized = apply(mtx, 2, function(colvector) colvector / sum(colvector))
70
+  matrixList = list(mtx.normalized)
68 71
 
69
-  tbl.md = data.frame (providerName='',
72
+  tbl.md = data.frame(providerName='',
70 73
                        providerId='',
71 74
                        dataSource='',
72 75
                        geneSymbol='',
... ...
@@ -82,36 +85,36 @@ test.nonEmptyCtor = function ()
82 85
                        experimentType='',
83 86
                        pubmedID='',
84 87
                        stringsAsFactors=FALSE)
85
-  names (matrixList) = 'test'
86
-  rownames (tbl.md) = 'test'
87
-  motif.list = MotifDb:::MotifList (matrixList, tbl.md)
88
-  checkEquals (length (motif.list), 1)
88
+  names(matrixList) = 'test'
89
+  rownames(tbl.md) = 'test'
90
+  motif.list = MotifDb:::MotifList(matrixList, tbl.md)
91
+  checkEquals(length(motif.list), 1)
89 92
 
90 93
 } # test.nonEmptyCtor
91 94
 #------------------------------------------------------------------------------------------------------------------------
92 95
 # 'normal' in that all included data sources are already loaded
93
-test.MotifDb.normalMode = function ()
96
+test.MotifDb.normalMode = function()
94 97
 {
95
-  print ('--- test.MotifDb.normalMode')
98
+  print('--- test.MotifDb.normalMode')
96 99
 
97
-  mdb = MotifDb #  (quiet=TRUE)
98
-    # (5 jun 2012)
100
+  mdb = MotifDb # (quiet=TRUE)
101
+    #(5 jun 2012)
99 102
     # JASPAR_CORE: 459
100 103
     # ScerTF: 196
101 104
     # UniPROBE: 380
102 105
     # FlyFactorSurvey: 614
103 106
     # hPDI: 437
104
-  checkTrue (length (mdb) > 2080)
107
+  checkTrue(length(mdb) > 2080)
105 108
 
106 109
 } # test.MotifDb.normalMode
107 110
 #------------------------------------------------------------------------------------------------------------------------
108 111
 # this mode is not intended for users, but may see use in the future.
109
-test.MotifDb.emptyMode = function ()
112
+test.MotifDb.emptyMode = function()
110 113
 {
111
-  print ('--- test.MotifDb.emptyMode')
114
+  print('--- test.MotifDb.emptyMode')
112 115
 
113
-  mdb = MotifDb:::.MotifDb (loadAllSources=FALSE, quiet=TRUE)
114
-  checkTrue (length (mdb) == 0)
116
+  mdb = MotifDb:::.MotifDb(loadAllSources=FALSE, quiet=TRUE)
117
+  checkTrue(length(mdb) == 0)
115 118
 
116 119
 } # test.MotifDb.emptyMode
117 120
 #------------------------------------------------------------------------------------------------------------------------
... ...
@@ -122,86 +125,86 @@ test.MotifDb.emptyMode = function ()
122 125
 
123 126
 # Many more NA's exist...need to fix these; here's a quick fix for now
124 127
 
125
-test.noNAorganisms = function ()
128
+test.noNAorganisms = function()
126 129
 
127 130
 {
128
-  print ('--- test.noNAorganisms')
129
-  #checkEquals (which (is.na (mcols(MotifDb)$organism)), integer (0))
131
+  print('--- test.noNAorganisms')
132
+  #checkEquals(which(is.na(mcols(MotifDb)$organism)), integer(0))
130 133
 
131 134
   # There's a fair number of NA organisms, mostly due to including the homer DB
132
-  checkEquals(sum(is.na (mcols(MotifDb)$organism)), 366)
135
+  checkEquals(sum(is.na(mcols(MotifDb)$organism)), 366)
133 136
 
134 137
 } # test.noNAorganisms
135 138
 #------------------------------------------------------------------------------------------------------------------------
136
-test.allMatricesAreNormalized = function ()
139
+test.allMatricesAreNormalized = function()
137 140
 {
138
-  print ('--- test.allMatricesAreNormalized')
139
-  mdb = MotifDb# (quiet=TRUE)
141
+  print('--- test.allMatricesAreNormalized')
142
+  mdb = MotifDb#(quiet=TRUE)
140 143
   matrices = mdb@listData
141 144
     # a lenient test required by "Cparvum-UniPROBE-Cgd2_3490.UP00395" and  "Hsapiens-UniPROBE-Sox4.UP00401"
142 145
     # for reasons not yet explored.  10e-8 should be be possible
143
-  checkTrue(all(sapply(matrices, function (m) all (abs (colSums (m) - 1.0) < 0.02))))
146
+  checkTrue(all(sapply(matrices, function(m) all(abs(colSums(m) - 1.0) < 0.02))))
144 147
 
145 148
 } # test.allMatricesAreNormalized
146 149
 #------------------------------------------------------------------------------------------------------------------------
147
-test.providerNames = function ()
150
+test.providerNames = function()
148 151
 {
149
-  print ('--- test.getProviderNames')
150
-  mdb = MotifDb # ()
152
+  print('--- test.getProviderNames')
153
+  mdb = MotifDb #()
151 154
   pn = mcols(mdb)$providerName
152
-  checkEquals (length (which (is.na (pn))), 0)
153
-  checkEquals (length (which (pn == '')), 0)
155
+  checkEquals(length(which(is.na(pn))), 0)
156
+  checkEquals(length(which(pn == '')), 0)
154 157
 
155 158
 } # test.providerNames
156 159
 #------------------------------------------------------------------------------------------------------------------------
157
-test.geneSymbols = function ()
160
+test.geneSymbols = function()
158 161
 {
159
-  print ('--- test.getGeneSymbols')
160
-  mdb = MotifDb # ()
162
+  print('--- test.getGeneSymbols')
163
+  mdb = MotifDb #()
161 164
   syms = mcols(mdb)$geneSymbol
162
-  checkEquals (length (which (is.na (syms))), 683)  # no symols yet for the dgf stamlab motifs
163
-  checkEquals (length (which (syms == '')), 0)
165
+  checkEquals(length(which(is.na(syms))), 683)  # no symols yet for the dgf stamlab motifs
166
+  checkEquals(length(which(syms == '')), 0)
164 167
 
165 168
 } # test.geneSymbols
166 169
 #------------------------------------------------------------------------------------------------------------------------
167
-test.geneIdsAndTypes = function ()
170
+test.geneIdsAndTypes = function()
168 171
 {
169
-  print ('--- test.getGeneIdsAndTypes')
172
+  print('--- test.getGeneIdsAndTypes')
170 173
   mdb = MotifDb
171 174
   tbl <- mcols(mdb)
172 175
   geneIds = tbl$geneId
173 176
   geneIdTypes = tbl$geneIdType
174
-  typeCounts = as.list (table (geneIdTypes))
177
+  typeCounts = as.list(table(geneIdTypes))
175 178
 
176 179
   checkTrue(typeCounts$ENTREZ > 2300)
177 180
   checkTrue(typeCounts$FLYBASE >= 45)
178 181
   checkTrue(typeCounts$SGD >= 600)
179 182
   checkTrue(nrow(subset(tbl, is.na(geneIdType))) > 2000)
180 183
 
181
-  empty.count = length (which (geneIds == ''))
182
-  checkEquals (empty.count, 0)
184
+  empty.count = length(which(geneIds == ''))
185
+  checkEquals(empty.count, 0)
183 186
 
184 187
 
185 188
 } # test.geneIdsAndTypes
186 189
 #------------------------------------------------------------------------------------------------------------------------
187 190
 # make sure that all proteinIds have explicit values, either proper identifiers or NA
188 191
 # currently tested by looking for empty string assignments
189
-test.proteinIds = function ()
192
+test.proteinIds = function()
190 193
 {
191
-  print ('--- test.proteinIds')
192
-  mdb = MotifDb # (quiet=TRUE)
194
+  print('--- test.proteinIds')
195
+  mdb = MotifDb #(quiet=TRUE)
193 196
   NA.string.count <- sum(is.na(mcols(mdb)$proteinId))
194
-#  NA.string.count = length (grep ('NA', mcols(mdb)$proteinId))
197
+#  NA.string.count = length(grep('NA', mcols(mdb)$proteinId))
195 198
 
196 199
   checkEquals(NA.string.count, 2514)
197 200
   # FIX THIS; Currently 2514 don't have protein IDs
198
-  #checkEquals (NA.string.count, 0)
201
+  #checkEquals(NA.string.count, 0)
199 202
 
200
-  empty.count = length (which (mcols(mdb)$proteinId==""))
201
-  if (empty.count > 0)
202
-    browser ('test.proteinIds')
203
+  empty.count = length(which(mcols(mdb)$proteinId==""))
204
+  if(empty.count > 0)
205
+    browser('test.proteinIds')
203 206
 
204
-  checkEquals (empty.count, 0)
207
+  checkEquals(empty.count, 0)
205 208
 
206 209
      # FlyFactorSurvey, as digested by me, had a blanket assigment of UNIPROT to all proteinIds
207 210
      # Herve' pointed out that this applied also to entries with no proteinId.
... ...
@@ -209,86 +212,88 @@ test.proteinIds = function ()
209 212
 
210 213
   ### FIX THIS TOO! Currently have 913 entries with a proteinIdType and no proteinId
211 214
   x = mcols(mdb)
212
-  # checkEquals (nrow (subset (x, !is.na (proteinIdType) & is.na (proteinId))), 0)
215
+  # checkEquals(nrow(subset(x, !is.na(proteinIdType) & is.na(proteinId))), 0)
213 216
 
214 217
 
215 218
 } # test.proteinIds
216 219
 #------------------------------------------------------------------------------------------------------------------------
217 220
 # only for UniPROBE do we not have sequence count.  might be possible to get them along with 'insertion sequences'
218
-test.sequenceCount = function ()
221
+test.sequenceCount = function()
219 222
 {
220
-  print ('--- test.sequenceCount')
221
-  mdb = MotifDb # ()
223
+  print('--- test.sequenceCount')
224
+  mdb = MotifDb #()
222 225
   x = mcols(mdb)
223
-  if (interactive ()) {
224
-    x.up = subset (x, dataSource == 'UniPROBE')
225
-    checkTrue (all (is.na (x.up$sequenceCount)))
226
+  if(interactive()) {
227
+    x.up = subset(x, dataSource == 'UniPROBE')
228
+    checkTrue(all(is.na(x.up$sequenceCount)))
226 229
     }
227 230
   else {
228
-    uniprobe.indices = which (x$dataSource == 'UniPROBE')
229
-    checkTrue (all (is.na (x$sequenceCount [uniprobe.indices])))
231
+    uniprobe.indices = which(x$dataSource == 'UniPROBE')
232
+    checkTrue(all(is.na(x$sequenceCount [uniprobe.indices])))
230 233
     }
231 234
 
232 235
 } # test.sequenceCount
233 236
 #------------------------------------------------------------------------------------------------------------------------
234 237
 # make sure that a legitimate organism-dataSource-identifier is supplied for each matrix and as a rowname
235 238
 # of the corresponding DataFrame
236
-test.longNames = function ()
239
+test.longNames = function()
237 240
 {
238
-  print ('--- test.longNames')
241
+  print('--- test.longNames')
239 242
   mdb = MotifDb
240
-  longNames = strsplit (names (mdb), '-')
241
-  organisms = unique (sapply (longNames, '[', 1))
243
+  longNames = strsplit(names(mdb), '-')
244
+  organisms = unique(sapply(longNames, '[', 1))
242 245
 
243
-  dataSources = unique (lapply (longNames, '[', 2))
246
+  dataSources = unique(lapply(longNames, '[', 2))
244 247
 
245
-  recognized.dataSources = unique (mcols(mdb)$dataSource)
246
-  recognized.organisms = unique (mcols(mdb)$organism)
247
-    # a few (3) matrices from JASPAR core have NA organism.  make this into a character
248
+  recognized.dataSources = c(unique(mcols(mdb)$dataSource),
249
+                             c("HOCOMOCOv11B", "HOCOMOCOv11C", "HOCOMOCOv11A"))
250
+
251
+  recognized.organisms = unique(mcols(mdb)$organism)
252
+    # a few(3) matrices from JASPAR core have NA organism.  make this into a character
248 253
     # so that it can be matched up against the 'NA' extracted from longNames just above
249
-  na.indices = which (is.na (recognized.organisms))
250
-  if (length (na.indices) > 0)
254
+  na.indices = which(is.na(recognized.organisms))
255
+  if(length(na.indices) > 0)
251 256
      recognized.organisms [na.indices] = 'NA'
252 257
 
253
-  checkTrue (all (organisms %in% recognized.organisms))
254
-  checkTrue (all (dataSources %in% recognized.dataSources))
258
+  checkTrue(all(organisms %in% recognized.organisms))
259
+  checkTrue(all(dataSources %in% recognized.dataSources))
255 260
 
256 261
 } # test.longNames
257 262
 #------------------------------------------------------------------------------------------------------------------------
258 263
 # make sure that a legitimate organism is specified for each matrix
259
-test.organisms = function ()
264
+test.organisms = function()
260 265
 {
261
-  print ('--- test.organisms')
262
-  mdb = MotifDb # (quiet=TRUE)
266
+  print('--- test.organisms')
267
+  mdb = MotifDb #(quiet=TRUE)
263 268
   organisms = mcols(mdb)$organism
264 269
 
265
-     # jaspar_core has 3 NA speciesId: TBP, HNF4A and CEBPA (MA0108.2, MA0114.1, MA0102.2)
270
+     # jaspar_core has 3 NA speciesId: TBP, HNF4A and CEBPA(MA0108.2, MA0114.1, MA0102.2)
266 271
      # their website shows these as vertebrates, which I map to 'Vertebrata'.  An organismID of '-'
267 272
   # gets the same treatment, matching website also.
268 273
 
269 274
   ### Note: this failing test is the same as the test.noNAorganisms test!
270 275
   # As in case of noNA, need to add organisms for these
271
-  #checkEquals (which (is.na (mcols(MotifDb)$organism)), integer (0))
276
+  #checkEquals(which(is.na(mcols(MotifDb)$organism)), integer(0))
272 277
 
273
-  empty.count = length (which (mcols(mdb)$organism==""))
274
-  checkEquals (empty.count, 0)
278
+  empty.count = length(which(mcols(mdb)$organism==""))
279
+  checkEquals(empty.count, 0)
275 280
 
276 281
 } # test.organisms
277 282
 #------------------------------------------------------------------------------------------------------------------------
278
-test.bindingDomains = function ()
283
+test.bindingDomains = function()
279 284
 {
280
-  print ('--- test.bindingDomains')
281
-  mdb = MotifDb # (quiet=TRUE)
282
-  checkTrue (length (unique (mcols(mdb)$bindingDomain)) > 1)
285
+  print('--- test.bindingDomains')
286
+  mdb = MotifDb #(quiet=TRUE)
287
+  checkTrue(length(unique(mcols(mdb)$bindingDomain)) > 1)
283 288
 
284 289
 } # test.bindingDomains
285 290
 #------------------------------------------------------------------------------------------------------------------------
286
-test.flyBindingDomains = function ()
291
+test.flyBindingDomains = function()
287 292
 {
288
-  print ('--- test.flyBindingDomains')
293
+  print('--- test.flyBindingDomains')
289 294
 
290 295
   x = mcols(MotifDb)
291
-  tmp = as.list (head (sort (table (subset (x, organism=='Dmelanogaster')$bindingDomain), decreasing=TRUE), n=3))
296
+  tmp = as.list(head(sort(table(subset(x, organism=='Dmelanogaster')$bindingDomain), decreasing=TRUE), n=3))
292 297
 
293 298
     # these counts will likely change with a fresh load of data from FlyFactorSurvey.
294 299
 
... ...
@@ -299,38 +304,38 @@ test.flyBindingDomains = function ()
299 304
 
300 305
 } # test.flyBindingDomains
301 306
 #------------------------------------------------------------------------------------------------------------------------
302
-test.experimentTypes = function ()
307
+test.experimentTypes = function()
303 308
 {
304
-  print ('--- test.experimentTypes')
305
-  mdb = MotifDb # (quiet=TRUE)
309
+  print('--- test.experimentTypes')
310
+  mdb = MotifDb #(quiet=TRUE)
306 311
   x = mcols(mdb)
307
-  checkTrue (length (unique (x$experimentType)) >= 18)
308
-  checkEquals (length (which (x$experimentType=='')), 0)
312
+  checkTrue(length(unique(x$experimentType)) >= 18)
313
+  checkEquals(length(which(x$experimentType=='')), 0)
309 314
 
310 315
 } # test.experimentTypes
311 316
 #------------------------------------------------------------------------------------------------------------------------
312
-test.tfFamilies = function ()
317
+test.tfFamilies = function()
313 318
 {
314