diff --git a/NAMESPACE b/NAMESPACE index 07e1b10b..49e076c7 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -36,6 +36,5 @@ importFrom(ggplot2,margin) importFrom(ggplot2,rel) importFrom(ggplot2,unit) importFrom(lifecycle,deprecated) -importFrom(tibble,tibble) importFrom(utils,download.file) importFrom(utils,read.csv2) diff --git a/NEWS.md b/NEWS.md index f419022a..d5061f58 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,7 +1,12 @@ # tidyBdE (development version) +Mostly changes on the color functions: + - `bde_vivid_pal()` and `bde_rose_pal()` have been deprecated. Use the new -function `bde_palettes()` instead. + function `bde_palettes()` instead. +- `scale_color_bde_d()` and friends leverage now on `bde_palettes()`, and + these functions gain two new arguments: `alpha` y `rev`. +- Update and review documentation. # tidyBdE 0.3.4 diff --git a/R/bde_check_access.R b/R/bde_check_access.R index 865718f8..b1c3592c 100644 --- a/R/bde_check_access.R +++ b/R/bde_check_access.R @@ -1,6 +1,5 @@ #' Check access to BdE #' -#' #' @description #' Check if R has access to resources at #' . diff --git a/R/catalogs.R b/R/catalogs.R index cb07583a..a57c09f6 100644 --- a/R/catalogs.R +++ b/R/catalogs.R @@ -1,14 +1,15 @@ #' Load BdE catalogs #' +#' @description #' Load the time-series catalogs provided by BdE. +#' #' @export #' #' @family catalog #' #' @encoding UTF-8 #' -#' @return A `tibble`. -#' +#' @return A [tibble][tibble::tibble]. #' #' @source #' [Time-series bulk data @@ -25,7 +26,6 @@ #' #' @inheritParams bde_catalog_update #' -#' #' @details #' Accepted values for `catalog` are: #' @@ -45,10 +45,7 @@ #' "**") #' #' knitr::kable(t) -#' -#' #' ``` -#' #' Use `"ALL"` as a shorthand for updating all the catalogs at a glance. #' #' If the requested catalog is not cached [bde_catalog_update()] is invoked. @@ -57,148 +54,135 @@ #' \donttest{ #' bde_catalog_load("TI", verbose = TRUE) #' } -bde_catalog_load <- - function(catalog = c("ALL", "BE", "SI", "TC", "TI", "PB"), - parse_dates = TRUE, - cache_dir = NULL, - update_cache = FALSE, - verbose = FALSE) { - catalog <- match.arg(catalog) - # Validate - valid_catalogs <- - c("BE", "SI", "TC", "TI", "PB", "ALL") - stopifnot( - catalog %in% valid_catalogs, - length(catalog) == 1, - is.null(cache_dir) || is.character(cache_dir), - is.logical(verbose), - is.logical(parse_dates), - is.logical(update_cache) - ) - - if (catalog == "ALL") { - catalog_to_load <- setdiff(valid_catalogs, "ALL") +bde_catalog_load <- function(catalog = c("ALL", "BE", "SI", "TC", "TI", "PB"), + parse_dates = TRUE, cache_dir = NULL, + update_cache = FALSE, verbose = FALSE) { + catalog <- match.arg(catalog) + # Validate + valid_catalogs <- c("BE", "SI", "TC", "TI", "PB", "ALL") + stopifnot( + catalog %in% valid_catalogs, length(catalog) == 1, + any(is.null(cache_dir), is.character(cache_dir)), + is.logical(verbose), is.logical(parse_dates), + is.logical(update_cache) + ) + + + catalog_to_load <- catalog + if (catalog == "ALL") catalog_to_load <- setdiff(valid_catalogs, "ALL") + + # Get cache dir + cache_dir <- bde_hlp_cachedir(cache_dir = cache_dir, verbose = verbose) + + final_catalog <- lapply(catalog_to_load, function(x) { + catalog_file <- paste0("catalogo_", tolower(x), ".csv") + catalog_file <- file.path(cache_dir, catalog_file) + has_cache <- file.exists(catalog_file) + + if (all(has_cache, isFALSE(update_cache))) { + if (verbose) message("tidyBdE> Cached version of ", x, " detected") } else { - catalog_to_load <- catalog - } + # If no catalog is found or requested, update + if (verbose) message("tidyBdE> Need to download catalog ", x) + + result <- bde_catalog_update( + catalog = x, cache_dir = cache_dir, + verbose = verbose + ) - # Get cache dir - cache_dir <- - bde_hlp_cachedir(cache_dir = cache_dir, verbose = verbose) - - final_catalog <- lapply(catalog_to_load, function(x) { - catalog_file <- paste0("catalogo_", tolower(x), ".csv") - catalog_file <- file.path(cache_dir, catalog_file) - has_cache <- file.exists(catalog_file) - - if (all(has_cache, isFALSE(update_cache))) { - if (verbose) message("tidyBdE> Cached version of ", x, " detected") - } else { - # If no catalog is found or requested, update - if (verbose) message("tidyBdE> Need to download catalog ", x) - - result <- bde_catalog_update( - catalog = x, - cache_dir = cache_dir, - verbose = verbose - ) - - # On error return NULL - if (is.data.frame(result) || isFALSE(result)) { - message("Download not available for ", x) - return(NULL) - } + # On error return NULL + if (any(is.data.frame(result), isFALSE(result))) { + message("Download not available for ", x) + return(NULL) } + } - # Catch error - # nocov start - r <- readLines(catalog_file) - if (length(r) == 0) { - message("File ", catalog_file, " not valid") - return(invisible()) - } - # nocov end - - catalog_load <- - read.csv2( - catalog_file, - sep = ",", - stringsAsFactors = FALSE, - na.strings = "", - header = FALSE - ) - - # Convert names - # Hard-coded, problematic on checks because UTF-8 values - # Some OS would fail if this workaround is not used - names_catalog <- c( - "Nombre_de_la_serie", - "Numero_secuencial", - "Alias_de_la_serie", - "Nombre_del_archivo_con_los_valores_de_la_serie", - "Descripcion_de_la_serie", - "Tipo_de_variable", - "Codigo_de_unidades", - "Exponente", - "Numero_de_decimales", - "Descripcion_de_unidades_y_exponente", - "Frecuencia_de_la_serie", - "Fecha_de_la_primera_observacion", - "Fecha_de_la_ultima_observacion", - "Numero_de_observaciones", - "Titulo_de_la_serie", - "Fuente", - "Notas" - ) + # Catch error + # nocov start + r <- readLines(catalog_file) + if (length(r) == 0) { + message("File ", catalog_file, " not valid") + return(invisible()) + } + # nocov end - # Rename and delete first row - names(catalog_load) <- names_catalog - catalog_load <- catalog_load[-1, ] + catalog_load <- read.csv2(catalog_file, + sep = ",", + stringsAsFactors = FALSE, na.strings = "", + header = FALSE + ) - catalog_load <- bde_hlp_tochar(catalog_load) - return(catalog_load) - }) + # Convert names + # Hard-coded, problematic on checks because UTF-8 values + # Some OS would fail if this workaround is not used + names_catalog <- c( + "Nombre_de_la_serie", + "Numero_secuencial", + "Alias_de_la_serie", + "Nombre_del_archivo_con_los_valores_de_la_serie", + "Descripcion_de_la_serie", + "Tipo_de_variable", + "Codigo_de_unidades", + "Exponente", + "Numero_de_decimales", + "Descripcion_de_unidades_y_exponente", + "Frecuencia_de_la_serie", + "Fecha_de_la_primera_observacion", + "Fecha_de_la_ultima_observacion", + "Numero_de_observaciones", + "Titulo_de_la_serie", + "Fuente", + "Notas" + ) - res_all <- unlist(lapply(final_catalog, is.null)) + # Rename and delete first row + names(catalog_load) <- names_catalog + catalog_load <- catalog_load[-1, ] - if (any(res_all)) { - msg <- paste0(catalog_to_load[res_all], collapse = ", ") - message("tidyBdE> Could not load catalogs: ", msg) - } + catalog_load <- bde_hlp_tochar(catalog_load) + return(catalog_load) + }) - # Guess formats + res_all <- unlist(lapply(final_catalog, is.null)) - # Unlist - final_catalog <- dplyr::bind_rows(final_catalog) - final_catalog <- - bde_hlp_guess(final_catalog, preserve = names(final_catalog)[c(5, 15)]) + if (any(res_all)) { + msg <- paste0(catalog_to_load[res_all], collapse = ", ") + message("tidyBdE> Could not load catalogs: ", msg) + } + # Guess formats - # To tibble - final_catalog <- tibble::as_tibble(final_catalog) + # Unlist + final_catalog <- dplyr::bind_rows(final_catalog) + final_catalog <- bde_hlp_guess(final_catalog, + preserve = names(final_catalog)[c(5, 15)] + ) - # Parse dates dates - if (parse_dates) { - if (verbose) { - message("tidyBdE> Parsing dates") - } - date_fields <- - names(final_catalog)[grep("Fecha", names(final_catalog))] + # To tibble + final_catalog <- tibble::as_tibble(final_catalog) - for (i in seq_len(length(date_fields))) { - field <- date_fields[i] - final_catalog[field] <- - bde_parse_dates(final_catalog[[field]]) - } + + # Parse dates dates + if (parse_dates) { + if (verbose) { + message("tidyBdE> Parsing dates") + } + date_fields <- names(final_catalog)[grep("Fecha", names(final_catalog))] + + for (i in seq_len(length(date_fields))) { + field <- date_fields[i] + final_catalog[field] <- bde_parse_dates(final_catalog[[field]]) } - return(final_catalog) } + return(final_catalog) +} #' Update BdE catalogs #' +#' @description #' Update the time-series catalogs provided by BdE. #' #' @export @@ -215,7 +199,6 @@ bde_catalog_load <- #' #' @param catalog A vector of characters indicating the catalogs to be updated #' or `"ALL"` as a shorthand. See **Details**. -#' #' @param cache_dir A path to a cache directory. The directory can also be set #' via options with `options(bde_cache_dir = "path/to/dir")`. #' @param verbose Logical `TRUE` or `FALSE`, display information useful for @@ -242,104 +225,101 @@ bde_catalog_load <- #' knitr::kable(t) #' #' ``` -#' #' Use `"ALL"` as a shorthand for updating all the catalogs at a glance. #' #' @examplesIf bde_check_access() #' \donttest{ #' bde_catalog_update("TI", verbose = TRUE) #' } -bde_catalog_update <- - function(catalog = c("ALL", "BE", "SI", "TC", "TI", "PB"), - cache_dir = NULL, - verbose = FALSE) { - catalog <- match.arg(catalog) - # Validate - valid_catalogs <- - c("BE", "SI", "TC", "TI", "PB", "ALL") - stopifnot( - catalog %in% valid_catalogs, - is.null(cache_dir) || is.character(cache_dir), - is.logical(verbose) - ) +bde_catalog_update <- function(catalog = c("ALL", "BE", "SI", "TC", "TI", "PB"), + cache_dir = NULL, verbose = FALSE) { + catalog <- match.arg(catalog) + # Validate + valid_catalogs <- c("BE", "SI", "TC", "TI", "PB", "ALL") + stopifnot( + catalog %in% valid_catalogs, + any(is.null(cache_dir), is.character(cache_dir)), + is.logical(verbose) + ) - # nocov start - if (!bde_check_access()) { - tbl <- bde_hlp_return_null() - return(tbl) - } - # nocov end + # nocov start + if (!bde_check_access()) { + tbl <- bde_hlp_return_null() + return(tbl) + } + # nocov end - # Get cache dir - cache_dir <- - bde_hlp_cachedir(cache_dir = cache_dir, verbose = verbose) + # Get cache dir + cache_dir <- bde_hlp_cachedir(cache_dir = cache_dir, verbose = verbose) - # Loop and download - if ("ALL" %in% catalog) { - catalog_download <- valid_catalogs[valid_catalogs != "ALL"] - } else { - catalog_download <- catalog - } - if (verbose) { - message( - "tidyBdE> Updating catalogs: ", - paste0(catalog_download, collapse = ", ") - ) - } - res <- lapply(catalog_download, function(x) { - serie <- x - base_url <- paste0( - "https://www.bde.es/webbe/es/estadisticas/", - "compartido/datos/csv/" - ) - catalog_file <- paste0("catalogo_", tolower(serie), ".csv") + # Loop and download + catalog_download <- catalog + if ("ALL" %in% catalog) { + catalog_download <- valid_catalogs[valid_catalogs != "ALL"] + } - full_url <- paste0(base_url, catalog_file) - local_file <- file.path(cache_dir, catalog_file) + if (verbose) { + message( + "tidyBdE> Updating catalogs: ", + paste0(catalog_download, collapse = ", ") + ) + } - # Download - result <- bde_hlp_download( - url = full_url, - local_file = local_file, - verbose = verbose - ) - return(result) - }) + res <- lapply(catalog_download, function(x) { + serie <- x + base_url <- paste0( + "https://www.bde.es/webbe/es/estadisticas/", + "compartido/datos/csv/" + ) + catalog_file <- paste0("catalogo_", tolower(serie), ".csv") - return(invisible(res)) - } + full_url <- paste0(base_url, catalog_file) + local_file <- file.path(cache_dir, catalog_file) + + # Download + result <- bde_hlp_download( + url = full_url, + local_file = local_file, + verbose = verbose + ) + return(result) + }) + + return(invisible(res)) +} #' Search BdE catalogs #' +#' @description #' Search for keywords on the time-series catalogs. #' #' @export #' #' @family catalog #' -#' @return A tibble with the results of the query. +#' @return A [tibble][tibble::tibble] with the results of the query. #' -#' @param pattern [`regex`][base::grep()] pattern to search See -#' **Details** and **Examples**. +#' @param pattern [`regex`][base::regex] pattern to search See **Details** +#' and **Examples**. #' #' @inheritDotParams bde_catalog_load #' #' @encoding UTF-8 #' #' @details -#' **Note that** BdE files are only provided in -#' Spanish, for the time being. Therefore search terms should be provided -#' in Spanish as well in order to get search results. +#' **Note that** BdE files are only provided in Spanish, for the time being. +#' Therefore search terms should be provided in Spanish as well in order to get +#' search results. #' -#' This function uses [base::regex()] function for finding matches on -#' the catalogs. You can pass [regular expressions][base::regex()] to broaden +#' This function uses [base::grep()] function for finding matches on +#' the catalogs. You can pass [regular expressions][base::regex] to broaden #' the search. #' -#' @seealso [bde_catalog_load()], [base::regex()] +#' @seealso [bde_catalog_load()], [base::regex] #' #' @examplesIf bde_check_access() #' \donttest{ @@ -361,10 +341,6 @@ bde_catalog_update <- #' bde_catalog_search("^3779313$") #' } bde_catalog_search <- function(pattern, ...) { - if (missing(pattern) || is.null(pattern) || is.na(pattern)) { - stop("`pattern` should be a character.") - } - # Extract info catalog_search <- bde_catalog_load(...) diff --git a/R/scales.R b/R/scales.R index 7825f181..f515a7ff 100644 --- a/R/scales.R +++ b/R/scales.R @@ -20,6 +20,8 @@ #' @param palette Name of the BdE palette to apply. One of `"bde_vivid_pal"`, #' `"bde_rose_pal"`. See [bde_palettes()] for details. #' +#' @inheritParams bde_palettes +#' #' @param ... Further arguments of [ggplot2::discrete_scale()] or #' [ggplot2::continuous_scale()]. #' @@ -47,10 +49,10 @@ #' theme_minimal() #' scale_color_bde_d <- function(palette = c("bde_vivid_pal", "bde_rose_pal"), - ...) { + alpha = NULL, rev = FALSE, ...) { palette <- match.arg(palette) - cols_v <- bde_palettes(palette = palette) + cols_v <- bde_palettes(palette = palette, alpha = alpha, rev = rev) pal <- scales::manual_pal(cols_v) ggplot2::discrete_scale( @@ -71,10 +73,10 @@ scale_colour_bde_d <- scale_color_bde_d #' @name scales_bde #' @export scale_fill_bde_d <- function(palette = c("bde_vivid_pal", "bde_rose_pal"), - ...) { + alpha = NULL, rev = FALSE, ...) { palette <- match.arg(palette) - cols_v <- bde_palettes(palette = palette) + cols_v <- bde_palettes(palette = palette, alpha = alpha, rev = rev) pal <- scales::manual_pal(cols_v) ggplot2::discrete_scale( @@ -90,18 +92,25 @@ scale_fill_bde_d <- function(palette = c("bde_vivid_pal", "bde_rose_pal"), #' @name scales_bde #' @export scale_color_bde_c <- function(palette = c("bde_rose_pal", "bde_vivid_pal"), - ...) { + alpha = NULL, rev = FALSE, ...) { palette <- match.arg(palette) cols <- switch(palette, - "bde_vivid_pal" = bde_palettes(6, "bde_vivid_pal"), - "bde_rose_pal" = bde_palettes(6, "bde_rose_pal")[c(1, 2, 3, 6, 5, 4)] + "bde_vivid_pal" = bde_palettes(6, "bde_vivid_pal", + alpha = alpha, + rev = rev + ), + "bde_rose_pal" = bde_palettes(6, "bde_rose_pal", + alpha = alpha, + rev = rev + )[c(1, 2, 3, 6, 5, 4)] ) ggplot2::continuous_scale( aesthetics = "color", scale_name = palette, palette = scales::gradient_n_pal(cols), + guide = "colorbar", ... ) } @@ -116,18 +125,25 @@ scale_colour_bde_c <- scale_color_bde_c #' @name scales_bde #' @export scale_fill_bde_c <- function(palette = c("bde_rose_pal", "bde_vivid_pal"), - ...) { + alpha = NULL, rev = FALSE, ...) { palette <- match.arg(palette) cols <- switch(palette, - "bde_vivid_pal" = bde_palettes(6, "bde_vivid_pal"), - "bde_rose_pal" = bde_palettes(6, "bde_rose_pal")[c(1, 2, 3, 6, 5, 4)] + "bde_vivid_pal" = bde_palettes(6, "bde_vivid_pal", + alpha = alpha, + rev = rev + ), + "bde_rose_pal" = bde_palettes(6, "bde_rose_pal", + alpha = alpha, + rev = rev + )[c(1, 2, 3, 6, 5, 4)] ) ggplot2::continuous_scale( aesthetics = "fill", scale_name = palette, palette = scales::gradient_n_pal(cols), + guide = "colorbar", ... ) } diff --git a/R/series.R b/R/series.R index de3994ff..e45a27b5 100644 --- a/R/series.R +++ b/R/series.R @@ -24,7 +24,7 @@ #' #' #' @return -#' A `tibble` with a field "Date" and : +#' A [tibble][tibble::tibble] with a field "Date" and : #' - With `out_format = "wide"` each series is presented in a separate #' column with the name defined by `series_label`. #' - With `out_format = "long"` the tibble would have two more columns, @@ -98,14 +98,10 @@ #' scale_color_bde_d() + #' theme_tidybde() #' } -bde_series_load <- function(series_code, - series_label = NULL, - out_format = "wide", - parse_dates = TRUE, - parse_numeric = TRUE, - cache_dir = NULL, - update_cache = FALSE, - verbose = FALSE, +bde_series_load <- function(series_code, series_label = NULL, + out_format = "wide", parse_dates = TRUE, + parse_numeric = TRUE, cache_dir = NULL, + update_cache = FALSE, verbose = FALSE, extract_metadata = FALSE) { if (missing(series_code)) { stop("`series_code` can't be NULL") @@ -128,8 +124,6 @@ bde_series_load <- function(series_code, stop("`series_label` and `series_code` should have the same length") } - - # Lookup on catalogs all_catalogs <- bde_catalog_load( catalog = "ALL", parse_dates = parse_dates, @@ -190,8 +184,6 @@ bde_series_load <- function(series_code, tbl <- bde_hlp_return_null() return(tbl) } - # nocov end - # nocov start if (!(alias_serie %in% names(serie_file))) { if (verbose) { message( @@ -299,8 +291,8 @@ bde_series_load <- function(series_code, #' @param extract_metadata Logical `TRUE/FALSE`. On `TRUE` the output is the #' metadata of the requested series. #' -#' @return A tibble with a field "Date" and the alias of the fields series as -#' described on the catalogs. See [bde_catalog_load()]. +#' @return A [tibble][tibble::tibble] with a field "Date" and the alias of the +#' fields series as described on the catalogs. See [bde_catalog_load()]. #' #' @note #' This function tries to coerce the columns to numbers. For some series a diff --git a/R/theme_tidybde.R b/R/theme_tidybde.R index 3d4cd9bb..69516e88 100644 --- a/R/theme_tidybde.R +++ b/R/theme_tidybde.R @@ -38,7 +38,7 @@ #' names(series_TC_pivot) <- c("x", "y") #' #' ggplot(series_TC_pivot, aes(x = x, y = y)) + -#' geom_line(linewidth = 0.8, color = bde_vivid_pal()(1)) + +#' geom_line(linewidth = 0.8, color = bde_palettes(n = 1)) + #' labs( #' title = "Title", #' subtitle = "Some metric", diff --git a/R/tidyBdE-package.R b/R/tidyBdE-package.R index 107309cd..6214d855 100644 --- a/R/tidyBdE-package.R +++ b/R/tidyBdE-package.R @@ -10,6 +10,5 @@ NULL # import stuffs #' @importFrom utils download.file read.csv2 -#' @importFrom tibble tibble #' @importFrom ggplot2 unit element_rect element_text element_blank element_line NULL diff --git a/README.Rmd b/README.Rmd index 0dac939e..52cea94d 100644 --- a/README.Rmd +++ b/README.Rmd @@ -126,8 +126,8 @@ BdE: ```{r chart, fig.asp=0.7} ggplot(time_series, aes(x = Date, y = EUR_GBP_XR)) + - geom_line(colour = bde_vivid_pal()(1)) + - geom_smooth(method = "gam", colour = bde_vivid_pal()(2)[2]) + + geom_line(colour = bde_palettes(n = 1)) + + geom_smooth(method = "gam", colour = bde_palettes(n = 2)[2]) + labs( title = "EUR/GBP Exchange Rate (2010-2020)", subtitle = "%", @@ -176,12 +176,6 @@ ggplot(plotseries, aes(x = Date, y = serie_value)) + Two custom palettes, based on the used by BdE on some publications are available. -```{r palettes, fig.asp=0.7} -scales::show_col(bde_rose_pal()(6)) - -scales::show_col(bde_vivid_pal()(6)) -``` - Those palettes can be applied to a `ggplot2` using some custom utils included on the package (see `help("scale_color_bde_d", package = "tidyBdE")`). diff --git a/README.md b/README.md index fbe04d14..e58b0b65 100644 --- a/README.md +++ b/README.md @@ -116,8 +116,8 @@ publications of BdE: ``` r ggplot(time_series, aes(x = Date, y = EUR_GBP_XR)) + - geom_line(colour = bde_vivid_pal()(1)) + - geom_smooth(method = "gam", colour = bde_vivid_pal()(2)[2]) + + geom_line(colour = bde_palettes(n = 1)) + + geom_smooth(method = "gam", colour = bde_palettes(n = 2)[2]) + labs( title = "EUR/GBP Exchange Rate (2010-2020)", subtitle = "%", @@ -170,19 +170,6 @@ ggplot(plotseries, aes(x = Date, y = serie_value)) + Two custom palettes, based on the used by BdE on some publications are available. -``` r -scales::show_col(bde_rose_pal()(6)) -``` - - - -``` r - -scales::show_col(bde_vivid_pal()(6)) -``` - - - Those palettes can be applied to a `ggplot2` using some custom utils included on the package (see `help("scale_color_bde_d", package = "tidyBdE")`). diff --git a/codemeta.json b/codemeta.json index c4cfb1ae..09b61f38 100644 --- a/codemeta.json +++ b/codemeta.json @@ -192,7 +192,7 @@ }, "applicationCategory": "Macroeconomics", "isPartOf": "https://ropenspain.es/", - "fileSize": "290.036KB", + "fileSize": "273.699KB", "citation": [ { "@type": "SoftwareSourceCode", diff --git a/inst/WORDLIST b/inst/WORDLIST index 2868d0ef..edce3ce5 100644 --- a/inst/WORDLIST +++ b/inst/WORDLIST @@ -50,7 +50,7 @@ rOS rect secuencial serie +superseeded tibble -tidyBdE’ tidyr tidyverse diff --git a/man/bde_catalog_load.Rd b/man/bde_catalog_load.Rd index 3ab4132f..b631b083 100644 --- a/man/bde_catalog_load.Rd +++ b/man/bde_catalog_load.Rd @@ -33,7 +33,7 @@ the \code{cache_dir}.} debugging.} } \value{ -A \code{tibble}. +A \link[tibble:tibble]{tibble}. } \description{ Load the time-series catalogs provided by BdE. diff --git a/man/bde_catalog_search.Rd b/man/bde_catalog_search.Rd index 0cc0d915..aaa95c13 100644 --- a/man/bde_catalog_search.Rd +++ b/man/bde_catalog_search.Rd @@ -8,8 +8,8 @@ bde_catalog_search(pattern, ...) } \arguments{ -\item{pattern}{\code{\link[base:grep]{regex}} pattern to search See -\strong{Details} and \strong{Examples}.} +\item{pattern}{\code{\link[base:regex]{regex}} pattern to search See \strong{Details} +and \strong{Examples}.} \item{...}{ Arguments passed on to \code{\link[=bde_catalog_load]{bde_catalog_load}} @@ -27,17 +27,17 @@ debugging.} }} } \value{ -A tibble with the results of the query. +A \link[tibble:tibble]{tibble} with the results of the query. } \description{ Search for keywords on the time-series catalogs. } \details{ -\strong{Note that} BdE files are only provided in -Spanish, for the time being. Therefore search terms should be provided -in Spanish as well in order to get search results. +\strong{Note that} BdE files are only provided in Spanish, for the time being. +Therefore search terms should be provided in Spanish as well in order to get +search results. -This function uses \code{\link[base:regex]{base::regex()}} function for finding matches on +This function uses \code{\link[base:grep]{base::grep()}} function for finding matches on the catalogs. You can pass \link[base:regex]{regular expressions} to broaden the search. } @@ -64,7 +64,7 @@ bde_catalog_search("^3779313$") \dontshow{\}) # examplesIf} } \seealso{ -\code{\link[=bde_catalog_load]{bde_catalog_load()}}, \code{\link[base:regex]{base::regex()}} +\code{\link[=bde_catalog_load]{bde_catalog_load()}}, \link[base:regex]{base::regex} Other catalog: \code{\link{bde_catalog_load}()}, diff --git a/man/bde_series_full_load.Rd b/man/bde_series_full_load.Rd index 11a0017c..4c310c64 100644 --- a/man/bde_series_full_load.Rd +++ b/man/bde_series_full_load.Rd @@ -39,8 +39,8 @@ debugging.} metadata of the requested series.} } \value{ -A tibble with a field "Date" and the alias of the fields series as -described on the catalogs. See \code{\link[=bde_catalog_load]{bde_catalog_load()}}. +A \link[tibble:tibble]{tibble} with a field "Date" and the alias of the +fields series as described on the catalogs. See \code{\link[=bde_catalog_load]{bde_catalog_load()}}. } \description{ Load a full time-series file provided by BdE. diff --git a/man/bde_series_load.Rd b/man/bde_series_load.Rd index f53cb6fe..08009573 100644 --- a/man/bde_series_load.Rd +++ b/man/bde_series_load.Rd @@ -49,7 +49,7 @@ debugging.} metadata of the requested series.} } \value{ -A \code{tibble} with a field "Date" and : +A \link[tibble:tibble]{tibble} with a field "Date" and : \itemize{ \item With \code{out_format = "wide"} each series is presented in a separate column with the name defined by \code{series_label}. diff --git a/man/figures/README-palettes-1.png b/man/figures/README-palettes-1.png deleted file mode 100644 index 845c7eef..00000000 Binary files a/man/figures/README-palettes-1.png and /dev/null differ diff --git a/man/figures/README-palettes-2.png b/man/figures/README-palettes-2.png deleted file mode 100644 index 8cfa1507..00000000 Binary files a/man/figures/README-palettes-2.png and /dev/null differ diff --git a/man/scales_bde.Rd b/man/scales_bde.Rd index 70282f6b..8d086fd9 100644 --- a/man/scales_bde.Rd +++ b/man/scales_bde.Rd @@ -10,18 +10,46 @@ \alias{scale_fill_bde_c} \title{BdE scales for \CRANpkg{ggplot2}.} \usage{ -scale_color_bde_d(palette = c("bde_vivid_pal", "bde_rose_pal"), ...) +scale_color_bde_d( + palette = c("bde_vivid_pal", "bde_rose_pal"), + alpha = NULL, + rev = FALSE, + ... +) -scale_fill_bde_d(palette = c("bde_vivid_pal", "bde_rose_pal"), ...) +scale_fill_bde_d( + palette = c("bde_vivid_pal", "bde_rose_pal"), + alpha = NULL, + rev = FALSE, + ... +) -scale_color_bde_c(palette = c("bde_rose_pal", "bde_vivid_pal"), ...) +scale_color_bde_c( + palette = c("bde_rose_pal", "bde_vivid_pal"), + alpha = NULL, + rev = FALSE, + ... +) -scale_fill_bde_c(palette = c("bde_rose_pal", "bde_vivid_pal"), ...) +scale_fill_bde_c( + palette = c("bde_rose_pal", "bde_vivid_pal"), + alpha = NULL, + rev = FALSE, + ... +) } \arguments{ \item{palette}{Name of the BdE palette to apply. One of \code{"bde_vivid_pal"}, \code{"bde_rose_pal"}. See \code{\link[=bde_palettes]{bde_palettes()}} for details.} +\item{alpha}{An alpha-transparency level in the range \verb{[0,1]} (\code{0} means +transparent and \code{1} means opaque). A missing, i.e., \code{alpha = NULL}, does +not add opacity codes (\code{"FF"}) to the individual color hex codes. See +\code{\link[ggplot2:reexports]{ggplot2::alpha()}}.} + +\item{rev}{Logical indicating whether the ordering of the colors should be +reversed.} + \item{...}{Further arguments of \code{\link[ggplot2:discrete_scale]{ggplot2::discrete_scale()}} or \code{\link[ggplot2:continuous_scale]{ggplot2::continuous_scale()}}.} } diff --git a/man/theme_tidybde.Rd b/man/theme_tidybde.Rd index 1c83ef8e..127ccb43 100644 --- a/man/theme_tidybde.Rd +++ b/man/theme_tidybde.Rd @@ -47,7 +47,7 @@ if (nrow(series_TC) > 0) { names(series_TC_pivot) <- c("x", "y") ggplot(series_TC_pivot, aes(x = x, y = y)) + - geom_line(linewidth = 0.8, color = bde_vivid_pal()(1)) + + geom_line(linewidth = 0.8, color = bde_palettes(n = 1)) + labs( title = "Title", subtitle = "Some metric", diff --git a/tests/testthat.R b/tests/testthat.R index 0770a35d..dcd367a5 100644 --- a/tests/testthat.R +++ b/tests/testthat.R @@ -1,3 +1,11 @@ +# This file is part of the standard setup for testthat. +# It is recommended that you do not modify it. +# +# Where should you do additional test configuration? +# Learn more about the roles of various files in: +# * https://r-pkgs.org/testing-design.html#sec-tests-files-overview +# * https://testthat.r-lib.org/articles/special-files.html + library(testthat) library(tidyBdE) diff --git a/tests/testthat/_snaps/bde_col_pal.md b/tests/testthat/_snaps/bde_palettes.md similarity index 100% rename from tests/testthat/_snaps/bde_col_pal.md rename to tests/testthat/_snaps/bde_palettes.md diff --git a/tests/testthat/test-deprecated.R b/tests/testthat/test-deprecated.R index acfe8642..0c3d936d 100644 --- a/tests/testthat/test-deprecated.R +++ b/tests/testthat/test-deprecated.R @@ -1,7 +1,7 @@ test_that("bde_vivid_pal", { + skip_if_not_installed("lifecycle") expect_snapshot(vpal <- bde_vivid_pal()(3)) - expect_identical( bde_palettes(n = 3, "bde_vivid_pal"), vpal @@ -9,9 +9,9 @@ test_that("bde_vivid_pal", { }) test_that("bde_rose_pal", { + skip_if_not_installed("lifecycle") expect_snapshot(vpal <- bde_rose_pal()(4)) - expect_identical( bde_palettes(n = 4, "bde_rose_pal"), vpal diff --git a/tests/testthat/test-scales.R b/tests/testthat/test-scales.R index 8265be7f..dcd8d449 100644 --- a/tests/testthat/test-scales.R +++ b/tests/testthat/test-scales.R @@ -15,13 +15,22 @@ test_that("Discrete scale", { mod3 <- ggplot2::layer_data(p3)$colour expect_identical(mod, mod3) + # Alpha + + p3 <- p + scale_colour_bde_d(alpha = 0.9) + + mod_alpha <- ggplot2::layer_data(p3)$colour + + expect_true(all(ggplot2::alpha(mod, 0.9) == mod_alpha)) + + # Another pal p4 <- p + scale_color_bde_d(palette = "bde_rose_pal") mod4 <- ggplot2::layer_data(p4)$colour expect_false(any(mod == mod4)) - # Another param + # Another aes pf <- ggplot2::ggplot(d) + ggplot2::geom_point(ggplot2::aes(x, y, fill = l), shape = 21) @@ -38,51 +47,48 @@ test_that("Discrete scale", { test_that("Continous scale", { - skip("Not ready yet") d <- data.frame(x = 1:5, y = 1:5, z = 21:25, l = letters[1:5]) p <- ggplot2::ggplot(d) + ggplot2::geom_point(ggplot2::aes(x, y, colour = z)) init <- ggplot2::layer_data(p)$colour - p2 <- p + scale_colour_terrain_c() + p2 <- p + scale_color_bde_c() mod <- ggplot2::layer_data(p2)$colour expect_true(!any(init %in% mod)) # Renamed - p3 <- p + scale_color_terrain_c() + p3 <- p + scale_colour_bde_c() mod3 <- ggplot2::layer_data(p3)$colour expect_identical(mod, mod3) # Alpha - expect_snapshot(p + scale_colour_terrain_c(alpha = -1), - error = TRUE - ) - p3 <- p + scale_colour_terrain_c(alpha = 0.9) + p3 <- p + scale_colour_bde_c(alpha = 0.9) mod_alpha <- ggplot2::layer_data(p3)$colour - expect_true(all(adjustcolor(mod, alpha.f = 0.9) == mod_alpha)) + expect_true(all(ggplot2::alpha(mod, 0.9) == mod_alpha)) - # Reverse also with alpha - expect_snapshot(p + scale_colour_terrain_c(direction = 0.5), - error = TRUE - ) + # Another pal + p4 <- p + scale_color_bde_c(palette = "bde_vivid_pal") + mod4 <- ggplot2::layer_data(p4)$colour + expect_false(any(mod == mod4)) + # Another aes + pf <- ggplot2::ggplot(d) + + ggplot2::geom_point(ggplot2::aes(x, y, fill = z), shape = 21) - p4 <- p + scale_colour_terrain_c( - direction = -1, - alpha = 0.7 - ) + pfill <- pf + scale_fill_bde_c() + colfill <- ggplot2::layer_data(pfill)$fill - mod_alpha_rev <- ggplot2::layer_data(p4)$colour + expect_identical(mod, colfill) + pfill2 <- pf + scale_fill_bde_c(palette = "bde_vivid_pal") + colfill2 <- ggplot2::layer_data(pfill2)$fill - expect_true( - all(rev(adjustcolor(mod, alpha.f = 0.7)) == mod_alpha_rev) - ) + expect_identical(mod4, colfill2) }) diff --git a/vignettes/articles/Main_Macroeconomic_Series.Rmd b/vignettes/articles/Main_Macroeconomic_Series.Rmd index b77ce5d8..c64ea9a9 100644 --- a/vignettes/articles/Main_Macroeconomic_Series.Rmd +++ b/vignettes/articles/Main_Macroeconomic_Series.Rmd @@ -30,7 +30,7 @@ library(dplyr) library(tidyr) -col <- tidyBdE::bde_rose_pal()(1) +col <- bde_palettes(1, "bde_rose_pal") date <- Sys.Date() ny <- as.numeric(format(date, format = "%Y")) - 4 nd <- as.Date(paste0(ny, "-12-31")) diff --git a/vignettes/chart-1.png b/vignettes/chart-1.png new file mode 100644 index 00000000..2da3f832 Binary files /dev/null and b/vignettes/chart-1.png differ diff --git a/vignettes/tidyBdE.Rmd b/vignettes/tidyBdE.Rmd index 5d208ea9..03e6672e 100644 --- a/vignettes/tidyBdE.Rmd +++ b/vignettes/tidyBdE.Rmd @@ -86,8 +86,8 @@ BdE: ```r ggplot(time_series, aes(x = Date, y = EUR_GBP_XR)) + - geom_line(colour = bde_vivid_pal()(1)) + - geom_smooth(method = "gam", colour = bde_vivid_pal()(2)[2]) + + geom_line(colour = bde_palettes(n = 1)) + + geom_smooth(method = "gam", colour = bde_palettes(n = 2)[2]) + labs( title = "EUR/GBP Exchange Rate (2010-2020)", subtitle = "%", @@ -106,8 +106,10 @@ ggplot(time_series, aes(x = Date, y = EUR_GBP_XR)) + theme_tidybde() ``` -![EUR/GBP Exchange Rate (2010-2020) via -tidyBdE](../man/figures/README-chart-1.png) +
+EUR/GBP Exchange Rate (2010-2020) +

