diff options
Diffstat (limited to 'lib/stdlib/test')
34 files changed, 3343 insertions, 641 deletions
diff --git a/lib/stdlib/test/Makefile b/lib/stdlib/test/Makefile index 5502c69fa5..b36265302c 100644 --- a/lib/stdlib/test/Makefile +++ b/lib/stdlib/test/Makefile @@ -20,6 +20,7 @@ MODULES= \ digraph_utils_SUITE \ dummy1_h \ dummy_h \ + dummy_via \ edlin_expand_SUITE \ epp_SUITE \ erl_eval_helper \ @@ -65,6 +66,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 91fff3cee4..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. @@ -571,8 +591,18 @@ do_encrypted_abstr(Beam, Key) -> ?line {ok,{simple,[{"Abst",Abst}]}} = beam_lib:chunks(Beam, ["Abst"]), ?line {ok,cleared} = beam_lib:clear_crypto_key_fun(), + + %% Try to force a stop/start race. + ?line start_stop_race(10000), + ok. +start_stop_race(0) -> + ok; +start_stop_race(N) -> + {error,_} = beam_lib:crypto_key_fun(bad_fun), + undefined = beam_lib:clear_crypto_key_fun(), + start_stop_race(N-1). bad_fun(F) -> {error,E} = beam_lib:crypto_key_fun(F), @@ -773,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/binary_module_SUITE.erl b/lib/stdlib/test/binary_module_SUITE.erl index 8fb63f33bd..bac59a3107 100644 --- a/lib/stdlib/test/binary_module_SUITE.erl +++ b/lib/stdlib/test/binary_module_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, - interesting/1,random_ref_comp/1,random_ref_sr_comp/1, + interesting/1,scope_return/1,random_ref_comp/1,random_ref_sr_comp/1, random_ref_fla_comp/1,parts/1, bin_to_list/1, list_to_bin/1, copy/1, referenced/1,guard/1,encode_decode/1,badargs/1,longest_common_trap/1]). @@ -67,7 +67,7 @@ end_per_testcase(_Case, Config) -> suite() -> [{ct_hooks,[ts_install_cth]}]. all() -> - [interesting, random_ref_fla_comp, random_ref_sr_comp, + [scope_return,interesting, random_ref_fla_comp, random_ref_sr_comp, random_ref_comp, parts, bin_to_list, list_to_bin, copy, referenced, guard, encode_decode, badargs, longest_common_trap]. @@ -379,6 +379,20 @@ subj() -> Subject. +scope_return(doc) -> + ["Test correct return values for scopes (OTP-9701)."]; +scope_return(Config) when is_list(Config) -> + N=10000, + Bin=binary:copy(<<"a">>,N), + scope_loop(Bin,0,N). + +scope_loop(_,N,N) -> + ok; +scope_loop(Bin,N,M) -> + ?line {N,1} = binary:match(Bin,<<"a">>,[{scope,{N,1}}]), + ?line {N,1} = binary:match(Bin,[<<"a">>,<<"b">>],[{scope,{N,1}}]), + scope_loop(Bin,N+1,M). + interesting(doc) -> ["Try some interesting patterns"]; interesting(Config) when is_list(Config) -> 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/dummy_via.erl b/lib/stdlib/test/dummy_via.erl new file mode 100644 index 0000000000..e405811cbe --- /dev/null +++ b/lib/stdlib/test/dummy_via.erl @@ -0,0 +1,94 @@ +-module(dummy_via). +-export([reset/0, + register_name/2, + whereis_name/1, + unregister_name/1, + send/2]). + + +reset() -> + P = whereis(?MODULE), + catch unlink(P), + Ref = erlang:monitor(process, P), + catch exit(P, kill), + receive {'DOWN',Ref,_,_,_} -> ok end, + Me = self(), + Pid = spawn_link(fun() -> + register(?MODULE, self()), + Me ! {self(), started}, + loop([]) + end), + receive + {Pid, started} -> + Pid + after 10000 -> + exit(timeout) + end. + +register_name(Name, Pid) when is_pid(Pid) -> + call({register_name, Name, Pid}). + +unregister_name(Name) -> + call({unregister_name, Name}). + +whereis_name(Name) -> + call({whereis_name, Name}). + +send(Name, Msg) -> + case whereis_name(Name) of + undefined -> + exit({badarg, {Name, Msg}}); + Pid when is_pid(Pid) -> + Pid ! Msg, + Pid + end. + +call(Req) -> + MRef = erlang:monitor(process, ?MODULE), + ?MODULE ! {self(), MRef, Req}, + receive + {'DOWN', MRef, _, _, _} -> + erlang:error(badarg); + {MRef, badarg} -> + erlang:error(badarg); + {MRef, Reply} -> + Reply + after 5000 -> + erlang:error(timeout) + end. + +loop(Reg) -> + receive + {'DOWN', _, _, P, _} when is_pid(P) -> + loop([X || {_,Pid,_} = X <- Reg, Pid =/= P]); + {From, Ref, Request} when is_pid(From), is_reference(Ref) -> + {Reply, NewReg} = handle_request(Request, Reg), + From ! {Ref, Reply}, + loop(NewReg) + end. + +handle_request({register_name, Name, Pid}, Reg) when is_pid(Pid) -> + case lists:keyfind(Name, 1, Reg) of + false -> + Ref = erlang:monitor(process, Pid), + {yes, [{Name, Pid, Ref}|Reg]}; + _ -> + {no, Reg} + end; +handle_request({whereis_name, Name}, Reg) -> + case lists:keyfind(Name, 1, Reg) of + {_, Pid, _} -> + {Pid, Reg}; + false -> + {undefined, Reg} + end; +handle_request({unregister_name, Name}, Reg) -> + case lists:keyfind(Name, 1, Reg) of + {_, _, Ref} -> + catch erlang:demonitor(Ref); + _ -> + ok + end, + {ok, lists:keydelete(Name, 1, Reg)}; +handle_request(_, Reg) -> + {badarg, Reg}. 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..ca2f18a05a 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}) -> @@ -1161,15 +1167,22 @@ do_funs(LFH, EFH) -> [[[0]]], ['F'], LFH, EFH), %% Tests for a bug found by the Dialyzer - used to crash. - ?line check(fun() -> Pmod = erl_eval_helper:new(42), Pmod:add(5) end, - "begin Pmod = erl_eval_helper:new(42), Pmod:add(5) end.", - 47, - ['Pmod'], LFH, EFH), - ?line check(fun() -> Pmod = erl_eval_helper:new(42), B = Pmod:add(7), B end, - "begin Pmod = erl_eval_helper:new(42), B = Pmod:add(7), B end.", - 49, - ['B','Pmod'], LFH, EFH), - + case test_server:is_native(erl_eval) of + true -> + %% Parameterized modules are not supported by HiPE. + ok; + false -> + check(fun() -> Pmod = erl_eval_helper:new(42), Pmod:add(5) end, + "begin Pmod = erl_eval_helper:new(42), Pmod:add(5) end.", + 47, + ['Pmod'], LFH, EFH), + check(fun() -> Pmod = erl_eval_helper:new(42), + B = Pmod:add(7), B end, + "begin Pmod = erl_eval_helper:new(42), " + "B = Pmod:add(7), B end.", + 49, + ['B','Pmod'], LFH, EFH) + end, ok. count_down(F, N) when N > 0 -> diff --git a/lib/stdlib/test/erl_expand_records_SUITE.erl b/lib/stdlib/test/erl_expand_records_SUITE.erl index f8c1ad783c..8b162cfda0 100644 --- a/lib/stdlib/test/erl_expand_records_SUITE.erl +++ b/lib/stdlib/test/erl_expand_records_SUITE.erl @@ -178,6 +178,9 @@ expr(Config) when is_list(Config) -> true -> not_ok end. + + is_record(_, _, _) -> + error(wrong_is_record). ">> ], @@ -366,6 +369,8 @@ strict(Config) when is_list(Config) -> end catch error:_ -> ok end. + element(_, _) -> + error(wrong_element). ">> ], ?line run(Config, Ts1, [strict_record_tests]), @@ -380,6 +385,8 @@ strict(Config) when is_list(Config) -> case foo of _ when A#r2.a =:= 1 -> ok end. + element(_, _) -> + error(wrong_element). ">> ], ?line run(Config, Ts2, [no_strict_record_tests]), @@ -415,6 +422,11 @@ update(Config) when is_list(Config) -> t2() -> R0 = #r{}, #r{_ = R0#r{a = ok}}. + + %% Implicit calls to setelement/3 must go to the BIF, + %% not to this function. + setelement(_, _, _) -> + erlang:error(wrong_setelement_called). ">> ], ?line run(Config, Ts), diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl index 9041adbe5c..4e93f056ad 100644 --- a/lib/stdlib/test/erl_lint_SUITE.erl +++ b/lib/stdlib/test/erl_lint_SUITE.erl @@ -2631,7 +2631,35 @@ bif_clash(Config) when is_list(Config) -> binary_part(A,B,C). ">>, [warn_unused_import], - {warnings,[{2,erl_lint,{redefine_bif_import,{binary_part,3}}}]}} + {warnings,[{2,erl_lint,{redefine_bif_import,{binary_part,3}}}]}}, + %% Don't accept call to a guard BIF if there is a local definition + %% or an import with the same name. Note: is_record/2 is an + %% exception, since it is more of syntatic sugar than a real BIF. + {clash21, + <<"-export([is_list/1]). + -import(x, [is_tuple/1]). + -record(r, {a,b}). + x(T) when is_tuple(T) -> ok; + x(T) when is_list(T) -> ok. + y(T) when is_tuple(T) =:= true -> ok; + y(T) when is_list(T) =:= true -> ok; + y(T) when is_record(T, r, 3) -> ok; + y(T) when is_record(T, r, 3) =:= true -> ok; + y(T) when is_record(T, r) =:= true -> ok. + is_list(_) -> + ok. + is_record(_, _) -> + ok. + is_record(_, _, _) -> + ok. + ">>, + [{no_auto_import,[{is_tuple,1}]}], + {errors,[{4,erl_lint,{illegal_guard_local_call,{is_tuple,1}}}, + {5,erl_lint,{illegal_guard_local_call,{is_list,1}}}, + {6,erl_lint,{illegal_guard_local_call,{is_tuple,1}}}, + {7,erl_lint,{illegal_guard_local_call,{is_list,1}}}, + {8,erl_lint,{illegal_guard_local_call,{is_record,3}}}, + {9,erl_lint,{illegal_guard_local_call,{is_record,3}}}],[]}} ], ?line [] = run(Config, Ts), 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 3ac6da3d28..59532b65a0 100644 --- a/lib/stdlib/test/ets_SUITE.erl +++ b/lib/stdlib/test/ets_SUITE.erl @@ -72,6 +72,7 @@ exit_many_many_tables_owner/1]). -export([write_concurrency/1, heir/1, give_away/1, setopts/1]). -export([bad_table/1, types/1]). +-export([otp_9932/1]). -export([otp_9423/1]). -export([init_per_testcase/2, end_per_testcase/2]). @@ -145,6 +146,7 @@ all() -> exit_many_large_table_owner, exit_many_tables_owner, exit_many_many_tables_owner, write_concurrency, heir, give_away, setopts, bad_table, types, + otp_9932, otp_9423]. groups() -> @@ -176,6 +178,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 +307,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 +326,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 +587,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 +796,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) -> @@ -819,6 +825,14 @@ t_delete_all_objects(Config) when is_list(Config) -> repeat_for_opts(t_delete_all_objects_do), ?line verify_etsmem(EtsMem). +get_kept_objects(T) -> + case ets:info(T,stats) of + false -> + 0; + {_,_,_,_,_,_,KO} -> + KO + end. + t_delete_all_objects_do(Opts) -> ?line T=ets_new(x,Opts), ?line filltabint(T,4000), @@ -828,10 +842,10 @@ t_delete_all_objects_do(Opts) -> ?line true = ets:delete_all_objects(T), ?line '$end_of_table' = ets:next(T,O), ?line 0 = ets:info(T,size), - ?line 4000 = ets:info(T,kept_objects), + ?line 4000 = get_kept_objects(T), ?line ets:safe_fixtable(T,false), ?line 0 = ets:info(T,size), - ?line 0 = ets:info(T,kept_objects), + ?line 0 = get_kept_objects(T), ?line filltabint(T,4000), ?line 4000 = ets:info(T,size), ?line true = ets:delete_all_objects(T), @@ -861,10 +875,10 @@ t_delete_object_do(Opts) -> ?line ets:delete_object(T,{First, integer_to_list(First)}), ?line Next = ets:next(T,First), ?line 3999 = ets:info(T,size), - ?line 1 = ets:info(T,kept_objects), + ?line 1 = get_kept_objects(T), ?line ets:safe_fixtable(T,false), ?line 3999 = ets:info(T,size), - ?line 0 = ets:info(T,kept_objects), + ?line 0 = get_kept_objects(T), ?line ets:delete(T), ?line T1 = ets_new(x,[ordered_set | Opts]), ?line filltabint(T1,4000), @@ -1934,7 +1948,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. @@ -2140,24 +2154,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, @@ -2165,14 +2179,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, @@ -2248,9 +2260,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(). @@ -2267,7 +2279,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)), @@ -2278,7 +2290,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)), @@ -2290,7 +2302,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)), @@ -2305,12 +2317,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(), @@ -2346,7 +2358,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"}), @@ -2375,6 +2387,8 @@ setopts_do(Opts) -> ?line {'EXIT',{badarg,_}} = (catch ets:setopts(T,{protection,private,false})), ?line {'EXIT',{badarg,_}} = (catch ets:setopts(T,protection)), ?line ets:delete(T), + unlink(Heir), + exit(Heir, bang), ok. bad_table(doc) -> ["All kinds of operations with bad table argument"]; @@ -2397,14 +2411,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, @@ -2644,7 +2658,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)}}; @@ -3250,7 +3264,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]) @@ -3612,7 +3626,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)]. @@ -3839,7 +3853,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), @@ -4243,7 +4257,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) @@ -4847,12 +4861,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). @@ -4921,12 +4930,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. @@ -4971,21 +4983,21 @@ grow_pseudo_deleted_do(Type) -> [true]}]), Left = Mult*(Mod-1), ?line Left = ets:info(T,size), - ?line Mult = ets:info(T,kept_objects), + ?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), io:format("Unfix table done. ~p nitems=~p\n",[now(),ets:info(T,size)]), ?line false = ets:info(T,fixed), - ?line 0 = ets:info(T,kept_objects), + ?line 0 = get_kept_objects(T), ?line done = receive_any(), %%verify_table_load(T), % may fail if concurrency is poor (genny) ets:delete(T), @@ -5012,20 +5024,20 @@ shrink_pseudo_deleted_do(Type) -> [{'>', '$1', Half}], [true]}]), ?line Half = ets:info(T,size), - ?line Half = ets:info(T,kept_objects), - 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 Half = get_kept_objects(T), + 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), io:format("Unfix table done. ~p nitems=~p\n",[now(),ets:info(T,size)]), ?line false = ets:info(T,fixed), - ?line 0 = ets:info(T,kept_objects), + ?line 0 = get_kept_objects(T), ?line done = receive_any(), %%verify_table_load(T), % may fail if concurrency is poor (genny) ets:delete(T), @@ -5141,7 +5153,7 @@ smp_fixed_delete_do() -> ?line 0 = ets:info(T,size), ?line true = ets:info(T,fixed), ?line Buckets = num_of_buckets(T), - ?line NumOfObjs = ets:info(T,kept_objects), + ?line NumOfObjs = get_kept_objects(T), ets:safe_fixtable(T,false), %% Will fail as unfix does not shrink the table: %%?line Mem = ets:info(T,memory), @@ -5173,27 +5185,27 @@ smp_unfix_fix_do() -> Left = NumOfObjs - Deleted, ?line Left = ets:info(T,size), ?line true = ets:info(T,fixed), - ?line Deleted = ets:info(T,kept_objects), + ?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 = ets:info(T,kept_objects) >= 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), @@ -5203,7 +5215,7 @@ smp_unfix_fix_do() -> Child ! done, {'DOWN', Mref, process, Child, normal} = receive_any(), ?line false = ets:info(T,fixed), - ?line 0 = ets:info(T,kept_objects), + ?line 0 = get_kept_objects(T), %%verify_table_load(T), ets:delete(T), process_flag(scheduler,0). @@ -5224,11 +5236,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(), @@ -5241,7 +5253,7 @@ otp_8166_do(WC) -> ZombieCrPid ! quit, {'DOWN', ZombieCrMref, process, ZombieCrPid, normal} = receive_any(), ?line false = ets:info(T,fixed), - ?line 0 = ets:info(T,kept_objects), + ?line 0 = get_kept_objects(T), %%verify_table_load(T), ets:delete(T), process_flag(scheduler,0). @@ -5308,7 +5320,7 @@ otp_8166_zombie_creator(T,Deleted) -> verify_table_load(T) -> ?line Stats = ets:info(T,stats), - ?line {Buckets,AvgLen,StdDev,ExpSD,_MinLen,_MaxLen} = Stats, + ?line {Buckets,AvgLen,StdDev,ExpSD,_MinLen,_MaxLen,_} = Stats, ?line ok = if AvgLen > 7 -> io:format("Table overloaded: Stats=~p\n~p\n", @@ -5424,6 +5436,22 @@ types_do(Opts) -> ?line verify_etsmem(EtsMem). +%% OTP-9932: Memory overwrite when inserting large integers in compressed bag. +%% Will crash with segv on 64-bit opt if not fixed. +otp_9932(Config) when is_list(Config) -> + T = ets:new(xxx, [bag, compressed]), + Fun = fun(N) -> + Key = {1316110174588445 bsl N,1316110174588583 bsl N}, + S = {Key, Key}, + true = ets:insert(T, S), + [S] = ets:lookup(T, Key), + true = ets:insert(T, S), + [S] = ets:lookup(T, Key) + end, + lists:foreach(Fun, lists:seq(0, 16)), + ets:delete(T). + + otp_9423(doc) -> ["vm-deadlock caused by race between ets:delete and others on write_concurrency table"]; otp_9423(Config) when is_list(Config) -> InitF = fun(_) -> {0,0} end, @@ -5488,7 +5516,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; @@ -5537,31 +5565,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( @@ -5638,6 +5665,8 @@ spawn_logger(Procs) -> true -> exit(Proc, kill); _ -> ok end, + erlang:display({"Waiting for 'DOWN' from", Proc, + process_info(Proc), pid_status(Proc)}), receive {'DOWN', Mon, _, _, _} -> ok @@ -5648,6 +5677,15 @@ spawn_logger(Procs) -> spawn_logger([From]) end. +pid_status(Pid) -> + try + erts_debug:get_internal_state({process_status, Pid}) + catch + error:undef -> + erts_debug:set_internal_state(available_internal_state, true), + pid_status(Pid) + end. + start_spawn_logger() -> case whereis(ets_test_spawn_logger) of Pid when is_pid(Pid) -> true; @@ -5673,7 +5711,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. @@ -5685,9 +5723,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; @@ -5750,11 +5796,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 -> @@ -5920,7 +5966,7 @@ very_big_num(0, Result) -> ?line Result. make_port() -> - ?line open_port({spawn, efile}, [eof]). + ?line open_port({spawn, "efile"}, [eof]). make_pid() -> ?line spawn_link(?MODULE, sleeper, []). 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/filename_SUITE.erl b/lib/stdlib/test/filename_SUITE.erl index 70b0d413dc..4cfa589660 100644 --- a/lib/stdlib/test/filename_SUITE.erl +++ b/lib/stdlib/test/filename_SUITE.erl @@ -483,6 +483,22 @@ find_src(Config) when is_list(Config) -> %% Try to find the source for a preloaded module. ?line {error,{preloaded,init}} = filename:find_src(init), + + %% Make sure that find_src works for a slim BEAM file. + OldPath = code:get_path(), + try + PrivDir = ?config(priv_dir, Config), + code:add_patha(PrivDir), + Src = "simple", + SrcPath = filename:join(PrivDir, Src) ++ ".erl", + SrcContents = "-module(simple).\n", + ok = file:write_file(SrcPath, SrcContents), + {ok,simple} = compile:file(SrcPath, [slim,{outdir,PrivDir}]), + BeamPath = filename:join(PrivDir, Src), + {BeamPath,[]} = filename:find_src(simple) + after + code:set_path(OldPath) + end, ok. %% diff --git a/lib/stdlib/test/gen_event_SUITE.erl b/lib/stdlib/test/gen_event_SUITE.erl index b3a7edc140..5c51e12e35 100644 --- a/lib/stdlib/test/gen_event_SUITE.erl +++ b/lib/stdlib/test/gen_event_SUITE.erl @@ -62,6 +62,8 @@ start(suite) -> []; start(Config) when is_list(Config) -> OldFl = process_flag(trap_exit, true), + ?line dummy_via:reset(), + ?line {ok, Pid0} = gen_event:start(), %anonymous ?line [] = gen_event:which_handlers(Pid0), ?line ok = gen_event:stop(Pid0), @@ -85,6 +87,11 @@ start(Config) when is_list(Config) -> ?line [] = gen_event:which_handlers(Pid4), ?line ok = gen_event:stop({global, my_dummy_name}), + ?line {ok, Pid5} = gen_event:start_link({via, dummy_via, my_dummy_name}), + ?line [] = gen_event:which_handlers({via, dummy_via, my_dummy_name}), + ?line [] = gen_event:which_handlers(Pid5), + ?line ok = gen_event:stop({via, dummy_via, my_dummy_name}), + ?line {ok, _} = gen_event:start_link({local, my_dummy_name}), ?line {error, {already_started, _}} = gen_event:start_link({local, my_dummy_name}), @@ -92,15 +99,28 @@ start(Config) when is_list(Config) -> gen_event:start({local, my_dummy_name}), ?line ok = gen_event:stop(my_dummy_name), - ?line {ok, Pid5} = gen_event:start_link({global, my_dummy_name}), + ?line {ok, Pid6} = gen_event:start_link({global, my_dummy_name}), ?line {error, {already_started, _}} = gen_event:start_link({global, my_dummy_name}), ?line {error, {already_started, _}} = gen_event:start({global, my_dummy_name}), - exit(Pid5, shutdown), + exit(Pid6, shutdown), + receive + {'EXIT', Pid6, shutdown} -> ok + after 10000 -> + ?t:fail(exit_gen_event) + end, + + ?line {ok, Pid7} = gen_event:start_link({via, dummy_via, my_dummy_name}), + ?line {error, {already_started, _}} = + gen_event:start_link({via, dummy_via, my_dummy_name}), + ?line {error, {already_started, _}} = + gen_event:start({via, dummy_via, my_dummy_name}), + + exit(Pid7, shutdown), receive - {'EXIT', Pid5, shutdown} -> ok + {'EXIT', Pid7, shutdown} -> ok after 10000 -> ?t:fail(exit_gen_event) end, diff --git a/lib/stdlib/test/gen_fsm_SUITE.erl b/lib/stdlib/test/gen_fsm_SUITE.erl index d60629d841..bdb4ea65b5 100644 --- a/lib/stdlib/test/gen_fsm_SUITE.erl +++ b/lib/stdlib/test/gen_fsm_SUITE.erl @@ -21,11 +21,11 @@ -include_lib("test_server/include/test_server.hrl"). %% Test cases --export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, +-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, init_per_group/2,end_per_group/2]). --export([ start1/1, start2/1, start3/1, start4/1 , start5/1, start6/1, - start7/1, start8/1, start9/1, start10/1, start11/1]). +-export([start1/1, start2/1, start3/1, start4/1, start5/1, start6/1, + start7/1, start8/1, start9/1, start10/1, start11/1, start12/1]). -export([ abnormal1/1, abnormal2/1]). @@ -56,14 +56,14 @@ suite() -> [{ct_hooks,[ts_install_cth]}]. -all() -> +all() -> [{group, start}, {group, abnormal}, shutdown, {group, sys}, hibernate, enter_loop]. -groups() -> +groups() -> [{start, [], [start1, start2, start3, start4, start5, start6, start7, - start8, start9, start10, start11]}, + start8, start9, start10, start11, start12]}, {abnormal, [], [abnormal1, abnormal2]}, {sys, [], [sys1, call_format_status, error_format_status]}]. @@ -258,6 +258,25 @@ start11(Config) when is_list(Config) -> test_server:messages_get(), ok. +%% Via register linked +start12(Config) when is_list(Config) -> + ?line dummy_via:reset(), + ?line {ok, Pid} = + gen_fsm:start_link({via, dummy_via, my_fsm}, gen_fsm_SUITE, [], []), + ?line {error, {already_started, Pid}} = + gen_fsm:start_link({via, dummy_via, my_fsm}, gen_fsm_SUITE, [], []), + ?line {error, {already_started, Pid}} = + gen_fsm:start({via, dummy_via, my_fsm}, gen_fsm_SUITE, [], []), + + ?line ok = do_func_test(Pid), + ?line ok = do_sync_func_test(Pid), + ?line ok = do_func_test({via, dummy_via, my_fsm}), + ?line ok = do_sync_func_test({via, dummy_via, my_fsm}), + ?line stop_it({via, dummy_via, my_fsm}), + + test_server:messages_get(), + ok. + %% Check that time outs in calls work abnormal1(suite) -> []; @@ -362,7 +381,25 @@ call_format_status(Config) when is_list(Config) -> ?line Status4 = sys:get_status(GlobalName2), ?line {status, Pid4, _Mod, [_PDict4, running, _, _, Data4]} = Status4, ?line [format_status_called | _] = lists:reverse(Data4), - ?line stop_it(Pid4). + ?line stop_it(Pid4), + + %% check that format_status can handle a name being a term other than a + %% pid or atom + ?line dummy_via:reset(), + ViaName1 = {via, dummy_via, "CallFormatStatus"}, + ?line {ok, Pid5} = gen_fsm:start(ViaName1, gen_fsm_SUITE, [], []), + ?line Status5 = sys:get_status(ViaName1), + ?line {status, Pid5, _Mod, [_PDict5, running, _, _, Data5]} = Status5, + ?line [format_status_called | _] = lists:reverse(Data5), + ?line stop_it(Pid5), + ViaName2 = {via, dummy_via, {name, "term"}}, + ?line {ok, Pid6} = gen_fsm:start(ViaName2, gen_fsm_SUITE, [], []), + ?line Status6 = sys:get_status(ViaName2), + ?line {status, Pid6, _Mod, [_PDict6, running, _, _, Data6]} = Status6, + ?line [format_status_called | _] = lists:reverse(Data6), + ?line stop_it(Pid6). + + error_format_status(Config) when is_list(Config) -> ?line error_logger_forwarder:register(), @@ -520,6 +557,8 @@ enter_loop(doc) -> enter_loop(Config) when is_list(Config) -> OldFlag = process_flag(trap_exit, true), + ?line dummy_via:reset(), + %% Locally registered process + {local, Name} ?line {ok, Pid1a} = proc_lib:start_link(?MODULE, enter_loop, [local, local]), @@ -623,10 +662,22 @@ enter_loop(Config) when is_list(Config) -> {'EXIT', Pid6b, process_not_registered_globally} -> ok after 1000 -> - ?line test_server:fail(gen_server_started) + ?line test_server:fail(gen_fsm_started) end, global:unregister_name(armitage), + dummy_via:register_name(armitage, self()), + ?line {ok, Pid6c} = + proc_lib:start_link(?MODULE, enter_loop, [anon, via]), + receive + {'EXIT', Pid6c, {process_not_registered_via, dummy_via}} -> + ok + after 1000 -> + ?line test_server:fail({gen_fsm_started, process_info(self(), + messages)}) + end, + dummy_via:unregister_name(armitage), + process_flag(trap_exit, OldFlag), ok. @@ -635,6 +686,7 @@ enter_loop(Reg1, Reg2) -> case Reg1 of local -> register(armitage, self()); global -> global:register_name(armitage, self()); + via -> dummy_via:register_name(armitage, self()); anon -> ignore end, proc_lib:init_ack({ok, self()}), @@ -643,6 +695,9 @@ enter_loop(Reg1, Reg2) -> gen_fsm:enter_loop(?MODULE, [], state0, [], {local,armitage}); global -> gen_fsm:enter_loop(?MODULE, [], state0, [], {global,armitage}); + via -> + gen_fsm:enter_loop(?MODULE, [], state0, [], + {via, dummy_via, armitage}); anon -> gen_fsm:enter_loop(?MODULE, [], state0, []) end. diff --git a/lib/stdlib/test/gen_server_SUITE.erl b/lib/stdlib/test/gen_server_SUITE.erl index a614d6595d..cdf15ba017 100644 --- a/lib/stdlib/test/gen_server_SUITE.erl +++ b/lib/stdlib/test/gen_server_SUITE.erl @@ -36,7 +36,7 @@ ]). % spawn export --export([spec_init_local/2, spec_init_global/2, +-export([spec_init_local/2, spec_init_global/2, spec_init_via/2, spec_init_default_timeout/2, spec_init_anonymous/1, spec_init_anonymous_default_timeout/1, spec_init_not_proc_lib/1, cast_fast_messup/0]). @@ -199,6 +199,35 @@ start(Config) when is_list(Config) -> test_server:fail(not_stopped) end, + %% via register + ?line dummy_via:reset(), + ?line {ok, Pid6} = + gen_server:start({via, dummy_via, my_test_name}, + gen_server_SUITE, [], []), + ?line ok = gen_server:call({via, dummy_via, my_test_name}, started_p), + ?line {error, {already_started, Pid6}} = + gen_server:start({via, dummy_via, my_test_name}, + gen_server_SUITE, [], []), + ?line ok = gen_server:call({via, dummy_via, my_test_name}, stop), + test_server:sleep(1), + ?line {'EXIT', {noproc,_}} = (catch gen_server:call(Pid6, started_p, 10)), + + %% via register linked + ?line dummy_via:reset(), + ?line {ok, Pid7} = + gen_server:start_link({via, dummy_via, my_test_name}, + gen_server_SUITE, [], []), + ?line ok = gen_server:call({via, dummy_via, my_test_name}, started_p), + ?line {error, {already_started, Pid7}} = + gen_server:start({via, dummy_via, my_test_name}, + gen_server_SUITE, [], []), + ?line ok = gen_server:call({via, dummy_via, my_test_name}, stop), + ?line receive + {'EXIT', Pid7, stopped} -> + ok + after 5000 -> + test_server:fail(not_stopped) + end, test_server:messages_get(), %% Must wait for all error messages before going to next test. @@ -694,7 +723,7 @@ multicall_down(Config) when is_list(Config) -> %% We use 'global' as a gen_server to call. ?line {Good, Bad} = gen_server:multi_call([Name, node()], global_name_server, - {whereis, gurkburk}, + info, 3000), io:format("good = ~p, bad = ~p~n", [Good, Bad]), ?line [Name] = Bad, @@ -853,6 +882,8 @@ otp_5854(doc) -> otp_5854(Config) when is_list(Config) -> OldFlag = process_flag(trap_exit, true), + ?line dummy_via:reset(), + %% Make sure gen_server:enter_loop does not accept {local,Name} %% when it's another process than the calling one which is %% registered under that name @@ -881,6 +912,18 @@ otp_5854(Config) when is_list(Config) -> end, global:unregister_name(armitage), + %% (same for {via, Mod, Name}) + dummy_via:register_name(armitage, self()), + ?line {ok, Pid3} = + start_link(spec_init_via, [{not_ok, armitage}, []]), + receive + {'EXIT', Pid3, {process_not_registered_via, dummy_via}} -> + ok + after 1000 -> + ?line test_server:fail(gen_server_started) + end, + dummy_via:unregister_name(armitage), + process_flag(trap_exit, OldFlag), ok. @@ -1060,7 +1103,22 @@ spec_init_global({not_ok, Name}, Options) -> %% Supervised init can occur here ... gen_server:enter_loop(?MODULE, Options, {}, {global, Name}, infinity). -spec_init_default_timeout({ok, Name}, Options) -> +spec_init_via({ok, Name}, Options) -> + process_flag(trap_exit, true), + dummy_via:register_name(Name, self()), + proc_lib:init_ack({ok, self()}), + %% Supervised init can occur here ... + gen_server:enter_loop(?MODULE, Options, {}, + {via, dummy_via, Name}, infinity); + +spec_init_via({not_ok, Name}, Options) -> + process_flag(trap_exit, true), + proc_lib:init_ack({ok, self()}), + %% Supervised init can occur here ... + gen_server:enter_loop(?MODULE, Options, {}, + {via, dummy_via, Name}, infinity). + +spec_init_default_timeout({ok, Name}, Options) -> process_flag(trap_exit, true), register(Name, self()), proc_lib:init_ack({ok, self()}), diff --git a/lib/stdlib/test/ms_transform_SUITE.erl b/lib/stdlib/test/ms_transform_SUITE.erl index 4e5df12798..a17307b07b 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) -> @@ -426,7 +455,6 @@ old_guards(Config) when is_list(Config) -> ?line setup(Config), Tests = [ {atom,is_atom}, - {constant,is_constant}, {float,is_float}, {integer,is_integer}, {list,is_list}, @@ -461,7 +489,6 @@ old_guards(Config) when is_list(Config) -> ?line [{'$1',[{is_integer,'$1'}, {is_float,'$1'}, {is_atom,'$1'}, - {is_constant,'$1'}, {is_list,'$1'}, {is_number,'$1'}, {is_pid,'$1'}, @@ -473,7 +500,7 @@ old_guards(Config) when is_list(Config) -> [true]}] = compile_and_run(RD, << "ets:fun2ms(fun(X) when integer(X)," - "float(X), atom(X), constant(X)," + "float(X), atom(X)," "list(X), number(X), pid(X)," "port(X), reference(X), tuple(X)," "binary(X), record(X,a) -> true end)" @@ -501,7 +528,6 @@ autoimported(Config) when is_list(Config) -> {self,0}, %{float,1}, see float_1_function/1 {is_atom,1}, - {is_constant,1}, {is_float,1}, {is_integer,1}, {is_list,1}, @@ -842,6 +868,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..50a76cdfb5 100644 --- a/lib/stdlib/test/qlc_SUITE.erl +++ b/lib/stdlib/test/qlc_SUITE.erl @@ -20,7 +20,6 @@ %%% Purpose:Test Suite for the 'qlc' module. %%%----------------------------------------------------------------- -module(qlc_SUITE). --compile(r12). -define(QLC, qlc). -define(QLCs, "qlc"). @@ -6118,6 +6117,7 @@ otp_6964(Config) when is_list(Config) -> qlc:e(Q, [{max_list_size,64*1024},{tmpdir_usage,Use}]) end, D = erlang:system_flag(backtrace_depth, 0), + try 20000 = length(F(allowed)), ErrReply = F(not_allowed), {error, qlc, {tmpdir_usage,joining}} = ErrReply, @@ -6129,8 +6129,10 @@ otp_6964(Config) when is_list(Config) -> 20000 = length(F(info_msg)), {info, joining} = qlc_SUITE:read_error_logger(), 20000 = length(F(error_msg)), - {error, joining} = qlc_SUITE:read_error_logger(), - _ = erlang:system_flag(backtrace_depth, D), + {error, joining} = qlc_SUITE:read_error_logger() + after + _ = erlang:system_flag(backtrace_depth, D) + end, qlc_SUITE:uninstall_error_logger()">>], ?line run(Config, T1), @@ -6632,7 +6634,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,_}}}}, @@ -7399,70 +7401,37 @@ backward(doc) -> "OTP-6674. Join info and extra constants."; backward(suite) -> []; backward(Config) when is_list(Config) -> - case try_old_join_info(Config) of - ok -> - ok; - Reply -> - Reply - end. - --ifdef(debug). -try_old_join_info(_Config) -> + try_old_join_info(Config), ok. --else. + try_old_join_info(Config) -> - case ?t:is_release_available("r12b") of - true -> - %% Check join info for handlers of extra constants. Start R12B-0. - ?line {ok, R12} = start_node_rel(r12, r12b, slave), - File = filename("handle.erl", Config), - ?line file:write_file(File, - <<"-module(handle).\n" - "-export([create_handle/0, lookup_handle/0]).\n" - "-include_lib(\"stdlib/include/qlc.hrl\").\n" - "create_handle() ->\n" - " H1 = qlc:sort([{192.0,1,a},{192.0,2,b},{192.0,3,c}]),\n" - " qlc:q([{X, Y} || {B,X,_} <- H1,\n" - " B =:= 192.0,\n" - " {Y} <- [{0},{1},{2}],\n" - " X == Y]).\n", - "\n", - "lookup_handle() ->\n" - " E = qlc_SUITE:table([{1,a},{2,b},{3,c}], 1, [1]),\n" - " qlc:q([{X, Y} || {X,_} <- E,\n" - " {Y} <- [{0},{1},{2}],\n" - " X =:= Y]).\n">>), - ?line {ok, handle} = rpc:call(R12, compile, file, - [File, [{outdir,?privdir}]]), - ?line {module, handle} = rpc:call(R12, code, load_abs, - [filename:rootname(File)]), - ?line H = rpc:call(R12, handle, create_handle, []), - ?line {module, handle} = code:load_abs(filename:rootname(File)), - ?line {block,0, - [{match,_,_, - {call,_,_, - [{lc,_,_, - [_, - {op,_,'=:=', - {float,_,192.0}, - {call,_,{atom,_,element},[{integer,_,1},_]}}]}]}}, - _,_, - {call,_,_, - [{lc,_,_, - [_, - {op,_,'=:=',{var,_,'B'},{float,_,192.0}}, - {op,_,'==',{var,_,'X'},{var,_,'Y'}}]}]}]} - = qlc:info(H,{format,abstract_code}), - ?line [{1,1},{2,2}] = qlc:e(H), - ?line H2 = rpc:call(R12, handle, lookup_handle, []), - ?line {qlc,_,[{generate,_,{qlc,_,_,[{join,lookup}]}},_],[]} = - qlc:info(H2, {format,debug}), - ?line [{1,1},{2,2}] = qlc:e(H2), - stop_node(R12); - false -> - ?line {skipped, "No support for old node"} - end. --endif. + %% Check join info for handlers of extra constants. + File = filename:join(?datadir, "join_info_compat.erl"), + M = join_info_compat, + {ok, M} = compile:file(File, [{outdir, ?datadir}]), + {module, M} = code:load_abs(filename:rootname(File)), + H = M:create_handle(), + {block,0, + [{match,_,_, + {call,_,_, + [{lc,_,_, + [_, + {op,_,'=:=', + {float,_,192.0}, + {call,_,{atom,_,element},[{integer,_,1},_]}}]}]}}, + _,_, + {call,_,_, + [{lc,_,_, + [_, + {op,_,'=:=',{var,_,'B'},{float,_,192.0}}, + {op,_,'==',{var,_,'X'},{var,_,'Y'}}]}]}]} + = qlc:info(H,{format,abstract_code}), + [{1,1},{2,2}] = qlc:e(H), + + H2 = M:lookup_handle(), + {qlc,_,[{generate,_,{qlc,_,_,[{join,lookup}]}},_],[]} = + qlc:info(H2, {format,debug}), + [{1,1},{2,2}] = qlc:e(H2). forward(doc) -> ""; @@ -8127,27 +8096,6 @@ fail(Source) -> %% Copied from global_SUITE.erl. -start_node_rel(Name, Rel, How) -> - {Release, Compat} = case Rel of - this -> - {[this], "+R8"}; - Rel when is_atom(Rel) -> - {[{release, atom_to_list(Rel)}], ""}; - RelList -> - {RelList, ""} - end, - ?line Pa = filename:dirname(code:which(?MODULE)), - ?line Res = test_server:start_node(Name, How, - [{args, - Compat ++ - " -kernel net_setuptime 100 " - " -pa " ++ Pa}, - {erl, Release}]), - Res. - -stop_node(Node) -> - ?line ?t:stop_node(Node). - install_error_logger() -> error_logger:add_report_handler(?MODULE, self()). diff --git a/lib/stdlib/test/qlc_SUITE_data/join_info_compat.erl b/lib/stdlib/test/qlc_SUITE_data/join_info_compat.erl new file mode 100644 index 0000000000..e0db132c47 --- /dev/null +++ b/lib/stdlib/test/qlc_SUITE_data/join_info_compat.erl @@ -0,0 +1,1771 @@ +%% +%% %CopyrightBegin% +%% +%% Copyright Ericsson AB 2008-2011. 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% +%% +-module(join_info_compat). + +-compile(export_all). + +create_handle() -> + H1 = qlc:sort([{192.0,1,a},{192.0,2,b},{192.0,3,c}]), + qlc:q({qlc_lc, + % fun-info: {23,109048965,'-create_handle/0-fun-23-'} + fun() -> + {qlc_v1, + % fun-info: {2,105724313,'-create_handle/0-fun-2-'} + fun(S01_0_1, RL01_0_1, Go01_0_1) -> + Fun1_0_1 = + % fun-info: {1,131900588,'-create_handle/0-fun-1-'} + fun(0, RL1_0_1, _, _, _, _, _, _, _) + when is_list(RL1_0_1) -> + lists:reverse(RL1_0_1); + (0, _, _, _, _, _, _, _, _) -> + []; + (1, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_1_1, + B1, + X1) + when is_list(RL1_0_1) -> + Fun1_0_1(element(1, Go1_0_1), + [{X1,Y1}|RL1_0_1], + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_1_1, + B1, + X1); + (1, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_1_1, + B1, + X1) -> + [{X1,Y1}| + % fun-info: {0,27702789,'-create_handle/0-fun-0-'} + fun() -> + Fun1_0_1(element(1, + Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_1_1, + B1, + X1) + end]; + (2, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + _, + B1, + X1) -> + Fun1_0_1(3, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + element(4, Go1_0_1), + B1, + X1); + (3, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + [{B1,X1,_}|C1_0_1], + _, + _) -> + Fun1_0_1(element(3, Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_0_1, + B1, + X1); + (3, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + [_|C1_0_1], + _, + _) -> + Fun1_0_1(3, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_0_1, + [], + []); + (3, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + [], + _, + _) -> + Fun1_0_1(element(2, Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + [], + [], + []); + (3, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_1_1, + _, + _) -> + case C1_1_1() of + [{B1,X1,_}|C1_0_1] -> + Fun1_0_1(element(3, + Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_0_1, + B1, + X1); + [_|C1_0_1] -> + Fun1_0_1(3, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_0_1, + [], + []); + [] -> + Fun1_0_1(element(2, + Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + [], + [], + []); + E1_0_1 -> + E1_0_1 + end; + (4, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_1_1, + B1, + X1) -> + if + B1 =:= 192.0 -> + Fun1_0_1(element(6, + Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_1_1, + B1, + X1); + true -> + Fun1_0_1(element(5, + Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_1_1, + B1, + X1) + end; + (5, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + _, + Y1, + C1_1_1, + B1, + X1) -> + Fun1_0_1(6, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + element(9, Go1_0_1), + Y1, + C1_1_1, + B1, + X1); + (6, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + [{Y1}|C1_0_1], + _, + C1_1_1, + B1, + X1) -> + Fun1_0_1(element(8, Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_0_1, + Y1, + C1_1_1, + B1, + X1); + (6, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + [_|C1_0_1], + _, + C1_1_1, + B1, + X1) -> + Fun1_0_1(6, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_0_1, + [], + C1_1_1, + B1, + X1); + (6, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + [], + _, + C1_1_1, + B1, + X1) -> + Fun1_0_1(element(7, Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + [], + [], + C1_1_1, + B1, + X1); + (6, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + _, + C1_1_1, + B1, + X1) -> + case C1_3_1() of + [{Y1}|C1_0_1] -> + Fun1_0_1(element(8, + Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_0_1, + Y1, + C1_1_1, + B1, + X1); + [_|C1_0_1] -> + Fun1_0_1(6, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_0_1, + [], + C1_1_1, + B1, + X1); + [] -> + Fun1_0_1(element(7, + Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + [], + [], + C1_1_1, + B1, + X1); + E1_0_1 -> + E1_0_1 + end; + (7, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_1_1, + B1, + X1) -> + if + X1 == Y1 -> + Fun1_0_1(element(11, + Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_1_1, + B1, + X1); + true -> + Fun1_0_1(element(10, + Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_1_1, + B1, + X1) + end; + (8, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + _, + B1, + X1) -> + Fun1_0_1(9, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + element(14, Go1_0_1), + B1, + X1); + (9, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + _, + [[{B1,X1,_}|{Y1}]|C1_0_1], + _, + _) -> + Fun1_0_1(element(13, Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_0_1, + B1, + X1); + (9, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + _, + [_|C1_0_1], + _, + _) -> + Fun1_0_1(9, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + [], + C1_0_1, + [], + []); + (9, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + _, + [], + _, + _) -> + Fun1_0_1(element(12, Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + [], + [], + [], + []); + (9, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + _, + C1_1_1, + _, + _) -> + case C1_1_1() of + [[{B1,X1,_}|{Y1}]|C1_0_1] -> + Fun1_0_1(element(13, + Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_0_1, + B1, + X1); + [_|C1_0_1] -> + Fun1_0_1(9, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + [], + C1_0_1, + [], + []); + [] -> + Fun1_0_1(element(12, + Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + [], + [], + [], + []); + E1_0_1 -> + E1_0_1 + end + end, + Fun1_0_1(S01_0_1, + RL01_0_1, + Fun1_0_1, + Go01_0_1, + [], + [], + [], + [], + []) + end, + % fun-info: {3,41816426,'-create_handle/0-fun-3-'} + fun() -> + {<<$\203:8/integer-unit:1-unsigned-big, + $P:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $.:8/integer-unit:1-unsigned-big, + $x:8/integer-unit:1-unsigned-big, + $\234:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $N:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $-:8/integer-unit:1-unsigned-big, + $):8/integer-unit:1-unsigned-big, + $-:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $I:8/integer-unit:1-unsigned-big, + $M:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $0:8/integer-unit:1-unsigned-big, + $\227:8/integer-unit:1-unsigned-big, + $%:8/integer-unit:1-unsigned-big, + $\026:8/integer-unit:1-unsigned-big, + $%:8/integer-unit:1-unsigned-big, + $r:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $0:8/integer-unit:1-unsigned-big, + $0:8/integer-unit:1-unsigned-big, + $F:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $":8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big>>, + <<$\203:8/integer-unit:1-unsigned-big, + $P:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $<:8/integer-unit:1-unsigned-big, + $x:8/integer-unit:1-unsigned-big, + $\234:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $N:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $-:8/integer-unit:1-unsigned-big, + $):8/integer-unit:1-unsigned-big, + $-:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $I:8/integer-unit:1-unsigned-big, + $M:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $0:8/integer-unit:1-unsigned-big, + $\227:8/integer-unit:1-unsigned-big, + $%:8/integer-unit:1-unsigned-big, + $\026:8/integer-unit:1-unsigned-big, + $%:8/integer-unit:1-unsigned-big, + $r:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $0:8/integer-unit:1-unsigned-big, + $0:8/integer-unit:1-unsigned-big, + $::8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $":8/integer-unit:1-unsigned-big, + $P:8/integer-unit:1-unsigned-big, + $x:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $Y:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $9:8/integer-unit:1-unsigned-big, + $\r:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big>>, + <<$\203:8/integer-unit:1-unsigned-big, + $P:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $I:8/integer-unit:1-unsigned-big, + $x:8/integer-unit:1-unsigned-big, + $\234:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $M:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $/:8/integer-unit:1-unsigned-big, + $H:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $N:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $\006:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $e:8/integer-unit:1-unsigned-big, + $\211:8/integer-unit:1-unsigned-big, + $E:8/integer-unit:1-unsigned-big, + $\s:8/integer-unit:1-unsigned-big, + $>:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\023:8/integer-unit:1-unsigned-big, + $\210:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\232:8/integer-unit:1-unsigned-big, + $\226:8/integer-unit:1-unsigned-big, + $\223:8/integer-unit:1-unsigned-big, + $\237:8/integer-unit:1-unsigned-big, + $X:8/integer-unit:1-unsigned-big, + $\222:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\235:8/integer-unit:1-unsigned-big, + $l:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $g:8/integer-unit:1-unsigned-big, + $i:8/integer-unit:1-unsigned-big, + $d:8/integer-unit:1-unsigned-big, + $\200:8/integer-unit:1-unsigned-big, + $\001:8/integer-unit:1-unsigned-big, + $R:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\r:8/integer-unit:1-unsigned-big, + $\214:8/integer-unit:1-unsigned-big, + $\030:8/integer-unit:1-unsigned-big, + $@:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $c:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\017:8/integer-unit:1-unsigned-big, + $=:8/integer-unit:1-unsigned-big>>, + <<$\203:8/integer-unit:1-unsigned-big, + $h:8/integer-unit:1-unsigned-big, + $\003:8/integer-unit:1-unsigned-big, + $d:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\005:8/integer-unit:1-unsigned-big, + $t:8/integer-unit:1-unsigned-big, + $u:8/integer-unit:1-unsigned-big, + $p:8/integer-unit:1-unsigned-big, + $l:8/integer-unit:1-unsigned-big, + $e:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $\f:8/integer-unit:1-unsigned-big, + $l:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\001:8/integer-unit:1-unsigned-big, + $h:8/integer-unit:1-unsigned-big, + $\003:8/integer-unit:1-unsigned-big, + $d:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\003:8/integer-unit:1-unsigned-big, + $v:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $r:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $\f:8/integer-unit:1-unsigned-big, + $d:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\001:8/integer-unit:1-unsigned-big, + $Y:8/integer-unit:1-unsigned-big, + $j:8/integer-unit:1-unsigned-big>>, + <<$\203:8/integer-unit:1-unsigned-big, + $P:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $*:8/integer-unit:1-unsigned-big, + $x:8/integer-unit:1-unsigned-big, + $\234:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $M:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $/:8/integer-unit:1-unsigned-big, + $H:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\005:8/integer-unit:1-unsigned-big, + $R:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\031:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $):8/integer-unit:1-unsigned-big, + $\f:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $e:8/integer-unit:1-unsigned-big, + $\211:8/integer-unit:1-unsigned-big, + $E:8/integer-unit:1-unsigned-big, + $\s:8/integer-unit:1-unsigned-big, + $.:8/integer-unit:1-unsigned-big, + $c:8/integer-unit:1-unsigned-big, + $\004:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $/:8/integer-unit:1-unsigned-big, + $\022:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\205:8/integer-unit:1-unsigned-big, + $\t:8/integer-unit:1-unsigned-big, + $\216:8/integer-unit:1-unsigned-big>>, + <<$\203:8/integer-unit:1-unsigned-big, + $P:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $j:8/integer-unit:1-unsigned-big, + $x:8/integer-unit:1-unsigned-big, + $\234:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $I:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $I:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $+:8/integer-unit:1-unsigned-big, + $N:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\f:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\024:8/integer-unit:1-unsigned-big, + $\006:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\222:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\202:8/integer-unit:1-unsigned-big, + $\234:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $D:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\034:8/integer-unit:1-unsigned-big, + $\006:8/integer-unit:1-unsigned-big, + $\006:8/integer-unit:1-unsigned-big, + $\006:8/integer-unit:1-unsigned-big, + $f:8/integer-unit:1-unsigned-big, + $\220:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $s:8/integer-unit:1-unsigned-big, + $Y:8/integer-unit:1-unsigned-big, + $b:8/integer-unit:1-unsigned-big, + $Q:8/integer-unit:1-unsigned-big, + $":8/integer-unit:1-unsigned-big, + $W:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $\003:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\023:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $/:8/integer-unit:1-unsigned-big, + $\002:8/integer-unit:1-unsigned-big, + $\205:8/integer-unit:1-unsigned-big, + $\027:8/integer-unit:1-unsigned-big, + $\237:8/integer-unit:1-unsigned-big, + $\205:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\227:8/integer-unit:1-unsigned-big, + $\007:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\227:8/integer-unit:1-unsigned-big, + $\021:8/integer-unit:1-unsigned-big, + $.:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\003:8/integer-unit:1-unsigned-big, + $\224:8/integer-unit:1-unsigned-big, + $\217:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\002:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\203:8/integer-unit:1-unsigned-big, + $>:8/integer-unit:1-unsigned-big, + $\034:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big>>} + end, + [{1, + 2, + 2, + {gen, + % fun-info: {4,131674517,'-create_handle/0-fun-4-'} + fun() -> + H1 + end}}, + {2,5,4,fil}, + {3, + 7, + 5, + {gen, + % fun-info: {5,108000324,'-create_handle/0-fun-5-'} + fun() -> + [{0},{1},{2}] + end}}, + {4,10,7,fil}, + {5, + 12, + 8, + {gen, + {join, + '==', + 1, + 3, + % fun-info: {9,59718458,'-create_handle/0-fun-9-'} + fun(H1_0_1) -> + F1_0_1 = + % fun-info: {7,779460,'-create_handle/0-fun-7-'} + fun(_, []) -> + []; + (F1_0_1, [O1_0_1|C1_0_1]) -> + case O1_0_1 of + {_,_,_} + when + 192.0 + =:= + element(1, O1_0_1) -> + [O1_0_1| + % fun-info: {6,23729943,'-create_handle/0-fun-6-'} + fun() -> + F1_0_1(F1_0_1, + C1_0_1) + end]; + _ -> + F1_0_1(F1_0_1, C1_0_1) + end; + (F1_0_1, C1_0_1) + when is_function(C1_0_1) -> + F1_0_1(F1_0_1, C1_0_1()); + (_, C1_0_1) -> + C1_0_1 + end, + % fun-info: {8,43652904,'-create_handle/0-fun-8-'} + fun() -> + F1_0_1(F1_0_1, H1_0_1) + end + end, + % fun-info: {13,102310144,'-create_handle/0-fun-13-'} + fun(H1_0_1) -> + F1_0_1 = + % fun-info: {11,74362432,'-create_handle/0-fun-11-'} + fun(_, []) -> + []; + (F1_0_1, [O1_0_1|C1_0_1]) -> + case O1_0_1 of + {_} -> + [O1_0_1| + % fun-info: {10,23729943,'-create_handle/0-fun-10-'} + fun() -> + F1_0_1(F1_0_1, + C1_0_1) + end]; + _ -> + F1_0_1(F1_0_1, C1_0_1) + end; + (F1_0_1, C1_0_1) + when is_function(C1_0_1) -> + F1_0_1(F1_0_1, C1_0_1()); + (_, C1_0_1) -> + C1_0_1 + end, + % fun-info: {12,43652904,'-create_handle/0-fun-12-'} + fun() -> + F1_0_1(F1_0_1, H1_0_1) + end + end, + % fun-info: {14,17838355,'-create_handle/0-fun-14-'} + fun() -> + {[{1,[192.0]}],[],[]} + end}}}], + % fun-info: {22,31304647,'-create_handle/0-fun-22-'} + fun(join) -> + {[[{1,"\002"},{3,"\001"}]],[]}; + (size) -> + % fun-info: {15,31963143,'-create_handle/0-fun-15-'} + fun(0) -> + 2; + (1) -> + 3; + (3) -> + 1; + (_) -> + undefined + end; + (template) -> + % fun-info: {16,113413274,'-create_handle/0-fun-16-'} + fun({1,2}, '=:=') -> + "\001"; + ({1,2}, '==') -> + "\001\002"; + ({3,1}, '=:=') -> + "\002"; + ({3,1}, '==') -> + "\001\002"; + (_, _) -> + [] + end; + (constants) -> + % fun-info: {18,52148739,'-create_handle/0-fun-18-'} + fun(1) -> + % fun-info: {17,5864387,'-create_handle/0-fun-17-'} + fun(1) -> + {values,[192.0],{some,[2]}}; + (_) -> + false + end; + (_) -> + no_column_fun + end; + (n_leading_constant_columns) -> + % fun-info: {19,82183172,'-create_handle/0-fun-19-'} + fun(1) -> + 1; + (_) -> + 0 + end; + (constant_columns) -> + % fun-info: {20,80910005,'-create_handle/0-fun-20-'} + fun(1) -> + "\001"; + (_) -> + [] + end; + (match_specs) -> + % fun-info: {21,91764346,'-create_handle/0-fun-21-'} + fun(1) -> + {[{{'$1','$2','_'}, + [{'=:=','$1',192.0}], + ['$_']}], + "\002"}; + (_) -> + undefined + end; + (_) -> + undefined + end} + end, + undefined}). + +lookup_handle() -> + E = qlc_SUITE:table([{1,a},{2,b},{3,c}], 1, [1]), + qlc:q({qlc_lc, + % fun-info: {46,120768015,'-lookup_handle/0-fun-22-'} + fun() -> + {qlc_v1, + % fun-info: {26,82970908,'-lookup_handle/0-fun-2-'} + fun(S02_0_1, RL02_0_1, Go02_0_1) -> + Fun2_0_1 = + % fun-info: {25,75235357,'-lookup_handle/0-fun-1-'} + fun(0, RL2_0_1, _, _, _, _, _, _) + when is_list(RL2_0_1) -> + lists:reverse(RL2_0_1); + (0, _, _, _, _, _, _, _) -> + []; + (1, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_1_1, + X2) + when is_list(RL2_0_1) -> + Fun2_0_1(element(1, Go2_0_1), + [{X2,Y2}|RL2_0_1], + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_1_1, + X2); + (1, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_1_1, + X2) -> + [{X2,Y2}| + % fun-info: {24,124255471,'-lookup_handle/0-fun-0-'} + fun() -> + Fun2_0_1(element(1, + Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_1_1, + X2) + end]; + (2, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + _, + X2) -> + Fun2_0_1(3, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + element(4, Go2_0_1), + X2); + (3, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + [{X2,_}|C2_0_1], + _) -> + Fun2_0_1(element(3, Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_0_1, + X2); + (3, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + [_|C2_0_1], + _) -> + Fun2_0_1(3, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_0_1, + []); + (3, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + [], + _) -> + Fun2_0_1(element(2, Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + [], + []); + (3, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_1_1, + _) -> + case C2_1_1() of + [{X2,_}|C2_0_1] -> + Fun2_0_1(element(3, + Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_0_1, + X2); + [_|C2_0_1] -> + Fun2_0_1(3, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_0_1, + []); + [] -> + Fun2_0_1(element(2, + Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + [], + []); + E2_0_1 -> + E2_0_1 + end; + (4, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + _, + Y2, + C2_1_1, + X2) -> + Fun2_0_1(5, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + element(7, Go2_0_1), + Y2, + C2_1_1, + X2); + (5, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + [{Y2}|C2_0_1], + _, + C2_1_1, + X2) -> + Fun2_0_1(element(6, Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_0_1, + Y2, + C2_1_1, + X2); + (5, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + [_|C2_0_1], + _, + C2_1_1, + X2) -> + Fun2_0_1(5, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_0_1, + [], + C2_1_1, + X2); + (5, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + [], + _, + C2_1_1, + X2) -> + Fun2_0_1(element(5, Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + [], + [], + C2_1_1, + X2); + (5, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + _, + C2_1_1, + X2) -> + case C2_2_1() of + [{Y2}|C2_0_1] -> + Fun2_0_1(element(6, + Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_0_1, + Y2, + C2_1_1, + X2); + [_|C2_0_1] -> + Fun2_0_1(5, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_0_1, + [], + C2_1_1, + X2); + [] -> + Fun2_0_1(element(5, + Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + [], + [], + C2_1_1, + X2); + E2_0_1 -> + E2_0_1 + end; + (6, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_1_1, + X2) -> + if + X2 =:= Y2 -> + Fun2_0_1(element(9, + Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_1_1, + X2); + true -> + Fun2_0_1(element(8, + Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_1_1, + X2) + end; + (7, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + _, + X2) -> + Fun2_0_1(8, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + element(12, Go2_0_1), + X2); + (8, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + _, + [[{X2,_}|{Y2}]|C2_0_1], + _) -> + Fun2_0_1(element(11, Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_0_1, + X2); + (8, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + _, + [_|C2_0_1], + _) -> + Fun2_0_1(8, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + [], + C2_0_1, + []); + (8, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + _, + [], + _) -> + Fun2_0_1(element(10, Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + [], + [], + []); + (8, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + _, + C2_1_1, + _) -> + case C2_1_1() of + [[{X2,_}|{Y2}]|C2_0_1] -> + Fun2_0_1(element(11, + Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_0_1, + X2); + [_|C2_0_1] -> + Fun2_0_1(8, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + [], + C2_0_1, + []); + [] -> + Fun2_0_1(element(10, + Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + [], + [], + []); + E2_0_1 -> + E2_0_1 + end + end, + Fun2_0_1(S02_0_1, + RL02_0_1, + Fun2_0_1, + Go02_0_1, + [], + [], + [], + []) + end, + % fun-info: {27,111349661,'-lookup_handle/0-fun-3-'} + fun() -> + {<<$\203:8/integer-unit:1-unsigned-big, + $P:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $.:8/integer-unit:1-unsigned-big, + $x:8/integer-unit:1-unsigned-big, + $\234:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $N:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $-:8/integer-unit:1-unsigned-big, + $):8/integer-unit:1-unsigned-big, + $-:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $I:8/integer-unit:1-unsigned-big, + $M:8/integer-unit:1-unsigned-big, + $\024:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $0:8/integer-unit:1-unsigned-big, + $\227:8/integer-unit:1-unsigned-big, + $%:8/integer-unit:1-unsigned-big, + $\026:8/integer-unit:1-unsigned-big, + $%:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $0:8/integer-unit:1-unsigned-big, + $0:8/integer-unit:1-unsigned-big, + $F:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $":8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\206:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big>>, + <<$\203:8/integer-unit:1-unsigned-big, + $P:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $.:8/integer-unit:1-unsigned-big, + $x:8/integer-unit:1-unsigned-big, + $\234:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $N:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $-:8/integer-unit:1-unsigned-big, + $):8/integer-unit:1-unsigned-big, + $-:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $I:8/integer-unit:1-unsigned-big, + $M:8/integer-unit:1-unsigned-big, + $\024:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $0:8/integer-unit:1-unsigned-big, + $\227:8/integer-unit:1-unsigned-big, + $%:8/integer-unit:1-unsigned-big, + $\026:8/integer-unit:1-unsigned-big, + $%:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $0:8/integer-unit:1-unsigned-big, + $0:8/integer-unit:1-unsigned-big, + $F:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\222:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big>>, + <<$\203:8/integer-unit:1-unsigned-big, + $h:8/integer-unit:1-unsigned-big, + $\003:8/integer-unit:1-unsigned-big, + $d:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\005:8/integer-unit:1-unsigned-big, + $t:8/integer-unit:1-unsigned-big, + $u:8/integer-unit:1-unsigned-big, + $p:8/integer-unit:1-unsigned-big, + $l:8/integer-unit:1-unsigned-big, + $e:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $\022:8/integer-unit:1-unsigned-big, + $l:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\001:8/integer-unit:1-unsigned-big, + $h:8/integer-unit:1-unsigned-big, + $\003:8/integer-unit:1-unsigned-big, + $d:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\003:8/integer-unit:1-unsigned-big, + $v:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $r:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $\022:8/integer-unit:1-unsigned-big, + $d:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\001:8/integer-unit:1-unsigned-big, + $Y:8/integer-unit:1-unsigned-big, + $j:8/integer-unit:1-unsigned-big>>, + <<$\203:8/integer-unit:1-unsigned-big, + $P:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $+:8/integer-unit:1-unsigned-big, + $x:8/integer-unit:1-unsigned-big, + $\234:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $M:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $/:8/integer-unit:1-unsigned-big, + $H:8/integer-unit:1-unsigned-big, + $\024:8/integer-unit:1-unsigned-big, + $N:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $\006:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $e:8/integer-unit:1-unsigned-big, + $\211:8/integer-unit:1-unsigned-big, + $E:8/integer-unit:1-unsigned-big, + $\s:8/integer-unit:1-unsigned-big, + $>:8/integer-unit:1-unsigned-big, + $c:8/integer-unit:1-unsigned-big, + $\004:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $/:8/integer-unit:1-unsigned-big, + $\022:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\227:8/integer-unit:1-unsigned-big, + $\t:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big>>, + <<$\203:8/integer-unit:1-unsigned-big, + $P:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\\:8/integer-unit:1-unsigned-big, + $x:8/integer-unit:1-unsigned-big, + $\234:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $I:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $I:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $+:8/integer-unit:1-unsigned-big, + $N:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\f:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\024:8/integer-unit:1-unsigned-big, + $\006:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\222:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\202:8/integer-unit:1-unsigned-big, + $\234:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $D:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\034:8/integer-unit:1-unsigned-big, + $\006:8/integer-unit:1-unsigned-big, + $\006:8/integer-unit:1-unsigned-big, + $\006:8/integer-unit:1-unsigned-big, + $&:8/integer-unit:1-unsigned-big, + $\220:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $s:8/integer-unit:1-unsigned-big, + $Y:8/integer-unit:1-unsigned-big, + $b:8/integer-unit:1-unsigned-big, + $Q:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $\003:8/integer-unit:1-unsigned-big, + $c:8/integer-unit:1-unsigned-big, + $\004:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $/:8/integer-unit:1-unsigned-big, + $>:8/integer-unit:1-unsigned-big, + $\v:8/integer-unit:1-unsigned-big, + $I:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\020:8/integer-unit:1-unsigned-big, + $H:8/integer-unit:1-unsigned-big, + $5:8/integer-unit:1-unsigned-big, + $#:8/integer-unit:1-unsigned-big, + $\\:8/integer-unit:1-unsigned-big, + $^:8/integer-unit:1-unsigned-big, + $\b:8/integer-unit:1-unsigned-big, + $(:8/integer-unit:1-unsigned-big, + $\037:8/integer-unit:1-unsigned-big, + $\231:8/integer-unit:1-unsigned-big, + $\005:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\024:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\031:8/integer-unit:1-unsigned-big, + $M:8/integer-unit:1-unsigned-big>>} + end, + [{1, + 2, + 2, + {gen, + % fun-info: {28,75197307,'-lookup_handle/0-fun-4-'} + fun() -> + E + end}}, + {2, + 5, + 4, + {gen, + % fun-info: {29,86826511,'-lookup_handle/0-fun-5-'} + fun() -> + [{0},{1},{2}] + end}}, + {3,8,6,fil}, + {4, + 10, + 7, + {gen, + {join, + '==', + 1, + 2, + % fun-info: {33,129609919,'-lookup_handle/0-fun-9-'} + fun(H2_0_1) -> + F2_0_1 = + % fun-info: {31,45768082,'-lookup_handle/0-fun-7-'} + fun(_, []) -> + []; + (F2_0_1, [O2_0_1|C2_0_1]) -> + case O2_0_1 of + {_,_} -> + [O2_0_1| + % fun-info: {30,28136696,'-lookup_handle/0-fun-6-'} + fun() -> + F2_0_1(F2_0_1, + C2_0_1) + end]; + _ -> + F2_0_1(F2_0_1, C2_0_1) + end; + (F2_0_1, C2_0_1) + when is_function(C2_0_1) -> + F2_0_1(F2_0_1, C2_0_1()); + (_, C2_0_1) -> + C2_0_1 + end, + % fun-info: {32,48059625,'-lookup_handle/0-fun-8-'} + fun() -> + F2_0_1(F2_0_1, H2_0_1) + end + end, + % fun-info: {37,63676968,'-lookup_handle/0-fun-13-'} + fun(H2_0_1) -> + F2_0_1 = + % fun-info: {35,129320532,'-lookup_handle/0-fun-11-'} + fun(_, []) -> + []; + (F2_0_1, [O2_0_1|C2_0_1]) -> + case O2_0_1 of + {_} -> + [O2_0_1| + % fun-info: {34,28136696,'-lookup_handle/0-fun-10-'} + fun() -> + F2_0_1(F2_0_1, + C2_0_1) + end]; + _ -> + F2_0_1(F2_0_1, C2_0_1) + end; + (F2_0_1, C2_0_1) + when is_function(C2_0_1) -> + F2_0_1(F2_0_1, C2_0_1()); + (_, C2_0_1) -> + C2_0_1 + end, + % fun-info: {36,48059625,'-lookup_handle/0-fun-12-'} + fun() -> + F2_0_1(F2_0_1, H2_0_1) + end + end, + % fun-info: {38,3236543,'-lookup_handle/0-fun-14-'} + fun() -> + {[],[],[]} + end}}}], + % fun-info: {45,56361026,'-lookup_handle/0-fun-21-'} + fun(join) -> + [[{1,"\001"},{2,"\001"}]]; + (size) -> + % fun-info: {39,40607542,'-lookup_handle/0-fun-15-'} + fun(0) -> + 2; + (1) -> + 2; + (2) -> + 1; + (_) -> + undefined + end; + (template) -> + % fun-info: {40,34907048,'-lookup_handle/0-fun-16-'} + fun({1,1}, _) -> + "\001\002"; + ({2,1}, _) -> + "\001\002"; + (_, _) -> + [] + end; + (constants) -> + % fun-info: {41,11686091,'-lookup_handle/0-fun-17-'} + fun(_) -> + no_column_fun + end; + (n_leading_constant_columns) -> + % fun-info: {42,21492441,'-lookup_handle/0-fun-18-'} + fun(_) -> + 0 + end; + (constant_columns) -> + % fun-info: {43,55297177,'-lookup_handle/0-fun-19-'} + fun(_) -> + [] + end; + (match_specs) -> + % fun-info: {44,55081557,'-lookup_handle/0-fun-20-'} + fun(_) -> + undefined + end; + (_) -> + undefined + end} + end, + undefined}). diff --git a/lib/stdlib/test/re_SUITE.erl b/lib/stdlib/test/re_SUITE.erl index c4817c0d38..d6d946a28f 100644 --- a/lib/stdlib/test/re_SUITE.erl +++ b/lib/stdlib/test/re_SUITE.erl @@ -445,124 +445,132 @@ split_specials(Config) when is_list(Config) -> ok. -error_handling(doc) -> - ["Test that errors are handled correctly by the erlang code."]; -error_handling(Config) when is_list(Config) -> +%% Test that errors are handled correctly by the erlang code. +error_handling(_Config) -> + case test_server:is_native(re) of + true -> + %% Exceptions from native code look too different. + {skip,"re is native"}; + false -> + error_handling() + end. + +error_handling() -> % This test checks the exception tuples manufactured in the erlang % code to hide the trapping from the user at least when it comes to errors Dog = ?t:timetrap(?t:minutes(1)), % 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,0,_} | _]}} = (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,0,_} | _]}} = (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,0,_} | _]}} = (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,0,_} | _]}} = (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,0,_} | _]}} = (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,0,_} | _]}} = (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,0,_} | _]}} = (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,0,_} | _]}} = (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,0,_} | _]}} = (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,0,_} | _]}} = (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,0,_} | _]}} = (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,0,_} | _]}} = (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,0,_} | _]}} = (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,0,_} | _]}} = (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,0,_} | _]}} = (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,0,_} | _]}} = (catch re:split("apa",{1,2,3,4},[])), ?line {'EXIT',{badarg,[{re,split, ["apa", RE, - [unicode]]}, - {?MODULE, error_handling,1} | _]}} = + [unicode]],_}, + {?MODULE,error_handling,0,_} | _]}} = (catch re:split("apa",RE,[unicode])), ?line {'EXIT',{badarg,[{re,split, ["apa", RE, - [{return,banana}]]}, - {?MODULE, error_handling,1} | _]}} = + [{return,banana}]],_}, + {?MODULE,error_handling,0,_} | _]}} = (catch re:split("apa",RE,[{return,banana}])), ?line {'EXIT',{badarg,[{re,split, ["apa", RE, - [banana]]}, - {?MODULE, error_handling,1} | _]}} = + [banana]],_}, + {?MODULE,error_handling,0,_} | _]}} = (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,0,_} | _]}} = (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..a881742f13 100644 --- a/lib/stdlib/test/shell_SUITE.erl +++ b/lib/stdlib/test/shell_SUITE.erl @@ -2388,13 +2388,28 @@ 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]}"++_ = - comm_err(<<"erlang:error(function_clause, [unproper | list]).">>), + case test_server:is_native(erl_eval) of + true -> + %% Native code has different exit reason. Don't bother + %% testing them. + ok; + false -> + "exception error: {function_clause," = + comm_err(<<"erlang:error(function_clause, " + "[unproper | list]).">>), + %% Cheating: + "exception error: no function clause matching " + "erl_eval:do_apply(4)" ++ _ = + comm_err(<<"erlang:error(function_clause, [4]).">>), + "exception error: no function clause matching " + "lists:reverse(" ++ _ = + comm_err(<<"F=fun() -> hello end, lists:reverse(F).">>), + "exception error: no function clause matching " + "lists:reverse(34) (lists.erl, line " ++ _ = + comm_err(<<"lists:reverse(34).">>) + end, ?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)" = - comm_err(<<"erlang:error(function_clause, [4]).">>), ?line "exception error: no function clause matching" ++ _ = comm_err(<<"fun(a, b, c, d) -> foo end" " (lists:seq(1,17)," @@ -2404,10 +2419,6 @@ otp_6554(Config) when is_list(Config) -> ?line "exception error: no function clause matching" = 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)" = - 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.">>), ?line "exception error: no such process or port" = diff --git a/lib/stdlib/test/sofs_SUITE.erl b/lib/stdlib/test/sofs_SUITE.erl index d6f88a655e..f11c6ec4d6 100644 --- a/lib/stdlib/test/sofs_SUITE.erl +++ b/lib/stdlib/test/sofs_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2001-2011. All Rights Reserved. +%% Copyright Ericsson AB 2001-2012. 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 @@ -536,7 +536,7 @@ projection(Conf) when is_list(Conf) -> from_term([], [[atom]]))), ?line {'EXIT', {badarg, _}} = (catch projection({external, fun(X) -> X end}, from_term([[a]]))), - ?line eval(projection({sofs,union}, + ?line eval(projection(fun sofs:union/1, from_term([[[1,2],[2,3]], [[a,b],[b,c]]])), from_term([[1,2,3], [a,b,c]])), ?line eval(projection(fun(_) -> from_term([a]) end, @@ -628,7 +628,7 @@ substitution(Conf) when is_list(Conf) -> ?line {'EXIT', {badarg, _}} = (catch substitution({external, fun(X) -> X end}, from_term([[a]]))), ?line eval(substitution(fun(X) -> X end, from_term([], [[atom]])), E), - ?line eval(substitution({sofs,union}, + ?line eval(substitution(fun sofs:union/1, from_term([[[1,2],[2,3]], [[a,b],[b,c]]])), from_term([{[[1,2],[2,3]],[1,2,3]}, {[[a,b],[b,c]],[a,b,c]}])), ?line eval(substitution(fun(_) -> from_term([a]) end, @@ -745,7 +745,7 @@ restriction(Conf) when is_list(Conf) -> ?line eval(restriction(Id, S3, E), E), ?line eval(restriction(Id, from_term([], [[atom]]), set([a])), from_term([], [[atom]])), - ?line eval(restriction({sofs,union}, + ?line eval(restriction(fun sofs:union/1, from_term([[[a],[b]], [[b],[c]], [[], [a,b]], [[1],[2]]]), from_term([[a,b],[1,2,3],[b,c]])), @@ -862,7 +862,7 @@ drestriction(Conf) when is_list(Conf) -> ?line eval(drestriction(Id, S3, E), S3), ?line eval(drestriction(Id, from_term([], [[atom]]), set([a])), from_term([], [[atom]])), - ?line eval(drestriction({sofs,union}, + ?line eval(drestriction(fun sofs:union/1, from_term([[[a],[b]], [[b],[c]], [[], [a,b]], [[1],[2]]]), from_term([[a,b],[1,2,3],[b,c]])), @@ -1028,7 +1028,7 @@ specification(Conf) when is_list(Conf) -> end, ?line eval(specification({external,Fun2x}, S2), from_term([[1],[3]])), - Fun3 = fun(_) -> neither_true_or_false end, + Fun3 = fun(_) -> neither_true_nor_false end, ?line {'EXIT', {badarg, _}} = (catch specification(Fun3, set([a]))), ?line {'EXIT', {badarg, _}} = @@ -1810,8 +1810,8 @@ partition_3(Conf) when is_list(Conf) -> S12a = from_term([[[a],[b]], [[b],[c]], [[], [a,b]], [[1],[2]]]), S12b = from_term([[a,b],[1,2,3],[b,c]]), - ?line eval(partition({sofs,union}, S12a, S12b), - lpartition({sofs,union}, S12a, S12b)), + ?line eval(partition(fun sofs:union/1, S12a, S12b), + lpartition(fun sofs:union/1, S12a, S12b)), Fun13 = fun(_) -> from_term([a]) end, S13a = from_term([], [[atom]]), @@ -1879,12 +1879,9 @@ digraph(Conf) when is_list(Conf) -> ?line {'EXIT', {badarg, _}} = (catch family_to_digraph(set([a]))), - ?line {'EXIT', {badarg, [{sofs,family_to_digraph,[_,_]}|_]}} = - (catch family_to_digraph(set([a]), [foo])), - ?line {'EXIT', {badarg, [{sofs,family_to_digraph,[_,_]}|_]}} = - (catch family_to_digraph(F, [foo])), - ?line {'EXIT', {cyclic, [{sofs,family_to_digraph,[_,_]}|_]}} = - (catch family_to_digraph(family([{a,[a]}]),[acyclic])), + digraph_fail(badarg, catch family_to_digraph(set([a]), [foo])), + digraph_fail(badarg, catch family_to_digraph(F, [foo])), + digraph_fail(cyclic, catch family_to_digraph(family([{a,[a]}]),[acyclic])), ?line G1 = family_to_digraph(E), ?line {'EXIT', {badarg, _}} = (catch digraph_to_family(G1, foo)), @@ -1927,6 +1924,13 @@ digraph(Conf) when is_list(Conf) -> ?line true = T0 == ets:all(), ok. +digraph_fail(ExitReason, Fail) -> + {'EXIT', {ExitReason, [{sofs,family_to_digraph,A,_}|_]}} = Fail, + case {test_server:is_native(sofs),A} of + {false,[_,_]} -> ok; + {true,2} -> ok + end. + constant_function(suite) -> []; constant_function(doc) -> [""]; constant_function(Conf) when is_list(Conf) -> @@ -1952,10 +1956,8 @@ misc(Conf) when is_list(Conf) -> % the "functional" part: ?line eval(union(intersection(partition(1,S), partition(Id,S))), difference(S, RR)), - - %% The function external:foo/1 is undefined. ?line {'EXIT', {undef, _}} = - (catch projection({external,foo}, set([a,b,c]))), + (catch projection(fun external:foo/1, set([a,b,c]))), ok. relational_restriction(R) -> @@ -1968,19 +1970,19 @@ family_specification(doc) -> [""]; family_specification(Conf) when is_list(Conf) -> E = empty_set(), %% internal - ?line eval(family_specification({sofs, is_set}, E), E), + ?line eval(family_specification(fun sofs:is_set/1, E), E), ?line {'EXIT', {badarg, _}} = - (catch family_specification({sofs,is_set}, set([]))), + (catch family_specification(fun sofs:is_set/1, set([]))), ?line F1 = from_term([{1,[1]}]), - ?line eval(family_specification({sofs,is_set}, F1), F1), + ?line eval(family_specification(fun sofs:is_set/1, F1), F1), Fun = fun(S) -> is_subset(S, set([0,1,2,3,4])) end, ?line F2 = family([{a,[1,2]},{b,[3,4,5]}]), ?line eval(family_specification(Fun, F2), family([{a,[1,2]}])), ?line F3 = from_term([{a,[]},{b,[]}]), - ?line eval(family_specification({sofs,is_set}, F3), F3), + ?line eval(family_specification(fun sofs:is_set/1, F3), F3), Fun2 = fun(_) -> throw(fippla) end, ?line fippla = (catch family_specification(Fun2, family([{a,[1]}]))), - Fun3 = fun(_) -> neither_true_or_false end, + Fun3 = fun(_) -> neither_true_nor_false end, ?line {'EXIT', {badarg, _}} = (catch family_specification(Fun3, F3)), @@ -2095,22 +2097,22 @@ family_projection(Conf) when is_list(Conf) -> ?line eval(family_projection(fun(X) -> X end, family([])), E), ?line L1 = [{a,[]}], - ?line eval(family_projection({sofs,union}, E), E), - ?line eval(family_projection({sofs,union}, from_term(L1, SSType)), + ?line eval(family_projection(fun sofs:union/1, E), E), + ?line eval(family_projection(fun sofs:union/1, from_term(L1, SSType)), family(L1)), ?line {'EXIT', {badarg, _}} = - (catch family_projection({sofs,union}, set([]))), + (catch family_projection(fun sofs:union/1, set([]))), ?line {'EXIT', {badarg, _}} = - (catch family_projection({sofs,union}, from_term([{1,[1]}]))), + (catch family_projection(fun sofs:union/1, from_term([{1,[1]}]))), ?line F2 = from_term([{a,[[1],[2]]},{b,[[3,4],[5]]}], SSType), - ?line eval(family_projection({sofs,union}, F2), + ?line eval(family_projection(fun sofs:union/1, F2), family_union(F2)), ?line F3 = from_term([{1,[{a,b},{b,c},{c,d}]},{3,[]},{5,[{3,5}]}], SRType), - ?line eval(family_projection({sofs,domain}, F3), family_domain(F3)), - ?line eval(family_projection({sofs,range}, F3), family_range(F3)), + ?line eval(family_projection(fun sofs:domain/1, F3), family_domain(F3)), + ?line eval(family_projection(fun sofs:range/1, F3), family_range(F3)), ?line eval(family_projection(fun(_) -> E end, family([{a,[b,c]}])), from_term([{a,[]}])), @@ -2290,7 +2292,7 @@ partition_family(Conf) when is_list(Conf) -> ?line eval(partition_family(1, E), E), ?line eval(partition_family(2, E), E), - ?line eval(partition_family({sofs,union}, E), E), + ?line eval(partition_family(fun sofs:union/1, E), E), ?line eval(partition_family(1, ER), EF), ?line eval(partition_family(2, ER), EF), ?line {'EXIT', {badarg, _}} = (catch partition_family(1, set([]))), @@ -2354,7 +2356,7 @@ partition_family(Conf) when is_list(Conf) -> ?line {'EXIT', {badarg, _}} = (catch partition_family({external, fun(X) -> X end}, from_term([[a]]))), - ?line eval(partition_family({sofs,union}, + ?line eval(partition_family(fun sofs:union/1, from_term([[[1],[1,2]], [[1,2]]])), from_term([{[1,2], [[[1],[1,2]],[[1,2]]]}])), ?line eval(partition_family(fun(X) -> X end, diff --git a/lib/stdlib/test/stdlib_SUITE.erl b/lib/stdlib/test/stdlib_SUITE.erl index 0cca030b3d..8a2cb5ea6b 100644 --- a/lib/stdlib/test/stdlib_SUITE.erl +++ b/lib/stdlib/test/stdlib_SUITE.erl @@ -33,8 +33,7 @@ -export([init_per_testcase/2, end_per_testcase/2]). % Test cases must be exported. --export([app_test/1]). --define(cases, [app_test]). +-export([app_test/1, appup_test/1]). %% %% all/1 @@ -42,7 +41,7 @@ suite() -> [{ct_hooks,[ts_install_cth]}]. all() -> - [app_test]. + [app_test, appup_test]. groups() -> []. @@ -79,3 +78,61 @@ app_test(Config) when is_list(Config) -> ?t:app_test(stdlib), ok. +%% Test that appup allows upgrade from/downgrade to a maximum of two +%% major releases back. +appup_test(_Config) -> + application:load(stdlib), + {_,_,Vsn} = lists:keyfind(stdlib,1,application:loaded_applications()), + AppupFile = filename:join([code:lib_dir(stdlib),ebin,"stdlib.appup"]), + {ok,[{Vsn,UpFrom,DownTo}=AppupScript]} = file:consult(AppupFile), + ct:log("~p~n",[AppupScript]), + {OkVsns,NokVsns} = create_test_vsns(Vsn), + check_appup(OkVsns,UpFrom,{ok,[restart_new_emulator]}), + check_appup(OkVsns,DownTo,{ok,[restart_new_emulator]}), + check_appup(NokVsns,UpFrom,error), + check_appup(NokVsns,DownTo,error), + ok. + +create_test_vsns(Current) -> + [XStr,YStr|Rest] = string:tokens(Current,"."), + X = list_to_integer(XStr), + Y = list_to_integer(YStr), + SecondMajor = vsn(X,Y-2), + SecondMinor = SecondMajor ++ ".1.3", + FirstMajor = vsn(X,Y-1), + FirstMinor = FirstMajor ++ ".57", + ThisMajor = vsn(X,Y), + This = + case Rest of + [] -> + []; + ["1"] -> + [ThisMajor]; + _ -> + ThisMinor = ThisMajor ++ ".1", + [ThisMajor,ThisMinor] + end, + OkVsns = This ++ [FirstMajor, FirstMinor, SecondMajor, SecondMinor], + + ThirdMajor = vsn(X,Y-3), + ThirdMinor = ThirdMajor ++ ".10.12", + Illegal = ThisMajor ++ ",1", + Newer1Major = vsn(X,Y+1), + Newer1Minor = Newer1Major ++ ".1", + Newer2Major = ThisMajor ++ "1", + NokVsns = [ThirdMajor,ThirdMinor, + Illegal, + Newer1Major,Newer1Minor, + Newer2Major], + {OkVsns,NokVsns}. + +vsn(X,Y) -> + integer_to_list(X) ++ "." ++ integer_to_list(Y). + +check_appup([Vsn|Vsns],Instrs,Expected) -> + case systools_relup:appup_search_for_version(Vsn, Instrs) of + Expected -> check_appup(Vsns,Instrs,Expected); + Other -> ct:fail({unexpected_result_for_vsn,Vsn,Other}) + end; +check_appup([],_,_) -> + ok. diff --git a/lib/stdlib/test/supervisor_1.erl b/lib/stdlib/test/supervisor_1.erl index 3198be0fed..777a48e38b 100644 --- a/lib/stdlib/test/supervisor_1.erl +++ b/lib/stdlib/test/supervisor_1.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2010. All Rights Reserved. +%% Copyright Ericsson AB 1996-2011. 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 @@ -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..60d037f4e0 --- /dev/null +++ b/lib/stdlib/test/supervisor_2.erl @@ -0,0 +1,42 @@ +%% +%% %CopyrightBegin% +%% +%% Copyright Ericsson AB 1996-2011. 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..71b76c093f 100644 --- a/lib/stdlib/test/supervisor_SUITE.erl +++ b/lib/stdlib/test/supervisor_SUITE.erl @@ -29,18 +29,23 @@ end_per_testcase/2]). %% Internal export --export([init/1, terminate_all_children/1]). +-export([init/1, terminate_all_children/1, + middle9212/0, gen_server9212/0, handle_info/2]). %% API tests -export([ sup_start_normal/1, sup_start_ignore_init/1, - sup_start_ignore_child/1, sup_start_error_return/1, - sup_start_fail/1, sup_stop_infinity/1, + sup_start_ignore_child/1, sup_start_ignore_temporary_child/1, + sup_start_ignore_temporary_child_start_child/1, + sup_start_ignore_temporary_child_start_child_simple/1, + sup_start_error_return/1, sup_start_fail/1, sup_stop_infinity/1, sup_stop_timeout/1, sup_stop_brutal_kill/1, child_adm/1, child_adm_simple/1, child_specs/1, extra_return/1]). %% 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,13 +55,14 @@ 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, do_not_save_start_parameters_for_temporary_children/1, do_not_save_child_specs_for_temporary_children/1, - simple_one_for_one_scale_many_temporary_children/1]). + simple_one_for_one_scale_many_temporary_children/1, + simple_global_supervisor/1]). %%------------------------------------------------------------------------- @@ -71,21 +77,27 @@ 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, - simple_one_for_one_scale_many_temporary_children, temporary_bystander]. + simple_one_for_one_scale_many_temporary_children, temporary_bystander, + simple_global_supervisor]. groups() -> [{sup_start, [], [sup_start_normal, sup_start_ignore_init, - sup_start_ignore_child, sup_start_error_return, - sup_start_fail]}, + sup_start_ignore_child, sup_start_ignore_temporary_child, + sup_start_ignore_temporary_child_start_child, + sup_start_ignore_temporary_child_start_child_simple, + sup_start_error_return, sup_start_fail]}, {sup_stop, [], [sup_stop_infinity, sup_stop_timeout, 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 +106,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 +127,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 +137,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. @@ -145,29 +162,23 @@ get_child_counts(Supervisor) -> %%------------------------------------------------------------------------- %% Test cases starts here. -%%------------------------------------------------------------------------- -sup_start_normal(doc) -> - ["Tests that the supervisor process starts correctly and that it " - "can be terminated gracefully."]; -sup_start_normal(suite) -> []; +%% ------------------------------------------------------------------------- +%% Tests that the supervisor process starts correctly and that it can +%% be terminated gracefully. sup_start_normal(Config) when is_list(Config) -> process_flag(trap_exit, true), {ok, Pid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), terminate(Pid, shutdown). %%------------------------------------------------------------------------- -sup_start_ignore_init(doc) -> - ["Tests what happens if init-callback returns ignore"]; -sup_start_ignore_init(suite) -> []; +%% Tests what happens if init-callback returns ignore. sup_start_ignore_init(Config) when is_list(Config) -> process_flag(trap_exit, true), ignore = start_link(ignore), check_exit_reason(normal). %%------------------------------------------------------------------------- -sup_start_ignore_child(doc) -> - ["Tests what happens if init-callback returns ignore"]; -sup_start_ignore_child(suite) -> []; +%% Tests what happens if init-callback returns ignore. sup_start_ignore_child(Config) when is_list(Config) -> process_flag(trap_exit, true), {ok, _Pid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), @@ -184,30 +195,75 @@ sup_start_ignore_child(Config) when is_list(Config) -> [2,1,0,2] = get_child_counts(sup_test). %%------------------------------------------------------------------------- -sup_start_error_return(doc) -> - ["Tests what happens if init-callback returns a invalid value"]; -sup_start_error_return(suite) -> []; +%% Tests what happens if child's init-callback returns ignore for a +%% temporary child when ChildSpec is returned directly from supervisor +%% init callback. +%% Child spec shall NOT be saved!!! +sup_start_ignore_temporary_child(Config) when is_list(Config) -> + process_flag(trap_exit, true), + Child1 = {child1, {supervisor_1, start_child, [ignore]}, + temporary, 1000, worker, []}, + Child2 = {child2, {supervisor_1, start_child, []}, temporary, + 1000, worker, []}, + {ok, _Pid} = start_link({ok, {{one_for_one, 2, 3600}, [Child1,Child2]}}), + + [{child2, CPid2, worker, []}] = supervisor:which_children(sup_test), + true = is_pid(CPid2), + [1,1,0,1] = get_child_counts(sup_test). + +%%------------------------------------------------------------------------- +%% Tests what happens if child's init-callback returns ignore for a +%% temporary child when child is started with start_child/2. +%% Child spec shall NOT be saved!!! +sup_start_ignore_temporary_child_start_child(Config) when is_list(Config) -> + process_flag(trap_exit, true), + {ok, _Pid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), + Child1 = {child1, {supervisor_1, start_child, [ignore]}, + temporary, 1000, worker, []}, + Child2 = {child2, {supervisor_1, start_child, []}, temporary, + 1000, worker, []}, + + {ok, undefined} = supervisor:start_child(sup_test, Child1), + {ok, CPid2} = supervisor:start_child(sup_test, Child2), + + [{child2, CPid2, worker, []}] = supervisor:which_children(sup_test), + [1,1,0,1] = get_child_counts(sup_test). + +%%------------------------------------------------------------------------- +%% Tests what happens if child's init-callback returns ignore for a +%% temporary child when child is started with start_child/2, and the +%% supervisor is simple_one_for_one. +%% Child spec shall NOT be saved!!! +sup_start_ignore_temporary_child_start_child_simple(Config) + when is_list(Config) -> + process_flag(trap_exit, true), + Child1 = {child1, {supervisor_1, start_child, [ignore]}, + temporary, 1000, worker, []}, + {ok, _Pid} = start_link({ok, {{simple_one_for_one, 2, 3600}, [Child1]}}), + + {ok, undefined} = supervisor:start_child(sup_test, []), + {ok, CPid2} = supervisor:start_child(sup_test, []), + + [{undefined, CPid2, worker, []}] = supervisor:which_children(sup_test), + [1,1,0,1] = get_child_counts(sup_test). + +%%------------------------------------------------------------------------- +%% Tests what happens if init-callback returns a invalid value. sup_start_error_return(Config) when is_list(Config) -> process_flag(trap_exit, true), {error, Term} = start_link(invalid), check_exit_reason(Term). %%------------------------------------------------------------------------- -sup_start_fail(doc) -> - ["Tests what happens if init-callback fails"]; -sup_start_fail(suite) -> []; +%% Tests what happens if init-callback fails. sup_start_fail(Config) when is_list(Config) -> process_flag(trap_exit, true), {error, Term} = start_link(fail), check_exit_reason(Term). %%------------------------------------------------------------------------- - -sup_stop_infinity(doc) -> - ["See sup_stop/1 when Shutdown = infinity, this walue is only allowed " - "for children of type supervisor"]; -sup_stop_infinity(suite) -> []; - +%% See sup_stop/1 when Shutdown = infinity, this walue is allowed for +%% children of type supervisor _AND_ worker. sup_stop_infinity(Config) when is_list(Config) -> process_flag(trap_exit, true), {ok, Pid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), @@ -216,19 +272,16 @@ 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). %%------------------------------------------------------------------------- - -sup_stop_timeout(doc) -> - ["See sup_stop/1 when Shutdown = 1000"]; -sup_stop_timeout(suite) -> []; - +%% See sup_stop/1 when Shutdown = 1000 sup_stop_timeout(Config) when is_list(Config) -> process_flag(trap_exit, true), {ok, Pid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), @@ -250,10 +303,7 @@ sup_stop_timeout(Config) when is_list(Config) -> %%------------------------------------------------------------------------- -sup_stop_brutal_kill(doc) -> - ["See sup_stop/1 when Shutdown = brutal_kill"]; -sup_stop_brutal_kill(suite) -> []; - +%% See sup_stop/1 when Shutdown = brutal_kill sup_stop_brutal_kill(Config) when is_list(Config) -> process_flag(trap_exit, true), {ok, Pid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), @@ -272,14 +322,10 @@ sup_stop_brutal_kill(Config) when is_list(Config) -> check_exit_reason(CPid2, killed). %%------------------------------------------------------------------------- -extra_return(doc) -> - ["The start function provided to start a child may " - "return {ok, Pid} or {ok, Pid, Info}, if it returns " - "the later check that the supervisor ignores the Info, " - "and includes it unchanged in return from start_child/2 " - "and restart_child/2"]; -extra_return(suite) -> []; - +%% The start function provided to start a child may return {ok, Pid} +%% or {ok, Pid, Info}, if it returns the latter check that the +%% supervisor ignores the Info, and includes it unchanged in return +%% from start_child/2 and restart_child/2. extra_return(Config) when is_list(Config) -> process_flag(trap_exit, true), Child = {child1, {supervisor_1, start_child, [extra_return]}, @@ -319,12 +365,10 @@ extra_return(Config) when is_list(Config) -> ok. %%------------------------------------------------------------------------- -child_adm(doc)-> - ["Test API functions start_child/2, terminate_child/2, delete_child/2 " - "restart_child/2, which_children/1, count_children/1. Only correct " - "childspecs are used, handling of incorrect childspecs is tested in " - "child_specs/1"]; -child_adm(suite) -> []; +%% Test API functions start_child/2, terminate_child/2, delete_child/2 +%% restart_child/2, which_children/1, count_children/1. Only correct +%% childspecs are used, handling of incorrect childspecs is tested in +%% child_specs/1. child_adm(Config) when is_list(Config) -> process_flag(trap_exit, true), Child = {child1, {supervisor_1, start_child, []}, permanent, 1000, @@ -388,11 +432,9 @@ child_adm(Config) when is_list(Config) -> = (catch supervisor:count_children(foo)), ok. %%------------------------------------------------------------------------- -child_adm_simple(doc) -> - ["The API functions terminate_child/2, delete_child/2 " - "restart_child/2 are not valid for a simple_one_for_one supervisor " - "check that the correct error message is returned."]; -child_adm_simple(suite) -> []; +%% The API functions terminate_child/2, delete_child/2 restart_child/2 +%% are not valid for a simple_one_for_one supervisor check that the +%% correct error message is returned. child_adm_simple(Config) when is_list(Config) -> Child = {child, {supervisor_1, start_child, []}, permanent, 1000, worker, []}, @@ -440,9 +482,7 @@ child_adm_simple(Config) when is_list(Config) -> ok. %%------------------------------------------------------------------------- -child_specs(doc) -> - ["Tests child specs, invalid formats should be rejected."]; -child_specs(suite) -> []; +%% Tests child specs, invalid formats should be rejected. child_specs(Config) when is_list(Config) -> process_flag(trap_exit, true), {ok, _Pid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), @@ -453,9 +493,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 +503,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 +512,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,21 +521,19 @@ 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. %%------------------------------------------------------------------------- -permanent_normal(doc) -> - ["A permanent child should always be restarted"]; -permanent_normal(suite) -> []; +%% A permanent child should always be restarted. permanent_normal(Config) when is_list(Config) -> {ok, SupPid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), Child1 = {child1, {supervisor_1, start_child, []}, permanent, 1000, @@ -516,10 +553,8 @@ permanent_normal(Config) when is_list(Config) -> [1,1,0,1] = get_child_counts(sup_test). %%------------------------------------------------------------------------- -transient_normal(doc) -> - ["A transient child should not be restarted if it exits with " - "reason normal"]; -transient_normal(suite) -> []; +%% A transient child should not be restarted if it exits with reason +%% normal. transient_normal(Config) when is_list(Config) -> {ok, SupPid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), Child1 = {child1, {supervisor_1, start_child, []}, transient, 1000, @@ -533,9 +568,7 @@ transient_normal(Config) when is_list(Config) -> [1,0,0,1] = get_child_counts(sup_test). %%------------------------------------------------------------------------- -temporary_normal(doc) -> - ["A temporary process should never be restarted"]; -temporary_normal(suite) -> []; +%% A temporary process should never be restarted. temporary_normal(Config) when is_list(Config) -> {ok, SupPid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), Child1 = {child1, {supervisor_1, start_child, []}, temporary, 1000, @@ -549,9 +582,82 @@ temporary_normal(Config) when is_list(Config) -> [0,0,0,0] = get_child_counts(sup_test). %%------------------------------------------------------------------------- -permanent_abnormal(doc) -> - ["A permanent child should always be restarted"]; -permanent_abnormal(suite) -> []; +%% A permanent child should always be restarted. +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). + +%%------------------------------------------------------------------------- +%% A transient child should not be restarted if it exits with reason +%% shutdown or {shutdown,Term}. +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). + +%%------------------------------------------------------------------------- +%% A temporary process should never be restarted. +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). + +%%------------------------------------------------------------------------- +%% A permanent child should always be restarted. permanent_abnormal(Config) when is_list(Config) -> {ok, SupPid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), Child1 = {child1, {supervisor_1, start_child, []}, permanent, 1000, @@ -570,10 +676,7 @@ permanent_abnormal(Config) when is_list(Config) -> [1,1,0,1] = get_child_counts(sup_test). %%------------------------------------------------------------------------- -transient_abnormal(doc) -> - ["A transient child should be restarted if it exits with " - "reason abnormal"]; -transient_abnormal(suite) -> []; +%% A transient child should be restarted if it exits with reason abnormal. transient_abnormal(Config) when is_list(Config) -> {ok, SupPid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), Child1 = {child1, {supervisor_1, start_child, []}, transient, 1000, @@ -592,9 +695,7 @@ transient_abnormal(Config) when is_list(Config) -> [1,1,0,1] = get_child_counts(sup_test). %%------------------------------------------------------------------------- -temporary_abnormal(doc) -> - ["A temporary process should never be restarted"]; -temporary_abnormal(suite) -> []; +%% A temporary process should never be restarted. temporary_abnormal(Config) when is_list(Config) -> {ok, SupPid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), Child1 = {child1, {supervisor_1, start_child, []}, temporary, 1000, @@ -607,11 +708,9 @@ temporary_abnormal(Config) when is_list(Config) -> [0,0,0,0] = get_child_counts(sup_test). %%------------------------------------------------------------------------- -temporary_bystander(doc) -> - ["A temporary process killed as part of a rest_for_one or one_for_all " - "restart strategy should not be restarted given its args are not " - " saved. Otherwise the supervisor hits its limit and crashes."]; -temporary_bystander(suite) -> []; +%% A temporary process killed as part of a rest_for_one or one_for_all +%% restart strategy should not be restarted given its args are not +%% saved. Otherwise the supervisor hits its limit and crashes. temporary_bystander(_Config) -> Child1 = {child1, {supervisor_1, start_child, []}, permanent, 100, worker, []}, @@ -638,9 +737,7 @@ temporary_bystander(_Config) -> [{child1, _, _, _}] = supervisor:which_children(SupPid2). %%------------------------------------------------------------------------- -one_for_one(doc) -> - ["Test the one_for_one base case."]; -one_for_one(suite) -> []; +%% Test the one_for_one base case. one_for_one(Config) when is_list(Config) -> process_flag(trap_exit, true), Child1 = {child1, {supervisor_1, start_child, []}, permanent, 1000, @@ -670,9 +767,7 @@ one_for_one(Config) when is_list(Config) -> check_exit([SupPid]). %%------------------------------------------------------------------------- -one_for_one_escalation(doc) -> - ["Test restart escalation on a one_for_one supervisor."]; -one_for_one_escalation(suite) -> []; +%% Test restart escalation on a one_for_one supervisor. one_for_one_escalation(Config) when is_list(Config) -> process_flag(trap_exit, true), @@ -692,9 +787,7 @@ one_for_one_escalation(Config) when is_list(Config) -> %%------------------------------------------------------------------------- -one_for_all(doc) -> - ["Test the one_for_all base case."]; -one_for_all(suite) -> []; +%% Test the one_for_all base case. one_for_all(Config) when is_list(Config) -> process_flag(trap_exit, true), @@ -730,9 +823,7 @@ one_for_all(Config) when is_list(Config) -> %%------------------------------------------------------------------------- -one_for_all_escalation(doc) -> - ["Test restart escalation on a one_for_all supervisor."]; -one_for_all_escalation(suite) -> []; +%% Test restart escalation on a one_for_all supervisor. one_for_all_escalation(Config) when is_list(Config) -> process_flag(trap_exit, true), @@ -751,9 +842,7 @@ one_for_all_escalation(Config) when is_list(Config) -> %%------------------------------------------------------------------------- -simple_one_for_one(doc) -> - ["Test the simple_one_for_one base case."]; -simple_one_for_one(suite) -> []; +%% Test the simple_one_for_one base case. simple_one_for_one(Config) when is_list(Config) -> process_flag(trap_exit, true), Child = {child, {supervisor_1, start_child, []}, permanent, 1000, @@ -782,11 +871,39 @@ simple_one_for_one(Config) when is_list(Config) -> terminate(SupPid, Pid4, Id4, abnormal), check_exit([SupPid]). + +%%------------------------------------------------------------------------- +%% Test simple_one_for_one children shutdown accordingly to the +%% supervisor's shutdown strategy. +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 " - "who's start function return extra info."]; -simple_one_for_one_extra(suite) -> []; +%% Tests automatic restart of children who's start function return +%% extra info. simple_one_for_one_extra(Config) when is_list(Config) -> process_flag(trap_exit, true), Child = {child, {supervisor_1, start_child, [extra_info]}, @@ -811,9 +928,7 @@ simple_one_for_one_extra(Config) when is_list(Config) -> check_exit([SupPid]). %%------------------------------------------------------------------------- -simple_one_for_one_escalation(doc) -> - ["Test restart escalation on a simple_one_for_one supervisor."]; -simple_one_for_one_escalation(suite) -> []; +%% Test restart escalation on a simple_one_for_one supervisor. simple_one_for_one_escalation(Config) when is_list(Config) -> process_flag(trap_exit, true), Child = {child, {supervisor_1, start_child, []}, permanent, 1000, @@ -828,9 +943,7 @@ simple_one_for_one_escalation(Config) when is_list(Config) -> check_exit([SupPid, CPid2]). %%------------------------------------------------------------------------- -rest_for_one(doc) -> - ["Test the rest_for_one base case."]; -rest_for_one(suite) -> []; +%% Test the rest_for_one base case. rest_for_one(Config) when is_list(Config) -> process_flag(trap_exit, true), Child1 = {child1, {supervisor_1, start_child, []}, permanent, 1000, @@ -878,9 +991,7 @@ rest_for_one(Config) when is_list(Config) -> check_exit([SupPid]). %%------------------------------------------------------------------------- -rest_for_one_escalation(doc) -> - ["Test restart escalation on a rest_for_one supervisor."]; -rest_for_one_escalation(suite) -> []; +%% Test restart escalation on a rest_for_one supervisor. rest_for_one_escalation(Config) when is_list(Config) -> process_flag(trap_exit, true), Child1 = {child1, {supervisor_1, start_child, []}, permanent, 1000, @@ -897,11 +1008,8 @@ rest_for_one_escalation(Config) when is_list(Config) -> check_exit([CPid2, SupPid]). %%------------------------------------------------------------------------- -child_unlink(doc)-> - ["Test that the supervisor does not hang forever if " - "the child unliks and then is terminated by the supervisor."]; -child_unlink(suite) -> - []; +%% Test that the supervisor does not hang forever if the child unliks +%% and then is terminated by the supervisor. child_unlink(Config) when is_list(Config) -> {ok, SupPid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), @@ -926,10 +1034,7 @@ child_unlink(Config) when is_list(Config) -> test_server:fail(supervisor_hangs) end. %%------------------------------------------------------------------------- -tree(doc) -> - ["Test a basic supervison tree."]; -tree(suite) -> - []; +%% Test a basic supervison tree. tree(Config) when is_list(Config) -> process_flag(trap_exit, true), @@ -1005,11 +1110,9 @@ tree(Config) when is_list(Config) -> [] = supervisor:which_children(NewSup2), [0,0,0,0] = get_child_counts(NewSup2). + %%------------------------------------------------------------------------- -count_children_memory(doc) -> - ["Test that count_children does not eat memory."]; -count_children_memory(suite) -> - []; +%% Test that count_children does not eat memory. count_children_memory(Config) when is_list(Config) -> process_flag(trap_exit, true), Child = {child, {supervisor_1, start_child, []}, temporary, 1000, @@ -1018,25 +1121,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, @@ -1051,24 +1154,25 @@ count_children_memory(Config) when is_list(Config) -> case (Size5 =< Size4) of true -> ok; false -> - test_server:fail({count_children, used_more_memory}) + test_server:fail({count_children, used_more_memory,Size4,Size5}) end, case Size7 =< Size6 of true -> ok; false -> - test_server:fail({count_children, used_more_memory}) + test_server:fail({count_children, used_more_memory,Size6,Size7}) end, [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 " - "save start parameters, as it potentially can " - "take up a huge amount of memory for no purpose."]; -do_not_save_start_parameters_for_temporary_children(suite) -> - []; +%% Temporary children shall not be restarted so they should not save +%% start parameters, as it potentially can take up a huge amount of +%% memory for no purpose. do_not_save_start_parameters_for_temporary_children(Config) when is_list(Config) -> process_flag(trap_exit, true), dont_save_start_parameters_for_temporary_children(one_for_all), @@ -1090,11 +1194,8 @@ child_spec({Name, MFA, RestartType, Shutdown, Type, Modules}, N) -> {NewName, MFA, RestartType, Shutdown, Type, Modules}. %%------------------------------------------------------------------------- -do_not_save_child_specs_for_temporary_children(doc) -> - ["Temporary children shall not be restarted so supervisors should " - "not save their spec when they terminate"]; -do_not_save_child_specs_for_temporary_children(suite) -> - []; +%% Temporary children shall not be restarted so supervisors should not +%% save their spec when they terminate. do_not_save_child_specs_for_temporary_children(Config) when is_list(Config) -> process_flag(trap_exit, true), dont_save_child_specs_for_temporary_children(one_for_all, kill), @@ -1243,13 +1344,18 @@ simple_one_for_one_scale_many_temporary_children(_Config) -> end || _<- lists:seq(1,10000)], {T2,done} = timer:tc(?MODULE,terminate_all_children,[C2]), - Scaling = T2 div T1, - if Scaling > 20 -> - %% The scaling shoul be linear (i.e.10, really), but we - %% give some extra here to avoid failing the test - %% unecessarily. - ?t:fail({bad_scaling,Scaling}); + if T1 > 0 -> + Scaling = T2 div T1, + if Scaling > 20 -> + %% The scaling shoul be linear (i.e.10, really), but we + %% give some extra here to avoid failing the test + %% unecessarily. + ?t:fail({bad_scaling,Scaling}); + true -> + ok + end; true -> + %% Means T2 div T1 -> infinity ok end. @@ -1261,6 +1367,92 @@ terminate_all_children([]) -> done. +%%------------------------------------------------------------------------- +%% OTP-9212. Restart of global supervisor. +simple_global_supervisor(_Config) -> + kill_supervisor(), + kill_worker(), + exit_worker(), + restart_worker(), + ok. + +kill_supervisor() -> + {Top, Sup2_1, Server_1} = start9212(), + + %% Killing a supervisor isn't really supported, but try it anyway... + exit(Sup2_1, kill), + timer:sleep(200), + Sup2_2 = global:whereis_name(sup2), + Server_2 = global:whereis_name(server), + true = is_pid(Sup2_2), + true = is_pid(Server_2), + true = Sup2_1 =/= Sup2_2, + true = Server_1 =/= Server_2, + + stop9212(Top). + +handle_info({fail, With, After}, _State) -> + timer:sleep(After), + erlang:error(With). + +kill_worker() -> + {Top, _Sup2, Server_1} = start9212(), + exit(Server_1, kill), + timer:sleep(200), + Server_2 = global:whereis_name(server), + true = is_pid(Server_2), + true = Server_1 =/= Server_2, + stop9212(Top). + +exit_worker() -> + %% Very much the same as kill_worker(). + {Top, _Sup2, Server_1} = start9212(), + Server_1 ! {fail, normal, 0}, + timer:sleep(200), + Server_2 = global:whereis_name(server), + true = is_pid(Server_2), + true = Server_1 =/= Server_2, + stop9212(Top). + +restart_worker() -> + {Top, _Sup2, Server_1} = start9212(), + ok = supervisor:terminate_child({global, sup2}, child), + {ok, _Child} = supervisor:restart_child({global, sup2}, child), + Server_2 = global:whereis_name(server), + true = is_pid(Server_2), + true = Server_1 =/= Server_2, + stop9212(Top). + +start9212() -> + Middle = {middle,{?MODULE,middle9212,[]}, permanent,2000,supervisor,[]}, + InitResult = {ok, {{one_for_all,3,60}, [Middle]}}, + {ok, TopPid} = start_link(InitResult), + + Sup2 = global:whereis_name(sup2), + Server = global:whereis_name(server), + true = is_pid(Sup2), + true = is_pid(Server), + {TopPid, Sup2, Server}. + +stop9212(Top) -> + Old = process_flag(trap_exit, true), + exit(Top, kill), + timer:sleep(200), + undefined = global:whereis_name(sup2), + undefined = global:whereis_name(server), + check_exit([Top]), + _ = process_flag(trap_exit, Old), + ok. + +middle9212() -> + Child = {child, {?MODULE,gen_server9212,[]},permanent, 2000, worker, []}, + InitResult = {ok, {{one_for_all,3,60}, [Child]}}, + supervisor:start_link({global,sup2}, ?MODULE, InitResult). + +gen_server9212() -> + InitResult = {ok, []}, + gen_server:start_link({global,server}, ?MODULE, InitResult, []). + %%------------------------------------------------------------------------- terminate(Pid, Reason) when Reason =/= supervisor -> @@ -1282,6 +1474,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/supervisor_bridge_SUITE.erl b/lib/stdlib/test/supervisor_bridge_SUITE.erl index c4d696564d..b3056ff41a 100644 --- a/lib/stdlib/test/supervisor_bridge_SUITE.erl +++ b/lib/stdlib/test/supervisor_bridge_SUITE.erl @@ -19,8 +19,9 @@ -module(supervisor_bridge_SUITE). -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, init_per_group/2,end_per_group/2,starting/1, - mini_terminate/1,mini_die/1,badstart/1]). --export([client/1,init/1,internal_loop_init/1,terminate/2]). + mini_terminate/1,mini_die/1,badstart/1, + simple_global_supervisor/1]). +-export([client/1,init/1,internal_loop_init/1,terminate/2,server9212/0]). -include_lib("test_server/include/test_server.hrl"). -define(bridge_name,supervisor_bridge_SUITE_server). @@ -31,7 +32,7 @@ suite() -> [{ct_hooks,[ts_install_cth]}]. all() -> - [starting, mini_terminate, mini_die, badstart]. + [starting, mini_terminate, mini_die, badstart, simple_global_supervisor]. groups() -> []. @@ -138,7 +139,9 @@ init(3) -> receive {InternalPid,init_done} -> {ok,InternalPid,self()} - end. + end; +init({4,Result}) -> + Result. internal_loop_init(Parent) -> register(?work_bridge_name, self()), @@ -160,7 +163,9 @@ terminate(Reason,{Parent,Worker}) -> io:format("Terminating bridge...\n"), exit(Worker,kill), Parent ! {dying,Reason}, - anything. + anything; +terminate(_Reason, _State) -> + any. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% @@ -197,3 +202,30 @@ badstart(Config) when is_list(Config) -> ok. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +%% OTP-9212. Restart of global supervisor. + +simple_global_supervisor(suite) -> []; +simple_global_supervisor(doc) -> "Globally registered supervisor."; +simple_global_supervisor(Config) when is_list(Config) -> + ?line Dog = test_server:timetrap({seconds,10}), + + Child = {child, {?MODULE,server9212,[]}, permanent, 2000, worker, []}, + InitResult = {ok, {{one_for_all,3,60}, [Child]}}, + {ok, Sup} = + supervisor:start_link({local,bridge9212}, ?MODULE, {4,InitResult}), + + BN_1 = global:whereis_name(?bridge_name), + ?line exit(BN_1, kill), + timer:sleep(200), + BN_2 = global:whereis_name(?bridge_name), + ?line true = is_pid(BN_2), + ?line true = BN_1 =/= BN_2, + + ?line process_flag(trap_exit, true), + exit(Sup, kill), + ?line receive {'EXIT', Sup, killed} -> ok end, + ?line test_server:timetrap_cancel(Dog), + ok. + +server9212() -> + supervisor_bridge:start_link({global,?bridge_name}, ?MODULE, 3). diff --git a/lib/stdlib/test/tar_SUITE.erl b/lib/stdlib/test/tar_SUITE.erl index 48f58cd05d..5bc34e35af 100644 --- a/lib/stdlib/test/tar_SUITE.erl +++ b/lib/stdlib/test/tar_SUITE.erl @@ -283,17 +283,16 @@ long_names(doc) -> long_names(Config) when is_list(Config) -> ?line DataDir = ?config(data_dir, Config), ?line Long = filename:join(DataDir, "long_names.tar"), + run_in_short_tempdir(Config, + fun() -> do_long_names(Long) end). +do_long_names(Long) -> %% Try table/2 and extract/2. ?line case erl_tar:table(Long, [verbose]) of {ok,List} when is_list(List) -> ?line io:format("~p\n", [List]) end, - - %% To avoid getting too long paths for Windows to handle, extract into - %% the current directory (which is the test_server directory). Its path - %% is quite a bit shorter than the path to priv_dir. ?line {ok,Cwd} = file:get_cwd(), ?line ok = erl_tar:extract(Long), ?line Base = filename:join([Cwd, "original_software", "written_by", @@ -312,17 +311,16 @@ long_names(Config) when is_list(Config) -> ?line "Here"++_ = binary_to_list(First), ?line "And"++_ = binary_to_list(Second), - %% Clean up. - ?line delete_files([filename:join(Cwd, "original_software"),EmptyDir]), - ok. create_long_names(doc) -> ["Creates a tar file from a deep directory structure (filenames are ", "longer than 100 characters)."]; create_long_names(Config) when is_list(Config) -> - ?line PrivDir = ?config(priv_dir, Config), - ?line ok = file:set_cwd(PrivDir), + run_in_short_tempdir(Config, fun create_long_names/0). + +create_long_names() -> + ?line {ok,Dir} = file:get_cwd(), Dirs = ["aslfjkshjkhliuf", "asdhjfehnbfsky", "sahajfskdfhsz", @@ -334,7 +332,7 @@ create_long_names(Config) when is_list(Config) -> ?line AFile = filename:join(DeepDir, "a_file"), ?line Hello = "hello, world\n", ?line ok = file:write_file(AFile, Hello), - ?line TarName = filename:join(PrivDir, "my_tar_with_long_names.tar"), + ?line TarName = filename:join(Dir, "my_tar_with_long_names.tar"), ?line ok = erl_tar:create(TarName, [AFile]), %% Print contents. @@ -347,9 +345,6 @@ create_long_names(Config) when is_list(Config) -> ?line {ok, Bin} = file:read_file(filename:join(ExtractDir, AFile)), ?line Hello = binary_to_list(Bin), - %% Clean up. - ?line delete_files([ExtractDir,TarName,hd(Dirs)]), - ok. make_dirs([Dir|Rest], []) -> @@ -538,7 +533,7 @@ symlinks(Config) when is_list(Config) -> ?line ok = file:make_dir(Dir), ?line ABadSymlink = filename:join(Dir, "bad_symlink"), ?line PointsTo = "/a/definitely/non_existing/path", - ?line Res = case file:make_symlink("/a/definitely/non_existing/path", ABadSymlink) of + ?line Res = case make_symlink("/a/definitely/non_existing/path", ABadSymlink) of {error, enotsup} -> {skip, "Symbolic links not supported on this platform"}; ok -> @@ -549,7 +544,30 @@ symlinks(Config) when is_list(Config) -> %% Clean up. ?line delete_files([Dir]), Res. - + +make_symlink(Path, Link) -> + case os:type() of + {win32,_} -> + %% Symlinks on Windows have two problems: + %% 1) file:read_link_info/1 cannot read out the target + %% of the symlink if the target does not exist. + %% That is possible (but not easy) to fix in the + %% efile driver. + %% + %% 2) Symlinks to files and directories are different + %% creatures. If the target is not existing, the + %% symlink will be created to be of the file-pointing + %% type. That can be partially worked around in erl_tar + %% by creating all symlinks when the end of the tar + %% file has been reached. + %% + %% But for now, pretend that there are no symlinks on + %% Windows. + {error, enotsup}; + _ -> + file:make_symlink(Path, Link) + end. + symlinks(Dir, BadSymlink, PointsTo) -> ?line Tar = filename:join(Dir, "symlink.tar"), ?line DerefTar = filename:join(Dir, "dereference.tar"), @@ -734,3 +752,42 @@ delete_files([Item|Rest]) -> end, delete_files(Rest). +%% Move to a temporary directory with as short name as possible and +%% execute Fun. Remove the directory and any files in it afterwards. +%% This is necessary because pathnames on Windows may be limited to +%% 260 characters. +run_in_short_tempdir(Config, Fun) -> + {ok,Cwd} = file:get_cwd(), + PrivDir0 = ?config(priv_dir, Config), + + %% Normalize name to make sure that there is no slash at the end. + PrivDir = filename:absname(PrivDir0), + + %% We need a base directory with a much shorter pathname than + %% priv_dir. We KNOW that priv_dir is located four levels below + %% the directory that common_test puts the ct_run.* directories + %% in. That fact is not documented, but a usually reliable source + %% assured me that the directory structure is unlikely to change + %% in future versions of common_test because of backwards + %% compatibility (tools developed by users of common_test depend + %% on the current directory layout). + Base = lists:foldl(fun(_, D) -> + filename:dirname(D) + end, PrivDir, [1,2,3,4]), + + Dir = make_temp_dir(Base, 0), + ok = file:set_cwd(Dir), + io:format("Running test in ~s\n", [Dir]), + try + Fun() + after + file:set_cwd(Cwd), + delete_files([Dir]) + end. + +make_temp_dir(Base, I) -> + Name = filename:join(Base, integer_to_list(I, 36)), + case file:make_dir(Name) of + ok -> Name; + {error,eexist} -> make_temp_dir(Base, I+1) + end. 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)], |