Skip to content

Commit 79ae1ff

Browse files
committed
tweak defaults
1 parent fbbed80 commit 79ae1ff

File tree

12 files changed

+83
-83
lines changed

12 files changed

+83
-83
lines changed

NEWS.md

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -4,17 +4,18 @@
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.
66
* `ncurl()` adds an 'async' option to perform HTTP requests asynchronously, returning immediately with a 'recvAio'. Also adds explicit arguments for HTTP method, headers (which takes a named list or character vector) and request data.
7-
* New `messenger()` function implements a multi-threaded console-based messaging system using NNG's scalability protocols.
7+
* New `messenger()` function implements a multi-threaded console-based messaging system using NNG's scalability protocols (currently as proof of concept).
88
* New `nano_init()` function intended to be called immediately after package load to set global options.
99

1010
#### Updates
1111

1212
* Behavioural change: messages have been upgraded to warnings across the package to allow for enhanced reporting of the originating call e.g. via `warnings()` and flexibility in handling via setting `options()`.
13+
* Returned NNG error codes are now all classed as 'errorValue' across the package.
1314
* Unified `send()` and `recv()` functions, and their asynchronous counterparts `send_aio()` and `recv_aio()`, are now S3 generics and can be used across Sockets, Contexts and Streams.
14-
* Revised 'block' argument for `send()` and `recv()` now allows an integer value for setting a timeout.
15+
* Revised 'block' argument for `send()` and `recv()` now allows an integer value for setting a timeout (under the hood this wraps an asynchronous send/recv followed by a wait to make it a synchronous function).
1516
* `send_ctx()` and `recv_ctx()` are deprecated and will be removed in a future package version - the methods for `send()` and `recv()` should be used instead.
1617
* To allow for more flexible practices, logging is now deprecated and being phased out. Logging can still be set via 'NANONEXT_LOG' prior to package load but `logging()` can no longer be used. Logging will be removed entirely in the next package version.
17-
* Returned NNG error codes are now all classed as 'errorValue' across the package.
18+
* Internal performance optimisations.
1819

1920
# nanonext 0.3.0
2021

R/aio.R

Lines changed: 25 additions & 30 deletions
Original file line numberDiff line numberDiff line change
@@ -7,8 +7,9 @@
77
#' Send data asynchronously over a connection (Socket, Context or Stream).
88
#'
99
#' @inheritParams send
10-
#' @param timeout (optional) integer value in milliseconds. If unspecified, a
11-
#' socket-specific default timeout will be used.
10+
#' @param timeout (optional) integer value in milliseconds. If unspecified, the
11+
#' default of -2L uses a socket-specific default, which is usually the same
12+
#' as no timeout.
1213
#'
1314
#' @return A 'sendAio' (object of class 'sendAio').
1415
#'
@@ -40,24 +41,23 @@
4041
#' @rdname send_aio
4142
#' @export
4243
#'
43-
send_aio <- function(con, data, mode = c("serial", "raw"), timeout) UseMethod("send_aio")
44+
send_aio <- function(con, data, mode = c("serial", "raw"), timeout = -2L) UseMethod("send_aio")
4445

