From 2c29aaac34a0fca69e1d2c781e8dc7db93e57c67 Mon Sep 17 00:00:00 2001 From: Martin Morgan Date: Wed, 27 Dec 2023 19:06:16 -0500 Subject: [PATCH 1/7] introduce j_query(); rename jsonpivot() to j_pivot() --- R/as_r.R | 6 +- R/cpp11.R | 4 +- R/j_query.R | 154 ++++++++++++++++++++++++++ R/{jsoncons.R => paths_and_pointer.R} | 63 ++--------- R/utilities.R | 5 + src/cpp11.cpp | 8 +- src/jsonpivot.h | 4 +- src/rjsoncons.cpp | 10 +- 8 files changed, 185 insertions(+), 69 deletions(-) create mode 100644 R/j_query.R rename R/{jsoncons.R => paths_and_pointer.R} (66%) diff --git a/R/as_r.R b/R/as_r.R index d68effb..562bb6d 100644 --- a/R/as_r.R +++ b/R/as_r.R @@ -8,9 +8,9 @@ #' #' @details #' -#' The `as = "R"` argument to `jsonpath()`, `jmespath()` and -#' `jsonpivot()`, and the `as_r()` function transform a JSON string -#' representation to an *R* object. Main rules are: +#' The `as = "R"` argument to `j_query()`, `j_pivot()`, etc., and the +#' `as_r()` function transform a JSON string representation to an *R* +#' object. Main rules are: #' #' - JSON arrays of a single type (boolean, integer, double, string) #' are transformed to *R* vectors of the same length and diff --git a/R/cpp11.R b/R/cpp11.R index 4a689bb..293793f 100644 --- a/R/cpp11.R +++ b/R/cpp11.R @@ -16,8 +16,8 @@ cpp_jsonpointer <- function(data, path, jtype, as) { .Call(`_rjsoncons_cpp_jsonpointer`, data, path, jtype, as) } -cpp_jsonpivot <- function(data, jtype, as) { - .Call(`_rjsoncons_cpp_jsonpivot`, data, jtype, as) +cpp_j_pivot <- function(data, jtype, as) { + .Call(`_rjsoncons_cpp_j_pivot`, data, jtype, as) } cpp_as_r <- function(data, jtype) { diff --git a/R/j_query.R b/R/j_query.R new file mode 100644 index 0000000..5025868 --- /dev/null +++ b/R/j_query.R @@ -0,0 +1,154 @@ +#' @rdname j_query +#' +#' @title Query and pivot for JSON documents +#' +#' @description `j_query()` executes a query against a JSON +#' document, automatically inferring the type of `path`. +#' +#' @param as character(1) return type. For `j_query()`, `"string"` +#' returns a single JSON string; `"R"` parses the JSON to R using +#' rules in `as_r()`. For `j_pivot()`, use `as = "data.frame"` or +#' `as = "tibble"` to coerce the result to a data.frame or tibble. +#' +#' @inheritParams jsonpath +#' +#' @examples +#' json <- '{ +#' "locations": [ +#' {"name": "Seattle", "state": "WA"}, +#' {"name": "New York", "state": "NY"}, +#' {"name": "Bellevue", "state": "WA"}, +#' {"name": "Olympia", "state": "WA"} +#' ] +#' }' +#' +#' j_query(json, "/locations/0/name") # JSONpointer +#' j_query(json, "$.locations[*].name", as = "R") # JSONpath +#' j_query(json, "locations[].state", as = "R") # JMESpath +#' +#' @export +j_query <- + function(data, path, object_names = "asis", as = "string", ...) +{ + stopifnot( + as %in% c("string", "R") + ) + + FUN <- switch( + j_path_type(path), + JSONpointer = jsonpointer, + JSONpath = jsonpath, + JMESpath = jmespath + ) + FUN(data, path, object_names = object_names, as = as, ...) +} + +j_pivot_impl <- + function(data, object_names = "asis", as = "string", ...) +{ + stopifnot( + .is_scalar_character(object_names), + .is_scalar_character(as) + ) + + data <- .as_json_string(data, ...) + cpp_j_pivot(data, object_names, as) +} + + +#' @rdname j_query +#' +#' @description `j_pivot()` transforms a JSON array-of-objects to an +#' object-of-arrays; this can be useful when forming a +#' column-based tibble from row-oriented JSON. +#' +#' @details +#' +#' `j_pivot()` transforms an 'array-of-objects' (typical when the +#' JSON is a row-oriented representation of a table) to an +#' 'object-of-arrays'. A simple example transforms an array of two +#' objects each with three fields `'[{"a": 1, "b": 2, "c": 3}, {"a": +#' 4, "b": 5, "c": 6}]'` to an object with with three fields, each a +#' vector of length 2 `'{"a": [1, 4], "b": [2, 5], "c": [3, 6]}'`. The +#' object-of-arrays representation corresponds closely to an _R_ +#' data.frame or tibble, as illustrated in the examples. +#' +#' @examples +#' j_pivot(json, "$.locations[?@.state=='WA']", as = "string") +#' j_pivot(json, "locations[?@.state=='WA']", as = "R") +#' j_pivot(json, "locations[?@.state=='WA']", as = "data.frame") +#' j_pivot(json, "locations[?@.state=='WA']", as = "tibble") +#' +#' @export +j_pivot <- + function(data, path, object_names = "asis", as = "string", ...) +{ + stopifnot( + as %in% c("string", "R", "data.frame", "tibble") + ) + + if (!missing(path)) + data <- j_query(data, path, object_names, as = "string", ...) + + switch( + as, + string = j_pivot_impl(data, object_names, as = "string", ...), + R = j_pivot_impl(data, object_names, as = "R", ...), + data.frame = + j_pivot_impl(data, object_names, as = "R", ...) |> + as.data.frame(), + tibble = + j_pivot_impl(data, object_names, as = "R", ...) |> + tibble::as_tibble() + ) +} + +#' @rdname j_query +#' +#' @description `j_path_type()` uses simple rules to identify +#' whether `path` is a JSONpointer, JSONpath, or JMESpath +#' expression. +#' +#' @details +#' +#' `j_path_type()` infers the type of `path` using a simple but +#' incomplete calssification: +#' +#' - `"JSONpointer"` is infered if the the path is `""` or starts with `"/"`. +#' - `"JSONpath"` expressions start with `"$"`. +#' - `"JMESpath"` expressions satisfy niether the `JSONpointer` nor +#' `JSONpath` criteria. +#' +#' Because of these rules, the valid JSONpointer path `"@"` is +#' interpretted as JMESpath; use `jsonpointer()` if JSONpointer +#' behavior is required. +#' +#' @param path `character(1)` used to query the JSON document. +#' +#' @examples +#' j_path_type("") +#' j_path_type("/locations/0/name") +#' j_path_type("$.locations[0].name") +#' j_path_type("locations[0].name") +#' +#' @export +j_path_type <- + function(path) +{ + stopifnot( + .is_scalar_nchar_0(path) || .is_scalar_character(path) + ) + + path <- trimws(path) + if (.is_scalar_nchar_0(path)) { + "JSONpointer" + } else { + switch( + substring(path, 1, 1), + "/" = "JSONpointer", + "$" = "JSONpath", + "JMESpath" + ) + } +} + diff --git a/R/jsoncons.R b/R/paths_and_pointer.R similarity index 66% rename from R/jsoncons.R rename to R/paths_and_pointer.R index 0a632b6..96ca7b8 100644 --- a/R/jsoncons.R +++ b/R/paths_and_pointer.R @@ -1,16 +1,12 @@ -#' @rdname jsoncons +#' @rdname paths_and_pointer #' -#' @title Query JSON using the jsoncons C++ library +#' @title JSONpath, JMESpath, or JSONpointer query of JSON documents #' #' @description `jsonpath()` executes a query against a JSON string #' using the 'jsonpath' specification #' -#' @param data an _R_ object. If `data` is a scalar (length 1) -#' character vector, it is treated as a single JSON -#' string. Otherwise, it is parsed to a JSON string using -#' `jsonlite::toJSON()`. Use `I()` to treat a scalar character -#' vector as an _R_ object rather than JSON string, e.g., `I("A")` -#' will be parsed to `["A"]` before processing. +#' @param data a character(1) JSON string, or an *R* object parsed to +#' a JSON string using `jsonlite::toJSON()`. #' #' @param path character(1) jsonpath or jmespath query string. #' @@ -26,7 +22,7 @@ #' TRUE` to automatically 'unbox' vectors of length 1 to JSON #' scalar values. #' -#' @return `jsonpath()`, `jmespath()` and `jsonpivot()` return a +#' @return `jsonpath()`, `jmespath()` and `jsonpointer()` return a #' character(1) JSON string (`as = "string"`, default) or *R* #' object (`as = "R"`) representing the result of the query. #' @@ -66,8 +62,8 @@ #' #' ## different ordering of object names -- 'asis' (default) or 'sort' #' json_obj <- '{"b": "1", "a": "2"}' -#' jsonpath(json_obj, "$") |> cat("\n") -#' jsonpath(json_obj, "$.*") |> cat("\n") +#' jsonpath(json_obj, "$") |> cat("\n") +#' jsonpath(json_obj, "$.*") |> cat("\n") #' jsonpath(json_obj, "$", "sort") |> cat("\n") #' jsonpath(json_obj, "$.*", "sort") |> cat("\n") #' @@ -83,7 +79,7 @@ jsonpath <- cpp_jsonpath(data, path, object_names, as) } -#' @rdname jsoncons +#' @rdname paths_and_pointers #' #' @description `jmespath()` executes a query against a JSON string #' using the 'jmespath' specification. @@ -117,7 +113,7 @@ jmespath <- cpp_jmespath(data, path, object_names, as) } -#' @rdname jsoncons +#' @rdname paths_and_pointers #' #' @description `jsonpointer()` extracts an element from a JSON string #' using the 'JSON pointer' specification. @@ -138,49 +134,10 @@ jsonpointer <- function(data, path, object_names = "asis", as = "string", ...) { stopifnot( - identical(nchar(path), 0L) || .is_scalar_character(path), + .is_scalar_nchar_0(path)|| .is_scalar_character(path), .is_scalar_character(object_names), .is_scalar_character(as) ) data <- .as_json_string(data, ...) cpp_jsonpointer(data, path, object_names, as) } - -#' @rdname jsoncons -#' -#' @description `jsonpivot()` transforms a JSON array-of-objects to -#' an object-of-arrays; this can be useful when forming a -#' column-based tibble from row-oriented JSON. -#' -#' @details -#' -#' `jsonpivot()` transforms an 'array-of-objects' (typical when the -#' JSON is a row-oriented representation of a table) to an -#' 'object-of-arrays'. A simple example transforms an array of two -#' objects each with three fields `'[{"a": 1, "b": 2, "c": 3}, {"a": -#' 4, "b": 5, "c": 6}]'` to an object with with three fields, each a -#' vector of length 2 `'{"a": [1, 4], "b": [2, 5], "c": [3, 6]}'`. The -#' object-of-arrays representation corresponds closely to an _R_ -#' data.frame or tibble, as illustrated in the examples. -#' -#' @examples -#' json |> -#' ## 'locations' is a array of objects with 'name' and 'state' scalars... -#' jmespath("locations") |> -#' ## ...pivot to a single object with 'name' and 'state' vectors... -#' jsonpivot(as = "R") |> -#' ## ... easily coerced to a data.frame or dplyr::tibble -#' as.data.frame() -#' -#' @export -jsonpivot <- - function(data, object_names = "asis", as = "string", ...) -{ - stopifnot( - .is_scalar_character(object_names), - .is_scalar_character(as) - ) - - data <- .as_json_string(data, ...) - cpp_jsonpivot(data, object_names, as) -} diff --git a/R/utilities.R b/R/utilities.R index ff56fe5..8a01abe 100644 --- a/R/utilities.R +++ b/R/utilities.R @@ -10,6 +10,11 @@ .is_scalar(x) && is.character(x) && nzchar(x) } +.is_scalar_nchar_0 <- + function(x) +{ + .is_scalar(x) && is.character(x) && identical(nchar(x), 0L) +} .as_json_string <- function(x, ...) { diff --git a/src/cpp11.cpp b/src/cpp11.cpp index 76c3e84..19646c3 100644 --- a/src/cpp11.cpp +++ b/src/cpp11.cpp @@ -34,10 +34,10 @@ extern "C" SEXP _rjsoncons_cpp_jsonpointer(SEXP data, SEXP path, SEXP jtype, SEX END_CPP11 } // rjsoncons.cpp -sexp cpp_jsonpivot(std::string data, std::string jtype, std::string as); -extern "C" SEXP _rjsoncons_cpp_jsonpivot(SEXP data, SEXP jtype, SEXP as) { +sexp cpp_j_pivot(std::string data, std::string jtype, std::string as); +extern "C" SEXP _rjsoncons_cpp_j_pivot(SEXP data, SEXP jtype, SEXP as) { BEGIN_CPP11 - return cpp11::as_sexp(cpp_jsonpivot(cpp11::as_cpp>(data), cpp11::as_cpp>(jtype), cpp11::as_cpp>(as))); + return cpp11::as_sexp(cpp_j_pivot(cpp11::as_cpp>(data), cpp11::as_cpp>(jtype), cpp11::as_cpp>(as))); END_CPP11 } // rjsoncons.cpp @@ -51,9 +51,9 @@ extern "C" SEXP _rjsoncons_cpp_as_r(SEXP data, SEXP jtype) { extern "C" { static const R_CallMethodDef CallEntries[] = { {"_rjsoncons_cpp_as_r", (DL_FUNC) &_rjsoncons_cpp_as_r, 2}, + {"_rjsoncons_cpp_j_pivot", (DL_FUNC) &_rjsoncons_cpp_j_pivot, 3}, {"_rjsoncons_cpp_jmespath", (DL_FUNC) &_rjsoncons_cpp_jmespath, 4}, {"_rjsoncons_cpp_jsonpath", (DL_FUNC) &_rjsoncons_cpp_jsonpath, 4}, - {"_rjsoncons_cpp_jsonpivot", (DL_FUNC) &_rjsoncons_cpp_jsonpivot, 3}, {"_rjsoncons_cpp_jsonpointer", (DL_FUNC) &_rjsoncons_cpp_jsonpointer, 4}, {"_rjsoncons_cpp_version", (DL_FUNC) &_rjsoncons_cpp_version, 0}, {NULL, NULL, 0} diff --git a/src/jsonpivot.h b/src/jsonpivot.h index f6d6abb..f609c00 100644 --- a/src/jsonpivot.h +++ b/src/jsonpivot.h @@ -51,7 +51,7 @@ Json pivot_array_as_object(const Json j) } template -Json jsonpivot(const Json j) +Json j_pivot(const Json j) { Json value; @@ -64,7 +64,7 @@ Json jsonpivot(const Json j) value = pivot_array_as_object(j); break; }; - default: cpp11::stop("`jsonpivot()` 'data' must be a JSON array"); + default: cpp11::stop("`j_pivot()` 'data' must be a JSON array"); }; return value; diff --git a/src/rjsoncons.cpp b/src/rjsoncons.cpp index 523e13a..a2ea296 100644 --- a/src/rjsoncons.cpp +++ b/src/rjsoncons.cpp @@ -111,19 +111,19 @@ sexp cpp_jsonpointer( // pivot template -sexp jsonpivot_impl(const std::string data, const std::string as) +sexp j_pivot_impl(const std::string data, const std::string as) { Json j = Json::parse(data); - Json result = jsonpivot(j); + Json result = j_pivot(j); return json_as(result, as); } [[cpp11::register]] -sexp cpp_jsonpivot(std::string data, std::string jtype, std::string as) +sexp cpp_j_pivot(std::string data, std::string jtype, std::string as) { switch(hash(jtype.c_str())) { - case hash("asis"): return jsonpivot_impl(data, as); - case hash("sort"): return jsonpivot_impl(data, as); + case hash("asis"): return j_pivot_impl(data, as); + case hash("sort"): return j_pivot_impl(data, as); default: cpp11::stop("unknown `object_names` = '" + jtype + "'`"); } } From 2c694cec3decf2c38c2bb6e1d15d78407c51a9a4 Mon Sep 17 00:00:00 2001 From: Martin Morgan Date: Wed, 27 Dec 2023 19:16:38 -0500 Subject: [PATCH 2/7] update documentation, tests for j_query(), j_pivot() --- DESCRIPTION | 2 +- NAMESPACE | 4 +- R/paths_and_pointer.R | 4 +- inst/tinytest/test_j_pivot_detail.R | 52 +++++++++++++ inst/tinytest/test_j_query.R | 73 ++++++++++++++++++ inst/tinytest/test_jsoncons.R | 2 +- inst/tinytest/test_jsonpivot.R | 52 ------------- man/as_r.Rd | 14 ++-- man/j_query.Rd | 91 +++++++++++++++++++++++ man/{jsoncons.Rd => paths_and_pointer.Rd} | 42 ++--------- vignettes/rjsoncons.Rmd | 14 +--- 11 files changed, 239 insertions(+), 111 deletions(-) create mode 100644 inst/tinytest/test_j_pivot_detail.R create mode 100644 inst/tinytest/test_j_query.R delete mode 100644 inst/tinytest/test_jsonpivot.R create mode 100644 man/j_query.Rd rename man/{jsoncons.Rd => paths_and_pointer.Rd} (65%) diff --git a/DESCRIPTION b/DESCRIPTION index 9595668..9e5b562 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -24,7 +24,7 @@ Description: The 'jsoncons' 'JSONpath' and 'JMESpath' queries into 'JSON' strings or 'R' objects. The 'jsoncons' library is also be easily linked to other packages for direct access to 'C++' functionality. -Suggests: jsonlite, tinytest, BiocStyle, knitr, rmarkdown +Suggests: jsonlite, tibble, tinytest, BiocStyle, knitr, rmarkdown License: BSL-1.0 LinkingTo: cpp11 NeedsCompilation: yes diff --git a/NAMESPACE b/NAMESPACE index 3419f1e..cd2fee9 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -1,9 +1,11 @@ # Generated by roxygen2: do not edit by hand export(as_r) +export(j_path_type) +export(j_pivot) +export(j_query) export(jmespath) export(jsonpath) -export(jsonpivot) export(jsonpointer) export(version) useDynLib(rjsoncons, .registration = TRUE) diff --git a/R/paths_and_pointer.R b/R/paths_and_pointer.R index 96ca7b8..8d18f05 100644 --- a/R/paths_and_pointer.R +++ b/R/paths_and_pointer.R @@ -79,7 +79,7 @@ jsonpath <- cpp_jsonpath(data, path, object_names, as) } -#' @rdname paths_and_pointers +#' @rdname paths_and_pointer #' #' @description `jmespath()` executes a query against a JSON string #' using the 'jmespath' specification. @@ -113,7 +113,7 @@ jmespath <- cpp_jmespath(data, path, object_names, as) } -#' @rdname paths_and_pointers +#' @rdname paths_and_pointer #' #' @description `jsonpointer()` extracts an element from a JSON string #' using the 'JSON pointer' specification. diff --git a/inst/tinytest/test_j_pivot_detail.R b/inst/tinytest/test_j_pivot_detail.R new file mode 100644 index 0000000..cc0d83f --- /dev/null +++ b/inst/tinytest/test_j_pivot_detail.R @@ -0,0 +1,52 @@ +expect_identical(j_pivot("null"), "null") +expect_identical(j_pivot('[]'), "{}") +expect_identical(j_pivot('[1]'), "{}") # no object names, so no fields... +expect_identical(j_pivot('[1, 2]'), "{}") +expect_identical(j_pivot('[{}]'), "{}") +expect_identical(j_pivot('[{"a": 1}]'), '{"a":[1]}') +expect_identical(j_pivot('[{"a": 1, "b": 2}]'), '{"a":[1],"b":[2]}') +expect_identical( + j_pivot('[{"a": 1, "b": 2},{"a": 3, "b": 4}]'), + '{"a":[1,3],"b":[2,4]}' +) +expect_identical( + j_pivot('[{"a": 1, "b": 2},{"a": 3, "b": null}]'), + '{"a":[1,3],"b":[2,null]}' +) + +## missing keys -- visit all objects and accumulate names +expect_identical( + j_pivot('[{"a": 1, "b": 2}, {"a": 3}]'), + '{"a":[1,3],"b":[2,null]}' +) +expect_identical( + j_pivot('[{"a": 1}, {"b": 2}]'), + '{"a":[1,null],"b":[null,2]}' +) +expect_identical( + j_pivot('[1, {"a": 2}, 3]'), + '{"a":[null,2,null]}' +) + +## object_names +expect_identical( + j_pivot('[{"a": 1, "z": 2, "m": 3}]', object_names = "asis"), + '{"a":[1],"z":[2],"m":[3]}' +) +expect_identical( + j_pivot('[{"a": 1, "z": 2, "m": 3}]', object_names = "sort"), + '{"a":[1],"m":[3],"z":[2]}' +) + +## errors +expect_error(j_pivot("1"), "`j_pivot\\(\\)` 'data' must be a JSON array") + +## as = "R" +expect_identical( + j_pivot('[{"a": 1, "b": 2}, {"a": 3, "b": 4}]', as = "R"), + list(a = c(1L, 3L), b = c(2L, 4L)) +) +expect_identical( + j_pivot('[{"a": 1, "b": 2}, {"a": 3}]', as = "R"), + list(a = c(1L, 3L), b = list(2L, NULL)) +) diff --git a/inst/tinytest/test_j_query.R b/inst/tinytest/test_j_query.R new file mode 100644 index 0000000..8cfe38e --- /dev/null +++ b/inst/tinytest/test_j_query.R @@ -0,0 +1,73 @@ +json <- '{ + "locations": [ + {"name": "Seattle", "state": "WA"}, + {"name": "New York", "state": "NY"}, + {"name": "Bellevue", "state": "WA"}, + {"name": "Olympia", "state": "WA"} + ] +}' + +## j_query + +expect_identical( + j_query(json, "/locations/0/name"), # JSONpointer + "Seattle" +) +expect_identical( + j_query(json, "$.locations[*].name"), # JSONpath + '["Seattle","New York","Bellevue","Olympia"]' + ) +expect_identical( + j_query(json, "locations[].name"), # JMESpath + '["Seattle","New York","Bellevue","Olympia"]' +) + +expect_identical( + j_query(json, "/locations/0", as = "R"), # JSONpointer + list(name = "Seattle", state = "WA") +) +expect_identical( + j_query(json, "$.locations[*].name", as = "R"), # JSONpath + c("Seattle", "New York", "Bellevue", "Olympia") +) +expect_identical( + j_query(json, "locations[].name", as = "R"), # JMESpath + c("Seattle", "New York", "Bellevue", "Olympia") +) + +## j_pivot + +expected_r <- list( + name = c("Seattle", "New York", "Bellevue", "Olympia"), + state = c("WA", "NY", "WA", "WA") +) + +expected_df <- structure( + expected_r, class = "data.frame", row.names = c(NA, -4L) +) + +expect_identical(j_pivot(json, "/locations", as = "R"), expected_r) +expect_identical(j_pivot(json, "/locations", as = "data.frame"), expected_df) + +expect_identical(j_pivot(json, "$.locations[*]", as = "R"), expected_r) +expect_identical(j_pivot(json, "$.locations[*]", as = "data.frame"), expected_df) + +expect_identical(j_pivot(json, "locations[]", as = "R"), expected_r) +expect_identical(j_pivot(json, "locations[]", as = "data.frame"), expected_df) + +expect_error(j_pivot(json, "/locations/0")) +expect_error(j_pivot(json, "/locations[0].name")) + +## j_path_type + +expect_identical(j_path_type(""), "JSONpointer") +expect_identical(j_path_type("/locations/0/name"), "JSONpointer") +expect_identical(j_path_type("$.locations[0].name"), "JSONpath") +expect_identical(j_path_type("locations[0].name"), "JMESpath") +expect_identical(j_path_type("@"), "JMESpath") + +expect_identical(j_path_type(" $.locations[0].name"), "JSONpath") + +expect_error(j_path_type(character())) +expect_error(j_path_type(c("", ""))) +expect_error(j_path_type(NA_character_)) diff --git a/inst/tinytest/test_jsoncons.R b/inst/tinytest/test_jsoncons.R index c67d17a..2f0c75a 100644 --- a/inst/tinytest/test_jsoncons.R +++ b/inst/tinytest/test_jsoncons.R @@ -151,6 +151,6 @@ expect_identical( expect_identical( ## as = "R" - jsonpointer(json, "/locations/0", as = "R") |> dput(), + jsonpointer(json, "/locations/0", as = "R"), list(name = "Seattle", state = "WA") ) diff --git a/inst/tinytest/test_jsonpivot.R b/inst/tinytest/test_jsonpivot.R deleted file mode 100644 index 8879319..0000000 --- a/inst/tinytest/test_jsonpivot.R +++ /dev/null @@ -1,52 +0,0 @@ -expect_identical(jsonpivot("null"), "null") -expect_identical(jsonpivot('[]'), "{}") -expect_identical(jsonpivot('[1]'), "{}") # no object names, so no fields... -expect_identical(jsonpivot('[1, 2]'), "{}") -expect_identical(jsonpivot('[{}]'), "{}") -expect_identical(jsonpivot('[{"a": 1}]'), '{"a":[1]}') -expect_identical(jsonpivot('[{"a": 1, "b": 2}]'), '{"a":[1],"b":[2]}') -expect_identical( - jsonpivot('[{"a": 1, "b": 2},{"a": 3, "b": 4}]'), - '{"a":[1,3],"b":[2,4]}' -) -expect_identical( - jsonpivot('[{"a": 1, "b": 2},{"a": 3, "b": null}]'), - '{"a":[1,3],"b":[2,null]}' -) - -## missing keys -- visit all objects and accumulate names -expect_identical( - jsonpivot('[{"a": 1, "b": 2}, {"a": 3}]'), - '{"a":[1,3],"b":[2,null]}' -) -expect_identical( - jsonpivot('[{"a": 1}, {"b": 2}]'), - '{"a":[1,null],"b":[null,2]}' -) -expect_identical( - jsonpivot('[1, {"a": 2}, 3]'), - '{"a":[null,2,null]}' -) - -## object_names -expect_identical( - jsonpivot('[{"a": 1, "z": 2, "m": 3}]', "asis"), - '{"a":[1],"z":[2],"m":[3]}' -) -expect_identical( - jsonpivot('[{"a": 1, "z": 2, "m": 3}]', "sort"), - '{"a":[1],"m":[3],"z":[2]}' -) - -## errors -expect_error(jsonpivot("1"), "`jsonpivot\\(\\)` 'data' must be a JSON array") - -## as = "R" -expect_identical( - jsonpivot('[{"a": 1, "b": 2}, {"a": 3, "b": 4}]', as = "R"), - list(a = c(1L, 3L), b = c(2L, 4L)) -) -expect_identical( - jsonpivot('[{"a": 1, "b": 2}, {"a": 3}]', as = "R"), - list(a = c(1L, 3L), b = list(2L, NULL)) -) diff --git a/man/as_r.Rd b/man/as_r.Rd index 4b99385..c6eed6c 100644 --- a/man/as_r.Rd +++ b/man/as_r.Rd @@ -7,12 +7,8 @@ as_r(data, object_names = "asis", ...) } \arguments{ -\item{data}{an \emph{R} object. If \code{data} is a scalar (length 1) -character vector, it is treated as a single JSON -string. Otherwise, it is parsed to a JSON string using -\code{jsonlite::toJSON()}. Use \code{I()} to treat a scalar character -vector as an \emph{R} object rather than JSON string, e.g., \code{I("A")} -will be parsed to \verb{["A"]} before processing.} +\item{data}{a character(1) JSON string, or an \emph{R} object parsed to +a JSON string using \code{jsonlite::toJSON()}.} \item{object_names}{character(1) order \code{data} object elements \code{"asis"} (default) or \code{"sort"} before filtering on \code{path}.} @@ -28,9 +24,9 @@ scalar values.} \code{as_r()} transforms a JSON string to an \emph{R} object. } \details{ -The \code{as = "R"} argument to \code{jsonpath()}, \code{jmespath()} and -\code{jsonpivot()}, and the \code{as_r()} function transform a JSON string -representation to an \emph{R} object. Main rules are: +The \code{as = "R"} argument to \code{j_query()}, \code{j_pivot()}, etc., and the +\code{as_r()} function transform a JSON string representation to an \emph{R} +object. Main rules are: \itemize{ \item JSON arrays of a single type (boolean, integer, double, string) are transformed to \emph{R} vectors of the same length and diff --git a/man/j_query.Rd b/man/j_query.Rd new file mode 100644 index 0000000..7883045 --- /dev/null +++ b/man/j_query.Rd @@ -0,0 +1,91 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/j_query.R +\name{j_query} +\alias{j_query} +\alias{j_pivot} +\alias{j_path_type} +\title{Query and pivot for JSON documents} +\usage{ +j_query(data, path, object_names = "asis", as = "string", ...) + +j_pivot(data, path, object_names = "asis", as = "string", ...) + +j_path_type(path) +} +\arguments{ +\item{data}{a character(1) JSON string, or an \emph{R} object parsed to +a JSON string using \code{jsonlite::toJSON()}.} + +\item{path}{\code{character(1)} used to query the JSON document.} + +\item{object_names}{character(1) order \code{data} object elements +\code{"asis"} (default) or \code{"sort"} before filtering on \code{path}.} + +\item{as}{character(1) return type. For \code{j_query()}, \code{"string"} +returns a single JSON string; \code{"R"} parses the JSON to R using +rules in \code{as_r()}. For \code{j_pivot()}, use \code{as = "data.frame"} or +\code{as = "tibble"} to coerce the result to a data.frame or tibble.} + +\item{...}{arguments passed to \code{jsonlite::toJSON} when \code{data} is +not a scalar character vector. For example, use \code{auto_unbox = TRUE} to automatically 'unbox' vectors of length 1 to JSON +scalar values.} +} +\description{ +\code{j_query()} executes a query against a JSON +document, automatically inferring the type of \code{path}. + +\code{j_pivot()} transforms a JSON array-of-objects to an +object-of-arrays; this can be useful when forming a +column-based tibble from row-oriented JSON. + +\code{j_path_type()} uses simple rules to identify +whether \code{path} is a JSONpointer, JSONpath, or JMESpath +expression. +} +\details{ +\code{j_pivot()} transforms an 'array-of-objects' (typical when the +JSON is a row-oriented representation of a table) to an +'object-of-arrays'. A simple example transforms an array of two +objects each with three fields \code{'[{"a": 1, "b": 2, "c": 3}, {"a": 4, "b": 5, "c": 6}]'} to an object with with three fields, each a +vector of length 2 \code{'{"a": [1, 4], "b": [2, 5], "c": [3, 6]}'}. The +object-of-arrays representation corresponds closely to an \emph{R} +data.frame or tibble, as illustrated in the examples. + +\code{j_path_type()} infers the type of \code{path} using a simple but +incomplete calssification: +\itemize{ +\item \code{"JSONpointer"} is infered if the the path is \code{""} or starts with \code{"/"}. +\item \code{"JSONpath"} expressions start with \code{"$"}. +\item \code{"JMESpath"} expressions satisfy niether the \code{JSONpointer} nor +\code{JSONpath} criteria. +} + +Because of these rules, the valid JSONpointer path \code{"@"} is +interpretted as JMESpath; use \code{jsonpointer()} if JSONpointer +behavior is required. +} +\examples{ +json <- '{ + "locations": [ + {"name": "Seattle", "state": "WA"}, + {"name": "New York", "state": "NY"}, + {"name": "Bellevue", "state": "WA"}, + {"name": "Olympia", "state": "WA"} + ] +}' + +j_query(json, "/locations/0/name") # JSONpointer +j_query(json, "$.locations[*].name", as = "R") # JSONpath +j_query(json, "locations[].state", as = "R") # JMESpath + +j_pivot(json, "$.locations[?@.state=='WA']", as = "string") +j_pivot(json, "locations[?@.state=='WA']", as = "R") +j_pivot(json, "locations[?@.state=='WA']", as = "data.frame") +j_pivot(json, "locations[?@.state=='WA']", as = "tibble") + +j_path_type("") +j_path_type("/locations/0/name") +j_path_type("$.locations[0].name") +j_path_type("locations[0].name") + +} diff --git a/man/jsoncons.Rd b/man/paths_and_pointer.Rd similarity index 65% rename from man/jsoncons.Rd rename to man/paths_and_pointer.Rd index eb52158..e13c007 100644 --- a/man/jsoncons.Rd +++ b/man/paths_and_pointer.Rd @@ -1,27 +1,20 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/jsoncons.R +% Please edit documentation in R/paths_and_pointer.R \name{jsonpath} \alias{jsonpath} \alias{jmespath} \alias{jsonpointer} -\alias{jsonpivot} -\title{Query JSON using the jsoncons C++ library} +\title{JSONpath, JMESpath, or JSONpointer query of JSON documents} \usage{ jsonpath(data, path, object_names = "asis", as = "string", ...) jmespath(data, path, object_names = "asis", as = "string", ...) jsonpointer(data, path, object_names = "asis", as = "string", ...) - -jsonpivot(data, object_names = "asis", as = "string", ...) } \arguments{ -\item{data}{an \emph{R} object. If \code{data} is a scalar (length 1) -character vector, it is treated as a single JSON -string. Otherwise, it is parsed to a JSON string using -\code{jsonlite::toJSON()}. Use \code{I()} to treat a scalar character -vector as an \emph{R} object rather than JSON string, e.g., \code{I("A")} -will be parsed to \verb{["A"]} before processing.} +\item{data}{a character(1) JSON string, or an \emph{R} object parsed to +a JSON string using \code{jsonlite::toJSON()}.} \item{path}{character(1) jsonpath or jmespath query string.} @@ -37,7 +30,7 @@ not a scalar character vector. For example, use \code{auto_unbox = TRUE} to auto scalar values.} } \value{ -\code{jsonpath()}, \code{jmespath()} and \code{jsonpivot()} return a +\code{jsonpath()}, \code{jmespath()} and \code{jsonpointer()} return a character(1) JSON string (\code{as = "string"}, default) or \emph{R} object (\code{as = "R"}) representing the result of the query. } @@ -50,19 +43,6 @@ using the 'jmespath' specification. \code{jsonpointer()} extracts an element from a JSON string using the 'JSON pointer' specification. - -\code{jsonpivot()} transforms a JSON array-of-objects to -an object-of-arrays; this can be useful when forming a -column-based tibble from row-oriented JSON. -} -\details{ -\code{jsonpivot()} transforms an 'array-of-objects' (typical when the -JSON is a row-oriented representation of a table) to an -'object-of-arrays'. A simple example transforms an array of two -objects each with three fields \code{'[{"a": 1, "b": 2, "c": 3}, {"a": 4, "b": 5, "c": 6}]'} to an object with with three fields, each a -vector of length 2 \code{'{"a": [1, 4], "b": [2, 5], "c": [3, 6]}'}. The -object-of-arrays representation corresponds closely to an \emph{R} -data.frame or tibble, as illustrated in the examples. } \examples{ json <- '{ @@ -100,8 +80,8 @@ jsonpath(I("Seattle"), "$[0]") |> cat("\n") ## different ordering of object names -- 'asis' (default) or 'sort' json_obj <- '{"b": "1", "a": "2"}' -jsonpath(json_obj, "$") |> cat("\n") -jsonpath(json_obj, "$.*") |> cat("\n") +jsonpath(json_obj, "$") |> cat("\n") +jsonpath(json_obj, "$.*") |> cat("\n") jsonpath(json_obj, "$", "sort") |> cat("\n") jsonpath(json_obj, "$.*", "sort") |> cat("\n") @@ -130,12 +110,4 @@ jsonpointer('{"b": 0, "a": 1}', "", "sort", as = "R") |> ## 'Key not found' -- path '/' is searches for a 0-length key try(jsonpointer('{"b": 0, "a": 1}', "/")) -json |> - ## 'locations' is a array of objects with 'name' and 'state' scalars... - jmespath("locations") |> - ## ...pivot to a single object with 'name' and 'state' vectors... - jsonpivot(as = "R") |> - ## ... easily coerced to a data.frame or dplyr::tibble - as.data.frame() - } diff --git a/vignettes/rjsoncons.Rmd b/vignettes/rjsoncons.Rmd index 8946e19..4b3e43b 100644 --- a/vignettes/rjsoncons.Rmd +++ b/vignettes/rjsoncons.Rmd @@ -114,16 +114,10 @@ jmespath(json, path, as = "R") |> The transformation from JSON 'array-of-objects' to 'object-of-arrays' suitable for direct representation as a `data.frame` is common, and is -implemented directly as `jsonpivot()` - -```{r jsonpivot} -json |> - ## select the 'array-of-objects' portion of the JSON document - jmespath("locations") |> - ## pivot and return represenation as R named list-of-vectors - jsonpivot(as = "R") |> - ## coerce to data.frame, tibble, etc. - data.frame() +implemented directly as `j_pivot()` + +```{r j_pivot} +j_pivot(json, "locations", as = "data.frame") ``` [purrr]: https://CRAN.R-project.org/package=purrr From ea8ca4fdfe3d286fbe9ab0d84650c7a7e939879d Mon Sep 17 00:00:00 2001 From: Martin Morgan Date: Mon, 1 Jan 2024 08:41:23 -0500 Subject: [PATCH 3/7] implement j_query() directly in C++ --- R/cpp11.R | 4 +++ R/j_query.R | 36 +++++++++++++-------------- R/paths_and_pointer.R | 2 +- R/utilities.R | 9 ++----- inst/tinytest/test_utilities.R | 6 +++++ src/cpp11.cpp | 8 ++++++ src/rjsoncons.cpp | 45 ++++++++++++++++++++++++++++++++++ 7 files changed, 84 insertions(+), 26 deletions(-) create mode 100644 inst/tinytest/test_utilities.R diff --git a/R/cpp11.R b/R/cpp11.R index 293793f..55f535c 100644 --- a/R/cpp11.R +++ b/R/cpp11.R @@ -16,6 +16,10 @@ cpp_jsonpointer <- function(data, path, jtype, as) { .Call(`_rjsoncons_cpp_jsonpointer`, data, path, jtype, as) } +cpp_j_query <- function(data, path, object_names, as, path_type) { + .Call(`_rjsoncons_cpp_j_query`, data, path, object_names, as, path_type) +} + cpp_j_pivot <- function(data, jtype, as) { .Call(`_rjsoncons_cpp_j_pivot`, data, jtype, as) } diff --git a/R/j_query.R b/R/j_query.R index 5025868..2e0a40a 100644 --- a/R/j_query.R +++ b/R/j_query.R @@ -28,27 +28,28 @@ #' #' @export j_query <- - function(data, path, object_names = "asis", as = "string", ...) + function( + data, path = "", object_names = "asis", as = "string", ..., + path_type = j_path_type(path) + ) { stopifnot( - as %in% c("string", "R") + .is_scalar_character(path, z.ok = TRUE), + object_names %in% c("asis", "sort"), + as %in% c("string", "R"), + path_type %in% c("JSONpointer", "JSONpath", "JMESpath") ) - FUN <- switch( - j_path_type(path), - JSONpointer = jsonpointer, - JSONpath = jsonpath, - JMESpath = jmespath - ) - FUN(data, path, object_names = object_names, as = as, ...) + data <- .as_json_string(data, ...) + cpp_j_query(data, path, object_names, as, path_type) } j_pivot_impl <- function(data, object_names = "asis", as = "string", ...) { stopifnot( - .is_scalar_character(object_names), - .is_scalar_character(as) + object_names %in% c("asis", "sort"), + as %in% c("string", "R") ) data <- .as_json_string(data, ...) @@ -81,14 +82,13 @@ j_pivot_impl <- #' #' @export j_pivot <- - function(data, path, object_names = "asis", as = "string", ...) + function(data, path = "", object_names = "asis", as = "string", ...) { stopifnot( as %in% c("string", "R", "data.frame", "tibble") ) - if (!missing(path)) - data <- j_query(data, path, object_names, as = "string", ...) + data <- j_query(data, path, object_names, as = "string", ...) switch( as, @@ -136,19 +136,19 @@ j_path_type <- function(path) { stopifnot( - .is_scalar_nchar_0(path) || .is_scalar_character(path) + .is_scalar_character(path, z.ok = TRUE) ) path <- trimws(path) - if (.is_scalar_nchar_0(path)) { - "JSONpointer" - } else { + if (nzchar(path)) { switch( substring(path, 1, 1), "/" = "JSONpointer", "$" = "JSONpath", "JMESpath" ) + } else { + "JSONpointer" } } diff --git a/R/paths_and_pointer.R b/R/paths_and_pointer.R index 8d18f05..bc40c9b 100644 --- a/R/paths_and_pointer.R +++ b/R/paths_and_pointer.R @@ -134,7 +134,7 @@ jsonpointer <- function(data, path, object_names = "asis", as = "string", ...) { stopifnot( - .is_scalar_nchar_0(path)|| .is_scalar_character(path), + .is_scalar_character(path, z.ok = TRUE), .is_scalar_character(object_names), .is_scalar_character(as) ) diff --git a/R/utilities.R b/R/utilities.R index 8a01abe..9b44dc3 100644 --- a/R/utilities.R +++ b/R/utilities.R @@ -5,16 +5,11 @@ } .is_scalar_character <- - function(x) + function(x, z.ok = FALSE) { - .is_scalar(x) && is.character(x) && nzchar(x) + .is_scalar(x) && is.character(x) && (z.ok || nzchar(x)) } -.is_scalar_nchar_0 <- - function(x) -{ - .is_scalar(x) && is.character(x) && identical(nchar(x), 0L) -} .as_json_string <- function(x, ...) { diff --git a/inst/tinytest/test_utilities.R b/inst/tinytest/test_utilities.R new file mode 100644 index 0000000..5f32566 --- /dev/null +++ b/inst/tinytest/test_utilities.R @@ -0,0 +1,6 @@ +expect_true(.is_scalar_character("a")) +expect_false(.is_scalar_character(character())) +expect_false(.is_scalar_character(c("a", "b"))) +expect_false(.is_scalar_character(NA_character_)) +expect_false(.is_scalar_character("")) +expect_true(.is_scalar_character("", z.ok = TRUE)) diff --git a/src/cpp11.cpp b/src/cpp11.cpp index 19646c3..2a44b1d 100644 --- a/src/cpp11.cpp +++ b/src/cpp11.cpp @@ -34,6 +34,13 @@ extern "C" SEXP _rjsoncons_cpp_jsonpointer(SEXP data, SEXP path, SEXP jtype, SEX END_CPP11 } // rjsoncons.cpp +sexp cpp_j_query(const std::string data, const std::string path, const std::string object_names, const std::string as, const std::string path_type); +extern "C" SEXP _rjsoncons_cpp_j_query(SEXP data, SEXP path, SEXP object_names, SEXP as, SEXP path_type) { + BEGIN_CPP11 + return cpp11::as_sexp(cpp_j_query(cpp11::as_cpp>(data), cpp11::as_cpp>(path), cpp11::as_cpp>(object_names), cpp11::as_cpp>(as), cpp11::as_cpp>(path_type))); + END_CPP11 +} +// rjsoncons.cpp sexp cpp_j_pivot(std::string data, std::string jtype, std::string as); extern "C" SEXP _rjsoncons_cpp_j_pivot(SEXP data, SEXP jtype, SEXP as) { BEGIN_CPP11 @@ -52,6 +59,7 @@ extern "C" { static const R_CallMethodDef CallEntries[] = { {"_rjsoncons_cpp_as_r", (DL_FUNC) &_rjsoncons_cpp_as_r, 2}, {"_rjsoncons_cpp_j_pivot", (DL_FUNC) &_rjsoncons_cpp_j_pivot, 3}, + {"_rjsoncons_cpp_j_query", (DL_FUNC) &_rjsoncons_cpp_j_query, 5}, {"_rjsoncons_cpp_jmespath", (DL_FUNC) &_rjsoncons_cpp_jmespath, 4}, {"_rjsoncons_cpp_jsonpath", (DL_FUNC) &_rjsoncons_cpp_jsonpath, 4}, {"_rjsoncons_cpp_jsonpointer", (DL_FUNC) &_rjsoncons_cpp_jsonpointer, 4}, diff --git a/src/rjsoncons.cpp b/src/rjsoncons.cpp index a2ea296..6aa6415 100644 --- a/src/rjsoncons.cpp +++ b/src/rjsoncons.cpp @@ -108,6 +108,51 @@ sexp cpp_jsonpointer( } } +// query + +template +sexp j_query_impl( + const std::string data, const std::string path, + const std::string as, const std::string path_type) +{ + // parse data + Json j = Json::parse(data); + + // evaluate path + Json result; + switch(hash(path_type.c_str())) { + case hash("JSONpointer"): { + result = jsonpointer::get(j, path); + break; + } + case hash("JSONpath"): { + result = jsonpath::json_query(j, path); + break; + } + case hash("JMESpath"): { + result = jmespath::search(j, path); + break; + } + default: cpp11::stop("unknown `path_type` = '" + path_type + "'"); + } + + // translate result + return json_as(result, as); +} + +[[cpp11::register]] +sexp cpp_j_query( + const std::string data, const std::string path, + const std::string object_names, const std::string as, + const std::string path_type) +{ + switch(hash(object_names.c_str())) { + case hash("asis"): return j_query_impl(data, path, as, path_type); + case hash("sort"): return j_query_impl(data, path, as, path_type); + default: cpp11::stop("unknown `object_names` = '" + object_names + "'"); + } +} + // pivot template From 3de9dd9b01d42d1270c6a71b8901950d3e33f93e Mon Sep 17 00:00:00 2001 From: Martin Morgan Date: Mon, 1 Jan 2024 08:49:45 -0500 Subject: [PATCH 4/7] implement jmespath() etc. via j_query() - removes cpp_jmespath() etc entry points --- R/cpp11.R | 12 -------- R/paths_and_pointer.R | 23 ++------------- src/cpp11.cpp | 32 +++----------------- src/rjsoncons.cpp | 68 ------------------------------------------- 4 files changed, 7 insertions(+), 128 deletions(-) diff --git a/R/cpp11.R b/R/cpp11.R index 55f535c..bed6473 100644 --- a/R/cpp11.R +++ b/R/cpp11.R @@ -4,18 +4,6 @@ cpp_version <- function() { .Call(`_rjsoncons_cpp_version`) } -cpp_jsonpath <- function(data, path, jtype, as) { - .Call(`_rjsoncons_cpp_jsonpath`, data, path, jtype, as) -} - -cpp_jmespath <- function(data, path, jtype, as) { - .Call(`_rjsoncons_cpp_jmespath`, data, path, jtype, as) -} - -cpp_jsonpointer <- function(data, path, jtype, as) { - .Call(`_rjsoncons_cpp_jsonpointer`, data, path, jtype, as) -} - cpp_j_query <- function(data, path, object_names, as, path_type) { .Call(`_rjsoncons_cpp_j_query`, data, path, object_names, as, path_type) } diff --git a/R/paths_and_pointer.R b/R/paths_and_pointer.R index bc40c9b..9db21da 100644 --- a/R/paths_and_pointer.R +++ b/R/paths_and_pointer.R @@ -71,12 +71,7 @@ jsonpath <- function(data, path, object_names = "asis", as = "string", ...) { - stopifnot( - .is_scalar_character(path), - .is_scalar_character(object_names) - ) - data <- .as_json_string(data, ...) - cpp_jsonpath(data, path, object_names, as) + j_query(data, path, object_names, as, ..., path_type = "JSONpath") } #' @rdname paths_and_pointer @@ -104,13 +99,7 @@ jsonpath <- jmespath <- function(data, path, object_names = "asis", as = "string", ...) { - stopifnot( - .is_scalar_character(path), - .is_scalar_character(object_names), - .is_scalar_character(as) - ) - data <- .as_json_string(data, ...) - cpp_jmespath(data, path, object_names, as) + j_query(data, path, object_names, as, ..., path_type = "JMESpath") } #' @rdname paths_and_pointer @@ -133,11 +122,5 @@ jmespath <- jsonpointer <- function(data, path, object_names = "asis", as = "string", ...) { - stopifnot( - .is_scalar_character(path, z.ok = TRUE), - .is_scalar_character(object_names), - .is_scalar_character(as) - ) - data <- .as_json_string(data, ...) - cpp_jsonpointer(data, path, object_names, as) + j_query(data, path, object_names, as, ..., path_type = "JSONpointer") } diff --git a/src/cpp11.cpp b/src/cpp11.cpp index 2a44b1d..40b5bca 100644 --- a/src/cpp11.cpp +++ b/src/cpp11.cpp @@ -13,27 +13,6 @@ extern "C" SEXP _rjsoncons_cpp_version() { END_CPP11 } // rjsoncons.cpp -sexp cpp_jsonpath(std::string data, std::string path, std::string jtype, std::string as); -extern "C" SEXP _rjsoncons_cpp_jsonpath(SEXP data, SEXP path, SEXP jtype, SEXP as) { - BEGIN_CPP11 - return cpp11::as_sexp(cpp_jsonpath(cpp11::as_cpp>(data), cpp11::as_cpp>(path), cpp11::as_cpp>(jtype), cpp11::as_cpp>(as))); - END_CPP11 -} -// rjsoncons.cpp -sexp cpp_jmespath(std::string data, std::string path, std::string jtype, std::string as); -extern "C" SEXP _rjsoncons_cpp_jmespath(SEXP data, SEXP path, SEXP jtype, SEXP as) { - BEGIN_CPP11 - return cpp11::as_sexp(cpp_jmespath(cpp11::as_cpp>(data), cpp11::as_cpp>(path), cpp11::as_cpp>(jtype), cpp11::as_cpp>(as))); - END_CPP11 -} -// rjsoncons.cpp -sexp cpp_jsonpointer(std::string data, std::string path, std::string jtype, std::string as); -extern "C" SEXP _rjsoncons_cpp_jsonpointer(SEXP data, SEXP path, SEXP jtype, SEXP as) { - BEGIN_CPP11 - return cpp11::as_sexp(cpp_jsonpointer(cpp11::as_cpp>(data), cpp11::as_cpp>(path), cpp11::as_cpp>(jtype), cpp11::as_cpp>(as))); - END_CPP11 -} -// rjsoncons.cpp sexp cpp_j_query(const std::string data, const std::string path, const std::string object_names, const std::string as, const std::string path_type); extern "C" SEXP _rjsoncons_cpp_j_query(SEXP data, SEXP path, SEXP object_names, SEXP as, SEXP path_type) { BEGIN_CPP11 @@ -57,13 +36,10 @@ extern "C" SEXP _rjsoncons_cpp_as_r(SEXP data, SEXP jtype) { extern "C" { static const R_CallMethodDef CallEntries[] = { - {"_rjsoncons_cpp_as_r", (DL_FUNC) &_rjsoncons_cpp_as_r, 2}, - {"_rjsoncons_cpp_j_pivot", (DL_FUNC) &_rjsoncons_cpp_j_pivot, 3}, - {"_rjsoncons_cpp_j_query", (DL_FUNC) &_rjsoncons_cpp_j_query, 5}, - {"_rjsoncons_cpp_jmespath", (DL_FUNC) &_rjsoncons_cpp_jmespath, 4}, - {"_rjsoncons_cpp_jsonpath", (DL_FUNC) &_rjsoncons_cpp_jsonpath, 4}, - {"_rjsoncons_cpp_jsonpointer", (DL_FUNC) &_rjsoncons_cpp_jsonpointer, 4}, - {"_rjsoncons_cpp_version", (DL_FUNC) &_rjsoncons_cpp_version, 0}, + {"_rjsoncons_cpp_as_r", (DL_FUNC) &_rjsoncons_cpp_as_r, 2}, + {"_rjsoncons_cpp_j_pivot", (DL_FUNC) &_rjsoncons_cpp_j_pivot, 3}, + {"_rjsoncons_cpp_j_query", (DL_FUNC) &_rjsoncons_cpp_j_query, 5}, + {"_rjsoncons_cpp_version", (DL_FUNC) &_rjsoncons_cpp_version, 0}, {NULL, NULL, 0} }; } diff --git a/src/rjsoncons.cpp b/src/rjsoncons.cpp index 6aa6415..7cdd6b9 100644 --- a/src/rjsoncons.cpp +++ b/src/rjsoncons.cpp @@ -40,74 +40,6 @@ sexp json_as(Json j, std::string as) } } -// jsonpath - -template -sexp jsonpath_impl( - const std::string data, const std::string path, - const std::string as) -{ - Json j = Json::parse(data); - Json result = jsonpath::json_query(j, path); - return json_as(result, as); -} - -[[cpp11::register]] -sexp cpp_jsonpath( - std::string data, std::string path, std::string jtype, std::string as) -{ - switch(hash(jtype.c_str())) { - case hash("asis"): return jsonpath_impl(data, path, as); - case hash("sort"): return jsonpath_impl(data, path, as); - default: cpp11::stop("unknown `object_names = '" + jtype + "'`"); - } -} - -// jmespath - -template -sexp jmespath_impl( - const std::string data, const std::string path, const std::string as) -{ - Json j = Json::parse(data); - Json result = jmespath::search(j, path); - return json_as(result, as); -} - -[[cpp11::register]] -sexp cpp_jmespath( - std::string data, std::string path, std::string jtype, std::string as) -{ - switch(hash(jtype.c_str())) { - case hash("asis"): return jmespath_impl(data, path, as); - case hash("sort"): return jmespath_impl(data, path, as); - default: cpp11::stop("unknown `object_names = '" + jtype + "'`"); - } -} - -// jsonpointer - -template -sexp jsonpointer_impl( - const std::string data, const std::string path, const std::string as) -{ - Json j = Json::parse(data); - Json result = jsonpointer::get(j, path); - return json_as(result, as); -} - - -[[cpp11::register]] -sexp cpp_jsonpointer( - std::string data, std::string path, std::string jtype, std::string as) -{ - switch(hash(jtype.c_str())) { - case hash("asis"): return jsonpointer_impl(data, path, as); - case hash("sort"): return jsonpointer_impl(data, path, as); - default: cpp11::stop("unknown `object_names = '" + jtype + "'`"); - } -} - // query template From 81ee4ab59a6533057b45ded73d3a98631fc85d94 Mon Sep 17 00:00:00 2001 From: Martin Morgan Date: Mon, 1 Jan 2024 09:40:04 -0500 Subject: [PATCH 5/7] simplify j_pivot() implementation to query in C++ --- R/cpp11.R | 4 ++-- R/j_query.R | 35 +++++++++++------------------ src/cpp11.cpp | 8 +++---- src/rjsoncons.cpp | 56 +++++++++++++++++++++++------------------------ 4 files changed, 46 insertions(+), 57 deletions(-) diff --git a/R/cpp11.R b/R/cpp11.R index bed6473..285ea47 100644 --- a/R/cpp11.R +++ b/R/cpp11.R @@ -8,8 +8,8 @@ cpp_j_query <- function(data, path, object_names, as, path_type) { .Call(`_rjsoncons_cpp_j_query`, data, path, object_names, as, path_type) } -cpp_j_pivot <- function(data, jtype, as) { - .Call(`_rjsoncons_cpp_j_pivot`, data, jtype, as) +cpp_j_pivot <- function(data, path, object_names, as, path_type) { + .Call(`_rjsoncons_cpp_j_pivot`, data, path, object_names, as, path_type) } cpp_as_r <- function(data, jtype) { diff --git a/R/j_query.R b/R/j_query.R index 2e0a40a..e5ed5f7 100644 --- a/R/j_query.R +++ b/R/j_query.R @@ -44,19 +44,6 @@ j_query <- cpp_j_query(data, path, object_names, as, path_type) } -j_pivot_impl <- - function(data, object_names = "asis", as = "string", ...) -{ - stopifnot( - object_names %in% c("asis", "sort"), - as %in% c("string", "R") - ) - - data <- .as_json_string(data, ...) - cpp_j_pivot(data, object_names, as) -} - - #' @rdname j_query #' #' @description `j_pivot()` transforms a JSON array-of-objects to an @@ -82,23 +69,28 @@ j_pivot_impl <- #' #' @export j_pivot <- - function(data, path = "", object_names = "asis", as = "string", ...) + function( + data, path = "", object_names = "asis", as = "string", ..., + path_type = j_path_type(path) + ) { stopifnot( - as %in% c("string", "R", "data.frame", "tibble") + .is_scalar_character(path, z.ok = TRUE), + object_names %in% c("asis", "sort"), + as %in% c("string", "R", "data.frame", "tibble"), + path_type %in% c("JSONpointer", "JSONpath", "JMESpath") ) - data <- j_query(data, path, object_names, as = "string", ...) - + data <- .as_json_string(data, ...) switch( as, - string = j_pivot_impl(data, object_names, as = "string", ...), - R = j_pivot_impl(data, object_names, as = "R", ...), + string = cpp_j_pivot(data, path, object_names, as, path_type), + R = cpp_j_pivot(data, path, object_names, as = "R", path_type), data.frame = - j_pivot_impl(data, object_names, as = "R", ...) |> + cpp_j_pivot(data, path, object_names, as = "R", path_type) |> as.data.frame(), tibble = - j_pivot_impl(data, object_names, as = "R", ...) |> + cpp_j_pivot(data, path, object_names, as = "R", path_type) |> tibble::as_tibble() ) } @@ -151,4 +143,3 @@ j_path_type <- "JSONpointer" } } - diff --git a/src/cpp11.cpp b/src/cpp11.cpp index 40b5bca..0d432fd 100644 --- a/src/cpp11.cpp +++ b/src/cpp11.cpp @@ -20,10 +20,10 @@ extern "C" SEXP _rjsoncons_cpp_j_query(SEXP data, SEXP path, SEXP object_names, END_CPP11 } // rjsoncons.cpp -sexp cpp_j_pivot(std::string data, std::string jtype, std::string as); -extern "C" SEXP _rjsoncons_cpp_j_pivot(SEXP data, SEXP jtype, SEXP as) { +sexp cpp_j_pivot(const std::string data, const std::string path, const std::string object_names, const std::string as, const std::string path_type); +extern "C" SEXP _rjsoncons_cpp_j_pivot(SEXP data, SEXP path, SEXP object_names, SEXP as, SEXP path_type) { BEGIN_CPP11 - return cpp11::as_sexp(cpp_j_pivot(cpp11::as_cpp>(data), cpp11::as_cpp>(jtype), cpp11::as_cpp>(as))); + return cpp11::as_sexp(cpp_j_pivot(cpp11::as_cpp>(data), cpp11::as_cpp>(path), cpp11::as_cpp>(object_names), cpp11::as_cpp>(as), cpp11::as_cpp>(path_type))); END_CPP11 } // rjsoncons.cpp @@ -37,7 +37,7 @@ extern "C" SEXP _rjsoncons_cpp_as_r(SEXP data, SEXP jtype) { extern "C" { static const R_CallMethodDef CallEntries[] = { {"_rjsoncons_cpp_as_r", (DL_FUNC) &_rjsoncons_cpp_as_r, 2}, - {"_rjsoncons_cpp_j_pivot", (DL_FUNC) &_rjsoncons_cpp_j_pivot, 3}, + {"_rjsoncons_cpp_j_pivot", (DL_FUNC) &_rjsoncons_cpp_j_pivot, 5}, {"_rjsoncons_cpp_j_query", (DL_FUNC) &_rjsoncons_cpp_j_query, 5}, {"_rjsoncons_cpp_version", (DL_FUNC) &_rjsoncons_cpp_version, 0}, {NULL, NULL, 0} diff --git a/src/rjsoncons.cpp b/src/rjsoncons.cpp index 7cdd6b9..29ef58e 100644 --- a/src/rjsoncons.cpp +++ b/src/rjsoncons.cpp @@ -43,32 +43,24 @@ sexp json_as(Json j, std::string as) // query template -sexp j_query_impl( - const std::string data, const std::string path, - const std::string as, const std::string path_type) +Json j_query_eval(Json j, const std::string path, const std::string path_type) { - // parse data - Json j = Json::parse(data); - // evaluate path - Json result; switch(hash(path_type.c_str())) { - case hash("JSONpointer"): { - result = jsonpointer::get(j, path); - break; - } - case hash("JSONpath"): { - result = jsonpath::json_query(j, path); - break; - } - case hash("JMESpath"): { - result = jmespath::search(j, path); - break; - } + case hash("JSONpointer"): return jsonpointer::get(j, path); + case hash("JSONpath"): return jsonpath::json_query(j, path); + case hash("JMESpath"): return jmespath::search(j, path); default: cpp11::stop("unknown `path_type` = '" + path_type + "'"); } +} - // translate result +template +sexp j_query_impl( + const std::string data, const std::string path, + const std::string as, const std::string path_type) +{ + Json j = Json::parse(data); + Json result = j_query_eval(j, path, path_type); return json_as(result, as); } @@ -81,27 +73,33 @@ sexp cpp_j_query( switch(hash(object_names.c_str())) { case hash("asis"): return j_query_impl(data, path, as, path_type); case hash("sort"): return j_query_impl(data, path, as, path_type); - default: cpp11::stop("unknown `object_names` = '" + object_names + "'"); + default: cpp11::stop("unknown `object_names = '" + object_names + "'`"); } } // pivot template -sexp j_pivot_impl(const std::string data, const std::string as) +sexp j_pivot_impl( + const std::string data, const std::string path, + const std::string as, const std::string path_type) { Json j = Json::parse(data); - Json result = j_pivot(j); - return json_as(result, as); + Json query = j_query_eval(j, path, path_type); + Json pivot = j_pivot(query); + return json_as(pivot, as); } [[cpp11::register]] -sexp cpp_j_pivot(std::string data, std::string jtype, std::string as) +sexp cpp_j_pivot( + const std::string data, const std::string path, + const std::string object_names, const std::string as, + const std::string path_type) { - switch(hash(jtype.c_str())) { - case hash("asis"): return j_pivot_impl(data, as); - case hash("sort"): return j_pivot_impl(data, as); - default: cpp11::stop("unknown `object_names` = '" + jtype + "'`"); + switch(hash(object_names.c_str())) { + case hash("asis"): return j_pivot_impl(data, path, as, path_type); + case hash("sort"): return j_pivot_impl(data, path, as, path_type); + default: cpp11::stop("unknown `object_names = '" + object_names + "'`"); } } From bfef7ce4b7503a144506ad4813649259ead79c6a Mon Sep 17 00:00:00 2001 From: Martin Morgan Date: Mon, 1 Jan 2024 09:40:48 -0500 Subject: [PATCH 6/7] minor documentation and unit test updates --- R/j_query.R | 4 +++ R/paths_and_pointer.R | 2 +- inst/tinytest/test_j_query.R | 9 +++++ inst/tinytest/test_utilities.R | 2 ++ man/j_query.Rd | 22 +++++++++++-- man/paths_and_pointer.Rd | 2 +- vignettes/rjsoncons.Rmd | 60 ++++++++++++++++++---------------- 7 files changed, 69 insertions(+), 32 deletions(-) diff --git a/R/j_query.R b/R/j_query.R index e5ed5f7..6a4101a 100644 --- a/R/j_query.R +++ b/R/j_query.R @@ -12,6 +12,10 @@ #' #' @inheritParams jsonpath #' +#' @param path_type character(1) type of `path`; one of +#' `"JSONpointer"`, `"JSONpath"`, `"JMESpath"`. Inferred from +#' `path` using `j_path_type()`. +#' #' @examples #' json <- '{ #' "locations": [ diff --git a/R/paths_and_pointer.R b/R/paths_and_pointer.R index 9db21da..f432b31 100644 --- a/R/paths_and_pointer.R +++ b/R/paths_and_pointer.R @@ -115,7 +115,7 @@ jmespath <- #' jsonpointer('{"b": 0, "a": 1}', "", "sort", as = "R") |> #' str() #' -#' ## 'Key not found' -- path '/' is searches for a 0-length key +#' ## 'Key not found' -- path '/' searches for a 0-length key #' try(jsonpointer('{"b": 0, "a": 1}', "/")) #' #' @export diff --git a/inst/tinytest/test_j_query.R b/inst/tinytest/test_j_query.R index 8cfe38e..e00b055 100644 --- a/inst/tinytest/test_j_query.R +++ b/inst/tinytest/test_j_query.R @@ -7,8 +7,17 @@ json <- '{ ] }' +json_pretty <- # remove whitespace + '{"locations":[{"name":"Seattle","state":"WA"},{"name":"New York","state":"NY"},{"name":"Bellevue","state":"WA"},{"name":"Olympia","state":"WA"}]}' + ## j_query +expect_identical(j_query(""), '[""]') # JSONpointer +expect_identical(j_query('""'), '') +expect_identical(j_query('[]'), '[]') +expect_identical(j_query('{}'), '{}') +expect_identical(j_query(json), json_pretty) + expect_identical( j_query(json, "/locations/0/name"), # JSONpointer "Seattle" diff --git a/inst/tinytest/test_utilities.R b/inst/tinytest/test_utilities.R index 5f32566..cb09233 100644 --- a/inst/tinytest/test_utilities.R +++ b/inst/tinytest/test_utilities.R @@ -1,3 +1,5 @@ +.is_scalar_character <- rjsoncons:::.is_scalar_character + expect_true(.is_scalar_character("a")) expect_false(.is_scalar_character(character())) expect_false(.is_scalar_character(c("a", "b"))) diff --git a/man/j_query.Rd b/man/j_query.Rd index 7883045..2c4c9da 100644 --- a/man/j_query.Rd +++ b/man/j_query.Rd @@ -6,9 +6,23 @@ \alias{j_path_type} \title{Query and pivot for JSON documents} \usage{ -j_query(data, path, object_names = "asis", as = "string", ...) +j_query( + data, + path = "", + object_names = "asis", + as = "string", + ..., + path_type = j_path_type(path) +) -j_pivot(data, path, object_names = "asis", as = "string", ...) +j_pivot( + data, + path = "", + object_names = "asis", + as = "string", + ..., + path_type = j_path_type(path) +) j_path_type(path) } @@ -29,6 +43,10 @@ rules in \code{as_r()}. For \code{j_pivot()}, use \code{as = "data.frame"} or \item{...}{arguments passed to \code{jsonlite::toJSON} when \code{data} is not a scalar character vector. For example, use \code{auto_unbox = TRUE} to automatically 'unbox' vectors of length 1 to JSON scalar values.} + +\item{path_type}{character(1) type of \code{path}; one of +\code{"JSONpointer"}, \code{"JSONpath"}, \code{"JMESpath"}. Inferred from +\code{path} using \code{j_path_type()}.} } \description{ \code{j_query()} executes a query against a JSON diff --git a/man/paths_and_pointer.Rd b/man/paths_and_pointer.Rd index e13c007..a0edaeb 100644 --- a/man/paths_and_pointer.Rd +++ b/man/paths_and_pointer.Rd @@ -107,7 +107,7 @@ jsonpointer(json, "/locations/0/name") jsonpointer('{"b": 0, "a": 1}', "", "sort", as = "R") |> str() -## 'Key not found' -- path '/' is searches for a 0-length key +## 'Key not found' -- path '/' searches for a 0-length key try(jsonpointer('{"b": 0, "a": 1}', "/")) } diff --git a/vignettes/rjsoncons.Rmd b/vignettes/rjsoncons.Rmd index 4b3e43b..38a562e 100644 --- a/vignettes/rjsoncons.Rmd +++ b/vignettes/rjsoncons.Rmd @@ -34,13 +34,13 @@ the package for direct access to the 'jsoncons' C++ library. Install the released package version from CRAN -```{r, eval = FALSE} +```{r install, eval = FALSE} install.pacakges("rjsoncons", repos = "https://CRAN.R-project.org") ``` Install the development version with -```{r, eval = FALSE} +```{r install_github, eval = FALSE} if (!requireNamespace("remotes", quiety = TRUE)) install.packages("remotes", repos = "https://CRAN.R-project.org") remotes::install_github("mtmorgan/rjsoncons") @@ -49,7 +49,7 @@ remotes::install_github("mtmorgan/rjsoncons") Attach the installed package to your *R* session, and check the version of the C++ library in use -```{r, messages = FALSE} +```{r library, messages = FALSE} library(rjsoncons) rjsoncons::version() ``` @@ -60,7 +60,7 @@ rjsoncons::version() Here is a simple JSON example document -```{r} +```{r json_example} json <- '{ "locations": [ {"name": "Seattle", "state": "WA"}, @@ -74,41 +74,45 @@ json <- '{ There are several common use cases. Use [rjsoncons][] to query the JSON string using [JSONpath][], [JMESPath][] or [JSONpointer][] syntax to filter larger documents to records of interest, e.g., only -cities in New York state. +cities in New York state, using 'JMESpath' syntax. -```{r} -jmespath(json, "locations[?state == 'NY']") |> +```{r j_query} +j_query(json, "locations[?state == 'NY']") |> cat("\n") ``` Use the `as = "R"` argument to extract deeply nested elements as *R* objects, e.g., a character vector of city names in Washington state. -```{r} -jmespath(json, "locations[?state == 'WA'].name", as = "R") +```{r as_arg} +j_query(json, "locations[?state == 'WA'].name", as = "R") ``` The JSON Pointer specification is simpler, indexing a single object in the document. JSON arrays are 0-based. ```{r jsonpointer} -jsonpointer(json, "/locations/0/state") +j_query(json, "/locations/0/state") ``` -Additional examples illustrating features available are on the help -pages, e.g., `?jmespath`. +The examples above use `j_query()`, which automatically infers query +specification from the form of `path` using `j_path_type()`. It may be +useful to indicate query specification more explicitly using +`jsonpointer()`, `jsonpath()`, or `jmespath()`; examples illustrating +features available for each query specification are on the help pages +`?jsonpointer`, `?jsonpath`, and `?jmespath`. ## Array-of-objects to *R* data.frame The following transforms a nested JSON document into a format that can be incorporated directly in *R* as a `data.frame`. -```{r} +```{r array_of_objects} path <- '{ name: locations[].name, state: locations[].state }' -jmespath(json, path, as = "R") |> +j_query(json, path, as = "R") |> data.frame() ``` @@ -132,10 +136,10 @@ converted to JSON using `jsonlite::toJSON()` before queries are made; `toJSON()` arguments like `auto_unbox = TRUE` can be added to the function call. -```{r} +```{r r_list} ## `lst` is an *R* list lst <- jsonlite::fromJSON(json, simplifyVector = FALSE) -jmespath(lst, "locations[?state == 'WA'].name | sort(@)", auto_unbox = TRUE) |> +j_query(lst, "locations[?state == 'WA'].name | sort(@)", auto_unbox = TRUE) |> cat("\n") ``` @@ -156,7 +160,7 @@ The main rules of this transformation are outlined here. JSON arrays of a single type (boolean, integer, double, string) are transformed to *R* vectors of the same length and corresponding type. -```{r} +```{r as_r} as_r('[true, false, true]') # boolean -> logical as_r('[1, 2, 3]') # integer -> integer as_r('[1.0, 2.0, 3.0]') # double -> numeric @@ -166,7 +170,7 @@ as_r('["a", "b", "c"]') # string -> character JSON arrays mixing integer and double values are transformed to *R* numeric vectors. -```{r} +```{r as_r_integer_numeric} as_r('[1, 2.0]') |> class() # numeric ``` @@ -175,13 +179,13 @@ integer representation, the array is transformed to an *R* numeric vector. NOTE that this results in loss of precision for JSON integer values greater than `2^53`. -```{r} +```{r as_r_64_bit} as_r('[1, 2147483648]') |> class() # 64-bit integers -> numeric ``` JSON objects are transformed to *R* named lists. -```{r} +```{r as_r_objects} as_r('{}') as_r('{"a": 1.0, "b": [2, 3, 4]}') |> str() ``` @@ -189,21 +193,21 @@ as_r('{"a": 1.0, "b": [2, 3, 4]}') |> str() There are several additional details. A JSON scalar and a JSON vector of length 1 are represented in the same way in *R*. -```{r} +```{r as_r_scalars} identical(as_r("3.14"), as_r("[3.14]")) ``` JSON arrays mixing types other than integer and double are transformed to *R* lists -```{r} +```{r as_r_mixed_arrays} as_r('[true, 1, "a"]') |> str() ``` JSON `null` values are represented as *R* `NULL` values; arrays of `null` are transformed to lists -```{r} +```{r as_r_null} as_r('null') # NULL as_r('[null]') |> str() # list(NULL) as_r('[null, null]') |> str() # list(NULL, NULL) @@ -214,7 +218,7 @@ argument. The default preserves names as they appear in the JSON definition; use `"sort"` to sort names alphabetically. This argument is applied recursively. -```{r} +```{r as_r_field_order} json <- '{"b": 1, "a": {"d": 2, "c": 3}}' as_r(json) |> str() as_r(json, object_names = "sort") |> str() @@ -225,7 +229,7 @@ arguments `simplifyVector = TRUE, simplifyDataFrame = FALSE, simplifyMatrix = FALSE)`. Unit tests (using the [tinytest][] framework) providing additional details are available at -```{r, eval = FALSE} +```{r as_r_tiny_test_source, eval = FALSE} system.file(package = "rjsoncons", "tinytest", "test_as_r.R") ``` @@ -237,8 +241,8 @@ The built-in parser can be replaced by alternative parsers by returning the query as a JSON string, e.g., using the `fromJSON()` in the [jsonlite][] package. -```{r} -jmespath(json, "locations[?state == 'WA']", as = "string") |> +```{r jsonlite_fromJSON} +j_query(json, "locations[?state == 'WA']") |> ## `fromJSON()` simplifies list-of-objects to data.frame jsonlite::fromJSON() ``` @@ -272,6 +276,6 @@ between R and the C++ 'jsoncons' library. This vignette was compiled using the following software versions -```{r} +```{r session_info} sessionInfo() ``` From eb829ed6e693a94f20ffdaff8c41aa6d3c4a5d9b Mon Sep 17 00:00:00 2001 From: Martin Morgan Date: Mon, 1 Jan 2024 10:06:25 -0500 Subject: [PATCH 7/7] version bump and NEWS update for j_query() and friends --- DESCRIPTION | 2 +- NEWS.md | 9 ++++++--- 2 files changed, 7 insertions(+), 4 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 9e5b562..0959c9c 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: rjsoncons Title: 'C++' Header-Only 'jsoncons' Library for 'JSON' Queries -Version: 1.1.0.9202 +Version: 1.1.0.9300 Authors@R: c( person( "Martin", "Morgan", role = c("aut", "cre"), diff --git a/NEWS.md b/NEWS.md index 317cb83..53c6667 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,9 +1,12 @@ # rjsoncons 1.2.0 -- (v.1.1.0.9200) implement `jsonpointer()` for querying JSON documents. -- (v.1.1.0.9100) update jsoncons library to 173.2, relaxing compiler +- (1.1.0.9300) implement `j_query()` (query without requiring path + specification), `j_pivot()`, and `j_path_type()`. Remove + `jsonpivot()`. +- (1.1.0.9200) implement `jsonpointer()` for querying JSON documents. +- (1.1.0.9100) update jsoncons library to 173.2, relaxing compiler requirements to c++11. -- (v.1.1.0.9000) implement `jsonpivot()` to transform JSON +- (1.1.0.9000) implement `jsonpivot()` to transform JSON array-of-objects to object-of-arrays, a common step before representation as a data.frame.