diff --git a/.Rbuildignore b/.Rbuildignore index e095fef6..c2964eef 100644 --- a/.Rbuildignore +++ b/.Rbuildignore @@ -61,3 +61,5 @@ ^data-raw/test_s4_fns/procure\.R$ ^data-raw/TEST_s4_fns/manufacture\.R$ ^data-raw/TEST_s4_fns/procure\.R$ +^data-raw/s4_fns/print\.R$ +^data-raw/s4_fns/depict\.R$ diff --git a/NAMESPACE b/NAMESPACE index 398024fb..688bf875 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -2,6 +2,7 @@ export("%>%") export(Ready4useArguments) +export(Ready4useDyad) export(Ready4useFiles) export(Ready4useProcessed) export(Ready4useRaw) @@ -62,10 +63,13 @@ export(write_fls_to_dv_ds) export(write_paired_ds_fls_to_dv) export(write_to_copy_fls_to_dv_dir) exportClasses(Ready4useArguments) +exportClasses(Ready4useDyad) exportClasses(Ready4useFiles) exportClasses(Ready4useProcessed) exportClasses(Ready4useRaw) +exportMethods(depict) import(methods) +import(ready4) importFrom(Hmisc,label) importFrom(assertthat,are_equal) importFrom(data.table,fread) @@ -103,6 +107,7 @@ importFrom(purrr,reduce) importFrom(purrr,walk) importFrom(readxl,read_excel) importFrom(ready4,add_lups) +importFrom(ready4,depict) importFrom(ready4,get_rds_from_dv) importFrom(ready4,make_files_tb) importFrom(ready4,make_local_path_to_dv_data) @@ -117,6 +122,7 @@ importFrom(ready4,write_fls_from_dv) importFrom(ready4,write_fls_to_dv) importFrom(ready4,write_to_dv_from_tbl) importFrom(ready4,write_to_dv_with_wait) +importFrom(ready4show,print_table) importFrom(rlang,exec) importFrom(rlang,sym) importFrom(stats,setNames) diff --git a/R/C3_ready4use_dataverses.R b/R/C3_ready4use_dataverses.R index 009b29f2..9e59afe4 100644 --- a/R/C3_ready4use_dataverses.R +++ b/R/C3_ready4use_dataverses.R @@ -4,7 +4,7 @@ setOldClass(c("ready4use_dataverses","tbl_df", "tbl", "data.frame")) #' @description Create a new valid instance of the ready4 S3 class for tibble object lookup table of files to be imported from a dataverse. #' @param x A prototype for the ready4 S3 class for tibble object lookup table of files to be imported from a dataverse., Default: make_pt_ready4use_dataverses() #' @return A validated instance of the ready4 S3 class for tibble object lookup table of files to be imported from a dataverse. -#' @details ready4 S3 class for tibble object lookup table of files to be imported from a dataverse. +#' @details Tibble object lookup table of files to be imported from a dataverse. #' @rdname ready4use_dataverses #' @export ready4use_dataverses <- function(x = make_pt_ready4use_dataverses()){ @@ -14,7 +14,7 @@ validate_ready4use_dataverses(make_new_ready4use_dataverses(x)) #' @description Create a new unvalidated instance of the ready4 S3 class for tibble object lookup table of files to be imported from a dataverse. #' @param x A prototype for the ready4 S3 class for tibble object lookup table of files to be imported from a dataverse. #' @return An unvalidated instance of the ready4 S3 class for tibble object lookup table of files to be imported from a dataverse. -#' @details ready4 S3 class for tibble object lookup table of files to be imported from a dataverse. +#' @details Tibble object lookup table of files to be imported from a dataverse. #' @rdname make_new_ready4use_dataverses #' @export #' @importFrom tibble is_tibble @@ -34,7 +34,7 @@ x #' @param data_repo_file_ext_chr Data repository file extension (a character vector), Default: character(0) #' @param data_repo_save_type_chr Data repository save type (a character vector), Default: character(0) #' @return A prototype for ready4 S3 class for tibble object lookup table of files to be imported from a dataverse. -#' @details ready4 S3 class for tibble object lookup table of files to be imported from a dataverse. +#' @details Tibble object lookup table of files to be imported from a dataverse. #' @rdname make_pt_ready4use_dataverses #' @export #' @importFrom ready4 update_pt_fn_args_ls @@ -60,7 +60,7 @@ rlang::exec(tibble::tibble,!!!args_ls) #' @description Validate an instance of the ready4 S3 class for tibble object lookup table of files to be imported from a dataverse. #' @param x An unvalidated instance of the ready4 S3 class for tibble object lookup table of files to be imported from a dataverse. #' @return A prototpe for ready4 S3 class for tibble object lookup table of files to be imported from a dataverse. -#' @details ready4 S3 class for tibble object lookup table of files to be imported from a dataverse. +#' @details Tibble object lookup table of files to be imported from a dataverse. #' @rdname validate_ready4use_dataverses #' @export #' @importFrom stringr str_detect str_c @@ -108,7 +108,7 @@ x} #' @description Check whether an object is a valid instance of the ready4 S3 class for tibble object lookup table of files to be imported from a dataverse. #' @param x An object of any type #' @return A logical value, TRUE if a valid instance of the ready4 S3 class for tibble object lookup table of files to be imported from a dataverse. -#' @details ready4 S3 class for tibble object lookup table of files to be imported from a dataverse. +#' @details Tibble object lookup table of files to be imported from a dataverse. #' @rdname is_ready4use_dataverses #' @export is_ready4use_dataverses <- function(x) inherits(validate_ready4use_dataverses(x), "ready4use_dataverses") diff --git a/R/C3_ready4use_dictionary.R b/R/C3_ready4use_dictionary.R index f0cf450b..91190c48 100644 --- a/R/C3_ready4use_dictionary.R +++ b/R/C3_ready4use_dictionary.R @@ -4,7 +4,7 @@ setOldClass(c("ready4use_dictionary","tbl_df", "tbl", "data.frame")) #' @description Create a new valid instance of the ready4 s3 class defining a data dictionary tibble. #' @param x A prototype for the ready4 s3 class defining a data dictionary tibble., Default: make_pt_ready4use_dictionary() #' @return A validated instance of the ready4 s3 class defining a data dictionary tibble. -#' @details ready4 s3 class defining a data dictionary tibble. +#' @details A data dictionary tibble. #' @rdname ready4use_dictionary #' @export ready4use_dictionary <- function(x = make_pt_ready4use_dictionary()){ @@ -14,7 +14,7 @@ validate_ready4use_dictionary(make_new_ready4use_dictionary(x)) #' @description Create a new unvalidated instance of the ready4 s3 class defining a data dictionary tibble. #' @param x A prototype for the ready4 s3 class defining a data dictionary tibble. #' @return An unvalidated instance of the ready4 s3 class defining a data dictionary tibble. -#' @details ready4 s3 class defining a data dictionary tibble. +#' @details A data dictionary tibble. #' @rdname make_new_ready4use_dictionary #' @export #' @importFrom tibble is_tibble @@ -31,7 +31,7 @@ x #' @param var_desc_chr Variable description (a character vector), Default: character(0) #' @param var_type_chr Variable type (a character vector), Default: character(0) #' @return A prototype for ready4 s3 class defining a data dictionary tibble. -#' @details ready4 s3 class defining a data dictionary tibble. +#' @details A data dictionary tibble. #' @rdname make_pt_ready4use_dictionary #' @export #' @importFrom ready4 update_pt_fn_args_ls @@ -51,7 +51,7 @@ rlang::exec(tibble::tibble,!!!args_ls) #' @description Validate an instance of the ready4 s3 class defining a data dictionary tibble. #' @param x An unvalidated instance of the ready4 s3 class defining a data dictionary tibble. #' @return A prototpe for ready4 s3 class defining a data dictionary tibble. -#' @details ready4 s3 class defining a data dictionary tibble. +#' @details A data dictionary tibble. #' @rdname validate_ready4use_dictionary #' @export #' @importFrom stringr str_detect str_c @@ -99,7 +99,7 @@ x} #' @description Check whether an object is a valid instance of the ready4 s3 class defining a data dictionary tibble. #' @param x An object of any type #' @return A logical value, TRUE if a valid instance of the ready4 s3 class defining a data dictionary tibble. -#' @details ready4 s3 class defining a data dictionary tibble. +#' @details A data dictionary tibble. #' @rdname is_ready4use_dictionary #' @export is_ready4use_dictionary <- function(x) inherits(validate_ready4use_dictionary(x), "ready4use_dictionary") diff --git a/R/C3_ready4use_distributions.R b/R/C3_ready4use_distributions.R index 3ce49b00..5a84b466 100644 --- a/R/C3_ready4use_distributions.R +++ b/R/C3_ready4use_distributions.R @@ -3,7 +3,7 @@ #' @description Create a new valid instance of the ready4 S3 class for list object that summarises the parameters of each distribution #' @param x A prototype for the ready4 S3 class for list object that summarises the parameters of each distribution, Default: make_pt_ready4use_distributions() #' @return A validated instance of the ready4 S3 class for list object that summarises the parameters of each distribution -#' @details ready4 S3 class for list object that summarises the parameters of each distribution +#' @details List object that summarises the parameters of each distribution #' @rdname ready4use_distributions #' @export ready4use_distributions <- function(x = make_pt_ready4use_distributions()){ @@ -13,7 +13,7 @@ validate_ready4use_distributions(make_new_ready4use_distributions(x)) #' @description Create a new unvalidated instance of the ready4 S3 class for list object that summarises the parameters of each distribution #' @param x A prototype for the ready4 S3 class for list object that summarises the parameters of each distribution #' @return An unvalidated instance of the ready4 S3 class for list object that summarises the parameters of each distribution -#' @details ready4 S3 class for list object that summarises the parameters of each distribution +#' @details List object that summarises the parameters of each distribution #' @rdname make_new_ready4use_distributions #' @export make_new_ready4use_distributions <- function(x){ @@ -31,7 +31,7 @@ x #' @param dstr_param_4_dbl Distribution parameter 4 (a double vector), Default: numeric(0) #' @param transformation_chr Transformation (a character vector), Default: character(0) #' @return A prototype for ready4 S3 class for list object that summarises the parameters of each distribution -#' @details ready4 S3 class for list object that summarises the parameters of each distribution +#' @details List object that summarises the parameters of each distribution #' @rdname make_pt_ready4use_distributions #' @export #' @importFrom ready4 update_pt_fn_args_ls @@ -54,7 +54,7 @@ rlang::exec(list,!!!args_ls) #' @description Validate an instance of the ready4 S3 class for list object that summarises the parameters of each distribution #' @param x An unvalidated instance of the ready4 S3 class for list object that summarises the parameters of each distribution #' @return A prototpe for ready4 S3 class for list object that summarises the parameters of each distribution -#' @details ready4 S3 class for list object that summarises the parameters of each distribution +#' @details List object that summarises the parameters of each distribution #' @rdname validate_ready4use_distributions #' @export #' @importFrom stringr str_detect str_c @@ -104,7 +104,7 @@ x} #' @description Check whether an object is a valid instance of the ready4 S3 class for list object that summarises the parameters of each distribution #' @param x An object of any type #' @return A logical value, TRUE if a valid instance of the ready4 S3 class for list object that summarises the parameters of each distribution -#' @details ready4 S3 class for list object that summarises the parameters of each distribution +#' @details List object that summarises the parameters of each distribution #' @rdname is_ready4use_distributions #' @export is_ready4use_distributions <- function(x) inherits(validate_ready4use_distributions(x), "ready4use_distributions") diff --git a/R/C3_ready4use_imports.R b/R/C3_ready4use_imports.R index 6a480cbd..4f3b673c 100644 --- a/R/C3_ready4use_imports.R +++ b/R/C3_ready4use_imports.R @@ -5,7 +5,7 @@ setOldClass(c("ready4use_imports","tbl_df", "tbl", "data.frame")) #' @description Create a new valid instance of the ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import. #' @param x A prototype for the ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import., Default: make_pt_ready4use_imports() #' @return A validated instance of the ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import. -#' @details ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import. +#' @details Tibble object lookup table of sources of raw (un-processed) data to import. #' @rdname ready4use_imports #' @export ready4use_imports <- function(x = make_pt_ready4use_imports()){ @@ -15,7 +15,7 @@ validate_ready4use_imports(make_new_ready4use_imports(x)) #' @description Create a new unvalidated instance of the ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import. #' @param x A prototype for the ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import. #' @return An unvalidated instance of the ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import. -#' @details ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import. +#' @details Tibble object lookup table of sources of raw (un-processed) data to import. #' @rdname make_new_ready4use_imports #' @export #' @importFrom tibble is_tibble @@ -41,7 +41,7 @@ x #' @param inc_fls_to_rename_ls Include files to rename (a list), Default: list() #' @param new_nms_for_inc_fls_ls New names for include files (a list), Default: list() #' @return A prototype for ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import. -#' @details ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import. +#' @details Tibble object lookup table of sources of raw (un-processed) data to import. #' @rdname make_pt_ready4use_imports #' @export #' @importFrom ready4 update_pt_fn_args_ls @@ -79,7 +79,7 @@ rlang::exec(tibble::tibble,!!!args_ls) #' @description Validate an instance of the ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import. #' @param x An unvalidated instance of the ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import. #' @return A prototpe for ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import. -#' @details ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import. +#' @details Tibble object lookup table of sources of raw (un-processed) data to import. #' @rdname validate_ready4use_imports #' @export #' @importFrom stringr str_detect str_c @@ -127,7 +127,7 @@ x} #' @description Check whether an object is a valid instance of the ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import. #' @param x An object of any type #' @return A logical value, TRUE if a valid instance of the ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import. -#' @details ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import. +#' @details Tibble object lookup table of sources of raw (un-processed) data to import. #' @rdname is_ready4use_imports #' @export is_ready4use_imports <- function(x) inherits(validate_ready4use_imports(x), "ready4use_imports") diff --git a/R/C3_ready4use_mapes.R b/R/C3_ready4use_mapes.R index 909f1ed0..bc8405a9 100644 --- a/R/C3_ready4use_mapes.R +++ b/R/C3_ready4use_mapes.R @@ -4,7 +4,7 @@ setOldClass(c("ready4use_mapes","tbl_df", "tbl", "data.frame")) #' @description Create a new valid instance of the ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. #' @param x A prototype for the ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors., Default: make_pt_ready4use_mapes() #' @return A validated instance of the ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. -#' @details ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. +#' @details Tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. #' @rdname ready4use_mapes #' @export ready4use_mapes <- function(x = make_pt_ready4use_mapes()){ @@ -14,7 +14,7 @@ validate_ready4use_mapes(make_new_ready4use_mapes(x)) #' @description Create a new unvalidated instance of the ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. #' @param x A prototype for the ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. #' @return An unvalidated instance of the ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. -#' @details ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. +#' @details Tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. #' @rdname make_new_ready4use_mapes #' @export #' @importFrom tibble is_tibble @@ -41,7 +41,7 @@ x #' @param mape_10_yr_shp_dbl Mean absolute prediction error 10 year shape (a double vector), Default: numeric(0) #' @param mape_15_yr_shp_dbl Mean absolute prediction error 15 year shape (a double vector), Default: numeric(0) #' @return A prototype for ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. -#' @details ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. +#' @details Tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. #' @rdname make_pt_ready4use_mapes #' @export #' @importFrom ready4 update_pt_fn_args_ls @@ -81,7 +81,7 @@ rlang::exec(tibble::tibble,!!!args_ls) #' @description Validate an instance of the ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. #' @param x An unvalidated instance of the ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. #' @return A prototpe for ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. -#' @details ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. +#' @details Tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. #' @rdname validate_ready4use_mapes #' @export #' @importFrom stringr str_detect str_c @@ -129,7 +129,7 @@ x} #' @description Check whether an object is a valid instance of the ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. #' @param x An object of any type #' @return A logical value, TRUE if a valid instance of the ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. -#' @details ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. +#' @details Tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. #' @rdname is_ready4use_mapes #' @export is_ready4use_mapes <- function(x) inherits(validate_ready4use_mapes(x), "ready4use_mapes") diff --git a/R/C4_Ready4useArguments.R b/R/C4_Ready4useArguments.R index bd89ed51..e510a526 100644 --- a/R/C4_Ready4useArguments.R +++ b/R/C4_Ready4useArguments.R @@ -1,6 +1,6 @@ #' Ready4useArguments #' -#' ready4 S4 class containing data to be passed to a function that constructs a spatial object from a lookup table. +#' Arguments for a function that constructs a spatial object. #' #' @include C4_Ready4useProcessed.R #' @slot crs_nbr_dbl Crs number (a double vector) diff --git a/R/C4_Ready4useDyad.R b/R/C4_Ready4useDyad.R new file mode 100644 index 00000000..6186e749 --- /dev/null +++ b/R/C4_Ready4useDyad.R @@ -0,0 +1,23 @@ +#' Ready4useDyad +#' +#' A dataset and data dictionary pair. +#' +setOldClass(c("ready4use_dictionary","tbl_df", "tbl", "data.frame")) +#' @slot ds_tb Dataset (a tibble) +#' @slot dictionary_r3 Dictionary (a ready4 S3) +#' @import ready4 +#' @name Ready4useDyad-class +#' @rdname Ready4useDyad-class +#' @export Ready4useDyad +#' @exportClass Ready4useDyad +Ready4useDyad <- methods::setClass("Ready4useDyad", +contains = "Ready4Launch", +slots = c(ds_tb = "tbl_df",dictionary_r3 = "ready4use_dictionary"), +prototype = list(ds_tb = tibble::tibble(),dictionary_r3 = ready4use_dictionary())) + + +methods::setValidity(methods::className("Ready4useDyad"), +function(object){ +msg <- NULL +if (is.null(msg)) TRUE else msg +}) diff --git a/R/C4_Ready4useFiles.R b/R/C4_Ready4useFiles.R index 0225bbe4..6c146b26 100644 --- a/R/C4_Ready4useFiles.R +++ b/R/C4_Ready4useFiles.R @@ -1,17 +1,19 @@ #' Ready4useFiles #' -#' ready4 S4 class defining data to be saved in local directory. +#' Metadata for dataset(s) to be saved in local directory. #' #' @slot merge_itms_chr Merge items (a character vector) #' @slot raw_fls_dir_1L_chr Raw files directory (a character vector of length one) #' @slot pkg_1L_chr Package (a character vector of length one) #' @slot overwrite_1L_lgl Overwrite (a logical vector of length one) #' @slot write_1L_lgl Write (a logical vector of length one) +#' @import ready4 #' @name Ready4useFiles-class #' @rdname Ready4useFiles-class #' @export Ready4useFiles #' @exportClass Ready4useFiles Ready4useFiles <- methods::setClass("Ready4useFiles", +contains = "Ready4Launch", slots = c(merge_itms_chr = "character",raw_fls_dir_1L_chr = "character",pkg_1L_chr = "character",overwrite_1L_lgl = "logical",write_1L_lgl = "logical"), prototype = list(merge_itms_chr = NA_character_,raw_fls_dir_1L_chr = NA_character_,pkg_1L_chr = NA_character_,overwrite_1L_lgl = NA,write_1L_lgl = NA)) diff --git a/R/C4_Ready4useProcessed.R b/R/C4_Ready4useProcessed.R index 06f858c7..d8278157 100644 --- a/R/C4_Ready4useProcessed.R +++ b/R/C4_Ready4useProcessed.R @@ -1,6 +1,6 @@ #' Ready4useProcessed #' -#' ready4 S4 class defining data to be saved in local directory in a processed (R) format. +#' Metadata for dataset(s) to be saved in local directory in a processed (R) format. #' #' @include C4_Ready4useFiles.R #' @slot write_type_1L_chr Write type (a character vector of length one) diff --git a/R/C4_Ready4useRaw.R b/R/C4_Ready4useRaw.R index 0c1cb71f..fd3f4456 100644 --- a/R/C4_Ready4useRaw.R +++ b/R/C4_Ready4useRaw.R @@ -1,6 +1,6 @@ #' Ready4useRaw #' -#' ready4 S4 class defining data to be saved in local directory in a raw (unprocessed) format. +#' Metadata for dataset(s) to be saved in local directory in a raw (unprocessed) format. #' #' @include C4_Ready4useFiles.R #' @slot write_type_1L_chr Write type (a character vector of length one) diff --git a/R/mthd_depict.R b/R/mthd_depict.R new file mode 100644 index 00000000..750f4b2b --- /dev/null +++ b/R/mthd_depict.R @@ -0,0 +1,84 @@ +#' +#' depict +#' @name depict-Ready4useDyad +#' @description depict method applied to Ready4useDyad +#' @param x An object of class Ready4useDyad +#' @param caption_1L_chr Caption (a character vector of length one), Default: 'NA' +#' @param display_1L_chr Display (a character vector of length one), Default: 'all' +#' @param mkdn_tbl_ref_1L_chr Markdown table reference (a character vector of length one), Default: '' +#' @param output_type_1L_chr Output type (a character vector of length one), Default: 'HTML' +#' @param type_1L_chr Type (a character vector of length one), Default: 'ds' +#' @param use_lbls_as_col_nms_1L_lgl Use labels as column names (a logical vector of length one), Default: T +#' @param use_rdocx_1L_lgl Use rdocx (a logical vector of length one), Default: F +#' @param ... Additional arguments +#' @return NULL +#' @rdname depict-methods +#' @aliases depict,Ready4useDyad-method +#' @export +#' @importFrom ready4show print_table +#' @importFrom ready4 depict +methods::setMethod("depict", "Ready4useDyad", function (x, caption_1L_chr = NA_character_, display_1L_chr = "all", + mkdn_tbl_ref_1L_chr = "", output_type_1L_chr = "HTML", type_1L_chr = "ds", + use_lbls_as_col_nms_1L_lgl = T, use_rdocx_1L_lgl = F, ...) +{ + if (type_1L_chr == "ds") { + df <- x@ds_tb + caption_1L_chr <- ifelse(is.na(caption_1L_chr), "Dataset", + caption_1L_chr) + } + if (type_1L_chr == "dict") { + df <- x@dictionary_r3 + caption_1L_chr <- ifelse(is.na(caption_1L_chr), "Data Dictionary", + caption_1L_chr) + } + if (display_1L_chr == "head") + df <- df %>% head() + if (display_1L_chr == "tail") + df <- df %>% tail() + df %>% ready4show::print_table(output_type_1L_chr = output_type_1L_chr, + use_rdocx_1L_lgl = use_rdocx_1L_lgl, caption_1L_chr = caption_1L_chr, + use_lbls_as_col_nms_1L_lgl = use_lbls_as_col_nms_1L_lgl, + mkdn_tbl_ref_1L_chr = mkdn_tbl_ref_1L_chr, ...) +}) +#' +#' depict +#' @name depict-Ready4useDyad +#' @description depict method applied to Ready4useDyad +#' @param x An object of class Ready4useDyad +#' @param caption_1L_chr Caption (a character vector of length one), Default: 'NA' +#' @param display_1L_chr Display (a character vector of length one), Default: 'all' +#' @param mkdn_tbl_ref_1L_chr Markdown table reference (a character vector of length one), Default: '' +#' @param output_type_1L_chr Output type (a character vector of length one), Default: 'HTML' +#' @param type_1L_chr Type (a character vector of length one), Default: 'ds' +#' @param use_lbls_as_col_nms_1L_lgl Use labels as column names (a logical vector of length one), Default: T +#' @param use_rdocx_1L_lgl Use rdocx (a logical vector of length one), Default: F +#' @param ... Additional arguments +#' @return NULL +#' @rdname depict-methods +#' @aliases depict,Ready4useDyad-method +#' @export +#' @importFrom ready4show print_table +#' @importFrom ready4 depict +methods::setMethod("depict", "Ready4useDyad", function (x, caption_1L_chr = NA_character_, display_1L_chr = "all", + mkdn_tbl_ref_1L_chr = "", output_type_1L_chr = "HTML", type_1L_chr = "ds", + use_lbls_as_col_nms_1L_lgl = T, use_rdocx_1L_lgl = F, ...) +{ + if (type_1L_chr == "ds") { + df <- x@ds_tb + caption_1L_chr <- ifelse(is.na(caption_1L_chr), "Dataset", + caption_1L_chr) + } + if (type_1L_chr == "dict") { + df <- x@dictionary_r3 + caption_1L_chr <- ifelse(is.na(caption_1L_chr), "Data Dictionary", + caption_1L_chr) + } + if (display_1L_chr == "head") + df <- df %>% head() + if (display_1L_chr == "tail") + df <- df %>% tail() + df %>% ready4show::print_table(output_type_1L_chr = output_type_1L_chr, + use_rdocx_1L_lgl = use_rdocx_1L_lgl, caption_1L_chr = caption_1L_chr, + use_lbls_as_col_nms_1L_lgl = use_lbls_as_col_nms_1L_lgl, + mkdn_tbl_ref_1L_chr = mkdn_tbl_ref_1L_chr, ...) +}) diff --git a/_pkgdown.yml b/_pkgdown.yml index d1175cd2..caf0950b 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -22,6 +22,7 @@ reference: - Ready4useRaw - Ready4useProcessed - Ready4useArguments + - Ready4useDyad - title: "Functions" - contents: - add_labels_from_dictionary @@ -30,6 +31,7 @@ reference: - get_r3_from_dv_csv - title: "Methods" - contents: + - depict-Ready4useDyad - manufacture.ready4use_dataverses - manufacture.ready4use_imports - procure.ready4use_dataverses diff --git a/data-raw/DATASET.R b/data-raw/DATASET.R index b7c5bd74..9753bb03 100644 --- a/data-raw/DATASET.R +++ b/data-raw/DATASET.R @@ -50,7 +50,7 @@ x_ready4class_constructor <- dplyr::bind_rows( dstr_param_3_dbl = "numeric(0)", dstr_param_4_dbl = "numeric(0)", transformation_chr = "character(0)")), - class_desc_chr = "ready4 S3 class for list object that summarises the parameters of each distribution"), + class_desc_chr = "List object that summarises the parameters of each distribution"), ready4class::make_pt_ready4class_constructor(make_s3_lgl = TRUE, name_stub_chr = "dataverses", pt_ls = list(list("tibble")), @@ -63,7 +63,7 @@ x_ready4class_constructor <- dplyr::bind_rows( data_repo_db_ui_chr = "character(0)", data_repo_file_ext_chr = "character(0)", data_repo_save_type_chr = "character(0)")), - class_desc_chr = "ready4 S3 class for tibble object lookup table of files to be imported from a dataverse."), + class_desc_chr = "Tibble object lookup table of files to be imported from a dataverse."), ready4class::make_pt_ready4class_constructor(make_s3_lgl = TRUE, name_stub_chr = "imports", pt_ls = list(list("tibble")), @@ -75,7 +75,7 @@ x_ready4class_constructor <- dplyr::bind_rows( inc_file_main_chr = "character(0)", inc_fls_to_rename_ls = "list()", new_nms_for_inc_fls_ls = "list()")), - class_desc_chr = "ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import.", + class_desc_chr = "Tibble object lookup table of sources of raw (un-processed) data to import.", parent_class_chr = "ready4use_dataverses"), ready4class::make_pt_ready4class_constructor(make_s3_lgl = TRUE, name_stub_chr = "mapes", @@ -96,7 +96,7 @@ x_ready4class_constructor <- dplyr::bind_rows( mape_05_yr_shp_dbl = "numeric(0)", mape_10_yr_shp_dbl = "numeric(0)", mape_15_yr_shp_dbl = "numeric(0)")), - class_desc_chr = "ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors."), + class_desc_chr = "Tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors."), ready4class::make_pt_ready4class_constructor(make_s3_lgl = T, name_stub_chr = "dictionary", pt_ls = list(list("tibble")), @@ -106,20 +106,20 @@ x_ready4class_constructor <- dplyr::bind_rows( var_ctg_chr = "character(0)", var_desc_chr = "character(0)", var_type_chr = "character(0)")), - class_desc_chr= "ready4 s3 class defining a data dictionary tibble."), + class_desc_chr= "A data dictionary tibble."), ready4class::make_pt_ready4class_constructor(make_s3_lgl = FALSE, name_stub_chr = "Files", slots_ls = list("merge_itms_chr","raw_fls_dir_1L_chr","pkg_1L_chr","overwrite_1L_lgl", "write_1L_lgl") %>% list(), # Cut: "lup_tbs_r4", pt_ls = list("character","character","character","logical", "logical") %>% list(), # Cut: "ready4class_lookup", - class_desc_chr= "ready4 S4 class defining data to be saved in local directory.", - parent_class_chr = NA_character_), # Cut: ,include_classes = list("ready4class_lookup") + class_desc_chr= "Metadata for dataset(s) to be saved in local directory.", + parent_class_chr = "Ready4Launch"), # NA_character_ # Cut: ,include_classes = list("ready4class_lookup") ready4class::make_pt_ready4class_constructor(make_s3_lgl = FALSE, name_stub_chr = "Raw", slots_ls = list("write_type_1L_chr") %>% list(), pt_ls = list("character") %>% list(), vals_ls = list(write_type_1L_chr ="raw"), allowed_vals_ls = list(write_type_1L_chr = "raw"), - class_desc_chr= "ready4 S4 class defining data to be saved in local directory in a raw (unprocessed) format.", + class_desc_chr= "Metadata for dataset(s) to be saved in local directory in a raw (unprocessed) format.", parent_class_chr = "Ready4useFiles", inc_clss_ls = list("Ready4useFiles")), ready4class::make_pt_ready4class_constructor(make_s3_lgl = FALSE, @@ -128,16 +128,22 @@ x_ready4class_constructor <- dplyr::bind_rows( pt_ls = list("character","character","character","character","list") %>% list(), vals_ls = list(write_type_1L_chr = "proc"), allowed_vals_ls = list(write_type_1L_chr = "proc"), - class_desc_chr= "ready4 S4 class defining data to be saved in local directory in a processed (R) format.", + class_desc_chr= "Metadata for dataset(s) to be saved in local directory in a processed (R) format.", parent_class_chr = "Ready4useFiles", inc_clss_ls = list("Ready4useFiles")), ready4class::make_pt_ready4class_constructor(make_s3_lgl = FALSE, name_stub_chr = "Arguments", slots_ls = list("crs_nbr_dbl") %>% list(), # Change pt_ls = list("numeric") %>% list(), - class_desc_chr= "ready4 S4 class containing data to be passed to a function that constructs a spatial object from a lookup table.", + class_desc_chr= "Arguments for a function that constructs a spatial object.", parent_class_chr = "Ready4useProcessed", - inc_clss_ls = list("Ready4useProcessed")) + inc_clss_ls = list("Ready4useProcessed")), + ready4class::make_pt_ready4class_constructor(make_s3_lgl = FALSE, + name_stub_chr = "Dyad", + slots_ls = list("ds_tb","dictionary_r3") %>% list(), # Change + pt_ls = list("tbl_df","ready4use_dictionary") %>% list(), + class_desc_chr= "A dataset and data dictionary pair.", + parent_class_chr = "Ready4Launch") ) %>% ready4class::ready4class_constructor() x_ready4pack_manifest <- ready4pack::make_pt_ready4pack_manifest(x_ready4fun_manifest, diff --git a/data-raw/s4_fns/depict.R b/data-raw/s4_fns/depict.R new file mode 100644 index 00000000..7d2d8348 --- /dev/null +++ b/data-raw/s4_fns/depict.R @@ -0,0 +1,35 @@ +depict_Ready4useDyad <- function(x, + caption_1L_chr = NA_character_, + display_1L_chr = "all", + mkdn_tbl_ref_1L_chr = "", + output_type_1L_chr = "HTML", + type_1L_chr = "ds", + use_lbls_as_col_nms_1L_lgl = T, + use_rdocx_1L_lgl = F, + ...){ + if(type_1L_chr == "ds"){ + df <- x@ds_tb + caption_1L_chr <- ifelse(is.na(caption_1L_chr), + "Dataset", + caption_1L_chr) + } + if(type_1L_chr == "dict"){ + df <- x@dictionary_r3 + caption_1L_chr <- ifelse(is.na(caption_1L_chr), + "Data Dictionary", + caption_1L_chr) + } + if(display_1L_chr == "head") + df <- df %>% + head() + if(display_1L_chr == "tail") + df <- df %>% + tail() + df %>% + ready4show::print_table(output_type_1L_chr = output_type_1L_chr, + use_rdocx_1L_lgl = use_rdocx_1L_lgl, + caption_1L_chr = caption_1L_chr, + use_lbls_as_col_nms_1L_lgl = use_lbls_as_col_nms_1L_lgl, + mkdn_tbl_ref_1L_chr = mkdn_tbl_ref_1L_chr, + ...) +} diff --git a/data-raw/test_s4_fns/manufacture.R b/data-raw/test_s4_fns/manufacture.R deleted file mode 100644 index 46dc0945..00000000 --- a/data-raw/test_s4_fns/manufacture.R +++ /dev/null @@ -1,3 +0,0 @@ -manufacture_Ready4useArguments <- function(x){ - paste0("The crs is ",x@crs_nbr_dbl," and the merge is ",x@merge_itms_chr) -} diff --git a/data-raw/test_s4_fns/procure.R b/data-raw/test_s4_fns/procure.R deleted file mode 100644 index 75261fdf..00000000 --- a/data-raw/test_s4_fns/procure.R +++ /dev/null @@ -1,3 +0,0 @@ -procure_Ready4useArguments <- function(x){ - paste0("The crs is ",x@crs_nbr_dbl) -} diff --git a/man/Ready4useArguments-class.Rd b/man/Ready4useArguments-class.Rd index 1be792f2..917a7740 100644 --- a/man/Ready4useArguments-class.Rd +++ b/man/Ready4useArguments-class.Rd @@ -6,7 +6,7 @@ \alias{Ready4useArguments} \title{Ready4useArguments} \description{ -ready4 S4 class containing data to be passed to a function that constructs a spatial object from a lookup table. +Arguments for a function that constructs a spatial object. } \section{Slots}{ diff --git a/man/Ready4useFiles-class.Rd b/man/Ready4useFiles-class.Rd index 6f0f8bd3..7c21944d 100644 --- a/man/Ready4useFiles-class.Rd +++ b/man/Ready4useFiles-class.Rd @@ -6,7 +6,7 @@ \alias{Ready4useFiles} \title{Ready4useFiles} \description{ -ready4 S4 class defining data to be saved in local directory. +Metadata for dataset(s) to be saved in local directory. } \section{Slots}{ diff --git a/man/Ready4useProcessed-class.Rd b/man/Ready4useProcessed-class.Rd index 4dfb17c9..90b59ce6 100644 --- a/man/Ready4useProcessed-class.Rd +++ b/man/Ready4useProcessed-class.Rd @@ -6,7 +6,7 @@ \alias{Ready4useProcessed} \title{Ready4useProcessed} \description{ -ready4 S4 class defining data to be saved in local directory in a processed (R) format. +Metadata for dataset(s) to be saved in local directory in a processed (R) format. } \section{Slots}{ diff --git a/man/Ready4useRaw-class.Rd b/man/Ready4useRaw-class.Rd index 490e4cb2..43f21856 100644 --- a/man/Ready4useRaw-class.Rd +++ b/man/Ready4useRaw-class.Rd @@ -6,7 +6,7 @@ \alias{Ready4useRaw} \title{Ready4useRaw} \description{ -ready4 S4 class defining data to be saved in local directory in a raw (unprocessed) format. +Metadata for dataset(s) to be saved in local directory in a raw (unprocessed) format. } \section{Slots}{ diff --git a/man/depict-methods.Rd b/man/depict-methods.Rd new file mode 100644 index 00000000..cd498822 --- /dev/null +++ b/man/depict-methods.Rd @@ -0,0 +1,55 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/mthd_depict.R +\name{depict-Ready4useDyad} +\alias{depict-Ready4useDyad} +\alias{depict,Ready4useDyad-method} +\title{depict} +\usage{ +\S4method{depict}{Ready4useDyad}( + x, + caption_1L_chr = NA_character_, + display_1L_chr = "all", + mkdn_tbl_ref_1L_chr = "", + output_type_1L_chr = "HTML", + type_1L_chr = "ds", + use_lbls_as_col_nms_1L_lgl = T, + use_rdocx_1L_lgl = F, + ... +) + +\S4method{depict}{Ready4useDyad}( + x, + caption_1L_chr = NA_character_, + display_1L_chr = "all", + mkdn_tbl_ref_1L_chr = "", + output_type_1L_chr = "HTML", + type_1L_chr = "ds", + use_lbls_as_col_nms_1L_lgl = T, + use_rdocx_1L_lgl = F, + ... +) +} +\arguments{ +\item{x}{An object of class Ready4useDyad} + +\item{caption_1L_chr}{Caption (a character vector of length one), Default: 'NA'} + +\item{display_1L_chr}{Display (a character vector of length one), Default: 'all'} + +\item{mkdn_tbl_ref_1L_chr}{Markdown table reference (a character vector of length one), Default: ''} + +\item{output_type_1L_chr}{Output type (a character vector of length one), Default: 'HTML'} + +\item{type_1L_chr}{Type (a character vector of length one), Default: 'ds'} + +\item{use_lbls_as_col_nms_1L_lgl}{Use labels as column names (a logical vector of length one), Default: T} + +\item{use_rdocx_1L_lgl}{Use rdocx (a logical vector of length one), Default: F} + +\item{...}{Additional arguments} +} +\description{ +depict method applied to Ready4useDyad + +depict method applied to Ready4useDyad +} diff --git a/man/is_ready4use_dataverses.Rd b/man/is_ready4use_dataverses.Rd index 3b182d94..8ddfa580 100644 --- a/man/is_ready4use_dataverses.Rd +++ b/man/is_ready4use_dataverses.Rd @@ -16,5 +16,5 @@ A logical value, TRUE if a valid instance of the ready4 S3 class for tibble obje Check whether an object is a valid instance of the ready4 S3 class for tibble object lookup table of files to be imported from a dataverse. } \details{ -ready4 S3 class for tibble object lookup table of files to be imported from a dataverse. +Tibble object lookup table of files to be imported from a dataverse. } diff --git a/man/is_ready4use_dictionary.Rd b/man/is_ready4use_dictionary.Rd index d73c6ae0..53a59eb4 100644 --- a/man/is_ready4use_dictionary.Rd +++ b/man/is_ready4use_dictionary.Rd @@ -16,5 +16,5 @@ A logical value, TRUE if a valid instance of the ready4 s3 class defining a data Check whether an object is a valid instance of the ready4 s3 class defining a data dictionary tibble. } \details{ -ready4 s3 class defining a data dictionary tibble. +A data dictionary tibble. } diff --git a/man/is_ready4use_distributions.Rd b/man/is_ready4use_distributions.Rd index 7ec9b462..47f508bc 100644 --- a/man/is_ready4use_distributions.Rd +++ b/man/is_ready4use_distributions.Rd @@ -16,5 +16,5 @@ A logical value, TRUE if a valid instance of the ready4 S3 class for list object Check whether an object is a valid instance of the ready4 S3 class for list object that summarises the parameters of each distribution } \details{ -ready4 S3 class for list object that summarises the parameters of each distribution +List object that summarises the parameters of each distribution } diff --git a/man/is_ready4use_imports.Rd b/man/is_ready4use_imports.Rd index 07366632..fadd7cec 100644 --- a/man/is_ready4use_imports.Rd +++ b/man/is_ready4use_imports.Rd @@ -16,5 +16,5 @@ A logical value, TRUE if a valid instance of the ready4 S3 class for tibble obje Check whether an object is a valid instance of the ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import. } \details{ -ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import. +Tibble object lookup table of sources of raw (un-processed) data to import. } diff --git a/man/is_ready4use_mapes.Rd b/man/is_ready4use_mapes.Rd index e479de8f..090e0ccb 100644 --- a/man/is_ready4use_mapes.Rd +++ b/man/is_ready4use_mapes.Rd @@ -16,5 +16,5 @@ A logical value, TRUE if a valid instance of the ready4 S3 class for tibble obje Check whether an object is a valid instance of the ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. } \details{ -ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. +Tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. } diff --git a/man/make_new_ready4use_dataverses.Rd b/man/make_new_ready4use_dataverses.Rd index 0be1334c..8f795f35 100644 --- a/man/make_new_ready4use_dataverses.Rd +++ b/man/make_new_ready4use_dataverses.Rd @@ -16,5 +16,5 @@ An unvalidated instance of the ready4 S3 class for tibble object lookup table of Create a new unvalidated instance of the ready4 S3 class for tibble object lookup table of files to be imported from a dataverse. } \details{ -ready4 S3 class for tibble object lookup table of files to be imported from a dataverse. +Tibble object lookup table of files to be imported from a dataverse. } diff --git a/man/make_new_ready4use_dictionary.Rd b/man/make_new_ready4use_dictionary.Rd index c455e49d..e3344511 100644 --- a/man/make_new_ready4use_dictionary.Rd +++ b/man/make_new_ready4use_dictionary.Rd @@ -16,5 +16,5 @@ An unvalidated instance of the ready4 s3 class defining a data dictionary tibble Create a new unvalidated instance of the ready4 s3 class defining a data dictionary tibble. } \details{ -ready4 s3 class defining a data dictionary tibble. +A data dictionary tibble. } diff --git a/man/make_new_ready4use_distributions.Rd b/man/make_new_ready4use_distributions.Rd index 00df2778..3f57259b 100644 --- a/man/make_new_ready4use_distributions.Rd +++ b/man/make_new_ready4use_distributions.Rd @@ -16,5 +16,5 @@ An unvalidated instance of the ready4 S3 class for list object that summarises t Create a new unvalidated instance of the ready4 S3 class for list object that summarises the parameters of each distribution } \details{ -ready4 S3 class for list object that summarises the parameters of each distribution +List object that summarises the parameters of each distribution } diff --git a/man/make_new_ready4use_imports.Rd b/man/make_new_ready4use_imports.Rd index 3ab56349..588e2efc 100644 --- a/man/make_new_ready4use_imports.Rd +++ b/man/make_new_ready4use_imports.Rd @@ -16,5 +16,5 @@ An unvalidated instance of the ready4 S3 class for tibble object lookup table of Create a new unvalidated instance of the ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import. } \details{ -ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import. +Tibble object lookup table of sources of raw (un-processed) data to import. } diff --git a/man/make_new_ready4use_mapes.Rd b/man/make_new_ready4use_mapes.Rd index 451a8a1e..416a3bd0 100644 --- a/man/make_new_ready4use_mapes.Rd +++ b/man/make_new_ready4use_mapes.Rd @@ -16,5 +16,5 @@ An unvalidated instance of the ready4 S3 class for tibble object that stores sim Create a new unvalidated instance of the ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. } \details{ -ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. +Tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. } diff --git a/man/make_pt_ready4use_dataverses.Rd b/man/make_pt_ready4use_dataverses.Rd index 67c327fc..63b923ff 100644 --- a/man/make_pt_ready4use_dataverses.Rd +++ b/man/make_pt_ready4use_dataverses.Rd @@ -36,5 +36,5 @@ A prototype for ready4 S3 class for tibble object lookup table of files to be im Create a new prototype for the ready4 S3 class for tibble object lookup table of files to be imported from a dataverse. } \details{ -ready4 S3 class for tibble object lookup table of files to be imported from a dataverse. +Tibble object lookup table of files to be imported from a dataverse. } diff --git a/man/make_pt_ready4use_dictionary.Rd b/man/make_pt_ready4use_dictionary.Rd index 7d6810ce..af0db484 100644 --- a/man/make_pt_ready4use_dictionary.Rd +++ b/man/make_pt_ready4use_dictionary.Rd @@ -27,5 +27,5 @@ A prototype for ready4 s3 class defining a data dictionary tibble. Create a new prototype for the ready4 s3 class defining a data dictionary tibble. } \details{ -ready4 s3 class defining a data dictionary tibble. +A data dictionary tibble. } diff --git a/man/make_pt_ready4use_distributions.Rd b/man/make_pt_ready4use_distributions.Rd index aafdadfd..9bac35e9 100644 --- a/man/make_pt_ready4use_distributions.Rd +++ b/man/make_pt_ready4use_distributions.Rd @@ -33,5 +33,5 @@ A prototype for ready4 S3 class for list object that summarises the parameters o Create a new prototype for the ready4 S3 class for list object that summarises the parameters of each distribution } \details{ -ready4 S3 class for list object that summarises the parameters of each distribution +List object that summarises the parameters of each distribution } diff --git a/man/make_pt_ready4use_imports.Rd b/man/make_pt_ready4use_imports.Rd index 71618003..8d27fb13 100644 --- a/man/make_pt_ready4use_imports.Rd +++ b/man/make_pt_ready4use_imports.Rd @@ -54,5 +54,5 @@ A prototype for ready4 S3 class for tibble object lookup table of sources of raw Create a new prototype for the ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import. } \details{ -ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import. +Tibble object lookup table of sources of raw (un-processed) data to import. } diff --git a/man/make_pt_ready4use_mapes.Rd b/man/make_pt_ready4use_mapes.Rd index 0c57fe1f..c8698bc4 100644 --- a/man/make_pt_ready4use_mapes.Rd +++ b/man/make_pt_ready4use_mapes.Rd @@ -57,5 +57,5 @@ A prototype for ready4 S3 class for tibble object that stores simulation structu Create a new prototype for the ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. } \details{ -ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. +Tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. } diff --git a/man/ready4use_dataverses.Rd b/man/ready4use_dataverses.Rd index 03ab4bfc..9470fadc 100644 --- a/man/ready4use_dataverses.Rd +++ b/man/ready4use_dataverses.Rd @@ -16,5 +16,5 @@ A validated instance of the ready4 S3 class for tibble object lookup table of fi Create a new valid instance of the ready4 S3 class for tibble object lookup table of files to be imported from a dataverse. } \details{ -ready4 S3 class for tibble object lookup table of files to be imported from a dataverse. +Tibble object lookup table of files to be imported from a dataverse. } diff --git a/man/ready4use_dictionary.Rd b/man/ready4use_dictionary.Rd index 67b906e2..57c45114 100644 --- a/man/ready4use_dictionary.Rd +++ b/man/ready4use_dictionary.Rd @@ -16,5 +16,5 @@ A validated instance of the ready4 s3 class defining a data dictionary tibble. Create a new valid instance of the ready4 s3 class defining a data dictionary tibble. } \details{ -ready4 s3 class defining a data dictionary tibble. +A data dictionary tibble. } diff --git a/man/ready4use_distributions.Rd b/man/ready4use_distributions.Rd index 886e70de..581ed0b9 100644 --- a/man/ready4use_distributions.Rd +++ b/man/ready4use_distributions.Rd @@ -16,5 +16,5 @@ A validated instance of the ready4 S3 class for list object that summarises the Create a new valid instance of the ready4 S3 class for list object that summarises the parameters of each distribution } \details{ -ready4 S3 class for list object that summarises the parameters of each distribution +List object that summarises the parameters of each distribution } diff --git a/man/ready4use_imports.Rd b/man/ready4use_imports.Rd index 1400e686..7aee2d84 100644 --- a/man/ready4use_imports.Rd +++ b/man/ready4use_imports.Rd @@ -16,5 +16,5 @@ A validated instance of the ready4 S3 class for tibble object lookup table of so Create a new valid instance of the ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import. } \details{ -ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import. +Tibble object lookup table of sources of raw (un-processed) data to import. } diff --git a/man/ready4use_mapes.Rd b/man/ready4use_mapes.Rd index a39b062c..73c393b9 100644 --- a/man/ready4use_mapes.Rd +++ b/man/ready4use_mapes.Rd @@ -16,5 +16,5 @@ A validated instance of the ready4 S3 class for tibble object that stores simula Create a new valid instance of the ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. } \details{ -ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. +Tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. } diff --git a/man/validate_ready4use_dataverses.Rd b/man/validate_ready4use_dataverses.Rd index d5cadfe8..687b1b8e 100644 --- a/man/validate_ready4use_dataverses.Rd +++ b/man/validate_ready4use_dataverses.Rd @@ -16,5 +16,5 @@ A prototpe for ready4 S3 class for tibble object lookup table of files to be imp Validate an instance of the ready4 S3 class for tibble object lookup table of files to be imported from a dataverse. } \details{ -ready4 S3 class for tibble object lookup table of files to be imported from a dataverse. +Tibble object lookup table of files to be imported from a dataverse. } diff --git a/man/validate_ready4use_dictionary.Rd b/man/validate_ready4use_dictionary.Rd index 4848e25b..1d0798a6 100644 --- a/man/validate_ready4use_dictionary.Rd +++ b/man/validate_ready4use_dictionary.Rd @@ -16,5 +16,5 @@ A prototpe for ready4 s3 class defining a data dictionary tibble. Validate an instance of the ready4 s3 class defining a data dictionary tibble. } \details{ -ready4 s3 class defining a data dictionary tibble. +A data dictionary tibble. } diff --git a/man/validate_ready4use_distributions.Rd b/man/validate_ready4use_distributions.Rd index 9af27fc8..bca6fd30 100644 --- a/man/validate_ready4use_distributions.Rd +++ b/man/validate_ready4use_distributions.Rd @@ -16,5 +16,5 @@ A prototpe for ready4 S3 class for list object that summarises the parameters of Validate an instance of the ready4 S3 class for list object that summarises the parameters of each distribution } \details{ -ready4 S3 class for list object that summarises the parameters of each distribution +List object that summarises the parameters of each distribution } diff --git a/man/validate_ready4use_imports.Rd b/man/validate_ready4use_imports.Rd index 1ea1e730..2a278b0a 100644 --- a/man/validate_ready4use_imports.Rd +++ b/man/validate_ready4use_imports.Rd @@ -16,5 +16,5 @@ A prototpe for ready4 S3 class for tibble object lookup table of sources of raw Validate an instance of the ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import. } \details{ -ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import. +Tibble object lookup table of sources of raw (un-processed) data to import. } diff --git a/man/validate_ready4use_mapes.Rd b/man/validate_ready4use_mapes.Rd index 41c81f51..3be98878 100644 --- a/man/validate_ready4use_mapes.Rd +++ b/man/validate_ready4use_mapes.Rd @@ -16,5 +16,5 @@ A prototpe for ready4 S3 class for tibble object that stores simulation structur Validate an instance of the ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. } \details{ -ready4 S3 class for tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. +Tibble object that stores simulation structural parameters relating to Mean Absolute Prediction Errors. }