EUR/GBP Exchange Rate (2010-2020)

+
The package provides also several "shortcut" functions for a selection of the most relevant macroeconomic series, so there is no need to look for them in diff --git a/vignettes/tidyBdE.Rmd.orig b/vignettes/tidyBdE.Rmd.orig index 2d5e455e..1a998be9 100644 --- a/vignettes/tidyBdE.Rmd.orig +++ b/vignettes/tidyBdE.Rmd.orig @@ -17,7 +17,7 @@ knitr::opts_chunk$set( tidy = "styler", warning = FALSE, message = FALSE, - dpi = 300, + dpi = 120, dev = "ragg_png", fig.path = "./", out.width = "100%" @@ -93,11 +93,11 @@ time_series <- bde_series_load(seq_number, series_label = "EUR_GBP_XR") %>% The package also provides a custom `ggplot2` theme based on the publications of BdE: -```{r chart, eval=FALSE} +```{r chart, eval=TRUE, fig.cap='EUR/GBP Exchange Rate (2010-2020)', fig.asp=0.7} ggplot(time_series, aes(x = Date, y = EUR_GBP_XR)) + - geom_line(colour = bde_vivid_pal()(1)) + - geom_smooth(method = "gam", colour = bde_vivid_pal()(2)[2]) + + geom_line(colour = bde_palettes(n=1)) + + geom_smooth(method = "gam", colour = bde_palettes(n=2)[2]) + labs(title = "EUR/GBP Exchange Rate (2010-2020)", subtitle = "%", caption = "Source: BdE") + @@ -113,9 +113,6 @@ ggplot(time_series, aes(x = Date, y = EUR_GBP_XR)) + ``` -![EUR/GBP Exchange Rate (2010-2020) via -tidyBdE](../man/figures/README-chart-1.png) - The package provides also several "shortcut" functions for a selection of the most relevant macroeconomic series, so there is no need to look for them in advance: