Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:23
erlang
3321-erts-Add-enif_dynamic_resource_call-and-en...
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 3321-erts-Add-enif_dynamic_resource_call-and-enif_init_re.patch of Package erlang
From 35e49283ccb6d047a219303624d22d2b6821df06 Mon Sep 17 00:00:00 2001 From: Sverker Eriksson <sverker@erlang.org> Date: Wed, 24 Feb 2021 14:53:27 +0100 Subject: [PATCH] erts: Add enif_dynamic_resource_call and enif_init_resource_type A "safe" way to call NIF code in another module. --- erts/doc/src/erl_nif.xml | 98 +++++++++++++++++-- erts/emulator/beam/erl_nif.c | 75 ++++++++++++-- erts/emulator/beam/erl_nif.h | 10 +- erts/emulator/beam/erl_nif_api_funcs.h | 4 +- erts/emulator/test/nif_SUITE.erl | 65 ++++++++++++ erts/emulator/test/nif_SUITE_data/nif_SUITE.c | 21 +++- erts/emulator/test/nif_SUITE_data/nif_mod.c | 46 +++++++-- 7 files changed, 289 insertions(+), 30 deletions(-) diff --git a/erts/doc/src/erl_nif.xml b/erts/doc/src/erl_nif.xml index 4c8d689307..faaebffbf4 100644 --- a/erts/doc/src/erl_nif.xml +++ b/erts/doc/src/erl_nif.xml @@ -693,8 +693,9 @@ int writeiovec(ErlNifEnv *env, ERL_NIF_TERM term, ERL_NIF_TERM *tail, <seecref marker="#upgrade"><c>upgrade</c></seecref>, <seecref marker="#unload"><c>unload</c></seecref>, <seecref marker="#ErlNifResourceDtor"><c>dtor</c></seecref>, - <seecref marker="#ErlNifResourceDown"><c>down</c></seecref> and - <seecref marker="#ErlNifResourceStop"><c>stop</c></seecref>). + <seecref marker="#ErlNifResourceDown"><c>down</c></seecref>, + <seecref marker="#ErlNifResourceStop"><c>stop</c></seecref> and + <seecref marker="#ErlNifResourceDynCall"><c>dyncall</c></seecref>). Works like a process bound environment but with a temporary pseudo process that "terminates" when the callback has returned. Terms may be created in this environment but they will @@ -823,12 +824,15 @@ typedef struct { <item> <code type="none"> typedef struct { - ErlNifResourceDtor* dtor; - ErlNifResourceStop* stop; - ErlNifResourceDown* down; + ErlNifResourceDtor* dtor; // #1 Destructor + ErlNifResourceStop* stop; // #2 Select stop + ErlNifResourceDown* down; // #3 Monitor down + int members; + ErlNifResourceDynCall* dyncall; // #4 Dynamic call } ErlNifResourceTypeInit;</code> - <p>Initialization structure read by <seecref marker="#enif_open_resource_type_x"> - enif_open_resource_type_x</seecref>.</p> + <p>Initialization structure read by + <seecref marker="#enif_open_resource_type_x">enif_open_resource_type_x</seecref> + <seecref marker="#enif_init_resource_type">enif_init_resource_type</seecref>.</p> </item> <tag><marker id="ErlNifResourceDtor"/><c>ErlNifResourceDtor</c></tag> <item> @@ -861,6 +865,18 @@ typedef void ErlNifResourceStop(ErlNifEnv* caller_env, void* obj, ErlNifEvent ev <c>is_direct_call</c> is true if the call is made directly from <c>enif_select</c> or false if it is a scheduled call (potentially from another thread).</p> </item> + <tag><marker id="ErlNifResourceDynCall"/><c>ErlNifResourceDynCall</c></tag> + <item> + <code type="none"> +typedef void ErlNifResourceDynCall(ErlNifEnv* caller_env, void* obj, void* call_data);</code> + <p> + The function prototype of a dynamic resource call function, called by + <seecref marker="#enif_dynamic_resource_call"> + enif_dynamic_resource_call</seecref>. Argument <c>obj</c> is the + resource object and <c>call_data</c> is the last argument to + <c>enif_dynamic_resource_call</c> passed through. + </p> + </item> <tag><marker id="ErlNifCharEncoding"/><c>ErlNifCharEncoding</c></tag> <item> <code type="none"> @@ -1291,6 +1307,38 @@ typedef struct { </desc> </func> + <func> + <name since="OTP 24.0"><ret>int</ret> + <nametext>enif_dynamic_resource_call(ErlNifEnv* caller_env, + ERL_NIF_MODULE rt_module, ERL_NIF_MODULE rt_name, ERL_NIF_TERM resource, + void* call_data)</nametext> + </name> + <fsummary>Call a resource in another module.</fsummary> + <desc> + <p> + Call code of a resource type implemented by another NIF module. The + atoms <c>rt_module</c> and <c>rt_name</c> identifies the resource type + to be called. Argument <c>resource</c> identifies a resource object of + that type. + </p> + <p> + The callback <seecref marker="#ErlNifResourceDynCall"><c>dyncall</c></seecref> + of the identified resource type will be called with a pointer to the + resource objects <c>obj</c> and the argument <c>call_data</c> passed + through. The <c>call_data</c> argument is typically a pointer to a + struct used to passed both arguments to the <c>dyncall</c> function as + well as results back to the caller. + </p> + <p> + Returns 0 if the <c>dyncall</c> callback function was called. + Returns a non-zero value if no call was made, which happens if <c>rt_module</c> + and <c>rt_name</c> did not identify a resource type with a + <c>dyncall</c> callback or if <c>resource</c> was not a resource + object of that type. + </p> + </desc> + </func> + <func> <name since="OTP R13B04"><ret>int</ret> <nametext>enif_equal_tids(ErlNifTid tid1, ErlNifTid tid2)</nametext> @@ -2842,7 +2890,41 @@ enif_map_iterator_destroy(env, &iter);</code> <p>Argument <c>init</c> is a pointer to an <seecref marker="#ErlNifResourceTypeInit"><c>ErlNifResourceTypeInit</c></seecref> structure that contains the function pointers for destructor, down and stop callbacks - for the resource type.</p> + for the resource type. + </p> + <note> + <p> + Only members <c>dtor</c>, <c>down</c> and <c>stop</c> in <seecref + marker="#ErlNifResourceTypeInit"><c>ErlNifResourceTypeInit</c></seecref> + are read by <c>enif_open_resource_type_x</c>. To implement the new + <c>dyncall</c> callback use <seecref + marker="#enif_init_resource_type"><c>enif_init_resource_type</c></seecref>. + </p> + </note> + </desc> + </func> + + <func> + <name since="OTP 24.0"><ret>ErlNifResourceType *</ret> + <nametext>enif_init_resource_type(ErlNifEnv* env, const char* name, + const ErlNifResourceTypeInit* init, + ErlNifResourceFlags flags, ErlNifResourceFlags* tried)</nametext> + </name> + <fsummary>Create or takeover a resource type.</fsummary> + <desc> + <p>Same as <seecref marker="#enif_open_resource_type_x"><c>enif_open_resource_type_x</c></seecref> + except it accepts an additional callback function for resource types that are + used together with <seecref marker="#enif_dynamic_resource_call"> + <c>enif_dynamic_resource_call</c></seecref>.</p> + <p>Argument <c>init</c> is a pointer to an + <seecref marker="#ErlNifResourceTypeInit"><c>ErlNifResourceTypeInit</c></seecref> + structure that contains the callback function pointers <c>dtor</c>, + <c>down</c>, <c>stop</c> and the new <c>dyncall</c>. The struct also + contains the field <c>members</c> that must be set to the number of initialized + callbacks counted from the top of the struct. For example, to + initialize all callbacks including <c>dyncall</c>, <c>members</c> + should be set to 4. All callbacks are optional and may be set to <c>NULL</c>. + </p> </desc> </func> diff --git a/erts/emulator/beam/erl_nif.c b/erts/emulator/beam/erl_nif.c index 3181958498..70b18b9ff1 100644 --- a/erts/emulator/beam/erl_nif.c +++ b/erts/emulator/beam/erl_nif.c @@ -2326,6 +2326,17 @@ static void resource_down_during_takeover(ErlNifEnv* env, void* obj, rt->fn_real.down(env, obj, pid, mon); erts_rwmtx_runlock(&erts_nif_call_tab_lock); } +static void resource_dyncall_during_takeover(ErlNifEnv* env, void* obj, + void* call_data) +{ + ErtsResource* resource = DATA_TO_RESOURCE(obj); + ErlNifResourceType* rt = resource->type; + + erts_rwmtx_rlock(&erts_nif_call_tab_lock); + ASSERT(rt->fn_real.dyncall); + rt->fn_real.dyncall(env, obj, call_data); + erts_rwmtx_runlock(&erts_nif_call_tab_lock); +} static void resource_dtor_nop(ErlNifEnv* env, void* obj) { @@ -2351,7 +2362,7 @@ ErlNifResourceType* open_resource_type(ErlNifEnv* env, const ErlNifResourceTypeInit* init, ErlNifResourceFlags flags, ErlNifResourceFlags* tried, - size_t sizeof_init) + int init_members) { ErlNifResourceType* type = NULL; ErlNifResourceFlags op = flags; @@ -2393,10 +2404,19 @@ ErlNifResourceType* open_resource_type(ErlNifEnv* env, ort->op = op; ort->type = type; sys_memzero(&ort->new_callbacks, sizeof(ErlNifResourceTypeInit)); - ASSERT(sizeof_init > 0 && sizeof_init <= sizeof(ErlNifResourceTypeInit)); - sys_memcpy(&ort->new_callbacks, init, sizeof_init); + switch (init_members) { + case 4: ort->new_callbacks.dyncall = init->dyncall; + case 3: ort->new_callbacks.down = init->down; + case 2: ort->new_callbacks.stop = init->stop; + case 1: ort->new_callbacks.dtor = init->dtor; + case 0: + break; + default: + ERTS_ASSERT(!"Invalid number of ErlNifResourceTypeInit members"); + } if (!ort->new_callbacks.dtor && (ort->new_callbacks.down || - ort->new_callbacks.stop)) { + ort->new_callbacks.stop || + ort->new_callbacks.dyncall)) { /* Set dummy dtor for fast rt_have_callbacks() * This case should be rare anyway */ ort->new_callbacks.dtor = resource_dtor_nop; @@ -2418,10 +2438,9 @@ enif_open_resource_type(ErlNifEnv* env, ErlNifResourceFlags flags, ErlNifResourceFlags* tried) { - ErlNifResourceTypeInit init = {dtor, NULL}; + ErlNifResourceTypeInit init = {dtor}; ASSERT(module_str == NULL); /* for now... */ - return open_resource_type(env, name_str, &init, flags, tried, - sizeof(init)); + return open_resource_type(env, name_str, &init, flags, tried, 1); } ErlNifResourceType* @@ -2431,8 +2450,17 @@ enif_open_resource_type_x(ErlNifEnv* env, ErlNifResourceFlags flags, ErlNifResourceFlags* tried) { - return open_resource_type(env, name_str, init, flags, tried, - env->mod_nif->entry.sizeof_ErlNifResourceTypeInit); + return open_resource_type(env, name_str, init, flags, tried, 3); +} + +ErlNifResourceType* +enif_init_resource_type(ErlNifEnv* env, + const char* name_str, + const ErlNifResourceTypeInit* init, + ErlNifResourceFlags flags, + ErlNifResourceFlags* tried) +{ + return open_resource_type(env, name_str, init, flags, tried, init->members); } static void prepare_opened_rt(struct erl_module_nif* lib) @@ -2459,6 +2487,7 @@ static void prepare_opened_rt(struct erl_module_nif* lib) type->fn.dtor = resource_dtor_during_takeover; type->fn.stop = resource_stop_during_takeover; type->fn.down = resource_down_during_takeover; + type->fn.dyncall = resource_dyncall_during_takeover; } type->owner = lib; @@ -2897,6 +2926,34 @@ size_t enif_sizeof_resource(void* obj) } } +int enif_dynamic_resource_call(ErlNifEnv* caller_env, + ERL_NIF_TERM rt_module_atom, + ERL_NIF_TERM rt_name_atom, + ERL_NIF_TERM resource_term, + void* call_data) +{ + Binary* mbin; + ErtsResource* resource; + ErlNifResourceType* rt; + + if (!is_internal_magic_ref(resource_term)) + return 1; + + mbin = erts_magic_ref2bin(resource_term); + resource = (ErtsResource*) ERTS_MAGIC_BIN_UNALIGNED_DATA(mbin); + if (ERTS_MAGIC_BIN_DESTRUCTOR(mbin) != NIF_RESOURCE_DTOR) + return 1; + rt = resource->type; + ASSERT(rt->owner); + if (rt->module != rt_module_atom || rt->name != rt_name_atom + || !rt->fn.dyncall) { + return 1; + } + + rt->fn.dyncall(caller_env, &resource->data, call_data); + return 0; +} + void* enif_dlopen(const char* lib, void (*err_handler)(void*,const char*), void* err_arg) diff --git a/erts/emulator/beam/erl_nif.h b/erts/emulator/beam/erl_nif.h index 1876193c6c..c84efc6e39 100644 --- a/erts/emulator/beam/erl_nif.h +++ b/erts/emulator/beam/erl_nif.h @@ -56,9 +56,10 @@ ** enif_vfprintf, enif_vsnprintf, enif_make_map_from_arrays ** 2.15: 22.0 ERL_NIF_SELECT_CANCEL, enif_select_(read|write) ** enif_term_type +** 2.16: 24.0 enif_init_resource_type, enif_dynamic_resource_call */ #define ERL_NIF_MAJOR_VERSION 2 -#define ERL_NIF_MINOR_VERSION 15 +#define ERL_NIF_MINOR_VERSION 16 /* * WHEN CHANGING INTERFACE VERSION, also replace erts version below with @@ -69,7 +70,7 @@ * If you're not on the OTP team, you should use a placeholder like * erts-@MyName@ instead. */ -#define ERL_NIF_MIN_ERTS_VERSION "erts-10.4" +#define ERL_NIF_MIN_ERTS_VERSION "erts-11.2" /* * The emulator will refuse to load a nif-lib with a major version @@ -96,7 +97,7 @@ typedef ErlNapiSInt64 ErlNifSInt64; typedef ErlNapiUInt ErlNifUInt; typedef ErlNapiSInt ErlNifSInt; -# define ERL_NIF_VM_VARIANT "beam.vanilla" +#define ERL_NIF_VM_VARIANT "beam.vanilla" typedef ErlNifUInt ERL_NIF_TERM; typedef ERL_NIF_TERM ERL_NIF_UINT; @@ -204,11 +205,14 @@ typedef struct enif_resource_type_t ErlNifResourceType; typedef void ErlNifResourceDtor(ErlNifEnv*, void*); typedef void ErlNifResourceStop(ErlNifEnv*, void*, ErlNifEvent, int is_direct_call); typedef void ErlNifResourceDown(ErlNifEnv*, void*, ErlNifPid*, ErlNifMonitor*); +typedef void ErlNifResourceDynCall(ErlNifEnv*, void* obj, void* call_data); typedef struct { ErlNifResourceDtor* dtor; ErlNifResourceStop* stop; /* at ERL_NIF_SELECT_STOP event */ ErlNifResourceDown* down; /* enif_monitor_process */ + int members; + ErlNifResourceDynCall* dyncall; } ErlNifResourceTypeInit; typedef ErlDrvSysInfo ErlNifSysInfo; diff --git a/erts/emulator/beam/erl_nif_api_funcs.h b/erts/emulator/beam/erl_nif_api_funcs.h index d8debba6a5..00797fb850 100644 --- a/erts/emulator/beam/erl_nif_api_funcs.h +++ b/erts/emulator/beam/erl_nif_api_funcs.h @@ -216,6 +216,8 @@ ERL_NIF_API_FUNC_DECL(void,enif_set_pid_undefined,(ErlNifPid* pid)); ERL_NIF_API_FUNC_DECL(int,enif_is_pid_undefined,(const ErlNifPid* pid)); ERL_NIF_API_FUNC_DECL(ErlNifTermType,enif_term_type,(ErlNifEnv* env, ERL_NIF_TERM term)); +ERL_NIF_API_FUNC_DECL(ErlNifResourceType*,enif_init_resource_type,(ErlNifEnv*, const char* name_str, const ErlNifResourceTypeInit*, ErlNifResourceFlags flags, ErlNifResourceFlags* tried)); +ERL_NIF_API_FUNC_DECL(int,enif_dynamic_resource_call,(ErlNifEnv*, ERL_NIF_TERM mod, ERL_NIF_TERM name, ERL_NIF_TERM rsrc, void* call_data)); /* ** ADD NEW ENTRIES HERE (before this comment) !!! @@ -404,7 +406,7 @@ ERL_NIF_API_FUNC_DECL(ErlNifTermType,enif_term_type,(ErlNifEnv* env, ERL_NIF_TER # define enif_set_pid_undefined ERL_NIF_API_FUNC_MACRO(enif_set_pid_undefined) # define enif_is_pid_undefined ERL_NIF_API_FUNC_MACRO(enif_is_pid_undefined) # define enif_term_type ERL_NIF_API_FUNC_MACRO(enif_term_type) - +# define enif_resource_handshake ERL_NIF_API_FUNC_MACRO(enif_resource_handshake) /* ** ADD NEW ENTRIES HERE (before this comment) */ diff --git a/erts/emulator/test/nif_SUITE.erl b/erts/emulator/test/nif_SUITE.erl index 147b15bb59..795b0efda3 100644 --- a/erts/emulator/test/nif_SUITE.erl +++ b/erts/emulator/test/nif_SUITE.erl @@ -50,6 +50,7 @@ api_macros/1, from_array/1, iolist_as_binary/1, resource/1, resource_binary/1, resource_takeover/1, + t_dynamic_resource_call/1, threading/1, send/1, send2/1, send3/1, send_threaded/1, send_trace/1, send_seq_trace/1, neg/1, is_checks/1, @@ -95,6 +96,7 @@ all() -> {group, select}, {group, monitor}, monitor_frenzy, + t_dynamic_resource_call, hipe, t_load_race, t_call_nif_early, @@ -1239,6 +1241,66 @@ gc_and_return(RetVal) -> false = code:purge(hipe_compiled), ok. +t_dynamic_resource_call(Config) -> + ensure_lib_loaded(Config), + Data = proplists:get_value(data_dir, Config), + File = filename:join(Data, "nif_mod"), + {ok,nif_mod,NifModBin} = compile:file(File, [binary,return_errors]), + + dynamic_resource_call_do(Config, NifModBin), + erlang:garbage_collect(), + + true = erlang:delete_module(nif_mod), + true = erlang:purge_module(nif_mod), + + receive after 10 -> ok end, + [{{resource_dtor_A_v1,_},1,2,102}, + {unload,1,3,103}] = nif_mod_call_history(), + + ok. + + +dynamic_resource_call_do(Config, NifModBin) -> + {module,nif_mod} = erlang:load_module(nif_mod,NifModBin), + + ok = nif_mod:load_nif_lib(Config, 1, + [{resource_type, 0, ?RT_CREATE, "with_dyncall", + resource_dtor_A, ?RT_CREATE, resource_dyncall}]), + + hold_nif_mod_priv_data(nif_mod:get_priv_data_ptr()), + [{load,1,1,101}, + {get_priv_data_ptr,1,2,102}] = nif_mod_call_history(), + + R = nif_mod:make_new_resource(0, <<>>), + + {0, 1001} = dynamic_resource_call(nif_mod, with_dyncall, R, 1000), + {1, 1000} = dynamic_resource_call(wrong, with_dyncall, R, 1000), + {1, 1000} = dynamic_resource_call(nif_mod, wrong, R, 1000), + + %% Upgrade resource type with new dyncall implementation. + {module,nif_mod} = erlang:load_module(nif_mod,NifModBin), + ok = nif_mod:load_nif_lib(Config, 2, + [{resource_type, 0, ?RT_TAKEOVER, "with_dyncall", + resource_dtor_A, ?RT_TAKEOVER, resource_dyncall}]), + [{upgrade,2,1,201}] = nif_mod_call_history(), + + {0, 1002} = dynamic_resource_call(nif_mod, with_dyncall, R, 1000), + true = erlang:purge_module(nif_mod), + [{unload,1,3,103}] = nif_mod_call_history(), + + %% Upgrade resource type with missing dyncall implementation. + {module,nif_mod} = erlang:load_module(nif_mod,NifModBin), + ok = nif_mod:load_nif_lib(Config, 1, + [{resource_type, 0, ?RT_TAKEOVER, "with_dyncall", + resource_dtor_A, ?RT_TAKEOVER, null}]), + [{upgrade,1,1,101}] = nif_mod_call_history(), + + {1, 1000} = dynamic_resource_call(nif_mod, with_dyncall, R, 1000), + true = erlang:purge_module(nif_mod), + [{unload,2,2,202}] = nif_mod_call_history(), + ok. + + %% Test NIF building heap fragments heap_frag(Config) when is_list(Config) -> @@ -3857,5 +3920,7 @@ compare_pids_nif(_, _) -> ?nif_stub. term_type_nif(_) -> ?nif_stub. +dynamic_resource_call(_,_,_,_) -> ?nif_stub. + nif_stub_error(Line) -> exit({nif_not_loaded,module,?MODULE,line,Line}). diff --git a/erts/emulator/test/nif_SUITE_data/nif_SUITE.c b/erts/emulator/test/nif_SUITE_data/nif_SUITE.c index 2c089b430c..b7580274ed 100644 --- a/erts/emulator/test/nif_SUITE_data/nif_SUITE.c +++ b/erts/emulator/test/nif_SUITE_data/nif_SUITE.c @@ -3343,6 +3343,23 @@ static void frenzy_resource_down(ErlNifEnv* env, void* obj, ErlNifPid* pid, abort(); } +static ERL_NIF_TERM dynamic_resource_call(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) +{ + const ERL_NIF_TERM rt_module = argv[0]; + const ERL_NIF_TERM rt_name = argv[1]; + const ERL_NIF_TERM rsrc = argv[2]; + int call_data; + int ret; + + if (!enif_get_int(env, argv[3], &call_data)) { + return enif_make_badarg(env); + } + ret = enif_dynamic_resource_call(env, rt_module, rt_name, rsrc, &call_data); + return enif_make_tuple2(env, + enif_make_int(env, ret), + enif_make_int(env, call_data)); +} + /*********** testing ioq ************/ static void ioq_resource_dtor(ErlNifEnv* env, void* obj) { @@ -3412,7 +3429,7 @@ static ERL_NIF_TERM ioq(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]) ERL_NIF_TERM *elems, tail, list; ErlNifEnv *myenv = NULL; - if (argv >= 3 && enif_is_identical(argv[2], enif_make_atom(env, "use_stack"))) + if (argc >= 3 && enif_is_identical(argv[2], enif_make_atom(env, "use_stack"))) iovec = &vec; if (argc >= 4 && enif_is_identical(argv[3], enif_make_atom(env, "use_env"))) myenv = env; @@ -3763,6 +3780,7 @@ static ErlNifFunc nif_funcs[] = {"compare_monitors_nif", 2, compare_monitors_nif}, {"make_monitor_term_nif", 1, make_monitor_term_nif}, {"monitor_frenzy_nif", 4, monitor_frenzy_nif}, + {"dynamic_resource_call", 4, dynamic_resource_call}, {"whereis_send", 3, whereis_send}, {"whereis_term", 2, whereis_term}, {"whereis_thd_lookup", 3, whereis_thd_lookup}, @@ -3777,6 +3795,7 @@ static ErlNifFunc nif_funcs[] = {"is_pid_undefined_nif", 1, is_pid_undefined_nif}, {"compare_pids_nif", 2, compare_pids_nif}, {"term_type_nif", 1, term_type_nif} + }; ERL_NIF_INIT(nif_SUITE,nif_funcs,load,NULL,upgrade,unload) diff --git a/erts/emulator/test/nif_SUITE_data/nif_mod.c b/erts/emulator/test/nif_SUITE_data/nif_mod.c index f2f49d0bde..117860e559 100644 --- a/erts/emulator/test/nif_SUITE_data/nif_mod.c +++ b/erts/emulator/test/nif_SUITE_data/nif_mod.c @@ -26,6 +26,9 @@ #if ERL_NIF_MAJOR_VERSION*100 + ERL_NIF_MINOR_VERSION >= 215 # define HAVE_ENIF_MONITOR_PROCESS #endif +#if ERL_NIF_MAJOR_VERSION*100 + ERL_NIF_MINOR_VERSION >= 216 +# define HAVE_ENIF_DYNAMIC_RESOURCE_CALL +#endif #define CHECK(X) ((void)((X) || (check_abort(__LINE__),1))) #ifdef __GNUC__ @@ -47,6 +50,7 @@ static ERL_NIF_TERM am_resource_type; static ERL_NIF_TERM am_resource_dtor_A; static ERL_NIF_TERM am_resource_dtor_B; static ERL_NIF_TERM am_resource_down_D; +static ERL_NIF_TERM am_resource_dyncall; static ERL_NIF_TERM am_return; static NifModPrivData* priv_data(ErlNifEnv* env) @@ -62,6 +66,7 @@ static void init(ErlNifEnv* env) am_resource_dtor_A = enif_make_atom(env, "resource_dtor_A"); am_resource_dtor_B = enif_make_atom(env, "resource_dtor_B"); am_resource_down_D = enif_make_atom(env, "resource_down_D"); + am_resource_dyncall = enif_make_atom(env, "resource_dyncall"); am_return = enif_make_atom(env, "return"); } @@ -123,6 +128,15 @@ static void resource_down_D(ErlNifEnv* env, void* a, ErlNifPid* pid, ErlNifMonit } #endif +#ifdef HAVE_ENIF_DYNAMIC_RESOURCE_CALL +static void resource_dyncall(ErlNifEnv* env, void* obj, void* call_data) +{ + int* p = (int*)call_data; + *p += NIF_LIB_VER; +} +#endif + + /* {resource_type, Ix|null, @@ -161,15 +175,31 @@ static void open_resource_type(ErlNifEnv* env, int arity, const ERL_NIF_TERM* ar ErlNifResourceTypeInit init; init.dtor = dtor; init.stop = NULL; - if (enif_is_identical(arr[6], am_null)) { - init.down = NULL; - } - else { - CHECK(enif_is_identical(arr[6], am_resource_down_D)); - init.down = resource_down_D; + init.down = NULL; + +# ifdef HAVE_ENIF_DYNAMIC_RESOURCE_CALL + init.members = 0xdead; + init.dyncall = (ErlNifResourceDynCall*) 0xdeadbeaf; + + if (enif_is_identical(arr[6], am_resource_dyncall)) { + init.dyncall = resource_dyncall; + init.members = 4; + got_ptr = enif_init_resource_type(env, rt_name, &init, + flags.e, &got_res.e); } - got_ptr = enif_open_resource_type_x(env, rt_name, &init, - flags.e, &got_res.e); + else +# endif + { + if (enif_is_identical(arr[6], am_resource_down_D)) { + init.down = resource_down_D; + } + else { + CHECK(enif_is_identical(arr[6], am_null)); + } + got_ptr = enif_open_resource_type_x(env, rt_name, &init, + flags.e, &got_res.e); + + } } else #endif -- 2.26.2
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor