diff --git a/NAMESPACE b/NAMESPACE index 01879020..58de5b90 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -1,6 +1,9 @@ # Generated by roxygen2: do not edit by hand export("%>%") +export("crs_nbr_dbl<-") +export("merge_with_chr_vec<-") +export("save_type<-") export(add_ds_to_dv_repo) export(add_dv_meta_to_imp_lup) export(add_files_to_dv) @@ -11,6 +14,7 @@ export(assert_matches_chr) export(assert_single_row_tb) export(bind_lups) export(bind_lups.ready4_dictionary) +export(crs_nbr_dbl) export(download_data) export(get_data) export(get_data.ready4_dv_import_lup) @@ -44,6 +48,7 @@ export(make_pt_ready4_dist) export(make_pt_ready4_dv_import_lup) export(make_pt_ready4_par_struc_mape) export(make_r3_from_csv_tb) +export(merge_with_chr_vec) export(read_import_from_csv) export(ready4_all_import_lup) export(ready4_dictionary) @@ -52,6 +57,7 @@ export(ready4_dv_import_lup) export(ready4_par_struc_mape) export(remove_labels_from_ds) export(save_raw) +export(save_type) export(transform_csv_col_to_ls_col) export(update_src_loc_to_url) export(update_src_loc_to_url.ready4_all_import_lup) @@ -66,6 +72,7 @@ export(write_dv_ds) export(write_dv_ds_fls) export(write_dv_fl_to_loc) export(write_fls_to_dv_ds) +export(write_paired_ds_fls_to_dv) export(write_pkg_dss_to_dv_ds_csvs) export(write_to_add_urls_to_dss) export(write_to_copy_fls_to_dv_dir) @@ -130,3 +137,4 @@ importFrom(tidyr,gather) importFrom(utils,data) importFrom(utils,getFromNamespace) importFrom(utils,read.csv) +importFrom(utils,write.csv) diff --git a/R/fn_add.R b/R/fn_add.R index b63a08ac..abb0607a 100644 --- a/R/fn_add.R +++ b/R/fn_add.R @@ -139,7 +139,7 @@ add_files_to_dv <- function (files_tb, data_dir_rt_1L_chr = ".", ds_url_1L_chr, #' @description add_labels_from_dictionary() is an Add function that updates an object by adding data to that object. Specifically, this function implements an algorithm to add labels from dictionary. Function argument ds_tb specifies the object to be updated. The function returns Labelled dataset (a tibble). #' @param ds_tb Dataset (a tibble) #' @param dictionary_tb Dictionary (a tibble) -#' @param remove_old_lbls_1L_lgl PARAM_DESCRIPTION, Default: F +#' @param remove_old_lbls_1L_lgl Remove old lbls (a logical vector of length one), Default: F #' @return Labelled dataset (a tibble) #' @rdname add_labels_from_dictionary #' @export @@ -147,7 +147,6 @@ add_files_to_dv <- function (files_tb, data_dir_rt_1L_chr = ".", ds_url_1L_chr, #' @importFrom dplyr filter mutate case_when #' @importFrom purrr reduce #' @importFrom Hmisc label -#' @keywords internal add_labels_from_dictionary <- function (ds_tb, dictionary_tb, remove_old_lbls_1L_lgl = F) { if (remove_old_lbls_1L_lgl) diff --git a/R/fn_get.R b/R/fn_get.R index d71507dd..c96852a3 100644 --- a/R/fn_get.R +++ b/R/fn_get.R @@ -44,7 +44,6 @@ get_file_from_dv <- function (ds_ui_1L_chr, fl_nm_1L_chr, save_fmt_1L_chr, repo_ #' @importFrom purrr map2_chr #' @importFrom ready4fun get_from_lup_obj #' @importFrom tibble as_tibble -#' @keywords internal get_fl_id_from_dv_ls <- function (ds_ls, fl_nm_1L_chr, nms_chr = NA_character_) { if (is.na(nms_chr[1])) { diff --git a/R/fn_read.R b/R/fn_read.R index 2386f379..a28dd846 100644 --- a/R/fn_read.R +++ b/R/fn_read.R @@ -1,7 +1,7 @@ #' Read import from comma separated variables file #' @description read_import_from_csv() is a Read function that reads an R script into memory. Specifically, this function implements an algorithm to read import from comma separated variables file. Function argument file_ref_chr specifies the path to object. The function returns Import (a ready4 S3). #' @param file_ref_chr File reference (a character vector) -#' @param is_url_1L_lgl PARAM_DESCRIPTION, Default: F +#' @param is_url_1L_lgl Is url (a logical vector of length one), Default: F #' @return Import (a ready4 S3) #' @rdname read_import_from_csv #' @export diff --git a/R/fn_transform.R b/R/fn_transform.R index 5276b6e6..645cdee4 100644 --- a/R/fn_transform.R +++ b/R/fn_transform.R @@ -1,6 +1,6 @@ #' Transform comma separated variables file column to list column -#' @description transform_csv_col_to_ls_col() is a Transform function that edits an object in such a way that core object attributes - e.g. shape, dimensions, elements, type - are altered. Specifically, this function implements an algorithm to transform comma separated variables file column to list column. Function argument csv_col specifies the object to be updated. The function returns List column (a list). -#' @param csv_col_xx PARAM_DESCRIPTION +#' @description transform_csv_col_to_ls_col() is a Transform function that edits an object in such a way that core object attributes - e.g. shape, dimensions, elements, type - are altered. Specifically, this function implements an algorithm to transform comma separated variables file column to list column. Function argument csv_col_xx specifies the object to be updated. The function returns List column (a list). +#' @param csv_col_xx Comma separated variables file column (an output object of multiple potential types) #' @return List column (a list) #' @rdname transform_csv_col_to_ls_col #' @export diff --git a/R/fn_update.R b/R/fn_update.R index 4d5154b0..fffc6e8b 100644 --- a/R/fn_update.R +++ b/R/fn_update.R @@ -2,8 +2,8 @@ #' @description update_tb_src_loc_to_url_sgl_tb() is an Update function that edits an object, while preserving core object attributes. Specifically, this function implements an algorithm to update tibble source local to url sgl tibble. Function argument x specifies the object to be updated. Argument y provides the object to be updated. The function returns Updated (a tibble). #' @param x An object #' @param y PARAM_DESCRIPTION -#' @param local_to_url_vec_chr PARAM_DESCRIPTION -#' @param urls_vec_chr PARAM_DESCRIPTION +#' @param local_to_url_vec_chr Local to url vec (a character vector) +#' @param urls_vec_chr Urls vec (a character vector) #' @return Updated (a tibble) #' @rdname update_tb_src_loc_to_url_sgl_tb #' @export diff --git a/R/fn_write.R b/R/fn_write.R index 2eee0326..01900cbd 100644 --- a/R/fn_write.R +++ b/R/fn_write.R @@ -107,7 +107,6 @@ write_dv_fl_to_loc <- function (ds_ui_1L_chr, fl_nm_1L_chr = NA_character_, fl_i #' @importFrom stats setNames #' @importFrom purrr map_int #' @importFrom dataverse get_dataset -#' @keywords internal write_fls_to_dv_ds <- function (dss_tb, dv_nm_1L_chr, ds_url_1L_chr, wait_time_in_secs_int = 5L, make_local_copy_1L_lgl = F, parent_dv_dir_1L_chr, paths_to_dirs_chr, inc_fl_types_chr = NA_character_, key_1L_chr = Sys.getenv("DATAVERSE_KEY"), @@ -138,6 +137,41 @@ write_fls_to_dv_ds <- function (dss_tb, dv_nm_1L_chr, ds_url_1L_chr, wait_time_i } return(ds_ls) } +#' Write paired dataset files to dataverse +#' @description write_paired_ds_fls_to_dv() is a Write function that writes a file to a specified local directory. Specifically, this function implements an algorithm to write paired dataset files to dataverse. The function is called for its side effects and does not return a value. WARNING: This function writes R scripts to your local environment. Make sure to only use if you want this behaviour +#' @param ds_tb Dataset (a tibble) +#' @param fl_nm_1L_chr File name (a character vector of length one) +#' @param desc_1L_chr Description (a character vector of length one) +#' @param ds_url_1L_chr Dataset url (a character vector of length one), Default: 'https://doi.org/10.7910/DVN/2Y9VF9' +#' @param pkg_dv_dir_1L_chr Package dataverse directory (a character vector of length one), Default: 'data-raw/dataverse' +#' @param data_dir_rt_1L_chr Data directory root (a character vector of length one), Default: '.' +#' @param key_1L_chr Key (a character vector of length one), Default: Sys.getenv("DATAVERSE_KEY") +#' @param server_1L_chr Server (a character vector of length one), Default: Sys.getenv("DATAVERSE_SERVER") +#' @return NULL +#' @rdname write_paired_ds_fls_to_dv +#' @export +#' @importFrom utils write.csv +#' @importFrom stats setNames +write_paired_ds_fls_to_dv <- function (ds_tb, fl_nm_1L_chr, desc_1L_chr, ds_url_1L_chr = "https://doi.org/10.7910/DVN/2Y9VF9", + pkg_dv_dir_1L_chr = "data-raw/dataverse", data_dir_rt_1L_chr = ".", + key_1L_chr = Sys.getenv("DATAVERSE_KEY"), server_1L_chr = Sys.getenv("DATAVERSE_SERVER")) +{ + if (!dir.exists(pkg_dv_dir_1L_chr)) + dir.create(pkg_dv_dir_1L_chr) + pkg_dv_dir_1L_chr <- paste0(pkg_dv_dir_1L_chr, "/", fl_nm_1L_chr) + if (!dir.exists(pkg_dv_dir_1L_chr)) + dir.create(pkg_dv_dir_1L_chr) + ds_tb %>% saveRDS(paste0(pkg_dv_dir_1L_chr, "/", fl_nm_1L_chr, + ".RDS")) + readRDS(paste0(pkg_dv_dir_1L_chr, "/", fl_nm_1L_chr, ".RDS")) %>% + utils::write.csv(file = paste0(pkg_dv_dir_1L_chr, "/", + fl_nm_1L_chr, ".csv"), row.names = F) + make_files_tb(paths_to_dirs_chr = pkg_dv_dir_1L_chr, recode_ls = c(rep(desc_1L_chr, + 2)) %>% as.list() %>% stats::setNames(c(rep(fl_nm_1L_chr, + 2)))) %>% add_files_to_dv(data_dir_rt_1L_chr = data_dir_rt_1L_chr, + ds_url_1L_chr = ds_url_1L_chr, key_1L_chr = key_1L_chr, + server_1L_chr = server_1L_chr) +} #' Write package datasets to dataverse dataset comma separated variables files #' @description write_pkg_dss_to_dv_ds_csvs() is a Write function that writes a file to a specified local directory. Specifically, this function implements an algorithm to write package datasets to dataverse dataset comma separated variables files. The function returns Dataset (a list). #' @param pkg_dss_tb Package datasets (a tibble) @@ -156,7 +190,6 @@ write_fls_to_dv_ds <- function (dss_tb, dv_nm_1L_chr, ds_url_1L_chr, wait_time_i #' @importFrom utils data #' @importFrom dplyr mutate_if #' @importFrom stringr str_c -#' @keywords internal write_pkg_dss_to_dv_ds_csvs <- function (pkg_dss_tb, dv_nm_1L_chr, ds_url_1L_chr, wait_time_in_secs_int = 5L, dev_pkg_nm_1L_chr = ready4fun::get_dev_pkg_nm(), parent_dv_dir_1L_chr = "../../../../Data/Dataverse", key_1L_chr = Sys.getenv("DATAVERSE_KEY"), server_1L_chr = Sys.getenv("DATAVERSE_SERVER")) @@ -177,7 +210,7 @@ write_pkg_dss_to_dv_ds_csvs <- function (pkg_dss_tb, dv_nm_1L_chr, ds_url_1L_chr } #' Write to add urls to datasets #' @description write_to_add_urls_to_dss() is a Write function that writes a file to a specified local directory. Specifically, this function implements an algorithm to write to add urls to datasets. The function returns Package datasets (a tibble). -#' @param ds_url_1L_chr PARAM_DESCRIPTION +#' @param ds_url_1L_chr Dataset url (a character vector of length one) #' @param pkg_dss_tb Package datasets (a tibble) #' @param pkg_nm_1L_chr Package name (a character vector of length one), Default: ready4fun::get_dev_pkg_nm() #' @return Package datasets (a tibble) diff --git a/R/gs_crs_nbr_dbl.R b/R/gnrc_crs_nbr_dbl.R similarity index 61% rename from R/gs_crs_nbr_dbl.R rename to R/gnrc_crs_nbr_dbl.R index 99510fe3..995cc40c 100644 --- a/R/gs_crs_nbr_dbl.R +++ b/R/gnrc_crs_nbr_dbl.R @@ -1,4 +1,12 @@ #' crs_nbr_dbl +#' @description S4 Generic function to get the value of the slot crs_nbr_dbl +#' @rdname crs_nbr_dbl-methods +#' @param x An object +#' +#' @export + +methods::setGeneric("crs_nbr_dbl", function(x) standardGeneric("crs_nbr_dbl")) +#' crs_nbr_dbl #' @name crs_nbr_dbl-ready4_script_data #' @description Get the value of the slot crs_nbr_dbl for S4 objects of class ready4_script_data #' @param x An object of class ready4_script_data @@ -9,6 +17,15 @@ methods::setMethod("crs_nbr_dbl", methods::className("ready4_script_data"), func x@crs_nbr_dbl }) #' crs_nbr_dbl<- +#' @description S4 Generic function to set the value of the slot crs_nbr_dbl +#' @rdname crs_nbr_dbl_set-methods +#' @param x An object +#' @param value Value to be assigned to x +#' +#' @export + +methods::setGeneric("crs_nbr_dbl<-", function(x, value) standardGeneric("crs_nbr_dbl<-")) +#' crs_nbr_dbl<- #' @name crs_nbr_dbl<--ready4_script_data #' @description Set the value of the slot crs_nbr_dbl for S4 objects of class ready4_script_data #' @param x An object of class ready4_script_data diff --git a/R/gs_merge_with_chr_vec.R b/R/gnrc_merge_with_chr_vec.R similarity index 59% rename from R/gs_merge_with_chr_vec.R rename to R/gnrc_merge_with_chr_vec.R index ea183b64..5b12ef9e 100644 --- a/R/gs_merge_with_chr_vec.R +++ b/R/gnrc_merge_with_chr_vec.R @@ -1,4 +1,12 @@ #' merge_with_chr_vec +#' @description S4 Generic function to get the value of the slot merge_with_chr_vec +#' @rdname merge_with_chr_vec-methods +#' @param x An object +#' +#' @export + +methods::setGeneric("merge_with_chr_vec", function(x) standardGeneric("merge_with_chr_vec")) +#' merge_with_chr_vec #' @name merge_with_chr_vec-ready4_local #' @description Get the value of the slot merge_with_chr_vec for S4 objects of class ready4_local #' @param x An object of class ready4_local @@ -9,6 +17,15 @@ methods::setMethod("merge_with_chr_vec", methods::className("ready4_local"), fun x@merge_with_chr_vec }) #' merge_with_chr_vec<- +#' @description S4 Generic function to set the value of the slot merge_with_chr_vec +#' @rdname merge_with_chr_vec_set-methods +#' @param x An object +#' @param value Value to be assigned to x +#' +#' @export + +methods::setGeneric("merge_with_chr_vec<-", function(x, value) standardGeneric("merge_with_chr_vec<-")) +#' merge_with_chr_vec<- #' @name merge_with_chr_vec<--ready4_local #' @description Set the value of the slot merge_with_chr_vec for S4 objects of class ready4_local #' @param x An object of class ready4_local diff --git a/R/gs_save_type.R b/R/gnrc_save_type.R similarity index 75% rename from R/gs_save_type.R rename to R/gnrc_save_type.R index 473bece1..f3b4bba8 100644 --- a/R/gs_save_type.R +++ b/R/gnrc_save_type.R @@ -1,4 +1,12 @@ #' save_type +#' @description S4 Generic function to get the value of the slot save_type +#' @rdname save_type-methods +#' @param x An object +#' +#' @export + +methods::setGeneric("save_type", function(x) standardGeneric("save_type")) +#' save_type #' @name save_type-ready4_local_raw #' @description Get the value of the slot save_type for S4 objects of class ready4_local_raw #' @param x An object of class ready4_local_raw @@ -9,6 +17,15 @@ methods::setMethod("save_type", methods::className("ready4_local_raw"), function x@save_type }) #' save_type<- +#' @description S4 Generic function to set the value of the slot save_type +#' @rdname save_type_set-methods +#' @param x An object +#' @param value Value to be assigned to x +#' +#' @export + +methods::setGeneric("save_type<-", function(x, value) standardGeneric("save_type<-")) +#' save_type<- #' @name save_type<--ready4_local_raw #' @description Set the value of the slot save_type for S4 objects of class ready4_local_raw #' @param x An object of class ready4_local_raw diff --git a/R/grp_generics.R b/R/grp_generics.R index b7eed88b..caa07a39 100644 --- a/R/grp_generics.R +++ b/R/grp_generics.R @@ -1,6 +1,6 @@ -#' Bind lookup tables +#' Bind lups #' @rdname bind_lups-methods -#' @description bind_lups() is a Bind Lookup Tables generic that rowbinds lookup tables of the same class, removing duplicates based on priority. +#' @description bind_lups() is a Bind Lups generic that rowbinds lookup tables of the same class, removing duplicates based on priority. #' @param x An object #' @param ... Additional arguments #' @export @@ -110,8 +110,8 @@ methods::setGeneric("save_raw") #' @rdname update_src_loc_to_url-methods #' @description update_src_loc_to_url() is an Update Source Local to Url generic that updates data from a local file reference to a URL #' @param x An object -#' @param local_to_url_vec_chr PARAM_DESCRIPTION -#' @param urls_vec_chr PARAM_DESCRIPTION +#' @param local_to_url_vec_chr Local to url vec (a character vector) +#' @param urls_vec_chr Urls vec (a character vector) #' @param ... Additional arguments #' @export diff --git a/R/mthd_bind_lups.R b/R/mthd_bind_lups.R index 4fe49229..b554cd95 100644 --- a/R/mthd_bind_lups.R +++ b/R/mthd_bind_lups.R @@ -1,7 +1,7 @@ -#' Bind lookup tables method applied to ready4 S3 class defining a data dictionary tibble.. -#' @description bind_lups.ready4_dictionary() is a Bind Lookup Tables method that rowbinds lookup tables of the same class, removing duplicates based on priority. This method is implemented for the ready4 s3 class defining a data dictionary tibble.. The function is called for its side effects and does not return a value. +#' Bind lups method applied to ready4 S3 class defining a data dictionary tibble.. +#' @description bind_lups.ready4_dictionary() is a Bind Lups method that rowbinds lookup tables of the same class, removing duplicates based on priority. This method is implemented for the ready4 s3 class defining a data dictionary tibble.. The function is called for its side effects and does not return a value. #' @param x An instance of ready4 s3 class defining a data dictionary tibble. -#' @param new_ready4_dict_r3 PARAM_DESCRIPTION +#' @param new_ready4_dict_r3 New ready4 dict (a ready4 S3) #' @return NA () #' @rdname bind_lups-methods #' @export diff --git a/R/mthd_update_src_loc_to_url.R b/R/mthd_update_src_loc_to_url.R index 58b214ac..ee79db91 100644 --- a/R/mthd_update_src_loc_to_url.R +++ b/R/mthd_update_src_loc_to_url.R @@ -1,8 +1,8 @@ #' Update source local to url method applied to ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import.. #' @description update_src_loc_to_url.ready4_all_import_lup() is an Update Source Local to Url method that updates data from a local file reference to a URL This method is implemented for the ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import.. The function is called for its side effects and does not return a value. #' @param x An instance of ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import. -#' @param local_to_url_vec_chr PARAM_DESCRIPTION -#' @param urls_vec_chr PARAM_DESCRIPTION +#' @param local_to_url_vec_chr Local to url vec (a character vector) +#' @param urls_vec_chr Urls vec (a character vector) #' @return NULL #' @rdname update_src_loc_to_url-methods #' @export diff --git a/_pkgdown.yml b/_pkgdown.yml index 495eb444..612ebf6a 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -26,10 +26,15 @@ reference: - ready4_script_data - title: "Functions" - contents: + - add_labels_from_dictionary - assert_matches_chr - assert_single_row_tb + - get_fl_id_from_dv_ls - get_local_path_to_dv_data - get_r3_from_dv_csv + - write_fls_to_dv_ds + - write_paired_ds_fls_to_dv + - write_pkg_dss_to_dv_ds_csvs - title: "Generics" - contents: - bind_lups diff --git a/data-raw/DATASET.R b/data-raw/DATASET.R index f9b8afa0..3eb5ded2 100644 --- a/data-raw/DATASET.R +++ b/data-raw/DATASET.R @@ -79,8 +79,8 @@ ready4fun::write_and_doc_ds(db_1L_chr = "prototype_lup", pkg_dss_tb = pkg_dss_tb) # # 10. Create a table of all functions to document -fns_dmt_tb <- ready4fun::make_dmt_for_all_fns(paths_ls = make_fn_nms(), - undocumented_fns_dir_chr = make_undmtd_fns_dir_chr(), +fns_dmt_tb <- ready4fun::make_dmt_for_all_fns(paths_ls = ready4fun::make_fn_nms(), + undocumented_fns_dir_chr = ready4fun::make_undmtd_fns_dir_chr(), custom_dmt_ls = list(details_ls = NULL, inc_for_main_user_lgl_ls = list(force_true_chr = c("add_labels_from_dictionary", "assert_matches_chr", diff --git a/data/fns_dmt_tb.rda b/data/fns_dmt_tb.rda index 9479f8c8..e94e481d 100644 Binary files a/data/fns_dmt_tb.rda and b/data/fns_dmt_tb.rda differ diff --git a/man/add_labels_from_dictionary.Rd b/man/add_labels_from_dictionary.Rd index 27b41b8a..0526a187 100644 --- a/man/add_labels_from_dictionary.Rd +++ b/man/add_labels_from_dictionary.Rd @@ -11,7 +11,7 @@ add_labels_from_dictionary(ds_tb, dictionary_tb, remove_old_lbls_1L_lgl = F) \item{dictionary_tb}{Dictionary (a tibble)} -\item{remove_old_lbls_1L_lgl}{PARAM_DESCRIPTION, Default: F} +\item{remove_old_lbls_1L_lgl}{Remove old lbls (a logical vector of length one), Default: F} } \value{ Labelled dataset (a tibble) @@ -19,4 +19,3 @@ Labelled dataset (a tibble) \description{ add_labels_from_dictionary() is an Add function that updates an object by adding data to that object. Specifically, this function implements an algorithm to add labels from dictionary. Function argument ds_tb specifies the object to be updated. The function returns Labelled dataset (a tibble). } -\keyword{internal} diff --git a/man/bind_lups-methods.Rd b/man/bind_lups-methods.Rd index b9bb975f..b8cdf2a9 100644 --- a/man/bind_lups-methods.Rd +++ b/man/bind_lups-methods.Rd @@ -4,7 +4,7 @@ \alias{bind_lups} \alias{bind_lups.ready4_dictionary} \alias{bind_lups,ready4_dictionary-method} -\title{Bind lookup tables} +\title{Bind lups} \usage{ bind_lups(x, ...) @@ -17,13 +17,13 @@ bind_lups.ready4_dictionary(x, new_ready4_dict_r3) \item{...}{Additional arguments} -\item{new_ready4_dict_r3}{PARAM_DESCRIPTION} +\item{new_ready4_dict_r3}{New ready4 dict (a ready4 S3)} } \value{ NA () } \description{ -bind_lups() is a Bind Lookup Tables generic that rowbinds lookup tables of the same class, removing duplicates based on priority. +bind_lups() is a Bind Lups generic that rowbinds lookup tables of the same class, removing duplicates based on priority. -bind_lups.ready4_dictionary() is a Bind Lookup Tables method that rowbinds lookup tables of the same class, removing duplicates based on priority. This method is implemented for the ready4 s3 class defining a data dictionary tibble.. The function is called for its side effects and does not return a value. +bind_lups.ready4_dictionary() is a Bind Lups method that rowbinds lookup tables of the same class, removing duplicates based on priority. This method is implemented for the ready4 s3 class defining a data dictionary tibble.. The function is called for its side effects and does not return a value. } diff --git a/man/crs_nbr_dbl-methods.Rd b/man/crs_nbr_dbl-methods.Rd index d770db19..96e6db4b 100644 --- a/man/crs_nbr_dbl-methods.Rd +++ b/man/crs_nbr_dbl-methods.Rd @@ -1,15 +1,20 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/gs_crs_nbr_dbl.R -\name{crs_nbr_dbl-ready4_script_data} +% Please edit documentation in R/gnrc_crs_nbr_dbl.R +\name{crs_nbr_dbl} +\alias{crs_nbr_dbl} \alias{crs_nbr_dbl-ready4_script_data} \alias{crs_nbr_dbl,ready4_script_data-method} \title{crs_nbr_dbl} \usage{ +crs_nbr_dbl(x) + \S4method{crs_nbr_dbl}{ready4_script_data}(x) } \arguments{ \item{x}{An object of class ready4_script_data} } \description{ +S4 Generic function to get the value of the slot crs_nbr_dbl + Get the value of the slot crs_nbr_dbl for S4 objects of class ready4_script_data } diff --git a/man/crs_nbr_dbl_set-methods.Rd b/man/crs_nbr_dbl_set-methods.Rd index 9b4e9170..7f2b1d40 100644 --- a/man/crs_nbr_dbl_set-methods.Rd +++ b/man/crs_nbr_dbl_set-methods.Rd @@ -1,15 +1,22 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/gs_crs_nbr_dbl.R -\name{crs_nbr_dbl<--ready4_script_data} +% Please edit documentation in R/gnrc_crs_nbr_dbl.R +\name{crs_nbr_dbl<-} +\alias{crs_nbr_dbl<-} \alias{crs_nbr_dbl<--ready4_script_data} \alias{crs_nbr_dbl<-,ready4_script_data-method} \title{crs_nbr_dbl<-} \usage{ +crs_nbr_dbl(x) <- value + \S4method{crs_nbr_dbl}{ready4_script_data}(x) <- value } \arguments{ \item{x}{An object of class ready4_script_data} + +\item{value}{Value to be assigned to x} } \description{ +S4 Generic function to set the value of the slot crs_nbr_dbl + Set the value of the slot crs_nbr_dbl for S4 objects of class ready4_script_data } diff --git a/man/fns_dmt_tb.Rd b/man/fns_dmt_tb.Rd index 89d48426..b6284671 100644 --- a/man/fns_dmt_tb.Rd +++ b/man/fns_dmt_tb.Rd @@ -5,7 +5,7 @@ \alias{fns_dmt_tb} \title{ready4use function documentation table} \format{ -An object of class \code{tbl_df} (inherits from \code{tbl}, \code{data.frame}) with 43 rows and 10 columns. +An object of class \code{tbl_df} (inherits from \code{tbl}, \code{data.frame}) with 44 rows and 10 columns. } \source{ \url{https://ready4-dev.github.io/ready4/} diff --git a/man/get_fl_id_from_dv_ls.Rd b/man/get_fl_id_from_dv_ls.Rd index a1545d2f..6143ffa3 100644 --- a/man/get_fl_id_from_dv_ls.Rd +++ b/man/get_fl_id_from_dv_ls.Rd @@ -19,4 +19,3 @@ Id (a character vector of length one) \description{ get_fl_id_from_dv_ls() is a Get function that retrieves a pre-existing data object from memory, local file system or online repository. Specifically, this function implements an algorithm to get file id from dataverse list. Function argument ds_ls specifies the where to look for the required object. The function returns Id (a character vector of length one). } -\keyword{internal} diff --git a/man/merge_with_chr_vec-methods.Rd b/man/merge_with_chr_vec-methods.Rd index 07944b1a..6d94e44b 100644 --- a/man/merge_with_chr_vec-methods.Rd +++ b/man/merge_with_chr_vec-methods.Rd @@ -1,15 +1,20 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/gs_merge_with_chr_vec.R -\name{merge_with_chr_vec-ready4_local} +% Please edit documentation in R/gnrc_merge_with_chr_vec.R +\name{merge_with_chr_vec} +\alias{merge_with_chr_vec} \alias{merge_with_chr_vec-ready4_local} \alias{merge_with_chr_vec,ready4_local-method} \title{merge_with_chr_vec} \usage{ +merge_with_chr_vec(x) + \S4method{merge_with_chr_vec}{ready4_local}(x) } \arguments{ \item{x}{An object of class ready4_local} } \description{ +S4 Generic function to get the value of the slot merge_with_chr_vec + Get the value of the slot merge_with_chr_vec for S4 objects of class ready4_local } diff --git a/man/merge_with_chr_vec_set-methods.Rd b/man/merge_with_chr_vec_set-methods.Rd index 1f480b4f..4967b7c5 100644 --- a/man/merge_with_chr_vec_set-methods.Rd +++ b/man/merge_with_chr_vec_set-methods.Rd @@ -1,15 +1,22 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/gs_merge_with_chr_vec.R -\name{merge_with_chr_vec<--ready4_local} +% Please edit documentation in R/gnrc_merge_with_chr_vec.R +\name{merge_with_chr_vec<-} +\alias{merge_with_chr_vec<-} \alias{merge_with_chr_vec<--ready4_local} \alias{merge_with_chr_vec<-,ready4_local-method} \title{merge_with_chr_vec<-} \usage{ +merge_with_chr_vec(x) <- value + \S4method{merge_with_chr_vec}{ready4_local}(x) <- value } \arguments{ \item{x}{An object of class ready4_local} + +\item{value}{Value to be assigned to x} } \description{ +S4 Generic function to set the value of the slot merge_with_chr_vec + Set the value of the slot merge_with_chr_vec for S4 objects of class ready4_local } diff --git a/man/read_import_from_csv.Rd b/man/read_import_from_csv.Rd index 560ec766..13491964 100644 --- a/man/read_import_from_csv.Rd +++ b/man/read_import_from_csv.Rd @@ -9,7 +9,7 @@ read_import_from_csv(file_ref_chr, is_url_1L_lgl = F) \arguments{ \item{file_ref_chr}{File reference (a character vector)} -\item{is_url_1L_lgl}{PARAM_DESCRIPTION, Default: F} +\item{is_url_1L_lgl}{Is url (a logical vector of length one), Default: F} } \value{ Import (a ready4 S3) diff --git a/man/save_type-methods.Rd b/man/save_type-methods.Rd index 24798493..cf8f319b 100644 --- a/man/save_type-methods.Rd +++ b/man/save_type-methods.Rd @@ -1,12 +1,15 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/gs_save_type.R -\name{save_type-ready4_local_raw} +% Please edit documentation in R/gnrc_save_type.R +\name{save_type} +\alias{save_type} \alias{save_type-ready4_local_raw} \alias{save_type,ready4_local_raw-method} \alias{save_type-ready4_local_proc} \alias{save_type,ready4_local_proc-method} \title{save_type} \usage{ +save_type(x) + \S4method{save_type}{ready4_local_raw}(x) \S4method{save_type}{ready4_local_proc}(x) @@ -15,6 +18,8 @@ \item{x}{An object of class ready4_local_proc} } \description{ +S4 Generic function to get the value of the slot save_type + Get the value of the slot save_type for S4 objects of class ready4_local_raw Get the value of the slot save_type for S4 objects of class ready4_local_proc diff --git a/man/save_type_set-methods.Rd b/man/save_type_set-methods.Rd index b7d92c62..edd2be40 100644 --- a/man/save_type_set-methods.Rd +++ b/man/save_type_set-methods.Rd @@ -1,20 +1,27 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/gs_save_type.R -\name{save_type<--ready4_local_raw} +% Please edit documentation in R/gnrc_save_type.R +\name{save_type<-} +\alias{save_type<-} \alias{save_type<--ready4_local_raw} \alias{save_type<-,ready4_local_raw-method} \alias{save_type<--ready4_local_proc} \alias{save_type<-,ready4_local_proc-method} \title{save_type<-} \usage{ +save_type(x) <- value + \S4method{save_type}{ready4_local_raw}(x) <- value \S4method{save_type}{ready4_local_proc}(x) <- value } \arguments{ \item{x}{An object of class ready4_local_proc} + +\item{value}{Value to be assigned to x} } \description{ +S4 Generic function to set the value of the slot save_type + Set the value of the slot save_type for S4 objects of class ready4_local_raw Set the value of the slot save_type for S4 objects of class ready4_local_proc diff --git a/man/transform_csv_col_to_ls_col.Rd b/man/transform_csv_col_to_ls_col.Rd index da8779b6..e8869a89 100644 --- a/man/transform_csv_col_to_ls_col.Rd +++ b/man/transform_csv_col_to_ls_col.Rd @@ -7,12 +7,12 @@ transform_csv_col_to_ls_col(csv_col_xx) } \arguments{ -\item{csv_col_xx}{PARAM_DESCRIPTION} +\item{csv_col_xx}{Comma separated variables file column (an output object of multiple potential types)} } \value{ List column (a list) } \description{ -transform_csv_col_to_ls_col() is a Transform function that edits an object in such a way that core object attributes - e.g. shape, dimensions, elements, type - are altered. Specifically, this function implements an algorithm to transform comma separated variables file column to list column. Function argument csv_col specifies the object to be updated. The function returns List column (a list). +transform_csv_col_to_ls_col() is a Transform function that edits an object in such a way that core object attributes - e.g. shape, dimensions, elements, type - are altered. Specifically, this function implements an algorithm to transform comma separated variables file column to list column. Function argument csv_col_xx specifies the object to be updated. The function returns List column (a list). } \keyword{internal} diff --git a/man/update_src_loc_to_url-methods.Rd b/man/update_src_loc_to_url-methods.Rd index 50eb2142..67052e2f 100644 --- a/man/update_src_loc_to_url-methods.Rd +++ b/man/update_src_loc_to_url-methods.Rd @@ -19,9 +19,9 @@ update_src_loc_to_url.ready4_all_import_lup( \arguments{ \item{x}{An instance of ready4 S3 class for tibble object lookup table of sources of raw (un-processed) data to import.} -\item{local_to_url_vec_chr}{PARAM_DESCRIPTION} +\item{local_to_url_vec_chr}{Local to url vec (a character vector)} -\item{urls_vec_chr}{PARAM_DESCRIPTION} +\item{urls_vec_chr}{Urls vec (a character vector)} \item{...}{Additional arguments} } diff --git a/man/update_tb_src_loc_to_url_sgl_tb.Rd b/man/update_tb_src_loc_to_url_sgl_tb.Rd index 32de96b5..6868efd3 100644 --- a/man/update_tb_src_loc_to_url_sgl_tb.Rd +++ b/man/update_tb_src_loc_to_url_sgl_tb.Rd @@ -11,9 +11,9 @@ update_tb_src_loc_to_url_sgl_tb(x, y, local_to_url_vec_chr, urls_vec_chr) \item{y}{PARAM_DESCRIPTION} -\item{local_to_url_vec_chr}{PARAM_DESCRIPTION} +\item{local_to_url_vec_chr}{Local to url vec (a character vector)} -\item{urls_vec_chr}{PARAM_DESCRIPTION} +\item{urls_vec_chr}{Urls vec (a character vector)} } \value{ Updated (a tibble) diff --git a/man/write_fls_to_dv_ds.Rd b/man/write_fls_to_dv_ds.Rd index 0a89ff04..f438be8e 100644 --- a/man/write_fls_to_dv_ds.Rd +++ b/man/write_fls_to_dv_ds.Rd @@ -44,4 +44,3 @@ Dataset (a list) \description{ write_fls_to_dv_ds() is a Write function that writes a file to a specified local directory. Specifically, this function implements an algorithm to write files to dataverse dataset. The function returns Dataset (a list). } -\keyword{internal} diff --git a/man/write_paired_ds_fls_to_dv.Rd b/man/write_paired_ds_fls_to_dv.Rd new file mode 100644 index 00000000..99f39e7b --- /dev/null +++ b/man/write_paired_ds_fls_to_dv.Rd @@ -0,0 +1,37 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/fn_write.R +\name{write_paired_ds_fls_to_dv} +\alias{write_paired_ds_fls_to_dv} +\title{Write paired dataset files to dataverse} +\usage{ +write_paired_ds_fls_to_dv( + ds_tb, + fl_nm_1L_chr, + desc_1L_chr, + ds_url_1L_chr = "https://doi.org/10.7910/DVN/2Y9VF9", + pkg_dv_dir_1L_chr = "data-raw/dataverse", + data_dir_rt_1L_chr = ".", + key_1L_chr = Sys.getenv("DATAVERSE_KEY"), + server_1L_chr = Sys.getenv("DATAVERSE_SERVER") +) +} +\arguments{ +\item{ds_tb}{Dataset (a tibble)} + +\item{fl_nm_1L_chr}{File name (a character vector of length one)} + +\item{desc_1L_chr}{Description (a character vector of length one)} + +\item{ds_url_1L_chr}{Dataset url (a character vector of length one), Default: 'https://doi.org/10.7910/DVN/2Y9VF9'} + +\item{pkg_dv_dir_1L_chr}{Package dataverse directory (a character vector of length one), Default: 'data-raw/dataverse'} + +\item{data_dir_rt_1L_chr}{Data directory root (a character vector of length one), Default: '.'} + +\item{key_1L_chr}{Key (a character vector of length one), Default: Sys.getenv("DATAVERSE_KEY")} + +\item{server_1L_chr}{Server (a character vector of length one), Default: Sys.getenv("DATAVERSE_SERVER")} +} +\description{ +write_paired_ds_fls_to_dv() is a Write function that writes a file to a specified local directory. Specifically, this function implements an algorithm to write paired dataset files to dataverse. The function is called for its side effects and does not return a value. WARNING: This function writes R scripts to your local environment. Make sure to only use if you want this behaviour +} diff --git a/man/write_pkg_dss_to_dv_ds_csvs.Rd b/man/write_pkg_dss_to_dv_ds_csvs.Rd index a4a917d3..d452a5de 100644 --- a/man/write_pkg_dss_to_dv_ds_csvs.Rd +++ b/man/write_pkg_dss_to_dv_ds_csvs.Rd @@ -38,4 +38,3 @@ Dataset (a list) \description{ write_pkg_dss_to_dv_ds_csvs() is a Write function that writes a file to a specified local directory. Specifically, this function implements an algorithm to write package datasets to dataverse dataset comma separated variables files. The function returns Dataset (a list). } -\keyword{internal} diff --git a/man/write_to_add_urls_to_dss.Rd b/man/write_to_add_urls_to_dss.Rd index 0d99fc04..db416bf6 100644 --- a/man/write_to_add_urls_to_dss.Rd +++ b/man/write_to_add_urls_to_dss.Rd @@ -11,7 +11,7 @@ write_to_add_urls_to_dss( ) } \arguments{ -\item{ds_url_1L_chr}{PARAM_DESCRIPTION} +\item{ds_url_1L_chr}{Dataset url (a character vector of length one)} \item{pkg_dss_tb}{Package datasets (a tibble)} diff --git a/pkgdown/favicon/apple-touch-icon-120x120.png b/pkgdown/favicon/apple-touch-icon-120x120.png index 600e2844..8dab57b7 100644 Binary files a/pkgdown/favicon/apple-touch-icon-120x120.png and b/pkgdown/favicon/apple-touch-icon-120x120.png differ diff --git a/pkgdown/favicon/apple-touch-icon-152x152.png b/pkgdown/favicon/apple-touch-icon-152x152.png index c944448c..d188f409 100644 Binary files a/pkgdown/favicon/apple-touch-icon-152x152.png and b/pkgdown/favicon/apple-touch-icon-152x152.png differ diff --git a/pkgdown/favicon/apple-touch-icon-180x180.png b/pkgdown/favicon/apple-touch-icon-180x180.png index e5205dc1..42d5eab1 100644 Binary files a/pkgdown/favicon/apple-touch-icon-180x180.png and b/pkgdown/favicon/apple-touch-icon-180x180.png differ diff --git a/pkgdown/favicon/apple-touch-icon-60x60.png b/pkgdown/favicon/apple-touch-icon-60x60.png index 14771b67..94529149 100644 Binary files a/pkgdown/favicon/apple-touch-icon-60x60.png and b/pkgdown/favicon/apple-touch-icon-60x60.png differ diff --git a/pkgdown/favicon/apple-touch-icon-76x76.png b/pkgdown/favicon/apple-touch-icon-76x76.png index 05c3701c..75c2f18e 100644 Binary files a/pkgdown/favicon/apple-touch-icon-76x76.png and b/pkgdown/favicon/apple-touch-icon-76x76.png differ diff --git a/pkgdown/favicon/apple-touch-icon.png b/pkgdown/favicon/apple-touch-icon.png index 35c3f289..42d5eab1 100644 Binary files a/pkgdown/favicon/apple-touch-icon.png and b/pkgdown/favicon/apple-touch-icon.png differ diff --git a/pkgdown/favicon/favicon-16x16.png b/pkgdown/favicon/favicon-16x16.png index ba8d0add..ad7d6255 100644 Binary files a/pkgdown/favicon/favicon-16x16.png and b/pkgdown/favicon/favicon-16x16.png differ diff --git a/pkgdown/favicon/favicon-32x32.png b/pkgdown/favicon/favicon-32x32.png index 8b09a0e2..b345f50c 100644 Binary files a/pkgdown/favicon/favicon-32x32.png and b/pkgdown/favicon/favicon-32x32.png differ