From 050c765c8c136b6e00a855bcb07478cea8e0983c Mon Sep 17 00:00:00 2001 From: c1au6i0 Date: Tue, 31 Dec 2024 11:14:17 -0500 Subject: [PATCH] feat tox provide all data and tests improved [skipci] --- NAMESPACE | 1 + R/cache.R | 1 - R/checks.R | 5 +- R/extr_comptox.R | 2 +- R/extr_ctd.R | 16 +- R/extr_ice.R | 26 +- R/extr_iris.R | 9 +- R/extr_monograph.R | 39 +- R/extr_pprtv.R | 54 +- R/extr_pubchem.R | 58 +- R/extr_tox.R | 50 +- R/other.R | 1 - R/utils.R | 4 +- man/extr_casrn_from_cid.Rd | 9 +- man/extr_chem_info.Rd | 6 +- man/extr_ice.Rd | 16 +- man/extr_ice_assay_names.Rd | 5 +- man/extr_iris.Rd | 14 +- man/extr_monograph.Rd | 28 +- man/extr_pprtv.Rd | 41 +- man/extr_pubchem_fema.Rd | 10 +- man/search_and_match.Rd | 33 + man/with_extr_sandbox.Rd | 4 +- tests/testthat/_snaps/tox.md | 3341 +++++++++++++++++++++++++++++++ tests/testthat/test-comptox.R | 53 +- tests/testthat/test-ctd.R | 131 +- tests/testthat/test-ice.R | 12 +- tests/testthat/test-iris.R | 26 +- tests/testthat/test-pubchem.R | 58 +- tests/testthat/test-tox.R | 18 +- tests/testthat/test_monograph.R | 6 +- tests/testthat/test_pprtv.R | 95 +- 32 files changed, 3832 insertions(+), 340 deletions(-) create mode 100644 man/search_and_match.Rd create mode 100644 tests/testthat/_snaps/tox.md diff --git a/NAMESPACE b/NAMESPACE index 497d375..192eb6f 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -15,3 +15,4 @@ export(extr_tetramer) export(extr_tox) export(with_extr_sandbox) export(write_dataframes_to_excel) +importFrom(cli,cli_warn) diff --git a/R/cache.R b/R/cache.R index f4f89d0..fb6d8f9 100644 --- a/R/cache.R +++ b/R/cache.R @@ -13,7 +13,6 @@ #' The function will overwrite any existing file with the same name. #' @noRd save_to_cache <- function(obj, file_name, verbose = FALSE) { - # Sys.getenv("R_USER_CACHE_DIR") cache_dir <- tools::R_user_dir("extractox", which = "cache") diff --git a/R/checks.R b/R/checks.R index 7138f9e..6bdbf64 100644 --- a/R/checks.R +++ b/R/checks.R @@ -1,5 +1,5 @@ -' Check for NA values in a specific column of a dataframe -#' +" Check for NA values in a specific column of a dataframe +#" #' Checks for NA values in a specified column of a dataframe and optionally warns if any are found. #' #' @param dat A dataframe that contains the data. @@ -9,7 +9,6 @@ #' @keywords internal #' @noRd check_na_warn <- function(dat, col_to_check, verbose = TRUE) { - ids_not_found <- dat$query[is.na(dat[[col_to_check]])] if (all(isTRUE(verbose), length(ids_not_found) != 0)) { diff --git a/R/extr_comptox.R b/R/extr_comptox.R index 078660f..ecf00c2 100644 --- a/R/extr_comptox.R +++ b/R/extr_comptox.R @@ -187,7 +187,7 @@ extr_comptox <- function(ids, sheet_names <- readxl::excel_sheets(xlsx_file) suppressMessages( - dat_list <- lapply(sheet_names, readxl::read_excel, path = xlsx_file) + dat_list <- lapply(sheet_names, readxl::read_excel, path = xlsx_file) ) names(dat_list) <- paste0("comptox_", gsub(" ", "_", tolower(sheet_names))) diff --git a/R/extr_ctd.R b/R/extr_ctd.R index 7d646b0..cf39f24 100644 --- a/R/extr_ctd.R +++ b/R/extr_ctd.R @@ -80,8 +80,10 @@ extr_ctd <- function( check_internet(verbose = verbose) - col_names <- c("chemical_name", "chemical_id", "casrn", "gene_symbol", - "gene_id", "organism", "organism_id", "pubmed_ids", "query") + col_names <- c( + "chemical_name", "chemical_id", "casrn", "gene_symbol", + "gene_id", "organism", "organism_id", "pubmed_ids", "query" + ) params <- list( inputType = category, @@ -145,11 +147,10 @@ extr_ctd <- function( # Lets clean up out$query <- gsub(" \\[Object not found\\]", "", out$query) - check_na_warn(dat = out,col_to_check = "gene_id", verbose = verbose) + check_na_warn(dat = out, col_to_check = "gene_id", verbose = verbose) unlink(csv_file) out - } #' Extract Tetramer Data from the CTD API @@ -198,8 +199,6 @@ extr_tetramer <- function( verify_ssl = FALSE, verbose = TRUE, ...) { - - if (missing(chem)) { cli::cli_abort("The argument {.field {chem}} is required.") } @@ -234,7 +233,7 @@ extr_tetramer <- function( ) } - check_na_warn(dat = out,col_to_check = "gene_id", verbose = verbose) + check_na_warn(dat = out, col_to_check = "gene_id", verbose = verbose) out } @@ -254,7 +253,6 @@ extr_tetramer_ <- function( verify_ssl = FALSE, verbose = verbose, ...) { - # Define the base URL base_url <- "https://ctdbase.org/query.go" @@ -330,5 +328,3 @@ extr_tetramer_ <- function( out } - - diff --git a/R/extr_ice.R b/R/extr_ice.R index 430a174..45faf9d 100644 --- a/R/extr_ice.R +++ b/R/extr_ice.R @@ -60,11 +60,13 @@ extr_ice <- function(casrn, check_status_code(resp, verbose = verbose) # This is used in case no results are retrieved in next chunk - col_names <- c("assay", "endpoint", "substance_type", "casrn", "qsar_ready_id", - "value", "unit", "species", "receptor_species", "route", "sex", - "strain", "life_stage", "tissue", "lesion", "location", - "assay_source", "in_vitro_assay_format", "reference", - "reference_url", "dtxsid", "substance_name", "pubmed_id") + col_names <- c( + "assay", "endpoint", "substance_type", "casrn", "qsar_ready_id", + "value", "unit", "species", "receptor_species", "route", "sex", + "strain", "life_stage", "tissue", "lesion", "location", + "assay_source", "in_vitro_assay_format", "reference", + "reference_url", "dtxsid", "substance_name", "pubmed_id" + ) out <- stats::setNames(as.data.frame(matrix(ncol = length(col_names), nrow = 0)), col_names) @@ -78,7 +80,7 @@ extr_ice <- function(casrn, }, error = function(e) { if (grepl("Unexpected content type \"text/plain\"", e$message)) { - if(isTRUE(verbose)){ + if (isTRUE(verbose)) { cli::cli_warn("It seems that the ids were not found in ICE: {conditionMessage(e)}") } @@ -112,14 +114,16 @@ extr_ice <- function(casrn, ids_founds <- casrn[casrn %in% out$casrn] if (nrow(out) > 0) { - out[, "query"] <- paste(ids_founds, collapse = ", ") - to_add <- stats::setNames(data.frame(matrix(ncol = ncol(out), - nrow = length(ids_not_found))), - names(out)) + to_add <- stats::setNames( + data.frame(matrix( + ncol = ncol(out), + nrow = length(ids_not_found) + )), + names(out) + ) to_add$query <- ids_not_found out <- rbind(to_add, out) - } else { out[1:length(casrn), "query"] <- casrn } diff --git a/R/extr_iris.R b/R/extr_iris.R index 141fbe8..5b56cb3 100644 --- a/R/extr_iris.R +++ b/R/extr_iris.R @@ -15,12 +15,11 @@ #' extr_iris(c("1332-21-4", "50-00-0")) #' } extr_iris <- function(casrn = NULL, verbose = TRUE) { + cancer_types <- c("non_cancer", "cancer") - cancer_types <- c("non_cancer", "cancer") - - if (missing(casrn)) { - cli::cli_abort("The argument {.field {casrn}} is required.") - } + if (missing(casrn)) { + cli::cli_abort("The argument {.field {casrn}} is required.") + } # Check if online check_internet(verbose = verbose) diff --git a/R/extr_monograph.R b/R/extr_monograph.R index 97c43be..e96fba9 100644 --- a/R/extr_monograph.R +++ b/R/extr_monograph.R @@ -5,19 +5,19 @@ #' #' @param search_type A character string specifying the type of search to #' perform. Valid options are "cas_rn" (CAS Registry Number) and "name" -#'. (name of the chemical). If `search_type` is "casrn", the function filters -#'. by the CAS Registry Number. +#' . (name of the chemical). If `search_type` is "casrn", the function filters +#' . by the CAS Registry Number. #' If `search_type` is "name", the function performs a partial match search #' for the chemical name. #' @param ids A character vector of IDs to search for. #' @param verbose A logical value indicating whether to print detailed messages. -#'. Default is TRUE. +#' . Default is TRUE. #' @param get_all Logical. If TRUE ignore all the other ignore `ids`, #' `search_type`, set `force = TRUE` and get the all dataset. #' This is was introduced for debugging purposes. #' @return A data frame containing the relevant information from the WHO IARC, -#'. including Monograph `volume`, `volume_publication_year`, `evaluation_year`, -#'. and `additional_information` where the chemical was described. +#' . including Monograph `volume`, `volume_publication_year`, `evaluation_year`, +#' . and `additional_information` where the chemical was described. #' @seealso \url{https://monographs.iarc.who.int/list-of-classifications/} #' @export #' @examples @@ -26,17 +26,17 @@ #' str(dat) #' #' # Example usage for name search -#' dat2 <- extr_monograph(search_type = "name", -#' ids = c("Aloe", "Schistosoma", -#'. "Styrene") -#'. ) +#' dat2 <- extr_monograph( +#' search_type = "name", +#' ids = c("Aloe", "Schistosoma", "Styrene") +#' ) #' str(dat2) #' } extr_monograph <- function(ids, - search_type ="casrn", + search_type = "casrn", verbose = TRUE, get_all = FALSE) { - if(isTRUE(get_all)) { + if (isTRUE(get_all)) { return(who_iarc_monographs) } @@ -54,16 +54,17 @@ extr_monograph <- function(ids, cli::cli_alert_info("Extracting WHO IARC monographs...\nLast updated: 2024-11-29 5:08pm (CET)") } - col_names <- c(names(who_iarc_monographs), "query") + col_names <- c(names(who_iarc_monographs), "query") - out <- search_and_match(dat = who_iarc_monographs, - ids = ids, - search_type = search_type, - col_names = col_names, - chemical_col = "agent" - ) + out <- search_and_match( + dat = who_iarc_monographs, + ids = ids, + search_type = search_type, + col_names = col_names, + chemical_col = "agent" + ) - check_na_warn(dat = out, col_to_check = "agent", verbose = verbose) + check_na_warn(dat = out, col_to_check = "agent", verbose = verbose) out } diff --git a/R/extr_pprtv.R b/R/extr_pprtv.R index a9ff8b4..8fbba6d 100644 --- a/R/extr_pprtv.R +++ b/R/extr_pprtv.R @@ -31,8 +31,10 @@ #' extr_pprtv(ids = "107-02-8", search_type = "casrn", verbose = TRUE) #' #' # Extract data for a chemical name -#' extr_pprtv(ids = "Acrolein", search_type = "name", verbose = TRUE, -#' force = FALSE) +#' extr_pprtv( +#' ids = "Acrolein", search_type = "name", verbose = TRUE, +#' force = FALSE +#' ) #' #' # Extract data for multiple identifiers #' extr_pprtv( @@ -45,13 +47,11 @@ #' } extr_pprtv <- function(ids, search_type = "casrn", verbose = TRUE, force = TRUE, get_all = FALSE) { - - if (all(missing(ids), !isTRUE(get_all))) { cli::cli_abort("The argument {.field ids} is required.") } - if (all(!search_type %in% c("casrn", "name"),!isTRUE(get_all))) { + if (all(!search_type %in% c("casrn", "name"), !isTRUE(get_all))) { cli::cli_abort("The argument {.field search_type} needs to be either `casrn` or `name`.") } @@ -59,9 +59,12 @@ extr_pprtv <- function(ids, search_type = "casrn", verbose = TRUE, force = TRUE, file_name <- "epa_pprtvs.rds" # Filename for caching # Check if path is present otherwise it download it again - full_path_cache_file <- fs::path(tools::R_user_dir("extractox", - which = "cache"), - file_name) + full_path_cache_file <- fs::path( + tools::R_user_dir("extractox", + which = "cache" + ), + file_name + ) cache_present <- fs::file_exists(full_path_cache_file) @@ -75,12 +78,14 @@ extr_pprtv <- function(ids, search_type = "casrn", verbose = TRUE, force = TRUE, url = "https://cfpub.epa.gov/ncea/pprtv/atoz.cfm", url_query_param = list(excel = "yes"), file_name = file_name, - verbose = verbose) - - # get eveything - if (get_all == TRUE) return(dat) - path_cache <- save_to_cache(dat, file_name, verbose = verbose) + verbose = verbose + ) + # get eveything + if (get_all == TRUE) { + return(dat) + } + path_cache <- save_to_cache(dat, file_name, verbose = verbose) } else { dat <- read_from_cache(file_name = file_name, verbose = verbose) @@ -95,20 +100,21 @@ extr_pprtv <- function(ids, search_type = "casrn", verbose = TRUE, force = TRUE, cli::cli_alert_info("Extracting EPA PPRTVs.") } - col_names <- c("pprtv_substance_id", "chemical", "casrn", "last_revision", - "pprtv_assessment", "iris_link", "rf_c_value", "rf_d_value", - "woe", "date_downloaded", "query") + col_names <- c( + "pprtv_substance_id", "chemical", "casrn", "last_revision", + "pprtv_assessment", "iris_link", "rf_c_value", "rf_d_value", + "woe", "date_downloaded", "query" + ) out <- search_and_match( - dat = dat, - ids = ids, - search_type = search_type, - col_names = col_names, - chemical_col = "chemical" - ) + dat = dat, + ids = ids, + search_type = search_type, + col_names = col_names, + chemical_col = "chemical" + ) - check_na_warn(dat = out, col_to_check = "chemical", verbose = verbose) + check_na_warn(dat = out, col_to_check = "chemical", verbose = verbose) out - } diff --git a/R/extr_pubchem.R b/R/extr_pubchem.R index 2a7da1e..ac4c777 100644 --- a/R/extr_pubchem.R +++ b/R/extr_pubchem.R @@ -8,23 +8,25 @@ #' @keywords internal #' @noRd create_na_df <- function(missing_chem) { - column_names <- c("cid", "iupac_name", "casrn", "cid_all", "casrn_all", - "molecular_formula", "molecular_weight", "canonical_smiles", - "isomeric_smiles", "inchi", "inchi_key", "iupac_name", - "x_log_p", "exact_mass", "monoisotopic_mass", "tpsa", - "complexity", "charge", "h_bond_donor_count", - "h_bond_acceptor_count", "rotatable_bond_count", - "heavy_atom_count", "isotope_atom_count", "atom_stereo_count", - "defined_atom_stereo_count", "undefined_atom_stereo_count", - "bond_stereo_count", "defined_bond_stereo_count", - "undefined_bond_stereo_count", "covalent_unit_count", - "volume3d", "x_steric_quadrupole3d", "y_steric_quadrupole3d", - "z_steric_quadrupole3d", "feature_count3d", - "feature_acceptor_count3d", "feature_donor_count3d", - "feature_anion_count3d", "feature_cation_count3d", - "feature_ring_count3d", "feature_hydrophobe_count3d", - "conformer_model_rmsd3d", "effective_rotor_count3d", - "conformer_count3d", "fingerprint2d", "query") + column_names <- c( + "cid", "iupac_name", "casrn", "cid_all", "casrn_all", + "molecular_formula", "molecular_weight", "canonical_smiles", + "isomeric_smiles", "inchi", "inchi_key", "iupac_name", + "x_log_p", "exact_mass", "monoisotopic_mass", "tpsa", + "complexity", "charge", "h_bond_donor_count", + "h_bond_acceptor_count", "rotatable_bond_count", + "heavy_atom_count", "isotope_atom_count", "atom_stereo_count", + "defined_atom_stereo_count", "undefined_atom_stereo_count", + "bond_stereo_count", "defined_bond_stereo_count", + "undefined_bond_stereo_count", "covalent_unit_count", + "volume3d", "x_steric_quadrupole3d", "y_steric_quadrupole3d", + "z_steric_quadrupole3d", "feature_count3d", + "feature_acceptor_count3d", "feature_donor_count3d", + "feature_anion_count3d", "feature_cation_count3d", + "feature_ring_count3d", "feature_hydrophobe_count3d", + "conformer_model_rmsd3d", "effective_rotor_count3d", + "conformer_count3d", "fingerprint2d", "query" + ) # Create the dataframe with all NAs out <- data.frame(matrix(NA, nrow = length(missing_chem), ncol = length(column_names))) @@ -60,7 +62,6 @@ create_na_df <- function(missing_chem) { #' extr_casrn_from_cid(cids) #' } extr_casrn_from_cid <- function(pubchem_ids, verbose = TRUE) { - if (missing(pubchem_ids)) { cli::cli_abort("The argument {.field pubchem_ids} is required.") } @@ -75,11 +76,13 @@ extr_casrn_from_cid <- function(pubchem_ids, verbose = TRUE) { col_names <- c("cid", "iupac_name", "casrn", "source_name", "source_id", "query") - if(ncol(casrn_data) == 0) { - casrn_data <- stats::setNames(as.data.frame( - matrix(ncol = length(col_names), nrow = length(pubchem_ids)) - ), - col_names) + if (ncol(casrn_data) == 0) { + casrn_data <- stats::setNames( + as.data.frame( + matrix(ncol = length(col_names), nrow = length(pubchem_ids)) + ), + col_names + ) casrn_data$query <- pubchem_ids } else { names(casrn_data) <- col_names @@ -116,7 +119,6 @@ extr_casrn_from_cid <- function(pubchem_ids, verbose = TRUE) { #' extr_chem_info(iupac_names = c("Formaldehyde", "Aflatoxin B1")) #' } extr_chem_info <- function(iupac_names, verbose = TRUE) { - if (missing(iupac_names)) { cli::cli_abort("The argument {.field {iupac_names}} is required.") } @@ -125,7 +127,7 @@ extr_chem_info <- function(iupac_names, verbose = TRUE) { iupac_cid <- webchem::get_cid(iupac_names, domain = "compound", verbose = verbose) - if(all(is.na(iupac_cid$cid))){ + if (all(is.na(iupac_cid$cid))) { out <- create_na_df(missing_chem = iupac_names) return(out) } @@ -188,7 +190,6 @@ extr_chem_info <- function(iupac_names, verbose = TRUE) { #' extr_pubchem_fema(c("83-67-0", "1490-04-6")) #' } extr_pubchem_fema <- function(casrn, verbose = TRUE) { - extr_pubchem_section(casrn, section = "FEMA Flavor Profile", verbose = verbose) } @@ -232,7 +233,7 @@ extr_pubchem_section <- function(casrn, section, verbose = TRUE) { extr_pubchem_section_(cas, section, verbose) }) - out <- do.call(rbind, dat) + out <- do.call(rbind, dat) check_na_warn(dat = out, col_to_check = "IUPAC_name", verbose = verbose) out } @@ -245,7 +246,6 @@ extr_pubchem_section <- function(casrn, section, verbose = TRUE) { #' @noRd #' @keywords internal extr_pubchem_section_ <- function(casrn, section, verbose = TRUE) { - dat_cid <- webchem::get_cid(casrn, match = "first", verbose = verbose) col_out <- c( @@ -261,7 +261,6 @@ extr_pubchem_section_ <- function(casrn, section, verbose = TRUE) { # Handle no CID retrieved if (is.na(dat_cid$cid)) { - names_casrn <- webchem::pc_sect(dat_cid$cid, "Depositor-Supplied Synonyms") na_matrix <- matrix(NA, nrow = 1, ncol = length(col_out)) out_df <- as.data.frame(na_matrix) @@ -279,7 +278,6 @@ extr_pubchem_section_ <- function(casrn, section, verbose = TRUE) { # Handle empty results for section if (ncol(dat_section) == 0) { - name_casrn <- webchem::pc_sect(dat_cid$cid, "Depositor-Supplied Synonyms") na_matrix <- matrix(NA, nrow = 1, ncol = length(col_out)) out_df <- as.data.frame(na_matrix) diff --git a/R/extr_tox.R b/R/extr_tox.R index 8f9765d..7e4978c 100644 --- a/R/extr_tox.R +++ b/R/extr_tox.R @@ -6,29 +6,42 @@ #' #' Specifically, this function: #' \itemize{ -#' \item Calls \code{\link{extr_monograph}} to return monographs informations from WHO IARC. -#' \item Calls \code{\link{extr_pubchem_ghs}} to retrieve GHS classification data from PubChem. +#' \item Calls \code{\link{extr_monograph}} to return monographs informations +#' from WHO IARC. +#' \item Calls \code{\link{extr_pubchem_ghs}} to retrieve GHS classification +#' data from PubChem. #' \item Calls \code{\link{extr_ice}} to gather assay data from the ICE database. -#' \item Calls \code{\link{extr_iris}} to retrieve risk assessment information from the IRIS database. -#' \item Calls \code{\link{extr_comptox}} to retrieve data from the CompTox Chemicals Dashboard. +#' \item Calls \code{\link{extr_iris}} to retrieve risk assessment information +#' from the IRIS database. +#' \item Calls \code{\link{extr_comptox}} to retrieve data from the CompTox +#' Chemicals Dashboard. #' } -#' @param casrn A character vector of CAS Registry Numbers (CASRN) representing the chemicals of interest. -#' @param verbose A logical value indicating whether to print detailed messages. Default is TRUE. -#' @return A list of data frames containing toxicological information retrieved from each database: +#' @param casrn A character vector of CAS Registry Numbers (CASRN) representing +#' the chemicals of interest. +#' @param verbose A logical value indicating whether to print detailed messages. +#' Default is TRUE. +#' @param force Logical indicating whether to force a fresh download of the EPA +#' PPRTV database. Default is TRUE. +#' @return A list of data frames containing toxicological information retrieved +#' from each database: #' \describe{ -#' \item{who_iarc_monographs}{Lists if any, the WHO IARC monographs related to that chemical.} -#' \item{ghs_dat}{Toxicity data from PubChem's Globally Harmonized System (GHS) classification.} -#' \item{ice_dat}{Assay data from the Integrated Chemical Environment (ICE) database.} +#' \item{who_iarc_monographs}{Lists if any, the WHO IARC monographs related +#' to that chemical.} +#' \item{pprtv}{Risk assessment data from the EPA PPRTV} +#' \item{ghs_dat}{Toxicity data from PubChem's Globally Harmonized System (GHS) +#' classification.} +#' \item{ice_dat}{Assay data from the Integrated Chemical Environment (ICE) +#' database.} #' \item{iris}{Risk assessment data from the IRIS database.} -#' \item{iris}{Risk assessment data from the IRIS database.} -#' \item{comptox_list}{List of dataframe with toxicity information from the CompTox Chemicals Dashboard.} +#' \item{comptox_list}{List of dataframe with toxicity information +#' from the CompTox Chemicals Dashboard.} #' } #' @export #' @examples #' \donttest{ #' extr_tox(casrn = c("100-00-5", "107-02-8")) #' } -extr_tox <- function(casrn, verbose = TRUE) { +extr_tox <- function(casrn, verbose = TRUE, force = TRUE) { if (missing(casrn)) { cli::cli_abort("The argument {.field {casrn}} is required.") } @@ -47,9 +60,16 @@ extr_tox <- function(casrn, verbose = TRUE) { iris_filt <- extr_iris(casrn = casrn, verbose = verbose) - extracted_monographs <- extr_monograph(ids = casrn, search_type = "casrn", verbose = verbose) + extracted_monographs <- extr_monograph(ids = casrn, search_type = "casrn", + verbose = verbose) + + extracted_pprtv <- extr_pprtv(ids = casrn, verbose = verbose) - list_1 <- list(who_iarc_monographs = extracted_monographs, ghs_dat = ghs_dat, iris = iris_filt, ice = ice_dat) + list_1 <- list(who_iarc_monographs = extracted_monographs, + pprtv = extracted_pprtv, + ghs_dat = ghs_dat, + iris = iris_filt, + ice = ice_dat) out <- c(list_1, comptox_list) out } diff --git a/R/other.R b/R/other.R index 931b95e..c7205a6 100644 --- a/R/other.R +++ b/R/other.R @@ -1,4 +1,3 @@ - #' Selection of assays of iris #' @keywords internal diff --git a/R/utils.R b/R/utils.R index d193afb..2989e21 100644 --- a/R/utils.R +++ b/R/utils.R @@ -111,7 +111,8 @@ search_and_match <- function(dat, ids, search_type, col_names, chemical_col = "c # Add NA rows for missing ids out <- merge(data.frame(query = ids, stringsAsFactors = FALSE), out, - by = "query", all.x = TRUE) + by = "query", all.x = TRUE + ) out <- out[, col_names] return(out) @@ -172,4 +173,3 @@ write_dataframes_to_excel <- function(df_list, filename) { openxlsx::saveWorkbook(wb, filename, overwrite = TRUE) cli::cli_alert_info("Excell file written in {filename}...") } - diff --git a/man/extr_casrn_from_cid.Rd b/man/extr_casrn_from_cid.Rd index a645b32..6ace071 100644 --- a/man/extr_casrn_from_cid.Rd +++ b/man/extr_casrn_from_cid.Rd @@ -4,10 +4,10 @@ \alias{extr_casrn_from_cid} \title{Retrieve CASRN for PubChem CIDs} \usage{ -extr_casrn_from_cid(pubchem_id, verbose = TRUE) +extr_casrn_from_cid(pubchem_ids, verbose = TRUE) } \arguments{ -\item{pubchem_id}{A numeric vector of PubChem CIDs. These are unique identifiers +\item{pubchem_ids}{A numeric vector of PubChem CIDs. These are unique identifiers for chemical compounds in the PubChem database.} \item{verbose}{A logical value indicating whether to print detailed messages. Default is TRUE.} @@ -17,8 +17,9 @@ A data frame containing the CID, CASRN, and IUPAC name of the compound. The returned data frame includes three columns: \describe{ \item{CID}{The PubChem Compound Identifier.} -\item{cas_rn}{The corresponding CASRN of the compound.} -\item{IUPACName}{The IUPAC name of the compound.} +\item{casrn}{The corresponding CASRN of the compound.} +\item{iupac_name}{The IUPAC name of the compound.} +\item{query}{The pubchem_id queried.} } } \description{ diff --git a/man/extr_chem_info.Rd b/man/extr_chem_info.Rd index 8992ffc..811c7d1 100644 --- a/man/extr_chem_info.Rd +++ b/man/extr_chem_info.Rd @@ -4,10 +4,10 @@ \alias{extr_chem_info} \title{Query Chemical Information from IUPAC Names} \usage{ -extr_chem_info(IUPAC_names, verbose = TRUE) +extr_chem_info(iupac_names, verbose = TRUE) } \arguments{ -\item{IUPAC_names}{A character vector of IUPAC names. These are standardized names +\item{iupac_names}{A character vector of IUPAC names. These are standardized names of chemical compounds that will be used to search in the PubChem database.} \item{verbose}{A logical value indicating whether to print detailed messages. Default is TRUE.} @@ -29,6 +29,6 @@ a unique row with the CID, CASRN, and additional chemical properties. \examples{ \donttest{ # Example with formaldehyde and aflatoxin -extr_chem_info(IUPAC_names = c("Formaldehyde", "Aflatoxin B1")) +extr_chem_info(iupac_names = c("Formaldehyde", "Aflatoxin B1")) } } diff --git a/man/extr_ice.Rd b/man/extr_ice.Rd index 9c0a8b2..66ccc1e 100644 --- a/man/extr_ice.Rd +++ b/man/extr_ice.Rd @@ -9,21 +9,25 @@ extr_ice(casrn, assays = NULL, verify_ssl = FALSE, verbose = TRUE, ...) \arguments{ \item{casrn}{A character vector specifying the CASRNs for the search.} -\item{assays}{A character vector specifying the assays to include in the search. Default is NULL, -meaning all assays are included. If you don't know the exact assay name, you can use the -\code{extr_ice_assay_names()} function to search for assay names that match a pattern you're interested in.} +\item{assays}{A character vector specifying the assays to include in the +search. Default is NULL, meaning all assays are included. If you don't +know the exact assay name, you can use the \code{extr_ice_assay_names()} +function to search for assay names that match a pattern you're interested in.} \item{verify_ssl}{Boolean to control of SSL should be verified or not.} -\item{verbose}{A logical value indicating whether to print detailed messages. Default is TRUE.} +\item{verbose}{A logical value indicating whether to print detailed messages. +Default is TRUE.} -\item{...}{Any other arguments to be supplied to \code{req_option} and thus to \code{libcurl}.} +\item{...}{Any other arguments to be supplied to \code{req_option} and +thus to \code{libcurl}.} } \value{ A data frame containing the extracted data from the ICE API. } \description{ -The \code{extr_ice} function sends a POST request to the ICE API to search for information based on specified chemical IDs and assays. +The \code{extr_ice} function sends a POST request to the ICE API to search for +information based on specified chemical IDs and assays. } \examples{ \donttest{ diff --git a/man/extr_ice_assay_names.Rd b/man/extr_ice_assay_names.Rd index 0d46865..beff391 100644 --- a/man/extr_ice_assay_names.Rd +++ b/man/extr_ice_assay_names.Rd @@ -4,11 +4,14 @@ \alias{extr_ice_assay_names} \title{Extract Assay Names from the ICE Database} \usage{ -extr_ice_assay_names(regex = NULL) +extr_ice_assay_names(regex = NULL, verbose = TRUE) } \arguments{ \item{regex}{A character string containing the regular expression to search for, or \code{NULL} to retrieve all assay names.} + +\item{verbose}{A logical value indicating whether to print detailed messages. +Default is TRUE.} } \value{ A character vector of matching assay names. diff --git a/man/extr_iris.Rd b/man/extr_iris.Rd index d8dc533..9b4433d 100644 --- a/man/extr_iris.Rd +++ b/man/extr_iris.Rd @@ -4,24 +4,20 @@ \alias{extr_iris} \title{Extract Data from EPA IRIS Database} \usage{ -extr_iris( - casrn = NULL, - cancer_types = c("non_cancer", "cancer"), - verbose = TRUE -) +extr_iris(casrn = NULL, verbose = TRUE) } \arguments{ \item{casrn}{A vector CASRN for the search.} -\item{cancer_types}{A character vector specifying the types of cancer to include in the search. Must be either "non_cancer" or "cancer".} - -\item{verbose}{A logical value indicating whether to print detailed messages. Default is TRUE.} +\item{verbose}{A logical value indicating whether to print detailed messages. +Default is TRUE.} } \value{ A data frame containing the extracted data. } \description{ -The \code{extr_iris} function sends a request to the EPA IRIS database to search for information based on a specified keywords and cancer types. It retrieves and parses the HTML content from the response. +The \code{extr_iris} function sends a request to the EPA IRIS database to search +for information based on a specified keywords and cancer types. It retrieves and parses the HTML content from the response. Note that if \code{keywords} is not provide all dataset are retrieved. } \examples{ diff --git a/man/extr_monograph.Rd b/man/extr_monograph.Rd index cfa403f..7571537 100644 --- a/man/extr_monograph.Rd +++ b/man/extr_monograph.Rd @@ -4,20 +4,29 @@ \alias{extr_monograph} \title{Retrieve WHO IARC Monograph Information} \usage{ -extr_monograph(ids, search_type = "casrn", verbose = TRUE) +extr_monograph(ids, search_type = "casrn", verbose = TRUE, get_all = FALSE) } \arguments{ \item{ids}{A character vector of IDs to search for.} -\item{search_type}{A character string specifying the type of search to perform. Valid options are "cas_rn" (CAS Registry Number) -and "name" (name of the chemical). If \code{search_type} is "casrn", the function filters by the CAS Registry Number. -If \code{search_type} is "name", the function performs a partial match search for the chemical name.} +\item{search_type}{A character string specifying the type of search to +perform. Valid options are "cas_rn" (CAS Registry Number) and "name" +. (name of the chemical). If \code{search_type} is "casrn", the function filters +. by the CAS Registry Number. +If \code{search_type} is "name", the function performs a partial match search +for the chemical name.} -\item{verbose}{A logical value indicating whether to print detailed messages. Default is TRUE.} +\item{verbose}{A logical value indicating whether to print detailed messages. +. Default is TRUE.} + +\item{get_all}{Logical. If TRUE ignore all the other ignore \code{ids}, +\code{search_type}, set \code{force = TRUE} and get the all dataset. +This is was introduced for debugging purposes.} } \value{ -A data frame containing the relevant information from the WHO IARC, including Monograph \code{volume}, \code{volume_publication_year}, -\code{evaluation_year}, and \code{additional_information} where the chemical was described. +A data frame containing the relevant information from the WHO IARC, +. including Monograph \code{volume}, \code{volume_publication_year}, \code{evaluation_year}, +. and \code{additional_information} where the chemical was described. } \description{ This function retrieves information regarding Monographs from the World Health Organization (WHO) International @@ -29,7 +38,10 @@ Agency for Research on Cancer (IARC) based on CAS Registry Number or Name of th str(dat) # Example usage for name search - dat2 <- extr_monograph(search_type = "name", ids = c("Aloe", "Schistosoma", "Styrene")) + dat2 <- extr_monograph(search_type = "name", + ids = c("Aloe", "Schistosoma", +. "Styrene") +. ) str(dat2) } } diff --git a/man/extr_pprtv.Rd b/man/extr_pprtv.Rd index 5a4eee3..7758ff9 100644 --- a/man/extr_pprtv.Rd +++ b/man/extr_pprtv.Rd @@ -4,26 +4,44 @@ \alias{extr_pprtv} \title{Extract Data from EPA PPRTVs} \usage{ -extr_pprtv(ids, search_type = "casrn", verbose = TRUE, force = TRUE) +extr_pprtv( + ids, + search_type = "casrn", + verbose = TRUE, + force = TRUE, + get_all = FALSE +) } \arguments{ -\item{ids}{Character vector of identifiers to search (e.g., CASRN or chemical names).} +\item{ids}{Character vector of identifiers to search (e.g., CASRN or chemical +names).} -\item{search_type}{Character string specifying the type of identifier: "casrn" or "name". -Default is "casrn". If \code{search_type} is "name", the function performs a partial match search for the chemical name.} +\item{search_type}{Character string specifying the type of identifier: "casrn" +or "name". +Default is "casrn". If \code{search_type} is "name", the function performs a +partial match search for the chemical name. NOTE: Since partial mached is +use, multiple seraches might match the same chemical, therefore chemical ids +might not be uniques.} -\item{verbose}{Logical indicating whether to display progress messages. Default is TRUE.} +\item{verbose}{Logical indicating whether to display progress messages. +Default is TRUE.} -\item{force}{Logical indicating whether to force a fresh download of the database. Default is TRUE.} +\item{force}{Logical indicating whether to force a fresh download of the +database. Default is TRUE.} + +\item{get_all}{Logical. If TRUE ignore all the other ignore \code{ids}, +\code{search_type}, set \code{force = TRUE} and get the all dataset. +This is was introduced for debugging purposes.} } \value{ -A data frame with extracted information matching the specified identifiers, -or NULL if no matches are found. +A data frame with extracted information matching the specified +identifiers, or NULL if no matches are found. } \description{ Extracts data for specified identifiers (CASRN or chemical names) from the EPA's -Provisional Peer-Reviewed Toxicity Values (PPRTVs) database. The function retrieves -and processes data, with options to use cached files or force a fresh download. +Provisional Peer-Reviewed Toxicity Values (PPRTVs) database. The function +retrieves and processes data, with options to use cached files or force a +fresh download. } \examples{ \donttest{ @@ -32,7 +50,8 @@ with_extr_sandbox({ # this is to write on tempdir as for CRAN policies extr_pprtv(ids = "107-02-8", search_type = "casrn", verbose = TRUE) # Extract data for a chemical name - extr_pprtv(ids = "Acrolein", search_type = "name", verbose = TRUE, force = FALSE) + extr_pprtv(ids = "Acrolein", search_type = "name", verbose = TRUE, + force = FALSE) # Extract data for multiple identifiers extr_pprtv( diff --git a/man/extr_pubchem_fema.Rd b/man/extr_pubchem_fema.Rd index a8b663c..c1fdf1b 100644 --- a/man/extr_pubchem_fema.Rd +++ b/man/extr_pubchem_fema.Rd @@ -9,13 +9,17 @@ extr_pubchem_fema(casrn, verbose = TRUE) \arguments{ \item{casrn}{A vector of CAS Registry Numbers (CASRN) as atomic vectors.} -\item{verbose}{A logical value indicating whether to print detailed messages. Default is TRUE.} +\item{verbose}{A logical value indicating whether to print detailed messages. +Default is TRUE.} } \value{ -A data frame containing the FEMA flavor profile information for each CASRN. If no information is found for a particular CASRN, the output will include a row indicating this. +A data frame containing the FEMA flavor profile information for each +CASRN. If no information is found for a particular CASRN, the output will include a row indicating this. } \description{ -This function retrieves FEMA (Flavor and Extract Manufacturers Association) flavor profile information for a list of CAS Registry Numbers (CASRN) from the PubChem database using the \code{webchem} package. It applies the function \code{extr_fema_pubchem_} to each CASRN in the input vector and combines the results into a single data frame. +This function retrieves FEMA (Flavor and Extract Manufacturers Association) +flavor profile information for a list of CAS Registry Numbers (CASRN) from +the PubChem database using the \code{webchem} package. } \examples{ \donttest{ diff --git a/man/search_and_match.Rd b/man/search_and_match.Rd new file mode 100644 index 0000000..781306b --- /dev/null +++ b/man/search_and_match.Rd @@ -0,0 +1,33 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/utils.R +\name{search_and_match} +\alias{search_and_match} +\title{Search and Match Data} +\usage{ +search_and_match(dat, ids, search_type, col_names, chemical_col = "chemical") +} +\arguments{ +\item{dat}{The dataframe to be searched.} + +\item{ids}{A vector of ids to search for.} + +\item{search_type}{The type of search: "casrn" or "name".} + +\item{col_names}{Column names to be used when creating a new dataframe in case of no matches.} + +\item{chemical_col}{The name of the column in dat where chemical names are stored.} +} +\value{ +A dataframe with search results. +} +\description{ +This function searches for matches in a dataframe based on a given list of ids and search type, +then combines the results into a single dataframe, making sure that NA rows are added for any missing ids. +The column \code{query} is a the end of the dataframe. +} +\details{ +This function is used in \code{extr_pprtv} and \code{extr_monograph}. +} +\seealso{ +\code{\link{extr_pprtv}}, \code{\link{extr_monograph}} +} diff --git a/man/with_extr_sandbox.Rd b/man/with_extr_sandbox.Rd index a49171d..c6a4d5c 100644 --- a/man/with_extr_sandbox.Rd +++ b/man/with_extr_sandbox.Rd @@ -4,10 +4,12 @@ \alias{with_extr_sandbox} \title{Run Code in a Temporary Sandbox Environment} \usage{ -with_extr_sandbox(code) +with_extr_sandbox(code, temp_dir = tempdir()) } \arguments{ \item{code}{The code to be executed inside the sandbox. Should be an expression.} + +\item{temp_dir}{A temporary directory created using \code{temdir()}.} } \value{ The result of the executed code. diff --git a/tests/testthat/_snaps/tox.md b/tests/testthat/_snaps/tox.md new file mode 100644 index 0000000..f675ddb --- /dev/null +++ b/tests/testthat/_snaps/tox.md @@ -0,0 +1,3341 @@ +# extr_tox fetches data for CASRN 50-00-0 + + Code + result[!names(result) %in% "comptox_cover_sheet"] + Output + $who_iarc_monographs + casrn agent group volume volume_publication_year + 1 50-00-0 Formaldehyde 1 Sup 7, 62, 88, 100F 2012 + evaluation_year additional_information query + 1 2009 50-00-0 + + $ghs_dat + cid casrn IUPAC_name + 1 712 50-00-0 Formaldehyde + 2 712 50-00-0 Formaldehyde + 3 712 50-00-0 Formaldehyde + 4 712 50-00-0 Formaldehyde + 5 712 50-00-0 Formaldehyde + 6 712 50-00-0 Formaldehyde + 7 712 50-00-0 Formaldehyde + 8 712 50-00-0 Formaldehyde + 9 712 50-00-0 Formaldehyde + 10 712 50-00-0 Formaldehyde + 11 712 50-00-0 Formaldehyde + 12 712 50-00-0 Formaldehyde + 13 712 50-00-0 Formaldehyde + 14 712 50-00-0 Formaldehyde + 15 712 50-00-0 Formaldehyde + 16 712 50-00-0 Formaldehyde + 17 712 50-00-0 Formaldehyde + 18 712 50-00-0 Formaldehyde + 19 712 50-00-0 Formaldehyde + 20 712 50-00-0 Formaldehyde + 21 712 50-00-0 Formaldehyde + 22 712 50-00-0 Formaldehyde + 23 712 50-00-0 Formaldehyde + 24 712 50-00-0 Formaldehyde + 25 712 50-00-0 Formaldehyde + 26 712 50-00-0 Formaldehyde + 27 712 50-00-0 Formaldehyde + 28 712 50-00-0 Formaldehyde + 29 712 50-00-0 Formaldehyde + 30 712 50-00-0 Formaldehyde + 31 712 50-00-0 Formaldehyde + 32 712 50-00-0 Formaldehyde + 33 712 50-00-0 Formaldehyde + 34 712 50-00-0 Formaldehyde + 35 712 50-00-0 Formaldehyde + 36 712 50-00-0 Formaldehyde + 37 712 50-00-0 Formaldehyde + 38 712 50-00-0 Formaldehyde + 39 712 50-00-0 Formaldehyde + 40 712 50-00-0 Formaldehyde + 41 712 50-00-0 Formaldehyde + 42 712 50-00-0 Formaldehyde + 43 712 50-00-0 Formaldehyde + 44 712 50-00-0 Formaldehyde + 45 712 50-00-0 Formaldehyde + 46 712 50-00-0 Formaldehyde + 47 712 50-00-0 Formaldehyde + 48 712 50-00-0 Formaldehyde + 49 712 50-00-0 Formaldehyde + 50 712 50-00-0 Formaldehyde + 51 712 50-00-0 Formaldehyde + 52 712 50-00-0 Formaldehyde + 53 712 50-00-0 Formaldehyde + 54 712 50-00-0 Formaldehyde + 55 712 50-00-0 Formaldehyde + 56 712 50-00-0 Formaldehyde + 57 712 50-00-0 Formaldehyde + 58 712 50-00-0 Formaldehyde + 59 712 50-00-0 Formaldehyde + 60 712 50-00-0 Formaldehyde + 61 712 50-00-0 Formaldehyde + 62 712 50-00-0 Formaldehyde + 63 712 50-00-0 Formaldehyde + 64 712 50-00-0 Formaldehyde + 65 712 50-00-0 Formaldehyde + 66 712 50-00-0 Formaldehyde + 67 712 50-00-0 Formaldehyde + 68 712 50-00-0 Formaldehyde + 69 712 50-00-0 Formaldehyde + 70 712 50-00-0 Formaldehyde + 71 712 50-00-0 Formaldehyde + 72 712 50-00-0 Formaldehyde + 73 712 50-00-0 Formaldehyde + 74 712 50-00-0 Formaldehyde + 75 712 50-00-0 Formaldehyde + 76 712 50-00-0 Formaldehyde + 77 712 50-00-0 Formaldehyde + 78 712 50-00-0 Formaldehyde + 79 712 50-00-0 Formaldehyde + 80 712 50-00-0 Formaldehyde + 81 712 50-00-0 Formaldehyde + 82 712 50-00-0 Formaldehyde + 83 712 50-00-0 Formaldehyde + 84 712 50-00-0 Formaldehyde + 85 712 50-00-0 Formaldehyde + 86 712 50-00-0 Formaldehyde + 87 712 50-00-0 Formaldehyde + 88 712 50-00-0 Formaldehyde + 89 712 50-00-0 Formaldehyde + 90 712 50-00-0 Formaldehyde + 91 712 50-00-0 Formaldehyde + 92 712 50-00-0 Formaldehyde + 93 712 50-00-0 Formaldehyde + 94 712 50-00-0 Formaldehyde + 95 712 50-00-0 Formaldehyde + 96 712 50-00-0 Formaldehyde + 97 712 50-00-0 Formaldehyde + 98 712 50-00-0 Formaldehyde + 99 712 50-00-0 Formaldehyde + 100 712 50-00-0 Formaldehyde + 101 712 50-00-0 Formaldehyde + result + 1 Pictograms displayed are for > 99.9% (6390 of 6393) of reports that indicate hazard statements. This chemical does not meet GHS hazard criteria for < 0.1% (3 of 6393) of reports. + 2 + 3 Danger + 4 H301 (83.3%): Toxic if swallowed [Danger Acute toxicity, oral] + 5 H311 (83.3%): Toxic in contact with skin [Danger Acute toxicity, dermal] + 6 H314 (83.3%): Causes severe skin burns and eye damage [Danger Skin corrosion/irritation] + 7 H317 (90.6%): May cause an allergic skin reaction [Warning Sensitization, Skin] + 8 H318 (48.2%): Causes serious eye damage [Danger Serious eye damage/eye irritation] + 9 H330 (13.6%): Fatal if inhaled [Danger Acute toxicity, inhalation] + 10 H331 (78%): Toxic if inhaled [Danger Acute toxicity, inhalation] + 11 H341 (18.6%): Suspected of causing genetic defects [Warning Germ cell mutagenicity] + 12 H350 (18.6%): May cause cancer [Danger Carcinogenicity] + 13 H351 (64.8%): Suspected of causing cancer [Warning Carcinogenicity] + 14 P203, P260, P261, P262, P264, P264+P265, P270, P271, P272, P280, P284, P301+P316, P301+P330+P331, P302+P352, P302+P361+P354, P304+P340, P305+P354+P338, P316, P317, P318, P320, P321, P330, P333+P317, P361+P364, P362+P364, P363, P403+P233, P405, and P501 + 15 (The corresponding statement to each P-code can be found at the GHS Classification page.) + 16 Aggregated GHS information provided per 6393 reports by companies from 97 notifications to the ECHA C&L Inventory. Each notification may be associated with multiple companies. + 17 Reported as not meeting GHS hazard criteria per 3 of 6393 reports by companies. For more detailed information, please visit ECHA C&L website. + 18 There are 96 notifications provided by 6390 of 6393 reports by companies with hazard statement code(s). + 19 Information may vary between notifications depending on impurities, additives, and other factors. The percentage value in parenthesis indicates the notified classification ratio from companies that provide hazard codes. Only hazard codes with percentage values above 10% are shown. + 20 + 21 Danger + 22 H301: Toxic if swallowed [Danger Acute toxicity, oral] + 23 H311: Toxic in contact with skin [Danger Acute toxicity, dermal] + 24 H314: Causes severe skin burns and eye damage [Danger Skin corrosion/irritation] + 25 H317: May cause an allergic skin reaction [Warning Sensitization, Skin] + 26 H330: Fatal if inhaled [Danger Acute toxicity, inhalation] + 27 H350i: May cause cancer by inhalation [Danger Carcinogenicity] + 28 H401: Toxic to aquatic life [Hazardous to the aquatic environment, acute hazard] + 29 P203, P260, P261, P262, P264, P270, P271, P272, P273, P280, P284, P301+P316, P301+P330+P331, P302+P352, P302+P361+P354, P304+P340, P305+P354+P338, P316, P318, P320, P321, P330, P333+P317, P361+P364, P362+P364, P363, P403+P233, P405, and P501 + 30 (The corresponding statement to each P-code can be found at the GHS Classification page.) + 31 + 32 Danger + 33 H227: Combustible liquid [Warning Flammable liquids] + 34 H301: Toxic if swallowed [Danger Acute toxicity, oral] + 35 H311: Toxic in contact with skin [Danger Acute toxicity, dermal] + 36 H314: Causes severe skin burns and eye damage [Danger Skin corrosion/irritation] + 37 H317: May cause an allergic skin reaction [Warning Sensitization, Skin] + 38 H318: Causes serious eye damage [Danger Serious eye damage/eye irritation] + 39 H331: Toxic if inhaled [Danger Acute toxicity, inhalation] + 40 H341: Suspected of causing genetic defects [Warning Germ cell mutagenicity] + 41 H350: May cause cancer [Danger Carcinogenicity] + 42 H370: Causes damage to organs [Danger Specific target organ toxicity, single exposure] + 43 H402: Harmful to aquatic life [Hazardous to the aquatic environment, acute hazard] + 44 P203, P210, P260, P261, P262, P264, P264+P265, P270, P271, P272, P273, P280, P301+P316, P301+P330+P331, P302+P352, P302+P361+P354, P304+P340, P305+P354+P338, P308+P316, P316, P317, P318, P321, P330, P333+P317, P361+P364, P362+P364, P363, P370+P378, P403, P403+P233, P405, and P501 + 45 (The corresponding statement to each P-code can be found at the GHS Classification page.) + 46 + 47 Danger + 48 H220: Extremely flammable gas [Danger Flammable gases] + 49 H227: Combustible liquid [Warning Flammable liquids] + 50 H280: Contains gas under pressure; may explode if heated [Warning Gases under pressure] + 51 H302: Harmful if swallowed [Warning Acute toxicity, oral] + 52 H311: Toxic in contact with skin [Danger Acute toxicity, dermal] + 53 H315: Causes skin irritation [Warning Skin corrosion/irritation] + 54 H317: May cause an allergic skin reaction [Warning Sensitization, Skin] + 55 H319: Causes serious eye irritation [Warning Serious eye damage/eye irritation] + 56 H330: Fatal if inhaled [Danger Acute toxicity, inhalation] + 57 H334: May cause allergy or asthma symptoms or breathing difficulties if inhaled [Danger Sensitization, respiratory] + 58 H341: Suspected of causing genetic defects [Warning Germ cell mutagenicity] + 59 H350: May cause cancer [Danger Carcinogenicity] + 60 H370: Causes damage to organs [Danger Specific target organ toxicity, single exposure] + 61 H372: Causes damage to organs through prolonged or repeated exposure [Danger Specific target organ toxicity, repeated exposure] + 62 H401: Toxic to aquatic life [Hazardous to the aquatic environment, acute hazard] + 63 P203, P210, P222, P233, P260, P261, P262, P264, P264+P265, P270, P271, P272, P273, P280, P284, P301+P317, P302+P352, P304+P340, P305+P351+P338, P308+P316, P316, P318, P319, P320, P321, P330, P332+P317, P333+P317, P337+P317, P342+P316, P361+P364, P362+P364, P370+P378, P377, P381, P403, P403+P233, P405, P410+P403, and P501 + 64 (The corresponding statement to each P-code can be found at the GHS Classification page.) + 65 + 66 Danger + 67 H314: Causes severe skin burns and eye damage [Danger Skin corrosion/irritation] + 68 H317: May cause an allergic skin reaction [Warning Sensitization, Skin] + 69 H401: Toxic to aquatic life [Hazardous to the aquatic environment, acute hazard] + 70 H412: Harmful to aquatic life with long lasting effects [Hazardous to the aquatic environment, long-term hazard] + 71 P260, P261, P264, P272, P273, P280, P301+P330+P331, P302+P352, P302+P361+P354, P304+P340, P305+P354+P338, P316, P321, P333+P317, P362+P364, P363, P405, and P501 + 72 (The corresponding statement to each P-code can be found at the GHS Classification page.) + 73 + 74 Danger + 75 H220: Extremely flammable gas [Danger Flammable gases] + 76 H280: Contains gas under pressure; may explode if heated [Warning Gases under pressure] + 77 H302: Harmful if swallowed [Warning Acute toxicity, oral] + 78 H311: Toxic in contact with skin [Danger Acute toxicity, dermal] + 79 H315: Causes skin irritation [Warning Skin corrosion/irritation] + 80 H317: May cause an allergic skin reaction [Warning Sensitization, Skin] + 81 H319: Causes serious eye irritation [Warning Serious eye damage/eye irritation] + 82 H330: Fatal if inhaled [Danger Acute toxicity, inhalation] + 83 H334: May cause allergy or asthma symptoms or breathing difficulties if inhaled [Danger Sensitization, respiratory] + 84 H341: Suspected of causing genetic defects [Warning Germ cell mutagenicity] + 85 H350: May cause cancer [Danger Carcinogenicity] + 86 H370: Causes damage to organs [Danger Specific target organ toxicity, single exposure] + 87 H372: Causes damage to organs through prolonged or repeated exposure [Danger Specific target organ toxicity, repeated exposure] + 88 H401: Toxic to aquatic life [Hazardous to the aquatic environment, acute hazard] + 89 H412: Harmful to aquatic life with long lasting effects [Hazardous to the aquatic environment, long-term hazard] + 90 P203, P210, P222, P233, P260, P261, P262, P264, P264+P265, P270, P271, P272, P273, P280, P284, P301+P317, P302+P352, P304+P340, P305+P351+P338, P308+P316, P316, P318, P319, P320, P321, P330, P332+P317, P333+P317, P337+P317, P342+P316, P361+P364, P362+P364, P377, P381, P403, P403+P233, P405, P410+P403, and P501 + 91 (The corresponding statement to each P-code can be found at the GHS Classification page.) + 92 + 93 Danger + 94 H302: Harmful if swallowed [Warning Acute toxicity, oral] + 95 H314: Causes severe skin burns and eye damage [Danger Skin corrosion/irritation] + 96 H317: May cause an allergic skin reaction [Warning Sensitization, Skin] + 97 H330: Fatal if inhaled [Danger Acute toxicity, inhalation] + 98 H341: Suspected of causing genetic defects [Warning Germ cell mutagenicity] + 99 H350: May cause cancer [Danger Carcinogenicity] + 100 P203, P260, P261, P264, P270, P271, P272, P280, P284, P301+P317, P301+P330+P331, P302+P352, P302+P361+P354, P304+P340, P305+P354+P338, P316, P318, P320, P321, P330, P333+P317, P362+P364, P363, P403+P233, P405, and P501 + 101 (The corresponding statement to each P-code can be found at the GHS Classification page.) + source_name + 1 European Chemicals Agency (ECHA) + 2 European Chemicals Agency (ECHA) + 3 European Chemicals Agency (ECHA) + 4 European Chemicals Agency (ECHA) + 5 European Chemicals Agency (ECHA) + 6 European Chemicals Agency (ECHA) + 7 European Chemicals Agency (ECHA) + 8 European Chemicals Agency (ECHA) + 9 European Chemicals Agency (ECHA) + 10 European Chemicals Agency (ECHA) + 11 European Chemicals Agency (ECHA) + 12 European Chemicals Agency (ECHA) + 13 European Chemicals Agency (ECHA) + 14 European Chemicals Agency (ECHA) + 15 European Chemicals Agency (ECHA) + 16 European Chemicals Agency (ECHA) + 17 European Chemicals Agency (ECHA) + 18 European Chemicals Agency (ECHA) + 19 European Chemicals Agency (ECHA) + 20 Hazardous Chemical Information System (HCIS), Safe Work Australia + 21 Hazardous Chemical Information System (HCIS), Safe Work Australia + 22 Hazardous Chemical Information System (HCIS), Safe Work Australia + 23 Hazardous Chemical Information System (HCIS), Safe Work Australia + 24 Hazardous Chemical Information System (HCIS), Safe Work Australia + 25 Hazardous Chemical Information System (HCIS), Safe Work Australia + 26 Hazardous Chemical Information System (HCIS), Safe Work Australia + 27 Hazardous Chemical Information System (HCIS), Safe Work Australia + 28 Hazardous Chemical Information System (HCIS), Safe Work Australia + 29 Hazardous Chemical Information System (HCIS), Safe Work Australia + 30 Hazardous Chemical Information System (HCIS), Safe Work Australia + 31 Hazardous Substances Data Bank (HSDB) + 32 Hazardous Substances Data Bank (HSDB) + 33 Hazardous Substances Data Bank (HSDB) + 34 Hazardous Substances Data Bank (HSDB) + 35 Hazardous Substances Data Bank (HSDB) + 36 Hazardous Substances Data Bank (HSDB) + 37 Hazardous Substances Data Bank (HSDB) + 38 Hazardous Substances Data Bank (HSDB) + 39 Hazardous Substances Data Bank (HSDB) + 40 Hazardous Substances Data Bank (HSDB) + 41 Hazardous Substances Data Bank (HSDB) + 42 Hazardous Substances Data Bank (HSDB) + 43 Hazardous Substances Data Bank (HSDB) + 44 Hazardous Substances Data Bank (HSDB) + 45 Hazardous Substances Data Bank (HSDB) + 46 NITE-CMC + 47 NITE-CMC + 48 NITE-CMC + 49 NITE-CMC + 50 NITE-CMC + 51 NITE-CMC + 52 NITE-CMC + 53 NITE-CMC + 54 NITE-CMC + 55 NITE-CMC + 56 NITE-CMC + 57 NITE-CMC + 58 NITE-CMC + 59 NITE-CMC + 60 NITE-CMC + 61 NITE-CMC + 62 NITE-CMC + 63 NITE-CMC + 64 NITE-CMC + 65 NITE-CMC + 66 NITE-CMC + 67 NITE-CMC + 68 NITE-CMC + 69 NITE-CMC + 70 NITE-CMC + 71 NITE-CMC + 72 NITE-CMC + 73 NITE-CMC + 74 NITE-CMC + 75 NITE-CMC + 76 NITE-CMC + 77 NITE-CMC + 78 NITE-CMC + 79 NITE-CMC + 80 NITE-CMC + 81 NITE-CMC + 82 NITE-CMC + 83 NITE-CMC + 84 NITE-CMC + 85 NITE-CMC + 86 NITE-CMC + 87 NITE-CMC + 88 NITE-CMC + 89 NITE-CMC + 90 NITE-CMC + 91 NITE-CMC + 92 Regulation (EC) No 1272/2008 of the European Parliament and of the Council + 93 Regulation (EC) No 1272/2008 of the European Parliament and of the Council + 94 Regulation (EC) No 1272/2008 of the European Parliament and of the Council + 95 Regulation (EC) No 1272/2008 of the European Parliament and of the Council + 96 Regulation (EC) No 1272/2008 of the European Parliament and of the Council + 97 Regulation (EC) No 1272/2008 of the European Parliament and of the Council + 98 Regulation (EC) No 1272/2008 of the European Parliament and of the Council + 99 Regulation (EC) No 1272/2008 of the European Parliament and of the Council + 100 Regulation (EC) No 1272/2008 of the European Parliament and of the Council + 101 Regulation (EC) No 1272/2008 of the European Parliament and of the Council + source_id other query + 1 55163 NA 50-00-0 + 2 55163 NA 50-00-0 + 3 55163 NA 50-00-0 + 4 55163 NA 50-00-0 + 5 55163 NA 50-00-0 + 6 55163 NA 50-00-0 + 7 55163 NA 50-00-0 + 8 55163 NA 50-00-0 + 9 55163 NA 50-00-0 + 10 55163 NA 50-00-0 + 11 55163 NA 50-00-0 + 12 55163 NA 50-00-0 + 13 55163 NA 50-00-0 + 14 55163 NA 50-00-0 + 15 55163 NA 50-00-0 + 16 55163 NA 50-00-0 + 17 55163 NA 50-00-0 + 18 55163 NA 50-00-0 + 19 55163 NA 50-00-0 + 20 4750 NA 50-00-0 + 21 4750 NA 50-00-0 + 22 4750 NA 50-00-0 + 23 4750 NA 50-00-0 + 24 4750 NA 50-00-0 + 25 4750 NA 50-00-0 + 26 4750 NA 50-00-0 + 27 4750 NA 50-00-0 + 28 4750 NA 50-00-0 + 29 4750 NA 50-00-0 + 30 4750 NA 50-00-0 + 31 164 NA 50-00-0 + 32 164 NA 50-00-0 + 33 164 NA 50-00-0 + 34 164 NA 50-00-0 + 35 164 NA 50-00-0 + 36 164 NA 50-00-0 + 37 164 NA 50-00-0 + 38 164 NA 50-00-0 + 39 164 NA 50-00-0 + 40 164 NA 50-00-0 + 41 164 NA 50-00-0 + 42 164 NA 50-00-0 + 43 164 NA 50-00-0 + 44 164 NA 50-00-0 + 45 164 NA 50-00-0 + 46 69 NA 50-00-0 + 47 69 NA 50-00-0 + 48 69 NA 50-00-0 + 49 69 NA 50-00-0 + 50 69 NA 50-00-0 + 51 69 NA 50-00-0 + 52 69 NA 50-00-0 + 53 69 NA 50-00-0 + 54 69 NA 50-00-0 + 55 69 NA 50-00-0 + 56 69 NA 50-00-0 + 57 69 NA 50-00-0 + 58 69 NA 50-00-0 + 59 69 NA 50-00-0 + 60 69 NA 50-00-0 + 61 69 NA 50-00-0 + 62 69 NA 50-00-0 + 63 69 NA 50-00-0 + 64 69 NA 50-00-0 + 65 R04_C_056_JNIOSH,MOE NA 50-00-0 + 66 R04_C_056_JNIOSH,MOE NA 50-00-0 + 67 R04_C_056_JNIOSH,MOE NA 50-00-0 + 68 R04_C_056_JNIOSH,MOE NA 50-00-0 + 69 R04_C_056_JNIOSH,MOE NA 50-00-0 + 70 R04_C_056_JNIOSH,MOE NA 50-00-0 + 71 R04_C_056_JNIOSH,MOE NA 50-00-0 + 72 R04_C_056_JNIOSH,MOE NA 50-00-0 + 73 H29_B_039 NA 50-00-0 + 74 H29_B_039 NA 50-00-0 + 75 H29_B_039 NA 50-00-0 + 76 H29_B_039 NA 50-00-0 + 77 H29_B_039 NA 50-00-0 + 78 H29_B_039 NA 50-00-0 + 79 H29_B_039 NA 50-00-0 + 80 H29_B_039 NA 50-00-0 + 81 H29_B_039 NA 50-00-0 + 82 H29_B_039 NA 50-00-0 + 83 H29_B_039 NA 50-00-0 + 84 H29_B_039 NA 50-00-0 + 85 H29_B_039 NA 50-00-0 + 86 H29_B_039 NA 50-00-0 + 87 H29_B_039 NA 50-00-0 + 88 H29_B_039 NA 50-00-0 + 89 H29_B_039 NA 50-00-0 + 90 H29_B_039 NA 50-00-0 + 91 H29_B_039 NA 50-00-0 + 92 605-001-00-5 NA 50-00-0 + 93 605-001-00-5 NA 50-00-0 + 94 605-001-00-5 NA 50-00-0 + 95 605-001-00-5 NA 50-00-0 + 96 605-001-00-5 NA 50-00-0 + 97 605-001-00-5 NA 50-00-0 + 98 605-001-00-5 NA 50-00-0 + 99 605-001-00-5 NA 50-00-0 + 100 605-001-00-5 NA 50-00-0 + 101 605-001-00-5 NA 50-00-0 + + $iris + # A tibble: 3 x 9 + chemical_name casrn exposure_route assessment_type critical_effect_or_tumo~1 + + 1 Formaldehyde 50-00-0 Oral Noncancer Reduced weight gain, his~ + 2 Formaldehyde 50-00-0 Inhalation Cancer Nasopharyngeal cancer, s~ + 3 Formaldehyde 50-00-0 Inhalation Noncancer Decreased pulmonary func~ + # i abbreviated name: 1: critical_effect_or_tumor_type + # i 4 more variables: woe_characterization , toxicity_value_type , + # toxicity_value , query + + $ice + assay + 1 TER Corrosion + 2 OPERA, soil adsorption coefficient of organic compounds. + 3 TER Corrosion + 4 OPERA, Henry's Law Constant + 5 OPERA, The whole body primary biotransformation rate (half-life) constant for organic chemicals in fish. + 6 TER Corrosion + 7 OPERA, Octanol-Water Partition Coefficient + 8 TER Corrosion + 9 TER Corrosion + 10 OPERA, HPLC retention time. + 11 TER Corrosion + 12 OPERA, Human Plasma Fraction Unbound + 13 CoMPARA, AR Binding + 14 OPERA, Fish bioconcentration factor + 15 OPERA, OH rate constant for the atmospheric, gas-phase reaction between photochemically produced hydroxyl radicals and organic chemicals + 16 OPERA, Caco-2 permeability (logPapp) + 17 CERAPP, ER Agonist + 18 CoMPARA, AR Binding + 19 OPERA, biodegradation half-life for compounds containing only carbon and hydrogen + 20 CoMPARA, AR Antagonist + 21 OPERA, Human Hepatic Intrinsic Clearance + 22 CERAPP, ER Agonist + 23 CoMPARA, AR Antagonist + 24 CERAPP, ER Antagonist + 25 CERAPP, ER Antagonist + 26 CoMPARA, AR Agonist + 27 CoMPARA, AR Agonist + 28 CATMoS, Acute Oral Toxicity + 29 SENS-IS + 30 CATMoS, Acute Oral Toxicity + 31 U-SENS + 32 CERAPP, ER Binding + 33 U-SENS + 34 CERAPP, ER Binding + 35 Functional Use + 36 CATMoS, Acute Oral Toxicity + 37 Functional Use + 38 CATMoS, Acute Oral Toxicity + 39 Functional Use + 40 CATMoS, Acute Oral Toxicity + 41 Functional Use + 42 CATMoS, Acute Oral Toxicity + 43 Functional Use + 44 CATMoS, Acute Oral Toxicity + 45 Functional Use + 46 OPERA, Boiling Point + 47 Functional Use + 48 CATMoS, Acute Oral Toxicity + 49 CATMoS, Acute Oral Toxicity + 50 OPERA, Vapor Pressure + 51 OPERA, Water Solubility + 52 OPERA, Melting Point + 53 OPERA, Octanol-Air Partition Coefficient + 54 hCLAT + 55 hCLAT + 56 hCLAT + 57 hCLAT + 58 Report on Carcinogens + 59 IARC Carcinogenicity + 60 KeratinoSens + 61 KeratinoSens + 62 KeratinoSens + 63 KeratinoSens + 64 LuSens + 65 LuSens + 66 Human Maximization Test + 67 Human Maximization Test + 68 mMUSST + 69 SENS-IS + 70 DPRA + 71 DPRA + 72 DPRA + 73 DPRA + 74 DPRA + 75 DPRA + 76 DPRA + 77 LLNA + 78 IRIS Carcinogenicity + 79 OPERA, Octanol-Water Distribution Coefficient + 80 IRIS Carcinogenicity + 81 Genotoxicity + 82 hCLAT + 83 OPERA, Negative Log of Acid Dissociation Constant + 84 hCLAT + 85 OPERA, Negative Log of Acid Dissociation Constant + 86 hCLAT + 87 OPERA, Octanol-Water Distribution Coefficient + 88 hCLAT + 89 OPERA, Negative Log of Acid Dissociation Constant + 90 hCLAT + 91 Human Repeat Insult Patch Test + 92 Human Repeat Insult Patch Test + 93 Human Repeat Insult Patch Test + 94 Human Repeat Insult Patch Test + 95 Human Repeat Insult Patch Test + 96 Human Repeat Insult Patch Test + 97 Human Repeat Insult Patch Test + 98 Human Repeat Insult Patch Test + 99 Human Repeat Insult Patch Test + 100 Human Repeat Insult Patch Test + 101 DPRA + 102 DPRA + 103 DPRA + 104 DPRA + 105 DPRA + 106 DPRA + 107 DPRA + 108 DPRA + 109 DPRA + 110 Human Repeat Insult Patch Test + 111 Human Repeat Insult Patch Test + 112 Human Repeat Insult Patch Test + 113 Human Repeat Insult Patch Test + 114 DPRA + 115 DPRA + 116 DPRA + 117 DPRA + 118 DPRA + 119 DPRA + 120 DPRA + 121 DPRA + 122 DPRA + 123 DPRA + 124 DPRA + 125 DPRA + 126 DPRA + 127 DPRA + 128 DPRA + 129 DPRA + 130 DPRA + 131 OPERA, Number of oxygen atoms + 132 DPRA + 133 OPERA, HPLC retention time. + 134 DPRA + 135 OPERA, Number of rotatable bonds, excluding terminal bonds + 136 DPRA + 137 OPERA, Number of nitrogen atoms + 138 DPRA + 139 DPRA + 140 DPRA + 141 DPRA + 142 Human Repeat Insult Patch Test + 143 Human Repeat Insult Patch Test + 144 Human Repeat Insult Patch Test + 145 Human Repeat Insult Patch Test + 146 Human Repeat Insult Patch Test + 147 Human Repeat Insult Patch Test + 148 Human Repeat Insult Patch Test + 149 Human Repeat Insult Patch Test + 150 Human Repeat Insult Patch Test + 151 Human Repeat Insult Patch Test + 152 Human Repeat Insult Patch Test + 153 Human Repeat Insult Patch Test + 154 Human Repeat Insult Patch Test + 155 Human Repeat Insult Patch Test + 156 Human Repeat Insult Patch Test + 157 Human Repeat Insult Patch Test + 158 Human Repeat Insult Patch Test + 159 Human Repeat Insult Patch Test + 160 Human Repeat Insult Patch Test + 161 TER Corrosion + 162 Human Repeat Insult Patch Test + 163 TER Corrosion + 164 Human Repeat Insult Patch Test + 165 Human Repeat Insult Patch Test + 166 Human Repeat Insult Patch Test + 167 TER Corrosion + 168 Human Repeat Insult Patch Test + 169 TER Corrosion + 170 Human Repeat Insult Patch Test + 171 TER Corrosion + 172 Human Repeat Insult Patch Test + 173 TER Corrosion + 174 Human Repeat Insult Patch Test + 175 Rat Acute Oral Toxicity + 176 Rat Acute Oral Toxicity + 177 Rat Acute Inhalation Toxicity + 178 Rat Acute Inhalation Toxicity + 179 Rat Acute Inhalation Toxicity + 180 Rat Acute Inhalation Toxicity + 181 Rat Acute Inhalation Toxicity + 182 Rat Acute Inhalation Toxicity + 183 OPERA, Octanol-Water Distribution Coefficient + 184 hCLAT + 185 hCLAT + 186 Rat Acute Oral Toxicity + 187 Rat Acute Oral Toxicity + 188 Rat Acute Oral Toxicity + 189 Rat Acute Oral Toxicity + 190 Rat Acute Oral Toxicity + 191 Rat Acute Oral Toxicity + 192 KeratinoSens + 193 KeratinoSens + 194 hCLAT + 195 KeratinoSens + 196 hCLAT + 197 hCLAT + 198 hCLAT + 199 hCLAT + 200 Human Maximization Test + 201 Human Maximization Test + 202 Human Maximization Test + 203 Human Maximization Test + 204 LuSens + 205 LuSens + 206 KeratinoSens + 207 KeratinoSens + 208 DPRA + 209 OPERA, Water Solubility + 210 DPRA + 211 OPERA, The whole body primary biotransformation rate (half-life) constant for organic chemicals in fish. + 212 DPRA + 213 OPERA, Octanol-Water Partition Coefficient + 214 DPRA + 215 OPERA, soil adsorption coefficient of organic compounds. + 216 DPRA + 217 OPERA, Henry's Law Constant + 218 DPRA + 219 OPERA, Number of rings + 220 DPRA + 221 OPERA, Number of hydrogen bond donors (using CDK HBondDonorCountDescriptor algorithm) + 222 DPRA + 223 OPERA, Fraction of sp3 carbons to sp2 carbons + 224 LLNA + 225 OPERA, Number of carbon atoms + 226 LLNA + 227 OPERA, Number failures of the Lipinski's Rule Of 5 + 228 LLNA + 229 OPERA, Number of hydrogen bond acceptors (using CDK HBondAcceptorCountDescriptor algorithm) + 230 LLNA + 231 OPERA, Melting Point + 232 LLNA + 233 OPERA, Octanol-Air Partition Coefficient + 234 LLNA + 235 OPERA, Vapor Pressure + 236 LLNA + 237 OPERA, Molar refractivity + 238 LLNA + 239 Molecular Weight + 240 LLNA + 241 OPERA, Combined dipolarity/polarizability + 242 LLNA + 243 CATMoS, Acute Oral Toxicity + 244 LLNA + 245 OPERA, Boiling Point + 246 LLNA + 247 OPERA, Topological polar surface area + 248 LLNA + 249 OPERA, Number of rings containing heteroatoms (N, O, P, S, or halogens) + 250 LLNA + 251 OPERA, Number of aromatic atoms + 252 LLNA + 253 OPERA, Number of heavy atoms (i.e. not hydrogen) + 254 LLNA + 255 OPERA, Number of atoms + 256 Rat Acute Inhalation Toxicity + 257 OPERA, Octanol-Water Distribution Coefficient + 258 Rat Acute Inhalation Toxicity + 259 OPERA, Negative Log of Acid Dissociation Constant + 260 SEEM3, Exposure Predictions + 261 OPERA, Fish bioconcentration factor + 262 SEEM3, Exposure Predictions + 263 OPERA, OH rate constant for the atmospheric, gas-phase reaction between photochemically produced hydroxyl radicals and organic chemicals + 264 IRIS Carcinogenicity + 265 OPERA, Human Plasma Fraction Unbound + 266 SEEM3, Exposure Predictions + 267 OPERA, biodegradation half-life for compounds containing only carbon and hydrogen + 268 LLNA + 269 OPERA, Caco-2 permeability (logPapp) + 270 LLNA + 271 OPERA, Human Hepatic Intrinsic Clearance + 272 U-SENS + 273 U-SENS + 274 SENS-IS + 275 SENS-IS + 276 Human Maximization Test + 277 mMUSST + 278 Human Maximization Test + 279 Human Maximization Test + 280 U-SENS + endpoint + 1 Call + 2 Applicability_Domain + 3 Call + 4 Applicability_Domain + 5 Applicability_Domain + 6 Call + 7 Applicability_Domain + 8 Call + 9 Call + 10 Applicability_Domain + 11 Call + 12 Applicability_Domain + 13 Call + 14 Applicability_Domain + 15 Applicability_Domain + 16 Applicability_Domain + 17 Call + 18 Applicability_Domain + 19 Applicability_Domain + 20 Applicability_Domain + 21 Applicability_Domain + 22 Applicability_Domain + 23 Call + 24 Call + 25 Applicability_Domain + 26 Call + 27 Applicability_Domain + 28 Very Toxic + 29 Potency + 30 Applicability_Domain + 31 Call + 32 Call + 33 Call + 34 Applicability_Domain + 35 OECD Functional Use + 36 Non Toxic + 37 OECD Functional Use + 38 Applicability_Domain + 39 OECD Functional Use + 40 EPA Classification + 41 OECD Functional Use + 42 Applicability_Domain + 43 OECD Functional Use + 44 Applicability_Domain + 45 OECD Functional Use + 46 Applicability_Domain + 47 OECD Functional Use + 48 GHS Classification + 49 Applicability_Domain + 50 Applicability_Domain + 51 Applicability_Domain + 52 Applicability_Domain + 53 Applicability_Domain + 54 CD86, Call + 55 Call + 56 CD54, Call + 57 CD86, Call + 58 Listing status + 59 IARC group + 60 Call + 61 Call + 62 Imax + 63 Imax + 64 Imax + 65 Call + 66 Call + 67 Relative reliability score + 68 Call + 69 Potency + 70 Call + 71 Call + 72 Call + 73 Call + 74 Call + 75 Call + 76 Call + 77 Call + 78 Tumor type + 79 Applicability_Domain + 80 WOE characterization + 81 Bacterial mutagenicity + 82 Call + 83 Applicability_Domain + 84 CD86, Call + 85 Applicability_Domain + 86 CD54, Call + 87 Applicability_Domain + 88 Call + 89 Applicability_Domain + 90 CD54, Call + 91 Call + 92 Call + 93 Relative reliability score + 94 Relative reliability score + 95 Call + 96 Relative reliability score + 97 Call + 98 Call + 99 Relative reliability score + 100 Relative reliability score + 101 Call + 102 Call + 103 Call + 104 Call + 105 Call + 106 Depletion Cys + 107 Depletion Lys + Cys + 108 Depletion Cys + 109 Depletion Lys + 110 Induction dose per skin area + 111 Incidence of positive responses + 112 Induction dose per skin area, 5% incidence of positive responses + 113 Induction dose per skin area + 114 Depletion Lys + 115 Depletion Lys + Cys + 116 Depletion Cys + 117 Depletion Lys + Cys + 118 Depletion Lys + Cys + 119 Depletion Lys + 120 Depletion Lys + 121 Depletion Cys + 122 Depletion Lys + 123 Depletion Cys + 124 Depletion Cys + 125 Depletion Lys + Cys + 126 Depletion Lys + Cys + 127 Depletion Lys + 128 Depletion Lys + 129 Depletion Cys + 130 Depletion Lys + Cys + 131 nbO + 132 Depletion Lys + 133 RT + 134 Depletion Cys + 135 nbRotBd + 136 Depletion Lys + Cys + 137 nbN + 138 Depletion Lys + 139 Depletion Cys + 140 Depletion Lys + Cys + 141 Depletion Lys + 142 Concentration + 143 Concentration + 144 Incidence of positive responses + 145 Induction dose per skin area, 5% incidence of positive responses + 146 Induction dose per skin area, 5% incidence of positive responses + 147 Concentration, 5% incidence of positive responses + 148 Concentration, 5% incidence of positive responses + 149 Induction dose per skin area, one positive response + 150 Induction dose per skin area, one positive response + 151 Concentration, one positive response + 152 Concentration, one positive response + 153 Induction dose per skin area, 5% incidence of positive responses + 154 Induction dose per skin area + 155 Induction dose per skin area, one positive response + 156 Concentration, 5% incidence of positive responses + 157 Incidence of positive responses + 158 Concentration, one positive response + 159 Induction dose per skin area + 160 Concentration + 161 TER + 162 Incidence of positive responses + 163 TER + 164 Concentration, 5% incidence of positive responses + 165 Concentration + 166 Induction dose per skin area, one positive response + 167 TER + 168 Concentration, one positive response + 169 TER + 170 Induction dose per skin area + 171 TER + 172 Concentration + 173 TER + 174 Incidence of positive responses + 175 LD50 + 176 LD50 + 177 LC50 + 178 LC50 + 179 LC50 + 180 LC50 + 181 LC50 + 182 LC50 + 183 LogD, ph 5.5 + 184 CD86, EC150 + 185 CD54, EC200 + 186 LD50 + 187 LD50 + 188 LD50 + 189 LD50 + 190 LD50 + 191 LD50 + 192 EC1.5 + 193 EC3 + 194 CV75 + 195 EC1.5 + 196 CD86, EC150 + 197 CD54, EC200 + 198 CV75 + 199 CV75 + 200 Induction dose per skin area + 201 Incidence of positive responses + 202 Induction dose per skin area, one positive response + 203 Concentration + 204 EC1.5 + 205 IC50 + 206 IC50 + 207 IC50 + 208 Depletion Cys + 209 WS + 210 Depletion Lys + Cys + 211 LogKM + 212 Depletion Lys + Cys + 213 LogP + 214 Depletion Lys + 215 LogKOC + 216 Depletion Cys + 217 HL + 218 Depletion Lys + Cys + 219 nbRing + 220 Depletion Lys + 221 ndHBdDon + 222 Depletion Cys + 223 Sp3Sp2HybRatio + 224 EC3 + 225 nbC + 226 EC3 + 227 nbLipinskiFailures + 228 EC3 + 229 nbHBdAcc + 230 EC3 + 231 MP + 232 EC3 + 233 KOA + 234 EC3 + 235 VP + 236 EC3 + 237 MolarRefract + 238 EC3 + 239 MW + 240 EC3 + 241 CombDipolPolariz + 242 EC3 + 243 LD50 + 244 EC3 + 245 BP + 246 EC3 + 247 TopoPolSurfAir + 248 EC3 + 249 nbHeteroRing + 250 EC3 + 251 nbAromAtom + 252 EC3 + 253 nbHeavyAtoms + 254 EC3 + 255 nbAtoms + 256 LC50 + 257 LogD, ph 7.4 + 258 LC50 + 259 pKa, Ionizations + 260 5th percentile + 261 LogBCF + 262 95th percentile + 263 LogAOH + 264 Inhalation risk unit + 265 Fu + 266 50th percentile + 267 LogBioDeg + 268 EC3 + 269 LogCACO2 + 270 EC3 + 271 Clint + 272 CD86, EC150 + 273 CD86, EC150 + 274 Concentration + 275 Concentration + 276 Induction dose per skin area, 5% incidence of positive responses + 277 CD86, EC120 + 278 Concentration, one positive response + 279 Concentration, 5% incidence of positive responses + 280 CV70 + substance_type casrn qsar_ready_id + 1 Mixture ICE_660959215 + 2 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 3 Mixture ICE_660959215 + 4 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 5 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 6 Mixture ICE_660959215 + 7 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 8 Mixture ICE_660959215 + 9 Mixture ICE_660959215 + 10 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 11 Mixture ICE_660959215 + 12 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 13 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 14 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 15 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 16 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 17 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 18 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 19 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 20 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 21 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 22 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 23 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 24 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 25 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 26 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 27 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 28 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 29 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 30 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 31 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 32 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 33 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 34 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 35 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 36 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 37 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 38 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 39 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 40 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 41 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 42 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 43 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 44 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 45 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 46 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 47 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 48 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 49 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 50 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 51 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 52 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 53 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 54 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 55 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 56 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 57 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 58 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 59 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 60 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 61 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 62 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 63 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 64 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 65 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 66 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 67 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 68 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 69 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 70 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 71 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 72 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 73 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 74 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 75 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 76 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 77 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 78 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 79 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 80 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 81 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 82 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 83 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 84 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 85 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 86 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 87 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 88 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 89 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 90 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 91 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 92 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 93 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 94 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 95 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 96 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 97 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 98 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 99 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 100 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 101 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 102 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 103 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 104 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 105 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 106 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 107 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 108 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 109 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 110 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 111 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 112 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 113 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 114 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 115 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 116 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 117 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 118 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 119 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 120 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 121 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 122 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 123 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 124 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 125 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 126 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 127 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 128 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 129 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 130 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 131 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 132 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 133 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 134 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 135 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 136 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 137 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 138 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 139 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 140 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 141 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 142 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 143 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 144 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 145 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 146 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 147 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 148 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 149 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 150 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 151 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 152 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 153 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 154 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 155 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 156 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 157 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 158 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 159 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 160 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 161 Mixture ICE_660959215 + 162 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 163 Mixture ICE_660959215 + 164 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 165 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 166 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 167 Mixture ICE_660959215 + 168 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 169 Mixture ICE_660959215 + 170 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 171 Mixture ICE_660959215 + 172 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 173 Mixture ICE_660959215 + 174 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 175 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 176 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 177 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 178 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 179 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 180 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 181 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 182 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 183 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 184 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 185 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 186 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 187 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 188 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 189 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 190 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 191 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 192 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 193 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 194 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 195 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 196 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 197 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 198 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 199 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 200 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 201 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 202 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 203 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 204 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 205 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 206 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 207 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 208 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 209 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 210 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 211 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 212 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 213 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 214 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 215 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 216 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 217 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 218 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 219 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 220 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 221 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 222 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 223 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 224 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 225 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 226 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 227 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 228 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 229 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 230 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 231 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 232 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 233 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 234 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 235 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 236 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 237 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 238 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 239 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 240 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 241 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 242 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 243 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 244 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 245 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 246 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 247 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 248 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 249 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 250 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 251 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 252 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 253 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 254 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 255 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 256 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 257 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 258 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 259 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 260 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 261 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 262 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 263 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 264 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 265 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 266 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 267 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 268 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 269 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 270 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 271 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 272 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 273 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 274 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 275 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 276 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 277 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 278 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 279 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + 280 Chemical 50-00-0 WSFSSNUMVMOOMR-UHFFFAOYSA-N + value + 1 Inactive + 2 1 + 3 Inactive + 4 1 + 5 0 + 6 Inactive + 7 1 + 8 Inactive + 9 Inactive + 10 0 + 11 Inactive + 12 0 + 13 0 + 14 1 + 15 1 + 16 0 + 17 0.0 + 18 1 + 19 0 + 20 1 + 21 0 + 22 1 + 23 0.0 + 24 0.0 + 25 1 + 26 0.0 + 27 1 + 28 0 + 29 Strong + 30 1 + 31 Active + 32 0 + 33 Active + 34 1.0 + 35 Biocide + 36 0 + 37 Flavouring and nutrient + 38 1 + 39 Preservative + 40 2 + 41 Monomers + 42 1 + 43 Binder + 44 1 + 45 Monomers + 46 1 + 47 Preservative + 48 3 + 49 1 + 50 1 + 51 1 + 52 1 + 53 1 + 54 Inactive + 55 Active + 56 Active + 57 Active + 58 Known + 59 1 + 60 Active + 61 Active + 62 16.92 + 63 4.1 + 64 3.99 + 65 Active + 66 Active + 67 1 + 68 Active + 69 Strong + 70 Active + 71 Active + 72 Active + 73 Active + 74 Active + 75 Active + 76 Active + 77 Active + 78 Squamous cell carcinoma + 79 0 + 80 B1 (Probable human carcinogen - based on limited evidence of carcinogenicity in humans) (1986 guidelines) + 81 Weakly Positive; Weakly Positive; Positive; Positive; Positive; Positive; Positive; Positive; Positive + 82 Active + 83 0 + 84 Active + 85 0 + 86 Active + 87 0 + 88 Inactive + 89 0 + 90 Inactive + 91 Active + 92 Active + 93 2 + 94 3 + 95 Active + 96 2 + 97 Active + 98 Inactive + 99 2 + 100 3 + 101 Active + 102 Active + 103 Active + 104 Active + 105 Active + 106 48.6 + 107 25.3 + 108 44.2 + 109 2.0 + 110 2868.0 + 111 4.494 + 112 931.9 + 113 286.8 + 114 3.6 + 115 24.0 + 116 36.7 + 117 19.0 + 118 19.55 + 119 1.3 + 120 1.8 + 121 37.3 + 122 3.8 + 123 40.6 + 124 36.6 + 125 19.9 + 126 15.4 + 127 3.2 + 128 0.3 + 129 30.5 + 130 28.6 + 131 1.0 + 132 2.5 + 133 0.0 + 134 49.6 + 135 0.0 + 136 25.95 + 137 0.0 + 138 2.3 + 139 54.8 + 140 22.2 + 141 2.4 + 142 3.7 + 143 0.37 + 144 7.843 + 145 319.0 + 146 1828.0 + 147 0.4116 + 148 2.359 + 149 71.69 + 150 358.4 + 151 0.0925 + 152 0.4625 + 153 757.0 + 154 1434.0 + 155 172.1 + 156 0.9768 + 157 5.682 + 158 0.222 + 159 860.3 + 160 1.11 + 161 12.3 + 162 0.0 + 163 6.4 + 164 1.202 + 165 0.037 + 166 358.4 + 167 12.3 + 168 0.4625 + 169 6.4 + 170 28.68 + 171 6.1 + 172 1.85 + 173 6.1 + 174 7.692 + 175 > 100.0 + 176 100.0 + 177 < 0.5682 + 178 0.5866 + 179 1.0002 + 180 1.0064 + 181 0.3068 + 182 0.3068 + 183 0.35 + 184 4.3 + 185 5.2 + 186 550.0 + 187 < 800.0 + 188 2020.0 + 189 800.0 + 190 500.0 + 191 > 7000.0 + 192 63.21 + 193 72.2 + 194 5.8 + 195 137.0 + 196 4.3 + 197 5.14 + 198 5.8 + 199 23.3 + 200 1148.0 + 201 72.0 + 202 63.79 + 203 1.85 + 204 184.4 + 205 > 288.0 + 206 201.63 + 207 385.9 + 208 44.7 + 209 1.17 + 210 24.45 + 211 -0.65 + 212 35.8 + 213 0.35 + 214 4.2 + 215 0.44 + 216 60.4 + 217 -6.46 + 218 26.95 + 219 0.0 + 220 11.2 + 221 0.0 + 222 51.4 + 223 0.0 + 224 0.37 + 225 1.0 + 226 0.27 + 227 0.0 + 228 0.35 + 229 1.0 + 230 0.44 + 231 -105.0 + 232 0.37 + 233 1.21 + 234 0.99 + 235 2.92 + 236 0.7 + 237 6.307 + 238 0.61 + 239 30.0106 + 240 8.0 + 241 0.562 + 242 5.6 + 243 290.0 + 244 4.2 + 245 -19.0 + 246 3.8 + 247 17.07 + 248 14.5 + 249 0.0 + 250 3.6 + 251 0.0 + 252 0.11 + 253 2.0 + 254 0.3 + 255 4.0 + 256 0.203 + 257 0.35 + 258 0.578 + 259 0.0 + 260 1.409E-9 + 261 0.24 + 262 0.6579 + 263 -11.03 + 264 1.3E-5 + 265 0.73 + 266 2.938E-5 + 267 0.91 + 268 8.2 + 269 -5.07 + 270 12.3 + 271 6.35 + 272 1.6 + 273 5.74 + 274 37.0 + 275 37.0 + 276 79.74 + 277 0.634 + 278 0.1028 + 279 0.1285 + 280 5.74 + unit species receptor_species route sex + 1 + 2 + 3 + 4 + 5 + 6 + 7 + 8 + 9 + 10 + 11 + 12 + 13 + 14 + 15 + 16 + 17 + 18 + 19 + 20 + 21 + 22 + 23 + 24 + 25 + 26 + 27 + 28 + 29 + 30 + 31 + 32 + 33 + 34 + 35 + 36 + 37 + 38 + 39 + 40 + 41 + 42 + 43 + 44 + 45 + 46 + 47 + 48 + 49 + 50 + 51 + 52 + 53 + 54 + 55 + 56 + 57 + 58 + 59 + 60 + 61 + 62 + 63 + 64 + 65 + 66 Human Dermal + 67 Human Dermal + 68 + 69 + 70 + 71 + 72 + 73 + 74 + 75 + 76 + 77 Mouse Dermal + 78 Inhalation + 79 + 80 Inhalation + 81 Mouse Dosed drinking water Male + 82 + 83 + 84 + 85 + 86 + 87 + 88 + 89 + 90 + 91 Human Dermal + 92 Human Dermal + 93 Human Dermal + 94 Human Dermal + 95 Human Dermal + 96 Human Dermal + 97 Human Dermal + 98 Human Dermal + 99 Human Dermal + 100 Human Dermal + 101 + 102 + 103 + 104 + 105 + 106 % + 107 % + 108 % + 109 % + 110 ug/cm2 Human Dermal + 111 % Human Dermal + 112 ug/cm2 Human Dermal + 113 ug/cm2 Human Dermal + 114 % + 115 % + 116 % + 117 % + 118 % + 119 % + 120 % + 121 % + 122 % + 123 % + 124 % + 125 % + 126 % + 127 % + 128 % + 129 % + 130 % + 131 count + 132 % + 133 Minutes + 134 % + 135 count + 136 % + 137 count + 138 % + 139 % + 140 % + 141 % + 142 % Human Dermal + 143 % Human Dermal + 144 % Human Dermal + 145 ug/cm2 Human Dermal + 146 ug/cm2 Human Dermal + 147 % Human Dermal + 148 % Human Dermal + 149 ug/cm2 Human Dermal + 150 ug/cm2 Human Dermal + 151 % Human Dermal + 152 % Human Dermal + 153 ug/cm2 Human Dermal + 154 ug/cm2 Human Dermal + 155 ug/cm2 Human Dermal + 156 % Human Dermal + 157 % Human Dermal + 158 % Human Dermal + 159 ug/cm2 Human Dermal + 160 % Human Dermal + 161 kiloohms + 162 % Human Dermal + 163 kiloohms + 164 % Human Dermal + 165 % Human Dermal + 166 ug/cm2 Human Dermal + 167 kiloohms + 168 % Human Dermal + 169 kiloohms + 170 ug/cm2 Human Dermal + 171 kiloohms + 172 % Human Dermal + 173 kiloohms + 174 % Human Dermal + 175 mg/kg Rat Male + 176 mg/kg Rat Male + 177 mg/L + 178 mg/L + 179 mg/L + 180 mg/L + 181 mg/L + 182 mg/L + 183 Log10 unitless + 184 ug/mL + 185 ug/mL + 186 mg/kg Rat Male + 187 mg/kg Rat Male + 188 mg/kg Rat Male + 189 mg/kg Rat Male + 190 mg/kg Rat Male + 191 mg/kg Rat Male + 192 uM + 193 uM + 194 ug/mL + 195 uM + 196 ug/mL + 197 ug/mL + 198 ug/mL + 199 ug/mL + 200 ug/cm2 Human Dermal + 201 % Human Dermal + 202 ug/cm2 Human Dermal + 203 % Human Dermal + 204 uM + 205 uM + 206 uM + 207 uM + 208 % + 209 Log10 moles/L + 210 % + 211 Log10 days + 212 % + 213 Log 10 unitless + 214 % + 215 Log10 L/Kg + 216 % + 217 Log10 atm-m3/mole + 218 % + 219 count + 220 % + 221 count + 222 % + 223 Unitless Fraction + 224 % Mouse Dermal + 225 count + 226 % Mouse Dermal + 227 count + 228 % Mouse Dermal + 229 count + 230 % Mouse Dermal + 231 Degree C + 232 % Mouse Dermal + 233 Log 10 unitless + 234 % Mouse Dermal + 235 Log10 mmHg + 236 % Mouse Dermal + 237 m3/mol + 238 % Mouse Dermal + 239 g/mol + 240 % Mouse Dermal + 241 dipole moment/ volume + 242 % Mouse Dermal + 243 mg/kg + 244 % Mouse Dermal + 245 Degree C + 246 % Mouse Dermal + 247 A^2 + 248 % Mouse Dermal + 249 count + 250 % Mouse Dermal + 251 count + 252 % Mouse Dermal + 253 count + 254 % Mouse Dermal + 255 count + 256 mg/L + 257 Log10 unitless + 258 mg/L + 259 count + 260 mg/kg/day + 261 Log10 unitless + 262 mg/kg/day + 263 Log10 cm3/molecule-sec + 264 ug/m3 Inhalation + 265 Unitless Fraction + 266 mg/kg/day + 267 Log10 days + 268 % Mouse Dermal + 269 log(10-6 cm/s) + 270 % Mouse Dermal + 271 ul/min/10^6 cells + 272 ug/mL + 273 ug/mL + 274 % + 275 % + 276 ug/cm2 Human Dermal + 277 ug/mL + 278 % Human Dermal + 279 % Human Dermal + 280 ug/mL + strain life_stage tissue lesion location assay_source + 1 + 2 + 3 + 4 + 5 + 6 + 7 + 8 + 9 + 10 + 11 + 12 + 13 + 14 + 15 + 16 + 17 + 18 + 19 + 20 + 21 + 22 + 23 + 24 + 25 + 26 + 27 + 28 + 29 + 30 + 31 + 32 + 33 + 34 + 35 + 36 + 37 + 38 + 39 + 40 + 41 + 42 + 43 + 44 + 45 + 46 + 47 + 48 + 49 + 50 + 51 + 52 + 53 + 54 + 55 + 56 + 57 + 58 + 59 + 60 + 61 + 62 + 63 + 64 + 65 + 66 + 67 + 68 + 69 + 70 + 71 + 72 + 73 + 74 + 75 + 76 + 77 + 78 + 79 + 80 + 81 P53 +/- (C57BL/6) + 82 + 83 + 84 + 85 + 86 + 87 + 88 + 89 + 90 + 91 + 92 + 93 + 94 + 95 + 96 + 97 + 98 + 99 + 100 + 101 + 102 + 103 + 104 + 105 + 106 + 107 + 108 + 109 + 110 + 111 + 112 + 113 + 114 + 115 + 116 + 117 + 118 + 119 + 120 + 121 + 122 + 123 + 124 + 125 + 126 + 127 + 128 + 129 + 130 + 131 + 132 + 133 + 134 + 135 + 136 + 137 + 138 + 139 + 140 + 141 + 142 + 143 + 144 + 145 + 146 + 147 + 148 + 149 + 150 + 151 + 152 + 153 + 154 + 155 + 156 + 157 + 158 + 159 + 160 + 161 + 162 + 163 + 164 + 165 + 166 + 167 + 168 + 169 + 170 + 171 + 172 + 173 + 174 + 175 + 176 + 177 + 178 + 179 + 180 + 181 + 182 + 183 + 184 + 185 + 186 + 187 + 188 + 189 + 190 + 191 + 192 + 193 + 194 + 195 + 196 + 197 + 198 + 199 + 200 + 201 + 202 + 203 + 204 + 205 + 206 + 207 + 208 + 209 + 210 + 211 + 212 + 213 + 214 + 215 + 216 + 217 + 218 + 219 + 220 + 221 + 222 + 223 + 224 + 225 + 226 + 227 + 228 + 229 + 230 + 231 + 232 + 233 + 234 + 235 + 236 + 237 + 238 + 239 + 240 + 241 + 242 + 243 + 244 + 245 + 246 + 247 + 248 + 249 + 250 + 251 + 252 + 253 + 254 + 255 + 256 + 257 + 258 + 259 + 260 + 261 + 262 + 263 + 264 + 265 + 266 + 267 + 268 + 269 + 270 + 271 + 272 + 273 + 274 + 275 + 276 + 277 + 278 + 279 + 280 + in_vitro_assay_format + 1 + 2 + 3 + 4 + 5 + 6 + 7 + 8 + 9 + 10 + 11 + 12 + 13 + 14 + 15 + 16 + 17 + 18 + 19 + 20 + 21 + 22 + 23 + 24 + 25 + 26 + 27 + 28 + 29 + 30 + 31 + 32 + 33 + 34 + 35 + 36 + 37 + 38 + 39 + 40 + 41 + 42 + 43 + 44 + 45 + 46 + 47 + 48 + 49 + 50 + 51 + 52 + 53 + 54 + 55 + 56 + 57 + 58 + 59 + 60 + 61 + 62 + 63 + 64 + 65 + 66 + 67 + 68 + 69 + 70 + 71 + 72 + 73 + 74 + 75 + 76 + 77 + 78 + 79 + 80 + 81 + 82 + 83 + 84 + 85 + 86 + 87 + 88 + 89 + 90 + 91 + 92 + 93 + 94 + 95 + 96 + 97 + 98 + 99 + 100 + 101 + 102 + 103 + 104 + 105 + 106 + 107 + 108 + 109 + 110 + 111 + 112 + 113 + 114 + 115 + 116 + 117 + 118 + 119 + 120 + 121 + 122 + 123 + 124 + 125 + 126 + 127 + 128 + 129 + 130 + 131 + 132 + 133 + 134 + 135 + 136 + 137 + 138 + 139 + 140 + 141 + 142 + 143 + 144 + 145 + 146 + 147 + 148 + 149 + 150 + 151 + 152 + 153 + 154 + 155 + 156 + 157 + 158 + 159 + 160 + 161 + 162 + 163 + 164 + 165 + 166 + 167 + 168 + 169 + 170 + 171 + 172 + 173 + 174 + 175 + 176 + 177 + 178 + 179 + 180 + 181 + 182 + 183 + 184 + 185 + 186 + 187 + 188 + 189 + 190 + 191 + 192 + 193 + 194 + 195 + 196 + 197 + 198 + 199 + 200 + 201 + 202 + 203 + 204 + 205 + 206 + 207 + 208 + 209 + 210 + 211 + 212 + 213 + 214 + 215 + 216 + 217 + 218 + 219 + 220 + 221 + 222 + 223 + 224 + 225 + 226 + 227 + 228 + 229 + 230 + 231 + 232 + 233 + 234 + 235 + 236 + 237 + 238 + 239 + 240 + 241 + 242 + 243 + 244 + 245 + 246 + 247 + 248 + 249 + 250 + 251 + 252 + 253 + 254 + 255 + 256 + 257 + 258 + 259 + 260 + 261 + 262 + 263 + 264 + 265 + 266 + 267 + 268 + 269 + 270 + 271 + 272 + 273 + 274 + 275 + 276 + 277 + 278 + 279 + 280 + reference + 1 Botham et al. 1992; 20732113; 10.1016/0887-2333(92)90031-l + 2 + 3 Botham et al. 1992; 20732113; 10.1016/0887-2333(92)90031-l + 4 + 5 + 6 Botham et al. 1992; 20732113; 10.1016/0887-2333(92)90031-l + 7 + 8 Botham et al. 1992; 20732113; 10.1016/0887-2333(92)90031-l + 9 Botham et al. 1992; 20732113; 10.1016/0887-2333(92)90031-l + 10 + 11 Botham et al. 1992; 20732113; 10.1016/0887-2333(92)90031-l + 12 + 13 + 14 + 15 + 16 + 17 + 18 + 19 + 20 + 21 + 22 + 23 + 24 + 25 + 26 + 27 + 28 + 29 Cottrez et al. 2015; 25724174; 10.1016/j.tiv.2015.02.012 + 30 + 31 Piroird et al. 2015; 25820135; 10.1016/j.tiv.2015.03.009 + 32 + 33 Piroird et al. 2015; 25820135; 10.1016/j.tiv.2015.03.009 + 34 + 35 Data retrieved by NICEATM from the Environmental Protection Agency's Chemical and Products Database Version 3, dated 2020-12-16 + 36 + 37 Data retrieved by NICEATM from the Environmental Protection Agency's Chemical and Products Database Version 3, dated 2020-12-16 + 38 + 39 Data retrieved by NICEATM from the Environmental Protection Agency's Chemical and Products Database Version 3, dated 2020-12-16 + 40 + 41 Data retrieved by NICEATM from the Environmental Protection Agency's Chemical and Products Database Version 3, dated 2020-12-16 + 42 + 43 Data retrieved by NICEATM from the Environmental Protection Agency's Chemical and Products Database Version 3, dated 2020-12-16 + 44 + 45 Data retrieved by NICEATM from the Environmental Protection Agency's Chemical and Products Database Version 3, dated 2020-12-16 + 46 + 47 Data retrieved by NICEATM from the Environmental Protection Agency's Chemical and Products Database Version 3, dated 2020-12-16 + 48 + 49 + 50 + 51 + 52 + 53 + 54 Ashikaga et al. 2010; 20822320; 10.1177/026119291003800403|Nukada et al. 2011; 21767275; 10.1111/j.1600-0536.2011.01952.x|Nukada et al. 2012; 22796097; 10.1016/j.tiv.2012.07.001|Nukada personal communication (undated)|Nukada et al. 2013; 23149339; 10.1016/j.tiv.2012.11.006 + 55 Ashikaga et al. 2010; 20822320; 10.1177/026119291003800403|Nukada et al. 2011; 21767275; 10.1111/j.1600-0536.2011.01952.x|Nukada et al. 2012; 22796097; 10.1016/j.tiv.2012.07.001|Nukada personal communication (undated)|Nukada et al. 2013; 23149339; 10.1016/j.tiv.2012.11.006 + 56 Ashikaga et al. 2010; 20822320; 10.1177/026119291003800403|Nukada et al. 2011; 21767275; 10.1111/j.1600-0536.2011.01952.x|Nukada et al. 2012; 22796097; 10.1016/j.tiv.2012.07.001|Nukada personal communication (undated)|Nukada et al. 2013; 23149339; 10.1016/j.tiv.2012.11.006 + 57 Ashikaga et al. 2010; 20822320; 10.1177/026119291003800403|Nukada et al. 2011; 21767275; 10.1111/j.1600-0536.2011.01952.x|Nukada et al. 2012; 22796097; 10.1016/j.tiv.2012.07.001|Nukada personal communication (undated)|Nukada et al. 2013; 23149339; 10.1016/j.tiv.2012.11.006 + 58 + 59 + 60 Bauch et al. 2012; 22659254; 10.1016/j.yrtph.2012.05.013 + 61 Bauch et al. 2012; 22659254; 10.1016/j.yrtph.2012.05.013 + 62 Bauch et al. 2012; 22659254; 10.1016/j.yrtph.2012.05.013 + 63 Bauch et al. 2012; 22659254; 10.1016/j.yrtph.2012.05.013 + 64 Urbisch et al. 2015; 25541156; 10.1016/j.yrtph.2014.12.008 + 65 Urbisch et al. 2015; 25541156; 10.1016/j.yrtph.2014.12.008 + 66 Kligman 1966; 5924294; 10.1038/jid.1966.160|Greif 1967; Not available; Not available|Magnusson and Kligman 1969; 5774356; 10.1038/jid.1969.42|Basketter et al. 1994; 8045461; 10.1016/0278-6915(94)90112-0|Basketter et al. 1999; 10654593; 10.1016/S0278-6915(99)00112-x|Gerberick et al. 2000; 10684384; 10.1053/ajcd.2000.0003|Akkan et al. 2003; Not available; Not available + 67 Kligman 1966; 5924294; 10.1038/jid.1966.160|Greif 1967; Not available; Not available|Magnusson and Kligman 1969; 5774356; 10.1038/jid.1969.42|Basketter et al. 1994; 8045461; 10.1016/0278-6915(94)90112-0|Basketter et al. 1999; 10654593; 10.1016/S0278-6915(99)00112-x|Gerberick et al. 2000; 10684384; 10.1053/ajcd.2000.0003|Akkan et al. 2003; Not available; Not available + 68 Urbisch et al. 2015; 25541156; 10.1016/j.yrtph.2014.12.008 + 69 Cottrez et al. 2015; 25724174; 10.1016/j.tiv.2015.02.012 + 70 Joint Research Centre of the European Union 2013 + 71 Joint Research Centre of the European Union 2013 + 72 Joint Research Centre of the European Union 2013 + 73 Joint Research Centre of the European Union 2013 + 74 Joint Research Centre of the European Union 2013 + 75 Joint Research Centre of the European Union 2013 + 76 Joint Research Centre of the European Union 2013 + 77 ECPA personal communication (undated) + 78 + 79 + 80 + 81 + 82 Ashikaga et al. 2010; 20822320; 10.1177/026119291003800403|Nukada et al. 2011; 21767275; 10.1111/j.1600-0536.2011.01952.x|Nukada et al. 2012; 22796097; 10.1016/j.tiv.2012.07.001|Nukada personal communication (undated)|Nukada et al. 2013; 23149339; 10.1016/j.tiv.2012.11.006 + 83 + 84 Ashikaga et al. 2010; 20822320; 10.1177/026119291003800403|Nukada et al. 2011; 21767275; 10.1111/j.1600-0536.2011.01952.x|Nukada et al. 2012; 22796097; 10.1016/j.tiv.2012.07.001|Nukada personal communication (undated)|Nukada et al. 2013; 23149339; 10.1016/j.tiv.2012.11.006 + 85 + 86 Ashikaga et al. 2010; 20822320; 10.1177/026119291003800403|Nukada et al. 2011; 21767275; 10.1111/j.1600-0536.2011.01952.x|Nukada et al. 2012; 22796097; 10.1016/j.tiv.2012.07.001|Nukada personal communication (undated)|Nukada et al. 2013; 23149339; 10.1016/j.tiv.2012.11.006 + 87 + 88 Ashikaga et al. 2010; 20822320; 10.1177/026119291003800403|Nukada et al. 2011; 21767275; 10.1111/j.1600-0536.2011.01952.x|Nukada et al. 2012; 22796097; 10.1016/j.tiv.2012.07.001|Nukada personal communication (undated)|Nukada et al. 2013; 23149339; 10.1016/j.tiv.2012.11.006 + 89 + 90 Ashikaga et al. 2010; 20822320; 10.1177/026119291003800403|Nukada et al. 2011; 21767275; 10.1111/j.1600-0536.2011.01952.x|Nukada et al. 2012; 22796097; 10.1016/j.tiv.2012.07.001|Nukada personal communication (undated)|Nukada et al. 2013; 23149339; 10.1016/j.tiv.2012.11.006 + 91 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 92 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 93 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 94 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 95 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 96 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 97 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 98 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 99 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 100 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 101 Joint Research Centre of the European Union 2013 + 102 Joint Research Centre of the European Union 2013 + 103 Joint Research Centre of the European Union 2013 + 104 Joint Research Centre of the European Union 2013 + 105 Joint Research Centre of the European Union 2013 + 106 Joint Research Centre of the European Union 2013 + 107 Joint Research Centre of the European Union 2013 + 108 Joint Research Centre of the European Union 2013 + 109 Joint Research Centre of the European Union 2013 + 110 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 111 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 112 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 113 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 114 Joint Research Centre of the European Union 2013 + 115 Joint Research Centre of the European Union 2013 + 116 Joint Research Centre of the European Union 2013 + 117 Joint Research Centre of the European Union 2013 + 118 Joint Research Centre of the European Union 2013 + 119 Joint Research Centre of the European Union 2013 + 120 Joint Research Centre of the European Union 2013 + 121 Joint Research Centre of the European Union 2013 + 122 Joint Research Centre of the European Union 2013 + 123 Joint Research Centre of the European Union 2013 + 124 Joint Research Centre of the European Union 2013 + 125 Joint Research Centre of the European Union 2013 + 126 Joint Research Centre of the European Union 2013 + 127 Joint Research Centre of the European Union 2013 + 128 Joint Research Centre of the European Union 2013 + 129 Joint Research Centre of the European Union 2013 + 130 Joint Research Centre of the European Union 2013 + 131 + 132 Joint Research Centre of the European Union 2013 + 133 + 134 Joint Research Centre of the European Union 2013 + 135 + 136 Joint Research Centre of the European Union 2013 + 137 + 138 Joint Research Centre of the European Union 2013 + 139 Joint Research Centre of the European Union 2013 + 140 Joint Research Centre of the European Union 2013 + 141 Joint Research Centre of the European Union 2013 + 142 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 143 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 144 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 145 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 146 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 147 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 148 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 149 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 150 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 151 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 152 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 153 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 154 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 155 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 156 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 157 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 158 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 159 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 160 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 161 Botham et al. 1992; 20732113; 10.1016/0887-2333(92)90031-l + 162 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 163 Botham et al. 1992; 20732113; 10.1016/0887-2333(92)90031-l + 164 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 165 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 166 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 167 Botham et al. 1992; 20732113; 10.1016/0887-2333(92)90031-l + 168 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 169 Botham et al. 1992; 20732113; 10.1016/0887-2333(92)90031-l + 170 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 171 Botham et al. 1992; 20732113; 10.1016/0887-2333(92)90031-l + 172 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 173 Botham et al. 1992; 20732113; 10.1016/0887-2333(92)90031-l + 174 Marzulli and Maibach 1974; 4459237; 10.1016/0015-6264(74)90367-8|Gerberick et al. 2001; 11526521; 10.1053/ajcd.2001.23926|Akkan et al. 2003; Not available; Not available|Griem et al. 2003; 14623479; 10.1016/j.yrtph.2003.07.001|Schneider and Akkan 2004; 15135206; 10.1016/j.yrtph.2004.02.002 + 175 + 176 + 177 AEGL + 178 AEGL + 179 AEGL + 180 AEGL + 181 AEGL + 182 AEGL + 183 + 184 Ashikaga et al. 2010; 20822320; 10.1177/026119291003800403|Nukada et al. 2011; 21767275; 10.1111/j.1600-0536.2011.01952.x|Nukada et al. 2012; 22796097; 10.1016/j.tiv.2012.07.001|Nukada personal communication (undated)|Nukada et al. 2013; 23149339; 10.1016/j.tiv.2012.11.006 + 185 Ashikaga et al. 2010; 20822320; 10.1177/026119291003800403|Nukada et al. 2011; 21767275; 10.1111/j.1600-0536.2011.01952.x|Nukada et al. 2012; 22796097; 10.1016/j.tiv.2012.07.001|Nukada personal communication (undated)|Nukada et al. 2013; 23149339; 10.1016/j.tiv.2012.11.006 + 186 + 187 + 188 + 189 + 190 + 191 + 192 Bauch et al. 2012; 22659254; 10.1016/j.yrtph.2012.05.013 + 193 Bauch et al. 2012; 22659254; 10.1016/j.yrtph.2012.05.013 + 194 Ashikaga et al. 2010; 20822320; 10.1177/026119291003800403|Nukada et al. 2011; 21767275; 10.1111/j.1600-0536.2011.01952.x|Nukada et al. 2012; 22796097; 10.1016/j.tiv.2012.07.001|Nukada personal communication (undated)|Nukada et al. 2013; 23149339; 10.1016/j.tiv.2012.11.006 + 195 Bauch et al. 2012; 22659254; 10.1016/j.yrtph.2012.05.013 + 196 Ashikaga et al. 2010; 20822320; 10.1177/026119291003800403|Nukada et al. 2011; 21767275; 10.1111/j.1600-0536.2011.01952.x|Nukada et al. 2012; 22796097; 10.1016/j.tiv.2012.07.001|Nukada personal communication (undated)|Nukada et al. 2013; 23149339; 10.1016/j.tiv.2012.11.006 + 197 Ashikaga et al. 2010; 20822320; 10.1177/026119291003800403|Nukada et al. 2011; 21767275; 10.1111/j.1600-0536.2011.01952.x|Nukada et al. 2012; 22796097; 10.1016/j.tiv.2012.07.001|Nukada personal communication (undated)|Nukada et al. 2013; 23149339; 10.1016/j.tiv.2012.11.006 + 198 Ashikaga et al. 2010; 20822320; 10.1177/026119291003800403|Nukada et al. 2011; 21767275; 10.1111/j.1600-0536.2011.01952.x|Nukada et al. 2012; 22796097; 10.1016/j.tiv.2012.07.001|Nukada personal communication (undated)|Nukada et al. 2013; 23149339; 10.1016/j.tiv.2012.11.006 + 199 Ashikaga et al. 2010; 20822320; 10.1177/026119291003800403|Nukada et al. 2011; 21767275; 10.1111/j.1600-0536.2011.01952.x|Nukada et al. 2012; 22796097; 10.1016/j.tiv.2012.07.001|Nukada personal communication (undated)|Nukada et al. 2013; 23149339; 10.1016/j.tiv.2012.11.006 + 200 Kligman 1966; 5924294; 10.1038/jid.1966.160|Greif 1967; Not available; Not available|Magnusson and Kligman 1969; 5774356; 10.1038/jid.1969.42|Basketter et al. 1994; 8045461; 10.1016/0278-6915(94)90112-0|Basketter et al. 1999; 10654593; 10.1016/S0278-6915(99)00112-x|Gerberick et al. 2000; 10684384; 10.1053/ajcd.2000.0003|Akkan et al. 2003; Not available; Not available + 201 Kligman 1966; 5924294; 10.1038/jid.1966.160|Greif 1967; Not available; Not available|Magnusson and Kligman 1969; 5774356; 10.1038/jid.1969.42|Basketter et al. 1994; 8045461; 10.1016/0278-6915(94)90112-0|Basketter et al. 1999; 10654593; 10.1016/S0278-6915(99)00112-x|Gerberick et al. 2000; 10684384; 10.1053/ajcd.2000.0003|Akkan et al. 2003; Not available; Not available + 202 Kligman 1966; 5924294; 10.1038/jid.1966.160|Greif 1967; Not available; Not available|Magnusson and Kligman 1969; 5774356; 10.1038/jid.1969.42|Basketter et al. 1994; 8045461; 10.1016/0278-6915(94)90112-0|Basketter et al. 1999; 10654593; 10.1016/S0278-6915(99)00112-x|Gerberick et al. 2000; 10684384; 10.1053/ajcd.2000.0003|Akkan et al. 2003; Not available; Not available + 203 Kligman 1966; 5924294; 10.1038/jid.1966.160|Greif 1967; Not available; Not available|Magnusson and Kligman 1969; 5774356; 10.1038/jid.1969.42|Basketter et al. 1994; 8045461; 10.1016/0278-6915(94)90112-0|Basketter et al. 1999; 10654593; 10.1016/S0278-6915(99)00112-x|Gerberick et al. 2000; 10684384; 10.1053/ajcd.2000.0003|Akkan et al. 2003; Not available; Not available + 204 Urbisch et al. 2015; 25541156; 10.1016/j.yrtph.2014.12.008 + 205 Urbisch et al. 2015; 25541156; 10.1016/j.yrtph.2014.12.008 + 206 Bauch et al. 2012; 22659254; 10.1016/j.yrtph.2012.05.013 + 207 Bauch et al. 2012; 22659254; 10.1016/j.yrtph.2012.05.013 + 208 Joint Research Centre of the European Union 2013 + 209 + 210 Joint Research Centre of the European Union 2013 + 211 + 212 Joint Research Centre of the European Union 2013 + 213 + 214 Joint Research Centre of the European Union 2013 + 215 + 216 Joint Research Centre of the European Union 2013 + 217 + 218 Joint Research Centre of the European Union 2013 + 219 + 220 Joint Research Centre of the European Union 2013 + 221 + 222 Joint Research Centre of the European Union 2013 + 223 + 224 ECPA personal communication (undated) + 225 + 226 ECPA personal communication (undated) + 227 + 228 ECPA personal communication (undated) + 229 + 230 ECPA personal communication (undated) + 231 + 232 ECPA personal communication (undated) + 233 + 234 ECPA personal communication (undated) + 235 + 236 ECPA personal communication (undated) + 237 + 238 ECPA personal communication (undated) + 239 + 240 ECPA personal communication (undated) + 241 + 242 ECPA personal communication (undated) + 243 + 244 ECPA personal communication (undated) + 245 + 246 ECPA personal communication (undated) + 247 + 248 ECPA personal communication (undated) + 249 + 250 ECPA personal communication (undated) + 251 + 252 ECPA personal communication (undated) + 253 + 254 ECPA personal communication (undated) + 255 + 256 AEGL + 257 + 258 AEGL + 259 + 260 Data retrieved by NICEATM from the Environmental Protection Agency's Human Exposure github page in November 2022 + 261 + 262 Data retrieved by NICEATM from the Environmental Protection Agency's Human Exposure github page in November 2022 + 263 + 264 + 265 + 266 Data retrieved by NICEATM from the Environmental Protection Agency's Human Exposure github page in November 2022 + 267 + 268 ECPA personal communication (undated) + 269 + 270 ECPA personal communication (undated) + 271 + 272 Piroird et al. 2015; 25820135; 10.1016/j.tiv.2015.03.009 + 273 Piroird et al. 2015; 25820135; 10.1016/j.tiv.2015.03.009 + 274 Cottrez et al. 2015; 25724174; 10.1016/j.tiv.2015.02.012 + 275 Cottrez et al. 2015; 25724174; 10.1016/j.tiv.2015.02.012 + 276 Kligman 1966; 5924294; 10.1038/jid.1966.160|Greif 1967; Not available; Not available|Magnusson and Kligman 1969; 5774356; 10.1038/jid.1969.42|Basketter et al. 1994; 8045461; 10.1016/0278-6915(94)90112-0|Basketter et al. 1999; 10654593; 10.1016/S0278-6915(99)00112-x|Gerberick et al. 2000; 10684384; 10.1053/ajcd.2000.0003|Akkan et al. 2003; Not available; Not available + 277 Urbisch et al. 2015; 25541156; 10.1016/j.yrtph.2014.12.008 + 278 Kligman 1966; 5924294; 10.1038/jid.1966.160|Greif 1967; Not available; Not available|Magnusson and Kligman 1969; 5774356; 10.1038/jid.1969.42|Basketter et al. 1994; 8045461; 10.1016/0278-6915(94)90112-0|Basketter et al. 1999; 10654593; 10.1016/S0278-6915(99)00112-x|Gerberick et al. 2000; 10684384; 10.1053/ajcd.2000.0003|Akkan et al. 2003; Not available; Not available + 279 Kligman 1966; 5924294; 10.1038/jid.1966.160|Greif 1967; Not available; Not available|Magnusson and Kligman 1969; 5774356; 10.1038/jid.1969.42|Basketter et al. 1994; 8045461; 10.1016/0278-6915(94)90112-0|Basketter et al. 1999; 10654593; 10.1016/S0278-6915(99)00112-x|Gerberick et al. 2000; 10684384; 10.1053/ajcd.2000.0003|Akkan et al. 2003; Not available; Not available + 280 Piroird et al. 2015; 25820135; 10.1016/j.tiv.2015.03.009 + reference_url dtxsid substance_name pubmed_id + 1 dicyanamine/formaldehyde condensate + 2 DTXSID7020637 Formaldehyde + 3 dicyanamine/formaldehyde condensate + 4 DTXSID7020637 Formaldehyde + 5 DTXSID7020637 Formaldehyde + 6 dicyanamine/formaldehyde condensate + 7 DTXSID7020637 Formaldehyde + 8 dicyanamine/formaldehyde condensate + 9 dicyanamine/formaldehyde condensate + 10 DTXSID7020637 Formaldehyde + 11 dicyanamine/formaldehyde condensate + 12 DTXSID7020637 Formaldehyde + 13 DTXSID7020637 Formaldehyde + 14 DTXSID7020637 Formaldehyde + 15 DTXSID7020637 Formaldehyde + 16 DTXSID7020637 Formaldehyde + 17 DTXSID7020637 Formaldehyde + 18 DTXSID7020637 Formaldehyde + 19 DTXSID7020637 Formaldehyde + 20 DTXSID7020637 Formaldehyde + 21 DTXSID7020637 Formaldehyde + 22 DTXSID7020637 Formaldehyde + 23 DTXSID7020637 Formaldehyde + 24 DTXSID7020637 Formaldehyde + 25 DTXSID7020637 Formaldehyde + 26 DTXSID7020637 Formaldehyde + 27 DTXSID7020637 Formaldehyde + 28 DTXSID7020637 Formaldehyde + 29 DTXSID7020637 Formaldehyde + 30 DTXSID7020637 Formaldehyde + 31 DTXSID7020637 Formaldehyde + 32 DTXSID7020637 Formaldehyde + 33 DTXSID7020637 Formaldehyde + 34 DTXSID7020637 Formaldehyde + 35 DTXSID7020637 Formaldehyde + 36 DTXSID7020637 Formaldehyde + 37 DTXSID7020637 Formaldehyde + 38 DTXSID7020637 Formaldehyde + 39 DTXSID7020637 Formaldehyde + 40 DTXSID7020637 Formaldehyde + 41 DTXSID7020637 Formaldehyde + 42 DTXSID7020637 Formaldehyde + 43 DTXSID7020637 Formaldehyde + 44 DTXSID7020637 Formaldehyde + 45 DTXSID7020637 Formaldehyde + 46 DTXSID7020637 Formaldehyde + 47 DTXSID7020637 Formaldehyde + 48 DTXSID7020637 Formaldehyde + 49 DTXSID7020637 Formaldehyde + 50 DTXSID7020637 Formaldehyde + 51 DTXSID7020637 Formaldehyde + 52 DTXSID7020637 Formaldehyde + 53 DTXSID7020637 Formaldehyde + 54 DTXSID7020637 Formaldehyde + 55 DTXSID7020637 Formaldehyde + 56 DTXSID7020637 Formaldehyde + 57 DTXSID7020637 Formaldehyde + 58 DTXSID7020637 Formaldehyde + 59 DTXSID7020637 Formaldehyde + 60 DTXSID7020637 Formaldehyde + 61 DTXSID7020637 Formaldehyde + 62 DTXSID7020637 Formaldehyde + 63 DTXSID7020637 Formaldehyde + 64 DTXSID7020637 Formaldehyde + 65 DTXSID7020637 Formaldehyde + 66 DTXSID7020637 Formaldehyde + 67 DTXSID7020637 Formaldehyde + 68 DTXSID7020637 Formaldehyde + 69 DTXSID7020637 Formaldehyde + 70 DTXSID7020637 Formaldehyde + 71 DTXSID7020637 Formaldehyde + 72 DTXSID7020637 Formaldehyde + 73 DTXSID7020637 Formaldehyde + 74 DTXSID7020637 Formaldehyde + 75 DTXSID7020637 Formaldehyde + 76 DTXSID7020637 Formaldehyde + 77 DTXSID7020637 Formaldehyde + 78 DTXSID7020637 Formaldehyde + 79 DTXSID7020637 Formaldehyde + 80 DTXSID7020637 Formaldehyde + 81 DTXSID7020637 Formaldehyde + 82 DTXSID7020637 Formaldehyde + 83 DTXSID7020637 Formaldehyde + 84 DTXSID7020637 Formaldehyde + 85 DTXSID7020637 Formaldehyde + 86 DTXSID7020637 Formaldehyde + 87 DTXSID7020637 Formaldehyde + 88 DTXSID7020637 Formaldehyde + 89 DTXSID7020637 Formaldehyde + 90 DTXSID7020637 Formaldehyde + 91 DTXSID7020637 Formaldehyde + 92 DTXSID7020637 Formaldehyde + 93 DTXSID7020637 Formaldehyde + 94 DTXSID7020637 Formaldehyde + 95 DTXSID7020637 Formaldehyde + 96 DTXSID7020637 Formaldehyde + 97 DTXSID7020637 Formaldehyde + 98 DTXSID7020637 Formaldehyde + 99 DTXSID7020637 Formaldehyde + 100 DTXSID7020637 Formaldehyde + 101 DTXSID7020637 Formaldehyde + 102 DTXSID7020637 Formaldehyde + 103 DTXSID7020637 Formaldehyde + 104 DTXSID7020637 Formaldehyde + 105 DTXSID7020637 Formaldehyde + 106 DTXSID7020637 Formaldehyde + 107 DTXSID7020637 Formaldehyde + 108 DTXSID7020637 Formaldehyde + 109 DTXSID7020637 Formaldehyde + 110 DTXSID7020637 Formaldehyde + 111 DTXSID7020637 Formaldehyde + 112 DTXSID7020637 Formaldehyde + 113 DTXSID7020637 Formaldehyde + 114 DTXSID7020637 Formaldehyde + 115 DTXSID7020637 Formaldehyde + 116 DTXSID7020637 Formaldehyde + 117 DTXSID7020637 Formaldehyde + 118 DTXSID7020637 Formaldehyde + 119 DTXSID7020637 Formaldehyde + 120 DTXSID7020637 Formaldehyde + 121 DTXSID7020637 Formaldehyde + 122 DTXSID7020637 Formaldehyde + 123 DTXSID7020637 Formaldehyde + 124 DTXSID7020637 Formaldehyde + 125 DTXSID7020637 Formaldehyde + 126 DTXSID7020637 Formaldehyde + 127 DTXSID7020637 Formaldehyde + 128 DTXSID7020637 Formaldehyde + 129 DTXSID7020637 Formaldehyde + 130 DTXSID7020637 Formaldehyde + 131 DTXSID7020637 Formaldehyde + 132 DTXSID7020637 Formaldehyde + 133 DTXSID7020637 Formaldehyde + 134 DTXSID7020637 Formaldehyde + 135 DTXSID7020637 Formaldehyde + 136 DTXSID7020637 Formaldehyde + 137 DTXSID7020637 Formaldehyde + 138 DTXSID7020637 Formaldehyde + 139 DTXSID7020637 Formaldehyde + 140 DTXSID7020637 Formaldehyde + 141 DTXSID7020637 Formaldehyde + 142 DTXSID7020637 Formaldehyde + 143 DTXSID7020637 Formaldehyde + 144 DTXSID7020637 Formaldehyde + 145 DTXSID7020637 Formaldehyde + 146 DTXSID7020637 Formaldehyde + 147 DTXSID7020637 Formaldehyde + 148 DTXSID7020637 Formaldehyde + 149 DTXSID7020637 Formaldehyde + 150 DTXSID7020637 Formaldehyde + 151 DTXSID7020637 Formaldehyde + 152 DTXSID7020637 Formaldehyde + 153 DTXSID7020637 Formaldehyde + 154 DTXSID7020637 Formaldehyde + 155 DTXSID7020637 Formaldehyde + 156 DTXSID7020637 Formaldehyde + 157 DTXSID7020637 Formaldehyde + 158 DTXSID7020637 Formaldehyde + 159 DTXSID7020637 Formaldehyde + 160 DTXSID7020637 Formaldehyde + 161 dicyanamine/formaldehyde condensate + 162 DTXSID7020637 Formaldehyde + 163 dicyanamine/formaldehyde condensate + 164 DTXSID7020637 Formaldehyde + 165 DTXSID7020637 Formaldehyde + 166 DTXSID7020637 Formaldehyde + 167 dicyanamine/formaldehyde condensate + 168 DTXSID7020637 Formaldehyde + 169 dicyanamine/formaldehyde condensate + 170 DTXSID7020637 Formaldehyde + 171 dicyanamine/formaldehyde condensate + 172 DTXSID7020637 Formaldehyde + 173 dicyanamine/formaldehyde condensate + 174 DTXSID7020637 Formaldehyde + 175 DTXSID7020637 Formaldehyde + 176 DTXSID7020637 Formaldehyde + 177 DTXSID7020637 Formaldehyde + 178 DTXSID7020637 Formaldehyde + 179 DTXSID7020637 Formaldehyde + 180 DTXSID7020637 Formaldehyde + 181 DTXSID7020637 Formaldehyde + 182 DTXSID7020637 Formaldehyde + 183 DTXSID7020637 Formaldehyde + 184 DTXSID7020637 Formaldehyde + 185 DTXSID7020637 Formaldehyde + 186 DTXSID7020637 Formaldehyde + 187 DTXSID7020637 Formaldehyde + 188 DTXSID7020637 Formaldehyde + 189 DTXSID7020637 Formaldehyde + 190 DTXSID7020637 Formaldehyde + 191 DTXSID7020637 Formaldehyde + 192 DTXSID7020637 Formaldehyde + 193 DTXSID7020637 Formaldehyde + 194 DTXSID7020637 Formaldehyde + 195 DTXSID7020637 Formaldehyde + 196 DTXSID7020637 Formaldehyde + 197 DTXSID7020637 Formaldehyde + 198 DTXSID7020637 Formaldehyde + 199 DTXSID7020637 Formaldehyde + 200 DTXSID7020637 Formaldehyde + 201 DTXSID7020637 Formaldehyde + 202 DTXSID7020637 Formaldehyde + 203 DTXSID7020637 Formaldehyde + 204 DTXSID7020637 Formaldehyde + 205 DTXSID7020637 Formaldehyde + 206 DTXSID7020637 Formaldehyde + 207 DTXSID7020637 Formaldehyde + 208 DTXSID7020637 Formaldehyde + 209 DTXSID7020637 Formaldehyde + 210 DTXSID7020637 Formaldehyde + 211 DTXSID7020637 Formaldehyde + 212 DTXSID7020637 Formaldehyde + 213 DTXSID7020637 Formaldehyde + 214 DTXSID7020637 Formaldehyde + 215 DTXSID7020637 Formaldehyde + 216 DTXSID7020637 Formaldehyde + 217 DTXSID7020637 Formaldehyde + 218 DTXSID7020637 Formaldehyde + 219 DTXSID7020637 Formaldehyde + 220 DTXSID7020637 Formaldehyde + 221 DTXSID7020637 Formaldehyde + 222 DTXSID7020637 Formaldehyde + 223 DTXSID7020637 Formaldehyde + 224 DTXSID7020637 Formaldehyde + 225 DTXSID7020637 Formaldehyde + 226 DTXSID7020637 Formaldehyde + 227 DTXSID7020637 Formaldehyde + 228 DTXSID7020637 Formaldehyde + 229 DTXSID7020637 Formaldehyde + 230 DTXSID7020637 Formaldehyde + 231 DTXSID7020637 Formaldehyde + 232 DTXSID7020637 Formaldehyde + 233 DTXSID7020637 Formaldehyde + 234 DTXSID7020637 Formaldehyde + 235 DTXSID7020637 Formaldehyde + 236 DTXSID7020637 Formaldehyde + 237 DTXSID7020637 Formaldehyde + 238 DTXSID7020637 Formaldehyde + 239 DTXSID7020637 Formaldehyde + 240 DTXSID7020637 Formaldehyde + 241 DTXSID7020637 Formaldehyde + 242 DTXSID7020637 Formaldehyde + 243 DTXSID7020637 Formaldehyde + 244 DTXSID7020637 Formaldehyde + 245 DTXSID7020637 Formaldehyde + 246 DTXSID7020637 Formaldehyde + 247 DTXSID7020637 Formaldehyde + 248 DTXSID7020637 Formaldehyde + 249 DTXSID7020637 Formaldehyde + 250 DTXSID7020637 Formaldehyde + 251 DTXSID7020637 Formaldehyde + 252 DTXSID7020637 Formaldehyde + 253 DTXSID7020637 Formaldehyde + 254 DTXSID7020637 Formaldehyde + 255 DTXSID7020637 Formaldehyde + 256 DTXSID7020637 Formaldehyde + 257 DTXSID7020637 Formaldehyde + 258 DTXSID7020637 Formaldehyde + 259 DTXSID7020637 Formaldehyde + 260 DTXSID7020637 Formaldehyde + 261 DTXSID7020637 Formaldehyde + 262 DTXSID7020637 Formaldehyde + 263 DTXSID7020637 Formaldehyde + 264 DTXSID7020637 Formaldehyde + 265 DTXSID7020637 Formaldehyde + 266 DTXSID7020637 Formaldehyde + 267 DTXSID7020637 Formaldehyde + 268 DTXSID7020637 Formaldehyde + 269 DTXSID7020637 Formaldehyde + 270 DTXSID7020637 Formaldehyde + 271 DTXSID7020637 Formaldehyde + 272 DTXSID7020637 Formaldehyde + 273 DTXSID7020637 Formaldehyde + 274 DTXSID7020637 Formaldehyde + 275 DTXSID7020637 Formaldehyde + 276 DTXSID7020637 Formaldehyde + 277 DTXSID7020637 Formaldehyde + 278 DTXSID7020637 Formaldehyde + 279 DTXSID7020637 Formaldehyde + 280 DTXSID7020637 Formaldehyde + query + 1 50-00-0 + 2 50-00-0 + 3 50-00-0 + 4 50-00-0 + 5 50-00-0 + 6 50-00-0 + 7 50-00-0 + 8 50-00-0 + 9 50-00-0 + 10 50-00-0 + 11 50-00-0 + 12 50-00-0 + 13 50-00-0 + 14 50-00-0 + 15 50-00-0 + 16 50-00-0 + 17 50-00-0 + 18 50-00-0 + 19 50-00-0 + 20 50-00-0 + 21 50-00-0 + 22 50-00-0 + 23 50-00-0 + 24 50-00-0 + 25 50-00-0 + 26 50-00-0 + 27 50-00-0 + 28 50-00-0 + 29 50-00-0 + 30 50-00-0 + 31 50-00-0 + 32 50-00-0 + 33 50-00-0 + 34 50-00-0 + 35 50-00-0 + 36 50-00-0 + 37 50-00-0 + 38 50-00-0 + 39 50-00-0 + 40 50-00-0 + 41 50-00-0 + 42 50-00-0 + 43 50-00-0 + 44 50-00-0 + 45 50-00-0 + 46 50-00-0 + 47 50-00-0 + 48 50-00-0 + 49 50-00-0 + 50 50-00-0 + 51 50-00-0 + 52 50-00-0 + 53 50-00-0 + 54 50-00-0 + 55 50-00-0 + 56 50-00-0 + 57 50-00-0 + 58 50-00-0 + 59 50-00-0 + 60 50-00-0 + 61 50-00-0 + 62 50-00-0 + 63 50-00-0 + 64 50-00-0 + 65 50-00-0 + 66 50-00-0 + 67 50-00-0 + 68 50-00-0 + 69 50-00-0 + 70 50-00-0 + 71 50-00-0 + 72 50-00-0 + 73 50-00-0 + 74 50-00-0 + 75 50-00-0 + 76 50-00-0 + 77 50-00-0 + 78 50-00-0 + 79 50-00-0 + 80 50-00-0 + 81 50-00-0 + 82 50-00-0 + 83 50-00-0 + 84 50-00-0 + 85 50-00-0 + 86 50-00-0 + 87 50-00-0 + 88 50-00-0 + 89 50-00-0 + 90 50-00-0 + 91 50-00-0 + 92 50-00-0 + 93 50-00-0 + 94 50-00-0 + 95 50-00-0 + 96 50-00-0 + 97 50-00-0 + 98 50-00-0 + 99 50-00-0 + 100 50-00-0 + 101 50-00-0 + 102 50-00-0 + 103 50-00-0 + 104 50-00-0 + 105 50-00-0 + 106 50-00-0 + 107 50-00-0 + 108 50-00-0 + 109 50-00-0 + 110 50-00-0 + 111 50-00-0 + 112 50-00-0 + 113 50-00-0 + 114 50-00-0 + 115 50-00-0 + 116 50-00-0 + 117 50-00-0 + 118 50-00-0 + 119 50-00-0 + 120 50-00-0 + 121 50-00-0 + 122 50-00-0 + 123 50-00-0 + 124 50-00-0 + 125 50-00-0 + 126 50-00-0 + 127 50-00-0 + 128 50-00-0 + 129 50-00-0 + 130 50-00-0 + 131 50-00-0 + 132 50-00-0 + 133 50-00-0 + 134 50-00-0 + 135 50-00-0 + 136 50-00-0 + 137 50-00-0 + 138 50-00-0 + 139 50-00-0 + 140 50-00-0 + 141 50-00-0 + 142 50-00-0 + 143 50-00-0 + 144 50-00-0 + 145 50-00-0 + 146 50-00-0 + 147 50-00-0 + 148 50-00-0 + 149 50-00-0 + 150 50-00-0 + 151 50-00-0 + 152 50-00-0 + 153 50-00-0 + 154 50-00-0 + 155 50-00-0 + 156 50-00-0 + 157 50-00-0 + 158 50-00-0 + 159 50-00-0 + 160 50-00-0 + 161 50-00-0 + 162 50-00-0 + 163 50-00-0 + 164 50-00-0 + 165 50-00-0 + 166 50-00-0 + 167 50-00-0 + 168 50-00-0 + 169 50-00-0 + 170 50-00-0 + 171 50-00-0 + 172 50-00-0 + 173 50-00-0 + 174 50-00-0 + 175 50-00-0 + 176 50-00-0 + 177 50-00-0 + 178 50-00-0 + 179 50-00-0 + 180 50-00-0 + 181 50-00-0 + 182 50-00-0 + 183 50-00-0 + 184 50-00-0 + 185 50-00-0 + 186 50-00-0 + 187 50-00-0 + 188 50-00-0 + 189 50-00-0 + 190 50-00-0 + 191 50-00-0 + 192 50-00-0 + 193 50-00-0 + 194 50-00-0 + 195 50-00-0 + 196 50-00-0 + 197 50-00-0 + 198 50-00-0 + 199 50-00-0 + 200 50-00-0 + 201 50-00-0 + 202 50-00-0 + 203 50-00-0 + 204 50-00-0 + 205 50-00-0 + 206 50-00-0 + 207 50-00-0 + 208 50-00-0 + 209 50-00-0 + 210 50-00-0 + 211 50-00-0 + 212 50-00-0 + 213 50-00-0 + 214 50-00-0 + 215 50-00-0 + 216 50-00-0 + 217 50-00-0 + 218 50-00-0 + 219 50-00-0 + 220 50-00-0 + 221 50-00-0 + 222 50-00-0 + 223 50-00-0 + 224 50-00-0 + 225 50-00-0 + 226 50-00-0 + 227 50-00-0 + 228 50-00-0 + 229 50-00-0 + 230 50-00-0 + 231 50-00-0 + 232 50-00-0 + 233 50-00-0 + 234 50-00-0 + 235 50-00-0 + 236 50-00-0 + 237 50-00-0 + 238 50-00-0 + 239 50-00-0 + 240 50-00-0 + 241 50-00-0 + 242 50-00-0 + 243 50-00-0 + 244 50-00-0 + 245 50-00-0 + 246 50-00-0 + 247 50-00-0 + 248 50-00-0 + 249 50-00-0 + 250 50-00-0 + 251 50-00-0 + 252 50-00-0 + 253 50-00-0 + 254 50-00-0 + 255 50-00-0 + 256 50-00-0 + 257 50-00-0 + 258 50-00-0 + 259 50-00-0 + 260 50-00-0 + 261 50-00-0 + 262 50-00-0 + 263 50-00-0 + 264 50-00-0 + 265 50-00-0 + 266 50-00-0 + 267 50-00-0 + 268 50-00-0 + 269 50-00-0 + 270 50-00-0 + 271 50-00-0 + 272 50-00-0 + 273 50-00-0 + 274 50-00-0 + 275 50-00-0 + 276 50-00-0 + 277 50-00-0 + 278 50-00-0 + 279 50-00-0 + 280 50-00-0 + + $comptox_main_data + # A tibble: 1 x 64 + input found_by preferred_name dtxcid casrn inchikey iupac_name smiles + + 1 50-00-0 CASRN Formaldehyde DTXCID30637 50-00-0 WSFSSNU~ Formaldeh~ C=O + # i 56 more variables: inchi_string , ms_ready_smiles , + # qsar_ready_smiles , molecular_formula , average_mass , + # monoisotopic_mass , qc_level , safety_data , expocast , + # data_sources , toxval_data , number_of_pubmed_articles , + # pubchem_data_sources , cpdat_count , iris_link , + # pprtv_link , wikipedia_article , qc_notes , + # toxprint_fingerprint , actor_report , ... + + $comptox_abstract_sifter + # A tibble: 1 x 3 + dsstox_link_to_dashboard preferred_name chemical_entity_query + + 1 DTXSID7020637 Formaldehyde 50-00-0 OR Formaldehyde + + $comptox_synonym_identifier + # A tibble: 1 x 3 + searched_chemical identifier pc_codes + + 1 Formaldehyde NSC 298885|UN 2209|Formalin 40|Superlysoform|Forma~ PC-0430~ + + $comptox_related_relationships + # A tibble: 56 x 7 + input dtxsid preferred_name has_relationship_with related_dtxsid + + 1 50-00-0 DTXSID7020637 Formaldehyde Searched Chemical DTXSID7020637 + 2 50-00-0 DTXSID7020637 Formaldehyde Predecessor: Component DTXSID6029709 + 3 50-00-0 DTXSID7020637 Formaldehyde Predecessor: Component DTXSID6029757 + 4 50-00-0 DTXSID7020637 Formaldehyde Predecessor: Component DTXSID60873853 + 5 50-00-0 DTXSID7020637 Formaldehyde Predecessor: Component DTXSID60905168 + 6 50-00-0 DTXSID7020637 Formaldehyde Predecessor: Component DTXSID6094144 + 7 50-00-0 DTXSID7020637 Formaldehyde Predecessor: Component DTXSID8049626 + 8 50-00-0 DTXSID7020637 Formaldehyde Predecessor: Component DTXSID701029969 + 9 50-00-0 DTXSID7020637 Formaldehyde Predecessor: Component DTXSID701092815 + 10 50-00-0 DTXSID7020637 Formaldehyde Predecessor: Component DTXSID70873849 + # i 46 more rows + # i 2 more variables: related_preferred_name , related_casrn + + $comptox_toxcast_assays_ac50 + # A tibble: 1,485 x 2 + input x50_00_0_dtxsid7020637 + + 1 ACEA_AR_agonist_80hr - + 2 ACEA_AR_agonist_AUC_viability - + 3 ACEA_AR_antagonist_80hr - + 4 ACEA_AR_antagonist_AUC_viability - + 5 ACEA_ER_80hr - + 6 ACEA_ER_AUC_viability - + 7 APR_HepG2_CellCycleArrest_1hr - + 8 APR_HepG2_CellCycleArrest_24hr - + 9 APR_HepG2_CellCycleArrest_72hr - + 10 APR_HepG2_CellLoss_1hr - + # i 1,475 more rows + + $comptox_toxval_details + # A tibble: 143 x 63 + searched_chemical dtxsid casrn name source sub_source toxval_type + + 1 Formaldehyde DTXSID7020637 50-00-0 Formal~ NIOSH - IDLH + 2 Formaldehyde DTXSID7020637 50-00-0 Formal~ Cal O~ Cal OEHHA~ cancer slo~ + 3 Formaldehyde DTXSID7020637 50-00-0 Formal~ ATSDR - LOAEL + 4 Formaldehyde DTXSID7020637 50-00-0 Formal~ ATSDR - LOAEL + 5 Formaldehyde DTXSID7020637 50-00-0 Formal~ ATSDR - MRL + 6 Formaldehyde DTXSID7020637 50-00-0 Formal~ ATSDR - MRL + 7 Formaldehyde DTXSID7020637 50-00-0 Formal~ ATSDR - MRL + 8 Formaldehyde DTXSID7020637 50-00-0 Formal~ ATSDR - MRL + 9 Formaldehyde DTXSID7020637 50-00-0 Formal~ ATSDR - MRL + 10 Formaldehyde DTXSID7020637 50-00-0 Formal~ ATSDR - NOAEL + # i 133 more rows + # i 56 more variables: toxval_subtype , toxval_type_supercategory , + # qualifier , toxval_numeric , toxval_units , + # risk_assessment_class , study_type , study_duration_class , + # study_duration_value , study_duration_units , + # species_common , strain , latin_name , + # species_supercategory , sex , generation , ... + + $comptox_chemical_properties + # A tibble: 46 x 8 + dtxsid dtxcid type name value units source description + + 1 DTXSID7020637 DTXCID30637 experimental Henry'~ 3.37~ atm-~ "Phys~ "The PHYSP~ + 2 DTXSID7020637 DTXCID30637 experimental Boilin~ -21.~ °C "NIOS~ "The NIOSH~ + 3 DTXSID7020637 DTXCID30637 experimental Boilin~ -19.1 °C "Phys~ "The PHYSP~ + 4 DTXSID7020637 DTXCID30637 experimental Meltin~ -92.~ °C "NIOS~ "The NIOSH~ + 5 DTXSID7020637 DTXCID30637 experimental Meltin~ -92.0 °C "Jean~ "Jean-Clau~ + 6 DTXSID7020637 DTXCID30637 experimental Water ~ 13.2 mol/L "Kovd~ "Kovdienko~ + 7 DTXSID7020637 DTXCID30637 experimental Water ~ 13.2~ mol/L "Phys~ "The PHYSP~ + 8 DTXSID7020637 DTXCID30637 experimental Water ~ 18.2 mol/L "Lewi~ "Lewis, K.~ + 9 DTXSID7020637 DTXCID30637 experimental LogKow~ 0.35 "Phys~ "The PHYSP~ + 10 DTXSID7020637 DTXCID30637 experimental pKa Ba~ 1.15 "Data~ "This pKa ~ + # i 36 more rows + + diff --git a/tests/testthat/test-comptox.R b/tests/testthat/test-comptox.R index 0a2e821..f5bf53f 100644 --- a/tests/testthat/test-comptox.R +++ b/tests/testthat/test-comptox.R @@ -7,22 +7,23 @@ test_that("Valid chemical name input", { skip_on_cran() expect_silent({ - dat <- extr_comptox( - ids = c("Aspirin"), - download_items = c("DTXCID", "CASRN"), - verbose = FALSE) + out <- extr_comptox( + ids = c("Aspirin"), + download_items = c("DTXCID", "CASRN"), + verbose = FALSE + ) }) - expect_true(is.list(dat)) - expect_true(all(unlist(lapply(dat, is.data.frame)))) - expect_equal(nrow(dat$comptox_main_data), 1) - expect_equal(nrow(dat$comptox_main_data), 1) - expect_equal(nrow(dat$comptox_cover_sheet), 4) - + expect_true(is.list(out)) + expect_true(all(unlist(lapply(out, is.data.frame)))) + expect_equal(nrow(out$comptox_main_data), 1) + expect_equal(nrow(out$comptox_main_data), 1) + expect_equal(nrow(out$comptox_cover_sheet), 4) }) Sys.sleep(3) -col_names <- c("comptox_cover_sheet", "comptox_main_data", "comptox_abstract_sifter", +col_names <- c( + "comptox_cover_sheet", "comptox_main_data", "comptox_abstract_sifter", "comptox_synonym_identifier", "comptox_related_relationships", "comptox_toxcast_assays_ac50", "comptox_toxval_details", "comptox_chemical_properties" ) @@ -31,28 +32,34 @@ test_that("Valid inputs", { skip_on_cran() ids <- c("50-00-0", "Aspirin", "DTXSID5020023") - expect_message({ - dat <- extr_comptox( - ids = ids) - }, "Getting info from CompTox") - - expect_equal(names(dat), col_names) - expect_equal(dat$comptox_main_data$input, ids) - expect_equal(ncol(dat$comptox_main_data), 64) + expect_message( + { + out <- extr_comptox( + ids = ids + ) + }, + "Getting info from CompTox" + ) + expect_equal(names(out), col_names) + expect_equal(out$comptox_main_data$input, ids) + expect_equal(ncol(out$comptox_main_data), 64) }) Sys.sleep(3) test_that("extr_comptox when download_items is set to one val", { expect_no_error( - dat <- extr_comptox(c("50-00-0", "80-05-7")) + out <- extr_comptox(c("50-00-0", "80-05-7")) ) }) test_that("extr_comptox warn for unknown ids", { - expect_warning({ - dat <- extr_comptox(c("31-12-5", "bella", "ciao")) - }, "Chemicals.*bella.*ciao.*not found!") + expect_warning( + { + out <- extr_comptox(c("31-12-5", "bella", "ciao")) + }, + "Chemicals.*bella.*ciao.*not found!" + ) }) diff --git a/tests/testthat/test-ctd.R b/tests/testthat/test-ctd.R index e3eaacb..07274bf 100644 --- a/tests/testthat/test-ctd.R +++ b/tests/testthat/test-ctd.R @@ -8,9 +8,11 @@ input_terms <- c("50-00-0", "64-17-5", "methanal", "ethanol") song <- c("bella", "ciao bella ciao", "bella ciao ciao ciao") -expected_columns <- c("chemical_name", "chemical_id", "casrn", "gene_symbol", - "gene_id", "organism", "organism_id", "pubmed_ids", - "query") +expected_columns <- c( + "chemical_name", "chemical_id", "casrn", "gene_symbol", + "gene_id", "organism", "organism_id", "pubmed_ids", + "query" +) # @@@@@@@@@@@@@ @@ -42,34 +44,38 @@ Sys.sleep(3) test_that("extr_ctd fetches other data", { skip_on_cran() dat <- extr_ctd( - input_terms = input_terms, - category = "chem", - report_type = "genes_curated", - input_term_search_type = "directAssociations", - action_types = "ANY", - ontology = c("go_bp", "go_cc") - ) - expect_true(is.data.frame(dat)) + input_terms = input_terms, + category = "chem", + report_type = "genes_curated", + input_term_search_type = "directAssociations", + action_types = "ANY", + ontology = c("go_bp", "go_cc") + ) + expect_true(is.data.frame(dat)) - expect_true(all(expected_columns %in% colnames(dat))) - expect_gt(nrow(dat), 0) + expect_true(all(expected_columns %in% colnames(dat))) + expect_gt(nrow(dat), 0) }) Sys.sleep(3) test_that("extr_ctd no results", { skip_on_cran() - expect_warning({ - dat <- extr_ctd( - input_terms = song, - category = "chem", - report_type = "genes_curated", - input_term_search_type = "directAssociations", - action_types = "ANY", - ontology = c("go_bp", "go_cc") - )}, "Chemicals .*not found!") + expect_warning( + { + dat <- extr_ctd( + input_terms = song, + category = "chem", + report_type = "genes_curated", + input_term_search_type = "directAssociations", + action_types = "ANY", + ontology = c("go_bp", "go_cc") + ) + }, + "Chemicals .*not found!" + ) - expect_equal(nrow(dat), 3) + expect_equal(nrow(dat), 3) }) Sys.sleep(3) @@ -96,17 +102,22 @@ Sys.sleep(3) test_that("extr_tetramer return NAS for unknown ids", { skip_on_cran() - expect_warning({ - dat <- extr_ctd( - input_terms = c("50-00-0", "64-17-5","methanal", "ethanol", "bella", "ciao", - "50-0000000"), category = "chem", report_type = "genes_curated", - input_term_search_type = "directAssociations", - action_types = "ANY", - ontology = c("go_bp", "go_cc")) - }, "Chemicals .*not found!") + expect_warning( + { + dat <- extr_ctd( + input_terms = c( + "50-00-0", "64-17-5", "methanal", "ethanol", "bella", "ciao", + "50-0000000" + ), category = "chem", report_type = "genes_curated", + input_term_search_type = "directAssociations", + action_types = "ANY", + ontology = c("go_bp", "go_cc") + ) + }, + "Chemicals .*not found!" + ) expect_equal(sum(is.na(dat$gene_id)), 3) - }) @@ -120,38 +131,44 @@ test_that("extr_tetramer fetches tetramers data", { skip_on_cran() dat <- extr_tetramer( - chem = c("50-00-0", "ethanol"), - disease = "", - gene = "", - go = "", - input_term_search_type = "directAssociations", - qt_match_type = "equals" - ) - expect_true(is.data.frame(dat)) + chem = c("50-00-0", "ethanol"), + disease = "", + gene = "", + go = "", + input_term_search_type = "directAssociations", + qt_match_type = "equals" + ) + expect_true(is.data.frame(dat)) - expected_columns <- c("chemical", "chemical_id", "gene", "gene_id", "phenotype", - "phenotype_id", "disease", "disease_id", "query") + expected_columns <- c( + "chemical", "chemical_id", "gene", "gene_id", "phenotype", + "phenotype_id", "disease", "disease_id", "query" + ) - expect_true(all(expected_columns %in% colnames(dat))) - expect_gt(nrow(dat), 0) + expect_true(all(expected_columns %in% colnames(dat))) + expect_gt(nrow(dat), 0) }) Sys.sleep(3) test_that("extr_tetramer no results", { skip_on_cran() - expect_warning({ - dat <- extr_tetramer( - chem = song, - disease = "", - gene = "", - go = "", - input_term_search_type = "directAssociations", - qt_match_type = "equals" - )}, "Chemicals .*not found!") + expect_warning( + { + dat <- extr_tetramer( + chem = song, + disease = "", + gene = "", + go = "", + input_term_search_type = "directAssociations", + qt_match_type = "equals" + ) + }, + "Chemicals .*not found!" + ) - expect_true(is.data.frame(dat)) - expect_equal(nrow(dat), 3) + expect_true(is.data.frame(dat)) + expect_equal(nrow(dat), 3) }) Sys.sleep(3) @@ -172,7 +189,3 @@ test_that("extr_tetramer no results with song (verbose = FALSE)", { ) }) }) - - - - diff --git a/tests/testthat/test-ice.R b/tests/testthat/test-ice.R index af0ea78..afbfd52 100644 --- a/tests/testthat/test-ice.R +++ b/tests/testthat/test-ice.R @@ -4,11 +4,13 @@ library(testthat) # ICE ---- # @@@@@@@@@ -col_names <- c("assay", "endpoint", "substance_type", "casrn", "qsar_ready_id", - "value", "unit", "species", "receptor_species", "route", "sex", - "strain", "life_stage", "tissue", "lesion", "location", - "assay_source", "in_vitro_assay_format", "reference", - "reference_url", "dtxsid", "substance_name", "pubmed_id", "query") +col_names <- c( + "assay", "endpoint", "substance_type", "casrn", "qsar_ready_id", + "value", "unit", "species", "receptor_species", "route", "sex", + "strain", "life_stage", "tissue", "lesion", "location", + "assay_source", "in_vitro_assay_format", "reference", + "reference_url", "dtxsid", "substance_name", "pubmed_id", "query" +) Sys.sleep(4) diff --git a/tests/testthat/test-iris.R b/tests/testthat/test-iris.R index 7f83c38..0937518 100644 --- a/tests/testthat/test-iris.R +++ b/tests/testthat/test-iris.R @@ -6,18 +6,23 @@ library(testthat) # @@@@@@@@@ -col_names <- c("chemical_name", "casrn", "exposure_route", "assessment_type", - "critical_effect_or_tumor_type", "woe_characterization", - "toxicity_value_type", "toxicity_value", "query") +col_names <- c( + "chemical_name", "casrn", "exposure_route", "assessment_type", + "critical_effect_or_tumor_type", "woe_characterization", + "toxicity_value_type", "toxicity_value", "query" +) Sys.sleep(4) test_that("extr_iris_ fetches data for multiple CASRN", { skip_on_cran() ids_search <- c("50-00-0", "1332-21-4") - expect_message({ - out <- extr_iris(ids_search, verbose = TRUE) - }, "Quering" ) + expect_message( + { + out <- extr_iris(ids_search, verbose = TRUE) + }, + "Quering" + ) expect_true(is.data.frame(out)) expect_equal(nrow(out), 4) @@ -30,9 +35,12 @@ Sys.sleep(4) test_that("extr_iris_ warn and fill with NA wrong CASRN", { skip_on_cran() ids_search <- c("50-00-0", "1332-21-4", "bella", "ciao") - expect_warning({ - out <- extr_iris(ids_search, verbose = TRUE) - }, "Chemicals.*found!") + expect_warning( + { + out <- extr_iris(ids_search, verbose = TRUE) + }, + "Chemicals.*found!" + ) expect_equal(nrow(out), 6) expect_true(all(out$query %in% ids_search)) diff --git a/tests/testthat/test-pubchem.R b/tests/testthat/test-pubchem.R index 3471e08..2d0a323 100644 --- a/tests/testthat/test-pubchem.R +++ b/tests/testthat/test-pubchem.R @@ -8,13 +8,16 @@ library(testthat) col_names <- c("cid", "iupac_name", "casrn", "source_name", "source_id", "query") -test_that("extr_ice generate results with 2 cid, one wrong", { +test_that("extr_casrn_from_cid generate results with 2 cid, one wrong", { skip_on_cran() ids_search <- c("bella", "712") - expect_warning({ - out <- extr_casrn_from_cid(pubchem_ids = ids_search, verbose = TRUE) - }, "Chemical .* found!") + expect_warning( + { + out <- extr_casrn_from_cid(pubchem_ids = ids_search, verbose = TRUE) + }, + "Chemical .* found!" + ) expect_equal(sum(is.na(out$casrn)), 1) expect_true(is.data.frame(out)) @@ -24,13 +27,16 @@ test_that("extr_ice generate results with 2 cid, one wrong", { Sys.sleep(4) -test_that("extr_ice generate results with all wrong", { +test_that("extr_casrn_from_cid generate results with all wrong", { skip_on_cran() ids_search <- c("bella", "ciao") - expect_warning({ - out <- extr_casrn_from_cid(pubchem_ids = ids_search, verbose = TRUE) - }, "Chemicals .* found!") + expect_warning( + { + out <- extr_casrn_from_cid(pubchem_ids = ids_search, verbose = TRUE) + }, + "Chemicals .* found!" + ) expect_equal(sum(is.na(out$casrn)), 2) expect_true(is.data.frame(out)) @@ -40,14 +46,13 @@ test_that("extr_ice generate results with all wrong", { Sys.sleep(4) -test_that("extr_ice generate results with all wrong", { +test_that("extr_casrn_from_cid generate results with all wrong", { skip_on_cran() ids_search <- c("bella", "ciao") expect_silent({ out <- extr_casrn_from_cid(pubchem_ids = ids_search, verbose = FALSE) }) - }) @@ -60,7 +65,6 @@ Sys.sleep(4) df_names <- create_na_df("ciao") test_that("extr_chem_info fetches chem outa", { - ids_search <- c("Formaldehyde", "Aflatoxin B1", "bella", "ciao") skip_on_cran() expect_warning({ @@ -76,7 +80,6 @@ test_that("extr_chem_info fetches chem outa", { Sys.sleep(4) test_that("extr_chem_info wrong only, silent", { - ids_search <- "bella ciao" skip_on_cran() expect_silent({ @@ -87,7 +90,6 @@ test_that("extr_chem_info wrong only, silent", { expect_equal(nrow(out), length(ids_search)) expect_equal(names(out), names(df_names)) expect_true(all(out$query %in% ids_search)) - }) # @@@@@@@@@@@@@@@ @@ -118,25 +120,31 @@ test_that("extr_pubchem_fema works correctly", { expect_equal(nrow(out), length(casrn_list)) expect_equal(names(out), col_names) expect_equal(out$query, casrn_list) - expect_equal(out$casrn , c("1490-04-6", "50-00-0", NA)) + expect_equal(out$casrn, c("1490-04-6", "50-00-0", NA)) }) Sys.sleep(4) test_that("extr_pubchem_fema produce CASRN warning", { skip_on_cran() - expect_warning({ + expect_warning( + { out <- extr_pubchem_fema(c("bella", "ciao"), verbose = TRUE) - }, "Chemical.*not found!") + }, + "Chemical.*not found!" + ) }) Sys.sleep(4) test_that("extr_pubchem_fema produce FEMA warning", { skip_on_cran() - expect_warning({ - out <- extr_pubchem_fema("50-00-0", verbose = TRUE) - }, "FEMA .*not found") + expect_warning( + { + out <- extr_pubchem_fema("50-00-0", verbose = TRUE) + }, + "FEMA .*not found" + ) }) Sys.sleep(4) @@ -151,15 +159,17 @@ test_that("extr_pubchem_ghs works correctly", { expect_equal(unique(out$query), casrn_list) expect_equal(names(out), col_names) - expect_equal(unique(out$casrn) , c("1490-04-6", "50-00-0", NA)) + expect_equal(unique(out$casrn), c("1490-04-6", "50-00-0", NA)) }) Sys.sleep(4) test_that("extr_pubchem_ghs produce warning", { skip_on_cran() - expect_warning({ - out <- extr_pubchem_ghs(c("bella", "ciao"), verbose = TRUE) - }, "not found") + expect_warning( + { + out <- extr_pubchem_ghs(c("bella", "ciao"), verbose = TRUE) + }, + "not found" + ) }) - diff --git a/tests/testthat/test-tox.R b/tests/testthat/test-tox.R index f1218ca..9127ee8 100644 --- a/tests/testthat/test-tox.R +++ b/tests/testthat/test-tox.R @@ -4,9 +4,21 @@ library(testthat) # TOX ---- # @@@@@@@@@ +col_names <- c("who_iarc_monographs", "pprtv", "ghs_dat", "iris", "ice", + "comptox_cover_sheet", "comptox_main_data", "comptox_abstract_sifter", + "comptox_synonym_identifier", "comptox_related_relationships", + "comptox_toxcast_assays_ac50", "comptox_toxval_details", + "comptox_chemical_properties") + # Sys.sleep(5) -test_that("extr_tox fetches data for CASRN 50-00-0", { +test_that("extr_tox fetches data for CASRN 50-00-0 and warn", { skip_on_cran() - result <- extr_tox(casrn = "50-00-0") - expect_snapshot(result[!names(result) %in% "comptox_cover_sheet"]) + expect_no_warning({ + out <- extr_tox(casrn = c("50-00-0", "ciao"), verbose = FALSE) + }) + + expect_true(is.list(out)) + expect_true(all(unlist(lapply(out, is.data.frame)))) + expect_equal(names(out), col_names) }) + diff --git a/tests/testthat/test_monograph.R b/tests/testthat/test_monograph.R index 78fa06c..0eb48c0 100644 --- a/tests/testthat/test_monograph.R +++ b/tests/testthat/test_monograph.R @@ -1,7 +1,9 @@ library(testthat) -col_names <- c("casrn", "agent", "group", "volume", "volume_publication_year", - "evaluation_year", "additional_information", "query") +col_names <- c( + "casrn", "agent", "group", "volume", "volume_publication_year", + "evaluation_year", "additional_information", "query" +) test_that("extr_monograph returns correct outs for CASRN search", { ids <- c("105-74-8", "120-58-1") diff --git a/tests/testthat/test_pprtv.R b/tests/testthat/test_pprtv.R index c32c85c..6ee625c 100644 --- a/tests/testthat/test_pprtv.R +++ b/tests/testthat/test_pprtv.R @@ -3,13 +3,17 @@ library(testthat) temp_dir <- tempdir() test_that("extr_pprtv casrn hit and not hit, verbose, force = TRUE", { - - ids_search = c("112-27-6", "98-86-2") - - expect_message({ - with_extr_sandbox(temp_dir = temp_dir, - out <- extr_pprtv(ids = ids_search, force = TRUE, verbose = TRUE) - )}, "Extracting EPA PPRTVs.") + ids_search <- c("112-27-6", "98-86-2") + + expect_message( + { + with_extr_sandbox( + temp_dir = temp_dir, + out <- extr_pprtv(ids = ids_search, force = TRUE, verbose = TRUE) + ) + }, + "Extracting EPA PPRTVs." + ) tmp_out <- fs::path(temp_dir, "R", "extractox") cache_exist <- fs::file_exists(fs::path(tmp_out, "epa_pprtvs.rds")) @@ -21,62 +25,59 @@ test_that("extr_pprtv casrn hit and not hit, verbose, force = TRUE", { }) test_that("Function to warn with verbose = TRUE", { - - ids_search = c("112-27-6", "bella", "ciao") - expect_warning({ - with_extr_sandbox(temp_dir = temp_dir, - out <- extr_pprtv(ids = ids_search, - force = FALSE, verbose = TRUE) - ) - }, "Chemicals .* not found!") + ids_search <- c("112-27-6", "bella", "ciao") + expect_warning( + { + with_extr_sandbox( + temp_dir = temp_dir, + out <- extr_pprtv( + ids = ids_search, + force = FALSE, verbose = TRUE + ) + ) + }, + "Chemicals .* not found!" + ) expect_equal(out$query, ids_search) expect_equal(nrow(out), length(ids_search)) expect_true(is.na(out$casrn[[3]])) - }) +}) test_that("Function verbose = FALSE", { - - ids_search = c("112-27-6", "98-86-2") + ids_search <- c("112-27-6", "98-86-2") expect_silent({ - with_extr_sandbox(temp_dir = temp_dir, - out <- extr_pprtv(ids = ids_search, - force = FALSE, verbose = FALSE) + with_extr_sandbox( + temp_dir = temp_dir, + out <- extr_pprtv( + ids = ids_search, + force = FALSE, verbose = FALSE + ) ) }) }) test_that("extr_pprtv na,es hit and not hit, verbose, force = TRUE", { - - ids_search = c("Ace", "Acetophenone") - - expect_message({ - with_extr_sandbox(temp_dir = temp_dir, - out <- extr_pprtv(ids = ids_search, - - search_type = "name", - force = TRUE, - verbose = TRUE) - )}, "Extracting EPA PPRTVs.") + ids_search <- c("Ace", "Acetophenone") + + expect_message( + { + with_extr_sandbox( + temp_dir = temp_dir, + out <- extr_pprtv( + ids = ids_search, + search_type = "name", + force = TRUE, + verbose = TRUE + ) + ) + }, + "Extracting EPA PPRTVs." + ) tmp_out <- fs::path(temp_dir, "R", "extractox") cache_exist <- fs::file_exists(fs::path(tmp_out, "epa_pprtvs.rds")) expect_equal(nrow(out), 11) - }) - - - - - - - - - - - - - -