Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
5 changes: 3 additions & 2 deletions DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -14,12 +14,13 @@ License: MIT + file LICENSE
URL: https://jsonedit.r-lib.org
Imports:
cli,
jsonlite,
rlang (>= 1.1.0),
V8
V8 (>= 6.0.5.9000)
Suggests:
testthat (>= 3.0.0)
Config/testthat/edition: 3
Encoding: UTF-8
Roxygen: list(markdown = TRUE)
RoxygenNote: 7.3.2
Remotes:
jeroen/V8
65 changes: 17 additions & 48 deletions R/parse.R
Original file line number Diff line number Diff line change
Expand Up @@ -78,8 +78,15 @@ text_parse <- function(text, ..., parse_options = NULL) {
check_string(text)
parse_options <- parse_options %||% parse_options()
check_no_text_parse_errors("parse", text, parse_options = parse_options)
out <- js_call(jsonc, "ffi_text_parse", text, parse_options)
out

# In particular, JSON arrays can have mixed types like `[1, "a"]` and we
# don't want those to be forcibly simplified to `c("1", "a")` on the way in.
#
# We don't need this for every function, but when we parse a JSON file
# we want predictable output, and for us that means no simplification
simplify <- FALSE

jsonc$call("ffi_text_parse", text, parse_options, simplify = simplify)
}

#' @rdname parse
Expand All @@ -98,8 +105,13 @@ text_parse_at_path <- function(text, path, ..., parse_options = NULL) {
path <- check_and_normalize_path(path)
parse_options <- parse_options %||% parse_options()
check_no_text_parse_errors("parse", text, parse_options = parse_options)
out <- js_call(jsonc, "ffi_text_parse_at_path", text, path, parse_options)
out
jsonc$call(
"ffi_text_parse_at_path",
text,
path,
parse_options,
simplify = FALSE
)
}

#' @rdname parse
Expand Down Expand Up @@ -141,7 +153,7 @@ text_parse_errors <- function(text, ..., parse_options = NULL) {
check_dots_empty0(...)
check_string(text, .internal = TRUE)
parse_options <- parse_options %||% parse_options()
js_call(jsonc, "ffi_text_parse_errors", text, parse_options)
jsonc$call("ffi_text_parse_errors", text, parse_options, simplify = FALSE)
}

check_no_text_parse_errors <- function(
Expand Down Expand Up @@ -253,46 +265,3 @@ error_code_to_error_message <- function(code) {

lookup[[code]]
}

# Call a JavaScript function
#
# This is `jsonc$call()` but with two changes:
# - A `NULL` returns visibly
# - The conversion from JSON does NO simplification
#
# In particular, JSON arrays can have mixed types like `[1, "a"]` and we
# don't want those to be forcibly simplified to `c("1", "a")` on the way in.
#
# We don't need this for every function, but when we parse a JSON file
# we want predictable output, and for us that means no simplification
js_call <- function(context, fun, ...) {
args <- list(...)

if (!is.null(names(args))) {
stop("Named arguments are not supported in JavaScript.")
}

args <- vapply(
args,
function(x) jsonlite::toJSON(x, auto_unbox = TRUE),
character(1)
)

args <- paste(args, collapse = ",")
src <- paste0("(", fun, ")(", args, ");")

out <- context$eval(src, serialize = TRUE, await = FALSE)

if (is.null(out)) {
# A JavaScript `undefined` becomes `NULL` and `fromJSON()` doesn't want that
NULL
} else {
# Otherwise, assume JSON but DON'T SIMPLIFY for stability and predictability
jsonlite::fromJSON(
out,
simplifyVector = FALSE,
simplifyDataFrame = FALSE,
simplifyMatrix = FALSE
)
}
}
2 changes: 1 addition & 1 deletion inst/js/parse.js
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,7 @@ function ffi_text_parse_at_path(text, path, parse_options) {
if (node) {
return get_node_value(node);
} else {
return undefined;
return null;
}
}

Expand Down
19 changes: 19 additions & 0 deletions tests/testthat/test-parse.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,25 @@ test_that("empty file parsing works", {
expect_identical(text_parse_at_path("", "a"), NULL)
})

test_that("Output is always returned visibly", {
expect_identical(withVisible(text_parse("{}"))$visible, TRUE)
expect_identical(
withVisible(text_parse_at_path('{ "a": 1 }', "a"))$visible,
TRUE
)

# These must return visible `NULL`
expect_identical(withVisible(text_parse(""))$visible, TRUE)
expect_identical(withVisible(text_parse_at_path("", "a"))$visible, TRUE)

# These must return visible `NULL`
expect_identical(withVisible(text_parse("null"))$visible, TRUE)
expect_identical(
withVisible(text_parse_at_path('{ "a": null }', "a"))$visible,
TRUE
)
})

test_that("works outside of a base object `{`", {
expect_identical(text_parse("1"), 1L)
expect_identical(text_parse("1.5"), 1.5)
Expand Down
Loading