aboutsummaryrefslogtreecommitdiffstats
path: root/erts/emulator/test
diff options
context:
space:
mode:
Diffstat (limited to 'erts/emulator/test')
-rw-r--r--erts/emulator/test/bif_SUITE.erl2
-rw-r--r--erts/emulator/test/bs_construct_SUITE.erl48
-rw-r--r--erts/emulator/test/code_SUITE.erl132
-rw-r--r--erts/emulator/test/distribution_SUITE.erl69
-rw-r--r--erts/emulator/test/message_queue_data_SUITE.erl42
-rw-r--r--erts/emulator/test/tracer_SUITE.erl103
-rw-r--r--erts/emulator/test/tracer_SUITE_data/tracer_test.c4
-rw-r--r--erts/emulator/test/tracer_test.erl4
8 files changed, 296 insertions, 108 deletions
diff --git a/erts/emulator/test/bif_SUITE.erl b/erts/emulator/test/bif_SUITE.erl
index 26bb416bf0..ec6cb6ab72 100644
--- a/erts/emulator/test/bif_SUITE.erl
+++ b/erts/emulator/test/bif_SUITE.erl
@@ -646,6 +646,8 @@ erlang_halt(Config) when is_list(Config) ->
{badrpc,nodedown} = rpc:call(N2, erlang, halt, [0]),
{ok,N3} = slave:start(H, halt_node3),
{badrpc,nodedown} = rpc:call(N3, erlang, halt, [0,[]]),
+ {ok,N4} = slave:start(H, halt_node4),
+ {badrpc,nodedown} = rpc:call(N4, erlang, halt, [lists:duplicate(300,$x)]),
% This test triggers a segfault when dumping a crash dump
% to make sure that we can handle it properly.
diff --git a/erts/emulator/test/bs_construct_SUITE.erl b/erts/emulator/test/bs_construct_SUITE.erl
index 941cb435f7..22a1c0b765 100644
--- a/erts/emulator/test/bs_construct_SUITE.erl
+++ b/erts/emulator/test/bs_construct_SUITE.erl
@@ -527,7 +527,7 @@ huge_float_check({'EXIT',{system_limit,_}}) -> ok;
huge_float_check({'EXIT',{badarg,_}}) -> ok.
huge_binary(Config) when is_list(Config) ->
- ct:timetrap({seconds, 30}),
+ ct:timetrap({seconds, 60}),
16777216 = size(<<0:(id(1 bsl 26)),(-1):(id(1 bsl 26))>>),
garbage_collect(),
{Shift,Return} = case free_mem() of
@@ -561,30 +561,13 @@ huge_binary(Config) when is_list(Config) ->
end.
free_mem() ->
- Cmd = "uname; free",
- Output = string:tokens(os:cmd(Cmd), "\n"),
- io:format("Output from command ~p\n~p\n",[Cmd,Output]),
- case Output of
- [OS, ColumnNames, Values | _] ->
- case string:str(OS,"Linux") of
- 0 ->
- io:format("Unknown OS\n",[]),
- undefined;
- _ ->
- case {string:tokens(ColumnNames, " \t"),
- string:tokens(Values, " \t")} of
- {[_,_,"free"|_],["Mem:",_,_,FreeKb|_]} ->
- list_to_integer(FreeKb) div 1024;
- _ ->
- io:format("Failed to parse output from 'free':\n",[]),
- undefined
- end
- end;
- _ ->
- io:format("Too few lines in output\n",[]),
- undefined
+ {ok,Apps} = application:ensure_all_started(os_mon),
+ Mem = memsup:get_system_memory_data(),
+ [ok = application:stop(App)||App <- Apps],
+ case proplists:get_value(free_memory,Mem) of
+ undefined -> undefined;
+ Val -> Val div 1024
end.
-
system_limit(Config) when is_list(Config) ->
WordSize = erlang:system_info(wordsize),
@@ -614,8 +597,7 @@ system_limit_32() ->
{'EXIT',{system_limit,_}} = (catch <<42:536870912/unit:8>>),
{'EXIT',{system_limit,_}} = (catch <<42:(id(536870912))/unit:8>>),
{'EXIT',{system_limit,_}} = (catch <<0:(id(8)),42:536870912/unit:8>>),
- {'EXIT',{system_limit,_}} =
- (catch <<0:(id(8)),42:(id(536870912))/unit:8>>),
+ {'EXIT',{system_limit,_}} = (catch <<0:(id(8)),42:(id(536870912))/unit:8>>),
%% The size would be silently truncated, resulting in a crash.
{'EXIT',{system_limit,_}} = (catch <<0:(1 bsl 35)>>),
@@ -627,16 +609,10 @@ system_limit_32() ->
ok.
badarg(Config) when is_list(Config) ->
- {'EXIT',{badarg,_}} =
- (catch <<0:(id(1 bsl 100)),0:(id(-1))>>),
- {'EXIT',{badarg,_}} =
- (catch <<0:(id(1 bsl 100)),0:(id(-(1 bsl 70)))>>),
- {'EXIT',{badarg,_}} =
- (catch <<0:(id(-(1 bsl 70))),0:(id(1 bsl 100))>>),
-
- {'EXIT',{badarg,_}} =
- (catch <<(id(<<>>))/binary,0:(id(-(1 bsl 100)))>>),
-
+ {'EXIT',{badarg,_}} = (catch <<0:(id(1 bsl 100)),0:(id(-1))>>),
+ {'EXIT',{badarg,_}} = (catch <<0:(id(1 bsl 100)),0:(id(-(1 bsl 70)))>>),
+ {'EXIT',{badarg,_}} = (catch <<0:(id(-(1 bsl 70))),0:(id(1 bsl 100))>>),
+ {'EXIT',{badarg,_}} = (catch <<(id(<<>>))/binary,0:(id(-(1 bsl 100)))>>),
ok.
copy_writable_binary(Config) when is_list(Config) ->
diff --git a/erts/emulator/test/code_SUITE.erl b/erts/emulator/test/code_SUITE.erl
index 29b95ef674..2347a3d4ef 100644
--- a/erts/emulator/test/code_SUITE.erl
+++ b/erts/emulator/test/code_SUITE.erl
@@ -26,7 +26,7 @@
external_fun/1,get_chunk/1,module_md5/1,make_stub/1,
make_stub_many_funs/1,constant_pools/1,constant_refc_binaries/1,
false_dependency/1,coverage/1,fun_confusion/1,
- t_copy_literals/1]).
+ t_copy_literals/1, t_copy_literals_frags/1]).
-define(line_trace, 1).
-include_lib("common_test/include/ct.hrl").
@@ -38,7 +38,7 @@ all() ->
t_check_process_code_ets, t_check_old_code, external_fun, get_chunk,
module_md5, make_stub, make_stub_many_funs,
constant_pools, constant_refc_binaries, false_dependency,
- coverage, fun_confusion, t_copy_literals].
+ coverage, fun_confusion, t_copy_literals, t_copy_literals_frags].
init_per_suite(Config) ->
erts_debug:set_internal_state(available_internal_state, true),
@@ -766,6 +766,134 @@ t_copy_literals(Config) when is_list(Config) ->
ok = flush(),
ok.
+-define(mod, t_copy_literals_frags).
+t_copy_literals_frags(Config) when is_list(Config) ->
+ Bin = gen_lit(?mod,[{a,{1,2,3,4,5,6,7}},
+ {b,"hello world"},
+ {c, <<"hello world">>},
+ {d, {"hello world", {1.0, 2.0, <<"some">>, "string"}}},
+ {e, <<"off heap", 0, 1, 2, 3, 4, 5, 6, 7,
+ 8, 9,10,11,12,13,14,15,
+ 0, 1, 2, 3, 4, 5, 6, 7,
+ 8, 9,10,11,12,13,14,15,
+ 0, 1, 2, 3, 4, 5, 6, 7,
+ 8, 9,10,11,12,13,14,15,
+ 0, 1, 2, 3, 4, 5, 6, 7,
+ 8, 9,10,11,12,13,14,15>>}]),
+
+ {module, ?mod} = erlang:load_module(?mod, Bin),
+ N = 6000,
+ Recv = spawn_opt(fun() -> receive
+ read ->
+ io:format("reading"),
+ literal_receiver()
+ end
+ end, [link,{min_heap_size, 10000}]),
+ Switcher = spawn_link(fun() -> literal_switcher() end),
+ Pids = [spawn_opt(fun() -> receive
+ {Pid, go, Recv, N} ->
+ io:format("sender batch (~w) start ~w~n",[N,self()]),
+ literal_sender(N,Recv),
+ Pid ! {self(), ok}
+ end
+ end, [link,{min_heap_size,800}]) || _ <- lists:seq(1,100)],
+ _ = [Pid ! {self(), go, Recv, N} || Pid <- Pids],
+ %% don't read immediately
+ timer:sleep(5),
+ Recv ! read,
+ Switcher ! {switch,?mod,Bin,[Recv|Pids],200},
+ _ = [receive {Pid, ok} -> ok end || Pid <- Pids],
+ Switcher ! {self(), done},
+ receive {Switcher, ok} -> ok end,
+ Recv ! {self(), done},
+ receive {Recv, ok} -> ok end,
+ ok.
+
+literal_receiver() ->
+ receive
+ {Pid, done} ->
+ io:format("reader_done~n"),
+ Pid ! {self(), ok};
+ {_Pid, msg, [A,B,C,D,E]} ->
+ A = ?mod:a(),
+ B = ?mod:b(),
+ C = ?mod:c(),
+ D = ?mod:d(),
+ E = ?mod:e(),
+ literal_receiver();
+ {Pid, sender_confirm} ->
+ io:format("sender confirm ~w~n", [Pid]),
+ Pid ! {self(), ok},
+ literal_receiver()
+ end.
+
+literal_sender(0, Recv) ->
+ Recv ! {self(), sender_confirm},
+ receive {Recv, ok} -> ok end;
+literal_sender(N, Recv) ->
+ Recv ! {self(), msg, [?mod:a(),
+ ?mod:b(),
+ ?mod:c(),
+ ?mod:d(),
+ ?mod:e()]},
+ literal_sender(N - 1, Recv).
+
+literal_switcher() ->
+ receive
+ {switch,Mod,Bin,Pids,Tmo} ->
+ literal_switcher(Mod,Bin,Pids,Tmo)
+ end.
+literal_switcher(Mod,Bin,Pids,Tmo) ->
+ receive
+ {Pid,done} ->
+ Pid ! {self(),ok}
+ after Tmo ->
+ io:format("load module ~w~n", [Mod]),
+ {module, Mod} = erlang:load_module(Mod,Bin),
+ ok = check_and_purge(Pids,Mod),
+ io:format("purge complete ~w~n", [Mod]),
+ literal_switcher(Mod,Bin,Pids,Tmo+Tmo)
+ end.
+
+check_and_purge([],Mod) ->
+ erlang:purge_module(Mod),
+ ok;
+check_and_purge(Pids,Mod) ->
+ io:format("purge ~w~n", [Mod]),
+ Tag = make_ref(),
+ _ = [begin
+ erlang:check_process_code(Pid,Mod,[{async,{Tag,Pid}}])
+ end || Pid <- Pids],
+ Retry = check_and_purge_receive(Pids,Tag,[]),
+ check_and_purge(Retry,Mod).
+
+check_and_purge_receive([Pid|Pids],Tag,Retry) ->
+ receive
+ {check_process_code, {Tag, Pid}, false} ->
+ check_and_purge_receive(Pids,Tag,Retry);
+ {check_process_code, {Tag, Pid}, true} ->
+ check_and_purge_receive(Pids,Tag,[Pid|Retry])
+ end;
+check_and_purge_receive([],_,Retry) ->
+ Retry.
+
+
+gen_lit(Module,Terms) ->
+ FunStrings = [lists:flatten(io_lib:format("~w() -> ~w.~n", [F,Term]))||{F,Term}<-Terms],
+ FunForms = function_forms(FunStrings),
+ Forms = [{attribute,erl_anno:new(1),module,Module},
+ {attribute,erl_anno:new(2),export,[FA || {FA,_} <- FunForms]}] ++
+ [Function || {_, Function} <- FunForms],
+ {ok, Module, Bin} = compile:forms(Forms),
+ Bin.
+
+function_forms([]) -> [];
+function_forms([S|Ss]) ->
+ {ok, Ts,_} = erl_scan:string(S),
+ {ok, Form} = erl_parse:parse_form(Ts),
+ Fun = element(3, Form),
+ Arity = element(4, Form),
+ [{{Fun,Arity}, Form}|function_forms(Ss)].
chase_msg(0, Pid) ->
chase_loop(Pid);
diff --git a/erts/emulator/test/distribution_SUITE.erl b/erts/emulator/test/distribution_SUITE.erl
index d0096fb1bc..26780f6017 100644
--- a/erts/emulator/test/distribution_SUITE.erl
+++ b/erts/emulator/test/distribution_SUITE.erl
@@ -55,7 +55,8 @@
bad_dist_ext_receive/1,
bad_dist_ext_process_info/1,
bad_dist_ext_control/1,
- bad_dist_ext_connection_id/1]).
+ bad_dist_ext_connection_id/1,
+ start_epmd_false/1, epmd_module/1]).
%% Internal exports.
-export([sender/3, receiver2/2, dummy_waiter/0, dead_process/0,
@@ -64,6 +65,9 @@
dist_evil_parallel_receiver/0,
sendersender/4, sendersender2/4]).
+%% epmd_module exports
+-export([start_link/0, register_node/2, port_please/2]).
+
suite() ->
[{ct_hooks,[ts_install_cth]},
{timetrap, {minutes, 4}}].
@@ -76,7 +80,8 @@ all() ->
{group, trap_bif}, {group, dist_auto_connect},
dist_parallel_send, atom_roundtrip, unicode_atom_roundtrip, atom_roundtrip_r15b,
contended_atom_cache_entry, contended_unicode_atom_cache_entry,
- bad_dist_structure, {group, bad_dist_ext}].
+ bad_dist_structure, {group, bad_dist_ext},
+ start_epmd_false, epmd_module].
groups() ->
[{bulk_send, [], [bulk_send_small, bulk_send_big, bulk_send_bigbig]},
@@ -1881,6 +1886,66 @@ dmsg_ext(Term) ->
dmsg_bad_atom_cache_ref() ->
[$R, 137].
+start_epmd_false(Config) when is_list(Config) ->
+ %% Start a node with the option -start_epmd false.
+ {ok, OtherNode} = start_node(start_epmd_false, "-start_epmd false"),
+ %% We should be able to ping it, as epmd was started by us:
+ pong = net_adm:ping(OtherNode),
+ stop_node(OtherNode),
+
+ ok.
+
+epmd_module(Config) when is_list(Config) ->
+ %% We need a relay node to test this, since the test node uses the
+ %% standard epmd module.
+ Sock1 = start_relay_node(epmd_module_node1, "-epmd_module " ++ ?MODULE_STRING),
+ Node1 = inet_rpc_nodename(Sock1),
+ %% Ask what port it's listening on - it won't have registered with
+ %% epmd.
+ {ok, {ok, Port1}} = do_inet_rpc(Sock1, application, get_env, [kernel, dist_listen_port]),
+
+ %% Start a second node, passing the port number as a secret
+ %% argument.
+ Sock2 = start_relay_node(epmd_module_node2, "-epmd_module " ++ ?MODULE_STRING
+ ++ " -other_node_port " ++ integer_to_list(Port1)),
+ Node2 = inet_rpc_nodename(Sock2),
+ %% Node 1 can't ping node 2
+ {ok, pang} = do_inet_rpc(Sock1, net_adm, ping, [Node2]),
+ {ok, []} = do_inet_rpc(Sock1, erlang, nodes, []),
+ {ok, []} = do_inet_rpc(Sock2, erlang, nodes, []),
+ %% But node 2 can ping node 1
+ {ok, pong} = do_inet_rpc(Sock2, net_adm, ping, [Node1]),
+ {ok, [Node2]} = do_inet_rpc(Sock1, erlang, nodes, []),
+ {ok, [Node1]} = do_inet_rpc(Sock2, erlang, nodes, []),
+
+ stop_relay_node(Sock2),
+ stop_relay_node(Sock1).
+
+%% epmd_module functions:
+
+start_link() ->
+ ignore.
+
+register_node(_Name, Port) ->
+ %% Save the port number we're listening on.
+ application:set_env(kernel, dist_listen_port, Port),
+ Creation = rand:uniform(3),
+ {ok, Creation}.
+
+port_please(_Name, _Ip) ->
+ case init:get_argument(other_node_port) of
+ error ->
+ %% None specified. Default to 42.
+ Port = 42,
+ Version = 5,
+ {port, Port, Version};
+ {ok, [[PortS]]} ->
+ %% Port number given on command line.
+ Port = list_to_integer(PortS),
+ Version = 5,
+ {port, Port, Version}
+ end.
+
%%% Utilities
timestamp() ->
diff --git a/erts/emulator/test/message_queue_data_SUITE.erl b/erts/emulator/test/message_queue_data_SUITE.erl
index 226462676c..44e77dfad0 100644
--- a/erts/emulator/test/message_queue_data_SUITE.erl
+++ b/erts/emulator/test/message_queue_data_SUITE.erl
@@ -52,18 +52,12 @@ basic(Config) when is_list(Config) ->
ok = rpc:call(Node2, ?MODULE, basic_test, [on_heap]),
stop_node(Node2),
- {ok, Node3} = start_node(Config, "+hmqd mixed"),
- ok = rpc:call(Node3, ?MODULE, basic_test, [mixed]),
- stop_node(Node3),
-
ok.
is_valid_mqd_value(off_heap) ->
true;
is_valid_mqd_value(on_heap) ->
true;
-is_valid_mqd_value(mixed) ->
- true;
is_valid_mqd_value(_) ->
false.
@@ -78,9 +72,6 @@ basic_test(Default) ->
{message_queue_data, off_heap} = process_info(self(), message_queue_data),
off_heap = process_flag(message_queue_data, on_heap),
{message_queue_data, on_heap} = process_info(self(), message_queue_data),
- on_heap = process_flag(message_queue_data, mixed),
- {message_queue_data, mixed} = process_info(self(), message_queue_data),
- mixed = process_flag(message_queue_data, Default),
{'EXIT', _} = (catch process_flag(message_queue_data, blupp)),
P1 = spawn_opt(fun () -> receive after infinity -> ok end end,
@@ -101,12 +92,6 @@ basic_test(Default) ->
unlink(P3),
exit(P3, bye),
- P4 = spawn_opt(fun () -> receive after infinity -> ok end end,
- [link, {message_queue_data, mixed}]),
- {message_queue_data, mixed} = process_info(P4, message_queue_data),
- unlink(P4),
- exit(P4, bye),
-
{'EXIT', _} = (catch spawn_opt(fun () -> receive after infinity -> ok end end,
[link, {message_queue_data, blapp}])),
@@ -116,21 +101,18 @@ process_info_messages(Config) when is_list(Config) ->
Tester = self(),
P1 = spawn_opt(fun () ->
receive after 500 -> ok end,
- mixed = process_flag(message_queue_data, off_heap),
+ on_heap = process_flag(message_queue_data, off_heap),
Tester ! first,
receive after 500 -> ok end,
off_heap = process_flag(message_queue_data, on_heap),
Tester ! second,
receive after 500 -> ok end,
- on_heap = process_flag(message_queue_data, mixed),
+ on_heap = process_flag(message_queue_data, off_heap),
Tester ! third,
- receive after 500 -> ok end,
- mixed = process_flag(message_queue_data, off_heap),
- Tester ! fourth,
receive after infinity -> ok end
end,
- [link, {message_queue_data, mixed}]),
+ [link, {message_queue_data, on_heap}]),
P1 ! "A",
receive first -> ok end,
@@ -139,25 +121,20 @@ process_info_messages(Config) when is_list(Config) ->
P1 ! "C",
receive third -> ok end,
P1 ! "D",
- receive fourth -> ok end,
- P1 ! "E",
- {messages, ["A", "B", "C", "D", "E"]} = process_info(P1, messages),
+ {messages, ["A", "B", "C", "D"]} = process_info(P1, messages),
P2 = spawn_opt(fun () ->
receive after 500 -> ok end,
- mixed = process_flag(message_queue_data, off_heap),
+ on_heap = process_flag(message_queue_data, off_heap),
Tester ! first,
receive after 500 -> ok end,
off_heap = process_flag(message_queue_data, on_heap),
Tester ! second,
receive after 500 -> ok end,
- on_heap = process_flag(message_queue_data, mixed),
+ on_heap = process_flag(message_queue_data, off_heap),
Tester ! third,
receive after 500 -> ok end,
- mixed = process_flag(message_queue_data, off_heap),
- Tester ! fourth,
- receive after 500 -> ok end,
Tester ! process_info(self(), messages),
@@ -165,11 +142,10 @@ process_info_messages(Config) when is_list(Config) ->
receive M2 -> M2 = "B" end,
receive M3 -> M3 = "C" end,
receive M4 -> M4 = "D" end,
- receive M5 -> M5 = "E" end,
Tester ! self()
end,
- [link, {message_queue_data, mixed}]),
+ [link, {message_queue_data, on_heap}]),
P2 ! "A",
receive first -> ok end,
@@ -178,12 +154,10 @@ process_info_messages(Config) when is_list(Config) ->
P2 ! "C",
receive third -> ok end,
P2 ! "D",
- receive fourth -> ok end,
- P2 ! "E",
receive
Msg ->
- {messages, ["A", "B", "C", "D", "E"]} = Msg
+ {messages, ["A", "B", "C", "D"]} = Msg
end,
receive P2 -> ok end,
diff --git a/erts/emulator/test/tracer_SUITE.erl b/erts/emulator/test/tracer_SUITE.erl
index 20fb7e475e..9eb55c9af3 100644
--- a/erts/emulator/test/tracer_SUITE.erl
+++ b/erts/emulator/test/tracer_SUITE.erl
@@ -28,9 +28,9 @@
init_per_group/2,end_per_group/2, init_per_testcase/2,
end_per_testcase/2]).
-export([load/1, unload/1, reload/1, invalid_tracers/1]).
--export([send/1, recv/1, spawn/1, exit/1, link/1, unlink/1,
- getting_linked/1, getting_unlinked/1, register/1, unregister/1,
- in/1, out/1, gc_start/1, gc_end/1]).
+-export([send/1, recv/1, call/1, call_return/1, spawn/1, exit/1,
+ link/1, unlink/1, getting_linked/1, getting_unlinked/1,
+ register/1, unregister/1, in/1, out/1, gc_start/1, gc_end/1]).
suite() -> [{ct_hooks,[ts_install_cth]},
{timetrap, {minutes, 1}}].
@@ -39,9 +39,9 @@ all() ->
[load, unload, reload, invalid_tracers, {group, basic}].
groups() ->
- [{ basic, [], [send, recv, spawn, exit, link, unlink, getting_linked,
- getting_unlinked, register, unregister, in, out,
- gc_start, gc_end]}].
+ [{ basic, [], [send, recv, call, call_return, spawn, exit,
+ link, unlink, getting_linked, getting_unlinked,
+ register, unregister, in, out, gc_start, gc_end]}].
init_per_suite(Config) ->
erlang:trace_pattern({'_','_','_'}, false, [local]),
@@ -223,8 +223,8 @@ send(_Config) ->
Expect = fun(Pid, State, EOpts) ->
receive
Msg ->
- {send, State, Pid, ok, Self, Opts} = Msg,
- check_opts(EOpts, Opts)
+ {send, State, Pid, ok, Opts} = Msg,
+ check_opts(EOpts, Opts, Self)
end
end,
test(send, Tc, Expect).
@@ -239,13 +239,59 @@ recv(_Config) ->
Expect = fun(Pid, State, EOpts) ->
receive
Msg ->
- {'receive', State, Pid, ok, undefined, Opts} = Msg,
+ {'receive', State, Pid, ok, Opts} = Msg,
check_opts(EOpts, Opts)
end
end,
test('receive', Tc, Expect, false).
+call(_Config) ->
+
+ Self = self(),
+ Tc = fun(Pid) ->
+ Pid ! fun() -> call_test(Self), Self ! ok end,
+ receive ok -> ok after 100 -> ct:fail(timeout) end
+ end,
+
+ erlang:trace_pattern({?MODULE, call_test, 1}, [], [local]),
+
+ Expect = fun(Pid, State, EOpts) ->
+ receive
+ Msg ->
+ {call, State, Pid, {?MODULE, call_test, [Self]}, Opts} = Msg,
+ check_opts(EOpts, Opts)
+ end
+ end,
+ test(call, Tc, Expect).
+
+call_return(_Config) ->
+
+ Self = self(),
+ Tc = fun(Pid) ->
+ Pid ! fun() -> call_test(undefined), Self ! ok end,
+ receive ok -> ok after 100 -> ct:fail(timeout) end
+ end,
+
+ 1 = erlang:trace_pattern({?MODULE, call_test, 1}, [{'_',[],[{return_trace}]}], [local]),
+
+ Expect = fun(Pid, State, EOpts) ->
+ receive
+ CallMsg ->
+ {call, State, Pid, {?MODULE, call_test, [undefined]}, COpts} = CallMsg,
+ check_opts(EOpts, COpts)
+ end,
+ receive
+ RetMsg ->
+ {return_from, State, Pid, {?MODULE, call_test, 1}, ROpts} = RetMsg,
+ check_opts(EOpts, ROpts, undefined)
+ end
+ end,
+ test(call, Tc, Expect).
+
+call_test(Arg) ->
+ Arg.
+
spawn(_Config) ->
Tc = fun(Pid) ->
@@ -256,9 +302,8 @@ spawn(_Config) ->
fun(Pid, State, EOpts) ->
receive
Msg ->
- {spawn, State, Pid, NewPid,
- {lists,seq,[1,10]}, Opts} = Msg,
- check_opts(EOpts, Opts),
+ {spawn, State, Pid, NewPid, Opts} = Msg,
+ check_opts(EOpts, Opts, {lists,seq,[1,10]}),
true = is_pid(NewPid) andalso NewPid /= Pid
end
end,
@@ -274,7 +319,7 @@ exit(_Config) ->
fun(Pid, State, EOpts) ->
receive
Msg ->
- {exit, State, Pid, normal, undefined, Opts} = Msg,
+ {exit, State, Pid, normal, Opts} = Msg,
check_opts(EOpts, Opts)
end
end,
@@ -295,7 +340,7 @@ link(_Config) ->
fun(Pid, State, EOpts) ->
receive
Msg ->
- {link, State, Pid, NewPid, undefined, Opts} = Msg,
+ {link, State, Pid, NewPid, Opts} = Msg,
check_opts(EOpts, Opts),
true = is_pid(NewPid) andalso NewPid /= Pid
end
@@ -318,7 +363,7 @@ unlink(_Config) ->
fun(Pid, State, EOpts) ->
receive
Msg ->
- {unlink, State, Pid, NewPid, undefined, Opts} = Msg,
+ {unlink, State, Pid, NewPid, Opts} = Msg,
check_opts(EOpts, Opts),
true = is_pid(NewPid) andalso NewPid /= Pid
end
@@ -340,7 +385,7 @@ getting_linked(_Config) ->
fun(Pid, State, EOpts) ->
receive
Msg ->
- {getting_linked, State, Pid, NewPid, undefined, Opts} = Msg,
+ {getting_linked, State, Pid, NewPid, Opts} = Msg,
check_opts(EOpts, Opts),
true = is_pid(NewPid) andalso NewPid /= Pid
end
@@ -364,7 +409,7 @@ getting_unlinked(_Config) ->
fun(Pid, State, EOpts) ->
receive
Msg ->
- {getting_unlinked, State, Pid, NewPid, undefined, Opts} = Msg,
+ {getting_unlinked, State, Pid, NewPid, Opts} = Msg,
check_opts(EOpts, Opts),
true = is_pid(NewPid) andalso NewPid /= Pid
end
@@ -386,7 +431,7 @@ register(_Config) ->
fun(Pid, State, EOpts) ->
receive
Msg ->
- {register, State, Pid, ?MODULE, undefined, Opts} = Msg,
+ {register, State, Pid, ?MODULE, Opts} = Msg,
check_opts(EOpts, Opts)
end
end,
@@ -407,7 +452,7 @@ unregister(_Config) ->
fun(Pid, State, EOpts) ->
receive
Msg ->
- {unregister, State, Pid, ?MODULE, undefined, Opts} = Msg,
+ {unregister, State, Pid, ?MODULE, Opts} = Msg,
check_opts(EOpts, Opts)
end
end,
@@ -427,8 +472,7 @@ in(_Config) ->
N = (fun F(N) ->
receive
Msg ->
- {in, State, Pid, _,
- undefined, Opts} = Msg,
+ {in, State, Pid, _, Opts} = Msg,
check_opts(EOpts, Opts),
F(N+1)
after 0 -> N
@@ -452,8 +496,7 @@ out(_Config) ->
N = (fun F(N) ->
receive
Msg ->
- {out, State, Pid, _,
- undefined, Opts} = Msg,
+ {out, State, Pid, _, Opts} = Msg,
check_opts(EOpts, Opts),
F(N+1)
after 0 -> N
@@ -477,7 +520,7 @@ gc_start(_Config) ->
fun(Pid, State, EOpts) ->
receive
Msg ->
- {gc_major_start, State, Pid, _, undefined, Opts} = Msg,
+ {gc_major_start, State, Pid, _, Opts} = Msg,
check_opts(EOpts, Opts)
end
end,
@@ -497,7 +540,7 @@ gc_end(_Config) ->
fun(Pid, State, EOpts) ->
receive
Msg ->
- {gc_major_end, State, Pid, _, undefined, Opts} = Msg,
+ {gc_major_end, State, Pid, _, Opts} = Msg,
check_opts(EOpts, Opts)
end
end,
@@ -513,9 +556,7 @@ test(Event, TraceFlag, Tc, Expect, Removes) ->
test(Event, TraceFlag, Tc, Expect, _Removes, Dies) ->
ComplexState = {fun() -> ok end, <<0:(128*8)>>},
- Opts = #{ timestamp => undefined,
- scheduler_id => undefined,
- match_spec_result => true },
+ Opts = #{ },
%% Test that trace works
State1 = {#{ Event => trace }, self(), ComplexState},
@@ -540,8 +581,8 @@ test(Event, TraceFlag, Tc, Expect, _Removes, Dies) ->
Tc(Pid1T),
ok = trace_delivered(Pid1T),
- Expect(Pid1T, State1, Opts#{ scheduler_id := number,
- timestamp := timestamp}),
+ Expect(Pid1T, State1, Opts#{ scheduler_id => number,
+ timestamp => timestamp}),
receive M11T -> ct:fail({unexpected, M11T}) after 0 -> ok end,
if not Dies ->
{flags, [scheduler_id, TraceFlag, timestamp]}
@@ -568,6 +609,8 @@ test(Event, TraceFlag, Tc, Expect, _Removes, Dies) ->
ok.
+check_opts(E, O, Extra) ->
+ check_opts(E#{ extra => Extra }, O).
check_opts(#{ scheduler_id := number } = E, #{ scheduler_id := N } = O)
when is_integer(N) ->
E1 = maps:remove(scheduler_id, E),
diff --git a/erts/emulator/test/tracer_SUITE_data/tracer_test.c b/erts/emulator/test/tracer_SUITE_data/tracer_test.c
index 908f35da9c..a26bb33600 100644
--- a/erts/emulator/test/tracer_SUITE_data/tracer_test.c
+++ b/erts/emulator/test/tracer_SUITE_data/tracer_test.c
@@ -36,7 +36,7 @@ static ERL_NIF_TERM trace(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
static ErlNifFunc nif_funcs[] = {
{"enabled", 3, enabled},
- {"trace", 6, trace}
+ {"trace", 5, trace}
};
ERL_NIF_INIT(tracer_test, nif_funcs, load, NULL, upgrade, unload)
@@ -100,7 +100,7 @@ static ERL_NIF_TERM trace(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
ErlNifPid self, to;
ERL_NIF_TERM *tuple, msg;
const ERL_NIF_TERM *state_tuple;
- ASSERT(argc == 6);
+ ASSERT(argc == 5);
enif_get_tuple(env, argv[1], &state_arity, &state_tuple);
diff --git a/erts/emulator/test/tracer_test.erl b/erts/emulator/test/tracer_test.erl
index d4778f4531..1da80bfe31 100644
--- a/erts/emulator/test/tracer_test.erl
+++ b/erts/emulator/test/tracer_test.erl
@@ -24,14 +24,14 @@
%%% Test tracer
%%%
--export([enabled/3, trace/6]).
+-export([enabled/3, trace/5]).
-export([load/1, load/2]).
-on_load(load/0).
enabled(_, _, _) ->
erlang:nif_error(nif_not_loaded).
-trace(_, _, _, _, _, _) ->
+trace(_, _, _, _, _) ->
erlang:nif_error(nif_not_loaded).
load() ->