@@ -233,7 +233,7 @@ SEXP rnng_aio_get_msgraw(SEXP env) {
233233 return mk_error_raio (raio -> result , env );
234234
235235 SEXP out ;
236- const int mod = raio -> mode , kpr = 1 ;
236+ const int mod = - raio -> mode , kpr = 1 ;
237237 unsigned char * buf ;
238238 size_t sz ;
239239
@@ -277,7 +277,14 @@ SEXP rnng_aio_get_msgdata(SEXP env) {
277277 return mk_error_raio (raio -> result , env );
278278
279279 SEXP out ;
280- const int mod = raio -> mode , kpr = LOGICAL (Rf_findVarInFrame (env , nano_StateSymbol ))[0 ];
280+ int mod , kpr ;
281+ if (raio -> mode > 0 ) {
282+ mod = raio -> mode ;
283+ kpr = 0 ;
284+ } else {
285+ mod = - raio -> mode ;
286+ kpr = 1 ;
287+ }
281288 unsigned char * buf ;
282289 size_t sz ;
283290
@@ -541,7 +548,7 @@ SEXP rnng_recv_aio(SEXP con, SEXP mode, SEXP timeout, SEXP keep, SEXP bytes, SEX
541548 nano_aio * raio = R_Calloc (1 , nano_aio );
542549
543550 raio -> type = RECVAIO ;
544- raio -> mode = nano_matcharg (mode );
551+ raio -> mode = kpr ? - nano_matcharg ( mode ) : nano_matcharg (mode );
545552 raio -> data = NULL ;
546553
547554 if ((xc = nng_aio_alloc (& raio -> aio , raio_complete , raio ))) {
@@ -562,7 +569,7 @@ SEXP rnng_recv_aio(SEXP con, SEXP mode, SEXP timeout, SEXP keep, SEXP bytes, SEX
562569 nano_aio * raio = R_Calloc (1 , nano_aio );
563570
564571 raio -> type = RECVAIO ;
565- raio -> mode = nano_matcharg (mode );
572+ raio -> mode = kpr ? - nano_matcharg ( mode ) : nano_matcharg (mode );
566573 raio -> data = NULL ;
567574
568575 if ((xc = nng_aio_alloc (& raio -> aio , raio_complete , raio ))) {
@@ -585,7 +592,7 @@ SEXP rnng_recv_aio(SEXP con, SEXP mode, SEXP timeout, SEXP keep, SEXP bytes, SEX
585592 nng_iov * iov = R_Calloc (1 , nng_iov );
586593
587594 iaio -> type = IOV_RECVAIO ;
588- iaio -> mode = nano_matchargs (mode );
595+ iaio -> mode = kpr ? - nano_matchargs ( mode ) : nano_matchargs (mode );
589596 iaio -> data = iov ;
590597 iov -> iov_len = xlen ;
591598 iov -> iov_buf = R_Calloc (xlen , unsigned char );
@@ -626,7 +633,6 @@ SEXP rnng_recv_aio(SEXP con, SEXP mode, SEXP timeout, SEXP keep, SEXP bytes, SEX
626633 REPROTECT (env = Rf_eval (env , clo ), pxi );
627634#endif
628635 Rf_defineVar (nano_AioSymbol , aio , env );
629- Rf_defineVar (nano_StateSymbol , keep , env );
630636
631637 if (kpr ) {
632638 PROTECT (fun = Rf_allocSExp (CLOSXP ));
@@ -791,10 +797,10 @@ SEXP rnng_aio_http(SEXP env, SEXP response, SEXP which) {
791797 const int typ = INTEGER (which )[0 ];
792798 SEXP exist ;
793799 switch (typ ) {
794- case 0 : exist = Rf_findVarInFrame (ENCLOS (env ), nano_StatusSymbol ); break ;
795- case 1 : exist = Rf_findVarInFrame (ENCLOS (env ), nano_IdSymbol ); break ;
796- case 2 : exist = Rf_findVarInFrame (ENCLOS (env ), nano_RawSymbol ); break ;
797- default : exist = Rf_findVarInFrame (ENCLOS (env ), nano_ProtocolSymbol ); break ;
800+ case 1 : exist = Rf_findVarInFrame (ENCLOS (env ), nano_StatusSymbol ); break ;
801+ case 2 : exist = Rf_findVarInFrame (ENCLOS (env ), nano_StateSymbol ); break ;
802+ case 3 : exist = Rf_findVarInFrame (ENCLOS (env ), nano_RawSymbol ); break ;
803+ default : exist = Rf_findVarInFrame (ENCLOS (env ), nano_ResultSymbol ); break ;
798804 }
799805 if (exist != R_UnboundValue )
800806 return exist ;
@@ -848,7 +854,7 @@ SEXP rnng_aio_http(SEXP env, SEXP response, SEXP which) {
848854 }
849855 UNPROTECT (1 );
850856 }
851- Rf_defineVar (nano_IdSymbol , rvec , ENCLOS (env ));
857+ Rf_defineVar (nano_StateSymbol , rvec , ENCLOS (env ));
852858
853859 nng_http_res_get_data (handle -> res , & dat , & sz );
854860 vec = Rf_allocVector (RAWSXP , sz );
@@ -863,13 +869,13 @@ SEXP rnng_aio_http(SEXP env, SEXP response, SEXP which) {
863869 cvec = R_tryEvalSilent (cvec , R_BaseEnv , & xc );
864870 UNPROTECT (1 );
865871 }
866- Rf_defineVar (nano_ProtocolSymbol , cvec , ENCLOS (env ));
872+ Rf_defineVar (nano_ResultSymbol , cvec , ENCLOS (env ));
867873
868874 switch (typ ) {
869- case 0 : out = Rf_findVarInFrame (ENCLOS (env ), nano_StatusSymbol ); break ;
870- case 1 : out = Rf_findVarInFrame (ENCLOS (env ), nano_IdSymbol ); break ;
871- case 2 : out = Rf_findVarInFrame (ENCLOS (env ), nano_RawSymbol ); break ;
872- default : out = Rf_findVarInFrame (ENCLOS (env ), nano_ProtocolSymbol ); break ;
875+ case 1 : out = Rf_findVarInFrame (ENCLOS (env ), nano_StatusSymbol ); break ;
876+ case 2 : out = Rf_findVarInFrame (ENCLOS (env ), nano_StateSymbol ); break ;
877+ case 3 : out = Rf_findVarInFrame (ENCLOS (env ), nano_RawSymbol ); break ;
878+ default : out = Rf_findVarInFrame (ENCLOS (env ), nano_ResultSymbol ); break ;
873879 }
874880 return out ;
875881
@@ -918,7 +924,7 @@ SEXP rnng_request(SEXP con, SEXP data, SEXP sendmode, SEXP recvmode, SEXP timeou
918924 nano_aio * raio = R_Calloc (1 , nano_aio );
919925
920926 raio -> type = RECVAIO ;
921- raio -> mode = nano_matcharg (recvmode );
927+ raio -> mode = kpr ? - nano_matcharg ( recvmode ) : nano_matcharg (recvmode );
922928 raio -> data = NULL ;
923929
924930 if ((xc = nng_aio_alloc (& raio -> aio , raio_complete , raio ))) {
@@ -944,7 +950,6 @@ SEXP rnng_request(SEXP con, SEXP data, SEXP sendmode, SEXP recvmode, SEXP timeou
944950 PROTECT (sendaio = R_MakeExternalPtr (saio , R_NilValue , R_NilValue ));
945951 R_RegisterCFinalizerEx (sendaio , saio_finalizer , TRUE);
946952 R_MakeWeakRef (aio , sendaio , R_NilValue , TRUE);
947- Rf_defineVar (nano_StateSymbol , keep , env );
948953
949954 if (kpr ) {
950955 PROTECT (fun = Rf_allocSExp (CLOSXP ));
0 commit comments