Skip to content

Commit

Permalink
support geneSim for MPO
Browse files Browse the repository at this point in the history
  • Loading branch information
huerqiang committed Apr 10, 2023
1 parent 93df863 commit 00c21e6
Show file tree
Hide file tree
Showing 5 changed files with 20 additions and 9 deletions.
2 changes: 1 addition & 1 deletion R/DOSE-package.R
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ NULL
#'
#' @name DataSet
#' @aliases EG2DO DO2EG EG2ALLDO DO2ALLEG DOIC dotbl
#' EG2DOLite DOLite2EG DOLiteTerm geneList
#' mpotbl EG2DOLite DOLite2EG DOLiteTerm geneList
#' NCG_EXTID2PATHID NCG_PATHID2EXTID NCG_PATHID2NAME
#' DGN_EXTID2PATHID DGN_PATHID2EXTID DGN_PATHID2NAME
#' VDGN_EXTID2PATHID VDGN_PATHID2EXTID VDGN_PATHID2NAME
Expand Down
4 changes: 2 additions & 2 deletions R/geneSim.R
Original file line number Diff line number Diff line change
Expand Up @@ -22,12 +22,12 @@ geneSim <- function(geneID1,
combine="BMA") {


DOID1 <- lapply(geneID1, gene2DO, organism = organism)
DOID1 <- lapply(geneID1, gene2DO, organism = organism, ont = ont)
if (is.null(geneID2)) {
geneID2 <- geneID1
DOID2 <- DOID1
} else {
DOID2 <- lapply(geneID2, gene2DO, organism = organism)
DOID2 <- lapply(geneID2, gene2DO, organism = organism, ont = ont)
}

m <- length(geneID1)
Expand Down
18 changes: 13 additions & 5 deletions R/utilities.R
Original file line number Diff line number Diff line change
Expand Up @@ -169,12 +169,13 @@ computeIC <- function(ont="DO"){
##' @title convert Gene ID to DO Terms
##' @param gene entrez gene ID
##' @param organism organism
##' @param ont ont
##' @return DO Terms
##' @importMethodsFrom AnnotationDbi get
##' @importMethodsFrom AnnotationDbi exists
##' @export
##' @author Guangchuang Yu \url{http://guangchuangyu.github.io}
gene2DO <- function(gene, organism = "hsa") {
gene2DO <- function(gene, organism = "hsa", ont = "DO") {
gene <- as.character(gene)
if (organism == "hsa") {
if(!exists(".DOSEEnv")) .initial()
Expand All @@ -187,13 +188,20 @@ gene2DO <- function(gene, organism = "hsa") {
}
EG2DO <- get("EG2DO", envir=.DOSEEnv)
} else {
eg.do <- toTable(MPOMPMGI)[, c(2,1)]
colnames(eg.do) <- c("eg", "doid")
MPOTERMs <- names(as.list(MPOANCESTOR))
if (ont == "DO") {
eg.do <- toTable(MPOMGIDO)
colnames(eg.do) <- c("eg", "doid")
MPOTERMs <- names(as.list(HDOANCESTOR))
} else {
eg.do <- toTable(MPOMPMGI)[, c(2,1)]
colnames(eg.do) <- c("eg", "doid")
MPOTERMs <- names(as.list(MPOANCESTOR))
}
EG2DO <- with(eg.do, split(as.character(doid), as.character(eg)))
EG2DO <- lapply(EG2DO, function(i) unique(i[ i %in% MPOTERMs ]))
i <- unlist(lapply(EG2DO, function(i) length(i) != 0))
EG2DO <- EG2DO[i]
EG2DO <- EG2DO[i]

}

DO <- EG2DO[[gene]]
Expand Down
1 change: 1 addition & 0 deletions man/DataSet.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

4 changes: 3 additions & 1 deletion man/gene2DO.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

0 comments on commit 00c21e6

Please sign in to comment.