Skip to content

Commit

Permalink
Add more checks, shorten expressions in output
Browse files Browse the repository at this point in the history
  • Loading branch information
hsonne committed Jul 1, 2023
1 parent 3697c34 commit 24074e9
Showing 1 changed file with 95 additions and 16 deletions.
111 changes: 95 additions & 16 deletions R/find_weaknesses_in_scripts.R
Original file line number Diff line number Diff line change
Expand Up @@ -39,9 +39,19 @@ find_weaknesses_in_scripts <- function(x = parse_scripts(root), root = NULL)
),
find_code_snippets(
x,
check_function = is_true_or_false_constant,
check_function = is_logical_constant,
recommendation = "use TRUE/FALSE instead of T/F",
type = "parent"
),
find_code_snippets(
x,
check_function = is_comparison_with_true,
recommendation = "use just 'x' instead of 'x == TRUE/T'"
),
find_code_snippets(
x,
check_function = is_comparison_with_false,
recommendation = "use '!x' instead of 'x == FALSE/F'"
)
)

Expand Down Expand Up @@ -76,36 +86,77 @@ find_code_snippets <- function(
}

# to_matches_function ----------------------------------------------------------
to_matches_function <- function(check_function, type = "self")
to_matches_function <- function(check_function, type = "self", max_chars = 50L)
{
function(x, parent, index) {

if (!check_function(x)) {
return(FALSE)
}

structure(TRUE, name = kwb.utils::collapsed(
if (identical(type, "self")) {
deparse(x)
} else if (identical(type, "element_2")) {
deparse(x[[2L]])
} else if (identical(type, "parent")) {
deparse(parent)
} else {
stop("unknown type: ", type)
}
))
structure(
TRUE,
name = kwb.utils::shorten(max_chars = max_chars, kwb.utils::collapsed(
if (identical(type, "self")) {
deparse(x)
} else if (identical(type, "element_2")) {
deparse(x[[2L]])
} else if (identical(type, "parent")) {
deparse(parent)
} else {
stop("unknown type: ", type)
}
))
)
}
}

# is_true_or_false_constant ----------------------------------------------------
is_true_or_false_constant <- function(x)
# is_logical_constant_false ----------------------------------------------------
is_logical_constant_false <- function(x, type = "short")
{
is_logical_constant(x, type, use_true = FALSE)
}

# is_logical_constant_true -----------------------------------------------------
is_logical_constant_true <- function(x, type = "short")
{
is_logical_constant(x, type, use_false = FALSE)
}

# is_logical_constant ----------------------------------------------------------
is_logical_constant <- function(
x,
type = "short",
use_false = TRUE,
use_true = TRUE
)
{
if (!is.symbol(x)) {
return(FALSE)
}

deparse(x) %in% deparsed_logical_values(type, use_false, use_true)
}

# deparsed_logical_values ------------------------------------------------------
deparsed_logical_values <- function(
type = c("short", "long", "either")[3L],
use_false = TRUE,
use_true = TRUE
)
{
values <- c("F", "T", "FALSE", "TRUE")
use_false_true <- c(use_false, use_true)

deparse(x) %in% c("T", "F")
if (type == "short") {
values[1:2][use_false_true]
} else if (type == "long") {
values[3:4][use_false_true]
} else if (type == "either") {
values[rep(use_false_true, 2L)]
} else {
stop("Unknown type: ", type)
}
}

# is_colon_seq_1_to_length -----------------------------------------------------
Expand Down Expand Up @@ -152,6 +203,34 @@ is_bad_function_name <- function(x)
grepl("\\.", deparse(function_name))
}


# is_comparison_with_false -----------------------------------------------------
is_comparison_with_false <- function(x)
{
is_comparison_with_logical(x, use_true = FALSE)
}

# is_comparison_with_true ------------------------------------------------------
is_comparison_with_true <- function(x)
{
is_comparison_with_logical(x, use_false = FALSE)
}

# is_comparison_with_logical ---------------------------------------------------
is_comparison_with_logical <- function(x, use_false = TRUE, use_true = TRUE)
{
if (!is.call(x)) {
return(FALSE)
}

operator <- deparse(x[[1]])

operator %in% c("==", "!=") && (
is_logical_constant(x[[2]], type = "either", use_false, use_true) ||
is_logical_constant(x[[3]], type = "either", use_false, use_true)
)
}

# summarise_extracted_matches --------------------------------------------------
summarise_extracted_matches <- function(x)
{
Expand Down

0 comments on commit 24074e9

Please sign in to comment.