diff --git a/R/01_classDefinitions.R b/R/01_classDefinitions.R index e6e03e1..f8ea091 100644 --- a/R/01_classDefinitions.R +++ b/R/01_classDefinitions.R @@ -385,6 +385,7 @@ setClass( datasetname = "character", age_range_old = "numeric", age_range_young = "numeric", + age_units = "character", notes = "character", pi_list = "ANY", samples = "samples", @@ -397,6 +398,7 @@ setClass( datasetname = NA_character_, age_range_old = NA_integer_, age_range_young = NA_integer_, + age_units = NA_character_, notes = NA_character_, pi_list = list(), samples = NULL, @@ -512,3 +514,43 @@ setClass("sites", }) %>% unlist()) }) + +#' @title S4 class for specimen information +#' @description Taxon class for single taxon information +#' from the Neotoma Paleoecology Database. +#' @returns object of class `taxon` +#' @export +setClass("taxon", + slots = c(taxonid = "numeric", + taxoncode = "character", + taxonname = "character", + author = "character", + ecolgroup = "character", + highertaxonid = "numeric", + status = "character", + taxagroupid = "character", + publicationid = "numeric", + publication = "character"), + prototype = list(taxonid = NA_integer_, + taxoncode = NA_character_, + taxonname = NA_character_, + author = NA_character_, + ecolgroup = NA_character_, + highertaxonid = NA_integer_, + status = NA_character_, + taxagroupid = NA_character_, + publicationid = NA_integer_, + publication = NA_character_)) + +#' @title S4 class for taxa information +#' @description Taxa class for taxa information +#' from the Neotoma Paleoecology Database. +#' @returns object of class `taxon` +#' @export +setClass("taxa", representation(taxa = "list"), + validity = function(object) { + all(map(object, function(x) { + class(x) == "taxon" + }) %>% + unlist()) + }) diff --git a/R/build_dataset.R b/R/build_dataset.R index 112a495..3fc5ced 100644 --- a/R/build_dataset.R +++ b/R/build_dataset.R @@ -38,6 +38,7 @@ build_dataset <- function(x) { datasetname = use_na(testNull(x$datasetname, NA), "char"), age_range_old = use_na(testNull(x$agerange[[1]]$ageold, NA), "int"), age_range_young = use_na(testNull(x$agerange[[1]]$ageyoung, NA), "int"), + age_units = use_na(testNull(x$agerange[[1]]$units, NA), "char"), notes = use_na(testNull(x$datasetnotes, NA), "char"), pi_list = pi_list, samples = samples, diff --git a/R/dataset-methods.R b/R/dataset-methods.R index db215b0..9aba81e 100644 --- a/R/dataset-methods.R +++ b/R/dataset-methods.R @@ -10,6 +10,7 @@ setMethod(f = "show", datasettype = object@datasettype, age_range_old = object@age_range_old, age_range_young = object@age_range_young, + age_units = object@age_units, notes = object@notes), row.names = FALSE) }) @@ -25,6 +26,7 @@ setMethod(f = "show", datasettype = y@datasettype, age_range_old = y@age_range_old, age_range_young = y@age_range_young, + age_units = y@age_units, notes = y@notes) }) %>% bind_rows() %>% @@ -173,6 +175,7 @@ setMethod(f = "as.data.frame", datasettype = x@datasettype, age_range_old = x@age_range_old, age_range_young = x@age_range_young, + age_units = x@age_units, notes = x@notes) }) diff --git a/R/get_taxa.R b/R/get_taxa.R new file mode 100644 index 0000000..ff3db6b --- /dev/null +++ b/R/get_taxa.R @@ -0,0 +1,127 @@ +#' @md +#' @title get_taxa +#' @description a sites object with the requested taxa. +#' @param x string taxa name or names +#' @returns A Neotoma2 sites object with datasets with the requested taxa. +#' +#' @export +get_taxon <- function(x = NA, ...) { + if (!missing(x)) { + UseMethod("get_taxa", x) + } else { + UseMethod("get_taxa", NA) + } +} + +parse_taxon <- function(result) { # nolint + + fix_null <- function(x) { + for (i in seq_len(length(x))) { + if (is.null(x[[i]])) { + x[[i]] <- NA + } else { + if (is(x[[i]], "list")) { + x[[i]] <- fix_null(x[[i]]) + } + } + } + return(x) + } + + data <- result$data %>% + fix_null() + + # With a large dataset this seems to take some time, but it's not too bad. + newTaxon <- map(data, function(x) { + + new_taxon <- new("taxon", + taxonid = x$taxonid, + taxoncode = x$taxoncode, + taxonname = x$taxonname, + author = x$author, + ecolgroup = x$ecolgroup, + highertaxonid = x$highertaxonid, + status = x$status, + taxagroupid = x$taxagroupid, + publicationid = x$publicationid, + publication = x$publication) + + print(new_taxon) + }) + + return(new_taxon) + +} + + +#' @title Get Taxa Default +#' @param x Use a taxon ID to extract site information +#' @param ... accepted arguments, see details for more information. +#' @importFrom utils URLencode +#' @returns `sites` object containing the requested `taxa` +#' @export +get_taxon.default <- function(x, ...) { + oo <- options(scipen = 9999999) + on.exit(options(oo)) + cl <- as.list(match.call()) + + cl[[1]] <- NULL + + cl <- lapply(cl, eval, envir = parent.frame()) + + all_data <- ifelse(is.null(cl$all_data), FALSE, TRUE) + error_check <- check_args(cl) # nolint + + if (error_check[[2]]$flag == 1) { + stop(paste0(unlist(error_check[[2]]$message), collapse = "\n ")) + } else { + cl <- error_check[[1]] + } + + base_url <- paste0("data/taxa") + result <- parseURL(base_url, ...) %>% + cleanNULL() + + if (is.null(result$data[1][[1]]) || is.null(result[1][[1]])) { + return(NULL) + + } else { + output <- parse_taxa(result) + return(output) + } +} + +#' @title Get Taxa Numeric +#' @param x Use a taxon ID to extract sites information +#' @param ... Additional parameters to get_taxa +#' @returns `sites` object with requested `taxa` +#' @examples \donttest{ +#' allds <- get_datasets(1:3) +#' } +#' @export +get_taxon.numeric <- function(x, ...) { + use_na <- function(x, type) { + if (is.na(x)) { + return(switch(type, + "char" = NA_character_, + "int" = NA_integer_)) + } else { + return(x) + } + } + + if (length(x) > 0) { + taxa_id <- paste0(x, collapse = ",") + } + + base_url <- paste0("data/taxa/", taxa_id) + result <- neotoma2::parseURL(base_url, ...) + result_length <- length(result[2]$data) + + if (result_length > 0) { + output <- parse_taxa(result) + return(output) + } else { + return(NULL) + } +} \ No newline at end of file diff --git a/R/get_taxon.R b/R/get_taxon.R new file mode 100644 index 0000000..633c185 --- /dev/null +++ b/R/get_taxon.R @@ -0,0 +1,124 @@ +#' @md +#' @title get_taxon +#' @description a sites object with the requested taxa. +#' @param x string taxa name or names +#' @returns A Neotoma2 sites object with datasets with the requested taxa. +#' +#' @export +get_taxon <- function(x = NA, ...) { + if (!missing(x)) { + UseMethod("get_taxon", x) + } else { + UseMethod("get_taxon", NA) + } +} + +parse_taxon <- function(result) { # nolint + + fix_null <- function(x) { + for (i in seq_len(length(x))) { + if (is.null(x[[i]])) { + x[[i]] <- NA + } else { + if (is(x[[i]], "list")) { + x[[i]] <- fix_null(x[[i]]) + } + } + } + return(x) + } + + data <- result$data %>% + fix_null() + + newTaxa <- map(data, function(x) { + new_taxon <- new("taxon", + taxonid = use_na(testNull(x$taxonid, NA), "int"), + taxoncode = use_na(testNull(x$taxoncode, NA), "char"), + taxonname = use_na(testNull(x$taxonname, NA), "char"), + author = use_na(testNull(x$author, NA), "char"), + ecolgroup = use_na(testNull(x$ecolgroup, NA), "char"), + highertaxonid = use_na(testNull(x$highertaxonid, NA), "int"), + status = use_na(testNull(x$status, NA), "char"), + taxagroupid = use_na(testNull(x$taxagroupid, NA), "int"), + publicationid = use_na(testNull(x$publicationid, NA), "int"), + publication = use_na(testNull(x$publication, NA), "char")) + }) + + taxa <- new("taxa", taxa = newTaxa) + + return(taxa) +} + + +#' @title Get Taxa Default +#' @param x Use a taxon ID to extract site information +#' @param ... accepted arguments, see details for more information. +#' @importFrom utils URLencode +#' @returns `sites` object containing the requested `taxa` +#' @export +get_taxon.default <- function(x, ...) { + oo <- options(scipen = 9999999) + on.exit(options(oo)) + cl <- as.list(match.call()) + + cl[[1]] <- NULL + + cl <- lapply(cl, eval, envir = parent.frame()) + + all_data <- ifelse(is.null(cl$all_data), FALSE, TRUE) + error_check <- check_args(cl) # nolint + + if (error_check[[2]]$flag == 1) { + stop(paste0(unlist(error_check[[2]]$message), collapse = "\n ")) + } else { + cl <- error_check[[1]] + } + + base_url <- paste0("data/taxa") + result <- parseURL(base_url, ...) %>% + cleanNULL() + + if (is.null(result$data[1][[1]]) || is.null(result[1][[1]])) { + return(NULL) + + } else { + output <- parse_taxon(result) + return(output) + } +} + +#' @title Get Taxa Numeric +#' @param x Use a taxon ID to extract sites information +#' @param ... Additional parameters to get_taxa +#' @returns `sites` object with requested `taxa` +#' @examples \donttest{ +#' allds <- get_datasets(1:3) +#' } +#' @export +get_taxon.numeric <- function(x, ...) { + use_na <- function(x, type) { + if (is.na(x)) { + return(switch(type, + "char" = NA_character_, + "int" = NA_integer_)) + } else { + return(x) + } + } + + if (length(x) > 0) { + taxa_id <- paste0(x, collapse = ",") + } + + base_url <- paste0("data/taxa/", taxa_id) + result <- neotoma2::parseURL(base_url, ...) + result_length <- length(result[2]$data) + + if (result_length > 0) { + output <- parse_taxon(result) + return(output) + } else { + return(NULL) + } +} \ No newline at end of file diff --git a/R/taxon-methods.R b/R/taxon-methods.R new file mode 100644 index 0000000..f7c5a2f --- /dev/null +++ b/R/taxon-methods.R @@ -0,0 +1,237 @@ +# Start "Show Method" for all Neotoma Objects +#' @title Show Taxon Method +#' @param object taxon object +#' @returns null - side effect, prints a `data.frame` with `taxon` metadata +setMethod(f = "show", + signature = "taxon", + definition = function(object) { + print(data.frame(taxonid = as.character(object@taxonid), + taxoncode = object@taxoncode, + taxonname = object@taxonname, + author = object@author, + ecolgroup = object@ecolgroup, + highertaxonid = object@highertaxonid, + status = object@status, + taxagroupid = object@taxagroupid, + publicationid = object@publicationid, + publication = object@publication), row.names = FALSE) + }) + +# Start "Show Method" for all Neotoma Objects +#' @title Show Taxa Method +#' @param object taxon object +#' @returns null - side effect, prints a `data.frame` with `taxon` metadata +setMethod(f = "show", + signature = "taxa", + definition = function(object) { + map(object@taxa, function(y) { + df <- data.frame(taxonid = as.character(y@taxonid), + taxoncode = y@taxoncode, + taxonname = y@taxonname, + author = y@author, + ecolgroup = y@ecolgroup, + highertaxonid = y@highertaxonid, + status = y@status, + taxagroupid = y@taxagroupid, + publicationid = y@publicationid, + publication = y@publication) + }) %>% + bind_rows() %>% + print(row.names = FALSE) + }) + + +#' @title Slicer +#' @param x taxa object +#' @param i iteration in taxa list +#' @description Obtain one of the elements within a taxa list +#' @returns sliced `taxa` object +#' @export +setMethod(f = "[[", + signature = signature(x = "taxa", i = "numeric"), + definition = function(x, i) { + if (length(i) == 1) { + out <- new("taxon", x@taxa[[i]]) + } else { + out <- purrr::map(i, function(z) { + new("taxon", x@taxa[[z]]) + }) + out <- new("taxa", taxa = out) + } + return(out) + }) + +#' @title Get slot names +#' @param x A taxon object. +#' @description Get all names for named elements within a `taxon` object. +#' @returns `list` with all names of `taxon` slots +#' @export +setMethod(f = "names", + signature = signature(x = "taxon"), + definition = function(x) { + slotNames(x) + }) + +#' @title Insert taxon +#' @param x taxa object +#' @param i iteration in taxa list +#' @param value The value to be used +#' @description Obtain one of the elements within a taxa list +#' @returns One `taxon` slot's value +#' @export +setMethod(f = "[[<-", + signature = signature(x = "taxa"), + definition = function(x, i, value) { + taxaset <- x@taxa + taxaset[[i]] <- value + out <- new("taxa", taxa = taxaset) + return(out) + }) + + +#' @title Assign taxon field by numeric index +#' @param x The taxon object. +#' @param i The column indicator. +#' @param value The value to be used. +#' @returns `taxon` slot with new assigned character value +setMethod(f = "[<-", + signature = signature(x = "taxon", i = "character"), + definition = function(x, i, value) { + for (idx in 1:length(i)) { + slot(x, i[idx]) <- value[idx] + } + return(x) + }) + +#' @title Assign taxon field by numeric index +#' @param x The taxon object. +#' @param i The column indicator. +#' @param value The value to be used. +#' @returns `taxon` slot with new assigned numeric value +setMethod(f = "[<-", + signature = signature(x = "taxon", i = "numeric"), + definition = function(x, i, value) { + slots <- slotNames(x) + for (idx in 1:length(i)) { + slot(x, slots[i[idx]]) <- value[idx] + } + return(x) + }) + +#' @title Assign taxon field by numeric index +#' @param x The taxon object. +#' @param name name of the slot. +#' @param value The value to be used. +#' @returns Assign new `taxon` by numeric index +setMethod(f = "$<-", + signature = signature(x = "taxon"), + definition = function(x, name, value) { + slot(x, name) <- value + return(x) + }) + + + +#' @title Get or remove taxa by numeric index +#' @param x The taxa object +#' @param i The numeric index +#' @returns Get or remove `taxa` by numeric index +setMethod(f = "[", + signature = signature(x = "taxa", i = "numeric"), + definition = function(x, i) { + new("taxa", taxa = x@taxa[i]) + }) + +#' @title $ +#' @param x taxon object +#' @param name name of the slot +#' @description Obtain slots of a taxon without using at-mark +#' @returns Obtain a `taxon`'s `slot` value using $ +#' @export +setMethod(f = "$", + signature = signature(x = "taxon"), + definition = function(x, name) { + slot(x, name) + }) + +#' @title $ for taxa +#' @param x taxa object +#' @param name name of the slot. +#' @description Obtain slots of a taxon without using at-mark +#' @returns Obtain a `taxa`' `slot` value using $ +#' @export +setMethod(f = "$", + signature = signature(x = "taxa"), + definition = function(x, name) { + x %>% + map(function(y) { + slot(y, name) + }) %>% + unlist() + }) + +#' @title as.data.frame taxon +#' @param x taxon object +#' @description show as dataframe as prep to save as csv +#' @returns `data.frame` with `taxon` metadata +#' @export +setMethod(f = "as.data.frame", + signature = signature("taxon"), + definition = function(x) { + data.frame(taxonid = as.character(object@taxonid), + taxoncode = object@taxoncode, + taxonname = object@taxonname, + author = object@author, + ecolgroup = object@ecolgroup, + highertaxonid = object@highertaxonid, + status = object@status, + taxagroupid = object@taxagroupid, + publicationid = object@publicationid, + publication = object@publication) + }) + +#' @title as.data.frame taxa +#' @param x taxa object +#' @description show as dataframe as prep to save as csv +#' @returns `data.frame` with `taxa` metadata +#' @export +setMethod(f = "as.data.frame", + signature = signature("taxa"), + definition = function(x) { + x@taxa %>% map(as.data.frame) %>% bind_rows() + }) + +#' @title Length Method taxa +#' @export +#' @returns `int` that showcases the length of a `taxa` object +#' @param x taxa object +setMethod(f = "length", + signature = signature(x = "taxa"), + definition = function(x) { + length(x@taxa) + }) + +#' @title c Method - Combine taxa objects +#' @param x taxa object 1 +#' @param y taxa object 2 +#' @returns concatenated `taxa` object +#' @export +setMethod(f = "c", + signature = signature(x = "taxa"), + definition = function(x, y) { + new("taxa", + taxa = unlist(c(x@taxa, + y@taxa), recursive = FALSE)) + }) + +#' @title write CSV +#' @param x taxa object +#' @param ... Additional parameters associated with the call. +#' @returns null -side effect for printing a CSV file +#' @export +setMethod(f = "write.csv", + signature = "taxa", + definition = function(x, ...) { + df1 <- as.data.frame(x) + write.csv(df1, ...) + }) diff --git a/man/as.data.frame-taxa-method.Rd b/man/as.data.frame-taxa-method.Rd new file mode 100644 index 0000000..7abdc59 --- /dev/null +++ b/man/as.data.frame-taxa-method.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/taxon-methods.R +\name{as.data.frame,taxa-method} +\alias{as.data.frame,taxa-method} +\title{as.data.frame taxa} +\usage{ +\S4method{as.data.frame}{taxa}(x) +} +\arguments{ +\item{x}{taxa object} +} +\value{ +\code{data.frame} with \code{taxa} metadata +} +\description{ +show as dataframe as prep to save as csv +} diff --git a/man/as.data.frame-taxon-method.Rd b/man/as.data.frame-taxon-method.Rd new file mode 100644 index 0000000..ea9adce --- /dev/null +++ b/man/as.data.frame-taxon-method.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/taxon-methods.R +\name{as.data.frame,taxon-method} +\alias{as.data.frame,taxon-method} +\title{as.data.frame taxon} +\usage{ +\S4method{as.data.frame}{taxon}(x) +} +\arguments{ +\item{x}{taxon object} +} +\value{ +\code{data.frame} with \code{taxon} metadata +} +\description{ +show as dataframe as prep to save as csv +} diff --git a/man/c-taxa-method.Rd b/man/c-taxa-method.Rd new file mode 100644 index 0000000..e19e7aa --- /dev/null +++ b/man/c-taxa-method.Rd @@ -0,0 +1,19 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/taxon-methods.R +\name{c,taxa-method} +\alias{c,taxa-method} +\title{c Method - Combine taxa objects} +\usage{ +\S4method{c}{taxa}(x, y) +} +\arguments{ +\item{x}{taxa object 1} + +\item{y}{taxa object 2} +} +\value{ +concatenated \code{taxa} object +} +\description{ +c Method - Combine taxa objects +} diff --git a/man/cash-set-taxon-method.Rd b/man/cash-set-taxon-method.Rd new file mode 100644 index 0000000..dd0cff7 --- /dev/null +++ b/man/cash-set-taxon-method.Rd @@ -0,0 +1,21 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/taxon-methods.R +\name{$<-,taxon-method} +\alias{$<-,taxon-method} +\title{Assign taxon field by numeric index} +\usage{ +\S4method{$}{taxon}(x, name) <- value +} +\arguments{ +\item{x}{The taxon object.} + +\item{name}{name of the slot.} + +\item{value}{The value to be used.} +} +\value{ +Assign new \code{taxon} by numeric index +} +\description{ +Assign taxon field by numeric index +} diff --git a/man/cash-taxa-method.Rd b/man/cash-taxa-method.Rd new file mode 100644 index 0000000..9c25e31 --- /dev/null +++ b/man/cash-taxa-method.Rd @@ -0,0 +1,19 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/taxon-methods.R +\name{$,taxa-method} +\alias{$,taxa-method} +\title{$ for taxa} +\usage{ +\S4method{$}{taxa}(x, name) +} +\arguments{ +\item{x}{taxa object} + +\item{name}{name of the slot.} +} +\value{ +Obtain a \code{taxa}' \code{slot} value using $ +} +\description{ +Obtain slots of a taxon without using at-mark +} diff --git a/man/cash-taxon-method.Rd b/man/cash-taxon-method.Rd new file mode 100644 index 0000000..8674e58 --- /dev/null +++ b/man/cash-taxon-method.Rd @@ -0,0 +1,19 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/taxon-methods.R +\name{$,taxon-method} +\alias{$,taxon-method} +\title{$} +\usage{ +\S4method{$}{taxon}(x, name) +} +\arguments{ +\item{x}{taxon object} + +\item{name}{name of the slot} +} +\value{ +Obtain a \code{taxon}'s \code{slot} value using $ +} +\description{ +Obtain slots of a taxon without using at-mark +} diff --git a/man/get_taxon.Rd b/man/get_taxon.Rd new file mode 100644 index 0000000..8b4cbc0 --- /dev/null +++ b/man/get_taxon.Rd @@ -0,0 +1,23 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/get_taxa.R, R/get_taxon.R +\name{get_taxon} +\alias{get_taxon} +\title{get_taxa} +\usage{ +get_taxon(x = NA, ...) + +get_taxon(x = NA, ...) +} +\arguments{ +\item{x}{string taxa name or names} +} +\value{ +A Neotoma2 sites object with datasets with the requested taxa. + +A Neotoma2 sites object with datasets with the requested taxa. +} +\description{ +a sites object with the requested taxa. + +a sites object with the requested taxa. +} diff --git a/man/get_taxon.default.Rd b/man/get_taxon.default.Rd new file mode 100644 index 0000000..1b9cc76 --- /dev/null +++ b/man/get_taxon.default.Rd @@ -0,0 +1,25 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/get_taxa.R, R/get_taxon.R +\name{get_taxon.default} +\alias{get_taxon.default} +\title{Get Taxa Default} +\usage{ +\method{get_taxon}{default}(x, ...) + +\method{get_taxon}{default}(x, ...) +} +\arguments{ +\item{x}{Use a taxon ID to extract site information} + +\item{...}{accepted arguments, see details for more information.} +} +\value{ +\code{sites} object containing the requested \code{taxa} + +\code{sites} object containing the requested \code{taxa} +} +\description{ +Get Taxa Default + +Get Taxa Default +} diff --git a/man/get_taxon.numeric.Rd b/man/get_taxon.numeric.Rd new file mode 100644 index 0000000..7bf54e3 --- /dev/null +++ b/man/get_taxon.numeric.Rd @@ -0,0 +1,33 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/get_taxa.R, R/get_taxon.R +\name{get_taxon.numeric} +\alias{get_taxon.numeric} +\title{Get Taxa Numeric} +\usage{ +\method{get_taxon}{numeric}(x, ...) + +\method{get_taxon}{numeric}(x, ...) +} +\arguments{ +\item{x}{Use a taxon ID to extract sites information} + +\item{...}{Additional parameters to get_taxa} +} +\value{ +\code{sites} object with requested \code{taxa} + +\code{sites} object with requested \code{taxa} +} +\description{ +Get Taxa Numeric + +Get Taxa Numeric +} +\examples{ +\donttest{ +allds <- get_datasets(1:3) +} +\donttest{ +allds <- get_datasets(1:3) +} +} diff --git a/man/length-taxa-method.Rd b/man/length-taxa-method.Rd new file mode 100644 index 0000000..88774ce --- /dev/null +++ b/man/length-taxa-method.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/taxon-methods.R +\name{length,taxa-method} +\alias{length,taxa-method} +\title{Length Method taxa} +\usage{ +\S4method{length}{taxa}(x) +} +\arguments{ +\item{x}{taxa object} +} +\value{ +\code{int} that showcases the length of a \code{taxa} object +} +\description{ +Length Method taxa +} diff --git a/man/names-taxon-method.Rd b/man/names-taxon-method.Rd new file mode 100644 index 0000000..b3ee60e --- /dev/null +++ b/man/names-taxon-method.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/taxon-methods.R +\name{names,taxon-method} +\alias{names,taxon-method} +\title{Get slot names} +\usage{ +\S4method{names}{taxon}(x) +} +\arguments{ +\item{x}{A taxon object.} +} +\value{ +\code{list} with all names of \code{taxon} slots +} +\description{ +Get all names for named elements within a \code{taxon} object. +} diff --git a/man/show-taxa-method.Rd b/man/show-taxa-method.Rd new file mode 100644 index 0000000..cb0f75f --- /dev/null +++ b/man/show-taxa-method.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/taxon-methods.R +\name{show,taxa-method} +\alias{show,taxa-method} +\title{Show Taxa Method} +\usage{ +\S4method{show}{taxa}(object) +} +\arguments{ +\item{object}{taxon object} +} +\value{ +null - side effect, prints a \code{data.frame} with \code{taxon} metadata +} +\description{ +Show Taxa Method +} diff --git a/man/show-taxon-method.Rd b/man/show-taxon-method.Rd new file mode 100644 index 0000000..60d900d --- /dev/null +++ b/man/show-taxon-method.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/taxon-methods.R +\name{show,taxon-method} +\alias{show,taxon-method} +\title{Show Taxon Method} +\usage{ +\S4method{show}{taxon}(object) +} +\arguments{ +\item{object}{taxon object} +} +\value{ +null - side effect, prints a \code{data.frame} with \code{taxon} metadata +} +\description{ +Show Taxon Method +} diff --git a/man/sub-sub-taxa-numeric-method.Rd b/man/sub-sub-taxa-numeric-method.Rd new file mode 100644 index 0000000..c4bc011 --- /dev/null +++ b/man/sub-sub-taxa-numeric-method.Rd @@ -0,0 +1,19 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/taxon-methods.R +\name{[[,taxa,numeric-method} +\alias{[[,taxa,numeric-method} +\title{Slicer} +\usage{ +\S4method{[[}{taxa,numeric}(x, i) +} +\arguments{ +\item{x}{taxa object} + +\item{i}{iteration in taxa list} +} +\value{ +sliced \code{taxa} object +} +\description{ +Obtain one of the elements within a taxa list +} diff --git a/man/sub-subset-taxa-ANY-ANY-ANY-method.Rd b/man/sub-subset-taxa-ANY-ANY-ANY-method.Rd new file mode 100644 index 0000000..64e98c8 --- /dev/null +++ b/man/sub-subset-taxa-ANY-ANY-ANY-method.Rd @@ -0,0 +1,21 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/taxon-methods.R +\name{[[<-,taxa,ANY,ANY,ANY-method} +\alias{[[<-,taxa,ANY,ANY,ANY-method} +\title{Insert taxon} +\usage{ +\S4method{[[}{taxa,ANY,ANY,ANY}(x, i) <- value +} +\arguments{ +\item{x}{taxa object} + +\item{i}{iteration in taxa list} + +\item{value}{The value to be used} +} +\value{ +One \code{taxon} slot's value +} +\description{ +Obtain one of the elements within a taxa list +} diff --git a/man/sub-taxa-numeric-method.Rd b/man/sub-taxa-numeric-method.Rd new file mode 100644 index 0000000..ac0b9bb --- /dev/null +++ b/man/sub-taxa-numeric-method.Rd @@ -0,0 +1,19 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/taxon-methods.R +\name{[,taxa,numeric-method} +\alias{[,taxa,numeric-method} +\title{Get or remove taxa by numeric index} +\usage{ +\S4method{[}{taxa,numeric}(x, i) +} +\arguments{ +\item{x}{The taxa object} + +\item{i}{The numeric index} +} +\value{ +Get or remove \code{taxa} by numeric index +} +\description{ +Get or remove taxa by numeric index +} diff --git a/man/subset-taxon-character-ANY-ANY-method.Rd b/man/subset-taxon-character-ANY-ANY-method.Rd new file mode 100644 index 0000000..874c4c0 --- /dev/null +++ b/man/subset-taxon-character-ANY-ANY-method.Rd @@ -0,0 +1,21 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/taxon-methods.R +\name{[<-,taxon,character,ANY,ANY-method} +\alias{[<-,taxon,character,ANY,ANY-method} +\title{Assign taxon field by numeric index} +\usage{ +\S4method{[}{taxon,character,ANY,ANY}(x, i) <- value +} +\arguments{ +\item{x}{The taxon object.} + +\item{i}{The column indicator.} + +\item{value}{The value to be used.} +} +\value{ +\code{taxon} slot with new assigned character value +} +\description{ +Assign taxon field by numeric index +} diff --git a/man/subset-taxon-numeric-ANY-ANY-method.Rd b/man/subset-taxon-numeric-ANY-ANY-method.Rd new file mode 100644 index 0000000..0538985 --- /dev/null +++ b/man/subset-taxon-numeric-ANY-ANY-method.Rd @@ -0,0 +1,21 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/taxon-methods.R +\name{[<-,taxon,numeric,ANY,ANY-method} +\alias{[<-,taxon,numeric,ANY,ANY-method} +\title{Assign taxon field by numeric index} +\usage{ +\S4method{[}{taxon,numeric,ANY,ANY}(x, i) <- value +} +\arguments{ +\item{x}{The taxon object.} + +\item{i}{The column indicator.} + +\item{value}{The value to be used.} +} +\value{ +\code{taxon} slot with new assigned numeric value +} +\description{ +Assign taxon field by numeric index +} diff --git a/man/taxa-class.Rd b/man/taxa-class.Rd new file mode 100644 index 0000000..264a2f5 --- /dev/null +++ b/man/taxa-class.Rd @@ -0,0 +1,13 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/01_classDefinitions.R +\docType{class} +\name{taxa-class} +\alias{taxa-class} +\title{S4 class for taxa information} +\value{ +object of class \code{taxon} +} +\description{ +Taxa class for taxa information +from the Neotoma Paleoecology Database. +} diff --git a/man/taxon-class.Rd b/man/taxon-class.Rd new file mode 100644 index 0000000..99656df --- /dev/null +++ b/man/taxon-class.Rd @@ -0,0 +1,13 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/01_classDefinitions.R +\docType{class} +\name{taxon-class} +\alias{taxon-class} +\title{S4 class for specimen information} +\value{ +object of class \code{taxon} +} +\description{ +Taxon class for single taxon information +from the Neotoma Paleoecology Database. +} diff --git a/man/write.csv-taxa-method.Rd b/man/write.csv-taxa-method.Rd new file mode 100644 index 0000000..3be964d --- /dev/null +++ b/man/write.csv-taxa-method.Rd @@ -0,0 +1,19 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/taxon-methods.R +\name{write.csv,taxa-method} +\alias{write.csv,taxa-method} +\title{write CSV} +\usage{ +\S4method{write.csv}{taxa}(x, ...) +} +\arguments{ +\item{x}{taxa object} + +\item{...}{Additional parameters associated with the call.} +} +\value{ +null -side effect for printing a CSV file +} +\description{ +write CSV +}