diff options
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r-- | lib/stdlib/test/binary_module_SUITE.erl | 18 | ||||
-rw-r--r-- | lib/stdlib/test/filename_SUITE.erl | 16 | ||||
-rw-r--r-- | lib/stdlib/test/qlc_SUITE.erl | 120 | ||||
-rw-r--r-- | lib/stdlib/test/qlc_SUITE_data/join_info_compat.erl | 1771 | ||||
-rw-r--r-- | lib/stdlib/test/stdlib_SUITE.erl | 63 | ||||
-rw-r--r-- | lib/stdlib/test/tar_SUITE.erl | 31 |
6 files changed, 1924 insertions, 95 deletions
diff --git a/lib/stdlib/test/binary_module_SUITE.erl b/lib/stdlib/test/binary_module_SUITE.erl index 8fb63f33bd..bac59a3107 100644 --- a/lib/stdlib/test/binary_module_SUITE.erl +++ b/lib/stdlib/test/binary_module_SUITE.erl @@ -20,7 +20,7 @@ -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, init_per_group/2,end_per_group/2, - interesting/1,random_ref_comp/1,random_ref_sr_comp/1, + interesting/1,scope_return/1,random_ref_comp/1,random_ref_sr_comp/1, random_ref_fla_comp/1,parts/1, bin_to_list/1, list_to_bin/1, copy/1, referenced/1,guard/1,encode_decode/1,badargs/1,longest_common_trap/1]). @@ -67,7 +67,7 @@ end_per_testcase(_Case, Config) -> suite() -> [{ct_hooks,[ts_install_cth]}]. all() -> - [interesting, random_ref_fla_comp, random_ref_sr_comp, + [scope_return,interesting, random_ref_fla_comp, random_ref_sr_comp, random_ref_comp, parts, bin_to_list, list_to_bin, copy, referenced, guard, encode_decode, badargs, longest_common_trap]. @@ -379,6 +379,20 @@ subj() -> Subject. +scope_return(doc) -> + ["Test correct return values for scopes (OTP-9701)."]; +scope_return(Config) when is_list(Config) -> + N=10000, + Bin=binary:copy(<<"a">>,N), + scope_loop(Bin,0,N). + +scope_loop(_,N,N) -> + ok; +scope_loop(Bin,N,M) -> + ?line {N,1} = binary:match(Bin,<<"a">>,[{scope,{N,1}}]), + ?line {N,1} = binary:match(Bin,[<<"a">>,<<"b">>],[{scope,{N,1}}]), + scope_loop(Bin,N+1,M). + interesting(doc) -> ["Try some interesting patterns"]; interesting(Config) when is_list(Config) -> diff --git a/lib/stdlib/test/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/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl index 8a9d8f7883..50a76cdfb5 100644 --- a/lib/stdlib/test/qlc_SUITE.erl +++ b/lib/stdlib/test/qlc_SUITE.erl @@ -20,7 +20,6 @@ %%% Purpose:Test Suite for the 'qlc' module. %%%----------------------------------------------------------------- -module(qlc_SUITE). --compile(r12). -define(QLC, qlc). -define(QLCs, "qlc"). @@ -6118,6 +6117,7 @@ otp_6964(Config) when is_list(Config) -> qlc:e(Q, [{max_list_size,64*1024},{tmpdir_usage,Use}]) end, D = erlang:system_flag(backtrace_depth, 0), + try 20000 = length(F(allowed)), ErrReply = F(not_allowed), {error, qlc, {tmpdir_usage,joining}} = ErrReply, @@ -6129,8 +6129,10 @@ otp_6964(Config) when is_list(Config) -> 20000 = length(F(info_msg)), {info, joining} = qlc_SUITE:read_error_logger(), 20000 = length(F(error_msg)), - {error, joining} = qlc_SUITE:read_error_logger(), - _ = erlang:system_flag(backtrace_depth, D), + {error, joining} = qlc_SUITE:read_error_logger() + after + _ = erlang:system_flag(backtrace_depth, D) + end, qlc_SUITE:uninstall_error_logger()">>], ?line run(Config, T1), @@ -7399,70 +7401,37 @@ backward(doc) -> "OTP-6674. Join info and extra constants."; backward(suite) -> []; backward(Config) when is_list(Config) -> - case try_old_join_info(Config) of - ok -> - ok; - Reply -> - Reply - end. - --ifdef(debug). -try_old_join_info(_Config) -> + try_old_join_info(Config), ok. --else. + try_old_join_info(Config) -> - case ?t:is_release_available("r12b") of - true -> - %% Check join info for handlers of extra constants. Start R12B-0. - ?line {ok, R12} = start_node_rel(r12, r12b, slave), - File = filename("handle.erl", Config), - ?line file:write_file(File, - <<"-module(handle).\n" - "-export([create_handle/0, lookup_handle/0]).\n" - "-include_lib(\"stdlib/include/qlc.hrl\").\n" - "create_handle() ->\n" - " H1 = qlc:sort([{192.0,1,a},{192.0,2,b},{192.0,3,c}]),\n" - " qlc:q([{X, Y} || {B,X,_} <- H1,\n" - " B =:= 192.0,\n" - " {Y} <- [{0},{1},{2}],\n" - " X == Y]).\n", - "\n", - "lookup_handle() ->\n" - " E = qlc_SUITE:table([{1,a},{2,b},{3,c}], 1, [1]),\n" - " qlc:q([{X, Y} || {X,_} <- E,\n" - " {Y} <- [{0},{1},{2}],\n" - " X =:= Y]).\n">>), - ?line {ok, handle} = rpc:call(R12, compile, file, - [File, [{outdir,?privdir}]]), - ?line {module, handle} = rpc:call(R12, code, load_abs, - [filename:rootname(File)]), - ?line H = rpc:call(R12, handle, create_handle, []), - ?line {module, handle} = code:load_abs(filename:rootname(File)), - ?line {block,0, - [{match,_,_, - {call,_,_, - [{lc,_,_, - [_, - {op,_,'=:=', - {float,_,192.0}, - {call,_,{atom,_,element},[{integer,_,1},_]}}]}]}}, - _,_, - {call,_,_, - [{lc,_,_, - [_, - {op,_,'=:=',{var,_,'B'},{float,_,192.0}}, - {op,_,'==',{var,_,'X'},{var,_,'Y'}}]}]}]} - = qlc:info(H,{format,abstract_code}), - ?line [{1,1},{2,2}] = qlc:e(H), - ?line H2 = rpc:call(R12, handle, lookup_handle, []), - ?line {qlc,_,[{generate,_,{qlc,_,_,[{join,lookup}]}},_],[]} = - qlc:info(H2, {format,debug}), - ?line [{1,1},{2,2}] = qlc:e(H2), - stop_node(R12); - false -> - ?line {skipped, "No support for old node"} - end. --endif. + %% Check join info for handlers of extra constants. + File = filename:join(?datadir, "join_info_compat.erl"), + M = join_info_compat, + {ok, M} = compile:file(File, [{outdir, ?datadir}]), + {module, M} = code:load_abs(filename:rootname(File)), + H = M:create_handle(), + {block,0, + [{match,_,_, + {call,_,_, + [{lc,_,_, + [_, + {op,_,'=:=', + {float,_,192.0}, + {call,_,{atom,_,element},[{integer,_,1},_]}}]}]}}, + _,_, + {call,_,_, + [{lc,_,_, + [_, + {op,_,'=:=',{var,_,'B'},{float,_,192.0}}, + {op,_,'==',{var,_,'X'},{var,_,'Y'}}]}]}]} + = qlc:info(H,{format,abstract_code}), + [{1,1},{2,2}] = qlc:e(H), + + H2 = M:lookup_handle(), + {qlc,_,[{generate,_,{qlc,_,_,[{join,lookup}]}},_],[]} = + qlc:info(H2, {format,debug}), + [{1,1},{2,2}] = qlc:e(H2). forward(doc) -> ""; @@ -8127,27 +8096,6 @@ fail(Source) -> %% Copied from global_SUITE.erl. -start_node_rel(Name, Rel, How) -> - {Release, Compat} = case Rel of - this -> - {[this], "+R8"}; - Rel when is_atom(Rel) -> - {[{release, atom_to_list(Rel)}], ""}; - RelList -> - {RelList, ""} - end, - ?line Pa = filename:dirname(code:which(?MODULE)), - ?line Res = test_server:start_node(Name, How, - [{args, - Compat ++ - " -kernel net_setuptime 100 " - " -pa " ++ Pa}, - {erl, Release}]), - Res. - -stop_node(Node) -> - ?line ?t:stop_node(Node). - install_error_logger() -> error_logger:add_report_handler(?MODULE, self()). diff --git a/lib/stdlib/test/qlc_SUITE_data/join_info_compat.erl b/lib/stdlib/test/qlc_SUITE_data/join_info_compat.erl new file mode 100644 index 0000000000..e0db132c47 --- /dev/null +++ b/lib/stdlib/test/qlc_SUITE_data/join_info_compat.erl @@ -0,0 +1,1771 @@ +%% +%% %CopyrightBegin% +%% +%% Copyright Ericsson AB 2008-2011. All Rights Reserved. +%% +%% The contents of this file are subject to the Erlang Public License, +%% Version 1.1, (the "License"); you may not use this file except in +%% compliance with the License. You should have received a copy of the +%% Erlang Public License along with this software. If not, it can be +%% retrieved online at http://www.erlang.org/. +%% +%% Software distributed under the License is distributed on an "AS IS" +%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See +%% the License for the specific language governing rights and limitations +%% under the License. +%% +%% %CopyrightEnd% +%% +-module(join_info_compat). + +-compile(export_all). + +create_handle() -> + H1 = qlc:sort([{192.0,1,a},{192.0,2,b},{192.0,3,c}]), + qlc:q({qlc_lc, + % fun-info: {23,109048965,'-create_handle/0-fun-23-'} + fun() -> + {qlc_v1, + % fun-info: {2,105724313,'-create_handle/0-fun-2-'} + fun(S01_0_1, RL01_0_1, Go01_0_1) -> + Fun1_0_1 = + % fun-info: {1,131900588,'-create_handle/0-fun-1-'} + fun(0, RL1_0_1, _, _, _, _, _, _, _) + when is_list(RL1_0_1) -> + lists:reverse(RL1_0_1); + (0, _, _, _, _, _, _, _, _) -> + []; + (1, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_1_1, + B1, + X1) + when is_list(RL1_0_1) -> + Fun1_0_1(element(1, Go1_0_1), + [{X1,Y1}|RL1_0_1], + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_1_1, + B1, + X1); + (1, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_1_1, + B1, + X1) -> + [{X1,Y1}| + % fun-info: {0,27702789,'-create_handle/0-fun-0-'} + fun() -> + Fun1_0_1(element(1, + Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_1_1, + B1, + X1) + end]; + (2, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + _, + B1, + X1) -> + Fun1_0_1(3, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + element(4, Go1_0_1), + B1, + X1); + (3, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + [{B1,X1,_}|C1_0_1], + _, + _) -> + Fun1_0_1(element(3, Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_0_1, + B1, + X1); + (3, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + [_|C1_0_1], + _, + _) -> + Fun1_0_1(3, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_0_1, + [], + []); + (3, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + [], + _, + _) -> + Fun1_0_1(element(2, Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + [], + [], + []); + (3, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_1_1, + _, + _) -> + case C1_1_1() of + [{B1,X1,_}|C1_0_1] -> + Fun1_0_1(element(3, + Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_0_1, + B1, + X1); + [_|C1_0_1] -> + Fun1_0_1(3, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_0_1, + [], + []); + [] -> + Fun1_0_1(element(2, + Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + [], + [], + []); + E1_0_1 -> + E1_0_1 + end; + (4, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_1_1, + B1, + X1) -> + if + B1 =:= 192.0 -> + Fun1_0_1(element(6, + Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_1_1, + B1, + X1); + true -> + Fun1_0_1(element(5, + Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_1_1, + B1, + X1) + end; + (5, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + _, + Y1, + C1_1_1, + B1, + X1) -> + Fun1_0_1(6, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + element(9, Go1_0_1), + Y1, + C1_1_1, + B1, + X1); + (6, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + [{Y1}|C1_0_1], + _, + C1_1_1, + B1, + X1) -> + Fun1_0_1(element(8, Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_0_1, + Y1, + C1_1_1, + B1, + X1); + (6, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + [_|C1_0_1], + _, + C1_1_1, + B1, + X1) -> + Fun1_0_1(6, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_0_1, + [], + C1_1_1, + B1, + X1); + (6, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + [], + _, + C1_1_1, + B1, + X1) -> + Fun1_0_1(element(7, Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + [], + [], + C1_1_1, + B1, + X1); + (6, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + _, + C1_1_1, + B1, + X1) -> + case C1_3_1() of + [{Y1}|C1_0_1] -> + Fun1_0_1(element(8, + Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_0_1, + Y1, + C1_1_1, + B1, + X1); + [_|C1_0_1] -> + Fun1_0_1(6, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_0_1, + [], + C1_1_1, + B1, + X1); + [] -> + Fun1_0_1(element(7, + Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + [], + [], + C1_1_1, + B1, + X1); + E1_0_1 -> + E1_0_1 + end; + (7, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_1_1, + B1, + X1) -> + if + X1 == Y1 -> + Fun1_0_1(element(11, + Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_1_1, + B1, + X1); + true -> + Fun1_0_1(element(10, + Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_1_1, + B1, + X1) + end; + (8, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + _, + B1, + X1) -> + Fun1_0_1(9, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + element(14, Go1_0_1), + B1, + X1); + (9, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + _, + [[{B1,X1,_}|{Y1}]|C1_0_1], + _, + _) -> + Fun1_0_1(element(13, Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_0_1, + B1, + X1); + (9, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + _, + [_|C1_0_1], + _, + _) -> + Fun1_0_1(9, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + [], + C1_0_1, + [], + []); + (9, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + _, + [], + _, + _) -> + Fun1_0_1(element(12, Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + [], + [], + [], + []); + (9, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + _, + C1_1_1, + _, + _) -> + case C1_1_1() of + [[{B1,X1,_}|{Y1}]|C1_0_1] -> + Fun1_0_1(element(13, + Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + Y1, + C1_0_1, + B1, + X1); + [_|C1_0_1] -> + Fun1_0_1(9, + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + [], + C1_0_1, + [], + []); + [] -> + Fun1_0_1(element(12, + Go1_0_1), + RL1_0_1, + Fun1_0_1, + Go1_0_1, + C1_3_1, + [], + [], + [], + []); + E1_0_1 -> + E1_0_1 + end + end, + Fun1_0_1(S01_0_1, + RL01_0_1, + Fun1_0_1, + Go01_0_1, + [], + [], + [], + [], + []) + end, + % fun-info: {3,41816426,'-create_handle/0-fun-3-'} + fun() -> + {<<$\203:8/integer-unit:1-unsigned-big, + $P:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $.:8/integer-unit:1-unsigned-big, + $x:8/integer-unit:1-unsigned-big, + $\234:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $N:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $-:8/integer-unit:1-unsigned-big, + $):8/integer-unit:1-unsigned-big, + $-:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $I:8/integer-unit:1-unsigned-big, + $M:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $0:8/integer-unit:1-unsigned-big, + $\227:8/integer-unit:1-unsigned-big, + $%:8/integer-unit:1-unsigned-big, + $\026:8/integer-unit:1-unsigned-big, + $%:8/integer-unit:1-unsigned-big, + $r:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $0:8/integer-unit:1-unsigned-big, + $0:8/integer-unit:1-unsigned-big, + $F:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $":8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big>>, + <<$\203:8/integer-unit:1-unsigned-big, + $P:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $<:8/integer-unit:1-unsigned-big, + $x:8/integer-unit:1-unsigned-big, + $\234:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $N:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $-:8/integer-unit:1-unsigned-big, + $):8/integer-unit:1-unsigned-big, + $-:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $I:8/integer-unit:1-unsigned-big, + $M:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $0:8/integer-unit:1-unsigned-big, + $\227:8/integer-unit:1-unsigned-big, + $%:8/integer-unit:1-unsigned-big, + $\026:8/integer-unit:1-unsigned-big, + $%:8/integer-unit:1-unsigned-big, + $r:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $0:8/integer-unit:1-unsigned-big, + $0:8/integer-unit:1-unsigned-big, + $::8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $":8/integer-unit:1-unsigned-big, + $P:8/integer-unit:1-unsigned-big, + $x:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $Y:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $9:8/integer-unit:1-unsigned-big, + $\r:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big>>, + <<$\203:8/integer-unit:1-unsigned-big, + $P:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $I:8/integer-unit:1-unsigned-big, + $x:8/integer-unit:1-unsigned-big, + $\234:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $M:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $/:8/integer-unit:1-unsigned-big, + $H:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $N:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $\006:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $e:8/integer-unit:1-unsigned-big, + $\211:8/integer-unit:1-unsigned-big, + $E:8/integer-unit:1-unsigned-big, + $\s:8/integer-unit:1-unsigned-big, + $>:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\023:8/integer-unit:1-unsigned-big, + $\210:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\232:8/integer-unit:1-unsigned-big, + $\226:8/integer-unit:1-unsigned-big, + $\223:8/integer-unit:1-unsigned-big, + $\237:8/integer-unit:1-unsigned-big, + $X:8/integer-unit:1-unsigned-big, + $\222:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\235:8/integer-unit:1-unsigned-big, + $l:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $g:8/integer-unit:1-unsigned-big, + $i:8/integer-unit:1-unsigned-big, + $d:8/integer-unit:1-unsigned-big, + $\200:8/integer-unit:1-unsigned-big, + $\001:8/integer-unit:1-unsigned-big, + $R:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\r:8/integer-unit:1-unsigned-big, + $\214:8/integer-unit:1-unsigned-big, + $\030:8/integer-unit:1-unsigned-big, + $@:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $c:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\017:8/integer-unit:1-unsigned-big, + $=:8/integer-unit:1-unsigned-big>>, + <<$\203:8/integer-unit:1-unsigned-big, + $h:8/integer-unit:1-unsigned-big, + $\003:8/integer-unit:1-unsigned-big, + $d:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\005:8/integer-unit:1-unsigned-big, + $t:8/integer-unit:1-unsigned-big, + $u:8/integer-unit:1-unsigned-big, + $p:8/integer-unit:1-unsigned-big, + $l:8/integer-unit:1-unsigned-big, + $e:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $\f:8/integer-unit:1-unsigned-big, + $l:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\001:8/integer-unit:1-unsigned-big, + $h:8/integer-unit:1-unsigned-big, + $\003:8/integer-unit:1-unsigned-big, + $d:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\003:8/integer-unit:1-unsigned-big, + $v:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $r:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $\f:8/integer-unit:1-unsigned-big, + $d:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\001:8/integer-unit:1-unsigned-big, + $Y:8/integer-unit:1-unsigned-big, + $j:8/integer-unit:1-unsigned-big>>, + <<$\203:8/integer-unit:1-unsigned-big, + $P:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $*:8/integer-unit:1-unsigned-big, + $x:8/integer-unit:1-unsigned-big, + $\234:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $M:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $/:8/integer-unit:1-unsigned-big, + $H:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\005:8/integer-unit:1-unsigned-big, + $R:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\031:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $):8/integer-unit:1-unsigned-big, + $\f:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $e:8/integer-unit:1-unsigned-big, + $\211:8/integer-unit:1-unsigned-big, + $E:8/integer-unit:1-unsigned-big, + $\s:8/integer-unit:1-unsigned-big, + $.:8/integer-unit:1-unsigned-big, + $c:8/integer-unit:1-unsigned-big, + $\004:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $/:8/integer-unit:1-unsigned-big, + $\022:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\205:8/integer-unit:1-unsigned-big, + $\t:8/integer-unit:1-unsigned-big, + $\216:8/integer-unit:1-unsigned-big>>, + <<$\203:8/integer-unit:1-unsigned-big, + $P:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $j:8/integer-unit:1-unsigned-big, + $x:8/integer-unit:1-unsigned-big, + $\234:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $I:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $I:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $+:8/integer-unit:1-unsigned-big, + $N:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\f:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\024:8/integer-unit:1-unsigned-big, + $\006:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\222:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\202:8/integer-unit:1-unsigned-big, + $\234:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $D:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\034:8/integer-unit:1-unsigned-big, + $\006:8/integer-unit:1-unsigned-big, + $\006:8/integer-unit:1-unsigned-big, + $\006:8/integer-unit:1-unsigned-big, + $f:8/integer-unit:1-unsigned-big, + $\220:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $s:8/integer-unit:1-unsigned-big, + $Y:8/integer-unit:1-unsigned-big, + $b:8/integer-unit:1-unsigned-big, + $Q:8/integer-unit:1-unsigned-big, + $":8/integer-unit:1-unsigned-big, + $W:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $\003:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\023:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $/:8/integer-unit:1-unsigned-big, + $\002:8/integer-unit:1-unsigned-big, + $\205:8/integer-unit:1-unsigned-big, + $\027:8/integer-unit:1-unsigned-big, + $\237:8/integer-unit:1-unsigned-big, + $\205:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\227:8/integer-unit:1-unsigned-big, + $\007:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\227:8/integer-unit:1-unsigned-big, + $\021:8/integer-unit:1-unsigned-big, + $.:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\003:8/integer-unit:1-unsigned-big, + $\224:8/integer-unit:1-unsigned-big, + $\217:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\002:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\203:8/integer-unit:1-unsigned-big, + $>:8/integer-unit:1-unsigned-big, + $\034:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big>>} + end, + [{1, + 2, + 2, + {gen, + % fun-info: {4,131674517,'-create_handle/0-fun-4-'} + fun() -> + H1 + end}}, + {2,5,4,fil}, + {3, + 7, + 5, + {gen, + % fun-info: {5,108000324,'-create_handle/0-fun-5-'} + fun() -> + [{0},{1},{2}] + end}}, + {4,10,7,fil}, + {5, + 12, + 8, + {gen, + {join, + '==', + 1, + 3, + % fun-info: {9,59718458,'-create_handle/0-fun-9-'} + fun(H1_0_1) -> + F1_0_1 = + % fun-info: {7,779460,'-create_handle/0-fun-7-'} + fun(_, []) -> + []; + (F1_0_1, [O1_0_1|C1_0_1]) -> + case O1_0_1 of + {_,_,_} + when + 192.0 + =:= + element(1, O1_0_1) -> + [O1_0_1| + % fun-info: {6,23729943,'-create_handle/0-fun-6-'} + fun() -> + F1_0_1(F1_0_1, + C1_0_1) + end]; + _ -> + F1_0_1(F1_0_1, C1_0_1) + end; + (F1_0_1, C1_0_1) + when is_function(C1_0_1) -> + F1_0_1(F1_0_1, C1_0_1()); + (_, C1_0_1) -> + C1_0_1 + end, + % fun-info: {8,43652904,'-create_handle/0-fun-8-'} + fun() -> + F1_0_1(F1_0_1, H1_0_1) + end + end, + % fun-info: {13,102310144,'-create_handle/0-fun-13-'} + fun(H1_0_1) -> + F1_0_1 = + % fun-info: {11,74362432,'-create_handle/0-fun-11-'} + fun(_, []) -> + []; + (F1_0_1, [O1_0_1|C1_0_1]) -> + case O1_0_1 of + {_} -> + [O1_0_1| + % fun-info: {10,23729943,'-create_handle/0-fun-10-'} + fun() -> + F1_0_1(F1_0_1, + C1_0_1) + end]; + _ -> + F1_0_1(F1_0_1, C1_0_1) + end; + (F1_0_1, C1_0_1) + when is_function(C1_0_1) -> + F1_0_1(F1_0_1, C1_0_1()); + (_, C1_0_1) -> + C1_0_1 + end, + % fun-info: {12,43652904,'-create_handle/0-fun-12-'} + fun() -> + F1_0_1(F1_0_1, H1_0_1) + end + end, + % fun-info: {14,17838355,'-create_handle/0-fun-14-'} + fun() -> + {[{1,[192.0]}],[],[]} + end}}}], + % fun-info: {22,31304647,'-create_handle/0-fun-22-'} + fun(join) -> + {[[{1,"\002"},{3,"\001"}]],[]}; + (size) -> + % fun-info: {15,31963143,'-create_handle/0-fun-15-'} + fun(0) -> + 2; + (1) -> + 3; + (3) -> + 1; + (_) -> + undefined + end; + (template) -> + % fun-info: {16,113413274,'-create_handle/0-fun-16-'} + fun({1,2}, '=:=') -> + "\001"; + ({1,2}, '==') -> + "\001\002"; + ({3,1}, '=:=') -> + "\002"; + ({3,1}, '==') -> + "\001\002"; + (_, _) -> + [] + end; + (constants) -> + % fun-info: {18,52148739,'-create_handle/0-fun-18-'} + fun(1) -> + % fun-info: {17,5864387,'-create_handle/0-fun-17-'} + fun(1) -> + {values,[192.0],{some,[2]}}; + (_) -> + false + end; + (_) -> + no_column_fun + end; + (n_leading_constant_columns) -> + % fun-info: {19,82183172,'-create_handle/0-fun-19-'} + fun(1) -> + 1; + (_) -> + 0 + end; + (constant_columns) -> + % fun-info: {20,80910005,'-create_handle/0-fun-20-'} + fun(1) -> + "\001"; + (_) -> + [] + end; + (match_specs) -> + % fun-info: {21,91764346,'-create_handle/0-fun-21-'} + fun(1) -> + {[{{'$1','$2','_'}, + [{'=:=','$1',192.0}], + ['$_']}], + "\002"}; + (_) -> + undefined + end; + (_) -> + undefined + end} + end, + undefined}). + +lookup_handle() -> + E = qlc_SUITE:table([{1,a},{2,b},{3,c}], 1, [1]), + qlc:q({qlc_lc, + % fun-info: {46,120768015,'-lookup_handle/0-fun-22-'} + fun() -> + {qlc_v1, + % fun-info: {26,82970908,'-lookup_handle/0-fun-2-'} + fun(S02_0_1, RL02_0_1, Go02_0_1) -> + Fun2_0_1 = + % fun-info: {25,75235357,'-lookup_handle/0-fun-1-'} + fun(0, RL2_0_1, _, _, _, _, _, _) + when is_list(RL2_0_1) -> + lists:reverse(RL2_0_1); + (0, _, _, _, _, _, _, _) -> + []; + (1, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_1_1, + X2) + when is_list(RL2_0_1) -> + Fun2_0_1(element(1, Go2_0_1), + [{X2,Y2}|RL2_0_1], + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_1_1, + X2); + (1, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_1_1, + X2) -> + [{X2,Y2}| + % fun-info: {24,124255471,'-lookup_handle/0-fun-0-'} + fun() -> + Fun2_0_1(element(1, + Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_1_1, + X2) + end]; + (2, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + _, + X2) -> + Fun2_0_1(3, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + element(4, Go2_0_1), + X2); + (3, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + [{X2,_}|C2_0_1], + _) -> + Fun2_0_1(element(3, Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_0_1, + X2); + (3, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + [_|C2_0_1], + _) -> + Fun2_0_1(3, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_0_1, + []); + (3, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + [], + _) -> + Fun2_0_1(element(2, Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + [], + []); + (3, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_1_1, + _) -> + case C2_1_1() of + [{X2,_}|C2_0_1] -> + Fun2_0_1(element(3, + Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_0_1, + X2); + [_|C2_0_1] -> + Fun2_0_1(3, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_0_1, + []); + [] -> + Fun2_0_1(element(2, + Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + [], + []); + E2_0_1 -> + E2_0_1 + end; + (4, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + _, + Y2, + C2_1_1, + X2) -> + Fun2_0_1(5, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + element(7, Go2_0_1), + Y2, + C2_1_1, + X2); + (5, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + [{Y2}|C2_0_1], + _, + C2_1_1, + X2) -> + Fun2_0_1(element(6, Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_0_1, + Y2, + C2_1_1, + X2); + (5, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + [_|C2_0_1], + _, + C2_1_1, + X2) -> + Fun2_0_1(5, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_0_1, + [], + C2_1_1, + X2); + (5, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + [], + _, + C2_1_1, + X2) -> + Fun2_0_1(element(5, Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + [], + [], + C2_1_1, + X2); + (5, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + _, + C2_1_1, + X2) -> + case C2_2_1() of + [{Y2}|C2_0_1] -> + Fun2_0_1(element(6, + Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_0_1, + Y2, + C2_1_1, + X2); + [_|C2_0_1] -> + Fun2_0_1(5, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_0_1, + [], + C2_1_1, + X2); + [] -> + Fun2_0_1(element(5, + Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + [], + [], + C2_1_1, + X2); + E2_0_1 -> + E2_0_1 + end; + (6, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_1_1, + X2) -> + if + X2 =:= Y2 -> + Fun2_0_1(element(9, + Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_1_1, + X2); + true -> + Fun2_0_1(element(8, + Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_1_1, + X2) + end; + (7, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + _, + X2) -> + Fun2_0_1(8, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + element(12, Go2_0_1), + X2); + (8, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + _, + [[{X2,_}|{Y2}]|C2_0_1], + _) -> + Fun2_0_1(element(11, Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_0_1, + X2); + (8, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + _, + [_|C2_0_1], + _) -> + Fun2_0_1(8, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + [], + C2_0_1, + []); + (8, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + _, + [], + _) -> + Fun2_0_1(element(10, Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + [], + [], + []); + (8, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + _, + C2_1_1, + _) -> + case C2_1_1() of + [[{X2,_}|{Y2}]|C2_0_1] -> + Fun2_0_1(element(11, + Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + Y2, + C2_0_1, + X2); + [_|C2_0_1] -> + Fun2_0_1(8, + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + [], + C2_0_1, + []); + [] -> + Fun2_0_1(element(10, + Go2_0_1), + RL2_0_1, + Fun2_0_1, + Go2_0_1, + C2_2_1, + [], + [], + []); + E2_0_1 -> + E2_0_1 + end + end, + Fun2_0_1(S02_0_1, + RL02_0_1, + Fun2_0_1, + Go02_0_1, + [], + [], + [], + []) + end, + % fun-info: {27,111349661,'-lookup_handle/0-fun-3-'} + fun() -> + {<<$\203:8/integer-unit:1-unsigned-big, + $P:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $.:8/integer-unit:1-unsigned-big, + $x:8/integer-unit:1-unsigned-big, + $\234:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $N:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $-:8/integer-unit:1-unsigned-big, + $):8/integer-unit:1-unsigned-big, + $-:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $I:8/integer-unit:1-unsigned-big, + $M:8/integer-unit:1-unsigned-big, + $\024:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $0:8/integer-unit:1-unsigned-big, + $\227:8/integer-unit:1-unsigned-big, + $%:8/integer-unit:1-unsigned-big, + $\026:8/integer-unit:1-unsigned-big, + $%:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $0:8/integer-unit:1-unsigned-big, + $0:8/integer-unit:1-unsigned-big, + $F:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $":8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\206:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big>>, + <<$\203:8/integer-unit:1-unsigned-big, + $P:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $.:8/integer-unit:1-unsigned-big, + $x:8/integer-unit:1-unsigned-big, + $\234:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $N:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $-:8/integer-unit:1-unsigned-big, + $):8/integer-unit:1-unsigned-big, + $-:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $I:8/integer-unit:1-unsigned-big, + $M:8/integer-unit:1-unsigned-big, + $\024:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $0:8/integer-unit:1-unsigned-big, + $\227:8/integer-unit:1-unsigned-big, + $%:8/integer-unit:1-unsigned-big, + $\026:8/integer-unit:1-unsigned-big, + $%:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $0:8/integer-unit:1-unsigned-big, + $0:8/integer-unit:1-unsigned-big, + $F:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\222:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big>>, + <<$\203:8/integer-unit:1-unsigned-big, + $h:8/integer-unit:1-unsigned-big, + $\003:8/integer-unit:1-unsigned-big, + $d:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\005:8/integer-unit:1-unsigned-big, + $t:8/integer-unit:1-unsigned-big, + $u:8/integer-unit:1-unsigned-big, + $p:8/integer-unit:1-unsigned-big, + $l:8/integer-unit:1-unsigned-big, + $e:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $\022:8/integer-unit:1-unsigned-big, + $l:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\001:8/integer-unit:1-unsigned-big, + $h:8/integer-unit:1-unsigned-big, + $\003:8/integer-unit:1-unsigned-big, + $d:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\003:8/integer-unit:1-unsigned-big, + $v:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $r:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $\022:8/integer-unit:1-unsigned-big, + $d:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\001:8/integer-unit:1-unsigned-big, + $Y:8/integer-unit:1-unsigned-big, + $j:8/integer-unit:1-unsigned-big>>, + <<$\203:8/integer-unit:1-unsigned-big, + $P:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $+:8/integer-unit:1-unsigned-big, + $x:8/integer-unit:1-unsigned-big, + $\234:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $M:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $/:8/integer-unit:1-unsigned-big, + $H:8/integer-unit:1-unsigned-big, + $\024:8/integer-unit:1-unsigned-big, + $N:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $\006:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $e:8/integer-unit:1-unsigned-big, + $\211:8/integer-unit:1-unsigned-big, + $E:8/integer-unit:1-unsigned-big, + $\s:8/integer-unit:1-unsigned-big, + $>:8/integer-unit:1-unsigned-big, + $c:8/integer-unit:1-unsigned-big, + $\004:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $/:8/integer-unit:1-unsigned-big, + $\022:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\227:8/integer-unit:1-unsigned-big, + $\t:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big>>, + <<$\203:8/integer-unit:1-unsigned-big, + $P:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\\:8/integer-unit:1-unsigned-big, + $x:8/integer-unit:1-unsigned-big, + $\234:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $I:8/integer-unit:1-unsigned-big, + $a:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $I:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $+:8/integer-unit:1-unsigned-big, + $N:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\f:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\024:8/integer-unit:1-unsigned-big, + $\006:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\222:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\202:8/integer-unit:1-unsigned-big, + $\234:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $D:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\034:8/integer-unit:1-unsigned-big, + $\006:8/integer-unit:1-unsigned-big, + $\006:8/integer-unit:1-unsigned-big, + $\006:8/integer-unit:1-unsigned-big, + $&:8/integer-unit:1-unsigned-big, + $\220:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $s:8/integer-unit:1-unsigned-big, + $Y:8/integer-unit:1-unsigned-big, + $b:8/integer-unit:1-unsigned-big, + $Q:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $`:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $\003:8/integer-unit:1-unsigned-big, + $c:8/integer-unit:1-unsigned-big, + $\004:8/integer-unit:1-unsigned-big, + $\n:8/integer-unit:1-unsigned-big, + $/:8/integer-unit:1-unsigned-big, + $>:8/integer-unit:1-unsigned-big, + $\v:8/integer-unit:1-unsigned-big, + $I:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\020:8/integer-unit:1-unsigned-big, + $H:8/integer-unit:1-unsigned-big, + $5:8/integer-unit:1-unsigned-big, + $#:8/integer-unit:1-unsigned-big, + $\\:8/integer-unit:1-unsigned-big, + $^:8/integer-unit:1-unsigned-big, + $\b:8/integer-unit:1-unsigned-big, + $(:8/integer-unit:1-unsigned-big, + $\037:8/integer-unit:1-unsigned-big, + $\231:8/integer-unit:1-unsigned-big, + $\005:8/integer-unit:1-unsigned-big, + $\000:8/integer-unit:1-unsigned-big, + $\024:8/integer-unit:1-unsigned-big, + $�:8/integer-unit:1-unsigned-big, + $\031:8/integer-unit:1-unsigned-big, + $M:8/integer-unit:1-unsigned-big>>} + end, + [{1, + 2, + 2, + {gen, + % fun-info: {28,75197307,'-lookup_handle/0-fun-4-'} + fun() -> + E + end}}, + {2, + 5, + 4, + {gen, + % fun-info: {29,86826511,'-lookup_handle/0-fun-5-'} + fun() -> + [{0},{1},{2}] + end}}, + {3,8,6,fil}, + {4, + 10, + 7, + {gen, + {join, + '==', + 1, + 2, + % fun-info: {33,129609919,'-lookup_handle/0-fun-9-'} + fun(H2_0_1) -> + F2_0_1 = + % fun-info: {31,45768082,'-lookup_handle/0-fun-7-'} + fun(_, []) -> + []; + (F2_0_1, [O2_0_1|C2_0_1]) -> + case O2_0_1 of + {_,_} -> + [O2_0_1| + % fun-info: {30,28136696,'-lookup_handle/0-fun-6-'} + fun() -> + F2_0_1(F2_0_1, + C2_0_1) + end]; + _ -> + F2_0_1(F2_0_1, C2_0_1) + end; + (F2_0_1, C2_0_1) + when is_function(C2_0_1) -> + F2_0_1(F2_0_1, C2_0_1()); + (_, C2_0_1) -> + C2_0_1 + end, + % fun-info: {32,48059625,'-lookup_handle/0-fun-8-'} + fun() -> + F2_0_1(F2_0_1, H2_0_1) + end + end, + % fun-info: {37,63676968,'-lookup_handle/0-fun-13-'} + fun(H2_0_1) -> + F2_0_1 = + % fun-info: {35,129320532,'-lookup_handle/0-fun-11-'} + fun(_, []) -> + []; + (F2_0_1, [O2_0_1|C2_0_1]) -> + case O2_0_1 of + {_} -> + [O2_0_1| + % fun-info: {34,28136696,'-lookup_handle/0-fun-10-'} + fun() -> + F2_0_1(F2_0_1, + C2_0_1) + end]; + _ -> + F2_0_1(F2_0_1, C2_0_1) + end; + (F2_0_1, C2_0_1) + when is_function(C2_0_1) -> + F2_0_1(F2_0_1, C2_0_1()); + (_, C2_0_1) -> + C2_0_1 + end, + % fun-info: {36,48059625,'-lookup_handle/0-fun-12-'} + fun() -> + F2_0_1(F2_0_1, H2_0_1) + end + end, + % fun-info: {38,3236543,'-lookup_handle/0-fun-14-'} + fun() -> + {[],[],[]} + end}}}], + % fun-info: {45,56361026,'-lookup_handle/0-fun-21-'} + fun(join) -> + [[{1,"\001"},{2,"\001"}]]; + (size) -> + % fun-info: {39,40607542,'-lookup_handle/0-fun-15-'} + fun(0) -> + 2; + (1) -> + 2; + (2) -> + 1; + (_) -> + undefined + end; + (template) -> + % fun-info: {40,34907048,'-lookup_handle/0-fun-16-'} + fun({1,1}, _) -> + "\001\002"; + ({2,1}, _) -> + "\001\002"; + (_, _) -> + [] + end; + (constants) -> + % fun-info: {41,11686091,'-lookup_handle/0-fun-17-'} + fun(_) -> + no_column_fun + end; + (n_leading_constant_columns) -> + % fun-info: {42,21492441,'-lookup_handle/0-fun-18-'} + fun(_) -> + 0 + end; + (constant_columns) -> + % fun-info: {43,55297177,'-lookup_handle/0-fun-19-'} + fun(_) -> + [] + end; + (match_specs) -> + % fun-info: {44,55081557,'-lookup_handle/0-fun-20-'} + fun(_) -> + undefined + end; + (_) -> + undefined + end} + end, + undefined}). diff --git a/lib/stdlib/test/stdlib_SUITE.erl b/lib/stdlib/test/stdlib_SUITE.erl index 0cca030b3d..8a2cb5ea6b 100644 --- a/lib/stdlib/test/stdlib_SUITE.erl +++ b/lib/stdlib/test/stdlib_SUITE.erl @@ -33,8 +33,7 @@ -export([init_per_testcase/2, end_per_testcase/2]). % Test cases must be exported. --export([app_test/1]). --define(cases, [app_test]). +-export([app_test/1, appup_test/1]). %% %% all/1 @@ -42,7 +41,7 @@ suite() -> [{ct_hooks,[ts_install_cth]}]. all() -> - [app_test]. + [app_test, appup_test]. groups() -> []. @@ -79,3 +78,61 @@ app_test(Config) when is_list(Config) -> ?t:app_test(stdlib), ok. +%% Test that appup allows upgrade from/downgrade to a maximum of two +%% major releases back. +appup_test(_Config) -> + application:load(stdlib), + {_,_,Vsn} = lists:keyfind(stdlib,1,application:loaded_applications()), + AppupFile = filename:join([code:lib_dir(stdlib),ebin,"stdlib.appup"]), + {ok,[{Vsn,UpFrom,DownTo}=AppupScript]} = file:consult(AppupFile), + ct:log("~p~n",[AppupScript]), + {OkVsns,NokVsns} = create_test_vsns(Vsn), + check_appup(OkVsns,UpFrom,{ok,[restart_new_emulator]}), + check_appup(OkVsns,DownTo,{ok,[restart_new_emulator]}), + check_appup(NokVsns,UpFrom,error), + check_appup(NokVsns,DownTo,error), + ok. + +create_test_vsns(Current) -> + [XStr,YStr|Rest] = string:tokens(Current,"."), + X = list_to_integer(XStr), + Y = list_to_integer(YStr), + SecondMajor = vsn(X,Y-2), + SecondMinor = SecondMajor ++ ".1.3", + FirstMajor = vsn(X,Y-1), + FirstMinor = FirstMajor ++ ".57", + ThisMajor = vsn(X,Y), + This = + case Rest of + [] -> + []; + ["1"] -> + [ThisMajor]; + _ -> + ThisMinor = ThisMajor ++ ".1", + [ThisMajor,ThisMinor] + end, + OkVsns = This ++ [FirstMajor, FirstMinor, SecondMajor, SecondMinor], + + ThirdMajor = vsn(X,Y-3), + ThirdMinor = ThirdMajor ++ ".10.12", + Illegal = ThisMajor ++ ",1", + Newer1Major = vsn(X,Y+1), + Newer1Minor = Newer1Major ++ ".1", + Newer2Major = ThisMajor ++ "1", + NokVsns = [ThirdMajor,ThirdMinor, + Illegal, + Newer1Major,Newer1Minor, + Newer2Major], + {OkVsns,NokVsns}. + +vsn(X,Y) -> + integer_to_list(X) ++ "." ++ integer_to_list(Y). + +check_appup([Vsn|Vsns],Instrs,Expected) -> + case systools_relup:appup_search_for_version(Vsn, Instrs) of + Expected -> check_appup(Vsns,Instrs,Expected); + Other -> ct:fail({unexpected_result_for_vsn,Vsn,Other}) + end; +check_appup([],_,_) -> + ok. diff --git a/lib/stdlib/test/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) -> |