diff options
-rw-r--r-- | .Rhistory | 4 | ||||
-rw-r--r-- | DESCRIPTION | 4 | ||||
-rw-r--r-- | NAMESPACE | 2 | ||||
-rw-r--r-- | R/chent.R | 204 | ||||
-rw-r--r-- | _pkgdown.yml | 2 | ||||
-rw-r--r-- | docs/404.html | 2 | ||||
-rw-r--r-- | docs/authors.html | 6 | ||||
-rw-r--r-- | docs/index.html | 2 | ||||
-rw-r--r-- | docs/pkgdown.yml | 2 | ||||
-rw-r--r-- | docs/reference/chent.html | 319 | ||||
-rw-r--r-- | docs/reference/draw_svg.chent.html | 2 | ||||
-rw-r--r-- | docs/reference/index.html | 6 | ||||
-rw-r--r-- | docs/reference/pai.html | 43 | ||||
-rw-r--r-- | docs/reference/plot.chent.html | 2 | ||||
-rw-r--r-- | docs/reference/ppp.html | 194 | ||||
-rw-r--r-- | docs/reference/print.chent.html | 2 | ||||
-rw-r--r-- | docs/reference/print.pai.html | 2 | ||||
-rw-r--r-- | docs/sitemap.xml | 3 | ||||
-rw-r--r-- | man/chent.Rd | 144 | ||||
-rw-r--r-- | man/pai.Rd | 26 | ||||
-rw-r--r-- | man/pp.Rd | 77 | ||||
-rw-r--r-- | man/ppp.Rd | 100 |
22 files changed, 982 insertions, 166 deletions
diff --git a/.Rhistory b/.Rhistory new file mode 100644 index 0000000..1a9e67f --- /dev/null +++ b/.Rhistory @@ -0,0 +1,4 @@ +library(chents) +?chent +library(chents) +?chent diff --git a/DESCRIPTION b/DESCRIPTION index e75912b..879bee7 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,8 +1,8 @@ Package: chents Type: Package Title: Chemical Entities as R Objects -Version: 0.3.1 -Date: 2023-11-10 +Version: 0.3.2 +Date: 2023-11-11 Authors@R: c(person("Johannes", "Ranke", role = c("aut", "cre", "cph"), email = "johannes.ranke@jrwb.de")) Description: Utilities for dealing with chemical entities and associated @@ -6,7 +6,7 @@ S3method(print,pai) export(chent) export(draw_svg.chent) export(pai) -export(pp) +export(ppp) importFrom(R6,R6Class) importFrom(grImport,PostScriptTrace) importFrom(grImport,grid.picture) @@ -23,6 +23,7 @@ #' if (!is.null(caffeine$Picture)) { #' plot(caffeine) #' } + chent <- R6Class("chent", public = list( #' @field identifier (`character(1)`)\cr @@ -241,6 +242,7 @@ chent <- R6Class("chent", #' @param repo Should the file be looked for in the current working #' directory, a local git repository under `~/git/chyaml`, or from #' the web (not implemented). + #' @param chyaml The filename to be looked for get_chyaml = function(repo = c("wd", "local", "web"), chyaml = paste0(URLencode(self$identifier), ".yaml")) { @@ -287,8 +289,15 @@ chent <- R6Class("chent", }, #' Add a water solubility - #' @param p0 The water solubility in mg/L - add_cwsat = function(cwsat, T = NA, pH = NA, source = NA, page = NA, remark = "") { + #' @param cwsat The water solubility in mg/L + #' @param T Temperature + #' @param pH The pH value + #' @param source An acronym specifying the source of the information + #' @param page The page from which the information was taken + #' @param remark A remark + add_cwsat = function(cwsat, T = NA, pH = NA, + source = NA, page = NA, remark = "") + { self$cwsat <- cwsat attr(self$cwsat, "T") <- T attr(self$cwsat, "pH") <- pH @@ -299,7 +308,13 @@ chent <- R6Class("chent", #' Add a plant uptake factor #' @param PUF The plant uptake factor, a number between 0 and 1 - add_PUF = function(PUF = 0, source = "focus_generic_gw_2014", page = 41, remark = "Conservative default value") { + #' @param source An acronym specifying the source of the information + #' @param page The page from which the information was taken + #' @param remark A remark + add_PUF = function(PUF = 0, + source = "focus_generic_gw_2014", page = 41, + remark = "Conservative default value") + { self$PUF <- PUF attr(self$PUF, "source") <- source attr(self$PUF, "page") <- page @@ -326,13 +341,22 @@ chent <- R6Class("chent", #' @field transformations Data frame of observed transformations transformations = data.frame(study_type = character(0), - TP_identifier = character(0), - max_occurrence = numeric(0), - source = character(0), - pages = character(0), - stringsAsFactors = FALSE), + TP_identifier = character(0), + max_occurrence = numeric(0), + source = character(0), + page = character(0), + stringsAsFactors = FALSE), #' Add a line in the internal dataframe holding observed transformations + #' @param study_type A characterisation of the study type + #' @param TP_identifier An identifier of one of the transformation products + #' in `self$TPs` + #' @param max_occurrence The maximum observed occurrence of the + #' transformation product, expressed as a fraction of the amount that would + #' result from stochiometric transformation + #' @param source An acronym specifying the source of the information + #' @param pages The page from which the information was taken + #' @param remark A remark add_transformation = function(study_type, TP_identifier, max_occurrence, remark = "", source = NA, pages = NA) { @@ -344,19 +368,40 @@ chent <- R6Class("chent", if (is.numeric(pages)) pages <- paste(pages, collapse = ", ") cn <- colnames(self$transformations) self$transformations <- rbind(self$transformations, - data.frame(study_type = study_type, - TP_identifier = TP_identifier, - max_occurrence = max_occurrence, - remark = remark, - source = source, - pages = pages, - stringsAsFactors = FALSE)) + data.frame(study_type = study_type, + TP_identifier = TP_identifier, + max_occurrence = max_occurrence, + remark = remark, + source = source, + page = page, + stringsAsFactors = FALSE)) }, #' @field soil_degradation Dataframe of modelling DT50 values soil_degradation = NULL, #' Add a line in the internal dataframe holding modelling DT50 values + #' @param soils Names of the soils + #' @param DT50_mod The modelling DT50 in the sense of regulatory pesticide + #' fate modelling + #' @param DT50_mod_ref The normalised modelling DT50 in the sense of + #' regulatory pesticide fate modelling + #' @param type The soil type + #' @param country The country (mainly for field studies) + #' @param pH_orig The pH stated in the study + #' @param pH_medium The medium in which this pH was measured + #' @param pH_H2O The pH extrapolated to pure water + #' @param perc_OC The percentage of organic carbon in the soil + #' @param temperature The temperature during the study in degrees Celsius + #' @param moisture The moisture during the study + #' @param category Is it a laboratory ('lab') or field study ('field') + #' @param formulation Name of the formulation applied, if it was not + #' the technical active ingredient + #' @param model The degradation model used for deriving `DT50_mod` + #' @param chi2 The relative error as defined in FOCUS kinetics + #' @param source An acronym specifying the source of the information + #' @param page The page from which the information was taken + #' @param remark A remark add_soil_degradation = function(soils, DT50_mod, DT50_mod_ref, type = NA, country = NA, pH_orig = NA, pH_medium = NA, pH_H2O = NA, @@ -396,7 +441,13 @@ chent <- R6Class("chent", #' @field soil_ff Dataframe of formation fractions soil_ff = NULL, - add_soil_ff = function(target, soils, ff = 1, remark = "", source, page = NA) { + # Add one or more formation fractions for degradation in soil + #' @param target The identifier(s) of the transformation product + #' @param soils The soil name(s) in which the transformation was observed + #' @param ff The formation fraction(s) + add_soil_ff = function(target, soils, ff = 1, + remark = "", source, page = NA) + { new_soil_ff = data.frame( target = target, target = target, @@ -416,12 +467,19 @@ chent <- R6Class("chent", #' @field soil_sorption Dataframe of soil sorption data soil_sorption = NULL, + #' Add soil sorption data + #' @param Kf The sorption constant in L/kg, either linear (then `N` is 1) + #' or according to Freundlich + #' @param Kfoc The constant from above, normalised to soil organic carbon + #' @param N The Freundlich exponent + #' @param perc_clay The percentage of clay in the soil + #' @param CEC The cation exchange capacity add_soil_sorption = function(soils, Kf, Kfoc, N, - type = NA, - pH_orig = NA, pH_medium = NA, - pH_H2O = NA, - perc_OC = NA, perc_clay = NA, CEC = NA, - remark = "", source, page = NA) { + type = NA, pH_orig = NA, pH_medium = NA, + pH_H2O = NA, + perc_OC = NA, perc_clay = NA, CEC = NA, + remark = "", source, page = NA) + { new_soil_sorption = data.frame( soils = soils, Kf = Kf, Kfoc = Kfoc, N = N, @@ -441,6 +499,10 @@ chent <- R6Class("chent", } }, + #' Write a PDF image of the structure + #' @param file The file to write to + #' @param dir The directory to write the file to + #' @param template A template expressed as SMILES to use in RDKit pdf = function(file = paste0(self$identifier, ".pdf"), dir = "structures/pdf", template = NULL) { if (!dir.exists(dir)) { @@ -462,8 +524,12 @@ chent <- R6Class("chent", m_line <- suppressWarnings(grep("MediaBox", head, value = TRUE)) self$pdf_height <- as.numeric(gsub("/MediaBox \\[.* (.*)\\]", "\\1", m_line)) }, - png = function(file = paste0(self$identifier, ".png"), dir = "structures/png", - antialias = 'gray') { + + #' Write a PNG image of the structure + #' @param antialias Passed to [png][grDevices::png] + png = function(file = paste0(self$identifier, ".png"), + dir = "structures/png", antialias = 'gray') + { if (!dir.exists(dir)) { message("Directory '", dir, "' does not exist") message("Trying to create directory '", dir, "'") @@ -475,7 +541,12 @@ chent <- R6Class("chent", plot(self) dev.off() }, - emf = function(file = paste0(self$identifier, ".emf"), dir = "structures/emf") { + + #' Write an EMF image of the structure using [emf][devEMF::emf] + #' @param file The file to write to + emf = function(file = paste0(self$identifier, ".emf"), + dir = "structures/emf") + { if (!requireNamespace("devEMF")) { stop("You need to have the devEMF package installed for this function") } @@ -521,8 +592,8 @@ print.chent = function(x, ...) { #' @param subdir The path to which the file should be written #' @export draw_svg.chent = function(x, width = 300, height = 150, - filename = paste0(names(x$identifier), ".svg"), - subdir = "svg") { + filename = paste0(names(x$identifier), ".svg"), + subdir = "svg") { if (!rdkit_available) { stop("RDkit is not available via reticulate") } else { @@ -560,8 +631,6 @@ plot.chent = function(x, ...) { #' @importFrom R6 R6Class #' @export #' @format An \code{\link{R6Class}} generator object -#' @field iso ISO common name according to ISO 1750 as retreived from pesticidecompendium.bcpc.org -#' @field bcpc List of information retrieved from pesticidecompendium.bcpc.org #' @examples #' # On Travis, we get a certificate validation error, #' # likely because the system (xenial) is so old, @@ -575,18 +644,35 @@ plot.chent = function(x, ...) { #' } #' #' } + pai <- R6Class("pai", inherit = chent, - public <- list( + public = list( + + #' @field iso ISO common name of the active ingredient according to ISO 1750 iso = NULL, + + #' @field bcpc Information retrieved from the BCPC compendium available online + #' at <pesticidecompendium.bcpc.org> bcpc = NULL, + + #' Creates a new instance of this [R6][R6::R6Class] class. + #' + #' @description This class is derived from [chent]. It makes it easy + #' to create a [chent] from the ISO common name of a pesticide active + #' ingredient, and additionally stores the ISO name as well as + #' the complete result of querying the BCPC compendium using + #' [bcpc_query][webchem::bcpc_query]. + #' + #' @param iso The ISO common name to be used in the query of the + #' BCPC compendium + #' + #' @param identifier Alternative identifier used for querying pubchem initialize = function(iso, identifier = iso, - smiles = NULL, - inchikey = NULL, - bcpc = TRUE, - pubchem = TRUE, pubchem_from = 'auto', - rdkit = TRUE, template = NULL, - chyaml = TRUE) + smiles = NULL, inchikey = NULL, bcpc = TRUE, + pubchem = TRUE, pubchem_from = 'auto', + rdkit = TRUE, template = NULL, + chyaml = TRUE) { if (!is.null(inchikey)) { @@ -631,10 +717,9 @@ pai <- R6Class("pai", } super$initialize(identifier = identifier, - smiles = smiles, - inchikey = self$inchikey, - pubchem = pubchem, pubchem_from = pubchem_from, - rdkit = rdkit, template = template, chyaml = chyaml) + smiles = smiles, inchikey = self$inchikey, + pubchem = pubchem, pubchem_from = pubchem_from, + rdkit = rdkit, template = template, chyaml = chyaml) invisible(self) } @@ -659,30 +744,47 @@ print.pai = function(x, ...) { } } -#' R6 class for holding a product with at least one active ingredient +#' @title R6 class for a plant protection product with at least one active ingredient #' -#' An R6 class for holding information about a product with at least one active ingredient +#' @description Contains basic information about the active ingredients in the +#' product #' #' @docType class #' @importFrom R6 R6Class #' @export #' @format An \code{\link{R6Class}} generator object. -#' @field name The name of the product -#' @field ais A list of active ingredients -#' @field concentrations The concentration of the ais -#' @field concentration_units Defaults to g/L -#' @keywords data - -pp <- R6Class("pp", - public <- list( + +ppp <- R6Class("ppp", + public = list( + + #' @field name The name of the product name = NULL, + + #' @field ais A list of active ingredients ais = list(), + + #' @field concentrations The concentration of the ais concentrations = NULL, + + #' @field concentration_units Defaults to g/L concentration_units = NULL, + + #' @field density The density of the product density = NULL, + + #' @field density_units Defaults to g/L density_units = "g/L", + + #' Creates a new instance of this [R6][R6::R6Class] class. + #' + #' @field ... Identifiers of the active ingredients + #' @field concentrations Concentrations of the active ingredients + #' @field concentration_units Defaults to g/L + #' @field density The density + #' @field density_units Defaults to g/L initialize = function(name, ..., concentrations, concentration_units = "g/L", - density = 1000, density_units = "g/L") { + density = 1000, density_units = "g/L") + { self$name <- name self$ais <- list(...) self$concentrations <- concentrations @@ -691,6 +793,8 @@ pp <- R6Class("pp", names(self$concentrations) <- names(self$ais) self$concentration_units <- concentration_units }, + + #' Printing method print = function() { cat("<pp> named", self$name, "\n") } diff --git a/_pkgdown.yml b/_pkgdown.yml index 2d8ddc3..f099651 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -12,4 +12,4 @@ reference: - print.chent - pai - print.pai - - pp + - ppp diff --git a/docs/404.html b/docs/404.html index eb79a5d..26a509c 100644 --- a/docs/404.html +++ b/docs/404.html @@ -32,7 +32,7 @@ </button> <span class="navbar-brand"> <a class="navbar-link" href="index.html">chents</a> - <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="">0.3.1</span> + <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="">0.3.2</span> </span> </div> diff --git a/docs/authors.html b/docs/authors.html index 0c3b654..1e764a7 100644 --- a/docs/authors.html +++ b/docs/authors.html @@ -17,7 +17,7 @@ </button> <span class="navbar-brand"> <a class="navbar-link" href="index.html">chents</a> - <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="">0.3.1</span> + <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="">0.3.2</span> </span> </div> @@ -60,13 +60,13 @@ <p>Ranke J (2023). <em>chents: Chemical Entities as R Objects</em>. -R package version 0.3.1, <a href="https://github.com/jranke/chents" class="external-link">https://github.com/jranke/chents</a>. +R package version 0.3.2, <a href="https://github.com/jranke/chents" class="external-link">https://github.com/jranke/chents</a>. </p> <pre>@Manual{, title = {chents: Chemical Entities as R Objects}, author = {Johannes Ranke}, year = {2023}, - note = {R package version 0.3.1}, + note = {R package version 0.3.2}, url = {https://github.com/jranke/chents}, }</pre> diff --git a/docs/index.html b/docs/index.html index f241bb6..313ff06 100644 --- a/docs/index.html +++ b/docs/index.html @@ -37,7 +37,7 @@ </button> <span class="navbar-brand"> <a class="navbar-link" href="index.html">chents</a> - <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="">0.3.1</span> + <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="">0.3.2</span> </span> </div> diff --git a/docs/pkgdown.yml b/docs/pkgdown.yml index dd7c4f0..eb77ea1 100644 --- a/docs/pkgdown.yml +++ b/docs/pkgdown.yml @@ -2,5 +2,5 @@ pandoc: 3.1.1 pkgdown: 2.0.7 pkgdown_sha: ~ articles: {} -last_built: 2023-11-10T17:41Z +last_built: 2023-11-11T07:23Z diff --git a/docs/reference/chent.html b/docs/reference/chent.html index a6b8dde..48ccf3f 100644 --- a/docs/reference/chent.html +++ b/docs/reference/chent.html @@ -19,7 +19,7 @@ generated using RDKit if RDKit and its python bindings are installed."><!-- math </button> <span class="navbar-brand"> <a class="navbar-link" href="../index.html">chents</a> - <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="">0.3.1</span> + <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="">0.3.2</span> </span> </div> @@ -126,15 +126,18 @@ List of information retrieved from PubChem</p></dd> <dt><code>TPs</code></dt> -<dd><p>List of transformation products as chent objects</p></dd> +<dd><p>List of transformation products as chent objects +Add a transformation product to the internal list</p></dd> <dt><code>transformations</code></dt> -<dd><p>Data frame of observed transformations</p></dd> +<dd><p>Data frame of observed transformations +Add a line in the internal dataframe holding observed transformations</p></dd> <dt><code>soil_degradation</code></dt> -<dd><p>Dataframe of modelling DT50 values</p></dd> +<dd><p>Dataframe of modelling DT50 values +Add a line in the internal dataframe holding modelling DT50 values</p></dd> <dt><code>soil_ff</code></dt> @@ -142,7 +145,8 @@ List of information retrieved from PubChem</p></dd> <dt><code>soil_sorption</code></dt> -<dd><p>Dataframe of soil sorption data</p></dd> +<dd><p>Dataframe of soil sorption data +Add soil sorption data</p></dd> </dl><p></p></div> @@ -262,7 +266,8 @@ Get chemical information from PubChem for a known PubChem CID</p></dd> <div class="section"> <h4 id="arguments-2">Arguments<a class="anchor" aria-label="anchor" href="#arguments-2"></a></h4> <p></p><div class="arguments"><dl><dt><code>pubchem_cid</code></dt> -<dd><p>CID</p></dd> +<dd><p>CID +Get chemical information from RDKit if available</p></dd> </dl><p></p></div> @@ -276,6 +281,15 @@ Get chemical information from PubChem for a known PubChem CID</p></dd> <p></p><div class="r"><div class="sourceCode"><pre><code><span><span class="va">chent</span><span class="op">$</span><span class="fu">get_rdkit</span><span class="op">(</span>template <span class="op">=</span> <span class="cn">NULL</span><span class="op">)</span></span></code></pre></div><p></p></div> </div> +<div class="section"> +<h4 id="arguments-3">Arguments<a class="anchor" aria-label="anchor" href="#arguments-3"></a></h4> +<p></p><div class="arguments"><dl><dt><code>template</code></dt> +<dd><p>Optional template specified as a SMILES code +Obtain information from a YAML file</p></dd> + + +</dl><p></p></div> +</div> </div><p></p><hr><a id="method-chent-get_chyaml"></a><div class="section"> <h3 id="method-get-chyaml-">Method <code>get_chyaml()</code><a class="anchor" aria-label="anchor" href="#method-get-chyaml-"></a></h3> @@ -288,6 +302,21 @@ Get chemical information from PubChem for a known PubChem CID</p></dd> <span><span class="op">)</span></span></code></pre></div><p></p></div> </div> +<div class="section"> +<h4 id="arguments-4">Arguments<a class="anchor" aria-label="anchor" href="#arguments-4"></a></h4> +<p></p><div class="arguments"><dl><dt><code>repo</code></dt> +<dd><p>Should the file be looked for in the current working +directory, a local git repository under <code>~/git/chyaml</code>, or from +the web (not implemented).</p></dd> + + +<dt><code>chyaml</code></dt> +<dd><p>The filename to be looked for +Add a vapour pressure</p></dd> + + +</dl><p></p></div> +</div> </div><p></p><hr><a id="method-chent-add_p0"></a><div class="section"> <h3 id="method-add-p-">Method <code>add_p0()</code><a class="anchor" aria-label="anchor" href="#method-add-p-"></a></h3> @@ -297,6 +326,31 @@ Get chemical information from PubChem for a known PubChem CID</p></dd> <p></p><div class="r"><div class="sourceCode"><pre><code><span><span class="va">chent</span><span class="op">$</span><span class="fu">add_p0</span><span class="op">(</span><span class="va">p0</span>, T <span class="op">=</span> <span class="cn">NA</span>, source <span class="op">=</span> <span class="cn">NA</span>, page <span class="op">=</span> <span class="cn">NA</span>, remark <span class="op">=</span> <span class="st">""</span><span class="op">)</span></span></code></pre></div><p></p></div> </div> +<div class="section"> +<h4 id="arguments-5">Arguments<a class="anchor" aria-label="anchor" href="#arguments-5"></a></h4> +<p></p><div class="arguments"><dl><dt><code>p0</code></dt> +<dd><p>The vapour pressure in Pa</p></dd> + + +<dt><code>T</code></dt> +<dd><p>Temperature</p></dd> + + +<dt><code>source</code></dt> +<dd><p>An acronym specifying the source of the information</p></dd> + + +<dt><code>page</code></dt> +<dd><p>The page from which the information was taken</p></dd> + + +<dt><code>remark</code></dt> +<dd><p>A remark +Add a water solubility</p></dd> + + +</dl><p></p></div> +</div> </div><p></p><hr><a id="method-chent-add_cwsat"></a><div class="section"> <h3 id="method-add-cwsat-">Method <code>add_cwsat()</code><a class="anchor" aria-label="anchor" href="#method-add-cwsat-"></a></h3> @@ -306,6 +360,35 @@ Get chemical information from PubChem for a known PubChem CID</p></dd> <p></p><div class="r"><div class="sourceCode"><pre><code><span><span class="va">chent</span><span class="op">$</span><span class="fu">add_cwsat</span><span class="op">(</span><span class="va">cwsat</span>, T <span class="op">=</span> <span class="cn">NA</span>, pH <span class="op">=</span> <span class="cn">NA</span>, source <span class="op">=</span> <span class="cn">NA</span>, page <span class="op">=</span> <span class="cn">NA</span>, remark <span class="op">=</span> <span class="st">""</span><span class="op">)</span></span></code></pre></div><p></p></div> </div> +<div class="section"> +<h4 id="arguments-6">Arguments<a class="anchor" aria-label="anchor" href="#arguments-6"></a></h4> +<p></p><div class="arguments"><dl><dt><code>cwsat</code></dt> +<dd><p>The water solubility in mg/L</p></dd> + + +<dt><code>T</code></dt> +<dd><p>Temperature</p></dd> + + +<dt><code>pH</code></dt> +<dd><p>The pH value</p></dd> + + +<dt><code>source</code></dt> +<dd><p>An acronym specifying the source of the information</p></dd> + + +<dt><code>page</code></dt> +<dd><p>The page from which the information was taken</p></dd> + + +<dt><code>remark</code></dt> +<dd><p>A remark +Add a plant uptake factor</p></dd> + + +</dl><p></p></div> +</div> </div><p></p><hr><a id="method-chent-add_PUF"></a><div class="section"> <h3 id="method-add-puf-">Method <code>add_PUF()</code><a class="anchor" aria-label="anchor" href="#method-add-puf-"></a></h3> @@ -320,6 +403,26 @@ Get chemical information from PubChem for a known PubChem CID</p></dd> <span><span class="op">)</span></span></code></pre></div><p></p></div> </div> +<div class="section"> +<h4 id="arguments-7">Arguments<a class="anchor" aria-label="anchor" href="#arguments-7"></a></h4> +<p></p><div class="arguments"><dl><dt><code>PUF</code></dt> +<dd><p>The plant uptake factor, a number between 0 and 1</p></dd> + + +<dt><code>source</code></dt> +<dd><p>An acronym specifying the source of the information</p></dd> + + +<dt><code>page</code></dt> +<dd><p>The page from which the information was taken</p></dd> + + +<dt><code>remark</code></dt> +<dd><p>A remark</p></dd> + + +</dl><p></p></div> +</div> </div><p></p><hr><a id="method-chent-add_TP"></a><div class="section"> <h3 id="method-add-tp-">Method <code>add_TP()</code><a class="anchor" aria-label="anchor" href="#method-add-tp-"></a></h3> @@ -329,6 +432,22 @@ Get chemical information from PubChem for a known PubChem CID</p></dd> <p></p><div class="r"><div class="sourceCode"><pre><code><span><span class="va">chent</span><span class="op">$</span><span class="fu">add_TP</span><span class="op">(</span><span class="va">x</span>, smiles <span class="op">=</span> <span class="cn">NULL</span>, pubchem <span class="op">=</span> <span class="cn">FALSE</span><span class="op">)</span></span></code></pre></div><p></p></div> </div> +<div class="section"> +<h4 id="arguments-8">Arguments<a class="anchor" aria-label="anchor" href="#arguments-8"></a></h4> +<p></p><div class="arguments"><dl><dt><code>x</code></dt> +<dd><p>A chent object, or an identifier to generate a chent object</p></dd> + + +<dt><code>smiles</code></dt> +<dd><p>A SMILES code for defining a chent object</p></dd> + + +<dt><code>pubchem</code></dt> +<dd><p>Should chemical information be obtained from PubChem?</p></dd> + + +</dl><p></p></div> +</div> </div><p></p><hr><a id="method-chent-add_transformation"></a><div class="section"> <h3 id="method-add-transformation-">Method <code>add_transformation()</code><a class="anchor" aria-label="anchor" href="#method-add-transformation-"></a></h3> @@ -345,6 +464,37 @@ Get chemical information from PubChem for a known PubChem CID</p></dd> <span><span class="op">)</span></span></code></pre></div><p></p></div> </div> +<div class="section"> +<h4 id="arguments-9">Arguments<a class="anchor" aria-label="anchor" href="#arguments-9"></a></h4> +<p></p><div class="arguments"><dl><dt><code>study_type</code></dt> +<dd><p>A characterisation of the study type</p></dd> + + +<dt><code>TP_identifier</code></dt> +<dd><p>An identifier of one of the transformation products +in <code>self$TPs</code></p></dd> + + +<dt><code>max_occurrence</code></dt> +<dd><p>The maximum observed occurrence of the +transformation product, expressed as a fraction of the amount that would +result from stochiometric transformation</p></dd> + + +<dt><code>remark</code></dt> +<dd><p>A remark</p></dd> + + +<dt><code>source</code></dt> +<dd><p>An acronym specifying the source of the information</p></dd> + + +<dt><code>pages</code></dt> +<dd><p>The page from which the information was taken</p></dd> + + +</dl><p></p></div> +</div> </div><p></p><hr><a id="method-chent-add_soil_degradation"></a><div class="section"> <h3 id="method-add-soil-degradation-">Method <code>add_soil_degradation()</code><a class="anchor" aria-label="anchor" href="#method-add-soil-degradation-"></a></h3> @@ -373,6 +523,85 @@ Get chemical information from PubChem for a known PubChem CID</p></dd> <span><span class="op">)</span></span></code></pre></div><p></p></div> </div> +<div class="section"> +<h4 id="arguments-10">Arguments<a class="anchor" aria-label="anchor" href="#arguments-10"></a></h4> +<p></p><div class="arguments"><dl><dt><code>soils</code></dt> +<dd><p>Names of the soils</p></dd> + + +<dt><code>DT50_mod</code></dt> +<dd><p>The modelling DT50 in the sense of regulatory pesticide +fate modelling</p></dd> + + +<dt><code>DT50_mod_ref</code></dt> +<dd><p>The normalised modelling DT50 in the sense of +regulatory pesticide fate modelling</p></dd> + + +<dt><code>type</code></dt> +<dd><p>The soil type</p></dd> + + +<dt><code>country</code></dt> +<dd><p>The country (mainly for field studies)</p></dd> + + +<dt><code>pH_orig</code></dt> +<dd><p>The pH stated in the study</p></dd> + + +<dt><code>pH_medium</code></dt> +<dd><p>The medium in which this pH was measured</p></dd> + + +<dt><code>pH_H2O</code></dt> +<dd><p>The pH extrapolated to pure water</p></dd> + + +<dt><code>perc_OC</code></dt> +<dd><p>The percentage of organic carbon in the soil</p></dd> + + +<dt><code>temperature</code></dt> +<dd><p>The temperature during the study in degrees Celsius</p></dd> + + +<dt><code>moisture</code></dt> +<dd><p>The moisture during the study</p></dd> + + +<dt><code>category</code></dt> +<dd><p>Is it a laboratory ('lab') or field study ('field')</p></dd> + + +<dt><code>formulation</code></dt> +<dd><p>Name of the formulation applied, if it was not +the technical active ingredient</p></dd> + + +<dt><code>model</code></dt> +<dd><p>The degradation model used for deriving <code>DT50_mod</code></p></dd> + + +<dt><code>chi2</code></dt> +<dd><p>The relative error as defined in FOCUS kinetics</p></dd> + + +<dt><code>remark</code></dt> +<dd><p>A remark</p></dd> + + +<dt><code>source</code></dt> +<dd><p>An acronym specifying the source of the information</p></dd> + + +<dt><code>page</code></dt> +<dd><p>The page from which the information was taken</p></dd> + + +</dl><p></p></div> +</div> </div><p></p><hr><a id="method-chent-add_soil_ff"></a><div class="section"> <h3 id="method-add-soil-ff-">Method <code>add_soil_ff()</code><a class="anchor" aria-label="anchor" href="#method-add-soil-ff-"></a></h3> @@ -382,6 +611,22 @@ Get chemical information from PubChem for a known PubChem CID</p></dd> <p></p><div class="r"><div class="sourceCode"><pre><code><span><span class="va">chent</span><span class="op">$</span><span class="fu">add_soil_ff</span><span class="op">(</span><span class="va">target</span>, <span class="va">soils</span>, ff <span class="op">=</span> <span class="fl">1</span>, remark <span class="op">=</span> <span class="st">""</span>, <span class="va">source</span>, page <span class="op">=</span> <span class="cn">NA</span><span class="op">)</span></span></code></pre></div><p></p></div> </div> +<div class="section"> +<h4 id="arguments-11">Arguments<a class="anchor" aria-label="anchor" href="#arguments-11"></a></h4> +<p></p><div class="arguments"><dl><dt><code>target</code></dt> +<dd><p>The identifier(s) of the transformation product</p></dd> + + +<dt><code>soils</code></dt> +<dd><p>The soil name(s) in which the transformation was observed</p></dd> + + +<dt><code>ff</code></dt> +<dd><p>The formation fraction(s)</p></dd> + + +</dl><p></p></div> +</div> </div><p></p><hr><a id="method-chent-add_soil_sorption"></a><div class="section"> <h3 id="method-add-soil-sorption-">Method <code>add_soil_sorption()</code><a class="anchor" aria-label="anchor" href="#method-add-soil-sorption-"></a></h3> @@ -406,6 +651,32 @@ Get chemical information from PubChem for a known PubChem CID</p></dd> <span><span class="op">)</span></span></code></pre></div><p></p></div> </div> +<div class="section"> +<h4 id="arguments-12">Arguments<a class="anchor" aria-label="anchor" href="#arguments-12"></a></h4> +<p></p><div class="arguments"><dl><dt><code>Kf</code></dt> +<dd><p>The sorption constant in L/kg, either linear (then <code>N</code> is 1) +or according to Freundlich</p></dd> + + +<dt><code>Kfoc</code></dt> +<dd><p>The constant from above, normalised to soil organic carbon</p></dd> + + +<dt><code>N</code></dt> +<dd><p>The Freundlich exponent</p></dd> + + +<dt><code>perc_clay</code></dt> +<dd><p>The percentage of clay in the soil</p></dd> + + +<dt><code>CEC</code></dt> +<dd><p>The cation exchange capacity +Write a PDF image of the structure</p></dd> + + +</dl><p></p></div> +</div> </div><p></p><hr><a id="method-chent-pdf"></a><div class="section"> <h3 id="method-pdf-">Method <code><a href="https://rdrr.io/r/grDevices/pdf.html" class="external-link">pdf()</a></code><a class="anchor" aria-label="anchor" href="#method-pdf-"></a></h3> @@ -419,6 +690,23 @@ Get chemical information from PubChem for a known PubChem CID</p></dd> <span><span class="op">)</span></span></code></pre></div><p></p></div> </div> +<div class="section"> +<h4 id="arguments-13">Arguments<a class="anchor" aria-label="anchor" href="#arguments-13"></a></h4> +<p></p><div class="arguments"><dl><dt><code>file</code></dt> +<dd><p>The file to write to</p></dd> + + +<dt><code>dir</code></dt> +<dd><p>The directory to write the file to</p></dd> + + +<dt><code>template</code></dt> +<dd><p>A template expressed as SMILES to use in RDKit +Write a PNG image of the structure</p></dd> + + +</dl><p></p></div> +</div> </div><p></p><hr><a id="method-chent-png"></a><div class="section"> <h3 id="method-png-">Method <code><a href="https://rdrr.io/r/grDevices/png.html" class="external-link">png()</a></code><a class="anchor" aria-label="anchor" href="#method-png-"></a></h3> @@ -432,6 +720,15 @@ Get chemical information from PubChem for a known PubChem CID</p></dd> <span><span class="op">)</span></span></code></pre></div><p></p></div> </div> +<div class="section"> +<h4 id="arguments-14">Arguments<a class="anchor" aria-label="anchor" href="#arguments-14"></a></h4> +<p></p><div class="arguments"><dl><dt><code>antialias</code></dt> +<dd><p>Passed to <a href="https://rdrr.io/r/grDevices/png.html" class="external-link">png</a> +Write an EMF image of the structure using <a href="https://rdrr.io/pkg/devEMF/man/emf.html" class="external-link">emf</a></p></dd> + + +</dl><p></p></div> +</div> </div><p></p><hr><a id="method-chent-emf"></a><div class="section"> <h3 id="method-emf-">Method <code>emf()</code><a class="anchor" aria-label="anchor" href="#method-emf-"></a></h3> @@ -441,6 +738,14 @@ Get chemical information from PubChem for a known PubChem CID</p></dd> <p></p><div class="r"><div class="sourceCode"><pre><code><span><span class="va">chent</span><span class="op">$</span><span class="fu">emf</span><span class="op">(</span>file <span class="op">=</span> <span class="fu"><a href="https://rdrr.io/r/base/paste.html" class="external-link">paste0</a></span><span class="op">(</span><span class="va">self</span><span class="op">$</span><span class="va">identifier</span>, <span class="st">".emf"</span><span class="op">)</span>, dir <span class="op">=</span> <span class="st">"structures/emf"</span><span class="op">)</span></span></code></pre></div><p></p></div> </div> +<div class="section"> +<h4 id="arguments-15">Arguments<a class="anchor" aria-label="anchor" href="#arguments-15"></a></h4> +<p></p><div class="arguments"><dl><dt><code>file</code></dt> +<dd><p>The file to write to</p></dd> + + +</dl><p></p></div> +</div> </div><p></p><hr><a id="method-chent-clone"></a><div class="section"> <h3 id="method-clone-">Method <code>clone()</code><a class="anchor" aria-label="anchor" href="#method-clone-"></a></h3> @@ -450,7 +755,7 @@ Get chemical information from PubChem for a known PubChem CID</p></dd> </div> <div class="section"> -<h4 id="arguments-3">Arguments<a class="anchor" aria-label="anchor" href="#arguments-3"></a></h4> +<h4 id="arguments-16">Arguments<a class="anchor" aria-label="anchor" href="#arguments-16"></a></h4> <p></p><div class="arguments"><dl><dt><code>deep</code></dt> <dd><p>Whether to make a deep clone.</p></dd> diff --git a/docs/reference/draw_svg.chent.html b/docs/reference/draw_svg.chent.html index cae8c0b..a95748e 100644 --- a/docs/reference/draw_svg.chent.html +++ b/docs/reference/draw_svg.chent.html @@ -17,7 +17,7 @@ </button> <span class="navbar-brand"> <a class="navbar-link" href="../index.html">chents</a> - <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="">0.3.1</span> + <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="">0.3.2</span> </span> </div> diff --git a/docs/reference/index.html b/docs/reference/index.html index d9eb797..6bc6df8 100644 --- a/docs/reference/index.html +++ b/docs/reference/index.html @@ -17,7 +17,7 @@ </button> <span class="navbar-brand"> <a class="navbar-link" href="../index.html">chents</a> - <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="">0.3.1</span> + <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="">0.3.2</span> </span> </div> @@ -72,9 +72,9 @@ </td> <td><p>Printing method for pai objects (pesticidal active ingredients)</p></td> </tr><tr><td> - <p><code><a href="pp.html">pp</a></code> </p> + <p><code><a href="ppp.html">ppp</a></code> </p> </td> - <td><p>R6 class for holding a product with at least one active ingredient</p></td> + <td><p>R6 class for a plant protection product with at least one active ingredient</p></td> </tr></tbody></table></div> <div class="col-md-3 hidden-xs hidden-sm" id="pkgdown-sidebar"> diff --git a/docs/reference/pai.html b/docs/reference/pai.html index 636007f..d8811d0 100644 --- a/docs/reference/pai.html +++ b/docs/reference/pai.html @@ -1,6 +1,6 @@ <!DOCTYPE html> -<!-- Generated by pkgdown: do not edit by hand --><html lang="en"><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><meta charset="utf-8"><meta http-equiv="X-UA-Compatible" content="IE=edge"><meta name="viewport" content="width=device-width, initial-scale=1.0"><title>An R6 class for pesticidal active ingredients and associated data — pai • chents</title><!-- jquery --><script src="https://cdnjs.cloudflare.com/ajax/libs/jquery/3.4.1/jquery.min.js" integrity="sha256-CSXorXvZcTkaix6Yvo6HppcZGetbYMGWSFlBw8HfCJo=" crossorigin="anonymous"></script><!-- Bootstrap --><link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/twitter-bootstrap/3.4.1/css/bootstrap.min.css" integrity="sha256-bZLfwXAP04zRMK2BjiO8iu9pf4FbLqX6zitd+tIvLhE=" crossorigin="anonymous"><script src="https://cdnjs.cloudflare.com/ajax/libs/twitter-bootstrap/3.4.1/js/bootstrap.min.js" integrity="sha256-nuL8/2cJ5NDSSwnKD8VqreErSWHtnEP9E7AySL+1ev4=" crossorigin="anonymous"></script><!-- bootstrap-toc --><link rel="stylesheet" href="../bootstrap-toc.css"><script src="../bootstrap-toc.js"></script><!-- Font Awesome icons --><link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/font-awesome/5.12.1/css/all.min.css" integrity="sha256-mmgLkCYLUQbXn0B1SRqzHar6dCnv9oZFPEC1g1cwlkk=" crossorigin="anonymous"><link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/font-awesome/5.12.1/css/v4-shims.min.css" integrity="sha256-wZjR52fzng1pJHwx4aV2AO3yyTOXrcDW7jBpJtTwVxw=" crossorigin="anonymous"><!-- clipboard.js --><script src="https://cdnjs.cloudflare.com/ajax/libs/clipboard.js/2.0.6/clipboard.min.js" integrity="sha256-inc5kl9MA1hkeYUt+EC3BhlIgyp/2jDIyBLS6k3UxPI=" crossorigin="anonymous"></script><!-- headroom.js --><script src="https://cdnjs.cloudflare.com/ajax/libs/headroom/0.11.0/headroom.min.js" integrity="sha256-AsUX4SJE1+yuDu5+mAVzJbuYNPHj/WroHuZ8Ir/CkE0=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/headroom/0.11.0/jQuery.headroom.min.js" integrity="sha256-ZX/yNShbjqsohH1k95liqY9Gd8uOiE1S4vZc+9KQ1K4=" crossorigin="anonymous"></script><!-- pkgdown --><link href="../pkgdown.css" rel="stylesheet"><script src="../pkgdown.js"></script><meta property="og:title" content="An R6 class for pesticidal active ingredients and associated data — pai"><meta property="og:description" content="The class is initialised with an identifier which is generally an ISO common name. -Additional chemical information is retrieved from the internet if available."><!-- mathjax --><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script><!--[if lt IE 9]> +<!-- Generated by pkgdown: do not edit by hand --><html lang="en"><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><meta charset="utf-8"><meta http-equiv="X-UA-Compatible" content="IE=edge"><meta name="viewport" content="width=device-width, initial-scale=1.0"><title>An R6 class for pesticidal active ingredients and associated data — pai • chents</title><!-- jquery --><script src="https://cdnjs.cloudflare.com/ajax/libs/jquery/3.4.1/jquery.min.js" integrity="sha256-CSXorXvZcTkaix6Yvo6HppcZGetbYMGWSFlBw8HfCJo=" crossorigin="anonymous"></script><!-- Bootstrap --><link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/twitter-bootstrap/3.4.1/css/bootstrap.min.css" integrity="sha256-bZLfwXAP04zRMK2BjiO8iu9pf4FbLqX6zitd+tIvLhE=" crossorigin="anonymous"><script src="https://cdnjs.cloudflare.com/ajax/libs/twitter-bootstrap/3.4.1/js/bootstrap.min.js" integrity="sha256-nuL8/2cJ5NDSSwnKD8VqreErSWHtnEP9E7AySL+1ev4=" crossorigin="anonymous"></script><!-- bootstrap-toc --><link rel="stylesheet" href="../bootstrap-toc.css"><script src="../bootstrap-toc.js"></script><!-- Font Awesome icons --><link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/font-awesome/5.12.1/css/all.min.css" integrity="sha256-mmgLkCYLUQbXn0B1SRqzHar6dCnv9oZFPEC1g1cwlkk=" crossorigin="anonymous"><link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/font-awesome/5.12.1/css/v4-shims.min.css" integrity="sha256-wZjR52fzng1pJHwx4aV2AO3yyTOXrcDW7jBpJtTwVxw=" crossorigin="anonymous"><!-- clipboard.js --><script src="https://cdnjs.cloudflare.com/ajax/libs/clipboard.js/2.0.6/clipboard.min.js" integrity="sha256-inc5kl9MA1hkeYUt+EC3BhlIgyp/2jDIyBLS6k3UxPI=" crossorigin="anonymous"></script><!-- headroom.js --><script src="https://cdnjs.cloudflare.com/ajax/libs/headroom/0.11.0/headroom.min.js" integrity="sha256-AsUX4SJE1+yuDu5+mAVzJbuYNPHj/WroHuZ8Ir/CkE0=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/headroom/0.11.0/jQuery.headroom.min.js" integrity="sha256-ZX/yNShbjqsohH1k95liqY9Gd8uOiE1S4vZc+9KQ1K4=" crossorigin="anonymous"></script><!-- pkgdown --><link href="../pkgdown.css" rel="stylesheet"><script src="../pkgdown.js"></script><meta property="og:title" content="An R6 class for pesticidal active ingredients and associated data — pai"><meta property="og:description" content="An R6 class for pesticidal active ingredients and associated data +An R6 class for pesticidal active ingredients and associated data"><!-- mathjax --><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script><!--[if lt IE 9]> <script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script> <script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script> <![endif]--></head><body data-spy="scroll" data-target="#toc"> @@ -18,7 +18,7 @@ Additional chemical information is retrieved from the internet if available."><! </button> <span class="navbar-brand"> <a class="navbar-link" href="../index.html">chents</a> - <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="">0.3.1</span> + <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="">0.3.2</span> </span> </div> @@ -47,8 +47,8 @@ Additional chemical information is retrieved from the internet if available."><! </div> <div class="ref-description"> - <p>The class is initialised with an identifier which is generally an ISO common name. -Additional chemical information is retrieved from the internet if available.</p> + <p>An R6 class for pesticidal active ingredients and associated data</p> +<p>An R6 class for pesticidal active ingredients and associated data</p> </div> @@ -56,6 +56,11 @@ Additional chemical information is retrieved from the internet if available.</p> <h2>Format</h2> <p>An <code>R6Class</code> generator object</p> </div> + <div id="details"> + <h2>Details</h2> + <p>The class is initialised with an identifier which is generally an ISO common name. +Additional chemical information is retrieved from the internet if available.</p> + </div> <div id="super-class"> <h2>Super class</h2> <p><code><a href="chent.html">chents::chent</a></code> -> <code>pai</code></p> @@ -63,11 +68,13 @@ Additional chemical information is retrieved from the internet if available.</p> <div id="public-fields"> <h2>Public fields</h2> <p></p><div class="r6-fields"><dl><dt><code>iso</code></dt> -<dd><p>ISO common name according to ISO 1750 as retreived from pesticidecompendium.bcpc.org</p></dd> +<dd><p>ISO common name of the active ingredient according to ISO 1750</p></dd> <dt><code>bcpc</code></dt> -<dd><p>List of information retrieved from pesticidecompendium.bcpc.org</p></dd> +<dd><p>Information retrieved from the BCPC compendium available online +at <pesticidecompendium.bcpc.org> +Creates a new instance of this <a href="https://r6.r-lib.org/reference/R6Class.html" class="external-link">R6</a> class.</p></dd> </dl><p></p></div> @@ -97,8 +104,11 @@ Additional chemical information is retrieved from the internet if available.</p> <li><span class="pkg-link" data-pkg="chents" data-topic="chent" data-id="try_pubchem"><a href="chent.html#method-try_pubchem"><code>chents::chent$try_pubchem()</code></a></span></li> </ul></details></p><hr><a id="method-pai-new"></a><div class="section"> <h3 id="method-new-">Method <code>new()</code><a class="anchor" aria-label="anchor" href="#method-new-"></a></h3> - -<div class="section"> +<p>This class is derived from <a href="chent.html">chent</a>. It makes it easy +to create a <a href="chent.html">chent</a> from the ISO common name of a pesticide active +ingredient, and additionally stores the ISO name as well as +the complete result of querying the BCPC compendium using +<a href="https://docs.ropensci.org/webchem/reference/bcpc_query.html" class="external-link">bcpc_query</a>.</p><div class="section"> <h4 id="usage">Usage<a class="anchor" aria-label="anchor" href="#usage"></a></h4> <p></p><div class="r"><div class="sourceCode"><pre><code><span><span class="va"><a href="../reference/pai.html">pai</a></span><span class="op">$</span><span class="fu">new</span><span class="op">(</span></span> <span> <span class="va">iso</span>,</span> @@ -114,6 +124,19 @@ Additional chemical information is retrieved from the internet if available.</p> <span><span class="op">)</span></span></code></pre></div><p></p></div> </div> +<div class="section"> +<h4 id="arguments">Arguments<a class="anchor" aria-label="anchor" href="#arguments"></a></h4> +<p></p><div class="arguments"><dl><dt><code>iso</code></dt> +<dd><p>The ISO common name to be used in the query of the +BCPC compendium</p></dd> + + +<dt><code>identifier</code></dt> +<dd><p>Alternative identifier used for querying pubchem</p></dd> + + +</dl><p></p></div> +</div> </div><p></p><hr><a id="method-pai-clone"></a><div class="section"> <h3 id="method-clone-">Method <code>clone()</code><a class="anchor" aria-label="anchor" href="#method-clone-"></a></h3> @@ -123,7 +146,7 @@ Additional chemical information is retrieved from the internet if available.</p> </div> <div class="section"> -<h4 id="arguments">Arguments<a class="anchor" aria-label="anchor" href="#arguments"></a></h4> +<h4 id="arguments-1">Arguments<a class="anchor" aria-label="anchor" href="#arguments-1"></a></h4> <p></p><div class="arguments"><dl><dt><code>deep</code></dt> <dd><p>Whether to make a deep clone.</p></dd> diff --git a/docs/reference/plot.chent.html b/docs/reference/plot.chent.html index 470ce79..26d8445 100644 --- a/docs/reference/plot.chent.html +++ b/docs/reference/plot.chent.html @@ -17,7 +17,7 @@ </button> <span class="navbar-brand"> <a class="navbar-link" href="../index.html">chents</a> - <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="">0.3.1</span> + <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="">0.3.2</span> </span> </div> diff --git a/docs/reference/ppp.html b/docs/reference/ppp.html new file mode 100644 index 0000000..7a9b861 --- /dev/null +++ b/docs/reference/ppp.html @@ -0,0 +1,194 @@ +<!DOCTYPE html> +<!-- Generated by pkgdown: do not edit by hand --><html lang="en"><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><meta charset="utf-8"><meta http-equiv="X-UA-Compatible" content="IE=edge"><meta name="viewport" content="width=device-width, initial-scale=1.0"><title>R6 class for a plant protection product with at least one active ingredient — ppp • chents</title><!-- jquery --><script src="https://cdnjs.cloudflare.com/ajax/libs/jquery/3.4.1/jquery.min.js" integrity="sha256-CSXorXvZcTkaix6Yvo6HppcZGetbYMGWSFlBw8HfCJo=" crossorigin="anonymous"></script><!-- Bootstrap --><link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/twitter-bootstrap/3.4.1/css/bootstrap.min.css" integrity="sha256-bZLfwXAP04zRMK2BjiO8iu9pf4FbLqX6zitd+tIvLhE=" crossorigin="anonymous"><script src="https://cdnjs.cloudflare.com/ajax/libs/twitter-bootstrap/3.4.1/js/bootstrap.min.js" integrity="sha256-nuL8/2cJ5NDSSwnKD8VqreErSWHtnEP9E7AySL+1ev4=" crossorigin="anonymous"></script><!-- bootstrap-toc --><link rel="stylesheet" href="../bootstrap-toc.css"><script src="../bootstrap-toc.js"></script><!-- Font Awesome icons --><link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/font-awesome/5.12.1/css/all.min.css" integrity="sha256-mmgLkCYLUQbXn0B1SRqzHar6dCnv9oZFPEC1g1cwlkk=" crossorigin="anonymous"><link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/font-awesome/5.12.1/css/v4-shims.min.css" integrity="sha256-wZjR52fzng1pJHwx4aV2AO3yyTOXrcDW7jBpJtTwVxw=" crossorigin="anonymous"><!-- clipboard.js --><script src="https://cdnjs.cloudflare.com/ajax/libs/clipboard.js/2.0.6/clipboard.min.js" integrity="sha256-inc5kl9MA1hkeYUt+EC3BhlIgyp/2jDIyBLS6k3UxPI=" crossorigin="anonymous"></script><!-- headroom.js --><script src="https://cdnjs.cloudflare.com/ajax/libs/headroom/0.11.0/headroom.min.js" integrity="sha256-AsUX4SJE1+yuDu5+mAVzJbuYNPHj/WroHuZ8Ir/CkE0=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/headroom/0.11.0/jQuery.headroom.min.js" integrity="sha256-ZX/yNShbjqsohH1k95liqY9Gd8uOiE1S4vZc+9KQ1K4=" crossorigin="anonymous"></script><!-- pkgdown --><link href="../pkgdown.css" rel="stylesheet"><script src="../pkgdown.js"></script><meta property="og:title" content="R6 class for a plant protection product with at least one active ingredient — ppp"><meta property="og:description" content="Contains basic information about the active ingredients in the +product"><!-- mathjax --><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js" integrity="sha256-nvJJv9wWKEm88qvoQl9ekL2J+k/RWIsaSScxxlsrv8k=" crossorigin="anonymous"></script><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/config/TeX-AMS-MML_HTMLorMML.js" integrity="sha256-84DKXVJXs0/F8OTMzX4UR909+jtl4G7SPypPavF+GfA=" crossorigin="anonymous"></script><!--[if lt IE 9]> +<script src="https://oss.maxcdn.com/html5shiv/3.7.3/html5shiv.min.js"></script> +<script src="https://oss.maxcdn.com/respond/1.4.2/respond.min.js"></script> +<![endif]--></head><body data-spy="scroll" data-target="#toc"> + + + <div class="container template-reference-topic"> + <header><div class="navbar navbar-default navbar-fixed-top" role="navigation"> + <div class="container"> + <div class="navbar-header"> + <button type="button" class="navbar-toggle collapsed" data-toggle="collapse" data-target="#navbar" aria-expanded="false"> + <span class="sr-only">Toggle navigation</span> + <span class="icon-bar"></span> + <span class="icon-bar"></span> + <span class="icon-bar"></span> + </button> + <span class="navbar-brand"> + <a class="navbar-link" href="../index.html">chents</a> + <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="">0.3.2</span> + </span> + </div> + + <div id="navbar" class="navbar-collapse collapse"> + <ul class="nav navbar-nav"><li> + <a href="../reference/index.html">Reference</a> +</li> + </ul><ul class="nav navbar-nav navbar-right"><li> + <a href="https://github.com/jranke/chents/" class="external-link"> + <span class="fab fa-github fa-lg"></span> + + </a> +</li> + </ul></div><!--/.nav-collapse --> + </div><!--/.container --> +</div><!--/.navbar --> + + + + </header><div class="row"> + <div class="col-md-9 contents"> + <div class="page-header"> + <h1>R6 class for a plant protection product with at least one active ingredient</h1> + <small class="dont-index">Source: <a href="https://github.com/jranke/chents/blob/HEAD/R/chent.R" class="external-link"><code>R/chent.R</code></a></small> + <div class="hidden name"><code>ppp.Rd</code></div> + </div> + + <div class="ref-description"> + <p>Contains basic information about the active ingredients in the +product</p> + </div> + + + <div id="format"> + <h2>Format</h2> + <p>An <code>R6Class</code> generator object.</p> + </div> + <div id="public-fields"> + <h2>Public fields</h2> + <p></p><div class="r6-fields"><dl><dt><code>name</code></dt> +<dd><p>The name of the product</p></dd> + + +<dt><code>ais</code></dt> +<dd><p>A list of active ingredients</p></dd> + + +<dt><code>concentrations</code></dt> +<dd><p>The concentration of the ais</p></dd> + + +<dt><code>concentration_units</code></dt> +<dd><p>Defaults to g/L</p></dd> + + +<dt><code>density</code></dt> +<dd><p>The density of the product</p></dd> + + +<dt><code>density_units</code></dt> +<dd><p>Defaults to g/L +Creates a new instance of this <a href="https://r6.r-lib.org/reference/R6Class.html" class="external-link">R6</a> class.</p></dd> + + +<dt><code>...</code></dt> +<dd><p>Identifiers of the active ingredients</p></dd> + + +<dt><code>concentrations</code></dt> +<dd><p>Concentrations of the active ingredients</p></dd> + + +<dt><code>concentration_units</code></dt> +<dd><p>Defaults to g/L</p></dd> + + +<dt><code>density</code></dt> +<dd><p>The density</p></dd> + + +<dt><code>density_units</code></dt> +<dd><p>Defaults to g/L +Printing method</p></dd> + + +</dl><p></p></div> + </div> + <div id="active-bindings"> + <h2>Active bindings</h2> + <p></p><div class="r6-active-bindings"><dl><dt><code>...</code></dt> +<dd><p>Identifiers of the active ingredients</p></dd> + + +</dl><p></p></div> + </div> + <div id="methods"> + <h2>Methods</h2> + +<div class="section"> +<h3 id="public-methods">Public methods<a class="anchor" aria-label="anchor" href="#public-methods"></a></h3> + +<ul><li><p><a href="#method-ppp-new"><code>ppp$new()</code></a></p></li> +<li><p><a href="#method-ppp-print"><code>ppp$print()</code></a></p></li> +<li><p><a href="#method-ppp-clone"><code>ppp$clone()</code></a></p></li> +</ul></div><p></p><hr><a id="method-ppp-new"></a><div class="section"> +<h3 id="method-new-">Method <code>new()</code><a class="anchor" aria-label="anchor" href="#method-new-"></a></h3> + +<div class="section"> +<h4 id="usage">Usage<a class="anchor" aria-label="anchor" href="#usage"></a></h4> +<p></p><div class="r"><div class="sourceCode"><pre><code><span><span class="va"><a href="../reference/ppp.html">ppp</a></span><span class="op">$</span><span class="fu">new</span><span class="op">(</span></span> +<span> <span class="va">name</span>,</span> +<span> <span class="va">...</span>,</span> +<span> <span class="va">concentrations</span>,</span> +<span> concentration_units <span class="op">=</span> <span class="st">"g/L"</span>,</span> +<span> density <span class="op">=</span> <span class="fl">1000</span>,</span> +<span> density_units <span class="op">=</span> <span class="st">"g/L"</span></span> +<span><span class="op">)</span></span></code></pre></div><p></p></div> +</div> + + +</div><p></p><hr><a id="method-ppp-print"></a><div class="section"> +<h3 id="method-print-">Method <code><a href="https://rdrr.io/r/base/print.html" class="external-link">print()</a></code><a class="anchor" aria-label="anchor" href="#method-print-"></a></h3> + +<div class="section"> +<h4 id="usage-1">Usage<a class="anchor" aria-label="anchor" href="#usage-1"></a></h4> +<p></p><div class="r"><div class="sourceCode"><pre><code><span><span class="va">ppp</span><span class="op">$</span><span class="fu">print</span><span class="op">(</span><span class="op">)</span></span></code></pre></div><p></p></div> +</div> + + +</div><p></p><hr><a id="method-ppp-clone"></a><div class="section"> +<h3 id="method-clone-">Method <code>clone()</code><a class="anchor" aria-label="anchor" href="#method-clone-"></a></h3> +<p>The objects of this class are cloneable with this method.</p><div class="section"> +<h4 id="usage-2">Usage<a class="anchor" aria-label="anchor" href="#usage-2"></a></h4> +<p></p><div class="r"><div class="sourceCode"><pre><code><span><span class="va">ppp</span><span class="op">$</span><span class="fu">clone</span><span class="op">(</span>deep <span class="op">=</span> <span class="cn">FALSE</span><span class="op">)</span></span></code></pre></div><p></p></div> +</div> + +<div class="section"> +<h4 id="arguments">Arguments<a class="anchor" aria-label="anchor" href="#arguments"></a></h4> +<p></p><div class="arguments"><dl><dt><code>deep</code></dt> +<dd><p>Whether to make a deep clone.</p></dd> + + +</dl><p></p></div> +</div> + +</div> + + </div> + + </div> + <div class="col-md-3 hidden-xs hidden-sm" id="pkgdown-sidebar"> + <nav id="toc" data-toggle="toc" class="sticky-top"><h2 data-toc-skip>Contents</h2> + </nav></div> +</div> + + + <footer><div class="copyright"> + <p></p><p>Developed by Johannes Ranke.</p> +</div> + +<div class="pkgdown"> + <p></p><p>Site built with <a href="https://pkgdown.r-lib.org/" class="external-link">pkgdown</a> 2.0.7.</p> +</div> + + </footer></div> + + + + + + + </body></html> + diff --git a/docs/reference/print.chent.html b/docs/reference/print.chent.html index 08497dd..da3ba4f 100644 --- a/docs/reference/print.chent.html +++ b/docs/reference/print.chent.html @@ -17,7 +17,7 @@ </button> <span class="navbar-brand"> <a class="navbar-link" href="../index.html">chents</a> - <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="">0.3.1</span> + <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="">0.3.2</span> </span> </div> diff --git a/docs/reference/print.pai.html b/docs/reference/print.pai.html index 3faa5f7..5a08066 100644 --- a/docs/reference/print.pai.html +++ b/docs/reference/print.pai.html @@ -17,7 +17,7 @@ </button> <span class="navbar-brand"> <a class="navbar-link" href="../index.html">chents</a> - <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="">0.3.1</span> + <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="">0.3.2</span> </span> </div> diff --git a/docs/sitemap.xml b/docs/sitemap.xml index 986ccf3..63ab18d 100644 --- a/docs/sitemap.xml +++ b/docs/sitemap.xml @@ -28,6 +28,9 @@ <loc>/reference/pp.html</loc> </url> <url> + <loc>/reference/ppp.html</loc> + </url> + <url> <loc>/reference/print.chent.html</loc> </url> <url> diff --git a/man/chent.Rd b/man/chent.Rd index e069938..686d6c7 100644 --- a/man/chent.Rd +++ b/man/chent.Rd @@ -73,7 +73,8 @@ Add a line in the internal dataframe holding modelling DT50 values} \item{\code{soil_ff}}{Dataframe of formation fractions} -\item{\code{soil_sorption}}{Dataframe of soil sorption data} +\item{\code{soil_sorption}}{Dataframe of soil sorption data +Add soil sorption data} } \if{html}{\out{</div>}} } @@ -214,7 +215,9 @@ Obtain information from a YAML file} \describe{ \item{\code{repo}}{Should the file be looked for in the current working directory, a local git repository under \verb{~/git/chyaml}, or from -the web (not implemented). +the web (not implemented).} + +\item{\code{chyaml}}{The filename to be looked for Add a vapour pressure} } \if{html}{\out{</div>}} @@ -256,7 +259,17 @@ Add a water solubility} \subsection{Arguments}{ \if{html}{\out{<div class="arguments">}} \describe{ -\item{\code{p0}}{The water solubility in mg/L +\item{\code{cwsat}}{The water solubility in mg/L} + +\item{\code{T}}{Temperature} + +\item{\code{pH}}{The pH value} + +\item{\code{source}}{An acronym specifying the source of the information} + +\item{\code{page}}{The page from which the information was taken} + +\item{\code{remark}}{A remark Add a plant uptake factor} } \if{html}{\out{</div>}} @@ -279,6 +292,12 @@ Add a plant uptake factor} \if{html}{\out{<div class="arguments">}} \describe{ \item{\code{PUF}}{The plant uptake factor, a number between 0 and 1} + +\item{\code{source}}{An acronym specifying the source of the information} + +\item{\code{page}}{The page from which the information was taken} + +\item{\code{remark}}{A remark} } \if{html}{\out{</div>}} } @@ -318,6 +337,26 @@ Add a plant uptake factor} )}\if{html}{\out{</div>}} } +\subsection{Arguments}{ +\if{html}{\out{<div class="arguments">}} +\describe{ +\item{\code{study_type}}{A characterisation of the study type} + +\item{\code{TP_identifier}}{An identifier of one of the transformation products +in \code{self$TPs}} + +\item{\code{max_occurrence}}{The maximum observed occurrence of the +transformation product, expressed as a fraction of the amount that would +result from stochiometric transformation} + +\item{\code{remark}}{A remark} + +\item{\code{source}}{An acronym specifying the source of the information} + +\item{\code{pages}}{The page from which the information was taken} +} +\if{html}{\out{</div>}} +} } \if{html}{\out{<hr>}} \if{html}{\out{<a id="method-chent-add_soil_degradation"></a>}} @@ -346,6 +385,50 @@ Add a plant uptake factor} )}\if{html}{\out{</div>}} } +\subsection{Arguments}{ +\if{html}{\out{<div class="arguments">}} +\describe{ +\item{\code{soils}}{Names of the soils} + +\item{\code{DT50_mod}}{The modelling DT50 in the sense of regulatory pesticide +fate modelling} + +\item{\code{DT50_mod_ref}}{The normalised modelling DT50 in the sense of +regulatory pesticide fate modelling} + +\item{\code{type}}{The soil type} + +\item{\code{country}}{The country (mainly for field studies)} + +\item{\code{pH_orig}}{The pH stated in the study} + +\item{\code{pH_medium}}{The medium in which this pH was measured} + +\item{\code{pH_H2O}}{The pH extrapolated to pure water} + +\item{\code{perc_OC}}{The percentage of organic carbon in the soil} + +\item{\code{temperature}}{The temperature during the study in degrees Celsius} + +\item{\code{moisture}}{The moisture during the study} + +\item{\code{category}}{Is it a laboratory ('lab') or field study ('field')} + +\item{\code{formulation}}{Name of the formulation applied, if it was not +the technical active ingredient} + +\item{\code{model}}{The degradation model used for deriving \code{DT50_mod}} + +\item{\code{chi2}}{The relative error as defined in FOCUS kinetics} + +\item{\code{remark}}{A remark} + +\item{\code{source}}{An acronym specifying the source of the information} + +\item{\code{page}}{The page from which the information was taken} +} +\if{html}{\out{</div>}} +} } \if{html}{\out{<hr>}} \if{html}{\out{<a id="method-chent-add_soil_ff"></a>}} @@ -355,6 +438,17 @@ Add a plant uptake factor} \if{html}{\out{<div class="r">}}\preformatted{chent$add_soil_ff(target, soils, ff = 1, remark = "", source, page = NA)}\if{html}{\out{</div>}} } +\subsection{Arguments}{ +\if{html}{\out{<div class="arguments">}} +\describe{ +\item{\code{target}}{The identifier(s) of the transformation product} + +\item{\code{soils}}{The soil name(s) in which the transformation was observed} + +\item{\code{ff}}{The formation fraction(s)} +} +\if{html}{\out{</div>}} +} } \if{html}{\out{<hr>}} \if{html}{\out{<a id="method-chent-add_soil_sorption"></a>}} @@ -379,6 +473,23 @@ Add a plant uptake factor} )}\if{html}{\out{</div>}} } +\subsection{Arguments}{ +\if{html}{\out{<div class="arguments">}} +\describe{ +\item{\code{Kf}}{The sorption constant in L/kg, either linear (then \code{N} is 1) +or according to Freundlich} + +\item{\code{Kfoc}}{The constant from above, normalised to soil organic carbon} + +\item{\code{N}}{The Freundlich exponent} + +\item{\code{perc_clay}}{The percentage of clay in the soil} + +\item{\code{CEC}}{The cation exchange capacity +Write a PDF image of the structure} +} +\if{html}{\out{</div>}} +} } \if{html}{\out{<hr>}} \if{html}{\out{<a id="method-chent-pdf"></a>}} @@ -392,6 +503,18 @@ Add a plant uptake factor} )}\if{html}{\out{</div>}} } +\subsection{Arguments}{ +\if{html}{\out{<div class="arguments">}} +\describe{ +\item{\code{file}}{The file to write to} + +\item{\code{dir}}{The directory to write the file to} + +\item{\code{template}}{A template expressed as SMILES to use in RDKit +Write a PNG image of the structure} +} +\if{html}{\out{</div>}} +} } \if{html}{\out{<hr>}} \if{html}{\out{<a id="method-chent-png"></a>}} @@ -405,6 +528,14 @@ Add a plant uptake factor} )}\if{html}{\out{</div>}} } +\subsection{Arguments}{ +\if{html}{\out{<div class="arguments">}} +\describe{ +\item{\code{antialias}}{Passed to \link[grDevices:png]{png} +Write an EMF image of the structure using \link[devEMF:emf]{emf}} +} +\if{html}{\out{</div>}} +} } \if{html}{\out{<hr>}} \if{html}{\out{<a id="method-chent-emf"></a>}} @@ -414,6 +545,13 @@ Add a plant uptake factor} \if{html}{\out{<div class="r">}}\preformatted{chent$emf(file = paste0(self$identifier, ".emf"), dir = "structures/emf")}\if{html}{\out{</div>}} } +\subsection{Arguments}{ +\if{html}{\out{<div class="arguments">}} +\describe{ +\item{\code{file}}{The file to write to} +} +\if{html}{\out{</div>}} +} } \if{html}{\out{<hr>}} \if{html}{\out{<a id="method-chent-clone"></a>}} @@ -8,6 +8,11 @@ An \code{\link{R6Class}} generator object } \description{ +An R6 class for pesticidal active ingredients and associated data + +An R6 class for pesticidal active ingredients and associated data +} +\details{ The class is initialised with an identifier which is generally an ISO common name. Additional chemical information is retrieved from the internet if available. } @@ -31,9 +36,11 @@ if (!is.null(atr$Picture)) { \section{Public fields}{ \if{html}{\out{<div class="r6-fields">}} \describe{ -\item{\code{iso}}{ISO common name according to ISO 1750 as retreived from pesticidecompendium.bcpc.org} +\item{\code{iso}}{ISO common name of the active ingredient according to ISO 1750} -\item{\code{bcpc}}{List of information retrieved from pesticidecompendium.bcpc.org} +\item{\code{bcpc}}{Information retrieved from the BCPC compendium available online +at <pesticidecompendium.bcpc.org> +Creates a new instance of this \link[R6:R6Class]{R6} class.} } \if{html}{\out{</div>}} } @@ -69,6 +76,11 @@ if (!is.null(atr$Picture)) { \if{html}{\out{<a id="method-pai-new"></a>}} \if{latex}{\out{\hypertarget{method-pai-new}{}}} \subsection{Method \code{new()}}{ +This class is derived from \link{chent}. It makes it easy +to create a \link{chent} from the ISO common name of a pesticide active +ingredient, and additionally stores the ISO name as well as +the complete result of querying the BCPC compendium using +\link[webchem:bcpc_query]{bcpc_query}. \subsection{Usage}{ \if{html}{\out{<div class="r">}}\preformatted{pai$new( iso, @@ -84,6 +96,16 @@ if (!is.null(atr$Picture)) { )}\if{html}{\out{</div>}} } +\subsection{Arguments}{ +\if{html}{\out{<div class="arguments">}} +\describe{ +\item{\code{iso}}{The ISO common name to be used in the query of the +BCPC compendium} + +\item{\code{identifier}}{Alternative identifier used for querying pubchem} +} +\if{html}{\out{</div>}} +} } \if{html}{\out{<hr>}} \if{html}{\out{<a id="method-pai-clone"></a>}} diff --git a/man/pp.Rd b/man/pp.Rd deleted file mode 100644 index 363f9ba..0000000 --- a/man/pp.Rd +++ /dev/null @@ -1,77 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/chent.R -\docType{class} -\name{pp} -\alias{pp} -\title{R6 class for holding a product with at least one active ingredient} -\format{ -An \code{\link{R6Class}} generator object. -} -\description{ -An R6 class for holding information about a product with at least one active ingredient -} -\keyword{data} -\section{Public fields}{ -\if{html}{\out{<div class="r6-fields">}} -\describe{ -\item{\code{name}}{The name of the product} - -\item{\code{ais}}{A list of active ingredients} - -\item{\code{concentrations}}{The concentration of the ais} - -\item{\code{concentration_units}}{Defaults to g/L} -} -\if{html}{\out{</div>}} -} -\section{Methods}{ -\subsection{Public methods}{ -\itemize{ -\item \href{#method-pp-new}{\code{pp$new()}} -\item \href{#method-pp-print}{\code{pp$print()}} -\item \href{#method-pp-clone}{\code{pp$clone()}} -} -} -\if{html}{\out{<hr>}} -\if{html}{\out{<a id="method-pp-new"></a>}} -\if{latex}{\out{\hypertarget{method-pp-new}{}}} -\subsection{Method \code{new()}}{ -\subsection{Usage}{ -\if{html}{\out{<div class="r">}}\preformatted{pp$new( - name, - ..., - concentrations, - concentration_units = "g/L", - density = 1000, - density_units = "g/L" -)}\if{html}{\out{</div>}} -} - -} -\if{html}{\out{<hr>}} -\if{html}{\out{<a id="method-pp-print"></a>}} -\if{latex}{\out{\hypertarget{method-pp-print}{}}} -\subsection{Method \code{print()}}{ -\subsection{Usage}{ -\if{html}{\out{<div class="r">}}\preformatted{pp$print()}\if{html}{\out{</div>}} -} - -} -\if{html}{\out{<hr>}} -\if{html}{\out{<a id="method-pp-clone"></a>}} -\if{latex}{\out{\hypertarget{method-pp-clone}{}}} -\subsection{Method \code{clone()}}{ -The objects of this class are cloneable with this method. -\subsection{Usage}{ -\if{html}{\out{<div class="r">}}\preformatted{pp$clone(deep = FALSE)}\if{html}{\out{</div>}} -} - -\subsection{Arguments}{ -\if{html}{\out{<div class="arguments">}} -\describe{ -\item{\code{deep}}{Whether to make a deep clone.} -} -\if{html}{\out{</div>}} -} -} -} diff --git a/man/ppp.Rd b/man/ppp.Rd new file mode 100644 index 0000000..c0d35f1 --- /dev/null +++ b/man/ppp.Rd @@ -0,0 +1,100 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/chent.R +\docType{class} +\name{ppp} +\alias{ppp} +\title{R6 class for a plant protection product with at least one active ingredient} +\format{ +An \code{\link{R6Class}} generator object. +} +\description{ +Contains basic information about the active ingredients in the +product +} +\section{Public fields}{ +\if{html}{\out{<div class="r6-fields">}} +\describe{ +\item{\code{name}}{The name of the product} + +\item{\code{ais}}{A list of active ingredients} + +\item{\code{concentrations}}{The concentration of the ais} + +\item{\code{concentration_units}}{Defaults to g/L} + +\item{\code{density}}{The density of the product} + +\item{\code{density_units}}{Defaults to g/L +Creates a new instance of this \link[R6:R6Class]{R6} class.} + +\item{\code{...}}{Identifiers of the active ingredients} + +\item{\code{concentrations}}{Concentrations of the active ingredients} + +\item{\code{concentration_units}}{Defaults to g/L} + +\item{\code{density}}{The density} + +\item{\code{density_units}}{Defaults to g/L +Printing method} +} +\if{html}{\out{</div>}} +} +\section{Active bindings}{ +\if{html}{\out{<div class="r6-active-bindings">}} +\describe{ +\item{\code{...}}{Identifiers of the active ingredients} +} +\if{html}{\out{</div>}} +} +\section{Methods}{ +\subsection{Public methods}{ +\itemize{ +\item \href{#method-ppp-new}{\code{ppp$new()}} +\item \href{#method-ppp-print}{\code{ppp$print()}} +\item \href{#method-ppp-clone}{\code{ppp$clone()}} +} +} +\if{html}{\out{<hr>}} +\if{html}{\out{<a id="method-ppp-new"></a>}} +\if{latex}{\out{\hypertarget{method-ppp-new}{}}} +\subsection{Method \code{new()}}{ +\subsection{Usage}{ +\if{html}{\out{<div class="r">}}\preformatted{ppp$new( + name, + ..., + concentrations, + concentration_units = "g/L", + density = 1000, + density_units = "g/L" +)}\if{html}{\out{</div>}} +} + +} +\if{html}{\out{<hr>}} +\if{html}{\out{<a id="method-ppp-print"></a>}} +\if{latex}{\out{\hypertarget{method-ppp-print}{}}} +\subsection{Method \code{print()}}{ +\subsection{Usage}{ +\if{html}{\out{<div class="r">}}\preformatted{ppp$print()}\if{html}{\out{</div>}} +} + +} +\if{html}{\out{<hr>}} +\if{html}{\out{<a id="method-ppp-clone"></a>}} +\if{latex}{\out{\hypertarget{method-ppp-clone}{}}} +\subsection{Method \code{clone()}}{ +The objects of this class are cloneable with this method. +\subsection{Usage}{ +\if{html}{\out{<div class="r">}}\preformatted{ppp$clone(deep = FALSE)}\if{html}{\out{</div>}} +} + +\subsection{Arguments}{ +\if{html}{\out{<div class="arguments">}} +\describe{ +\item{\code{deep}}{Whether to make a deep clone.} +} +\if{html}{\out{</div>}} +} +} +} |