aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r--lib/stdlib/test/erl_eval_SUITE.erl25
-rw-r--r--lib/stdlib/test/erl_expand_records_SUITE.erl12
-rw-r--r--lib/stdlib/test/erl_lint_SUITE.erl30
-rw-r--r--lib/stdlib/test/ets_SUITE.erl34
-rw-r--r--lib/stdlib/test/filename_SUITE.erl16
-rw-r--r--lib/stdlib/test/ms_transform_SUITE.erl5
-rw-r--r--lib/stdlib/test/qlc_SUITE.erl113
-rw-r--r--lib/stdlib/test/qlc_SUITE_data/join_info_compat.erl1771
-rw-r--r--lib/stdlib/test/re_SUITE.erl54
-rw-r--r--lib/stdlib/test/shell_SUITE.erl29
-rw-r--r--lib/stdlib/test/sofs_SUITE.erl64
-rw-r--r--lib/stdlib/test/supervisor_1.erl2
-rw-r--r--lib/stdlib/test/supervisor_2.erl2
-rw-r--r--lib/stdlib/test/supervisor_SUITE.erl290
-rw-r--r--lib/stdlib/test/tar_SUITE.erl31
15 files changed, 2152 insertions, 326 deletions
diff --git a/lib/stdlib/test/erl_eval_SUITE.erl b/lib/stdlib/test/erl_eval_SUITE.erl
index 369d8b224e..ca2f18a05a 100644
--- a/lib/stdlib/test/erl_eval_SUITE.erl
+++ b/lib/stdlib/test/erl_eval_SUITE.erl
@@ -1167,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/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl
index 0e8849b5b3..59532b65a0 100644
--- a/lib/stdlib/test/ets_SUITE.erl
+++ b/lib/stdlib/test/ets_SUITE.erl
@@ -72,9 +72,10 @@
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]).
+-export([init_per_testcase/2, end_per_testcase/2]).
%% Convenience for manual testing
-export([random_test/0]).
@@ -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() ->
@@ -2385,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"];
@@ -5432,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,
@@ -5645,7 +5665,8 @@ spawn_logger(Procs) ->
true -> exit(Proc, kill);
_ -> ok
end,
- erlang:display(process_info(Proc)),
+ erlang:display({"Waiting for 'DOWN' from", Proc,
+ process_info(Proc), pid_status(Proc)}),
receive
{'DOWN', Mon, _, _, _} ->
ok
@@ -5656,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;
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/ms_transform_SUITE.erl b/lib/stdlib/test/ms_transform_SUITE.erl
index c9688354b1..a17307b07b 100644
--- a/lib/stdlib/test/ms_transform_SUITE.erl
+++ b/lib/stdlib/test/ms_transform_SUITE.erl
@@ -455,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},
@@ -490,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'},
@@ -502,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)"
@@ -530,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},
diff --git a/lib/stdlib/test/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl
index 9be547c690..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").
@@ -7402,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) ->
"";
@@ -8130,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 3b2e637c84..d6d946a28f 100644
--- a/lib/stdlib/test/re_SUITE.erl
+++ b/lib/stdlib/test/re_SUITE.erl
@@ -445,9 +445,17 @@ 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)),
@@ -455,14 +463,14 @@ error_handling(Config) when is_list(Config) ->
% 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,_} | _]}} =
+ {?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,_} | _]}} =
+ {?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):
@@ -473,88 +481,88 @@ error_handling(Config) when is_list(Config) ->
[<<"apa">>,
{re_pattern,1,0,_},
[global,unicode]],_},
- {?MODULE,error_handling,1,_} | _]}} =
+ {?MODULE,error_handling,0,_} | _]}} =
(catch re:run(<<"apa">>,RE,[global,unicode])),
?line {'EXIT',{badarg,[{re,run,
["apa",
{re_pattern,1,0,_},
[global,unicode]],_},
- {?MODULE,error_handling,1,_} | _]}} =
+ {?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,_} | _]}} =
+ {?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,_} | _]}} =
+ {?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,_} | _]}} =
+ {?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,_} | _]}} =
+ {?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,_} | _]}} =
+ {?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,_} | _]}} =
+ {?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,_} | _]}} =
+ {?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,_} | _]}} =
+ {?MODULE,error_handling,0,_} | _]}} =
(catch re:split("apa","p",[global])),
?line {'EXIT',{badarg,[{re,split,["apa","p",[{capture,all}]],_},
- {?MODULE,error_handling,1,_} | _]}} =
+ {?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,_} | _]}} =
+ {?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,_} | _]}} =
+ {?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,_} | _]}} =
+ {?MODULE,error_handling,0,_} | _]}} =
(catch re:split("apa",{1,2,3,4},[])),
?line {'EXIT',{badarg,[{re,split,
["apa",
RE,
[unicode]],_},
- {?MODULE,error_handling,1,_} | _]}} =
+ {?MODULE,error_handling,0,_} | _]}} =
(catch re:split("apa",RE,[unicode])),
?line {'EXIT',{badarg,[{re,split,
["apa",
RE,
[{return,banana}]],_},
- {?MODULE,error_handling,1,_} | _]}} =
+ {?MODULE,error_handling,0,_} | _]}} =
(catch re:split("apa",RE,[{return,banana}])),
?line {'EXIT',{badarg,[{re,split,
["apa",
RE,
[banana]],_},
- {?MODULE,error_handling,1,_} | _]}} =
+ {?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
@@ -562,7 +570,7 @@ error_handling(Config) when is_list(Config) ->
["apa",
"(p",
[banana]],_},
- {?MODULE,error_handling,1,_} | _]}} =
+ {?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 b6019b86f0..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," =
- 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) (lists.erl, line " ++ _ =
- comm_err(<<"lists:reverse(34).">>),
?line "exception error: no true branch found when evaluating an if expression" =
comm_err(<<"if length([a,b]) > 17 -> a end.">>),
?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 73b282149a..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/supervisor_1.erl b/lib/stdlib/test/supervisor_1.erl
index f819594c46..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
diff --git a/lib/stdlib/test/supervisor_2.erl b/lib/stdlib/test/supervisor_2.erl
index 67aacf5a9c..60d037f4e0 100644
--- a/lib/stdlib/test/supervisor_2.erl
+++ b/lib/stdlib/test/supervisor_2.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
diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl
index d3d140abbc..71b76c093f 100644
--- a/lib/stdlib/test/supervisor_SUITE.erl
+++ b/lib/stdlib/test/supervisor_SUITE.erl
@@ -34,8 +34,10 @@
%% 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]).
@@ -85,8 +87,10 @@ all() ->
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]},
@@ -158,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}, []}}),
@@ -197,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 allowed "
- "for children of type supervisor _AND_ worker"];
-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}, []}}),
@@ -238,11 +281,7 @@ sup_stop_infinity(Config) when is_list(Config) ->
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}, []}}),
@@ -264,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}, []}}),
@@ -286,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]},
@@ -333,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,
@@ -402,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, []},
@@ -454,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}, []}}),
@@ -507,9 +533,7 @@ child_specs(Config) when is_list(Config) ->
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,
@@ -529,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,
@@ -546,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,
@@ -562,9 +582,7 @@ temporary_normal(Config) when is_list(Config) ->
[0,0,0,0] = get_child_counts(sup_test).
%%-------------------------------------------------------------------------
-permanent_shutdown(doc) ->
- ["A permanent child should always be restarted"];
-permanent_shutdown(suite) -> [];
+%% 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,
@@ -596,10 +614,8 @@ permanent_shutdown(Config) when is_list(Config) ->
[1,1,0,1] = get_child_counts(sup_test).
%%-------------------------------------------------------------------------
-transient_shutdown(doc) ->
- ["A transient child should not be restarted if it exits with "
- "reason shutdown or {shutdown,Term}"];
-transient_shutdown(suite) -> [];
+%% 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,
@@ -620,9 +636,7 @@ transient_shutdown(Config) when is_list(Config) ->
[1,0,0,1] = get_child_counts(sup_test).
%%-------------------------------------------------------------------------
-temporary_shutdown(doc) ->
- ["A temporary process should never be restarted"];
-temporary_shutdown(suite) -> [];
+%% 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,
@@ -643,9 +657,7 @@ temporary_shutdown(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_abnormal(Config) when is_list(Config) ->
{ok, SupPid} = start_link({ok, {{one_for_one, 2, 3600}, []}}),
Child1 = {child1, {supervisor_1, start_child, []}, permanent, 1000,
@@ -664,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,
@@ -686,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,
@@ -701,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, []},
@@ -732,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,
@@ -764,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),
@@ -786,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),
@@ -824,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),
@@ -845,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,
@@ -878,10 +873,8 @@ simple_one_for_one(Config) when is_list(Config) ->
%%-------------------------------------------------------------------------
-simple_one_for_one_shutdown(doc) ->
- ["Test simple_one_for_one children shutdown accordingly to the "
- "supervisor's shutdown strategy."];
-simple_one_for_one_shutdown(suite) -> [];
+%% 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,
@@ -909,10 +902,8 @@ simple_one_for_one_shutdown(Config) when is_list(Config) ->
%%-------------------------------------------------------------------------
-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]},
@@ -937,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,
@@ -954,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,
@@ -1004,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,
@@ -1023,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}, []}}),
@@ -1052,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),
@@ -1131,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,
@@ -1177,12 +1154,12 @@ 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],
@@ -1193,12 +1170,9 @@ proc_memory() ->
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),
@@ -1220,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),
@@ -1373,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.
diff --git a/lib/stdlib/test/tar_SUITE.erl b/lib/stdlib/test/tar_SUITE.erl
index 9ad3936928..5bc34e35af 100644
--- a/lib/stdlib/test/tar_SUITE.erl
+++ b/lib/stdlib/test/tar_SUITE.erl
@@ -533,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 ->
@@ -544,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"),
@@ -743,9 +766,9 @@ run_in_short_tempdir(Config, Fun) ->
%% 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 an usually reliable source
+ %% 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 backward
+ %% 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) ->