4546
#' @rdname send_aio
4647
#' @method send_aio nanoSocket
4748
#' @export
4849
#'
49-
send_aio.nanoSocket <- function(con, data, mode = c("serial", "raw"), timeout) {
50+
send_aio.nanoSocket <- function(con, data, mode = c("serial", "raw"), timeout = -2L) {
5051

5152
mode <- match.arg2(mode, c("serial", "raw"))
5253
force(data)
5354
data <- encode(data = data, mode = mode)
54-
if (missing(timeout)) timeout <- -2L
5555
aio <- .Call(rnng_send_aio, con, data, timeout)
5656
is.integer(aio) && return(invisible(aio))
5757

58-
env <- new.env(hash = FALSE)
59-
result <- NULL
58+
result <- data <- con <- NULL
6059
unresolv <- TRUE
60+
env <- new.env(hash = FALSE)
6161
makeActiveBinding(sym = "result", fun = function(x) {
6262
if (unresolv) {
6363
res <- .Call(rnng_aio_result, aio)
@@ -76,18 +76,17 @@ send_aio.nanoSocket <- function(con, data, mode = c("serial", "raw"), timeout) {
7676
#' @method send_aio nanoContext
7777
#' @export
7878
#'
79-
send_aio.nanoContext <- function(con, data, mode = c("serial", "raw"), timeout) {
79+
send_aio.nanoContext <- function(con, data, mode = c("serial", "raw"), timeout = -2L) {
8080

8181
mode <- match.arg2(mode, c("serial", "raw"))
8282
force(data)
8383
data <- encode(data = data, mode = mode)
84-
if (missing(timeout)) timeout <- -2L
8584
aio <- .Call(rnng_ctx_send_aio, con, data, timeout)
8685
is.integer(aio) && return(invisible(aio))
8786

88-
env <- new.env(hash = FALSE)
89-
result <- NULL
87+
result <- data <- con <- NULL
9088
unresolv <- TRUE
89+
env <- new.env(hash = FALSE)
9190
makeActiveBinding(sym = "result", fun = function(x) {
9291
if (unresolv) {
9392
res <- .Call(rnng_aio_result, aio)
@@ -106,17 +105,16 @@ send_aio.nanoContext <- function(con, data, mode = c("serial", "raw"), timeout)
106105
#' @method send_aio nanoStream
107106
#' @export
108107
#'
109-
send_aio.nanoStream <- function(con, data, mode = "raw", timeout) {
108+
send_aio.nanoStream <- function(con, data, mode = "raw", timeout = -2L) {
110109

111110
force(data)
112111
data <- encode(data = data, mode = 2L)
113-
if (missing(timeout)) timeout <- -2L
114112
aio <- .Call(rnng_stream_send_aio, con, data, timeout)
115113
is.integer(aio) && return(invisible(aio))
116114

117-
env <- new.env(hash = FALSE)
118-
result <- NULL
115+
result <- data <- con <- NULL
119116
unresolv <- TRUE
117+
env <- new.env(hash = FALSE)
120118
makeActiveBinding(sym = "result", fun = function(x) {
121119
if (unresolv) {
122120
res <- .Call(rnng_aio_result, aio)
@@ -190,10 +188,10 @@ send_aio.nanoStream <- function(con, data, mode = "raw", timeout) {
190188
recv_aio <- function(con,
191189
mode = c("serial", "character", "complex", "double",
192190
"integer", "logical", "numeric", "raw"),
193-
timeout,
191+
timeout = -2L,
194192
keep.raw = TRUE,
195193
...,
196-
n) UseMethod("recv_aio")
194+
n = 100000L) UseMethod("recv_aio")
197195

198196
#' @rdname recv_aio
199197
#' @method recv_aio nanoSocket
@@ -202,20 +200,19 @@ recv_aio <- function(con,
202200
recv_aio.nanoSocket <- function(con,
203201
mode = c("serial", "character", "complex", "double",
204202
"integer", "logical", "numeric", "raw"),
205-
timeout,
203+
timeout = -2L,
206204
keep.raw = TRUE,
207205
...) {
208206

209207
mode <- match.arg2(mode, c("serial", "character", "complex", "double",
210208
"integer", "logical", "numeric", "raw"))
211-
if (missing(timeout)) timeout <- -2L
212209
aio <- .Call(rnng_recv_aio, con, timeout)
213210
is.integer(aio) && return(invisible(aio))
214211

215212
keep.raw <- missing(keep.raw) || isTRUE(keep.raw)
216-
env <- new.env(hash = FALSE)
217-
data <- raw <- NULL
213+
data <- raw <- con <- NULL
218214
unresolv <- TRUE
215+
env <- new.env(hash = FALSE)
219216
if (keep.raw) {
220217
makeActiveBinding(sym = "raw", fun = function(x) {
221218
if (unresolv) {
@@ -279,20 +276,19 @@ recv_aio.nanoSocket <- function(con,
279276
recv_aio.nanoContext <- function(con,
280277
mode = c("serial", "character", "complex", "double",
281278
"integer", "logical", "numeric", "raw"),
282-
timeout,
279+
timeout = -2L,
283280
keep.raw = TRUE,
284281
...) {
285282

286283
mode <- match.arg2(mode, c("serial", "character", "complex", "double",
287284
"integer", "logical", "numeric", "raw"))
288-
if (missing(timeout)) timeout <- -2L
289285
aio <- .Call(rnng_ctx_recv_aio, con, timeout)
290286
is.integer(aio) && return(invisible(aio))
291287

292288
keep.raw <- missing(keep.raw) || isTRUE(keep.raw)
293-
env <- new.env(hash = FALSE)
294-
data <- raw <- NULL
289+
data <- raw <- con <- NULL
295290
unresolv <- TRUE
291+
env <- new.env(hash = FALSE)
296292
if (keep.raw) {
297293
makeActiveBinding(sym = "raw", fun = function(x) {
298294
if (unresolv) {
@@ -356,21 +352,20 @@ recv_aio.nanoContext <- function(con,
356352
recv_aio.nanoStream <- function(con,
357353
mode = c("character", "complex", "double", "integer",
358354
"logical", "numeric", "raw"),
359-
timeout,
355+
timeout = -2L,
360356
keep.raw = TRUE,
361-
n = 10000,
357+
n = 100000L,
362358
...) {
363359

364360
mode <- match.arg2(mode, c("character", "complex", "double", "integer",
365361
"logical", "numeric", "raw")) + 1L
366-
if (missing(timeout)) timeout <- -2L
367362
aio <- .Call(rnng_stream_recv_aio, con, n, timeout)
368363
is.integer(aio) && return(invisible(aio))
369364

370365
keep.raw <- missing(keep.raw) || isTRUE(keep.raw)
371-
env <- new.env(hash = FALSE)
372-
data <- raw <- NULL
366+
data <- raw <- con <- NULL
373367
unresolv <- TRUE
368+
env <- new.env(hash = FALSE)
374369
if (keep.raw) {
375370
makeActiveBinding(sym = "raw", fun = function(x) {
376371
if (unresolv) {

R/context.R

Lines changed: 13 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -67,9 +67,10 @@ context <- function(socket) {
6767
#' 'character', 'complex', 'double', 'integer', 'logical', 'numeric', or 'raw'.
6868
#' The default 'serial' means a serialised R object, for the other modes,
6969
#' the raw vector received will be converted into the respective mode.
70-
#' @param timeout in ms. If unspecified, a socket-specific default timeout will
71-
#' be used. Note that this applies to receiving the request. The total elapsed
72-
#' time would also include the time for performing 'execute' on the received
70+
#' @param timeout (optional) integer value in milliseconds. If unspecified, the
71+
#' default of -2L uses a socket-specific default, which is usually the same
72+
#' as no timeout. Note that this applies to receiving the request. The total
73+
#' elapsed time would also include performing 'execute' on the received
7374
#' data. The timeout then also applies to sending the result (in the event
7475
#' that the requestor has become unavailable since sending the request).
7576
#' @param ... additional arguments passed to the function specified by 'execute'.
@@ -111,13 +112,12 @@ reply <- function(context,
111112
recv_mode = c("serial", "character", "complex", "double",
112113
"integer", "logical", "numeric", "raw"),
113114
send_mode = c("serial", "raw"),
114-
timeout,
115+
timeout = -2L,
115116
...) {
116117

117118
recv_mode <- match.arg2(recv_mode, c("serial", "character", "complex", "double",
118119
"integer", "logical", "numeric", "raw"))
119120
send_mode <- match.arg2(send_mode, c("serial", "raw"))
120-
if (missing(timeout)) timeout <- -2L
121121
res <- .Call(rnng_ctx_recv, context, timeout)
122122
is.integer(res) && return(invisible(res))
123123
on.exit(expr = send_aio(context, as.raw(0L), mode = send_mode))
@@ -140,8 +140,9 @@ reply <- function(context,
140140
#' @inheritParams reply
141141
#' @inheritParams recv
142142
#' @param data an object (if send_mode = 'raw', a vector).
143-
#' @param timeout in ms. If unspecified, a socket-specific default timeout will
144-
#' be used. Note that this applies to receiving the result.
143+
#' @param timeout (optional) integer value in milliseconds. If unspecified, the
144+
#' default of -2L uses a socket-specific default, which is usually the same
145+
#' as no timeout. Note that this applies to receiving the result.
145146
#'
146147
#' @return A 'recvAio' (object of class 'recvAio').
147148
#'
@@ -182,7 +183,7 @@ request <- function(context,
182183
send_mode = c("serial", "raw"),
183184
recv_mode = c("serial", "character", "complex", "double",
184185
"integer", "logical", "numeric", "raw"),
185-
timeout,
186+
timeout = -2L,
186187
keep.raw = TRUE) {
187188

188189
send_mode <- match.arg2(send_mode, c("serial", "raw"))
@@ -193,14 +194,13 @@ request <- function(context,
193194
res <- .Call(rnng_ctx_send_aio, context, data, -2L)
194195
is.integer(res) && return(invisible(res))
195196

196-
if (missing(timeout)) timeout <- -2L
197197
aio <- .Call(rnng_ctx_recv_aio, context, timeout)
198198
is.integer(aio) && return(invisible(aio))
199199

200200
keep.raw <- missing(keep.raw) || isTRUE(keep.raw)
201-
env <- new.env(hash = FALSE)
202-
data <- raw <- NULL
201+
data <- raw <- context <- res <- NULL
203202
unresolv <- TRUE
203+
env <- new.env(hash = FALSE)
204204
if (keep.raw) {
205205
makeActiveBinding(sym = "raw", fun = function(x) {
206206
if (unresolv) {
@@ -278,10 +278,9 @@ request <- function(context,
278278
#' @keywords internal
279279
#' @export
280280
#'
281-
send_ctx <- function(context, data, mode = c("serial", "raw"), timeout, echo = TRUE) {
281+
send_ctx <- function(context, data, mode = c("serial", "raw"), timeout = -2L, echo = TRUE) {
282282

283283
mode <- match.arg2(mode, c("serial", "raw"))
284-
if (missing(timeout)) timeout <- -2L
285284
force(data)
286285
data <- encode(data = data, mode = mode)
287286
res <- .Call(rnng_ctx_send, context, data, timeout)
@@ -320,12 +319,11 @@ send_ctx <- function(context, data, mode = c("serial", "raw"), timeout, echo = T
320319
recv_ctx <- function(context,
321320
mode = c("serial", "character", "complex", "double",
322321
"integer", "logical", "numeric", "raw"),
323-
timeout,
322+
timeout = -2L,
324323
keep.raw = TRUE) {
325324

326325
mode <- match.arg2(mode, c("serial", "character", "complex", "double",
327326
"integer", "logical", "numeric", "raw"))
328-
if (missing(timeout)) timeout <- -2L
329327
res <- .Call(rnng_ctx_recv, context, timeout)
330328
is.integer(res) && return(invisible(res))
331329
on.exit(expr = return(res))

R/ncurl.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -67,9 +67,9 @@ ncurl <- function(url, async = FALSE, method = NULL, headers = NULL, data = NULL
6767
aio <- .Call(rnng_ncurl_aio, url, method, headers, data)
6868
is.integer(aio) && return(invisible(aio))
6969

70-
env <- new.env(hash = FALSE)
7170
data <- raw <- NULL
7271
unresolv <- TRUE
72+
env <- new.env(hash = FALSE)
7373
makeActiveBinding(sym = "raw", fun = function(x) {
7474
if (unresolv) {
7575
res <- .Call(rnng_aio_http, aio)

R/sendrecv.R

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -142,7 +142,7 @@ send.nanoStream <- function(con,
142142
#' @param keep.raw [default TRUE] logical flag whether to keep the received raw
143143
#' vector (useful for verification e.g. via hashing). If FALSE, will return
144144
#' the converted data only.
145-
#' @param n <Streams> [default 10000L] the maximum number of bytes to receive.
145+
#' @param n <Streams> [default 100000L] the maximum number of bytes to receive.
146146
#' Can be an over-estimate, but note that a buffer of this size is reserved.
147147
#' @param ... currently unused.
148148
#'
@@ -212,7 +212,7 @@ recv <- function(con,
212212
block,
213213
keep.raw = TRUE,
214214
...,
215-
n) UseMethod("recv")
215+
n = 100000L) UseMethod("recv")
216216

217217
#' @rdname recv
218218
#' @method recv nanoSocket
@@ -269,7 +269,7 @@ recv.nanoStream <- function(con,
269269
"logical", "numeric", "raw"),
270270
block = TRUE,
271271
keep.raw = TRUE,
272-
n = 10000L,
272+
n = 100000L,
273273
...) {
274274

275275
mode <- match.arg2(mode, c("character", "complex", "double", "integer",

man/recv.Rd

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