...
|
...
|
@@ -650,7 +650,7 @@ test.MotIV.toTable = function ()
|
650
|
650
|
test.hits = motifMatch (mdb[1]@listData, database=jaspar)
|
651
|
651
|
tbl.hits = MotIV.toTable (test.hits)
|
652
|
652
|
checkEquals (dim (tbl.hits), c (5, 5))
|
653
|
|
- checkEquals (colnames (tbl.hits), c ("name", "eVal", "sequence", "match", "strand"))
|
|
653
|
+ checkEquals (sort(colnames (tbl.hits)), sort(c("name", "eVal", "sequence", "match", "strand")))
|
654
|
654
|
|
655
|
655
|
} # test.MotIV.toTable
|
656
|
656
|
#------------------------------------------------------------------------------------------------------------------------
|
...
|
...
|
@@ -713,8 +713,8 @@ test.flyFactorGeneSymbols <- function()
|
713
|
713
|
{
|
714
|
714
|
print ("--- test.flyFactorGeneSymbols")
|
715
|
715
|
mdb = MotifDb
|
716
|
|
- checkEquals(mcols(query(mdb, "FBgn0259750"))$geneSymbol,
|
717
|
|
- c("FBgn0259750", "FBgn0259750"))
|
|
716
|
+ checkEquals(sort(mcols(query(mdb, "FBgn0259750"))$geneSymbol),
|
|
717
|
+ sort(c("FBgn0259750", "FBgn0259750")))
|
718
|
718
|
checkEquals(mcols(query(mdb, "FBgn0000014"))$geneSymbol, rep("abd-A", 3))
|
719
|
719
|
checkEquals(mcols(query(mdb, "FBgn0000015"))$geneSymbol, rep("Abd-B", 3))
|
720
|
720
|
|
...
|
...
|
@@ -760,8 +760,8 @@ test.geneToMotif <- function()
|
760
|
760
|
|
761
|
761
|
# use TFClass family classifcation
|
762
|
762
|
tbl.tfClass <- geneToMotif(mdb, genes, source="TfClaSS") # intentional mis-capitalization
|
763
|
|
- checkEquals(tbl.tfClass$gene, c("ATF5", "FOS", "FOS"))
|
764
|
|
- checkEquals(tbl.tfClass$motif, c("MA0833.1", "MA0099.2", "MA0476.1"))
|
|
763
|
+ checkEquals(sort(tbl.tfClass$gene), sort(c("ATF5", "FOS", "FOS")))
|
|
764
|
+ checkEquals(sort(tbl.tfClass$motif), sort(c("MA0833.1", "MA0099.2", "MA0476.1")))
|
765
|
765
|
checkEquals(tbl.tfClass$source, rep("TFClass", 3))
|
766
|
766
|
|
767
|
767
|
# MotifDb mode uses the MotifDb metadata, pulled from many sources
|
...
|
...
|
@@ -786,26 +786,17 @@ test.motifToGene <- function()
|
786
|
786
|
checkEquals(dim(tbl.mdb), c(3, 6))
|
787
|
787
|
expected <- sort(c("MA0592.2", "ELF1.SwissRegulon", "UP00022"))
|
788
|
788
|
actual <- sort(tbl.mdb$motif)
|
789
|
|
-
|
790
|
|
- print("--- expected")
|
791
|
|
- print(expected)
|
792
|
|
- print(lapply(expected, charToRaw))
|
793
|
|
-
|
794
|
|
- print("--- actual")
|
795
|
|
- print(actual)
|
796
|
|
- print(lapply(actual, charToRaw))
|
797
|
|
-
|
798
|
789
|
checkEquals(actual, expected)
|
799
|
|
- checkEquals(tbl.mdb$geneSymbol, c("Esrra", "ELF1", "Zfp740"))
|
800
|
|
- checkEquals(tbl.mdb$dataSource, c("jaspar2016", "SwissRegulon", "UniPROBE"))
|
801
|
|
- checkEquals(tbl.mdb$organism, c("Mmusculus", "Hsapiens", "Mmusculus"))
|
802
|
|
- checkEquals(tbl.mdb$source, rep("MotifDb", 3))
|
|
790
|
+ checkEquals(sort(tbl.mdb$geneSymbol), sort(c("Esrra", "ELF1", "Zfp740")))
|
|
791
|
+ checkEquals(sort(tbl.mdb$dataSource), sort(c("jaspar2016", "SwissRegulon", "UniPROBE")))
|
|
792
|
+ checkEquals(sort(tbl.mdb$organism), sort(c("Mmusculus", "Hsapiens", "Mmusculus")))
|
|
793
|
+ checkEquals(sort(tbl.mdb$source), rep("MotifDb", 3))
|
803
|
794
|
|
804
|
795
|
# TFClass mode uses TF family classifcation
|
805
|
796
|
tbl.tfClass <- motifToGene(MotifDb, motifs, source="TFClass")
|
806
|
797
|
checkEquals(dim(tbl.tfClass), c(9,4))
|
807
|
798
|
checkEquals(tbl.tfClass$motif, rep("MA0592.2", 9))
|
808
|
|
- checkEquals(sort(tbl.tfClass$gene), c("AR", "ESR1", "ESR2", "ESRRA", "ESRRB", "ESRRG", "NR3C1", "NR3C2", "PGR"))
|
|
799
|
+ checkEquals(sort(tbl.tfClass$gene), sort(c("AR", "ESR1", "ESR2", "ESRRA", "ESRRB", "ESRRG", "NR3C1", "NR3C2", "PGR")))
|
809
|
800
|
checkEquals(tbl.tfClass$source, rep("TFClass", 9))
|
810
|
801
|
|
811
|
802
|
# test motifs with regex characters in them, or other characters neither letter nor number
|
...
|
...
|
@@ -837,7 +828,7 @@ test.associateTranscriptionFactors <- function()
|
837
|
828
|
tbl.anno <- associateTranscriptionFactors(mdb, tbl, source="MotifDb", expand.rows=FALSE)
|
838
|
829
|
checkEquals(dim(tbl.anno), c(nrow(tbl), ncol(tbl) + 2))
|
839
|
830
|
checkTrue(all(c("geneSymbol", "pubmedID") %in% colnames(tbl.anno)))
|
840
|
|
- checkEquals(tbl.anno$geneSymbol, c("RUNX1", "TFAP2A", "TFAP2A", "TFAP2A", "AR"))
|
|
831
|
+ checkEquals(sort(tbl.anno$geneSymbol), sort(c("RUNX1", "TFAP2A", "TFAP2A", "TFAP2A", "AR")))
|
841
|
832
|
|
842
|
833
|
# now add in a bogus motif name, one for which there cannot possibly be a TF
|
843
|
834
|
|