Skip to content

Commit

Permalink
feat(R pkg): added validation for configuration values (#37)
Browse files Browse the repository at this point in the history
* Added validation for configuration values
* Failure of the configuration validation will now be mapped to a stop
inside the R session instead of showing the raw Rust panic message

Closes #36
  • Loading branch information
kpagacz authored Feb 8, 2025
1 parent cda88d7 commit 88c0dee
Show file tree
Hide file tree
Showing 9 changed files with 206 additions and 79 deletions.
4 changes: 3 additions & 1 deletion antidotum/tergo/DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -31,8 +31,10 @@ Suggests:
pkgdown,
desc,
knitr,
rmarkdown
rmarkdown,
testthat (>= 3.0.0)
URL: https://rtergo.pagacz.io,
https://github.com/kpagacz/tergo
BugReports: https://github.com/kpagacz/tergo/issues
VignetteBuilder: knitr
Config/testthat/edition: 3
7 changes: 5 additions & 2 deletions antidotum/tergo/R/extendr-wrappers.R
Original file line number Diff line number Diff line change
Expand Up @@ -52,10 +52,13 @@ get_config <- function(path) .Call(wrap__get_config, path)
#' print(config)
#'
#' # Make the indent 4 spaces
#' config$indent <- 4
#' config$indent <- 4L
#'
#' # Make the maximum line length 80 characters
#' config$line_length <- 80
#' config$line_length <- 80L
#'
#' # Make the function line breaks double
#' config$function_line_breaks <- "double"
get_default_config <- function() .Call(wrap__get_default_config)

# nolint end
Expand Down
14 changes: 10 additions & 4 deletions antidotum/tergo/R/styling.R
Original file line number Diff line number Diff line change
Expand Up @@ -128,7 +128,7 @@ style_pkg <- function(path = ".",
},
error = function(err) {
# Print File Path, Red Cross, and Error Message
if (verbose) cat(sprintf("%s %s : %s\n", basename(file), red_cross, err$message))
if (verbose) cat(sprintf("%s %s : %s\n", basename(file), red_cross, truncate_error(err$message)))
}
)
}
Expand Down Expand Up @@ -171,7 +171,7 @@ style_file <- function(file, configuration = list()) {
if (formatted[[1]] == "success") {
formatted[[2]]
} else {
stop("Failed to style the file.")
stop("Failed to style the file. Error: ", truncate_error(formatted[[2]]))
}
write(x = formatted[[2]], file = file)
invisible(NULL)
Expand All @@ -185,7 +185,7 @@ style_file <- function(file, configuration = list()) {
#'
#' @inheritParams style
#' @param text (`character`) the text to style
#' @return (`character`) the text formatted as R code
#' @return (`character`) The text formatted as R code.
#'
#' @export
#' @examples
Expand All @@ -202,11 +202,17 @@ style_text <- function(text, configuration = list()) {
if (formatted[[1]] == "success") {
formatted[[2]]
} else {
stop("Failed to style the text.")
stop("Failed to style the text. Error: ", truncate_error(formatted[[2]]))
}
},
FUN.VALUE = character(1),
USE.NAMES = FALSE
)
}

#' Truncate the error message
#'
#' @keywords internal
truncate_error <- function(err) {
ifelse(nchar(err) > 80, sprintf("%s...", substr(err, 1, 77)), err)
}
7 changes: 5 additions & 2 deletions antidotum/tergo/man/get_default_config.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion antidotum/tergo/man/style_text.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

12 changes: 12 additions & 0 deletions antidotum/tergo/man/truncate_error.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

202 changes: 133 additions & 69 deletions antidotum/tergo/src/rust/src/lib.rs
Original file line number Diff line number Diff line change
@@ -1,6 +1,57 @@
use extendr_api::prelude::*;
use std::collections::HashMap;
use tergo_lib::{Config, FunctionLineBreaks};

const ERROR: &str = "error";
const OK: &str = "success";

