aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r--lib/stdlib/test/Makefile1
-rw-r--r--lib/stdlib/test/beam_lib_SUITE.erl30
-rw-r--r--lib/stdlib/test/dets_SUITE.erl291
-rw-r--r--lib/stdlib/test/epp_SUITE.erl33
-rw-r--r--lib/stdlib/test/epp_SUITE_data/bar.hrl4
-rw-r--r--lib/stdlib/test/epp_SUITE_data/include/bar.hrl3
-rw-r--r--lib/stdlib/test/epp_SUITE_data/include/foo.hrl4
-rw-r--r--lib/stdlib/test/epp_SUITE_data/include_local.erl6
-rw-r--r--lib/stdlib/test/erl_eval_SUITE.erl6
-rw-r--r--lib/stdlib/test/erl_pp_SUITE.erl5
-rw-r--r--lib/stdlib/test/ets_SUITE.erl238
-rw-r--r--lib/stdlib/test/filelib_SUITE.erl7
-rw-r--r--lib/stdlib/test/ms_transform_SUITE.erl45
-rw-r--r--lib/stdlib/test/proc_lib_SUITE.erl2
-rw-r--r--lib/stdlib/test/qlc_SUITE.erl2
-rw-r--r--lib/stdlib/test/re_SUITE.erl92
-rw-r--r--lib/stdlib/test/shell_SUITE.erl6
-rw-r--r--lib/stdlib/test/sofs_SUITE.erl6
-rw-r--r--lib/stdlib/test/supervisor_1.erl6
-rw-r--r--lib/stdlib/test/supervisor_2.erl42
-rw-r--r--lib/stdlib/test/supervisor_SUITE.erl182
-rw-r--r--lib/stdlib/test/unicode_SUITE.erl4
22 files changed, 708 insertions, 307 deletions
diff --git a/lib/stdlib/test/Makefile b/lib/stdlib/test/Makefile
index 5502c69fa5..aa6a660c34 100644
--- a/lib/stdlib/test/Makefile
+++ b/lib/stdlib/test/Makefile
@@ -65,6 +65,7 @@ MODULES= \
stdlib_SUITE \
string_SUITE \
supervisor_1 \
+ supervisor_2 \
naughty_child \
shell_SUITE \
supervisor_SUITE \
diff --git a/lib/stdlib/test/beam_lib_SUITE.erl b/lib/stdlib/test/beam_lib_SUITE.erl
index 27520a5c88..5df19ca7f1 100644
--- a/lib/stdlib/test/beam_lib_SUITE.erl
+++ b/lib/stdlib/test/beam_lib_SUITE.erl
@@ -181,7 +181,8 @@ error(Conf) when is_list(Conf) ->
?line verify(not_a_beam_file, beam_lib:info(<<"short">>)),
?line {Binary1, _} = split_binary(Binary, byte_size(Binary)-10),
- ?line verify(chunk_too_big, beam_lib:chunks(Binary1, ["Abst"])),
+ LastChunk = last_chunk(Binary),
+ ?line verify(chunk_too_big, beam_lib:chunks(Binary1, [LastChunk])),
?line Chunks = chunk_info(Binary),
?line {value, {_, AbstractStart, _}} = lists:keysearch("Abst", 1, Chunks),
?line {Binary2, _} = split_binary(Binary, AbstractStart),
@@ -205,6 +206,12 @@ error(Conf) when is_list(Conf) ->
?line file:delete(ACopy),
ok.
+last_chunk(Bin) ->
+ L = beam_lib:info(Bin),
+ {chunks,Chunks} = lists:keyfind(chunks, 1, L),
+ {Last,_,_} = lists:last(Chunks),
+ Last.
+
do_error(BeamFile, ACopy) ->
% evil tests
?line Chunks = chunk_info(BeamFile),
@@ -330,6 +337,7 @@ strip(Conf) when is_list(Conf) ->
?line {Source2D1, BeamFile2D1} = make_beam(PrivDir, simple2, concat),
?line {Source3D1, BeamFile3D1} = make_beam(PrivDir, make_fun, make_fun),
?line {Source4D1, BeamFile4D1} = make_beam(PrivDir, constant, constant),
+ ?line {Source5D1, BeamFile5D1} = make_beam(PrivDir, lines, lines),
?line NoOfTables = length(ets:all()),
?line P0 = pps(),
@@ -360,13 +368,25 @@ strip(Conf) when is_list(Conf) ->
?line {module, make_fun} = code:load_abs(filename:rootname(BeamFile3D1)),
?line {module, constant} = code:load_abs(filename:rootname(BeamFile4D1)),
+ %% check that line number information is still present after stripping
+ ?line {module, lines} = code:load_abs(filename:rootname(BeamFile5D1)),
+ ?line {'EXIT',{badarith,[{lines,t,1,Info}|_]}} =
+ (catch lines:t(atom)),
+ ?line true = code:delete(lines),
+ ?line false = code:purge(lines),
+ ?line {ok, {lines,BeamFile5D1}} = beam_lib:strip(BeamFile5D1),
+ ?line {module, lines} = code:load_abs(filename:rootname(BeamFile5D1)),
+ ?line {'EXIT',{badarith,[{lines,t,1,Info}|_]}} =
+ (catch lines:t(atom)),
+
?line true = (P0 == pps()),
?line NoOfTables = length(ets:all()),
?line delete_files([SourceD1, BeamFileD1,
Source2D1, BeamFile2D1,
Source3D1, BeamFile3D1,
- Source4D1, BeamFile4D1]),
+ Source4D1, BeamFile4D1,
+ Source5D1, BeamFile5D1]),
ok.
@@ -783,6 +803,12 @@ simple_file(File, Module, constant2) ->
"t(A) -> "
" {a,b,[2,3],x,y}. "]),
ok = file:write_file(File, B);
+simple_file(File, Module, lines) ->
+ B = list_to_binary(["-module(", atom_to_list(Module), ").\n"
+ "-export([t/1]).\n"
+ "t(A) ->\n"
+ " A+1.\n"]),
+ ok = file:write_file(File, B);
simple_file(File, Module, F) ->
B = list_to_binary(["-module(", atom_to_list(Module), "). "
"-export([t/0]). "
diff --git a/lib/stdlib/test/dets_SUITE.erl b/lib/stdlib/test/dets_SUITE.erl
index 22a9d4a7ff..6f77cff2b9 100644
--- a/lib/stdlib/test/dets_SUITE.erl
+++ b/lib/stdlib/test/dets_SUITE.erl
@@ -34,6 +34,8 @@
-define(datadir(Conf), ?config(data_dir, Conf)).
-endif.
+-compile(r13). % OTP-9607
+
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
init_per_group/2,end_per_group/2,
not_run/1, newly_started/1, basic_v8/1, basic_v9/1,
@@ -53,7 +55,7 @@
simultaneous_open/1, insert_new/1, repair_continuation/1,
otp_5487/1, otp_6206/1, otp_6359/1, otp_4738/1, otp_7146/1,
otp_8070/1, otp_8856/1, otp_8898/1, otp_8899/1, otp_8903/1,
- otp_8923/1, otp_9282/1]).
+ otp_8923/1, otp_9282/1, otp_9607/1]).
-export([dets_dirty_loop/0]).
@@ -112,7 +114,7 @@ all() ->
many_clients, otp_4906, otp_5402, simultaneous_open,
insert_new, repair_continuation, otp_5487, otp_6206,
otp_6359, otp_4738, otp_7146, otp_8070, otp_8856, otp_8898,
- otp_8899, otp_8903, otp_8923, otp_9282]
+ otp_8899, otp_8903, otp_8923, otp_9282, otp_9607]
end.
groups() ->
@@ -554,7 +556,11 @@ dets_dirty_loop() ->
{From, [write, Name, Value]} ->
Ret = dets:insert(Name, Value),
From ! {self(), Ret},
- dets_dirty_loop()
+ dets_dirty_loop();
+ {From, [close, Name]} ->
+ Ret = dets:close(Name),
+ From ! {self(), Ret},
+ dets_dirty_loop()
end.
@@ -1568,8 +1574,10 @@ repair(Config, V) ->
?line FileSize = dets:info(TabRef, memory),
?line ok = dets:close(TabRef),
crash(Fname, FileSize+20),
- ?line {error, {bad_freelists, Fname}} =
+ %% Used to return bad_freelists, but that changed in OTP-9622
+ ?line {ok, TabRef} =
dets:open_file(TabRef, [{file,Fname},{version,V}]),
+ ?line ok = dets:close(TabRef),
?line file:delete(Fname),
%% File not closed, opening with read and read_write access tried.
@@ -1857,10 +1865,10 @@ fixtable(Config, Version) when is_list(Config) ->
?line {ok, _} = dets:open_file(T, Args),
%% badarg
- ?line {'EXIT', {badarg, [{dets,safe_fixtable,[no_table,true]}|_]}} =
- (catch dets:safe_fixtable(no_table,true)),
- ?line {'EXIT', {badarg, [{dets,safe_fixtable,[T,undefined]}|_]}} =
- (catch dets:safe_fixtable(T,undefined)),
+ ?line check_badarg(catch dets:safe_fixtable(no_table,true),
+ dets, safe_fixtable, [no_table,true]),
+ ?line check_badarg(catch dets:safe_fixtable(T,undefined),
+ dets, safe_fixtable, [T,undefined]),
%% The table is not allowed to grow while the elements are inserted:
@@ -1940,22 +1948,22 @@ match(Config, Version) ->
%% match, badarg
MSpec = [{'_',[],['$_']}],
- ?line {'EXIT', {badarg, [{dets,safe_fixtable,[no_table,true]}|_]}} =
- (catch dets:match(no_table, '_')),
- ?line {'EXIT', {badarg, [{dets,match,[T,'_',not_a_number]}|_]}} =
- (catch dets:match(T, '_', not_a_number)),
+ ?line check_badarg(catch dets:match(no_table, '_'),
+ dets, safe_fixtable, [no_table,true]),
+ ?line check_badarg(catch dets:match(T, '_', not_a_number),
+ dets, match, [T,'_',not_a_number]),
?line {EC1, _} = dets:select(T, MSpec, 1),
- ?line {'EXIT', {badarg, [{dets,match,[EC1]}|_]}} =
- (catch dets:match(EC1)),
+ ?line check_badarg(catch dets:match(EC1),
+ dets, match, [EC1]),
%% match_object, badarg
- ?line {'EXIT', {badarg, [{dets,safe_fixtable,[no_table,true]}|_]}} =
- (catch dets:match_object(no_table, '_')),
- ?line {'EXIT', {badarg, [{dets,match_object,[T,'_',not_a_number]}|_]}} =
- (catch dets:match_object(T, '_', not_a_number)),
+ ?line check_badarg(catch dets:match_object(no_table, '_'),
+ dets, safe_fixtable, [no_table,true]),
+ ?line check_badarg(catch dets:match_object(T, '_', not_a_number),
+ dets, match_object, [T,'_',not_a_number]),
?line {EC2, _} = dets:select(T, MSpec, 1),
- ?line {'EXIT', {badarg, [{dets,match_object,[EC2]}|_]}} =
- (catch dets:match_object(EC2)),
+ ?line check_badarg(catch dets:match_object(EC2),
+ dets, match_object, [EC2]),
dets:safe_fixtable(T, true),
?line {[_, _], C1} = dets:match_object(T, '_', 2),
@@ -2118,17 +2126,17 @@ select(Config, Version) ->
%% badarg
MSpec = [{'_',[],['$_']}],
- ?line {'EXIT', {badarg, [{dets,safe_fixtable,[no_table,true]}|_]}} =
- (catch dets:select(no_table, MSpec)),
- ?line {'EXIT', {badarg, [{dets,select,[T,<<17>>]}|_]}} =
- (catch dets:select(T, <<17>>)),
- ?line {'EXIT', {badarg, [{dets,select,[T,[]]}|_]}} =
- (catch dets:select(T, [])),
- ?line {'EXIT', {badarg, [{dets,select,[T,MSpec,not_a_number]}|_]}} =
- (catch dets:select(T, MSpec, not_a_number)),
+ ?line check_badarg(catch dets:select(no_table, MSpec),
+ dets, safe_fixtable, [no_table,true]),
+ ?line check_badarg(catch dets:select(T, <<17>>),
+ dets, select, [T,<<17>>]),
+ ?line check_badarg(catch dets:select(T, []),
+ dets, select, [T,[]]),
+ ?line check_badarg(catch dets:select(T, MSpec, not_a_number),
+ dets, select, [T,MSpec,not_a_number]),
?line {EC, _} = dets:match(T, '_', 1),
- ?line {'EXIT', {badarg, [{dets,select,[EC]}|_]}} =
- (catch dets:select(EC)),
+ ?line check_badarg(catch dets:select(EC),
+ dets, select, [EC]),
AllSpec = [{'_',[],['$_']}],
@@ -2210,8 +2218,8 @@ update_counter(Config) when is_list(Config) ->
?line file:delete(Fname),
P0 = pps(),
- ?line {'EXIT', {badarg, [{dets,update_counter,[no_table,1,1]}|_]}} =
- (catch dets:update_counter(no_table, 1, 1)),
+ ?line check_badarg(catch dets:update_counter(no_table, 1, 1),
+ dets, update_counter, [no_table,1,1]),
Args = [{file,Fname},{keypos,2}],
?line {ok, _} = dets:open_file(T, [{type,set} | Args]),
@@ -2254,66 +2262,66 @@ badarg(Config) when is_list(Config) ->
%% badargs are tested in match, select and fixtable too.
%% open
- ?line {'EXIT', {badarg, [{dets,open_file,[{a,tuple},[]]}|_]}} =
- (catch dets:open_file({a,tuple},[])),
- ?line {'EXIT', {badarg, [{dets,open_file,[{a,tuple}]}|_]}} =
- (catch dets:open_file({a,tuple})),
- ?line {'EXIT', {badarg, [{dets,open_file,[file,[foo]]}|_]}} =
- (catch dets:open_file(file,[foo])),
- ?line {'EXIT', {badarg,[{dets,open_file,[{hej,san},[{type,set}|3]]}|_]}} =
- (catch dets:open_file({hej,san},[{type,set}|3])),
+ ?line check_badarg(catch dets:open_file({a,tuple},[]),
+ dets, open_file, [{a,tuple},[]]),
+ ?line check_badarg(catch dets:open_file({a,tuple}),
+ dets, open_file,[{a,tuple}]),
+ ?line check_badarg(catch dets:open_file(file,[foo]),
+ dets, open_file, [file,[foo]]),
+ ?line check_badarg(catch dets:open_file({hej,san},[{type,set}|3]),
+ dets, open_file, [{hej,san},[{type,set}|3]]),
%% insert
- ?line {'EXIT', {badarg, [{dets,insert,[no_table,{1,2}]}|_]}} =
- (catch dets:insert(no_table, {1,2})),
- ?line {'EXIT', {badarg, [{dets,insert,[no_table,[{1,2}]]}|_]}} =
- (catch dets:insert(no_table, [{1,2}])),
- ?line {'EXIT', {badarg, [{dets,insert,[T,{1,2}]}|_]}} =
- (catch dets:insert(T, {1,2})),
- ?line {'EXIT', {badarg, [{dets,insert,[T,[{1,2}]]}|_]}} =
- (catch dets:insert(T, [{1,2}])),
- ?line {'EXIT', {badarg, [{dets,insert,[T,[{1,2,3}|3]]}|_]}} =
- (catch dets:insert(T, [{1,2,3} | 3])),
+ ?line check_badarg(catch dets:insert(no_table, {1,2}),
+ dets, insert, [no_table,{1,2}]),
+ ?line check_badarg(catch dets:insert(no_table, [{1,2}]),
+ dets, insert, [no_table,[{1,2}]]),
+ ?line check_badarg(catch dets:insert(T, {1,2}),
+ dets, insert, [T,{1,2}]),
+ ?line check_badarg(catch dets:insert(T, [{1,2}]),
+ dets, insert, [T,[{1,2}]]),
+ ?line check_badarg(catch dets:insert(T, [{1,2,3} | 3]),
+ dets, insert, [T,[{1,2,3}|3]]),
%% lookup{_keys}
- ?line {'EXIT', {badarg, [{dets,lookup_keys,[badarg,[]]}|_]}} =
- (catch dets:lookup_keys(T, [])),
- ?line {'EXIT', {badarg, [{dets,lookup,[no_table,1]}|_]}} =
- (catch dets:lookup(no_table, 1)),
- ?line {'EXIT', {badarg, [{dets,lookup_keys,[T,[1|2]]}|_]}} =
- (catch dets:lookup_keys(T, [1 | 2])),
+ ?line check_badarg(catch dets:lookup_keys(T, []),
+ dets, lookup_keys, [badarg,[]]),
+ ?line check_badarg(catch dets:lookup(no_table, 1),
+ dets, lookup, [no_table,1]),
+ ?line check_badarg(catch dets:lookup_keys(T, [1 | 2]),
+ dets, lookup_keys, [T,[1|2]]),
%% member
- ?line {'EXIT', {badarg, [{dets,member,[no_table,1]}|_]}} =
- (catch dets:member(no_table, 1)),
+ ?line check_badarg(catch dets:member(no_table, 1),
+ dets, member, [no_table,1]),
%% sync
- ?line {'EXIT', {badarg, [{dets,sync,[no_table]}|_]}} =
- (catch dets:sync(no_table)),
+ ?line check_badarg(catch dets:sync(no_table),
+ dets, sync, [no_table]),
%% delete{_keys}
- ?line {'EXIT', {badarg, [{dets,delete,[no_table,1]}|_]}} =
- (catch dets:delete(no_table, 1)),
+ ?line check_badarg(catch dets:delete(no_table, 1),
+ dets, delete, [no_table,1]),
%% delete_object
- ?line {'EXIT', {badarg, [{dets,delete_object,[no_table,{1,2,3}]}|_]}} =
- (catch dets:delete_object(no_table, {1,2,3})),
- ?line {'EXIT', {badarg, [{dets,delete_object,[T,{1,2}]}|_]}} =
- (catch dets:delete_object(T, {1,2})),
- ?line {'EXIT', {badarg, [{dets,delete_object,[no_table,[{1,2,3}]]}|_]}} =
- (catch dets:delete_object(no_table, [{1,2,3}])),
- ?line {'EXIT', {badarg, [{dets,delete_object,[T,[{1,2}]]}|_]}} =
- (catch dets:delete_object(T, [{1,2}])),
- ?line {'EXIT', {badarg, [{dets,delete_object,[T,[{1,2,3}|3]]}|_]}} =
- (catch dets:delete_object(T, [{1,2,3} | 3])),
+ ?line check_badarg(catch dets:delete_object(no_table, {1,2,3}),
+ dets, delete_object, [no_table,{1,2,3}]),
+ ?line check_badarg(catch dets:delete_object(T, {1,2}),
+ dets, delete_object, [T,{1,2}]),
+ ?line check_badarg(catch dets:delete_object(no_table, [{1,2,3}]),
+ dets, delete_object, [no_table,[{1,2,3}]]),
+ ?line check_badarg(catch dets:delete_object(T, [{1,2}]),
+ dets, delete_object, [T,[{1,2}]]),
+ ?line check_badarg(catch dets:delete_object(T, [{1,2,3} | 3]),
+ dets, delete_object, [T,[{1,2,3}|3]]),
%% first,next,slot
- ?line {'EXIT', {badarg, [{dets,first,[no_table]}|_]}} =
- (catch dets:first(no_table)),
- ?line {'EXIT', {badarg, [{dets,next,[no_table,1]}|_]}} =
- (catch dets:next(no_table, 1)),
- ?line {'EXIT', {badarg, [{dets,slot,[no_table,0]}|_]}} =
- (catch dets:slot(no_table, 0)),
+ ?line check_badarg(catch dets:first(no_table),
+ dets, first, [no_table]),
+ ?line check_badarg(catch dets:next(no_table, 1),
+ dets, next, [no_table,1]),
+ ?line check_badarg(catch dets:slot(no_table, 0),
+ dets, slot, [no_table,0]),
%% info
?line undefined = dets:info(no_table),
@@ -2321,27 +2329,27 @@ badarg(Config) when is_list(Config) ->
?line undefined = dets:info(T, foo),
%% match_delete
- ?line {'EXIT', {badarg, [{dets,safe_fixtable,[no_table,true]}|_]}} =
- (catch dets:match_delete(no_table, '_')),
+ ?line check_badarg(catch dets:match_delete(no_table, '_'),
+ dets, safe_fixtable, [no_table,true]),
%% delete_all_objects
- ?line {'EXIT', {badarg, [{dets,delete_all_objects,[no_table]}|_]}} =
- (catch dets:delete_all_objects(no_table)),
+ ?line check_badarg(catch dets:delete_all_objects(no_table),
+ dets, delete_all_objects, [no_table]),
%% select_delete
MSpec = [{'_',[],['$_']}],
- ?line {'EXIT', {badarg, [{dets,safe_fixtable,[no_table,true]}|_]}} =
- (catch dets:select_delete(no_table, MSpec)),
- ?line {'EXIT', {badarg, [{dets,select_delete,[T, <<17>>]}|_]}} =
- (catch dets:select_delete(T, <<17>>)),
+ ?line check_badarg(catch dets:select_delete(no_table, MSpec),
+ dets, safe_fixtable, [no_table,true]),
+ ?line check_badarg(catch dets:select_delete(T, <<17>>),
+ dets, select_delete, [T, <<17>>]),
%% traverse, fold
- ?line {'EXIT', {badarg, [{dets,safe_fixtable,[no_table,true]}|_]}} =
- (catch dets:traverse(no_table, fun(_) -> continue end)),
- ?line {'EXIT', {badarg, [{dets,safe_fixtable,[no_table,true]}|_]}} =
- (catch dets:foldl(fun(_, A) -> A end, [], no_table)),
- ?line {'EXIT', {badarg, [{dets,safe_fixtable,[no_table,true]}|_]}} =
- (catch dets:foldr(fun(_, A) -> A end, [], no_table)),
+ ?line check_badarg(catch dets:traverse(no_table, fun(_) -> continue end),
+ dets, safe_fixtable, [no_table,true]),
+ ?line check_badarg(catch dets:foldl(fun(_, A) -> A end, [], no_table),
+ dets, safe_fixtable, [no_table,true]),
+ ?line check_badarg(catch dets:foldr(fun(_, A) -> A end, [], no_table),
+ dets, safe_fixtable, [no_table,true]),
%% close
?line ok = dets:close(T),
@@ -2349,15 +2357,16 @@ badarg(Config) when is_list(Config) ->
?line {error, not_owner} = dets:close(T),
%% init_table
- ?line {'EXIT', {badarg,[{dets,init_table,[no_table,_,[]]}|_]}} =
- (catch dets:init_table(no_table, fun(X) -> X end)),
- ?line {'EXIT', {badarg,[{dets,init_table,[no_table,_,[]]}|_]}} =
- (catch dets:init_table(no_table, fun(X) -> X end, [])),
+ IF = fun(X) -> X end,
+ ?line check_badarg(catch dets:init_table(no_table, IF),
+ dets, init_table, [no_table,IF,[]]),
+ ?line check_badarg(catch dets:init_table(no_table, IF, []),
+ dets, init_table, [no_table,IF,[]]),
%% from_ets
Ets = ets:new(ets,[]),
- ?line {'EXIT', {badarg,[{dets,from_ets,[no_table,_]}|_]}} =
- (catch dets:from_ets(no_table, Ets)),
+ ?line check_badarg(catch dets:from_ets(no_table, Ets),
+ dets, from_ets, [no_table,Ets]),
ets:delete(Ets),
?line {ok, T} = dets:open_file(T, Args),
@@ -3879,10 +3888,91 @@ some_calls(Tab, Config) ->
?line ok = dets:close(T),
file:delete(File).
+otp_9607(doc) ->
+ ["OTP-9607. Test downgrading the slightly changed format."];
+otp_9607(suite) ->
+ [];
+otp_9607(Config) when is_list(Config) ->
+ %% Note: the bug is about almost full tables. The fix of that
+ %% problem is *not* tested here.
+ Version = r13b,
+ case ?t:is_release_available(atom_to_list(Version)) of
+ true ->
+ T = otp_9607,
+ File = filename(T, Config),
+ Key = a,
+ Value = 1,
+ Args = [{file,File}],
+ ?line {ok, T} = dets:open_file(T, Args),
+ ?line ok = dets:insert(T, {Key, Value}),
+ ?line ok = dets:close(T),
+
+ ?line Call = fun(P, A) ->
+ P ! {self(), A},
+ receive
+ {P, Ans} ->
+ Ans
+ after 5000 ->
+ exit(other_process_dead)
+ end
+ end,
+ %% Create a file on the modified format, read the file
+ %% with an emulator that doesn't know about the modified
+ %% format.
+ ?line {ok, Node} = start_node_rel(Version, Version, slave),
+ ?line Pid = rpc:call(Node, erlang, spawn,
+ [?MODULE, dets_dirty_loop, []]),
+ ?line {error,{needs_repair, File}} =
+ Call(Pid, [open, T, Args++[{repair,false}]]),
+ io:format("Expect repair:~n"),
+ ?line {ok, T} = Call(Pid, [open, T, Args]),
+ ?line [{Key,Value}] = Call(Pid, [read, T, Key]),
+ ?line ok = Call(Pid, [close, T]),
+ file:delete(File),
+
+ %% Create a file on the unmodified format. Modify the file
+ %% using an emulator that must not turn the file into the
+ %% modified format. Read the file and make sure it is not
+ %% repaired.
+ ?line {ok, T} = Call(Pid, [open, T, Args]),
+ ?line ok = Call(Pid, [write, T, {Key,Value}]),
+ ?line [{Key,Value}] = Call(Pid, [read, T, Key]),
+ ?line ok = Call(Pid, [close, T]),
+
+ Key2 = b,
+ Value2 = 2,
+
+ ?line {ok, T} = dets:open_file(T, Args),
+ ?line [{Key,Value}] = dets:lookup(T, Key),
+ ?line ok = dets:insert(T, {Key2,Value2}),
+ ?line ok = dets:close(T),
+
+ ?line {ok, T} = Call(Pid, [open, T, Args++[{repair,false}]]),
+ ?line [{Key2,Value2}] = Call(Pid, [read, T, Key2]),
+ ?line ok = Call(Pid, [close, T]),
+
+ ?t:stop_node(Node),
+ file:delete(File),
+ ok;
+ false ->
+ {skipped, "No support for old node"}
+ end.
+
+
+
%%
%% Parts common to several test cases
%%
+start_node_rel(Name, Rel, How) ->
+ Release = [{release, atom_to_list(Rel)}],
+ ?line Pa = filename:dirname(code:which(?MODULE)),
+ ?line test_server:start_node(Name, How,
+ [{args,
+ " -kernel net_setuptime 100 "
+ " -pa " ++ Pa},
+ {erl, Release}]).
+
crash(File, Where) ->
crash(File, Where, 10).
@@ -4268,6 +4358,11 @@ bad_object({error,{{bad_object,_}, FileName}}, FileName) ->
bad_object({error,{{{bad_object,_,_},_,_,_}, FileName}}, FileName) ->
ok. % Debug.
+check_badarg({'EXIT', {badarg, [{M,F,Args,_} | _]}}, M, F, Args) ->
+ true;
+check_badarg({'EXIT', {badarg, [{M,F,A,_} | _]}}, M, F, Args) ->
+ true = test_server:is_native(M) andalso length(Args) =:= A.
+
check_pps(P0) ->
case pps() of
P0 ->
diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl
index 57f3f4eddb..f79414db49 100644
--- a/lib/stdlib/test/epp_SUITE.erl
+++ b/lib/stdlib/test/epp_SUITE.erl
@@ -20,7 +20,7 @@
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
init_per_group/2,end_per_group/2]).
--export([rec_1/1, predef_mac/1,
+-export([rec_1/1, include_local/1, predef_mac/1,
upcase_mac_1/1, upcase_mac_2/1,
variable_1/1, otp_4870/1, otp_4871/1, otp_5362/1,
pmod/1, not_circular/1, skip_header/1, otp_6277/1, otp_7702/1,
@@ -63,7 +63,7 @@ end_per_testcase(_, Config) ->
suite() -> [{ct_hooks,[ts_install_cth]}].
all() ->
- [rec_1, {group, upcase_mac}, predef_mac,
+ [rec_1, {group, upcase_mac}, include_local, predef_mac,
{group, variable}, otp_4870, otp_4871, otp_5362, pmod,
not_circular, skip_header, otp_6277, otp_7702, otp_8130,
overload_mac, otp_8388, otp_8470, otp_8503, otp_8562,
@@ -97,6 +97,22 @@ rec_1(Config) when is_list(Config) ->
?line check_errors(List),
ok.
+include_local(doc) ->
+ [];
+include_local(suite) ->
+ [];
+include_local(Config) when is_list(Config) ->
+ ?line DataDir = ?config(data_dir, Config),
+ ?line File = filename:join(DataDir, "include_local.erl"),
+ %% include_local.erl includes include/foo.hrl which
+ %% includes bar.hrl (also in include/) without requiring
+ %% any additional include path, and overriding any file
+ %% of the same name that the path points to
+ ?line {ok, List} = epp:parse_file(File, [DataDir], []),
+ ?line {value, {attribute,_,a,{true,true}}} =
+ lists:keysearch(a,3,List),
+ ok.
+
%%% Here is a little reimplementation of epp:parse_file, which times out
%%% after 4 seconds if the epp server doesn't respond. If we use the
%%% regular epp:parse_file, the test case will time out, and then epp
@@ -234,16 +250,23 @@ otp_4871(Config) when is_list(Config) ->
%% so there are some sanity checks before killing.
?line {ok,Epp} = epp:open(File, []),
timer:sleep(1),
- ?line {current_function,{epp,_,_}} = process_info(Epp, current_function),
+ ?line true = current_module(Epp, epp),
?line {monitored_by,[Io]} = process_info(Epp, monitored_by),
- ?line {current_function,{file_io_server,_,_}} =
- process_info(Io, current_function),
+ ?line true = current_module(Io, file_io_server),
?line exit(Io, emulate_crash),
timer:sleep(1),
?line {error,{_Line,epp,cannot_parse}} = otp_4871_parse_file(Epp),
?line epp:close(Epp),
ok.
+current_module(Pid, Mod) ->
+ case process_info(Pid, current_function) of
+ {current_function, undefined} ->
+ true = test_server:is_native(Mod);
+ {current_function, {Mod, _, _}} ->
+ true
+ end.
+
otp_4871_parse_file(Epp) ->
case epp:parse_erl_form(Epp) of
{ok,_} -> otp_4871_parse_file(Epp);
diff --git a/lib/stdlib/test/epp_SUITE_data/bar.hrl b/lib/stdlib/test/epp_SUITE_data/bar.hrl
new file mode 100644
index 0000000000..01c527d549
--- /dev/null
+++ b/lib/stdlib/test/epp_SUITE_data/bar.hrl
@@ -0,0 +1,4 @@
+%% should not be included from include/foo.hrl even though the
+%% include path points here - include/bar.hrl overrides it
+
+-define(BAR_HRL, false).
diff --git a/lib/stdlib/test/epp_SUITE_data/include/bar.hrl b/lib/stdlib/test/epp_SUITE_data/include/bar.hrl
new file mode 100644
index 0000000000..038d3c900e
--- /dev/null
+++ b/lib/stdlib/test/epp_SUITE_data/include/bar.hrl
@@ -0,0 +1,3 @@
+%% included from foo.hrl in same directory
+
+-define(BAR_HRL, true).
diff --git a/lib/stdlib/test/epp_SUITE_data/include/foo.hrl b/lib/stdlib/test/epp_SUITE_data/include/foo.hrl
new file mode 100644
index 0000000000..a6dfa3d18a
--- /dev/null
+++ b/lib/stdlib/test/epp_SUITE_data/include/foo.hrl
@@ -0,0 +1,4 @@
+%% includes bar.hrl in same directory
+
+-define(FOO_HRL, true).
+-include("bar.hrl").
diff --git a/lib/stdlib/test/epp_SUITE_data/include_local.erl b/lib/stdlib/test/epp_SUITE_data/include_local.erl
new file mode 100644
index 0000000000..c8e155a064
--- /dev/null
+++ b/lib/stdlib/test/epp_SUITE_data/include_local.erl
@@ -0,0 +1,6 @@
+
+-module(include_local).
+
+-include("include/foo.hrl").
+
+-a({?FOO_HRL, ?BAR_HRL}).
diff --git a/lib/stdlib/test/erl_eval_SUITE.erl b/lib/stdlib/test/erl_eval_SUITE.erl
index 784c7cb86e..369d8b224e 100644
--- a/lib/stdlib/test/erl_eval_SUITE.erl
+++ b/lib/stdlib/test/erl_eval_SUITE.erl
@@ -1036,6 +1036,12 @@ funs(Config) when is_list(Config) ->
lists:usort([run_many_args(SAs) || SAs <- many_args(MaxArgs)]),
?line {'EXIT',{{argument_limit,_},_}} =
(catch run_many_args(many_args1(MaxArgs+1))),
+
+ ?line check(fun() -> M = lists, F = fun M:reverse/1,
+ [1,2] = F([2,1]), ok end,
+ "begin M = lists, F = fun M:reverse/1,"
+ " [1,2] = F([2,1]), ok end.",
+ ok),
ok.
run_many_args({S, As}) ->
diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl
index 280c95b1aa..64853ca078 100644
--- a/lib/stdlib/test/erl_pp_SUITE.erl
+++ b/lib/stdlib/test/erl_pp_SUITE.erl
@@ -116,7 +116,6 @@ func(Config) when is_list(Config) ->
{func_3,
<<"t() -> fun t/0.">>},
{func_4,
- %% Has already been expanded away in sys_pre_expand.
<<"t() -> fun modul:foo/3.">>},
{func_5, % 'when' is moved down one line
<<"tkjlksjflksdjflsdjlk()
@@ -127,7 +126,9 @@ func(Config) when is_list(Config) ->
<<"t() ->
(fun() ->
true
- end)().">>}
+ end)().">>},
+ {func_7,
+ <<"t(M, F, A) -> fun M:F/A.">>}
],
?line compile(Config, Ts),
ok.
diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl
index 57df963ae2..0e8849b5b3 100644
--- a/lib/stdlib/test/ets_SUITE.erl
+++ b/lib/stdlib/test/ets_SUITE.erl
@@ -74,7 +74,7 @@
-export([bad_table/1, types/1]).
-export([otp_9423/1]).
--export([init_per_testcase/2, end_per_testcase/2]).
+-export([init_per_testcase/2]).
%% Convenience for manual testing
-export([random_test/0]).
@@ -176,6 +176,7 @@ groups() ->
meta_newdel_unnamed, meta_newdel_named]}].
init_per_suite(Config) ->
+ erts_debug:set_internal_state(available_internal_state, true),
Config.
end_per_suite(_Config) ->
@@ -304,7 +305,6 @@ t_match_spec_run(Config) when is_list(Config) ->
end,
repeat_for_permutations(F, N_MS)
end,
-
test_terms(Fun, skip_refc_check),
?line verify_etsmem(EtsMem).
@@ -324,7 +324,7 @@ t_match_spec_run_test(List, MS, Result) ->
%% Check that tracing agree
Self = self(),
- {Tracee, MonRef} = spawn_monitor(fun() -> ms_tracee(Self, List) end),
+ {Tracee, MonRef} = my_spawn_monitor(fun() -> ms_tracee(Self, List) end),
receive {Tracee, ready} -> ok end,
MST = lists:map(fun(Clause) -> ms_clause_ets_to_trace(Clause) end, MS),
@@ -585,7 +585,6 @@ select_fail_do(Opts) ->
memory(doc) -> ["Whitebox test of ets:info(X,memory)"];
memory(suite) -> [];
memory(Config) when is_list(Config) ->
- ?line erts_debug:set_internal_state(available_internal_state, true),
?line ok = chk_normal_tab_struct_size(),
repeat_for_opts(memory_do,[compressed]),
?line catch erts_debug:set_internal_state(available_internal_state, false).
@@ -795,21 +794,26 @@ t_ets_dets(Config, Opts) ->
?line true = ets:from_dets(ETab,DTab),
?line 3000 = ets:info(ETab,size),
?line ets:delete(ETab),
- ?line {'EXIT',{badarg,[{ets,to_dets,[ETab,DTab]}|_]}} =
- (catch ets:to_dets(ETab,DTab)),
- ?line {'EXIT',{badarg,[{ets,from_dets,[ETab,DTab]}|_]}} =
- (catch ets:from_dets(ETab,DTab)),
+ ?line check_badarg(catch ets:to_dets(ETab,DTab),
+ ets, to_dets, [ETab,DTab]),
+ ?line check_badarg(catch ets:from_dets(ETab,DTab),
+ ets, from_dets, [ETab,DTab]),
?line ETab2 = ets_new(x,Opts),
?line filltabint(ETab2,3000),
?line dets:close(DTab),
- ?line {'EXIT',{badarg,[{ets,to_dets,[ETab2,DTab]}|_]}} =
- (catch ets:to_dets(ETab2,DTab)),
- ?line {'EXIT',{badarg,[{ets,from_dets,[ETab2,DTab]}|_]}} =
- (catch ets:from_dets(ETab2,DTab)),
+ ?line check_badarg(catch ets:to_dets(ETab2,DTab),
+ ets, to_dets, [ETab2,DTab]),
+ ?line check_badarg(catch ets:from_dets(ETab2,DTab),
+ ets, from_dets, [ETab2,DTab]),
?line ets:delete(ETab2),
?line (catch file:delete(Fname)),
ok.
+check_badarg({'EXIT', {badarg, [{M,F,Args,_} | _]}}, M, F, Args) ->
+ true;
+check_badarg({'EXIT', {badarg, [{M,F,A,_} | _]}}, M, F, Args) ->
+ true = test_server:is_native(M) andalso length(Args) =:= A.
+
t_delete_all_objects(doc) ->
["Test ets:delete_all_objects/1"];
t_delete_all_objects(suite) ->
@@ -1942,7 +1946,7 @@ evil_update_counter(Config) when is_list(Config) ->
evil_update_counter_do(Opts) ->
?line EtsMem = etsmem(),
?line process_flag(trap_exit, true),
- ?line Pids = [spawn_link(fun() -> evil_counter(I,Opts) end) || I <- lists:seq(1, 40)],
+ ?line Pids = [my_spawn_link(fun() -> evil_counter(I,Opts) end) || I <- lists:seq(1, 40)],
?line wait_for_all(gb_sets:from_list(Pids)),
?line verify_etsmem(EtsMem),
ok.
@@ -2148,24 +2152,24 @@ heir_do(Opts) ->
Combos),
%% No heir
- {Founder1,MrefF1} = spawn_monitor(fun()->heir_founder(Master,foo_data,Opts)end),
+ {Founder1,MrefF1} = my_spawn_monitor(fun()->heir_founder(Master,foo_data,Opts)end),
Founder1 ! {go, none},
?line {"No heir",Founder1} = receive_any(),
?line {'DOWN', MrefF1, process, Founder1, normal} = receive_any(),
?line undefined = ets:info(foo),
%% An already dead heir
- {Heir2,MrefH2} = spawn_monitor(fun()->die end),
+ {Heir2,MrefH2} = my_spawn_monitor(fun()->die end),
?line {'DOWN', MrefH2, process, Heir2, normal} = receive_any(),
- {Founder2,MrefF2} = spawn_monitor(fun()->heir_founder(Master,foo_data,Opts)end),
+ {Founder2,MrefF2} = my_spawn_monitor(fun()->heir_founder(Master,foo_data,Opts)end),
Founder2 ! {go, Heir2},
?line {"No heir",Founder2} = receive_any(),
?line {'DOWN', MrefF2, process, Founder2, normal} = receive_any(),
?line undefined = ets:info(foo),
%% When heir dies before founder
- {Founder3,MrefF3} = spawn_monitor(fun()->heir_founder(Master,"The dying heir",Opts)end),
- {Heir3,MrefH3} = spawn_monitor(fun()->heir_heir(Founder3)end),
+ {Founder3,MrefF3} = my_spawn_monitor(fun()->heir_founder(Master,"The dying heir",Opts)end),
+ {Heir3,MrefH3} = my_spawn_monitor(fun()->heir_heir(Founder3)end),
Founder3 ! {go, Heir3},
?line {'DOWN', MrefH3, process, Heir3, normal} = receive_any(),
Founder3 ! die_please,
@@ -2173,14 +2177,12 @@ heir_do(Opts) ->
?line undefined = ets:info(foo),
%% When heir dies and pid reused before founder dies
- erts_debug:set_internal_state(available_internal_state,true),
NextPidIx = erts_debug:get_internal_state(next_pid),
- {Founder4,MrefF4} = spawn_monitor(fun()->heir_founder(Master,"The dying heir",Opts)end),
- {Heir4,MrefH4} = spawn_monitor(fun()->heir_heir(Founder4)end),
+ {Founder4,MrefF4} = my_spawn_monitor(fun()->heir_founder(Master,"The dying heir",Opts)end),
+ {Heir4,MrefH4} = my_spawn_monitor(fun()->heir_heir(Founder4)end),
Founder4 ! {go, Heir4},
?line {'DOWN', MrefH4, process, Heir4, normal} = receive_any(),
erts_debug:set_internal_state(next_pid, NextPidIx),
- erts_debug:set_internal_state(available_internal_state,false),
{Heir4,MrefH4_B} = spawn_monitor_with_pid(Heir4,
fun()-> ?line die_please = receive_any() end),
Founder4 ! die_please,
@@ -2256,9 +2258,9 @@ heir_heir(Founder, Mode) ->
heir_1(HeirData,Mode,Opts) ->
io:format("test with heir_data = ~p\n", [HeirData]),
Master = self(),
- ?line Founder = spawn_link(fun() -> heir_founder(Master,HeirData,Opts) end),
+ ?line Founder = my_spawn_link(fun() -> heir_founder(Master,HeirData,Opts) end),
io:format("founder spawned = ~p\n", [Founder]),
- ?line {Heir,Mref} = spawn_monitor(fun() -> heir_heir(Founder,Mode) end),
+ ?line {Heir,Mref} = my_spawn_monitor(fun() -> heir_heir(Founder,Mode) end),
io:format("heir spawned = ~p\n", [{Heir,Mref}]),
?line Founder ! {go, Heir},
?line {'DOWN', Mref, process, Heir, normal} = receive_any().
@@ -2275,7 +2277,7 @@ give_away_do(Opts) ->
Parent = self(),
%% Give and then give back
- ?line {Receiver,Mref} = spawn_monitor(fun()-> give_away_receiver(T,Parent) end),
+ ?line {Receiver,Mref} = my_spawn_monitor(fun()-> give_away_receiver(T,Parent) end),
?line give_me = receive_any(),
?line true = ets:give_away(T,Receiver,here_you_are),
?line {'EXIT',{badarg,_}} = (catch ets:lookup(T,key)),
@@ -2286,7 +2288,7 @@ give_away_do(Opts) ->
%% Give and then let receiver keep it
?line true = ets:insert(T,{key,1}),
- ?line {Receiver3,Mref3} = spawn_monitor(fun()-> give_away_receiver(T,Parent) end),
+ ?line {Receiver3,Mref3} = my_spawn_monitor(fun()-> give_away_receiver(T,Parent) end),
?line give_me = receive_any(),
?line true = ets:give_away(T,Receiver3,here_you_are),
?line {'EXIT',{badarg,_}} = (catch ets:lookup(T,key)),
@@ -2298,7 +2300,7 @@ give_away_do(Opts) ->
?line T2 = ets_new(foo,[private | Opts]),
?line true = ets:insert(T2,{key,1}),
?line ets:setopts(T2,{heir,self(),"Som en gummiboll..."}),
- ?line {Receiver2,Mref2} = spawn_monitor(fun()-> give_away_receiver(T2,Parent) end),
+ ?line {Receiver2,Mref2} = my_spawn_monitor(fun()-> give_away_receiver(T2,Parent) end),
?line give_me = receive_any(),
?line true = ets:give_away(T2,Receiver2,here_you_are),
?line {'EXIT',{badarg,_}} = (catch ets:lookup(T2,key)),
@@ -2313,12 +2315,12 @@ give_away_do(Opts) ->
?line {'EXIT',{badarg,_}} = (catch ets:give_away(T2,"not a pid","To wrong type")),
?line true = ets:delete(T2),
- ?line {ReceiverNeg,MrefNeg} = spawn_monitor(fun()-> give_away_receiver(T2,Parent) end),
+ ?line {ReceiverNeg,MrefNeg} = my_spawn_monitor(fun()-> give_away_receiver(T2,Parent) end),
?line give_me = receive_any(),
?line {'EXIT',{badarg,_}} = (catch ets:give_away(T2,ReceiverNeg,"A deleted table")),
?line T3 = ets_new(foo,[public | Opts]),
- spawn_link(fun()-> {'EXIT',{badarg,_}} = (catch ets:give_away(T3,ReceiverNeg,"From non owner")),
+ my_spawn_link(fun()-> {'EXIT',{badarg,_}} = (catch ets:give_away(T3,ReceiverNeg,"From non owner")),
Parent ! done
end),
?line done = receive_any(),
@@ -2354,7 +2356,7 @@ setopts_do(Opts) ->
Self = self(),
?line T = ets_new(foo,[named_table, private | Opts]),
?line none = ets:info(T,heir),
- Heir = spawn_link(fun()->heir_heir(Self) end),
+ Heir = my_spawn_link(fun()->heir_heir(Self) end),
?line ets:setopts(T,{heir,Heir,"Data"}),
?line Heir = ets:info(T,heir),
?line ets:setopts(T,{heir,self(),"Data"}),
@@ -2405,14 +2407,14 @@ bad_table(Config) when is_list(Config) ->
bad_table_do(Opts, DummyFile) ->
Parent = self(),
- {Pid,Mref} = spawn_opt(fun()-> ets_new(priv,[private,named_table | Opts]),
- Priv = ets_new(priv,[private | Opts]),
- ets_new(prot,[protected,named_table | Opts]),
- Prot = ets_new(prot,[protected | Opts]),
- Parent ! {self(),Priv,Prot},
- die_please = receive_any()
- end,
- [link, monitor]),
+ {Pid,Mref} = my_spawn_opt(fun()-> ets_new(priv,[private,named_table | Opts]),
+ Priv = ets_new(priv,[private | Opts]),
+ ets_new(prot,[protected,named_table | Opts]),
+ Prot = ets_new(prot,[protected | Opts]),
+ Parent ! {self(),Priv,Prot},
+ die_please = receive_any()
+ end,
+ [link, monitor]),
{Pid,Priv,Prot} = receive_any(),
MatchSpec = {{key,'_'}, [], ['$$']},
Fun = fun(X,_) -> X end,
@@ -2652,7 +2654,7 @@ maybe_sort(L) when is_list(L) ->
%maybe_sort({'EXIT',{Reason, [{Module, Function, _}|_]}}) ->
% {'EXIT',{Reason, [{Module, Function, '_'}]}};
maybe_sort({'EXIT',{Reason, List}}) when is_list(List) ->
- {'EXIT',{Reason, lists:map(fun({Module, Function, _}) ->
+ {'EXIT',{Reason, lists:map(fun({Module, Function, _, _}) ->
{Module, Function, '_'}
end,
List)}};
@@ -3258,7 +3260,7 @@ delete_large_named_table_1(Name, Flags, Data, Fix) ->
?line lists:foreach(fun({K,_}) -> ets:delete(Tab, K) end, Data)
end,
Parent = self(),
- Pid = spawn_link(fun() ->
+ Pid = my_spawn_link(fun() ->
receive
{trace,Parent,call,_} ->
ets_new(Name, [named_table])
@@ -3620,7 +3622,7 @@ cycle(Tab, L) ->
ets:insert(Tab,list_to_tuple(L)),
cycle(Tab, tl(L)++[hd(L)]).
-dynamic_go() -> spawn_link(fun dynamic_init/0).
+dynamic_go() -> my_spawn_link(fun dynamic_init/0).
dynamic_init() -> [dyn_lookup(?MODULE) || _ <- lists:seq(1, 10)].
@@ -3847,7 +3849,7 @@ safe_fixtable_do(Opts) ->
Self = self(),
?line {{_,_,_},[{Self,1}]} = ets:info(Tab,safe_fixed),
%% Test that an unjustified 'unfix' is a no-op.
- {Pid,MRef} = spawn_monitor(fun() -> true = ets:safe_fixtable(Tab,false) end),
+ {Pid,MRef} = my_spawn_monitor(fun() -> true = ets:safe_fixtable(Tab,false) end),
{'DOWN', MRef, process, Pid, normal} = receive M -> M end,
?line true = ets:info(Tab,fixed),
?line {{_,_,_},[{Self,1}]} = ets:info(Tab,safe_fixed),
@@ -4251,7 +4253,7 @@ do_heavy_concurrent(Opts) ->
?line ok = fill_tab2(Tab, 0, Size),
?line Procs = lists:map(
fun (N) ->
- spawn_link(
+ my_spawn_link(
fun () ->
do_heavy_concurrent_proc(Tab, Size, N)
end)
@@ -4855,12 +4857,7 @@ otp_7665_act(Tab,Min,Max,DelNr) ->
%% Whitebox testing of meta name table hashing.
meta_wb(Config) when is_list(Config) ->
?line EtsMem = etsmem(),
- ?line erts_debug:set_internal_state(available_internal_state, true),
- try
- repeat_for_opts(meta_wb_do)
- after
- erts_debug:set_internal_state(available_internal_state, false)
- end,
+ repeat_for_opts(meta_wb_do),
?line verify_etsmem(EtsMem).
@@ -4929,12 +4926,15 @@ colliding_names(Name) ->
grow_shrink(Config) when is_list(Config) ->
?line EtsMem = etsmem(),
- grow_shrink_0(lists:seq(3071, 5000), EtsMem).
+ ?line grow_shrink_0(lists:seq(3071, 5000), EtsMem),
+ ?line verify_etsmem(EtsMem).
grow_shrink_0([N|Ns], EtsMem) ->
?line grow_shrink_1(N, [set]),
?line grow_shrink_1(N, [ordered_set]),
- ?line verify_etsmem(EtsMem),
+ %% Verifying ets-memory here takes too long time, since
+ %% lock-free allocators were introduced...
+ %% ?line verify_etsmem(EtsMem),
grow_shrink_0(Ns, EtsMem);
grow_shrink_0([], _) -> ok.
@@ -4981,13 +4981,13 @@ grow_pseudo_deleted_do(Type) ->
?line Left = ets:info(T,size),
?line Mult = get_kept_objects(T),
filltabstr(T,Mult),
- spawn_opt(fun()-> ?line true = ets:info(T,fixed),
- Self ! start,
- io:format("Starting to filltabstr... ~p\n",[now()]),
- filltabstr(T,Mult,Mult+10000),
- io:format("Done with filltabstr. ~p\n",[now()]),
- Self ! done
- end, [link, {scheduler,2}]),
+ my_spawn_opt(fun()-> ?line true = ets:info(T,fixed),
+ Self ! start,
+ io:format("Starting to filltabstr... ~p\n",[now()]),
+ filltabstr(T,Mult,Mult+10000),
+ io:format("Done with filltabstr. ~p\n",[now()]),
+ Self ! done
+ end, [link, {scheduler,2}]),
?line start = receive_any(),
io:format("Unfixing table...~p nitems=~p\n",[now(),ets:info(T,size)]),
?line true = ets:safe_fixtable(T,false),
@@ -5021,13 +5021,13 @@ shrink_pseudo_deleted_do(Type) ->
[true]}]),
?line Half = ets:info(T,size),
?line Half = get_kept_objects(T),
- spawn_opt(fun()-> ?line true = ets:info(T,fixed),
- Self ! start,
- io:format("Starting to delete... ~p\n",[now()]),
- del_one_by_one_set(T,1,Half+1),
- io:format("Done with delete. ~p\n",[now()]),
- Self ! done
- end, [link, {scheduler,2}]),
+ my_spawn_opt(fun()-> ?line true = ets:info(T,fixed),
+ Self ! start,
+ io:format("Starting to delete... ~p\n",[now()]),
+ del_one_by_one_set(T,1,Half+1),
+ io:format("Done with delete. ~p\n",[now()]),
+ Self ! done
+ end, [link, {scheduler,2}]),
?line start = receive_any(),
io:format("Unfixing table...~p nitems=~p\n",[now(),ets:info(T,size)]),
?line true = ets:safe_fixtable(T,false),
@@ -5184,24 +5184,24 @@ smp_unfix_fix_do() ->
?line Deleted = get_kept_objects(T),
{Child, Mref} =
- spawn_opt(fun()-> ?line true = ets:info(T,fixed),
- Parent ! start,
- io:format("Child waiting for table to be unfixed... now=~p mem=~p\n",
- [now(),ets:info(T,memory)]),
- repeat_while(fun()-> ets:info(T,fixed) end),
- io:format("Table unfixed. Child Fixating! now=~p mem=~p\n",
- [now(),ets:info(T,memory)]),
- ?line true = ets:safe_fixtable(T,true),
- repeat_while(fun(Key) when Key =< NumOfObjs ->
- ets:delete(T,Key), {true,Key+1};
- (Key) -> {false,Key}
- end,
- Deleted),
- ?line 0 = ets:info(T,size),
- ?line true = get_kept_objects(T) >= Left,
- ?line done = receive_any()
- end,
- [link, monitor, {scheduler,2}]),
+ my_spawn_opt(fun()-> ?line true = ets:info(T,fixed),
+ Parent ! start,
+ io:format("Child waiting for table to be unfixed... now=~p mem=~p\n",
+ [now(),ets:info(T,memory)]),
+ repeat_while(fun()-> ets:info(T,fixed) end),
+ io:format("Table unfixed. Child Fixating! now=~p mem=~p\n",
+ [now(),ets:info(T,memory)]),
+ ?line true = ets:safe_fixtable(T,true),
+ repeat_while(fun(Key) when Key =< NumOfObjs ->
+ ets:delete(T,Key), {true,Key+1};
+ (Key) -> {false,Key}
+ end,
+ Deleted),
+ ?line 0 = ets:info(T,size),
+ ?line true = get_kept_objects(T) >= Left,
+ ?line done = receive_any()
+ end,
+ [link, monitor, {scheduler,2}]),
?line start = receive_any(),
?line true = ets:info(T,fixed),
@@ -5232,11 +5232,11 @@ otp_8166_do(WC) ->
Deleted = NumOfObjs div 2,
filltabint(T,NumOfObjs),
{ReaderPid, ReaderMref} =
- spawn_opt(fun()-> otp_8166_reader(T,NumOfObjs) end,
- [link, monitor, {scheduler,2}]),
+ my_spawn_opt(fun()-> otp_8166_reader(T,NumOfObjs) end,
+ [link, monitor, {scheduler,2}]),
{ZombieCrPid, ZombieCrMref} =
- spawn_opt(fun()-> otp_8166_zombie_creator(T,Deleted) end,
- [link, monitor, {scheduler,3}]),
+ my_spawn_opt(fun()-> otp_8166_zombie_creator(T,Deleted) end,
+ [link, monitor, {scheduler,3}]),
repeat(fun() -> ZombieCrPid ! {loop, self()},
zombies_created = receive_any(),
@@ -5496,7 +5496,7 @@ run_workers_do(InitF,ExecF,FiniF,Laps, Exclude) ->
io:format("smp starting ~p workers\n",[NumOfProcs]),
Seeds = [{ProcN,random:uniform(9999)} || ProcN <- lists:seq(1,NumOfProcs)],
Parent = self(),
- Pids = [spawn_link(fun()-> worker(Seed,InitF,ExecF,FiniF,Laps,Parent,NumOfProcs) end)
+ Pids = [my_spawn_link(fun()-> worker(Seed,InitF,ExecF,FiniF,Laps,Parent,NumOfProcs) end)
|| Seed <- Seeds],
case Laps of
infinite -> Pids;
@@ -5545,31 +5545,30 @@ my_tab_to_list(_Ts,'$end_of_table', Acc) -> lists:reverse(Acc);
my_tab_to_list(Ts,Key, Acc) ->
my_tab_to_list(Ts,ets:next(Ts,Key),[ets:lookup(Ts, Key)| Acc]).
-wait_for_all_schedulers_online_to_execute() ->
- PMs = lists:map(fun (Sched) ->
- spawn_opt(fun () -> ok end,
- [monitor, {scheduler, Sched}])
- end,
- lists:seq(1,erlang:system_info(schedulers_online))),
- lists:foreach(fun ({P, M}) ->
- receive
- {'DOWN', M, process, P, _} -> ok
- end
- end,
- PMs),
- ok.
+
+wait_for_memory_deallocations() ->
+ try
+ erts_debug:set_internal_state(wait, deallocations)
+ catch
+ error:undef ->
+ erts_debug:set_internal_state(available_internal_state, true),
+ wait_for_memory_deallocations()
+ end.
+
etsmem() ->
- %% Wait until it is guaranteed that all already scheduled
- %% deallocations of DbTable structures have completed.
- wait_for_all_schedulers_online_to_execute(),
+ wait_for_memory_deallocations(),
AllTabs = lists:map(fun(T) -> {T,ets:info(T,name),ets:info(T,size),
ets:info(T,memory),ets:info(T,type)}
end, ets:all()),
+
+ EtsAllocInfo = erlang:system_info({allocator,ets_alloc}),
+ ErlangMemoryEts = try erlang:memory(ets) catch error:notsup -> notsup end,
+
Mem =
- {try erlang:memory(ets) catch error:notsup -> notsup end,
- case erlang:system_info({allocator,ets_alloc}) of
+ {ErlangMemoryEts,
+ case EtsAllocInfo of
false -> undefined;
MemInfo ->
CS = lists:foldl(
@@ -5646,6 +5645,7 @@ spawn_logger(Procs) ->
true -> exit(Proc, kill);
_ -> ok
end,
+ erlang:display(process_info(Proc)),
receive
{'DOWN', Mon, _, _, _} ->
ok
@@ -5681,7 +5681,7 @@ wait_for_test_procs(Kill) ->
ets_test_spawn_logger ! {sync_test_procs, Kill, self()},
receive test_procs_synced -> ok end.
-log_test_proc(Proc) ->
+log_test_proc(Proc) when is_pid(Proc) ->
ets_test_spawn_logger ! {new_test_proc, Proc},
Proc.
@@ -5693,9 +5693,17 @@ my_spawn_link(Fun) -> log_test_proc(spawn_link(Fun)).
my_spawn_link(M,F,A) -> log_test_proc(spawn_link(M,F,A)).
%%my_spawn_link(N,M,F,A) -> log_test_proc(spawn_link(N,M,F,A)).
-my_spawn_opt(Fun,Opts) -> log_test_proc(spawn_opt(Fun,Opts)).
-%%my_spawn_opt(M,F,A,Opts) -> log_test_proc(spawn_opt(M,F,A,Opts)).
-%%my_spawn_opt(N,M,F,A,Opts) -> log_test_proc(spawn_opt(N,M,F,A,Opts)).
+my_spawn_opt(Fun,Opts) ->
+ case spawn_opt(Fun,Opts) of
+ Pid when is_pid(Pid) -> log_test_proc(Pid);
+ {Pid, _} = Res when is_pid(Pid) -> log_test_proc(Pid), Res
+ end.
+
+my_spawn_monitor(Fun) ->
+ Res = spawn_monitor(Fun),
+ {Pid, _} = Res,
+ log_test_proc(Pid),
+ Res.
repeat(_Fun, 0) ->
ok;
@@ -5758,11 +5766,11 @@ spawn_monitor_with_pid(Pid, Fun, N, M) when N > M*10 ->
spawn_monitor_with_pid(Pid, Fun, N, M*10);
spawn_monitor_with_pid(Pid, Fun, N, M) ->
?line false = is_process_alive(Pid),
- case spawn(fun()-> case self() of
- Pid -> Fun();
- _ -> die
- end
- end) of
+ case my_spawn(fun()-> case self() of
+ Pid -> Fun();
+ _ -> die
+ end
+ end) of
Pid ->
{Pid, erlang:monitor(process, Pid)};
Other ->
diff --git a/lib/stdlib/test/filelib_SUITE.erl b/lib/stdlib/test/filelib_SUITE.erl
index 3010f5e760..1de639a166 100644
--- a/lib/stdlib/test/filelib_SUITE.erl
+++ b/lib/stdlib/test/filelib_SUITE.erl
@@ -97,11 +97,12 @@ wildcard_errors(Config) when is_list(Config) ->
wcc(Wc, Error) ->
{'EXIT',{{badpattern,Error},
- [{filelib,compile_wildcard,1}|_]}} = (catch filelib:compile_wildcard(Wc)),
+ [{filelib,compile_wildcard,1,_}|_]}} =
+ (catch filelib:compile_wildcard(Wc)),
{'EXIT',{{badpattern,Error},
- [{filelib,wildcard,1}|_]}} = (catch filelib:wildcard(Wc)),
+ [{filelib,wildcard,1,_}|_]}} = (catch filelib:wildcard(Wc)),
{'EXIT',{{badpattern,Error},
- [{filelib,wildcard,2}|_]}} = (catch filelib:wildcard(Wc, ".")).
+ [{filelib,wildcard,2,_}|_]}} = (catch filelib:wildcard(Wc, ".")).
do_wildcard_1(Dir, Wcf0) ->
do_wildcard_2(Dir, Wcf0),
diff --git a/lib/stdlib/test/ms_transform_SUITE.erl b/lib/stdlib/test/ms_transform_SUITE.erl
index 4e5df12798..c9688354b1 100644
--- a/lib/stdlib/test/ms_transform_SUITE.erl
+++ b/lib/stdlib/test/ms_transform_SUITE.erl
@@ -39,6 +39,7 @@
-export([float_1_function/1]).
-export([action_function/1]).
-export([warnings/1]).
+-export([no_warnings/1]).
-export([init_per_testcase/2, end_per_testcase/2]).
init_per_testcase(_Func, Config) ->
@@ -55,7 +56,7 @@ all() ->
[from_shell, basic_ets, basic_dbg, records,
record_index, multipass, bitsyntax, record_defaults,
andalso_orelse, float_1_function, action_function,
- warnings, top_match, old_guards, autoimported,
+ warnings, no_warnings, top_match, old_guards, autoimported,
semicolon].
groups() ->
@@ -155,6 +156,34 @@ warnings(Config) when is_list(Config) ->
compile_ww(Prog7),
ok.
+no_warnings(suite) ->
+ [];
+no_warnings(doc) ->
+ ["Check that variables bound in other function clauses don't generate "
+ "warning"];
+no_warnings(Config) when is_list(Config) ->
+ ?line setup(Config),
+ Prog = <<"tmp(X) when X > 100 ->\n",
+ " Y=X,\n"
+ " Y;\n"
+ "tmp(X) ->\n"
+ " ets:fun2ms(fun(Y) ->\n"
+ " {X, 3*Y}\n"
+ " end)">>,
+ ?line [] = compile_no_ww(Prog),
+
+ Prog2 = <<"tmp(X) when X > 100 ->\n",
+ " Y=X,\n"
+ " Y;\n"
+ "tmp(X) when X < 200 ->\n"
+ " ok;\n"
+ "tmp(X) ->\n"
+ " ets:fun2ms(fun(Y) ->\n"
+ " {X, 3*Y}\n"
+ " end)">>,
+ ?line [] = compile_no_ww(Prog2),
+ ok.
+
andalso_orelse(suite) ->
[];
andalso_orelse(doc) ->
@@ -842,6 +871,20 @@ compile_ww(Records,Expr) ->
nowarn_unused_record]),
Wlist.
+compile_no_ww(Expr) ->
+ Prog = <<
+ "-module(tmp).\n",
+ "-include_lib(\"stdlib/include/ms_transform.hrl\").\n",
+ "-export([tmp/1]).\n\n",
+ Expr/binary,".\n">>,
+ FN=temp_name(),
+ file:write_file(FN,Prog),
+ {ok,Forms} = epp:parse_file(FN,"",""),
+ {ok,tmp,_Bin,Wlist} = compile:forms(Forms,[return_warnings,
+ nowarn_unused_vars,
+ nowarn_unused_record]),
+ Wlist.
+
do_eval(String) ->
{done,{ok,T,_},[]} = erl_scan:tokens(
[],
diff --git a/lib/stdlib/test/proc_lib_SUITE.erl b/lib/stdlib/test/proc_lib_SUITE.erl
index 1565aa9bba..c95089117c 100644
--- a/lib/stdlib/test/proc_lib_SUITE.erl
+++ b/lib/stdlib/test/proc_lib_SUITE.erl
@@ -328,7 +328,7 @@ otp_6345(doc) ->
["'monitor' spawn_opt option"];
otp_6345(Config) when is_list(Config) ->
Opts = [link,monitor],
- {'EXIT', {badarg,[{proc_lib,check_for_monitor,_}|_Stack]}} =
+ {'EXIT', {badarg,[{proc_lib,check_for_monitor,_,_}|_Stack]}} =
(catch proc_lib:start(?MODULE, otp_6345_init, [self()],
1000, Opts)),
ok.
diff --git a/lib/stdlib/test/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl
index 98eeaee118..8a9d8f7883 100644
--- a/lib/stdlib/test/qlc_SUITE.erl
+++ b/lib/stdlib/test/qlc_SUITE.erl
@@ -6632,7 +6632,7 @@ otp_7232(Config) when is_list(Config) ->
{call,_,
{remote,_,{atom,_,qlc},{atom,_,sort}},
[{cons,_,
- {'fun',_,{function,math,sqrt,_}},
+ {'fun',_,{function,{atom,_,math},{atom,_,sqrt},_}},
{cons,_,
{string,_,\"<0.4.1>\"}, % could use list_to_pid..
{cons,_,{string,_,\"#Ref<\"++_},{nil,_}}}},
diff --git a/lib/stdlib/test/re_SUITE.erl b/lib/stdlib/test/re_SUITE.erl
index c4817c0d38..3b2e637c84 100644
--- a/lib/stdlib/test/re_SUITE.erl
+++ b/lib/stdlib/test/re_SUITE.erl
@@ -454,115 +454,115 @@ error_handling(Config) when is_list(Config) ->
% The malformed precomiled RE is detected after
% the trap to re:grun from grun, in the grun function clause
% that handles precompiled expressions
- ?line {'EXIT',{badarg,[{re,run,["apa",{1,2,3,4},[global]]},
- {?MODULE, error_handling,1} | _]}} =
+ ?line {'EXIT',{badarg,[{re,run,["apa",{1,2,3,4},[global]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:run("apa",{1,2,3,4},[global])),
% An invalid capture list will also cause a badarg late,
% but with a non pre compiled RE, the exception should be thrown by the
% grun function clause that handles RE's compiled implicitly by
% the run/3 BIF before trapping.
- ?line {'EXIT',{badarg,[{re,run,["apa","p",[{capture,[1,{a}]},global]]},
- {?MODULE, error_handling,1} | _]}} =
+ ?line {'EXIT',{badarg,[{re,run,["apa","p",[{capture,[1,{a}]},global]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:run("apa","p",[{capture,[1,{a}]},global])),
% And so the case of a precompiled expression together with
% a compile-option (binary and list subject):
?line {ok,RE} = re:compile("(p)"),
?line {match,[[{1,1},{1,1}]]} = re:run(<<"apa">>,RE,[global]),
?line {match,[[{1,1},{1,1}]]} = re:run("apa",RE,[global]),
- {'EXIT',{badarg,[{re,run,
- [<<"apa">>,
- {re_pattern,1,0,_},
- [global,unicode]]},
- {?MODULE, error_handling,1} | _]}} =
+ ?line {'EXIT',{badarg,[{re,run,
+ [<<"apa">>,
+ {re_pattern,1,0,_},
+ [global,unicode]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:run(<<"apa">>,RE,[global,unicode])),
- {'EXIT',{badarg,[{re,run,
- ["apa",
- {re_pattern,1,0,_},
- [global,unicode]]},
- {?MODULE, error_handling,1} | _]}} =
+ ?line {'EXIT',{badarg,[{re,run,
+ ["apa",
+ {re_pattern,1,0,_},
+ [global,unicode]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:run("apa",RE,[global,unicode])),
?line {'EXIT',{badarg,_}} = (catch re:run("apa","(p",[])),
?line {'EXIT',{badarg,_}} = (catch re:run("apa","(p",[global])),
% The replace errors:
- ?line {'EXIT',{badarg,[{re,replace,["apa",{1,2,3,4},"X",[]]},
- {?MODULE, error_handling,1} | _]}} =
+ ?line {'EXIT',{badarg,[{re,replace,["apa",{1,2,3,4},"X",[]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:replace("apa",{1,2,3,4},"X",[])),
- ?line {'EXIT',{badarg,[{re,replace,["apa",{1,2,3,4},"X",[global]]},
- {?MODULE, error_handling,1} | _]}} =
+ ?line {'EXIT',{badarg,[{re,replace,["apa",{1,2,3,4},"X",[global]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:replace("apa",{1,2,3,4},"X",[global])),
?line {'EXIT',{badarg,[{re,replace,
["apa",
{re_pattern,1,0,_},
"X",
- [unicode]]},
- {?MODULE, error_handling,1} | _]}} =
+ [unicode]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:replace("apa",RE,"X",[unicode])),
?line <<"aXa">> = iolist_to_binary(re:replace("apa","p","X",[])),
?line {'EXIT',{badarg,[{re,replace,
- ["apa","p","X",[{capture,all,binary}]]},
- {?MODULE, error_handling,1} | _]}} =
+ ["apa","p","X",[{capture,all,binary}]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch iolist_to_binary(re:replace("apa","p","X",
[{capture,all,binary}]))),
?line {'EXIT',{badarg,[{re,replace,
- ["apa","p","X",[{capture,all}]]},
- {?MODULE, error_handling,1} | _]}} =
+ ["apa","p","X",[{capture,all}]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch iolist_to_binary(re:replace("apa","p","X",
[{capture,all}]))),
?line {'EXIT',{badarg,[{re,replace,
- ["apa","p","X",[{return,banana}]]},
- {?MODULE, error_handling,1} | _]}} =
+ ["apa","p","X",[{return,banana}]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch iolist_to_binary(re:replace("apa","p","X",
[{return,banana}]))),
?line {'EXIT',{badarg,_}} = (catch re:replace("apa","(p","X",[])),
% Badarg, not compile error.
?line {'EXIT',{badarg,[{re,replace,
- ["apa","(p","X",[{return,banana}]]},
- {?MODULE, error_handling,1} | _]}} =
+ ["apa","(p","X",[{return,banana}]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch iolist_to_binary(re:replace("apa","(p","X",
[{return,banana}]))),
% And the split errors:
?line [<<"a">>,<<"a">>] = (catch re:split("apa","p",[])),
?line [<<"a">>,<<"p">>,<<"a">>] = (catch re:split("apa",RE,[])),
- ?line {'EXIT',{badarg,[{re,split,["apa","p",[global]]},
- {?MODULE, error_handling,1} | _]}} =
+ ?line {'EXIT',{badarg,[{re,split,["apa","p",[global]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:split("apa","p",[global])),
- ?line {'EXIT',{badarg,[{re,split,["apa","p",[{capture,all}]]},
- {?MODULE, error_handling,1} | _]}} =
+ ?line {'EXIT',{badarg,[{re,split,["apa","p",[{capture,all}]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:split("apa","p",[{capture,all}])),
- ?line {'EXIT',{badarg,[{re,split,["apa","p",[{capture,all,binary}]]},
- {?MODULE, error_handling,1} | _]}} =
+ ?line {'EXIT',{badarg,[{re,split,["apa","p",[{capture,all,binary}]],_},
+ {?MODULE, error_handling,1,_} | _]}} =
(catch re:split("apa","p",[{capture,all,binary}])),
- ?line {'EXIT',{badarg,[{re,split,["apa",{1,2,3,4},[]]},
- {?MODULE, error_handling,1} | _]}} =
+ ?line {'EXIT',{badarg,[{re,split,["apa",{1,2,3,4},[]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:split("apa",{1,2,3,4})),
- ?line {'EXIT',{badarg,[{re,split,["apa",{1,2,3,4},[]]},
- {?MODULE, error_handling,1} | _]}} =
+ ?line {'EXIT',{badarg,[{re,split,["apa",{1,2,3,4},[]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:split("apa",{1,2,3,4},[])),
?line {'EXIT',{badarg,[{re,split,
["apa",
RE,
- [unicode]]},
- {?MODULE, error_handling,1} | _]}} =
+ [unicode]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:split("apa",RE,[unicode])),
?line {'EXIT',{badarg,[{re,split,
["apa",
RE,
- [{return,banana}]]},
- {?MODULE, error_handling,1} | _]}} =
+ [{return,banana}]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:split("apa",RE,[{return,banana}])),
?line {'EXIT',{badarg,[{re,split,
["apa",
RE,
- [banana]]},
- {?MODULE, error_handling,1} | _]}} =
+ [banana]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:split("apa",RE,[banana])),
?line {'EXIT',{badarg,_}} = (catch re:split("apa","(p")),
%Exception on bad argument, not compilation error
?line {'EXIT',{badarg,[{re,split,
["apa",
"(p",
- [banana]]},
- {?MODULE, error_handling,1} | _]}} =
+ [banana]],_},
+ {?MODULE,error_handling,1,_} | _]}} =
(catch re:split("apa","(p",[banana])),
?t:timetrap_cancel(Dog),
ok.
diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl
index 8273377ba1..b6019b86f0 100644
--- a/lib/stdlib/test/shell_SUITE.erl
+++ b/lib/stdlib/test/shell_SUITE.erl
@@ -2388,12 +2388,12 @@ otp_6554(Config) when is_list(Config) ->
comm_err(<<"V = lists:seq(1, 20), case V of a -> ok end.">>),
?line "exception error: no function clause matching" =
comm_err(<<"fun(P) when is_pid(P) -> true end(a).">>),
- ?line "exception error: {function_clause,[{erl_eval,do_apply,[unproper|list]}"++_ =
+ ?line "exception error: {function_clause," =
comm_err(<<"erlang:error(function_clause, [unproper | list]).">>),
?line "exception error: function_clause" =
comm_err(<<"erlang:error(function_clause, 4).">>),
%% Cheating:
- ?line "exception error: no function clause matching erl_eval:do_apply(4)" =
+ ?line "exception error: no function clause matching erl_eval:do_apply(4)" ++ _ =
comm_err(<<"erlang:error(function_clause, [4]).">>),
?line "exception error: no function clause matching" ++ _ =
comm_err(<<"fun(a, b, c, d) -> foo end"
@@ -2406,7 +2406,7 @@ otp_6554(Config) when is_list(Config) ->
comm_err(<<"fun(P, q) when is_pid(P) -> true end(a, b).">>),
?line "exception error: no function clause matching lists:reverse(" ++ _ =
comm_err(<<"F=fun() -> hello end, lists:reverse(F).">>),
- ?line "exception error: no function clause matching lists:reverse(34)" =
+ ?line "exception error: no function clause matching lists:reverse(34) (lists.erl, line " ++ _ =
comm_err(<<"lists:reverse(34).">>),
?line "exception error: no true branch found when evaluating an if expression" =
comm_err(<<"if length([a,b]) > 17 -> a end.">>),
diff --git a/lib/stdlib/test/sofs_SUITE.erl b/lib/stdlib/test/sofs_SUITE.erl
index d6f88a655e..73b282149a 100644
--- a/lib/stdlib/test/sofs_SUITE.erl
+++ b/lib/stdlib/test/sofs_SUITE.erl
@@ -1879,11 +1879,11 @@ digraph(Conf) when is_list(Conf) ->
?line {'EXIT', {badarg, _}} =
(catch family_to_digraph(set([a]))),
- ?line {'EXIT', {badarg, [{sofs,family_to_digraph,[_,_]}|_]}} =
+ ?line {'EXIT', {badarg, [{sofs,family_to_digraph,[_,_],_}|_]}} =
(catch family_to_digraph(set([a]), [foo])),
- ?line {'EXIT', {badarg, [{sofs,family_to_digraph,[_,_]}|_]}} =
+ ?line {'EXIT', {badarg, [{sofs,family_to_digraph,[_,_],_}|_]}} =
(catch family_to_digraph(F, [foo])),
- ?line {'EXIT', {cyclic, [{sofs,family_to_digraph,[_,_]}|_]}} =
+ ?line {'EXIT', {cyclic, [{sofs,family_to_digraph,[_,_],_}|_]}} =
(catch family_to_digraph(family([{a,[a]}]),[acyclic])),
?line G1 = family_to_digraph(E),
diff --git a/lib/stdlib/test/supervisor_1.erl b/lib/stdlib/test/supervisor_1.erl
index 3198be0fed..f819594c46 100644
--- a/lib/stdlib/test/supervisor_1.erl
+++ b/lib/stdlib/test/supervisor_1.erl
@@ -62,6 +62,12 @@ handle_info(die, State) ->
handle_info(stop, State) ->
{stop, normal, State};
+handle_info({'EXIT',_,shutdown}, State) ->
+ {stop, shutdown, State};
+
+handle_info({'EXIT',_,{shutdown,Term}}, State) ->
+ {stop, {shutdown,Term}, State};
+
handle_info({sleep, Time}, State) ->
io:format("FOO: ~p~n", [Time]),
timer:sleep(Time),
diff --git a/lib/stdlib/test/supervisor_2.erl b/lib/stdlib/test/supervisor_2.erl
new file mode 100644
index 0000000000..67aacf5a9c
--- /dev/null
+++ b/lib/stdlib/test/supervisor_2.erl
@@ -0,0 +1,42 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 1996-2010. All Rights Reserved.
+%%
+%% The contents of this file are subject to the Erlang Public License,
+%% Version 1.1, (the "License"); you may not use this file except in
+%% compliance with the License. You should have received a copy of the
+%% Erlang Public License along with this software. If not, it can be
+%% retrieved online at http://www.erlang.org/.
+%%
+%% Software distributed under the License is distributed on an "AS IS"
+%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
+%% the License for the specific language governing rights and limitations
+%% under the License.
+%%
+%% %CopyrightEnd%
+%%
+%% Description: Simulates the behaviour that a child process may have.
+%% Is used by the supervisor_SUITE test suite.
+-module(supervisor_2).
+
+-export([start_child/1, init/1]).
+
+-export([handle_call/3, handle_info/2, terminate/2]).
+
+start_child(Time) when is_integer(Time), Time > 0 ->
+ gen_server:start_link(?MODULE, Time, []).
+
+init(Time) ->
+ process_flag(trap_exit, true),
+ {ok, Time}.
+
+handle_call(Req, _From, State) ->
+ {reply, Req, State}.
+
+handle_info(_, State) ->
+ {noreply, State}.
+
+terminate(_Reason, Time) ->
+ timer:sleep(Time),
+ ok.
diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl
index b48450c151..da6996cc9f 100644
--- a/lib/stdlib/test/supervisor_SUITE.erl
+++ b/lib/stdlib/test/supervisor_SUITE.erl
@@ -41,6 +41,8 @@
%% Tests concept permanent, transient and temporary
-export([ permanent_normal/1, transient_normal/1,
temporary_normal/1,
+ permanent_shutdown/1, transient_shutdown/1,
+ temporary_shutdown/1,
permanent_abnormal/1, transient_abnormal/1,
temporary_abnormal/1, temporary_bystander/1]).
@@ -50,7 +52,7 @@
one_for_all_escalation/1,
simple_one_for_one/1, simple_one_for_one_escalation/1,
rest_for_one/1, rest_for_one_escalation/1,
- simple_one_for_one_extra/1]).
+ simple_one_for_one_extra/1, simple_one_for_one_shutdown/1]).
%% Misc tests
-export([child_unlink/1, tree/1, count_children_memory/1,
@@ -71,6 +73,7 @@ all() ->
{group, restart_simple_one_for_one},
{group, restart_rest_for_one},
{group, normal_termination},
+ {group, shutdown_termination},
{group, abnormal_termination}, child_unlink, tree,
count_children_memory, do_not_save_start_parameters_for_temporary_children,
do_not_save_child_specs_for_temporary_children,
@@ -86,6 +89,8 @@ groups() ->
sup_stop_brutal_kill]},
{normal_termination, [],
[permanent_normal, transient_normal, temporary_normal]},
+ {shutdown_termination, [],
+ [permanent_shutdown, transient_shutdown, temporary_shutdown]},
{abnormal_termination, [],
[permanent_abnormal, transient_abnormal,
temporary_abnormal]},
@@ -94,8 +99,8 @@ groups() ->
{restart_one_for_all, [],
[one_for_all, one_for_all_escalation]},
{restart_simple_one_for_one, [],
- [simple_one_for_one, simple_one_for_one_extra,
- simple_one_for_one_escalation]},
+ [simple_one_for_one, simple_one_for_one_shutdown,
+ simple_one_for_one_extra, simple_one_for_one_escalation]},
{restart_rest_for_one, [],
[rest_for_one, rest_for_one_escalation]}].
@@ -115,7 +120,9 @@ end_per_group(_GroupName, Config) ->
init_per_testcase(count_children_memory, Config) ->
try erlang:memory() of
- _ -> Config
+ _ ->
+ erts_debug:set_internal_state(available_internal_state, true),
+ Config
catch error:notsup ->
{skip, "+Meamin used during test; erlang:memory/1 not available"}
end;
@@ -123,6 +130,9 @@ init_per_testcase(_Case, Config) ->
erlang:display(_Case),
Config.
+end_per_testcase(count_children_memory, _Config) ->
+ catch erts_debug:set_internal_state(available_internal_state, false),
+ ok;
end_per_testcase(_Case, _Config) ->
ok.
@@ -204,8 +214,8 @@ sup_start_fail(Config) when is_list(Config) ->
%%-------------------------------------------------------------------------
sup_stop_infinity(doc) ->
- ["See sup_stop/1 when Shutdown = infinity, this walue is only allowed "
- "for children of type supervisor"];
+ ["See sup_stop/1 when Shutdown = infinity, this walue is allowed "
+ "for children of type supervisor _AND_ worker"];
sup_stop_infinity(suite) -> [];
sup_stop_infinity(Config) when is_list(Config) ->
@@ -216,12 +226,13 @@ sup_stop_infinity(Config) when is_list(Config) ->
Child2 = {child2, {supervisor_1, start_child, []}, permanent,
infinity, worker, []},
{ok, CPid1} = supervisor:start_child(sup_test, Child1),
+ {ok, CPid2} = supervisor:start_child(sup_test, Child2),
link(CPid1),
- {error, {invalid_shutdown,infinity}} =
- supervisor:start_child(sup_test, Child2),
+ link(CPid2),
terminate(Pid, shutdown),
- check_exit_reason(CPid1, shutdown).
+ check_exit_reason(CPid1, shutdown),
+ check_exit_reason(CPid2, shutdown).
%%-------------------------------------------------------------------------
@@ -453,9 +464,8 @@ child_specs(Config) when is_list(Config) ->
B2 = {child, {m,f,[a]}, prmanent, 1000, worker, []},
B3 = {child, {m,f,[a]}, permanent, -10, worker, []},
B4 = {child, {m,f,[a]}, permanent, 10, wrker, []},
- B5 = {child, {m,f,[a]}, permanent, infinity, worker, []},
- B6 = {child, {m,f,[a]}, permanent, 1000, worker, dy},
- B7 = {child, {m,f,[a]}, permanent, 1000, worker, [1,2,3]},
+ B5 = {child, {m,f,[a]}, permanent, 1000, worker, dy},
+ B6 = {child, {m,f,[a]}, permanent, 1000, worker, [1,2,3]},
%% Correct child specs!
%% <Modules> (last parameter in a child spec) can be [] as we do
@@ -464,6 +474,7 @@ child_specs(Config) when is_list(Config) ->
C2 = {child, {m,f,[a]}, permanent, 1000, supervisor, []},
C3 = {child, {m,f,[a]}, temporary, 1000, worker, dynamic},
C4 = {child, {m,f,[a]}, transient, 1000, worker, [m]},
+ C5 = {child, {m,f,[a]}, permanent, infinity, worker, [m]},
{error, {invalid_mfa,mfa}} = supervisor:start_child(sup_test, B1),
{error, {invalid_restart_type, prmanent}} =
@@ -472,9 +483,8 @@ child_specs(Config) when is_list(Config) ->
= supervisor:start_child(sup_test, B3),
{error, {invalid_child_type,wrker}}
= supervisor:start_child(sup_test, B4),
- {error, _} = supervisor:start_child(sup_test, B5),
{error, {invalid_modules,dy}}
- = supervisor:start_child(sup_test, B6),
+ = supervisor:start_child(sup_test, B5),
{error, {invalid_mfa,mfa}} = supervisor:check_childspecs([B1]),
{error, {invalid_restart_type,prmanent}} =
@@ -482,15 +492,15 @@ child_specs(Config) when is_list(Config) ->
{error, {invalid_shutdown,-10}} = supervisor:check_childspecs([B3]),
{error, {invalid_child_type,wrker}}
= supervisor:check_childspecs([B4]),
- {error, _} = supervisor:check_childspecs([B5]),
- {error, {invalid_modules,dy}} = supervisor:check_childspecs([B6]),
+ {error, {invalid_modules,dy}} = supervisor:check_childspecs([B5]),
{error, {invalid_module, 1}} =
- supervisor:check_childspecs([B7]),
+ supervisor:check_childspecs([B6]),
ok = supervisor:check_childspecs([C1]),
ok = supervisor:check_childspecs([C2]),
ok = supervisor:check_childspecs([C3]),
ok = supervisor:check_childspecs([C4]),
+ ok = supervisor:check_childspecs([C5]),
ok.
%%-------------------------------------------------------------------------
@@ -549,6 +559,87 @@ temporary_normal(Config) when is_list(Config) ->
[0,0,0,0] = get_child_counts(sup_test).
%%-------------------------------------------------------------------------
+permanent_shutdown(doc) ->
+ ["A permanent child should always be restarted"];
+permanent_shutdown(suite) -> [];
+permanent_shutdown(Config) when is_list(Config) ->
+ {ok, SupPid} = start_link({ok, {{one_for_one, 2, 3600}, []}}),
+ Child1 = {child1, {supervisor_1, start_child, []}, permanent, 1000,
+ worker, []},
+
+ {ok, CPid1} = supervisor:start_child(sup_test, Child1),
+
+ terminate(SupPid, CPid1, child1, shutdown),
+
+ [{child1, CPid2 ,worker,[]}] = supervisor:which_children(sup_test),
+ case is_pid(CPid2) of
+ true ->
+ ok;
+ false ->
+ test_server:fail({permanent_child_not_restarted, Child1})
+ end,
+ [1,1,0,1] = get_child_counts(sup_test),
+
+ terminate(SupPid, CPid2, child1, {shutdown, some_info}),
+
+ [{child1, CPid3 ,worker,[]}] = supervisor:which_children(sup_test),
+ case is_pid(CPid3) of
+ true ->
+ ok;
+ false ->
+ test_server:fail({permanent_child_not_restarted, Child1})
+ end,
+
+ [1,1,0,1] = get_child_counts(sup_test).
+
+%%-------------------------------------------------------------------------
+transient_shutdown(doc) ->
+ ["A transient child should not be restarted if it exits with "
+ "reason shutdown or {shutdown,Term}"];
+transient_shutdown(suite) -> [];
+transient_shutdown(Config) when is_list(Config) ->
+ {ok, SupPid} = start_link({ok, {{one_for_one, 2, 3600}, []}}),
+ Child1 = {child1, {supervisor_1, start_child, []}, transient, 1000,
+ worker, []},
+
+ {ok, CPid1} = supervisor:start_child(sup_test, Child1),
+
+ terminate(SupPid, CPid1, child1, shutdown),
+
+ [{child1,undefined,worker,[]}] = supervisor:which_children(sup_test),
+ [1,0,0,1] = get_child_counts(sup_test),
+
+ {ok, CPid2} = supervisor:restart_child(sup_test, child1),
+
+ terminate(SupPid, CPid2, child1, {shutdown, some_info}),
+
+ [{child1,undefined,worker,[]}] = supervisor:which_children(sup_test),
+ [1,0,0,1] = get_child_counts(sup_test).
+
+%%-------------------------------------------------------------------------
+temporary_shutdown(doc) ->
+ ["A temporary process should never be restarted"];
+temporary_shutdown(suite) -> [];
+temporary_shutdown(Config) when is_list(Config) ->
+ {ok, SupPid} = start_link({ok, {{one_for_one, 2, 3600}, []}}),
+ Child1 = {child1, {supervisor_1, start_child, []}, temporary, 1000,
+ worker, []},
+
+ {ok, CPid1} = supervisor:start_child(sup_test, Child1),
+
+ terminate(SupPid, CPid1, child1, shutdown),
+
+ [] = supervisor:which_children(sup_test),
+ [0,0,0,0] = get_child_counts(sup_test),
+
+ {ok, CPid2} = supervisor:start_child(sup_test, Child1),
+
+ terminate(SupPid, CPid2, child1, {shutdown, some_info}),
+
+ [] = supervisor:which_children(sup_test),
+ [0,0,0,0] = get_child_counts(sup_test).
+
+%%-------------------------------------------------------------------------
permanent_abnormal(doc) ->
["A permanent child should always be restarted"];
permanent_abnormal(suite) -> [];
@@ -782,6 +873,38 @@ simple_one_for_one(Config) when is_list(Config) ->
terminate(SupPid, Pid4, Id4, abnormal),
check_exit([SupPid]).
+
+%%-------------------------------------------------------------------------
+simple_one_for_one_shutdown(doc) ->
+ ["Test simple_one_for_one children shutdown accordingly to the "
+ "supervisor's shutdown strategy."];
+simple_one_for_one_shutdown(suite) -> [];
+simple_one_for_one_shutdown(Config) when is_list(Config) ->
+ process_flag(trap_exit, true),
+ ShutdownTime = 1000,
+ Child = {child, {supervisor_2, start_child, []},
+ permanent, 2*ShutdownTime, worker, []},
+ {ok, SupPid} = start_link({ok, {{simple_one_for_one, 2, 3600}, [Child]}}),
+
+ %% Will be gracefully shutdown
+ {ok, _CPid1} = supervisor:start_child(sup_test, [ShutdownTime]),
+ {ok, _CPid2} = supervisor:start_child(sup_test, [ShutdownTime]),
+
+ %% Will be killed after 2*ShutdownTime milliseconds
+ {ok, _CPid3} = supervisor:start_child(sup_test, [5*ShutdownTime]),
+
+ {T, ok} = timer:tc(fun terminate/2, [SupPid, shutdown]),
+ if T < 1000*ShutdownTime ->
+ %% Because supervisor's children wait before exiting, it can't
+ %% terminate quickly
+ test_server:fail({shutdown_too_short, T});
+ T >= 1000*5*ShutdownTime ->
+ test_server:fail({shutdown_too_long, T});
+ true ->
+ check_exit([SupPid])
+ end.
+
+
%%-------------------------------------------------------------------------
simple_one_for_one_extra(doc) ->
["Tests automatic restart of children "
@@ -1018,25 +1141,25 @@ count_children_memory(Config) when is_list(Config) ->
[supervisor:start_child(sup_test, []) || _Ignore <- lists:seq(1,1000)],
garbage_collect(),
- _Size1 = erlang:memory(processes_used),
+ _Size1 = proc_memory(),
Children = supervisor:which_children(sup_test),
- _Size2 = erlang:memory(processes_used),
+ _Size2 = proc_memory(),
ChildCount = get_child_counts(sup_test),
- _Size3 = erlang:memory(processes_used),
+ _Size3 = proc_memory(),
[supervisor:start_child(sup_test, []) || _Ignore2 <- lists:seq(1,1000)],
garbage_collect(),
Children2 = supervisor:which_children(sup_test),
- Size4 = erlang:memory(processes_used),
+ Size4 = proc_memory(),
ChildCount2 = get_child_counts(sup_test),
- Size5 = erlang:memory(processes_used),
+ Size5 = proc_memory(),
garbage_collect(),
Children3 = supervisor:which_children(sup_test),
- Size6 = erlang:memory(processes_used),
+ Size6 = proc_memory(),
ChildCount3 = get_child_counts(sup_test),
- Size7 = erlang:memory(processes_used),
+ Size7 = proc_memory(),
1000 = length(Children),
[1,1000,0,1000] = ChildCount,
@@ -1062,6 +1185,10 @@ count_children_memory(Config) when is_list(Config) ->
[terminate(SupPid, Pid, child, kill) || {undefined, Pid, worker, _Modules} <- Children3],
[1,0,0,0] = get_child_counts(sup_test).
+proc_memory() ->
+ erts_debug:set_internal_state(wait, deallocations),
+ erlang:memory(processes_used).
+
%%-------------------------------------------------------------------------
do_not_save_start_parameters_for_temporary_children(doc) ->
["Temporary children shall not be restarted so they should not "
@@ -1282,6 +1409,13 @@ terminate(_, ChildPid, _, shutdown) ->
{'DOWN', Ref, process, ChildPid, shutdown} ->
ok
end;
+terminate(_, ChildPid, _, {shutdown, Term}) ->
+ Ref = erlang:monitor(process, ChildPid),
+ exit(ChildPid, {shutdown, Term}),
+ receive
+ {'DOWN', Ref, process, ChildPid, {shutdown, Term}} ->
+ ok
+ end;
terminate(_, ChildPid, _, normal) ->
Ref = erlang:monitor(process, ChildPid),
ChildPid ! stop,
diff --git a/lib/stdlib/test/unicode_SUITE.erl b/lib/stdlib/test/unicode_SUITE.erl
index 9aa800209d..4055af2741 100644
--- a/lib/stdlib/test/unicode_SUITE.erl
+++ b/lib/stdlib/test/unicode_SUITE.erl
@@ -322,7 +322,7 @@ roundtrips(Config) when is_list(Config) ->
ex_roundtrips(Config) when is_list(Config) ->
?line L1 = ranges(0, 16#D800 - 1,
erlang:system_info(context_reductions) * 11),
- ?line L2 = ranges(16#DFFF + 1, 16#FFFE - 1,
+ ?line L2 = ranges(16#DFFF + 1, 16#10000 - 1,
erlang:system_info(context_reductions) * 11),
%?line L3 = ranges(16#FFFF + 1, 16#10FFFF,
% erlang:system_info(context_reductions) * 11),
@@ -569,7 +569,6 @@ utf16_illegal_sequences_bif(Config) when is_list(Config) ->
ex_utf16_illegal_sequences_bif(Config) when is_list(Config) ->
?line utf16_fail_range_bif_simple(16#10FFFF+1, 16#10FFFF+512), %Too large.
?line utf16_fail_range_bif(16#D800, 16#DFFF), %Reserved for UTF-16.
- ?line utf16_fail_range_bif(16#FFFE, 16#FFFF), %Non-characters.
?line lonely_hi_surrogate_bif(16#D800, 16#DBFF,incomplete),
?line lonely_hi_surrogate_bif(16#DC00, 16#DFFF,error),
@@ -644,7 +643,6 @@ utf8_illegal_sequences_bif(Config) when is_list(Config) ->
ex_utf8_illegal_sequences_bif(Config) when is_list(Config) ->
?line fail_range_bif(16#10FFFF+1, 16#10FFFF+512), %Too large.
?line fail_range_bif(16#D800, 16#DFFF), %Reserved for UTF-16.
- ?line fail_range_bif(16#FFFE, 16#FFFF), %Reserved (BOM).
%% Illegal first character.
?line [fail_bif(<<I,16#8F,16#8F,16#8F>>,unicode) || I <- lists:seq(16#80, 16#BF)],