Skip to content

Commit fc37aa4

Browse files
committed
async capabilities for ncurl
1 parent 0775c2a commit fc37aa4

File tree

9 files changed

+355
-46
lines changed

9 files changed

+355
-46
lines changed

DESCRIPTION

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
Package: nanonext
22
Type: Package
33
Title: NNG (Nanomsg Next Gen) Lightweight Messaging Library
4-
Version: 0.3.0.9001
4+
Version: 0.3.0.9002
55
Description: R binding for NNG (Nanomsg Next Gen), a successor to ZeroMQ. NNG is
66
a socket library providing high-performance scalability protocols,
77
implementing a cross-platform standard for messaging and communications.

NEWS.md

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,9 @@
1-
# nanonext 0.3.0.9001 (development)
1+
# nanonext 0.3.0.9002 (development)
22

33
#### New Features
44

55
* New `stream()` interface exposes low-level byte stream functionality in the NNG library, intended for communicating with non-NNG endpoints, including but not limited to websocket servers.
6-
* `ncurl()` adds explicit arguments supporting HTTP methods other than GET, including for setting the 'Authorization' header.
6+
* `ncurl()` adds an 'async' option to perform HTTP requests asynchronously, returning immediately with a 'recvAio'. Also adds explicit arguments for HTTP method, content type and authorization headers and request data.
77

88
#### Updates
99

R/stream.R

