Skip to content

Commit

Permalink
added store and retrieve functions
Browse files Browse the repository at this point in the history
  • Loading branch information
douwe committed Feb 5, 2024
1 parent c855896 commit 666d45d
Show file tree
Hide file tree
Showing 4 changed files with 102 additions and 0 deletions.
2 changes: 2 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,9 @@ export(match_n)
export(match_s)
export(one_or_more)
export(reporter)
export(retrieve)
export(satisfy)
export(store)
export(succeed)
export(zero_or_more)
export(zero_or_one)
44 changes: 44 additions & 0 deletions R/store.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,44 @@
#' The `.parcr` environment is used for storing and retrieving variables by the
#' user.
#' @returns \value{None}
#' @noRd
.parcr <- list2env(list(), parent = emptyenv())

#' Store and retrieve objects
#'
#' Sometimes you want to use a parsed object to modify a later parser operation,
#' as in the example below. The `store()` and `retrieve()` functions provide the
#' tools to create such a parser.
#'
#' @param name a string used as the name of the stored object.
#' @param value object to be stored.
#'
#' @returns \value{None} for `store()` and the stored object for `retrieve()`.
#' @export
#'
#' @examples
#' parse_nr <- function(line) {
#' m <- stringr::str_extract(line, "number=(\\d+)", group=1)
#' if (is.na(m)) list()
#' else store("nr", as.numeric(m))
#' }
#'
#' p <- function() {
#' match_s(parse_nr) %then%
#' exactly(retrieve("nr"), literal("A"))
#' }
#'
#' p()(c("number=3", "A", "A", "A")) # success
#' p()(c("number=2", "A", "A", "A")) # failure
store <- function(name, value) {
.parcr[[name]] <- value
}

#' Retrieve an object
#'
#' @export
#' @rdname store
#'
retrieve <- function(name) {
.parcr[[name]]
}
39 changes: 39 additions & 0 deletions man/store.Rd

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

17 changes: 17 additions & 0 deletions tests/testthat/test-store.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,17 @@
test_that("storage and retrieval basics work", {
expect_no_error(store("a", 1))
expect_equal(retrieve("a"), 1)
})

test_that("storage and retrieval in a parser works", {
parse_nr <- function(line) {
m <- stringr::str_extract(line, "NUMBER=(\\d+)", group=1)
if (is.na(m)) list()
else {
N <- as.numeric(m)
store("N",N)
}
}
p <- function() {match_s(parse_nr) %then% exactly(retrieve("N"), literal("A"))}
expect_equal((p()(c("NUMBER=3", "A", "A", "A")))[["R"]], character(0))
})

0 comments on commit 666d45d

Please sign in to comment.