fn config_to_bool(
field: &str,
configuration: &HashMap<&str, Robj>,
default_value: bool,
) -> std::result::Result<bool, extendr_api::List> {
let config_value = configuration.get(field);
let value: bool;
if let Some(config) = config_value {
if let Some(casted) = config.as_bool() {
value = casted;
} else {
return Err(list!(
ERROR,
format!("{} configuration value must be a boolean.", field)
));
}
} else {
value = default_value;
}
Ok(value)
}

fn config_to_integer(
field: &str,
configuration: &HashMap<&str, Robj>,
default_value: i32,
) -> std::result::Result<i32, extendr_api::List> {
let config_value = configuration.get(field);
let value: i32;
if let Some(config) = config_value {
if let Some(casted) = config.as_integer() {
value = casted;
} else {
return Err(list!(
ERROR,
format!(
"{} configuration value must be an integer. Did you forget about L?",
field
)
));
}
} else {
value = default_value;
}
Ok(value)
}

/// Format code
///
/// @param source_code (`character`) the R code to format
Expand All @@ -13,71 +64,76 @@ fn format_code(source_code: &str, configuration: extendr_api::List) -> extendr_a
let configuration = configuration.into_hashmap();
let default_config = Config::default();
let config = Config::new(
configuration
.get("indent")
.map(|x| x.as_integer().expect("The indent must be an integer"))
.unwrap_or(default_config.indent.0),
configuration
.get("line_length")
.map(|x| x.as_integer().expect("The line_length must be an integer"))
.unwrap_or(default_config.line_length.0),
configuration
.get("embracing_op_no_nl")
.map(|x| {
x.as_bool()
.expect("The embracing_op_no_nl must be a boolean")
})
.unwrap_or(default_config.embracing_op_no_nl.0),
configuration
.get("allow_nl_after_assignment")
.map(|x| {
x.as_bool()
.expect("The allow_nl_after_assignment must be a boolean")
})
.unwrap_or(default_config.allow_nl_after_assignment.0),
configuration
.get("space_before_complex_rhs_in_formula")
.map(|x| {
x.as_bool()
.expect("The space_before_complex_rhs_in_formula must be a boolean")
})
.unwrap_or(default_config.space_before_complex_rhs_in_formula.0),
configuration
.get("strip_suffix_whitespace_in_function_defs")
.map(|x| {
x.as_bool()
.expect("The strip_suffix_whitespace_in_function_defs must be a boolean")
})
.unwrap_or(default_config.strip_suffix_whitespace_in_function_defs.0),
configuration
.get("function_line_breaks")
.map(|x| {
match x
.as_str()
.expect("The function_line_breaks must be character")
{
"single" => FunctionLineBreaks::Single,
"double" => FunctionLineBreaks::Double,
"hanging" => FunctionLineBreaks::Hanging,
_ => panic!("Unknown function line breaks. Allowed: single, double, hanging."),
match config_to_integer("indent", &configuration, default_config.indent.0) {
Ok(value) => value,
Err(error) => return error,
},
match config_to_integer("line_length", &configuration, default_config.line_length.0) {
Ok(value) => value,
Err(error) => return error,
},
match config_to_bool(
"embracing_op_no_nl",
&configuration,
default_config.embracing_op_no_nl.0,
) {
Ok(value) => value,
Err(error) => return error,
},
match config_to_bool(
"allow_nl_after_assignment",
&configuration,
default_config.allow_nl_after_assignment.0,
) {
Ok(value) => value,
Err(error) => return error,
},
match config_to_bool(
"space_before_complex_rhs_in_formula",
&configuration,
default_config.space_before_complex_rhs_in_formula.0,
) {
Ok(value) => value,
Err(error) => return error,
},
match config_to_bool(
"strip_suffix_whitespace_in_function_defs",
&configuration,
default_config.strip_suffix_whitespace_in_function_defs.0,
) {
Ok(value) => value,
Err(error) => return error,
},
match configuration.get("function_line_breaks") {
Some(text) => match text.as_str() {
Some("single") => FunctionLineBreaks::Single,
Some("double") => FunctionLineBreaks::Double,
Some("hanging") => FunctionLineBreaks::Hanging,
_ => {
return list!(
ERROR,
"Unknown function line breaks in the configuration value. Allowed: single, double, hanging."
)
}
})
.unwrap_or(default_config.function_line_breaks),
configuration
.get("insert_newline_in_quote_call")
.map(|x| {
x.as_bool()
.expect("The insert_newline_in_quote_call must be a boolean")
})
.unwrap_or(default_config.insert_newline_in_quote_call.0),
},
None => default_config.function_line_breaks,
},
match config_to_bool(
"insert_newline_in_quote_call",
&configuration,
default_config.insert_newline_in_quote_call.0,
) {
Ok(value) => value,
Err(error) => return error,
},
);

match tergo_lib::tergo_format(source_code, Some(&config)) {
Ok(formatted_code) => {
list!("success", formatted_code)
list!(OK, formatted_code)
}
Err(error) => {
list!("error", error)
list!(ERROR, error)
}
}
}
Expand Down Expand Up @@ -139,15 +195,20 @@ fn get_config(path: &str) -> extendr_api::List {
///
/// @details
/// The configuration values:
/// * indent - the number of spaces to use for indentation.
/// * line_length - the maximum number of characters in a line.
/// * embracing_op_no_nl - whether to allow a newline after an embracing operator.
/// * allow_nl_after_assignment - whether to allow a newline after an assignment operator.
/// * space_before_complex_rhs_in_formula - whether to add a space before a complex right-hand side in a formula.
/// * strip_suffix_whitespace_in_function_defs - whether to strip suffix whitespace in function definitions.
/// * function_line_breaks - the type of line breaks in function definitions when arguments do not
/// fit. Possible values are: hanging, double, single.
/// * insert_newline_in_quote_call - whether to insert a newline in calls to `quote`.
/// * indent (`integer`) - the number of spaces to use for indentation. E.g. 2L, 4L.
/// * line_length (`integer`) - the maximum number of characters in a line. E.g. 80L, 120L.
/// * embracing_op_no_nl (`logical`) - whether to allow a newline after an embracing operator. E.g.
/// TRUE, FALSE.
/// * allow_nl_after_assignment (`logical`) - whether to allow a newline after an assignment operator.
/// E.g. TRUE, FALSE.
/// * space_before_complex_rhs_in_formula (`logical`) - whether to add a space before a complex
/// right-hand side in a formula. E.g. TRUE, FALSE.
/// * strip_suffix_whitespace_in_function_defs (`logical`) - whether to strip suffix
/// whitespace in function definitions. E.g. TRUE, FALSE.
/// * function_line_breaks (`character`) - the type of line breaks in function definitions when arguments do not
/// fit. Possible values are: "hanging", "double", "single".
/// * insert_newline_in_quote_call (`logical`) - whether to insert a newline in calls to `quote`.
/// E.g. TRUE, FALSE.
///
/// @return `list` with the default configuration
/// @export
Expand All @@ -156,10 +217,13 @@ fn get_config(path: &str) -> extendr_api::List {
/// print(config)
///
/// # Make the indent 4 spaces
/// config$indent <- 4
/// config$indent <- 4L
///
/// # Make the maximum line length 80 characters
/// config$line_length <- 80
/// config$line_length <- 80L
///
/// # Make the function line breaks double
/// config$function_line_breaks <- "double"
#[extendr]
fn get_default_config() -> extendr_api::List {
let config = Config::default();
Expand Down
13 changes: 13 additions & 0 deletions antidotum/tergo/tests/testthat.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,13 @@
# 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(tergo)

testthat::test_check("tergo")

24 changes: 24 additions & 0 deletions antidotum/tergo/tests/testthat/test-style_text.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,24 @@
testthat::test_that("style_text validates the configuration", {
testthat::expect_error(
style_text(
"1+1",
configuration = list(line_length = 80),
"Failed to style the text. Error: line_length configuration value must be an integer. Did you forget about L?"
)
)
testthat::expect_error(
style_text(
"1+1",
configuration = list(indent = 2),
"Failed to style the text. Error: indent configuration value must be an integer. Did you forget about L?"
)
)
testthat::expect_error(
style_text(
"1+1",
configuration = list(embracing_op_no_nl = 2),
"Failed to style the text. Error: embracing_op_no_nl configuration value must be a boolean."
)
)
})

0 comments on commit 88c0dee

Please sign in to comment.