Lines changed: 66 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -75,6 +75,7 @@ stream <- function(dial = NULL, listen = NULL, textframes = FALSE) {
7575
#' nano cURL - a minimalist http(s) client.
7676
#'
7777
#' @param url the URL address.
78+
#' @param async [default FALSE] logical value whether to perform actions async.
7879
#' @param method (optional) the HTTP method.
7980
#' @param ctype (optional) the 'Content-type' header.
8081
#' @param auth (optional) the 'Authorization' header.
@@ -89,6 +90,8 @@ stream <- function(dial = NULL, listen = NULL, textframes = FALSE) {
8990
#' as html, json, xml etc. if required.}
9091
#' }
9192
#'
93+
#' Or else, if \code{async = TRUE}, a 'recvAio' (object of class 'recvAio').
94+
#'
9295
#' @section Redirects:
9396
#'
9497
#' In interactive sessions: will prompt upon receiving a redirect location
@@ -103,26 +106,74 @@ stream <- function(dial = NULL, listen = NULL, textframes = FALSE) {
103106
#'
104107
#' @examples
105108
#' ncurl("http://httpbin.org/get")
106-
#' ncurl("http://httpbin.org/put", "PUT", "text/plain", "Bearer APIKEY", "hello world")
107-
#' ncurl("http://httpbin.org/post", "POST", "application/json", data = '{"key": "value"}')
109+
#' ncurl("http://httpbin.org/put", ,"PUT", "text/plain", "Bearer APIKEY", "hello world")
110+
#' ncurl("http://httpbin.org/post", ,"POST", "application/json", ,'{"key": "value"}')
108111
#'
109112
#' @export
110113
#'
111-
ncurl <- function(url, method = NULL, ctype = NULL, auth = NULL, data = NULL) {
114+
ncurl <- function(url, async = FALSE, method = NULL, ctype = NULL, auth = NULL, data = NULL) {
112115

113116
data <- if (!missing(data)) writeBin(object = data, con = raw())
114-
res <- .Call(rnng_ncurl, url, method, ctype, auth, data)
115-
missing(res) && return(invisible())
116-
if (is.integer(res)) {
117-
logerror(res)
118-
return(invisible(res))
119-
} else if (is.character(res)) {
120-
continue <- if (interactive()) readline(sprintf("Follow redirect to <%s>? [Y/n] ", res)) else "n"
121-
continue %in% c("n", "N", "no", "NO") && return(invisible(res))
122-
return(ncurl(res))
123-
}
124-
data <- tryCatch(rawToChar(res), error = function(e) NULL)
125-
list(raw = res, data = data)
126117

118+
if (missing(async) || !isTRUE(async)) {
119+
120+
res <- .Call(rnng_ncurl, url, method, ctype, auth, data)
121+
missing(res) && return(invisible())
122+
if (is.integer(res)) {
123+
logerror(res)
124+
return(invisible(res))
125+
} else if (is.character(res)) {
126+
continue <- if (interactive()) readline(sprintf("Follow redirect to <%s>? [Y/n] ", res)) else "n"
127+
continue %in% c("n", "N", "no", "NO") && return(invisible(res))
128+
return(ncurl(res))
129+
}
130+
data <- tryCatch(rawToChar(res), error = function(e) NULL)
131+
list(raw = res, data = data)
132+
133+
} else {
134+
135+
aio <- .Call(rnng_ncurl_aio, url, method, ctype, auth, data)
136+
is.integer(aio) && {
137+
logerror(aio)
138+
return(invisible(`class<-`(aio, "errorValue")))
139+
}
140+
env <- `class<-`(new.env(), "recvAio")
141+
data <- raw <- NULL
142+
unresolv <- TRUE
143+
makeActiveBinding(sym = "raw", fun = function(x) {
144+
if (unresolv) {
145+
res <- .Call(rnng_aio_http, aio)
146+
missing(res) && return(.Call(rnng_aio_unresolv))
147+
is.integer(res) && {
148+
data <<- raw <<- `class<-`(res, "errorValue")
149+
unresolv <<- FALSE
150+
logerror(res)
151+
return(invisible(data))
152+
}
153+
raw <<- res
154+
data <<- tryCatch(rawToChar(res), error = function(e) NULL)
155+
unresolv <<- FALSE
156+
}
157+
raw
158+
}, env = env)
159+
makeActiveBinding(sym = "data", fun = function(x) {
160+
if (unresolv) {
161+
res <- .Call(rnng_aio_http, aio)
162+
missing(res) && return(.Call(rnng_aio_unresolv))
163+
is.integer(res) && {
164+
data <<- raw <<- `class<-`(res, "errorValue")
165+
unresolv <<- FALSE
166+
logerror(res)
167+
return(invisible(data))
168+
}
169+
raw <<- res
170+
data <<- tryCatch(rawToChar(res), error = function(e) NULL)
171+
unresolv <<- FALSE
172+
}
173+
data
174+
}, env = env)
175+
`[[<-`(`[[<-`(env, "keep.raw", TRUE), "aio", aio)
176+
177+
}
127178
}
128179

README.Rmd

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -412,16 +412,16 @@ ncurl("http://httpbin.org/headers")
412412
413413
```
414414

415-
For advanced use, supports additional HTTP methods such as POST or PUT.
415+
For advanced use, supports additional HTTP methods such as POST or PUT. In this respect, it may be used as a performant and lightweight method for making requests to REST APIs.
416416

417417
```{r ncurladv}
418418
419-
res <- ncurl("http://httpbin.org/post", "POST", "application/json", "Bearer APIKEY", '{"key": "value"}')
420-
res$data
419+
res <- ncurl("http://httpbin.org/post", async = TRUE, "POST", "application/json", "Bearer APIKEY", '{"key": "value"}')
420+
call_aio(res)$data
421421
422422
```
423423

424-
In this respect, it may be used as a performant and lightweight method for making requests to REST APIs.
424+
There is also the option of performing requests asynchronously, in which case the function returns immediately with a 'recvAio'.
425425

426426
[&laquo; Back to ToC](#table-of-contents)
427427

README.md

Lines changed: 23 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -370,7 +370,7 @@ aio
370370
#> < recvAio >
371371
#> - $data for message data
372372
aio$data |> str()
373-
#> num [1:100000000] -0.736 -1.684 0.223 0.326 1.103 ...
373+
#> num [1:100000000] 1.079 0.855 -0.88 1.192 -0.777 ...
374374
```
375375

376376
As `call_aio()` is blocking and will wait for completion, an alternative
@@ -405,37 +405,37 @@ an environment variable `NANONEXT_LOG`.
405405

406406
``` r
407407
logging(level = "info")
408-
#> 2022-03-29 00:05:47 [ log level ] set to: info
408+
#> 2022-03-29 13:53:51 [ log level ] set to: info
409409

410410
pub <- socket("pub", listen = "inproc://nanobroadcast")
411-
#> 2022-03-29 00:05:47 [ sock open ] id: 9 | protocol: pub
412-
#> 2022-03-29 00:05:47 [ list start ] sock: 9 | url: inproc://nanobroadcast
411+
#> 2022-03-29 13:53:51 [ sock open ] id: 9 | protocol: pub
412+
#> 2022-03-29 13:53:51 [ list start ] sock: 9 | url: inproc://nanobroadcast
413413
sub <- socket("sub", dial = "inproc://nanobroadcast")
414-
#> 2022-03-29 00:05:47 [ sock open ] id: 10 | protocol: sub
415-
#> 2022-03-29 00:05:47 [ dial start ] sock: 10 | url: inproc://nanobroadcast
414+
#> 2022-03-29 13:53:51 [ sock open ] id: 10 | protocol: sub
415+
#> 2022-03-29 13:53:51 [ dial start ] sock: 10 | url: inproc://nanobroadcast
416416

417417
sub |> subscribe(topic = "examples")
418-
#> 2022-03-29 00:05:47 [ subscribe ] sock: 10 | topic: examples
418+
#> 2022-03-29 13:53:51 [ subscribe ] sock: 10 | topic: examples
419419
pub |> send(c("examples", "this is an example"), mode = "raw", echo = FALSE)
420420
sub |> recv(mode = "character", keep.raw = FALSE)
421421
#> [1] "examples" "this is an example"
422422

423423
pub |> send(c("other", "this other topic will not be received"), mode = "raw", echo = FALSE)
424424
sub |> recv(mode = "character", keep.raw = FALSE)
425-
#> 2022-03-29 00:05:47 [ 8 ] Try again
425+
#> 2022-03-29 13:53:51 [ 8 ] Try again
426426

427427
# specify NULL to subscribe to ALL topics
428428
sub |> subscribe(topic = NULL)
429-
#> 2022-03-29 00:05:47 [ subscribe ] sock: 10 | topic: ALL
429+
#> 2022-03-29 13:53:51 [ subscribe ] sock: 10 | topic: ALL
430430
pub |> send(c("newTopic", "this is a new topic"), mode = "raw", echo = FALSE)
431431
sub |> recv("character", keep.raw = FALSE)
432432
#> [1] "newTopic" "this is a new topic"
433433

434434
sub |> unsubscribe(topic = NULL)
435-
#> 2022-03-29 00:05:47 [ unsubscribe ] sock: 10 | topic: ALL
435+
#> 2022-03-29 13:53:51 [ unsubscribe ] sock: 10 | topic: ALL
436436
pub |> send(c("newTopic", "this topic will now not be received"), mode = "raw", echo = FALSE)
437437
sub |> recv("character", keep.raw = FALSE)
438-
#> 2022-03-29 00:05:47 [ 8 ] Try again
438+
#> 2022-03-29 13:53:51 [ 8 ] Try again
439439

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

445445
# set logging level back to the default of errors only
446446
logging(level = "error")
447-
#> 2022-03-29 00:05:47 [ log level ] set to: error
447+
#> 2022-03-29 13:53:51 [ log level ] set to: error
448448

449449
close(pub)
450450
close(sub)
@@ -495,7 +495,7 @@ aio2$data
495495
# after the survey expires, the second resolves into a timeout error
496496
Sys.sleep(0.5)
497497
aio2$data
498-
#> 2022-03-29 00:05:48 [ 5 ] Timed out
498+
#> 2022-03-29 13:53:52 [ 5 ] Timed out
499499
#> 'errorValue' int 5
500500

501501
close(sur)
@@ -521,23 +521,25 @@ ncurl("http://httpbin.org/headers")
521521
#> [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
522522
#> [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
523523
#> [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
524-
#> [76] 2d 36 32 34 32 33 66 34 63 2d 35 31 38 62 62 65 38 66 34 31 65 31 37 37 39
525-
#> [101] 63 34 32 34 61 35 61 62 33 22 0a 20 20 7d 0a 7d 0a
524+
#> [76] 2d 36 32 34 33 30 31 36 30 2d 31 30 36 36 64 32 64 35 32 35 33 34 62 34 37
525+
#> [101] 36 35 37 65 32 34 30 62 32 22 0a 20 20 7d 0a 7d 0a
526526
#>
527527
#> $data
528-
#> [1] "{\n \"headers\": {\n \"Host\": \"httpbin.org\", \n \"X-Amzn-Trace-Id\": \"Root=1-62423f4c-518bbe8f41e1779c424a5ab3\"\n }\n}\n"
528+
#> [1] "{\n \"headers\": {\n \"Host\": \"httpbin.org\", \n \"X-Amzn-Trace-Id\": \"Root=1-62430160-1066d2d52534b47657e240b2\"\n }\n}\n"
529529
```
530530

531531
For advanced use, supports additional HTTP methods such as POST or PUT.
532+
In this respect, it may be used as a performant and lightweight method
533+
for making requests to REST APIs.
532534

533535
``` r
534-
res <- ncurl("http://httpbin.org/post", "POST", "application/json", "Bearer APIKEY", '{"key": "value"}')
535-
res$data
536-
#> [1] "{\n \"args\": {}, \n \"data\": \"{\\\"key\\\": \\\"value\\\"}\", \n \"files\": {}, \n \"form\": {}, \n \"headers\": {\n \"Authorization\": \"Bearer APIKEY\", \n \"Content-Length\": \"16\", \n \"Content-Type\": \"application/json\", \n \"Host\": \"httpbin.org\", \n \"X-Amzn-Trace-Id\": \"Root=1-62423f4c-4de27fd3765f72b51e01d918\"\n }, \n \"json\": {\n \"key\": \"value\"\n }, \n \"origin\": \"78.145.225.121\", \n \"url\": \"http://httpbin.org/post\"\n}\n"
536+
res <- ncurl("http://httpbin.org/post", async = TRUE, "POST", "application/json", "Bearer APIKEY", '{"key": "value"}')
537+
call_aio(res)$data
538+
#> [1] "{\n \"args\": {}, \n \"data\": \"{\\\"key\\\": \\\"value\\\"}\", \n \"files\": {}, \n \"form\": {}, \n \"headers\": {\n \"Authorization\": \"Bearer APIKEY\", \n \"Content-Length\": \"16\", \n \"Content-Type\": \"application/json\", \n \"Host\": \"httpbin.org\", \n \"X-Amzn-Trace-Id\": \"Root=1-62430160-4b8917cd2b569d8c0294f5ca\"\n }, \n \"json\": {\n \"key\": \"value\"\n }, \n \"origin\": \"79.173.189.204\", \n \"url\": \"http://httpbin.org/post\"\n}\n"
537539
```
538540

539-
In this respect, it may be used as a performant and lightweight method
540-
for making requests to REST APIs.
541+
There is also the option of performing requests asynchronously, in which
542+
case the function returns immediately with a ‘recvAio’.
541543

542544
[« Back to ToC](#table-of-contents)
543545

man/ncurl.Rd

Lines changed: 14 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)