diff --git a/NAMESPACE b/NAMESPACE index 6e305f41f..f02408886 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -99,6 +99,7 @@ export(unsplitOn) exportMethods("relabundance<-") exportMethods(ZTransform) exportMethods(addContaminantQC) +exportMethods(addHierarchyTree) exportMethods(addNotContaminantQC) exportMethods(addPerSampleDominantFeatures) exportMethods(addPerSampleDominantTaxa) @@ -130,6 +131,7 @@ exportMethods(getBestDMNFit) exportMethods(getDMN) exportMethods(getExperimentCrossAssociation) exportMethods(getExperimentCrossCorrelation) +exportMethods(getHierarchyTree) exportMethods(getPrevalence) exportMethods(getPrevalentAbundance) exportMethods(getPrevalentFeatures) diff --git a/NEWS b/NEWS index 5972ab843..4bae25012 100644 --- a/NEWS +++ b/NEWS @@ -97,6 +97,7 @@ Changes in version 1.9.x Changes in version 1.11.x + loadFromMetaphlan: support strain rank + agglomerateByRank: agglomerate tree fix ++ Replace taxonomyTree and addTaxonomyTree with getHierarchyTree and addHierarchyTree + splitOn: update rowTree fix + perSampleDominantFeatures: add new arguments (n, other.name, complete) + loadFromMetaphlan: support "taxonomy" column for specifying taxonomy diff --git a/R/deprecate.R b/R/deprecate.R new file mode 100644 index 000000000..c2cbce75c --- /dev/null +++ b/R/deprecate.R @@ -0,0 +1,40 @@ +#' These functions will be deprecated. Please use other functions instead. +#' +#' @param x a \code{\link{SummarizedExperiment}} object - +#' +#' @param ... - +#' +#' @name deprecate +NULL + +#' @rdname deprecate +setGeneric("addTaxonomyTree", + signature = "x", + function(x, ...) + standardGeneric("addTaxonomyTree")) + +#' @rdname deprecate +#' @export +setMethod("addTaxonomyTree", signature = c(x = "SummarizedExperiment"), + function(x){ + .Deprecated(msg = paste0("'addTaxonomyTree' is deprecated.", + "Use 'addHierarchyTree' instead.")) + addHierarchyTree(x) + } +) + +#' @rdname deprecate +setGeneric("taxonomyTree", + signature = "x", + function(x, ...) + standardGeneric("taxonomyTree")) + +#' @rdname deprecate +#' @export +setMethod("taxonomyTree", signature = c(x = "SummarizedExperiment"), + function(x){ + .Deprecated(msg = paste0("'taxonomyTree' is deprecated.", + "Use 'getHierarchyTree' instead.")) + getHierarchyTree(x) + } +) diff --git a/R/splitOn.R b/R/splitOn.R index b0dfc1198..7464d0bdb 100644 --- a/R/splitOn.R +++ b/R/splitOn.R @@ -97,9 +97,9 @@ NULL #' @rdname splitOn #' @export setGeneric("splitOn", - signature = "x", - function(x, ...) - standardGeneric("splitOn")) + signature = "x", + function(x, ...) + standardGeneric("splitOn")) # This function collects f (grouping variable), MARGIN, and # use_names and returns them as a list. @@ -108,8 +108,8 @@ setGeneric("splitOn", # Check f if(is.null(f)){ stop("'f' must either be a single non-empty character value or", - " vector coercible to factor alongside the one of the dimensions of 'x'", - call. = FALSE) + " vector coercible to factor alongside the one of the dimensions of 'x'", + call. = FALSE) } # Check MARGIN if( !(is.null(MARGIN) || (is.numeric(MARGIN) && (MARGIN == 1 || MARGIN == 2 ))) ){ @@ -122,18 +122,18 @@ setGeneric("splitOn", # Check if the length of f matches with one of the dimensions if(!length(f) %in% dim(x)){ stop("'f' must either be a single non-empty character value or", - " vector coercible to factor alongside the on of the ", - "dimensions of 'x'.", - call. = FALSE) + " vector coercible to factor alongside the on of the ", + "dimensions of 'x'.", + call. = FALSE) # If it matches with both dimensions, give error if MARGIN is not specified } else if( is.null(MARGIN) && all(length(f) == dim(x)) ){ stop("The length of 'f' matches with nrow and ncol. ", - "Please specify 'MARGIN'.", call. = FALSE) + "Please specify 'MARGIN'.", call. = FALSE) # If MARGIN is specified but it does not match with length of f } else if( !is.null(MARGIN) && (length(f) != dim(x)[[MARGIN]]) ){ stop("'f' does not match with ", - ifelse(MARGIN==1, "nrow", "ncol"), ". Please check 'MARGIN'.", - call. = FALSE) + ifelse(MARGIN==1, "nrow", "ncol"), ". Please check 'MARGIN'.", + call. = FALSE) # IF f matches with nrow } else if(length(f) == dim(x)[[1]] && is.null(MARGIN) ){ MARGIN <- 1L @@ -147,20 +147,20 @@ setGeneric("splitOn", if( !is.null(MARGIN) ){ # Search from rowData or colData based on MARGIN dim_name <- switch(MARGIN, - "1" = "rowData", - "2" = "colData") + "1" = "rowData", + "2" = "colData") # Specify right function dim_FUN <- switch(MARGIN, - "1" = retrieveFeatureInfo, - "2" = retrieveCellInfo) + "1" = retrieveFeatureInfo, + "2" = retrieveCellInfo) # Try to get information tmp <- try({dim_FUN(x, f, search = dim_name)}, - silent = TRUE) + silent = TRUE) # Give error if it cannot be found if(is(tmp,"try-error")){ stop("'f' is not found. ", - "Please check that 'f' specifies a column from ", dim_name, ".", - call. = FALSE) + "Please check that 'f' specifies a column from ", dim_name, ".", + call. = FALSE) } # Get values f <- tmp$value @@ -168,22 +168,22 @@ setGeneric("splitOn", } else{ # Try to get information from rowData tmp_row <- try({retrieveFeatureInfo(x, f, search = "rowData")}, - silent = TRUE) + silent = TRUE) # Try to get information from colData tmp_col <- try({retrieveCellInfo(x, f, search = "colData")}, - silent = TRUE) + silent = TRUE) # If it was not found if( is(tmp_row, "try-error") && is(tmp_col, "try-error") ){ stop("'f' is not found. ", - "Please check that 'f' specifies a column from ", - "rowData or colData.", - call. = FALSE) + "Please check that 'f' specifies a column from ", + "rowData or colData.", + call. = FALSE) # If f was found from both } else if( !is(tmp_row, "try-error") && !is(tmp_col, "try-error") ){ stop("'f' can be found from both rowData and colData. ", - "Please specify 'MARGIN'.", - call. = FALSE) + "Please specify 'MARGIN'.", + call. = FALSE) # If it was found from rowData } else if( !is(tmp_row, "try-error") ){ MARGIN <- 1L @@ -207,12 +207,12 @@ setGeneric("splitOn", # Check use_names if( !.is_a_bool(use_names) ){ stop("'use_names' must be TRUE or FALSE.", - call. = FALSE) + call. = FALSE) } # Create a list from arguments list(f = f, - MARGIN = MARGIN, - use_names = use_names) + MARGIN = MARGIN, + use_names = use_names) } # PErform the split @@ -221,8 +221,8 @@ setGeneric("splitOn", f <- args[["f"]] # Choose nrow or ncol based on MARGIN dim_FUN <- switch(args[["MARGIN"]], - "1" = nrow, - "2" = ncol) + "1" = nrow, + "2" = ncol) # Get indices from 1 to nrow/ncol idx <- seq_len(dim_FUN(x)) # Split indices into groups based on grouping variable @@ -276,12 +276,12 @@ setMethod("splitOn", signature = c(x = "SingleCellExperiment"), #' @export setMethod("splitOn", signature = c(x = "TreeSummarizedExperiment"), function(x, f = NULL, update_rowTree = FALSE, - ...){ + ...){ # Input check # Check update_rowTree if( !.is_a_bool(update_rowTree) ){ stop("'update_rowTree' must be TRUE or FALSE.", - call. = FALSE) + call. = FALSE) } # Input check end # Split data @@ -289,7 +289,7 @@ setMethod("splitOn", signature = c(x = "TreeSummarizedExperiment"), # Manipulate rowTree or not? if( update_rowTree ){ # If the returned value is a list, go through all of them - if( class(x) == "SimpleList" ){ + if( is(x, 'SimpleList') ){ x <- SimpleList(lapply(x, .agglomerate_trees)) } else { # Otherwise, the returned value is TreeSE @@ -306,9 +306,9 @@ setMethod("splitOn", signature = c(x = "TreeSummarizedExperiment"), #' @rdname splitOn #' @export setGeneric("unsplitOn", - signature = c("x"), - function(x, ...) - standardGeneric("unsplitOn")) + signature = c("x"), + function(x, ...) + standardGeneric("unsplitOn")) # Perform the unsplit .list_unsplit_on <- function(ses, update_rowTree = FALSE, MARGIN = NULL, ...){ @@ -316,13 +316,13 @@ setGeneric("unsplitOn", is_check <- vapply(ses,is,logical(1L),"SummarizedExperiment") if(!all(is_check)){ stop("Input must be a list of SummarizedExperiment or derived objects ", - "only.", - call. = FALSE) + "only.", + call. = FALSE) } # Check update_rowTree if( !.is_a_bool(update_rowTree) ){ stop("'update_rowTree' must be TRUE or FALSE.", - call. = FALSE) + call. = FALSE) } if( !(is.null(MARGIN) || (is.numeric(MARGIN) && (MARGIN == 1 || MARGIN == 2 ))) ){ stop("'MARGIN' must be NULL, 1, or 2.", call. = FALSE ) @@ -339,15 +339,15 @@ setGeneric("unsplitOn", if( is.null(MARGIN) ){ if( length(unique(dims[1L,])) == 1 && length(unique(dims[2L,])) == 1 ){ stop("The dimensions match with row and column-wise. ", - "Please specify 'MARGIN'.", call. = FALSE) + "Please specify 'MARGIN'.", call. = FALSE) } else if(length(unique(dims[1L,])) == 1L){ MARGIN <- 2L } else if(length(unique(dims[2L,])) == 1L) { MARGIN <- 1L } else { stop("The dimensions are not equal across all elements. ", - "Please check that either number of rows or columns match.", - call. = FALSE) + "Please check that either number of rows or columns match.", + call. = FALSE) } } else{ # Get correct dimension, it is opposite of MARGIN @@ -386,7 +386,7 @@ setGeneric("unsplitOn", if( class_x == "TreeSummarizedExperiment" ){ # Update or add old tree from the first element of list if( update_rowTree ){ - ans <- addTaxonomyTree(ans) + ans <- addHierarchyTree(ans) } else{ rowTree(ans) <- rowTree(ses[[1L]]) } diff --git a/R/taxonomy.R b/R/taxonomy.R index 0f70f1e8f..cc8d473c1 100644 --- a/R/taxonomy.R +++ b/R/taxonomy.R @@ -18,12 +18,6 @@ #' the lowest taxonomic information possible. If data from different levels, #' is to be mixed, the taxonomic level is prepended by default. #' -#' \code{taxonomyTree} generates a \code{phylo} tree object from the available -#' taxonomic information. Internally it uses -#' \code{\link[TreeSummarizedExperiment:toTree]{toTree}} and -#' \code{\link[TreeSummarizedExperiment:resolveLoop]{resolveLoop}} to sanitize -#' data if needed. -#' #' \code{IdTaxaToDataFrame} extracts taxonomic results from results of #' \code{\link[DECIPHER:IdTaxa]{IdTaxa}}. #' @@ -40,11 +34,11 @@ #' object #' #' @param rank a single character defining a taxonomic rank. Must be a value of -#' \code{taxonomyRanks()} function. +#' \code{taxonomyRanks()} function #' #' @param empty.fields a \code{character} value defining, which values should be #' regarded as empty. (Default: \code{c(NA, "", " ", "\t")}). They will be -#' removed if \code{na.rm = TRUE} before agglomeration. +#' removed if \code{na.rm = TRUE} before agglomeration #' #' @param with_rank \code{TRUE} or \code{FALSE}: Should the level be add as a #' suffix? For example: "Phylum:Crenarchaeota" (default: @@ -122,12 +116,6 @@ #' mapTaxonomy(GlobalPatterns, taxa = "Escherichia") #' # returns information on a single output #' mapTaxonomy(GlobalPatterns, taxa = "Escherichia",to="Family") -#' -#' # adding a rowTree() based on the available taxonomic information. Please -#' # note that any tree already stored in rowTree() will be overwritten. -#' x <- GlobalPatterns -#' x <- addTaxonomyTree(x) -#' x NULL #' @rdname taxonomy-methods @@ -139,8 +127,8 @@ TAXONOMY_RANKS <- c("domain","kingdom","phylum","class","order","family", #' @rdname taxonomy-methods setGeneric("taxonomyRanks", signature = c("x"), - function(x) - standardGeneric("taxonomyRanks")) + function(x) + standardGeneric("taxonomyRanks")) #' @rdname taxonomy-methods #' @@ -156,10 +144,10 @@ setMethod("taxonomyRanks", signature = c(x = "SummarizedExperiment"), #' @rdname taxonomy-methods setGeneric("taxonomyRankEmpty", - signature = "x", - function(x, rank = taxonomyRanks(x)[1L], + signature = "x", + function(x, rank = taxonomyRanks(x)[1L], empty.fields = c(NA, "", " ", "\t", "-", "_")) - standardGeneric("taxonomyRankEmpty")) + standardGeneric("taxonomyRankEmpty")) #' @rdname taxonomy-methods #' @aliases taxonomyRankEmpty @@ -169,18 +157,18 @@ setGeneric("taxonomyRankEmpty", #' @export setMethod("taxonomyRankEmpty", signature = c(x = "SummarizedExperiment"), function(x, rank = taxonomyRanks(x)[1], - empty.fields = c(NA, "", " ", "\t", "-", "_")){ + empty.fields = c(NA, "", " ", "\t", "-", "_")){ # input check if(ncol(rowData(x)) == 0L){ stop("rowData needs to be populated.", call. = FALSE) } if(!.is_non_empty_string(rank)){ stop("'rank' must be an non empty single character value.", - call. = FALSE) + call. = FALSE) } if(!is.character(empty.fields) || length(empty.fields) == 0L){ stop("'empty.fields' must be a character vector with one or ", - "more value", call. = FALSE) + "more value", call. = FALSE) } .check_taxonomic_rank(rank, x) .check_for_taxonomic_data_order(x) @@ -191,9 +179,9 @@ setMethod("taxonomyRankEmpty", signature = c(x = "SummarizedExperiment"), #' @rdname taxonomy-methods setGeneric("checkTaxonomy", - signature = "x", - function(x, ...) - standardGeneric("checkTaxonomy")) + signature = "x", + function(x, ...) + standardGeneric("checkTaxonomy")) #' @rdname taxonomy-methods #' @aliases checkTaxonomy @@ -232,8 +220,8 @@ setMethod("checkTaxonomy", signature = c(x = "SummarizedExperiment"), f <- tolower(ranks) %in% TAXONOMY_RANKS if(!any(f)){ stop("no taxonomic ranks detected in rowData(). Columns with one of ", - "the following names can be used: '", - paste(TAXONOMY_RANKS, collapse = "', '"), "'", call. = FALSE) + "the following names can be used: '", + paste(TAXONOMY_RANKS, collapse = "', '"), "'", call. = FALSE) } m <- match(TAXONOMY_RANKS, tolower(ranks[f])) m <- m[!is.na(m)] @@ -242,25 +230,25 @@ setMethod("checkTaxonomy", signature = c(x = "SummarizedExperiment"), check <- unique(c(m[-1], m[length(m)]) - m ) if(!all(check %in% c(1L,0L))){ stop("Taxonomic ranks are not in order. Please reorder columns, which ", - "correspond to taxonomic ranks like this:\n'", - paste(TAXONOMY_RANKS, collapse = "', '"), "'.", - call. = FALSE) + "correspond to taxonomic ranks like this:\n'", + paste(TAXONOMY_RANKS, collapse = "', '"), "'.", + call. = FALSE) } } #' @rdname taxonomy-methods setGeneric("getTaxonomyLabels", - signature = "x", - function(x, ...) - standardGeneric("getTaxonomyLabels")) + signature = "x", + function(x, ...) + standardGeneric("getTaxonomyLabels")) #' @rdname taxonomy-methods #' @aliases checkTaxonomy #' @export setMethod("getTaxonomyLabels", signature = c(x = "SummarizedExperiment"), function(x, empty.fields = c(NA, "", " ", "\t", "-", "_"), - with_rank = FALSE, make_unique = TRUE, resolve_loops = FALSE, ...){ + with_rank = FALSE, make_unique = TRUE, resolve_loops = FALSE, ...){ # input check if(nrow(x) == 0L){ stop("No data available in `x` ('x' has nrow(x) == 0L.)", @@ -324,9 +312,9 @@ setMethod("getTaxonomyLabels", signature = c(x = "SummarizedExperiment"), return(NULL) } stop("Only empty taxonomic information detected. Some rows contain ", - "only entries selected by 'empty.fields'. Cannot generated ", - "labels. Try option na.rm = TRUE in the function call.", - call. = FALSE) + "only entries selected by 'empty.fields'. Cannot generated ", + "labels. Try option na.rm = TRUE in the function call.", + call. = FALSE) } # if(is.matrix(tax_ranks_selected)){ @@ -352,9 +340,9 @@ setMethod("getTaxonomyLabels", signature = c(x = "SummarizedExperiment"), } .get_taxonomic_label <- function(x, - empty.fields = c(NA, "", " ", "\t", "-", "_"), - with_rank = FALSE, - resolve_loops = FALSE){ + empty.fields = c(NA, "", " ", "\t", "-", "_"), + with_rank = FALSE, + resolve_loops = FALSE){ rd <- rowData(x) tax_cols <- .get_tax_cols_from_se(x) tax_ranks_selected <- .get_tax_ranks_selected(x, rd, tax_cols, empty.fields) @@ -372,9 +360,9 @@ setMethod("getTaxonomyLabels", signature = c(x = "SummarizedExperiment"), # all_same_rank <- length(unique(tax_cols_selected)) == 1L ans <- mapply("[", - as.data.frame(t(as.data.frame(rd))), - tax_cols_selected, - SIMPLIFY = FALSE) + as.data.frame(t(as.data.frame(rd))), + tax_cols_selected, + SIMPLIFY = FALSE) ans <- unlist(ans, use.names = FALSE) if(with_rank || !all_same_rank){ ans <- .add_taxonomic_type(rd, ans, tax_cols_selected) @@ -382,21 +370,64 @@ setMethod("getTaxonomyLabels", signature = c(x = "SummarizedExperiment"), ans } -#' @rdname taxonomy-methods -setGeneric("taxonomyTree", - signature = "x", - function(x, ...) - standardGeneric("taxonomyTree")) +#' Calculate hierarchy tree +#' +#' These functions generate a hierarchy tree using taxonomic information from a +#' \code{\link[TreeSummarizedExperiment:TreeSummarizedExperiment-class]{SummarizedExperiment}} +#' object and add this hierarchy tree into the \code{rowTree}. +#' +#' \code{addHierarchyTree} calculates hierarchy tree from the available taxonomic +#' information and add it to \code{rowTree}. +#' +#' \code{getHierarchyTree} generates a hierarchy tree from the available +#' taxonomic information. Internally it uses +#' \code{\link[TreeSummarizedExperiment:toTree]{toTree}} and +#' \code{\link[TreeSummarizedExperiment:resolveLoop]{resolveLoop}} to sanitize +#' data if needed. +#' +#' @inheritParams taxonomy-methods +#' +#' @return +#' \itemize{ +#' \item{\code{addHierarchyTree}:} {a \code{TreeSummarizedExperiment} whose +#' \code{phylo} tree represents the hierarchy among available taxonomy +#' information} +#' \item{\code{getHierarchyTree}:} {a \code{phylo} tree representing the +#' hierarchy among available taxonomy information.} +#' } +#' +#' @name hierarchy-tree +#' +#' @examples +#' # Generating a hierarchy tree based on available taxonomic information. +#' data(GlobalPatterns) +#' tse <- GlobalPatterns +#' getHierarchyTree(tse) +#' +#' # Adding a hierarchy tree based on the available taxonomic information. +#' # Please note that any tree already stored in rowTree() will be overwritten. +#' tse <- addHierarchyTree(tse) +#' tse +#' +NULL -#' @rdname taxonomy-methods +#' @rdname hierarchy-tree +setGeneric("getHierarchyTree", + signature = "x", + function(x, ...) + standardGeneric("getHierarchyTree")) + +#' @rdname hierarchy-tree +#' @aliases getHierarchyTree #' @export -setMethod("taxonomyTree", signature = c(x = "SummarizedExperiment"), +#' @importFrom ape drop.tip +setMethod("getHierarchyTree", signature = c(x = "SummarizedExperiment"), function(x){ # Input check # If there is no rowData it is not possible to create rowTree if( ncol(rowData(x)) == 0L ){ stop("'x' does not have rowData. Tree cannot be created.", - call. = FALSE) + call. = FALSE) } # # Converted to data.frame so that drop = FALSE is enabled @@ -414,32 +445,33 @@ setMethod("taxonomyTree", signature = c(x = "SummarizedExperiment"), for(i in rev(seq_len(ncol(td)))){ if(any(td_NA[,i])){ to_drop <- paste0(colnames(td)[i],":",td[,i][td_NA[,i]]) - tree <- ape::drop.tip(tree, - to_drop, - trim.internal = FALSE, - collapse.singles = FALSE) + tree <- drop.tip( + tree, + to_drop, + trim.internal = FALSE, + collapse.singles = FALSE) } } tree } ) -#' @rdname taxonomy-methods -setGeneric("addTaxonomyTree", - signature = "x", - function(x, ...) - standardGeneric("addTaxonomyTree")) +#' @rdname hierarchy-tree +setGeneric("addHierarchyTree", + signature = "x", + function(x, ...) + standardGeneric("addHierarchyTree")) -#' @rdname taxonomy-methods +#' @rdname hierarchy-tree #' @export -setMethod("addTaxonomyTree", signature = c(x = "SummarizedExperiment"), +setMethod("addHierarchyTree", signature = c(x = "SummarizedExperiment"), function(x){ # - tree <- taxonomyTree(x) + tree <- getHierarchyTree(x) x <- as(x,"TreeSummarizedExperiment") rownames(x) <- getTaxonomyLabels(x, with_rank = TRUE, - resolve_loops = TRUE, - make_unique = FALSE) + resolve_loops = TRUE, + make_unique = FALSE) x <- changeTree(x, tree, rownames(x)) x } @@ -447,9 +479,9 @@ setMethod("addTaxonomyTree", signature = c(x = "SummarizedExperiment"), #' @rdname taxonomy-methods setGeneric("mapTaxonomy", - signature = "x", - function(x, ...) - standardGeneric("mapTaxonomy")) + signature = "x", + function(x, ...) + standardGeneric("mapTaxonomy")) #' @importFrom BiocGenerics %in% grepl .get_taxa_row_match <- function(taxa, td, from, use_grepl = FALSE){ @@ -490,33 +522,33 @@ setMethod("mapTaxonomy", signature = c(x = "SummarizedExperiment"), # input check if(!checkTaxonomy(x)){ stop("Non compatible taxonomic information found. ", - "checkTaxonomy(x) must be TRUE.", - call. = FALSE) + "checkTaxonomy(x) must be TRUE.", + call. = FALSE) } if(!is.null(taxa)){ if(!is.character(taxa)){ stop("'taxa' must be a character vector.", - call. = FALSE) + call. = FALSE) } } if(!is.null(from)){ if(!.is_a_string(from)){ stop("'from' must be a single character value.", - call. = FALSE) + call. = FALSE) } if(!(from %in% taxonomyRanks(x))){ stop("'from' must be an element of taxonomyRanks(x).", - call. = FALSE) + call. = FALSE) } } if(!is.null(to)){ if(!.is_a_string(to)){ stop("'to' must be a single character value.", - call. = FALSE) + call. = FALSE) } if(!(to %in% taxonomyRanks(x))){ stop("'to' must be an element of taxonomyRanks(x).", - call. = FALSE) + call. = FALSE) } } if(!is.null(from) && !is.null(to)){ @@ -537,11 +569,11 @@ setMethod("mapTaxonomy", signature = c(x = "SummarizedExperiment"), c_f <- rep(TRUE,ncol(td)) if(!is.null(from)){ r_fs <- lapply(taxa, .get_taxa_row_match, td = td, from = from, - use_grepl = use_grepl) + use_grepl = use_grepl) names(r_fs) <- taxa } else { r_fs <- lapply(taxa, .get_taxa_any_match, td = td, - use_grepl = use_grepl) + use_grepl = use_grepl) names(r_fs) <- taxa } if(!is.null(to)) { diff --git a/man/deprecate.Rd b/man/deprecate.Rd new file mode 100644 index 000000000..56ec43586 --- /dev/null +++ b/man/deprecate.Rd @@ -0,0 +1,28 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/deprecate.R +\name{deprecate} +\alias{deprecate} +\alias{addTaxonomyTree} +\alias{addTaxonomyTree,SummarizedExperiment-method} +\alias{taxonomyTree} +\alias{taxonomyTree,SummarizedExperiment-method} +\title{These functions will be deprecated. Please use other functions instead.} +\usage{ +addTaxonomyTree(x, ...) + +\S4method{addTaxonomyTree}{SummarizedExperiment}(x) + +taxonomyTree(x, ...) + +\S4method{taxonomyTree}{SummarizedExperiment}(x) +} +\arguments{ +\item{x}{a \code{\link{SummarizedExperiment}} object -} + +\item{...}{\itemize{ +\item +}} +} +\description{ +These functions will be deprecated. Please use other functions instead. +} diff --git a/man/hierarchy-tree.Rd b/man/hierarchy-tree.Rd new file mode 100644 index 000000000..3f46234a2 --- /dev/null +++ b/man/hierarchy-tree.Rd @@ -0,0 +1,61 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/taxonomy.R +\name{hierarchy-tree} +\alias{hierarchy-tree} +\alias{getHierarchyTree} +\alias{getHierarchyTree,SummarizedExperiment-method} +\alias{addHierarchyTree} +\alias{addHierarchyTree,SummarizedExperiment-method} +\title{Calculate hierarchy tree} +\usage{ +getHierarchyTree(x, ...) + +\S4method{getHierarchyTree}{SummarizedExperiment}(x) + +addHierarchyTree(x, ...) + +\S4method{addHierarchyTree}{SummarizedExperiment}(x) +} +\arguments{ +\item{x}{a +\code{\link[SummarizedExperiment:SummarizedExperiment-class]{SummarizedExperiment}} +object} + +\item{...}{optional arguments not used currently.} +} +\value{ +\itemize{ +\item{\code{addHierarchyTree}:} {a \code{TreeSummarizedExperiment} whose +\code{phylo} tree represents the hierarchy among available taxonomy +information} +\item{\code{getHierarchyTree}:} {a \code{phylo} tree representing the +hierarchy among available taxonomy information.} +} +} +\description{ +These functions generate a hierarchy tree using taxonomic information from a +\code{\link[TreeSummarizedExperiment:TreeSummarizedExperiment-class]{SummarizedExperiment}} +object and add this hierarchy tree into the \code{rowTree}. +} +\details{ +\code{addHierarchyTree} calculates hierarchy tree from the available taxonomic +information and add it to \code{rowTree}. + +\code{getHierarchyTree} generates a hierarchy tree from the available +taxonomic information. Internally it uses +\code{\link[TreeSummarizedExperiment:toTree]{toTree}} and +\code{\link[TreeSummarizedExperiment:resolveLoop]{resolveLoop}} to sanitize +data if needed. +} +\examples{ +# Generating a hierarchy tree based on available taxonomic information. +data(GlobalPatterns) +tse <- GlobalPatterns +getHierarchyTree(tse) + +# Adding a hierarchy tree based on the available taxonomic information. +# Please note that any tree already stored in rowTree() will be overwritten. +tse <- addHierarchyTree(tse) +tse + +} diff --git a/man/taxonomy-methods.Rd b/man/taxonomy-methods.Rd index 74d530b9f..d224bfa10 100644 --- a/man/taxonomy-methods.Rd +++ b/man/taxonomy-methods.Rd @@ -12,10 +12,6 @@ \alias{checkTaxonomy,SummarizedExperiment-method} \alias{getTaxonomyLabels} \alias{getTaxonomyLabels,SummarizedExperiment-method} -\alias{taxonomyTree} -\alias{taxonomyTree,SummarizedExperiment-method} -\alias{addTaxonomyTree} -\alias{addTaxonomyTree,SummarizedExperiment-method} \alias{mapTaxonomy} \alias{mapTaxonomy,SummarizedExperiment-method} \alias{IdTaxaToDataFrame} @@ -58,14 +54,6 @@ getTaxonomyLabels(x, ...) ... ) -taxonomyTree(x, ...) - -\S4method{taxonomyTree}{SummarizedExperiment}(x) - -addTaxonomyTree(x, ...) - -\S4method{addTaxonomyTree}{SummarizedExperiment}(x) - mapTaxonomy(x, ...) \S4method{mapTaxonomy}{SummarizedExperiment}(x, taxa = NULL, from = NULL, to = NULL, use_grepl = FALSE) @@ -78,11 +66,11 @@ IdTaxaToDataFrame(from) object} \item{rank}{a single character defining a taxonomic rank. Must be a value of -\code{taxonomyRanks()} function.} +\code{taxonomyRanks()} function} \item{empty.fields}{a \code{character} value defining, which values should be regarded as empty. (Default: \code{c(NA, "", " ", "\t")}). They will be -removed if \code{na.rm = TRUE} before agglomeration.} +removed if \code{na.rm = TRUE} before agglomeration} \item{...}{optional arguments not used currently.} @@ -146,12 +134,6 @@ creation. the lowest taxonomic information possible. If data from different levels, is to be mixed, the taxonomic level is prepended by default. -\code{taxonomyTree} generates a \code{phylo} tree object from the available -taxonomic information. Internally it uses -\code{\link[TreeSummarizedExperiment:toTree]{toTree}} and -\code{\link[TreeSummarizedExperiment:resolveLoop]{resolveLoop}} to sanitize -data if needed. - \code{IdTaxaToDataFrame} extracts taxonomic results from results of \code{\link[DECIPHER:IdTaxa]{IdTaxa}}. @@ -188,12 +170,6 @@ mapTaxonomy(GlobalPatterns) mapTaxonomy(GlobalPatterns, taxa = "Escherichia") # returns information on a single output mapTaxonomy(GlobalPatterns, taxa = "Escherichia",to="Family") - -# adding a rowTree() based on the available taxonomic information. Please -# note that any tree already stored in rowTree() will be overwritten. -x <- GlobalPatterns -x <- addTaxonomyTree(x) -x } \seealso{ \code{\link[=agglomerate-methods]{agglomerateByRank}}, diff --git a/tests/testthat/test-2taxonomy.R b/tests/testthat/test-2taxonomy.R index 9daaab994..ea06deab9 100644 --- a/tests/testthat/test-2taxonomy.R +++ b/tests/testthat/test-2taxonomy.R @@ -69,9 +69,9 @@ test_that("taxonomy", { c("Family:j","Phylum:a","Family:k","Family:l","Family:m", "Family:n","Family:o_1","Phylum:c","Family:o_2")) - # addTaxonomyTree + # addHierarchyTree data(GlobalPatterns, package="mia") - expect_warning(GlobalPatterns <- addTaxonomyTree(GlobalPatterns)) + expect_warning(GlobalPatterns <- addHierarchyTree(GlobalPatterns)) expect_equal(dim(GlobalPatterns),c(19216,26)) expect_equal(rowTree(GlobalPatterns)$Nnode, 1089) expect_equal(length(rowTree(GlobalPatterns)$tip.label), 1645)