... | ... |
@@ -1,11 +1,11 @@ |
1 | 1 |
Package: MotifDb |
2 | 2 |
Type: Package |
3 | 3 |
Title: An Annotated Collection of Protein-DNA Binding Sequence Motifs |
4 |
-Version: 1.23.8 |
|
4 |
+Version: 1.23.9 |
|
5 | 5 |
Date: 2018-05-23 |
6 | 6 |
Author: Paul Shannon, Matt Richards |
7 | 7 |
Maintainer: Paul Shannon <pshannon@systemsbiology.org> |
8 |
-Depends: R (>= 2.15.0), methods, BiocGenerics, S4Vectors, IRanges, Biostrings |
|
8 |
+Depends: R (>= 2.15.0), methods, BiocGenerics, S4Vectors, IRanges, Biostrings, motifStack |
|
9 | 9 |
Suggests: RUnit, seqLogo, MotIV |
10 | 10 |
Imports: rtracklayer, splitstackshape |
11 | 11 |
Description: More than 9900 annotated position frequency matrices from 14 public sources, for multiple organisms. |
... | ... |
@@ -491,7 +491,7 @@ setMethod ('geneToMotif', 'MotifList', |
491 | 491 |
|
492 | 492 |
function (object, geneSymbols, source, ignore.case=FALSE) { |
493 | 493 |
source <- tolower(source) |
494 |
- stopifnot(source %in% c("motifdb", "tfclass")) |
|
494 |
+ stopifnot(all(source %in% c("motifdb", "tfclass"))) |
|
495 | 495 |
extract.mdb <- function(gene){ |
496 | 496 |
geneSymbol <- NULL # workaround the R CMD check "no visible binding for global variable" |
497 | 497 |
if(ignore.case) |
... | ... |
@@ -503,13 +503,13 @@ setMethod ('geneToMotif', 'MotifList', |
503 | 503 |
colnames(tbl) <- c("geneSymbol", "motif", "dataSource", "organism", "pubmedID") |
504 | 504 |
tbl |
505 | 505 |
} |
506 |
- if(source %in% c("motifdb")){ |
|
506 |
+ if("motifdb" %in% source){ |
|
507 | 507 |
tbls <- lapply(geneSymbols, extract.mdb) |
508 | 508 |
result <- do.call(rbind, tbls) |
509 | 509 |
if(nrow(result) > 0) |
510 | 510 |
result$source <- "MotifDb" |
511 | 511 |
} |
512 |
- if(source %in% c("tfclass")){ |
|
512 |
+ if("tfclass" %in% source){ |
|
513 | 513 |
if(ignore.case) |
514 | 514 |
tbl <- subset(object@manuallyCuratedGeneMotifAssociationTable, tolower(tf.gene) %in% tolower(geneSymbols)) |
515 | 515 |
else |
516 | 516 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,15 @@ |
1 |
+#------------------------------------------------------------------------------------------------------------------------ |
|
2 |
+plotMotifs <- function(motifs) |
|
3 |
+{ |
|
4 |
+ stopifnot(length(motifs) > 0) |
|
5 |
+ |
|
6 |
+ if(length(motifs) == 1){ |
|
7 |
+ pcm <- new("pcm", mat=motifs[[1]], name=names(motifs)) |
|
8 |
+ plot(pcm) |
|
9 |
+ } |
|
10 |
+ |
|
11 |
+ motifStack(lapply(names(motifs), function(mName) new("pfm", motifs[[mName]], name=mName))) |
|
12 |
+ |
|
13 |
+} # plotMotifs |
|
14 |
+#------------------------------------------------------------------------------------------------------------------------ |
|
15 |
+ |
... | ... |
@@ -1070,3 +1070,5 @@ findMotifsWithMutuallyExclusiveMappings <- function() |
1070 | 1070 |
|
1071 | 1071 |
} # findMotifsWithMutuallyExclusiveMappings |
1072 | 1072 |
#------------------------------------------------------------------------------------------------------------------------ |
1073 |
+if(!interactive()) |
|
1074 |
+ runTests() |