Skip to content

Commit b69edeb

Browse files
committed
complete deferred evaluation pipe UI
1 parent f62c061 commit b69edeb

File tree

6 files changed

+69
-35
lines changed

6 files changed

+69
-35
lines changed

NAMESPACE

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,7 @@ S3method(print,nanoListener)
1717
S3method(print,nanoObject)
1818
S3method(print,nanoSocket)
1919
S3method(print,recvAio)
20+
S3method(print,resolvedExpr)
2021
S3method(print,sendAio)
2122
S3method(print,unresolvedExpr)
2223
S3method(print,unresolvedValue)

R/aio.R

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -123,7 +123,8 @@ stop_aio <- function(aio) {
123123
#'
124124
unresolved <- function(aio) {
125125

126-
{inherits(aio, "unresolvedValue") ||
126+
{inherits(aio, "unresolvedExpr") && inherits(.subset2(aio, "data"), "unresolvedValue") ||
127+
inherits(aio, "unresolvedValue") ||
127128
inherits(aio, "recvAio") && inherits(.subset2(aio, "data"), "unresolvedValue") ||
128129
inherits(aio, "sendAio") && inherits(.subset2(aio, "result"), "unresolvedValue")} &&
129130
return(TRUE)

R/utils.R

Lines changed: 21 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -225,12 +225,19 @@ ncurl <- function(http, ...) {
225225
#' @param f a function that accepts 'x' as its first argument.
226226
#'
227227
#' @return The evaluated result, or if x is an 'unresolvedValue', an
228-
#' 'unresolvedExpr' encapsulating the eventual evaluation result. Query its
229-
#' \code{$data} field for resolution.
228+
#' 'unresolvedExpr'.
230229
#'
231-
#' @details Supports stringing together a series of piped expressions (as per
230+
#' @details An 'unresolvedExpr' encapsulates the eventual evaluation result.
231+
#' Query its \code{$data} element for resolution. Once resolved, the object
232+
#' will change to a 'resolvedExpr' and the evaluated result will be accessible
233+
#' at \code{$data}.
234+
#'
235+
#' Supports stringing together a series of piped expressions (as per
232236
#' the below example).
233237
#'
238+
#' \code{\link{unresolved}} may be used on an 'unresolvedExpr' or its
239+
#' \code{$data} element to test for resolution.
240+
#'
234241
#' This function is marked [experimental], which means it is currently
235242
#' under development. Please note that the final implementation is likely to
236243
#' differ from the current version.
@@ -269,6 +276,7 @@ ncurl <- function(http, ...) {
269276
env <- `class<-`(new.env(), c("unresolvedExpr", "unresolvedValue"))
270277
makeActiveBinding(sym = "data", fun = function(x) {
271278
if (is.null(data)) data <- eval(mc, envir = parent.frame(), enclos = baseenv())
279+
if (!inherits(data, "unresolvedExpr")) `class<-`(env, "resolvedExpr")
272280
data
273281
}, env = env)
274282
env
@@ -288,7 +296,16 @@ ncurl <- function(http, ...) {
288296
#' @export
289297
#'
290298
print.unresolvedExpr <- function(x, ...) {
291-
cat("< unresolvedExpr >\n - $data for evaluated expression\n", file = stdout())
299+
cat("< unresolvedExpr >\n - $data to query resolution\n", file = stdout())
292300
invisible(x)
293301
}
294302

303+
#' @export
304+
#'
305+
print.resolvedExpr <- function(x, ...) {
306+
cat("< resolvedExpr >\n - $data for evaluated expression\n", file = stdout())
307+
invisible(x)
308+
}
309+
310+
311+

README.Rmd

Lines changed: 6 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -259,9 +259,11 @@ close(s2)
259259

260260
{nanonext} implements a deferred evaluation pipe `%>>%` for working with potentially unresolved values.
261261

262-
Simply pipe the value forward into a function or series of functions and it either evaluates or returns an 'unresolvedExpr', where the result may be accessed at `$data`. This will also return an 'unresolvedExpr' recursively by design whilst unresolved. However `$data` resolves to the evaluated expression when the original value does.
262+
Simply pipe the value forward into a function or series of functions and it either evaluates or returns an 'unresolvedExpr'.
263263

264-
It is possible to use `unresolved()` around the `$data` field to test for resolution, as in the example below.
264+
The result may be queried at `$data`, which will return another 'unresolvedExpr' recursively (by design) whilst unresolved. However when the original value resolves, the 'unresolvedExpr' will resolve into a 'resolvedExpr' and the evaluated expression may then be accessed at \code{$data}.
265+
266+
It is possible to use `unresolved()` around a 'unresolvedExpr' or its `$data` field to test for resolution, as in the example below.
265267

266268
The pipe operator semantics are similar to R's base pipe `|>`:
267269

@@ -283,7 +285,8 @@ unresolved(res$data)
283285
284286
# sending a message causes both 'msg' and 'res' to resolve
285287
s <- send_aio(s1, 1)
286-
unresolved(res$data)
288+
unresolved(res)
289+
res
287290
res$data
288291
289292
close(s1)

README.md

Lines changed: 29 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -327,13 +327,15 @@ close(s2)
327327
potentially unresolved values.
328328

329329
Simply pipe the value forward into a function or series of functions and
330-
it either evaluates or returns an ‘unresolvedExpr’, where the result may
331-
be accessed at `$data`. This will also return an ‘unresolvedExpr’
332-
recursively by design whilst unresolved. However `$data` resolves to the
333-
evaluated expression when the original value does.
330+
it either evaluates or returns an ‘unresolvedExpr’.
334331

335-
It is possible to use `unresolved()` around the `$data` field to test
336-
for resolution, as in the example below.
332+
The result may be queried at `$data`, which will return another
333+
‘unresolvedExpr’ recursively (by design) whilst unresolved. However when
334+
the original value resolves, the ‘unresolvedExpr’ will resolve into a
335+
‘resolvedExpr’ and the evaluated expression may then be accessed at .
336+
337+
It is possible to use `unresolved()` around a ‘unresolvedExpr’ or its
338+
`$data` field to test for resolution, as in the example below.
337339

338340
The pipe operator semantics are similar to R’s base pipe `|>`:
339341

@@ -350,14 +352,17 @@ msg <- recv_aio(s2)
350352
res <- msg$data %>>% c(2, 3) %>>% as.character()
351353
res
352354
#> < unresolvedExpr >
353-
#> - $data for evaluated expression
355+
#> - $data to query resolution
354356
unresolved(res$data)
355357
#> [1] TRUE
356358

357359
# sending a message causes both 'msg' and 'res' to resolve
358360
s <- send_aio(s1, 1)
359-
unresolved(res$data)
361+
unresolved(res)
360362
#> [1] FALSE
363+
res
364+
#> < resolvedExpr >
365+
#> - $data for evaluated expression
361366
res$data
362367
#> [1] "1" "2" "3"
363368

@@ -416,7 +421,7 @@ aio
416421
#> < recvAio >
417422
#> - $data for message data
418423
aio$data |> str()
419-
#> num [1:100000000] 0.112 -0.331 -0.798 -1.467 0.692 ...
424+
#> num [1:100000000] -0.149 1.493 -1.299 1.694 1.856 ...
420425
```
421426

422427
As `call_aio()` is blocking and will wait for completion, an alternative
@@ -451,37 +456,37 @@ an environment variable `NANONEXT_LOG`.
451456

452457
``` r
453458
logging(level = "info")
454-
#> 2022-03-06 22:41:13 [ log level ] set to: info
459+
#> 2022-03-07 00:33:28 [ log level ] set to: info
455460

456461
pub <- socket("pub", listen = "inproc://nanobroadcast")
457-
#> 2022-03-06 22:41:13 [ sock open ] id: 11 | protocol: pub
458-
#> 2022-03-06 22:41:13 [ list start ] sock: 11 | url: inproc://nanobroadcast
462+
#> 2022-03-07 00:33:28 [ sock open ] id: 11 | protocol: pub
463+
#> 2022-03-07 00:33:28 [ list start ] sock: 11 | url: inproc://nanobroadcast
459464
sub <- socket("sub", dial = "inproc://nanobroadcast")
460-
#> 2022-03-06 22:41:13 [ sock open ] id: 12 | protocol: sub
461-
#> 2022-03-06 22:41:13 [ dial start ] sock: 12 | url: inproc://nanobroadcast
465+
#> 2022-03-07 00:33:28 [ sock open ] id: 12 | protocol: sub
466+
#> 2022-03-07 00:33:28 [ dial start ] sock: 12 | url: inproc://nanobroadcast
462467

463468
sub |> subscribe(topic = "examples")
464-
#> 2022-03-06 22:41:13 [ subscribe ] sock: 12 | topic: examples
469+
#> 2022-03-07 00:33:28 [ subscribe ] sock: 12 | topic: examples
465470
pub |> send(c("examples", "this is an example"), mode = "raw", echo = FALSE)
466471
sub |> recv(mode = "character", keep.raw = FALSE)
467472
#> [1] "examples" "this is an example"
468473

469474
pub |> send(c("other", "this other topic will not be received"), mode = "raw", echo = FALSE)
470475
sub |> recv(mode = "character", keep.raw = FALSE)
471-
#> 2022-03-06 22:41:13 [ 8 ] Try again
476+
#> 2022-03-07 00:33:28 [ 8 ] Try again
472477

473478
# specify NULL to subscribe to ALL topics
474479
sub |> subscribe(topic = NULL)
475-
#> 2022-03-06 22:41:13 [ subscribe ] sock: 12 | topic: ALL
480+
#> 2022-03-07 00:33:28 [ subscribe ] sock: 12 | topic: ALL
476481
pub |> send(c("newTopic", "this is a new topic"), mode = "raw", echo = FALSE)
477482
sub |> recv("character", keep.raw = FALSE)
478483
#> [1] "newTopic" "this is a new topic"
479484

480485
sub |> unsubscribe(topic = NULL)
481-
#> 2022-03-06 22:41:13 [ unsubscribe ] sock: 12 | topic: ALL
486+
#> 2022-03-07 00:33:28 [ unsubscribe ] sock: 12 | topic: ALL
482487
pub |> send(c("newTopic", "this topic will now not be received"), mode = "raw", echo = FALSE)
483488
sub |> recv("character", keep.raw = FALSE)
484-
#> 2022-03-06 22:41:13 [ 8 ] Try again
489+
#> 2022-03-07 00:33:28 [ 8 ] Try again
485490

486491
# however the topics explicitly subscribed to are still received
487492
pub |> send(c("examples", "this example will still be received"), mode = "raw", echo = FALSE)
@@ -490,7 +495,7 @@ sub |> recv(mode = "character", keep.raw = FALSE)
490495

491496
# set logging level back to the default of errors only
492497
logging(level = "error")
493-
#> 2022-03-06 22:41:13 [ log level ] set to: error
498+
#> 2022-03-07 00:33:28 [ log level ] set to: error
494499

495500
close(pub)
496501
close(sub)
@@ -541,7 +546,7 @@ aio2$data
541546
# after the survey expires, the second resolves into a timeout error
542547
Sys.sleep(0.5)
543548
aio2$data
544-
#> 2022-03-06 22:41:13 [ 5 ] Timed out
549+
#> 2022-03-07 00:33:29 [ 5 ] Timed out
545550
#> 'errorValue' int 5
546551

547552
close(sur)
@@ -567,11 +572,11 @@ ncurl("http://httpbin.org/headers")
567572
#> [1] 7b 0a 20 20 22 68 65 61 64 65 72 73 22 3a 20 7b 0a 20 20 20 20 22 48 6f 73
568573
#> [26] 74 22 3a 20 22 68 74 74 70 62 69 6e 2e 6f 72 67 22 2c 20 0a 20 20 20 20 22
569574
#> [51] 58 2d 41 6d 7a 6e 2d 54 72 61 63 65 2d 49 64 22 3a 20 22 52 6f 6f 74 3d 31
570-
#> [76] 2d 36 32 32 35 33 38 38 61 2d 37 65 30 39 65 64 33 35 33 63 38 30 37 61 30
571-
#> [101] 34 37 37 37 65 36 65 32 62 22 0a 20 20 7d 0a 7d 0a
575+
#> [76] 2d 36 32 32 35 35 32 64 39 2d 33 65 32 38 34 66 63 30 36 37 62 65 37 32 65
576+
#> [101] 63 33 66 61 61 34 65 30 34 22 0a 20 20 7d 0a 7d 0a
572577
#>
573578
#> $data
574-
#> [1] "{\n \"headers\": {\n \"Host\": \"httpbin.org\", \n \"X-Amzn-Trace-Id\": \"Root=1-6225388a-7e09ed353c807a04777e6e2b\"\n }\n}\n"
579+
#> [1] "{\n \"headers\": {\n \"Host\": \"httpbin.org\", \n \"X-Amzn-Trace-Id\": \"Root=1-622552d9-3e284fc067be72ec3faa4e04\"\n }\n}\n"
575580
```
576581

577582
For advanced use, supports additional HTTP methods such as POST or PUT.

man/grapes-greater-than-greater-than-grapes.Rd

Lines changed: 10 additions & 3 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

0 commit comments

Comments
 (0)