Skip to content

Commit 6addc0a

Browse files
committed
fix memory protection
1 parent eb51392 commit 6addc0a

File tree

6 files changed

+197
-151
lines changed

6 files changed

+197
-151
lines changed

R/stream.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -38,7 +38,7 @@
3838
#'
3939
stream <- function(dial = NULL, listen = NULL, textframes = FALSE) {
4040

41-
textframes <- isTRUE(textframes)
41+
textframes <- !missing(textframes) && isTRUE(textframes)
4242
if (missing(dial)) {
4343
if (missing(listen)) {
4444
stop("specify a URL for either 'dial' or 'listen'")

README.md

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -377,7 +377,7 @@ aio
377377
#> < recvAio >
378378
#> - $data for message data
379379
aio$data |> str()
380-
#> num [1:100000000] -0.0308 0.1989 -0.9806 -0.1879 -0.3781 ...
380+
#> num [1:100000000] 0.369 -0.681 -0.413 0.83 -0.988 ...
381381
```
382382

383383
As `call_aio()` is blocking and will wait for completion, an alternative
@@ -514,11 +514,11 @@ ncurl("http://httpbin.org/headers")
514514
#> [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
515515
#> [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
516516
#> [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
517-
#> [76] 2d 36 32 36 32 36 61 65 62 2d 33 66 33 39 61 37 31 31 35 37 65 65 35 62 63
518-
#> [101] 65 35 38 36 65 62 38 66 34 22 0a 20 20 7d 0a 7d 0a
517+
#> [76] 2d 36 32 36 32 39 36 30 32 2d 34 38 64 39 33 64 39 33 33 64 36 32 35 66 30
518+
#> [101] 36 30 36 62 38 66 37 33 65 22 0a 20 20 7d 0a 7d 0a
519519
#>
520520
#> $data
521-
#> [1] "{\n \"headers\": {\n \"Host\": \"httpbin.org\", \n \"X-Amzn-Trace-Id\": \"Root=1-62626aeb-3f39a71157ee5bce586eb8f4\"\n }\n}\n"
521+
#> [1] "{\n \"headers\": {\n \"Host\": \"httpbin.org\", \n \"X-Amzn-Trace-Id\": \"Root=1-62629602-48d93d933d625f0606b8f73e\"\n }\n}\n"
522522
```
523523

524524
For advanced use, supports additional HTTP methods such as POST or PUT.
@@ -533,7 +533,7 @@ res
533533
#> - $raw for raw message
534534

535535
call_aio(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-62626aeb-71a64d74239ceae125f0a20f\"\n }, \n \"json\": {\n \"key\": \"value\"\n }, \n \"origin\": \"78.145.225.121\", \n \"url\": \"http://httpbin.org/post\"\n}\n"
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-62629602-1fb9951a0f4246df56d74460\"\n }, \n \"json\": {\n \"key\": \"value\"\n }, \n \"origin\": \"78.145.225.121\", \n \"url\": \"http://httpbin.org/post\"\n}\n"
537537
```
538538

539539
In this respect, it may be used as a performant and lightweight method

src/aio.c

Lines changed: 50 additions & 44 deletions
Original file line numberDiff line numberDiff line change
@@ -180,8 +180,7 @@ SEXP rnng_aio_get_msg(SEXP aio, SEXP mode, SEXP keep) {
180180
if (res)
181181
return mk_error(res);
182182

183-
const int mod = *INTEGER(mode);
184-
const int kpr = *LOGICAL(keep);
183+
const int mod = *INTEGER(mode), kpr = *LOGICAL(keep);
185184
unsigned char *buf = nng_msg_body(raio->data);
186185
size_t sz = nng_msg_len(raio->data);
187186

@@ -209,8 +208,7 @@ SEXP rnng_aio_stream_in(SEXP aio, SEXP mode, SEXP keep) {
209208
if (res)
210209
return mk_error(res);
211210

212-
const int mod = *INTEGER(mode);
213-
const int kpr = *LOGICAL(keep);
211+
const int mod = *INTEGER(mode), kpr = *LOGICAL(keep);
214212
nng_iov *iov = (nng_iov *) iaio->data;
215213
unsigned char *buf = iov->iov_buf;
216214
size_t sz = nng_aio_count(iaio->aio);
@@ -250,11 +248,11 @@ SEXP rnng_aio_stop(SEXP aio) {
250248

251249
nano_aio *aiop = (nano_aio *) R_ExternalPtrAddr(coreaio);
252250
nng_aio_stop(aiop->aio);
251+
nng_aio_free(aiop->aio);
252+
nng_mtx_free(aiop->mtx);
253253

254254
nng_iov *iov;
255255
nano_handle *handle;
256-
nng_aio_free(aiop->aio);
257-
nng_mtx_free(aiop->mtx);
258256
switch (aiop->type) {
259257
case RECVAIO:
260258
if (aiop->data != NULL)
@@ -290,7 +288,8 @@ SEXP rnng_aio_stop(SEXP aio) {
290288

291289
SEXP rnng_aio_unresolv(void) {
292290

293-
SEXP res = PROTECT(Rf_ScalarLogical(NA_LOGICAL));
291+
SEXP res;
292+
PROTECT(res = Rf_ScalarLogical(NA_LOGICAL));
294293
Rf_classgets(res, Rf_mkString("unresolvedValue"));
295294
UNPROTECT(1);
296295
return res;
@@ -316,11 +315,11 @@ SEXP rnng_recv_aio(SEXP socket, SEXP timeout) {
316315
error_return("'con' is not a valid Socket");
317316

318317
nng_socket *sock = (nng_socket *) R_ExternalPtrAddr(socket);
319-
nano_aio *raio;
320-
int xc;
321318
const nng_duration dur = (nng_duration) Rf_asInteger(timeout);
319+
nano_aio *raio = R_Calloc(1, nano_aio);
320+
int xc;
321+
SEXP aio;
322322

323-
raio = R_Calloc(1, nano_aio);
324323
raio->type = RECVAIO;
325324
raio->data = NULL;
326325

@@ -339,7 +338,7 @@ SEXP rnng_recv_aio(SEXP socket, SEXP timeout) {
339338
nng_aio_set_timeout(raio->aio, dur);
340339
nng_recv_aio(*sock, raio->aio);
341340

342-
SEXP aio = PROTECT(R_MakeExternalPtr(raio, nano_AioSymbol, R_NilValue));
341+
PROTECT(aio = R_MakeExternalPtr(raio, nano_AioSymbol, R_NilValue));
343342
R_RegisterCFinalizerEx(aio, raio_finalizer, TRUE);
344343

345344
UNPROTECT(1);
@@ -353,11 +352,11 @@ SEXP rnng_ctx_recv_aio(SEXP context, SEXP timeout) {
353352
error_return("'con' is not a valid Context");
354353

355354
nng_ctx *ctxp = (nng_ctx *) R_ExternalPtrAddr(context);
356-
nano_aio *raio;
357-
int xc;
358355
const nng_duration dur = (nng_duration) Rf_asInteger(timeout);
356+
nano_aio *raio = R_Calloc(1, nano_aio);
357+
int xc;
358+
SEXP aio;
359359

360-
raio = R_Calloc(1, nano_aio);
361360
raio->type = RECVAIO;
362361
raio->data = NULL;
363362

@@ -376,7 +375,7 @@ SEXP rnng_ctx_recv_aio(SEXP context, SEXP timeout) {
376375
nng_aio_set_timeout(raio->aio, dur);
377376
nng_ctx_recv(*ctxp, raio->aio);
378377

379-
SEXP aio = PROTECT(R_MakeExternalPtr(raio, nano_AioSymbol, R_NilValue));
378+
PROTECT(aio = R_MakeExternalPtr(raio, nano_AioSymbol, R_NilValue));
380379
R_RegisterCFinalizerEx(aio, raio_finalizer, TRUE);
381380

382381
UNPROTECT(1);
@@ -392,12 +391,12 @@ SEXP rnng_stream_recv_aio(SEXP stream, SEXP bytes, SEXP timeout) {
392391
nng_stream *sp = (nng_stream *) R_ExternalPtrAddr(stream);
393392
const nng_duration dur = (nng_duration) Rf_asInteger(timeout);
394393
const size_t xlen = Rf_asInteger(bytes);
394+
nano_aio *iaio = R_Calloc(1, nano_aio);
395+
nng_iov *iov = R_Calloc(1, nng_iov);
395396
int xc;
397+
SEXP aio;
396398

397-
nano_aio *iaio = R_Calloc(1, nano_aio);
398399
iaio->type = IOV_RECVAIO;
399-
400-
nng_iov *iov = R_Calloc(1, nng_iov);
401400
iaio->data = iov;
402401
iov->iov_len = xlen;
403402
iov->iov_buf = R_Calloc(xlen, unsigned char);
@@ -430,7 +429,7 @@ SEXP rnng_stream_recv_aio(SEXP stream, SEXP bytes, SEXP timeout) {
430429
nng_aio_set_timeout(iaio->aio, dur);
431430
nng_stream_recv(sp, iaio->aio);
432431

433-
SEXP aio = PROTECT(R_MakeExternalPtr(iaio, nano_AioSymbol, R_NilValue));
432+
PROTECT(aio = R_MakeExternalPtr(iaio, nano_AioSymbol, R_NilValue));
434433
R_RegisterCFinalizerEx(aio, iraio_finalizer, TRUE);
435434

436435
UNPROTECT(1);
@@ -446,15 +445,14 @@ SEXP rnng_send_aio(SEXP socket, SEXP data, SEXP timeout) {
446445
error_return("'con' is not a valid Socket");
447446

448447
nng_socket *sock = (nng_socket *) R_ExternalPtrAddr(socket);
449-
nano_aio *saio;
450-
nng_msg *msg;
451-
int xc;
452-
453448
const nng_duration dur = (nng_duration) Rf_asInteger(timeout);
454449
unsigned char *dp = RAW(data);
455450
const R_xlen_t xlen = Rf_xlength(data);
451+
nano_aio *saio = R_Calloc(1, nano_aio);
452+
nng_msg *msg;
453+
int xc;
454+
SEXP aio;
456455

457-
saio = R_Calloc(1, nano_aio);
458456
saio->type = SENDAIO;
459457

460458
xc = nng_msg_alloc(&msg, 0);
@@ -486,7 +484,7 @@ SEXP rnng_send_aio(SEXP socket, SEXP data, SEXP timeout) {
486484
nng_aio_set_timeout(saio->aio, dur);
487485
nng_send_aio(*sock, saio->aio);
488486

489-
SEXP aio = PROTECT(R_MakeExternalPtr(saio, nano_AioSymbol, R_NilValue));
487+
PROTECT(aio = R_MakeExternalPtr(saio, nano_AioSymbol, R_NilValue));
490488
R_RegisterCFinalizerEx(aio, saio_finalizer, TRUE);
491489

492490
UNPROTECT(1);
@@ -500,15 +498,14 @@ SEXP rnng_ctx_send_aio(SEXP context, SEXP data, SEXP timeout) {
500498
error_return("'con' is not a valid Context");
501499

502500
nng_ctx *ctxp = (nng_ctx *) R_ExternalPtrAddr(context);
503-
nano_aio *saio;
504-
nng_msg *msg;
505-
int xc;
506-
507501
const nng_duration dur = (nng_duration) Rf_asInteger(timeout);
508502
unsigned char *dp = RAW(data);
509503
const R_xlen_t xlen = Rf_xlength(data);
504+
nano_aio *saio = R_Calloc(1, nano_aio);
505+
nng_msg *msg;
506+
int xc;
507+
SEXP aio;
510508

511-
saio = R_Calloc(1, nano_aio);
512509
saio->type = SENDAIO;
513510

514511
xc = nng_msg_alloc(&msg, 0);
@@ -541,7 +538,7 @@ SEXP rnng_ctx_send_aio(SEXP context, SEXP data, SEXP timeout) {
541538
nng_aio_set_timeout(saio->aio, dur);
542539
nng_ctx_send(*ctxp, saio->aio);
543540

544-
SEXP aio = PROTECT(R_MakeExternalPtr(saio, nano_AioSymbol, R_NilValue));
541+
PROTECT(aio = R_MakeExternalPtr(saio, nano_AioSymbol, R_NilValue));
545542
R_RegisterCFinalizerEx(aio, saio_finalizer, TRUE);
546543

547544
UNPROTECT(1);
@@ -558,13 +555,13 @@ SEXP rnng_stream_send_aio(SEXP stream, SEXP data, SEXP timeout) {
558555
const nng_duration dur = (nng_duration) Rf_asInteger(timeout);
559556
unsigned char *dp = RAW(data);
560557
const R_xlen_t xlen = Rf_xlength(data);
561-
const int frames = LOGICAL(Rf_getAttrib(stream, nano_TextframesSymbol))[0];
558+
const int frames = *LOGICAL(Rf_getAttrib(stream, nano_TextframesSymbol));
559+
nano_aio *iaio = R_Calloc(1, nano_aio);
560+
nng_iov *iov = R_Calloc(1, nng_iov);
562561
int xc;
562+
SEXP aio;
563563

564-
nano_aio *iaio = R_Calloc(1, nano_aio);
565564
iaio->type = IOV_SENDAIO;
566-
567-
nng_iov *iov = R_Calloc(1, nng_iov);
568565
iaio->data = iov;
569566
iov->iov_len = frames == 1 ? xlen - 1 : xlen;
570567
iov->iov_buf = dp;
@@ -594,7 +591,7 @@ SEXP rnng_stream_send_aio(SEXP stream, SEXP data, SEXP timeout) {
594591
nng_aio_set_timeout(iaio->aio, dur);
595592
nng_stream_send(sp, iaio->aio);
596593

597-
SEXP aio = PROTECT(R_MakeExternalPtr(iaio, nano_AioSymbol, R_NilValue));
594+
PROTECT(aio = R_MakeExternalPtr(iaio, nano_AioSymbol, R_NilValue));
598595
R_RegisterCFinalizerEx(aio, isaio_finalizer, TRUE);
599596

600597
UNPROTECT(1);
@@ -606,14 +603,16 @@ SEXP rnng_stream_send_aio(SEXP stream, SEXP data, SEXP timeout) {
606603

607604
SEXP rnng_ncurl_aio(SEXP http, SEXP method, SEXP headers, SEXP data) {
608605

609-
int xc;
606+
const char *httr = CHAR(STRING_ELT(http, 0));
610607
nano_aio *haio = R_Calloc(1, nano_aio);
611-
haio->type = HTTP_AIO;
612608
nano_handle *handle = R_Calloc(1, nano_handle);
613-
handle->cfg = NULL;
609+
int xc;
610+
SEXP aio;
611+
612+
haio->type = HTTP_AIO;
614613
haio->data = handle;
614+
handle->cfg = NULL;
615615

616-
const char *httr = CHAR(STRING_ELT(http, 0));
617616
xc = nng_url_parse(&handle->url, httr);
618617
if (xc) {
619618
R_Free(handle);
@@ -649,7 +648,9 @@ SEXP rnng_ncurl_aio(SEXP http, SEXP method, SEXP headers, SEXP data) {
649648
}
650649
if (headers != R_NilValue) {
651650
R_xlen_t hlen = Rf_xlength(headers);
652-
SEXP names = PROTECT(Rf_getAttrib(headers, R_NamesSymbol));
651+
SEXP names;
652+
PROTECT(names = Rf_getAttrib(headers, R_NamesSymbol));
653+
653654
switch (TYPEOF(headers)) {
654655
case STRSXP:
655656
for (R_xlen_t i = 0; i < hlen; i++) {
@@ -684,6 +685,7 @@ SEXP rnng_ncurl_aio(SEXP http, SEXP method, SEXP headers, SEXP data) {
684685
}
685686
break;
686687
}
688+
687689
UNPROTECT(1);
688690
}
689691
if (data != R_NilValue) {
@@ -761,7 +763,7 @@ SEXP rnng_ncurl_aio(SEXP http, SEXP method, SEXP headers, SEXP data) {
761763

762764
nng_http_client_transact(handle->cli, handle->req, handle->res, haio->aio);
763765

764-
SEXP aio = PROTECT(R_MakeExternalPtr(haio, nano_AioSymbol, R_NilValue));
766+
PROTECT(aio = R_MakeExternalPtr(haio, nano_AioSymbol, R_NilValue));
765767
R_RegisterCFinalizerEx(aio, haio_finalizer, TRUE);
766768

767769
UNPROTECT(1);
@@ -799,9 +801,13 @@ SEXP rnng_aio_http(SEXP aio) {
799801

800802
void *dat;
801803
size_t sz;
804+
unsigned char *rp;
805+
SEXP vec;
806+
802807
nng_http_res_get_data(handle->res, &dat, &sz);
803-
SEXP vec = PROTECT(Rf_allocVector(RAWSXP, sz));
804-
unsigned char *rp = RAW(vec);
808+
809+
PROTECT(vec = Rf_allocVector(RAWSXP, sz));
810+
rp = RAW(vec);
805811
memcpy(rp, dat, sz);
806812

807813
UNPROTECT(1);

0 commit comments

Comments
 (0)