diff options
Diffstat (limited to 'lib/stdlib/test')
28 files changed, 673 insertions, 285 deletions
diff --git a/lib/stdlib/test/Makefile b/lib/stdlib/test/Makefile index 6aa09d7bd0..af82f22b21 100644 --- a/lib/stdlib/test/Makefile +++ b/lib/stdlib/test/Makefile @@ -66,6 +66,7 @@ MODULES= \ string_SUITE \ supervisor_1 \ supervisor_2 \ + supervisor_3 \ supervisor_deadlock \ naughty_child \ shell_SUITE \ diff --git a/lib/stdlib/test/base64_SUITE.erl b/lib/stdlib/test/base64_SUITE.erl index b28df94221..b0da6408ff 100644 --- a/lib/stdlib/test/base64_SUITE.erl +++ b/lib/stdlib/test/base64_SUITE.erl @@ -1,8 +1,7 @@ -%% -*- coding: utf-8 -*- %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2007-2012. All Rights Reserved. +%% Copyright Ericsson AB 2007-2013. 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/binary_module_SUITE.erl b/lib/stdlib/test/binary_module_SUITE.erl index 9b6f628aa9..d6886ba1e5 100644 --- a/lib/stdlib/test/binary_module_SUITE.erl +++ b/lib/stdlib/test/binary_module_SUITE.erl @@ -1,8 +1,7 @@ -%% -*- coding: utf-8 -*- %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1997-2012. All Rights Reserved. +%% Copyright Ericsson AB 1997-2013. 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/c_SUITE.erl b/lib/stdlib/test/c_SUITE.erl index 25281365be..8c55b616b9 100644 --- a/lib/stdlib/test/c_SUITE.erl +++ b/lib/stdlib/test/c_SUITE.erl @@ -20,7 +20,7 @@ -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, init_per_group/2,end_per_group/2]). -export([c_1/1, c_2/1, c_3/1, c_4/1, nc_1/1, nc_2/1, nc_3/1, nc_4/1, - memory/1]). + ls/1, memory/1]). -include_lib("test_server/include/test_server.hrl"). @@ -29,7 +29,7 @@ suite() -> [{ct_hooks,[ts_install_cth]}]. all() -> - [c_1, c_2, c_3, c_4, nc_1, nc_2, nc_3, nc_4, memory]. + [c_1, c_2, c_3, c_4, nc_1, nc_2, nc_3, nc_4, ls, memory]. groups() -> []. @@ -147,6 +147,13 @@ nc_4(Config) when is_list(Config) -> ?line Result = nc(R,[{outdir,W}]), ?line {ok, m} = Result. +ls(Config) when is_list(Config) -> + Directory = ?config(data_dir, Config), + ok = c:ls(Directory), + File = filename:join(Directory, "m.erl"), + ok = c:ls(File), + ok = c:ls("no_such_file"). + memory(doc) -> ["Checks that c:memory/[0,1] returns consistent results."]; memory(suite) -> diff --git a/lib/stdlib/test/dets_SUITE.erl b/lib/stdlib/test/dets_SUITE.erl index 065b74ad41..8ff7c3ccc9 100644 --- a/lib/stdlib/test/dets_SUITE.erl +++ b/lib/stdlib/test/dets_SUITE.erl @@ -33,8 +33,6 @@ -define(datadir(Conf), ?config(data_dir, Conf)). -endif. --compile(r13). % OTP-9607 - -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, init_per_group/2,end_per_group/2, newly_started/1, basic_v8/1, basic_v9/1, @@ -54,7 +52,7 @@ simultaneous_open/1, insert_new/1, repair_continuation/1, otp_5487/1, otp_6206/1, otp_6359/1, otp_4738/1, otp_7146/1, otp_8070/1, otp_8856/1, otp_8898/1, otp_8899/1, otp_8903/1, - otp_8923/1, otp_9282/1, otp_9607/1]). + otp_8923/1, otp_9282/1]). -export([dets_dirty_loop/0]). @@ -111,7 +109,7 @@ all() -> many_clients, otp_4906, otp_5402, simultaneous_open, insert_new, repair_continuation, otp_5487, otp_6206, otp_6359, otp_4738, otp_7146, otp_8070, otp_8856, otp_8898, - otp_8899, otp_8903, otp_8923, otp_9282, otp_9607 + otp_8899, otp_8903, otp_8923, otp_9282 ]. groups() -> @@ -3899,77 +3897,6 @@ some_calls(Tab, Config) -> ok = dets:close(T), file:delete(File). -otp_9607(doc) -> - ["OTP-9607. Test downgrading the slightly changed format."]; -otp_9607(suite) -> - []; -otp_9607(Config) when is_list(Config) -> - %% Note: the bug is about almost full tables. The fix of that - %% problem is *not* tested here. - Version = r13b, - case ?t:is_release_available(atom_to_list(Version)) of - true -> - T = otp_9607, - File = filename(T, Config), - Key = a, - Value = 1, - Args = [{file,File}], - {ok, T} = dets:open_file(T, Args), - ok = dets:insert(T, {Key, Value}), - ok = dets:close(T), - - Call = fun(P, A) -> - P ! {self(), A}, - receive - {P, Ans} -> - Ans - after 5000 -> - exit(other_process_dead) - end - end, - %% Create a file on the modified format, read the file - %% with an emulator that doesn't know about the modified - %% format. - {ok, Node} = start_node_rel(Version, Version, slave), - Pid = rpc:call(Node, erlang, spawn, - [?MODULE, dets_dirty_loop, []]), - {error,{needs_repair, File}} = - Call(Pid, [open, T, Args++[{repair,false}]]), - io:format("Expect repair:~n"), - {ok, T} = Call(Pid, [open, T, Args]), - [{Key,Value}] = Call(Pid, [read, T, Key]), - ok = Call(Pid, [close, T]), - file:delete(File), - - %% Create a file on the unmodified format. Modify the file - %% using an emulator that must not turn the file into the - %% modified format. Read the file and make sure it is not - %% repaired. - {ok, T} = Call(Pid, [open, T, Args]), - ok = Call(Pid, [write, T, {Key,Value}]), - [{Key,Value}] = Call(Pid, [read, T, Key]), - ok = Call(Pid, [close, T]), - - Key2 = b, - Value2 = 2, - - {ok, T} = dets:open_file(T, Args), - [{Key,Value}] = dets:lookup(T, Key), - ok = dets:insert(T, {Key2,Value2}), - ok = dets:close(T), - - {ok, T} = Call(Pid, [open, T, Args++[{repair,false}]]), - [{Key2,Value2}] = Call(Pid, [read, T, Key2]), - ok = Call(Pid, [close, T]), - - ?t:stop_node(Node), - file:delete(File), - ok; - false -> - {skipped, "No support for old node"} - end. - - %% %% Parts common to several test cases diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl index b2f1aa955a..0cbdf76270 100644 --- a/lib/stdlib/test/epp_SUITE.erl +++ b/lib/stdlib/test/epp_SUITE.erl @@ -104,6 +104,8 @@ include_local(suite) -> include_local(Config) when is_list(Config) -> ?line DataDir = ?config(data_dir, Config), ?line File = filename:join(DataDir, "include_local.erl"), + FooHrl = filename:join([DataDir,"include","foo.hrl"]), + BarHrl = filename:join([DataDir,"include","bar.hrl"]), %% include_local.erl includes include/foo.hrl which %% includes bar.hrl (also in include/) without requiring %% any additional include path, and overriding any file @@ -111,6 +113,8 @@ include_local(Config) when is_list(Config) -> ?line {ok, List} = epp:parse_file(File, [DataDir], []), ?line {value, {attribute,_,a,{true,true}}} = lists:keysearch(a,3,List), + [{File,1},{FooHrl,1},{BarHrl,1},{FooHrl,5},{File,5}] = + [ FileLine || {attribute,_,file,FileLine} <- List ], ok. %%% Here is a little reimplementation of epp:parse_file, which times out diff --git a/lib/stdlib/test/erl_eval_SUITE.erl b/lib/stdlib/test/erl_eval_SUITE.erl index 7ff4c81ea6..7ceef727f1 100644 --- a/lib/stdlib/test/erl_eval_SUITE.erl +++ b/lib/stdlib/test/erl_eval_SUITE.erl @@ -992,7 +992,7 @@ otp_10622(Config) when is_list(Config) -> <<0>>), check(fun() -> <<"\x{aa}ff"/utf8>> = <<"\x{aa}ff"/utf8>> end, "<<\"\\x{aa}ff\"/utf8>> = <<\"\\x{aa}ff\"/utf8>>. ", - <<"�\xaaff">>), + <<"Â\xaaff">>), %% The same bug as last example: check(fun() -> case <<"foo"/utf8>> of <<"foo"/utf8>> -> true diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl index 9c0a43abcc..70a9d70e5c 100644 --- a/lib/stdlib/test/erl_pp_SUITE.erl +++ b/lib/stdlib/test/erl_pp_SUITE.erl @@ -43,13 +43,13 @@ receive_after/1, bits/1, head_tail/1, cond1/1, block/1, case1/1, ops/1, messages/1, old_mnemosyne_syntax/1, - import_export/1, misc_attrs/1, + import_export/1, misc_attrs/1, dialyzer_attrs/1, hook/1, neg_indent/1, otp_6321/1, otp_6911/1, otp_6914/1, otp_8150/1, otp_8238/1, otp_8473/1, otp_8522/1, otp_8567/1, otp_8664/1, otp_9147/1, - otp_10302/1, otp_10820/1]). + otp_10302/1, otp_10820/1, otp_11100/1]). %% Internal export. -export([ehook/6]). @@ -77,11 +77,11 @@ groups() -> [func, call, recs, try_catch, if_then, receive_after, bits, head_tail, cond1, block, case1, ops, messages, old_mnemosyne_syntax]}, - {attributes, [], [misc_attrs, import_export]}, + {attributes, [], [misc_attrs, import_export, dialyzer_attrs]}, {tickets, [], [otp_6321, otp_6911, otp_6914, otp_8150, otp_8238, otp_8473, otp_8522, otp_8567, otp_8664, otp_9147, - otp_10302, otp_10820]}]. + otp_10302, otp_10820, otp_11100]}]. init_per_suite(Config) -> Config. @@ -597,6 +597,15 @@ misc_attrs(Config) when is_list(Config) -> ok. +dialyzer_attrs(suite) -> + []; +dialyzer_attrs(Config) when is_list(Config) -> + ok = pp_forms(<<"-type foo() :: #bar{}. ">>), + ok = pp_forms(<<"-opaque foo() :: {bar, fun((X, [42,...]) -> X)}. ">>), + ok = pp_forms(<<"-spec foo(bar(), qux()) -> [T | baz(T)]. ">>), + ok = pp_forms(<<"-callback foo(<<_:32,_:_*4>>, T) -> T. ">>), + ok. + hook(suite) -> []; hook(Config) when is_list(Config) -> @@ -1082,7 +1091,7 @@ otp_10820(Config) when is_list(Config) -> C1 = <<"%% coding: utf-8\n -module(any).">>, ok = do_otp_10820(Config, C1, "+pc latin1"), ok = do_otp_10820(Config, C1, "+pc unicode"), - C2 = <<"-module(any).">>, + C2 = <<"%% coding: latin-1\n -module(any).">>, ok = do_otp_10820(Config, C2, "+pc latin1"), ok = do_otp_10820(Config, C2, "+pc unicode"). @@ -1103,6 +1112,45 @@ file_attr_is_string("-file(\"" ++ _) -> true; file_attr_is_string([_ | L]) -> file_attr_is_string(L). +otp_11100(doc) -> + "OTP-11100. Fix printing of invalid forms."; +otp_11100(suite) -> []; +otp_11100(Config) when is_list(Config) -> + %% There are a few places where the added code ("options(none)") + %% doesn't make a difference (pp:bit_elem_type/1 is an example). + + %% Cannot trigger the use of the hook function with export/import. + "-export([{fy,a}/b]).\n" = + pf({attribute,1,export,[{{fy,a},b}]}), + "-type foo() :: integer(INVALID-FORM:{foo,bar}:).\n" = + pf({attribute,1,type,{foo,{type,1,integer,[{foo,bar}]},[]}}), + pf({attribute,1,type, + {a,{type,1,range,[{integer,1,1},{foo,bar}]},[]}}), + "-type foo(INVALID-FORM:{foo,bar}:) :: A.\n" = + pf({attribute,1,type,{foo,{var,1,'A'},[{foo,bar}]}}), + "-type foo() :: (INVALID-FORM:{foo,bar}: :: []).\n" = + pf({attribute,1,type, + {foo,{paren_type,1, + [{ann_type,1,[{foo,bar},{type,1,nil,[]}]}]}, + []}}), + "-type foo() :: <<_:INVALID-FORM:{foo,bar}:>>.\n" = + pf({attribute,1,type, + {foo,{type,1,binary,[{foo,bar},{integer,1,0}]},[]}}), + "-type foo() :: <<_:10, _:_*INVALID-FORM:{foo,bar}:>>.\n" = + pf({attribute,1,type, + {foo,{type,1,binary,[{integer,1,10},{foo,bar}]},[]}}), + "-type foo() :: #r{INVALID-FORM:{foo,bar}: :: integer()}.\n" = + pf({attribute,1,type, + {foo,{type,1,record, + [{atom,1,r}, + {type,1,field_type, + [{foo,bar},{type,1,integer,[]}]}]}, + []}}), + ok. + +pf(Form) -> + lists:flatten(erl_pp:form(Form,none)). + %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% compile(Config, Tests) -> diff --git a/lib/stdlib/test/erl_scan_SUITE.erl b/lib/stdlib/test/erl_scan_SUITE.erl index ecd181e87c..e628f7248d 100644 --- a/lib/stdlib/test/erl_scan_SUITE.erl +++ b/lib/stdlib/test/erl_scan_SUITE.erl @@ -1,4 +1,3 @@ -%% -*- coding: utf-8 -*- %% %% %CopyrightBegin% %% @@ -21,7 +20,8 @@ -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, init_per_group/2,end_per_group/2]). --export([ error_1/1, error_2/1, iso88591/1, otp_7810/1, otp_10302/1]). +-export([ error_1/1, error_2/1, iso88591/1, otp_7810/1, otp_10302/1, + otp_10990/1, otp_10992/1]). -import(lists, [nth/2,flatten/1]). -import(io_lib, [print/1]). @@ -60,7 +60,7 @@ end_per_testcase(_Case, Config) -> suite() -> [{ct_hooks,[ts_install_cth]}]. all() -> - [{group, error}, iso88591, otp_7810, otp_10302]. + [{group, error}, iso88591, otp_7810, otp_10302, otp_10990, otp_10992]. groups() -> [{error, [], [error_1, error_2]}]. @@ -1064,8 +1064,8 @@ otp_10302(Config) when is_list(Config) -> {string,0,"str"} = erl_parse:abstract("str"), {cons,0, {integer,0,$a}, - {cons,0,{integer,0,1024},{string,0,"c"}}} = - erl_parse:abstract("a"++[1024]++"c"), + {cons,0,{integer,0,55296},{string,0,"c"}}} = + erl_parse:abstract("a"++[55296]++"c"), Line = 17, {integer,Line,1} = erl_parse:abstract(1, Line), @@ -1080,8 +1080,8 @@ otp_10302(Config) when is_list(Config) -> {string,Line,"str"} = erl_parse:abstract("str", Line), {cons,Line, {integer,Line,$a}, - {cons,Line,{integer,Line,1024},{string,Line,"c"}}} = - erl_parse:abstract("a"++[1024]++"c", Line), + {cons,Line,{integer,Line,55296},{string,Line,"c"}}} = + erl_parse:abstract("a"++[55296]++"c", Line), Opts1 = [{line,17}], {integer,Line,1} = erl_parse:abstract(1, Opts1), @@ -1096,8 +1096,8 @@ otp_10302(Config) when is_list(Config) -> {string,Line,"str"} = erl_parse:abstract("str", Opts1), {cons,Line, {integer,Line,$a}, - {cons,Line,{integer,Line,1024},{string,Line,"c"}}} = - erl_parse:abstract("a"++[1024]++"c", Opts1), + {cons,Line,{integer,Line,55296},{string,Line,"c"}}} = + erl_parse:abstract("a"++[55296]++"c", Opts1), [begin {integer,Line,1} = erl_parse:abstract(1, Opts2), @@ -1121,6 +1121,29 @@ otp_10302(Config) when is_list(Config) -> erl_parse:abstract("a"++[1024]++"c", [{encoding,latin1}]), ok. +otp_10990(doc) -> + "OTP-10990. Floating point number in input string."; +otp_10990(suite) -> + []; +otp_10990(Config) when is_list(Config) -> + {'EXIT',_} = (catch {foo, erl_scan:string([$",42.0,$"],1)}), + ok. + +otp_10992(doc) -> + "OTP-10992. List of floats to abstract format."; +otp_10992(suite) -> + []; +otp_10992(Config) when is_list(Config) -> + {cons,0,{float,0,42.0},{nil,0}} = + erl_parse:abstract([42.0], [{encoding,unicode}]), + {cons,0,{float,0,42.0},{nil,0}} = + erl_parse:abstract([42.0], [{encoding,utf8}]), + {cons,0,{integer,0,65},{cons,0,{float,0,42.0},{nil,0}}} = + erl_parse:abstract([$A,42.0], [{encoding,unicode}]), + {cons,0,{integer,0,65},{cons,0,{float,0,42.0},{nil,0}}} = + erl_parse:abstract([$A,42.0], [{encoding,utf8}]), + ok. + test_string(String, Expected) -> {ok, Expected, _End} = erl_scan:string(String), test(String). diff --git a/lib/stdlib/test/escript_SUITE.erl b/lib/stdlib/test/escript_SUITE.erl index b6cdd0a9c7..eebfec3336 100644 --- a/lib/stdlib/test/escript_SUITE.erl +++ b/lib/stdlib/test/escript_SUITE.erl @@ -615,7 +615,7 @@ archive_script_file_access(Config) when is_list(Config) -> %% 3. If symlinks are supported, run one of the scripts via a symlink. %% %% This is in order to test error b) described above this test case. - case file:read_link(Symlink2) of + case element(1,os:type()) =:= win32 orelse file:read_link(Symlink2) of {ok,_} -> run(PrivDir, "./" ++ SymlinkName2 ++ " " ++ ScriptName2, [<<"ExitCode:0">>]); diff --git a/lib/stdlib/test/escript_SUITE_data/archive_script_file_access/archive_script_file_access.erl b/lib/stdlib/test/escript_SUITE_data/archive_script_file_access/archive_script_file_access.erl index b03c8ba70d..523621e4f3 100644 --- a/lib/stdlib/test/escript_SUITE_data/archive_script_file_access/archive_script_file_access.erl +++ b/lib/stdlib/test/escript_SUITE_data/archive_script_file_access/archive_script_file_access.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2012. All Rights Reserved. +%% Copyright Ericsson AB 2012-2013. 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 @@ -56,7 +56,7 @@ main([RelArchiveFile]) -> %% If symlinks are supported on this platform... RelSymlinkArchiveFile = "symlink_to_" ++ RelArchiveFile, - case file:read_link(RelSymlinkArchiveFile) of + case element(1,os:type()) =:= win32 orelse file:read_link(RelSymlinkArchiveFile) of {ok,_} -> DotSlashSymlinkArchiveFile = "./" ++ RelSymlinkArchiveFile, AbsSymlinkArchiveFile=filename:join(filename:dirname(AbsArchiveFile), diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl index d40609eeb0..82c3e7ecaf 100644 --- a/lib/stdlib/test/ets_SUITE.erl +++ b/lib/stdlib/test/ets_SUITE.erl @@ -33,7 +33,7 @@ -export([ match1/1, match2/1, match_object/1, match_object2/1]). -export([ dups/1, misc1/1, safe_fixtable/1, info/1, tab2list/1]). -export([ tab2file/1, tab2file2/1, tabfile_ext1/1, - tabfile_ext2/1, tabfile_ext3/1, tabfile_ext4/1]). + tabfile_ext2/1, tabfile_ext3/1, tabfile_ext4/1, badfile/1]). -export([ heavy_lookup/1, heavy_lookup_element/1, heavy_concurrent/1]). -export([ lookup_element_mult/1]). -export([]). @@ -75,6 +75,7 @@ -export([otp_9932/1]). -export([otp_9423/1]). -export([otp_10182/1]). +-export([memory_check_summary/1]). -export([init_per_testcase/2, end_per_testcase/2]). %% Convenience for manual testing @@ -149,7 +150,9 @@ all() -> give_away, setopts, bad_table, types, otp_10182, otp_9932, - otp_9423]. + otp_9423, + + memory_check_summary]. % MUST BE LAST groups() -> [{new, [], @@ -168,7 +171,7 @@ groups() -> [misc1, safe_fixtable, info, dups, tab2list]}, {files, [], [tab2file, tab2file2, tabfile_ext1, - tabfile_ext2, tabfile_ext3, tabfile_ext4]}, + tabfile_ext2, tabfile_ext3, tabfile_ext4, badfile]}, {heavy, [], [heavy_lookup, heavy_lookup_element, heavy_concurrent]}, {fold, [], @@ -185,7 +188,8 @@ init_per_suite(Config) -> end_per_suite(_Config) -> stop_spawn_logger(), - catch erts_debug:set_internal_state(available_internal_state, false). + catch erts_debug:set_internal_state(available_internal_state, false), + ok. init_per_group(_GroupName, Config) -> Config. @@ -193,6 +197,26 @@ init_per_group(_GroupName, Config) -> end_per_group(_GroupName, Config) -> Config. +%% Test that we did not have "too many" failed verify_etsmem()'s +%% in the test suite. +%% verify_etsmem() may give a low number of false positives +%% as concurrent activities, such as lingering processes +%% from earlier test suites, may do unrelated ets (de)allocations. +memory_check_summary(_Config) -> + case whereis(ets_test_spawn_logger) of + undefined -> + ?t:fail("No spawn logger exist"); + _ -> + ets_test_spawn_logger ! {self(), get_failed_memchecks}, + receive {get_failed_memchecks, FailedMemchecks} -> ok end, + io:format("Failed memchecks: ~p\n",[FailedMemchecks]), + if FailedMemchecks > 3 -> + ct:fail("Too many failed (~p) memchecks", [FailedMemchecks]); + true -> + ok + end + end. + %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% @@ -3268,15 +3292,14 @@ delete_large_named_table_1(Name, Flags, Data, Fix) -> end, Parent = self(), {Pid, MRef} = my_spawn_opt(fun() -> - receive - {trace,Parent,call,_} -> - ets_new(Name, [named_table]) - end - end, [link, monitor]), - ?line erlang:trace(self(), true, [call,{tracer,Pid}]), - ?line erlang:trace_pattern({ets,delete,1}, true, [global]), - ?line erlang:yield(), true = ets:delete(Tab), - ?line erlang:trace_pattern({ets,delete,1}, false, [global]), + receive + ets_new -> + ets_new(Name, [named_table]) + end + end, + [link, monitor]), + true = ets:delete(Tab), + Pid ! ets_new, receive {'DOWN',MRef,process,Pid,_} -> ok end, ok. @@ -4179,7 +4202,56 @@ tabfile_ext4(Config) when is_list(Config) -> file:delete(FName), ok. +badfile(suite) -> + []; +badfile(doc) -> + ["Tests that no disk_log is left open when file has been corrupted"]; +badfile(Config) when is_list(Config) -> + PrivDir = ?config(priv_dir,Config), + File = filename:join(PrivDir, "badfile"), + _ = file:delete(File), + T = ets:new(table, []), + true = ets:insert(T, [{a,1},{b,2}]), + ok = ets:tab2file(T, File, []), + true = ets:delete(T), + [H0 | Ts ] = get_all_terms(l, File), + H1 = tuple_to_list(H0), + H2 = [{K,V} || {K,V} <- H1, K =/= protection], + H = list_to_tuple(H2), + ok = file:delete(File), + write_terms(l, File, [H | Ts]), + %% All mandatory keys are no longer members of the header + {error, badfile} = ets:file2tab(File), + {error, badfile} = ets:tabfile_info(File), + file:delete(File), + {[],[]} = disk_log:accessible_logs(), + ok. + +get_all_terms(Log, File) -> + {ok, Log} = disk_log:open([{name,Log}, + {file, File}, + {mode, read_only}]), + Ts = get_all_terms(Log), + ok = disk_log:close(Log), + Ts. + +get_all_terms(Log) -> + get_all_terms1(Log, start, []). + +get_all_terms1(Log, Cont, Res) -> + case disk_log:chunk(Log, Cont) of + {error, _R} -> + throw(fel); + {Cont2, Terms} -> + get_all_terms1(Log, Cont2, Res ++ Terms); + eof -> + Res + end. +write_terms(Log, File, Terms) -> + {ok, Log} = disk_log:open([{name,Log},{file, File},{mode,read_write}]), + ok = disk_log:log(Log, Terms), + ok = disk_log:close(Log). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% @@ -5603,17 +5675,25 @@ etsmem() -> MemInfo -> CS = lists:foldl( fun ({instance, _, L}, Acc) -> - {value,{_,SBMBCS}} = lists:keysearch(sbmbcs, 1, L), - {value,{_,MBCS}} = lists:keysearch(mbcs, 1, L), - {value,{_,SBCS}} = lists:keysearch(sbcs, 1, L), - [SBMBCS,MBCS,SBCS | Acc] + {value,{mbcs,MBCS}} = lists:keysearch(mbcs, 1, L), + {value,{sbcs,SBCS}} = lists:keysearch(sbcs, 1, L), + NewAcc = [MBCS, SBCS | Acc], + case lists:keysearch(mbcs_pool, 1, L) of + {value,{mbcs_pool, MBCS_POOL}} -> + [MBCS_POOL|NewAcc]; + _ -> NewAcc + end end, [], MemInfo), lists:foldl( fun(L, {Bl0,BlSz0}) -> - {value,{_,Bl,_,_}} = lists:keysearch(blocks, 1, L), - {value,{_,BlSz,_,_}} = lists:keysearch(blocks_size, 1, L), + {value,BlTup} = lists:keysearch(blocks, 1, L), + blocks = element(1, BlTup), + Bl = element(2, BlTup), + {value,BlSzTup} = lists:keysearch(blocks_size, 1, L), + blocks_size = element(1, BlSzTup), + BlSz = element(2, BlSzTup), {Bl0+Bl,BlSz0+BlSz} end, {0,0}, CS) end}, @@ -5636,7 +5716,8 @@ verify_etsmem({MemInfo,AllTabs}) -> io:format("Actual: ~p", [MemInfo2]), io:format("Changed tables before: ~p\n",[AllTabs -- AllTabs2]), io:format("Changed tables after: ~p\n", [AllTabs2 -- AllTabs]), - ?t:fail() + ets_test_spawn_logger ! failed_memcheck, + {comment, "Failed memory check"} end. @@ -5658,10 +5739,10 @@ stop_loopers(Loopers) -> looper(Fun, State) -> looper(Fun, Fun(State)). -spawn_logger(Procs) -> +spawn_logger(Procs, FailedMemchecks) -> receive {new_test_proc, Proc} -> - spawn_logger([Proc|Procs]); + spawn_logger([Proc|Procs], FailedMemchecks); {sync_test_procs, Kill, From} -> lists:foreach(fun (Proc) when From == Proc -> ok; @@ -5684,7 +5765,14 @@ spawn_logger(Procs) -> end end, Procs), From ! test_procs_synced, - spawn_logger([From]) + spawn_logger([From], FailedMemchecks); + + failed_memcheck -> + spawn_logger(Procs, FailedMemchecks+1); + + {Pid, get_failed_memchecks} -> + Pid ! {get_failed_memchecks, FailedMemchecks}, + spawn_logger(Procs, FailedMemchecks) end. pid_status(Pid) -> @@ -5700,7 +5788,7 @@ start_spawn_logger() -> case whereis(ets_test_spawn_logger) of Pid when is_pid(Pid) -> true; _ -> register(ets_test_spawn_logger, - spawn_opt(fun () -> spawn_logger([]) end, + spawn_opt(fun () -> spawn_logger([], 0) end, [{priority, max}])) end. @@ -5711,8 +5799,7 @@ start_spawn_logger() -> stop_spawn_logger() -> Mon = erlang:monitor(process, ets_test_spawn_logger), (catch exit(whereis(ets_test_spawn_logger), kill)), - receive {'DOWN', Mon, _, _, _} -> ok end, - ok. + receive {'DOWN', Mon, _, _, _} -> ok end. wait_for_test_procs() -> wait_for_test_procs(false). @@ -5812,7 +5899,7 @@ spawn_monitor_with_pid(Pid, Fun, N) -> end) of Pid -> {Pid, erlang:monitor(process, Pid)}; - Other -> + _Other -> spawn_monitor_with_pid(Pid,Fun,N-1) end. @@ -6118,11 +6205,18 @@ repeat_for_opts(F, OptGenList) -> repeat_for_opts(F, OptGenList, []). repeat_for_opts(F, [], Acc) -> - lists:map(fun(Opts) -> - OptList = lists:filter(fun(E) -> E =/= void end, Opts), - io:format("Calling with options ~p\n",[OptList]), - F(OptList) - end, Acc); + lists:foldl(fun(Opts, RV_Acc) -> + OptList = lists:filter(fun(E) -> E =/= void end, Opts), + io:format("Calling with options ~p\n",[OptList]), + RV = F(OptList), + case RV_Acc of + {comment,_} -> RV_Acc; + _ -> case RV of + {comment,_} -> RV; + _ -> [RV | RV_Acc] + end + end + end, [], Acc); repeat_for_opts(F, [OptList | Tail], []) when is_list(OptList) -> repeat_for_opts(F, Tail, [[Opt] || Opt <- OptList]); repeat_for_opts(F, [OptList | Tail], AccList) when is_list(OptList) -> diff --git a/lib/stdlib/test/gen_event_SUITE.erl b/lib/stdlib/test/gen_event_SUITE.erl index 5c51e12e35..6be5a299b6 100644 --- a/lib/stdlib/test/gen_event_SUITE.erl +++ b/lib/stdlib/test/gen_event_SUITE.erl @@ -26,13 +26,14 @@ delete_handler/1, swap_handler/1, swap_sup_handler/1, notify/1, sync_notify/1, call/1, info/1, hibernate/1, call_format_status/1, call_format_status_anon/1, - error_format_status/1]). + error_format_status/1, get_state/1, replace_state/1]). suite() -> [{ct_hooks,[ts_install_cth]}]. all() -> [start, {group, test_all}, hibernate, - call_format_status, call_format_status_anon, error_format_status]. + call_format_status, call_format_status_anon, error_format_status, + get_state, replace_state]. groups() -> [{test_all, [], @@ -956,3 +957,45 @@ error_format_status(Config) when is_list(Config) -> ?line ok = gen_event:stop(Pid), process_flag(trap_exit, OldFl), ok. + +get_state(suite) -> + []; +get_state(doc) -> + ["Test that sys:get_state/1,2 return the gen_event state"]; +get_state(Config) when is_list(Config) -> + {ok, Pid} = gen_event:start({local, my_dummy_handler}), + State1 = self(), + ok = gen_event:add_handler(my_dummy_handler, dummy1_h, [State1]), + [{dummy1_h,false,State1}] = sys:get_state(Pid), + [{dummy1_h,false,State1}] = sys:get_state(Pid, 5000), + State2 = {?MODULE, self()}, + ok = gen_event:add_handler(my_dummy_handler, {dummy1_h,id}, [State2]), + Result1 = sys:get_state(Pid), + [{dummy1_h,false,State1},{dummy1_h,id,State2}] = lists:sort(Result1), + Result2 = sys:get_state(Pid, 5000), + [{dummy1_h,false,State1},{dummy1_h,id,State2}] = lists:sort(Result2), + ok = gen_event:stop(Pid), + ok. + +replace_state(suite) -> + []; +replace_state(doc) -> + ["Test that replace_state/2,3 replace the gen_event state"]; +replace_state(Config) when is_list(Config) -> + {ok, Pid} = gen_event:start({local, my_dummy_handler}), + State1 = self(), + ok = gen_event:add_handler(my_dummy_handler, dummy1_h, [State1]), + [{dummy1_h,false,State1}] = sys:get_state(Pid), + NState1 = "replaced", + Replace1 = fun({dummy1_h,false,_}=S) -> setelement(3,S,NState1) end, + [{dummy1_h,false,NState1}] = sys:replace_state(Pid, Replace1), + [{dummy1_h,false,NState1}] = sys:get_state(Pid), + NState2 = "replaced again", + Replace2 = fun({dummy1_h,false,_}=S) -> setelement(3,S,NState2) end, + [{dummy1_h,false,NState2}] = sys:replace_state(Pid, Replace2, 5000), + [{dummy1_h,false,NState2}] = sys:get_state(Pid), + %% verify no change in state if replace function crashes + Replace3 = fun(_) -> exit(fail) end, + [{dummy1_h,false,NState2}] = sys:replace_state(Pid, Replace3), + [{dummy1_h,false,NState2}] = sys:get_state(Pid), + ok. diff --git a/lib/stdlib/test/gen_fsm_SUITE.erl b/lib/stdlib/test/gen_fsm_SUITE.erl index a637a8543b..fd15838b7d 100644 --- a/lib/stdlib/test/gen_fsm_SUITE.erl +++ b/lib/stdlib/test/gen_fsm_SUITE.erl @@ -31,7 +31,7 @@ -export([shutdown/1]). --export([ sys1/1, call_format_status/1, error_format_status/1]). +-export([ sys1/1, call_format_status/1, error_format_status/1, get_state/1, replace_state/1]). -export([hibernate/1,hiber_idle/3,hiber_wakeup/3,hiber_idle/2,hiber_wakeup/2]). @@ -66,7 +66,7 @@ groups() -> start8, start9, start10, start11, start12]}, {abnormal, [], [abnormal1, abnormal2]}, {sys, [], - [sys1, call_format_status, error_format_status]}]. + [sys1, call_format_status, error_format_status, get_state, replace_state]}]. init_per_suite(Config) -> Config. @@ -413,6 +413,40 @@ error_format_status(Config) when is_list(Config) -> process_flag(trap_exit, OldFl), ok. +get_state(Config) when is_list(Config) -> + State = self(), + {ok, Pid} = gen_fsm:start(?MODULE, {state_data, State}, []), + {idle, State} = sys:get_state(Pid), + {idle, State} = sys:get_state(Pid, 5000), + stop_it(Pid), + + %% check that get_state can handle a name being an atom (pid is + %% already checked by the previous test) + {ok, Pid2} = gen_fsm:start({local, gfsm}, gen_fsm_SUITE, {state_data, State}, []), + {idle, State} = sys:get_state(gfsm), + {idle, State} = sys:get_state(gfsm, 5000), + stop_it(Pid2), + ok. + +replace_state(Config) when is_list(Config) -> + State = self(), + {ok, Pid} = gen_fsm:start(?MODULE, {state_data, State}, []), + {idle, State} = sys:get_state(Pid), + NState1 = "replaced", + Replace1 = fun({StateName, _}) -> {StateName, NState1} end, + {idle, NState1} = sys:replace_state(Pid, Replace1), + {idle, NState1} = sys:get_state(Pid), + NState2 = "replaced again", + Replace2 = fun({idle, _}) -> {state0, NState2} end, + {state0, NState2} = sys:replace_state(Pid, Replace2, 5000), + {state0, NState2} = sys:get_state(Pid), + %% verify no change in state if replace function crashes + Replace3 = fun(_) -> error(fail) end, + {state0, NState2} = sys:replace_state(Pid, Replace3), + {state0, NState2} = sys:get_state(Pid), + stop_it(Pid), + ok. + %% Hibernation hibernate(suite) -> []; hibernate(Config) when is_list(Config) -> diff --git a/lib/stdlib/test/gen_server_SUITE.erl b/lib/stdlib/test/gen_server_SUITE.erl index dffeadb423..a360a0809b 100644 --- a/lib/stdlib/test/gen_server_SUITE.erl +++ b/lib/stdlib/test/gen_server_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2012. All Rights Reserved. +%% Copyright Ericsson AB 1996-2013. 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 @@ -32,7 +32,7 @@ spec_init_local_registered_parent/1, spec_init_global_registered_parent/1, otp_5854/1, hibernate/1, otp_7669/1, call_format_status/1, - error_format_status/1, call_with_huge_message_queue/1 + error_format_status/1, get_state/1, replace_state/1, call_with_huge_message_queue/1 ]). % spawn export @@ -57,6 +57,7 @@ all() -> spec_init_local_registered_parent, spec_init_global_registered_parent, otp_5854, hibernate, otp_7669, call_format_status, error_format_status, + get_state, replace_state, call_with_huge_message_queue]. groups() -> @@ -1033,16 +1034,71 @@ error_format_status(Config) when is_list(Config) -> process_flag(trap_exit, OldFl), ok. +%% Verify that sys:get_state correctly returns gen_server state +%% +get_state(suite) -> + []; +get_state(doc) -> + ["Test that sys:get_state/1,2 return the gen_server state"]; +get_state(Config) when is_list(Config) -> + State = self(), + {ok, _Pid} = gen_server:start_link({local, get_state}, + ?MODULE, {state,State}, []), + State = sys:get_state(get_state), + State = sys:get_state(get_state, 5000), + {ok, Pid} = gen_server:start_link(?MODULE, {state,State}, []), + State = sys:get_state(Pid), + State = sys:get_state(Pid, 5000), + ok. + +%% Verify that sys:replace_state correctly replaces gen_server state +%% +replace_state(suite) -> + []; +replace_state(doc) -> + ["Test that sys:replace_state/1,2 replace the gen_server state"]; +replace_state(Config) when is_list(Config) -> + State = self(), + {ok, _Pid} = gen_server:start_link({local, replace_state}, + ?MODULE, {state,State}, []), + State = sys:get_state(replace_state), + NState1 = "replaced", + Replace1 = fun(_) -> NState1 end, + NState1 = sys:replace_state(replace_state, Replace1), + NState1 = sys:get_state(replace_state), + {ok, Pid} = gen_server:start_link(?MODULE, {state,NState1}, []), + NState1 = sys:get_state(Pid), + Suffix = " again", + NState2 = NState1 ++ Suffix, + Replace2 = fun(S) -> S ++ Suffix end, + NState2 = sys:replace_state(Pid, Replace2, 5000), + NState2 = sys:get_state(Pid, 5000), + %% verify no change in state if replace function crashes + Replace3 = fun(_) -> throw(fail) end, + NState2 = sys:replace_state(Pid, Replace3), + NState2 = sys:get_state(Pid, 5000), + ok. + %% Test that the time for a huge message queue is not %% significantly slower than with an empty message queue. call_with_huge_message_queue(Config) when is_list(Config) -> + case test_server:is_native(gen) of + true -> + {skip, + "gen is native - huge message queue optimization " + "is not implemented"}; + false -> + do_call_with_huge_message_queue() + end. + +do_call_with_huge_message_queue() -> ?line Pid = spawn_link(fun echo_loop/0), - ?line {Time,ok} = tc(fun() -> calls(10, Pid) end), + ?line {Time,ok} = tc(fun() -> calls(10000, Pid) end), ?line [self() ! {msg,N} || N <- lists:seq(1, 500000)], erlang:garbage_collect(), - ?line {NewTime,ok} = tc(fun() -> calls(10, Pid) end), + ?line {NewTime,ok} = tc(fun() -> calls(10000, Pid) end), io:format("Time for empty message queue: ~p", [Time]), io:format("Time for huge message queue: ~p", [NewTime]), diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl index 9f828c6d2d..5a8971c071 100644 --- a/lib/stdlib/test/io_SUITE.erl +++ b/lib/stdlib/test/io_SUITE.erl @@ -1,4 +1,3 @@ -%% -*- coding: utf-8 -*- %% %% %CopyrightBegin% %% diff --git a/lib/stdlib/test/io_proto_SUITE.erl b/lib/stdlib/test/io_proto_SUITE.erl index e16ba55481..76a8109a8d 100644 --- a/lib/stdlib/test/io_proto_SUITE.erl +++ b/lib/stdlib/test/io_proto_SUITE.erl @@ -147,8 +147,7 @@ unicode_prompt(Config) when is_list(Config) -> %% And one with oldshell ?line rtnode([{putline,""}, {putline, "2."}, - {getline_re, ".*2."}, - {getline, "2"}, + {getline_re, ".*2$"}, {putline, "shell:prompt_func({io_proto_SUITE,uprompt})."}, {getline_re, ".*default"}, {putline, "io:get_line('')."}, @@ -263,8 +262,7 @@ setopts_getopts(Config) when is_list(Config) -> %% And one with oldshell ?line rtnode([{putline,""}, {putline, "2."}, - {getline_re, ".*2."}, - {getline, "2"}, + {getline_re, ".*2$"}, {putline, "lists:keyfind(binary,1,io:getopts())."}, {getline_re, ".*{binary,false}"}, {putline, "io:get_line('')."}, @@ -467,8 +465,7 @@ unicode_options(Config) when is_list(Config) -> end, ?line rtnode([{putline,""}, {putline, "2."}, - {getline_re, ".*2."}, - {getline, "2"}, + {getline_re, ".*2$"}, {putline, "lists:keyfind(encoding,1,io:getopts())."}, {getline_re, ".*{encoding,latin1}"}, {putline, "io:format(\"~ts~n\",[[1024]])."}, @@ -701,8 +698,7 @@ binary_options(Config) when is_list(Config) -> old -> ok; new -> - ?line rtnode([{putline,""}, - {putline, "2."}, + ?line rtnode([{putline, "2."}, {getline, "2"}, {putline, "lists:keyfind(binary,1,io:getopts())."}, {getline, "{binary,false}"}, @@ -720,10 +716,8 @@ binary_options(Config) when is_list(Config) -> ],[]) end, %% And one with oldshell - ?line rtnode([{putline,""}, - {putline, "2."}, - {getline_re, ".*2."}, - {getline, "2"}, + ?line rtnode([{putline, "2."}, + {getline_re, ".*2$"}, {putline, "lists:keyfind(binary,1,io:getopts())."}, {getline_re, ".*{binary,false}"}, {putline, "io:get_line('')."}, diff --git a/lib/stdlib/test/lists_SUITE.erl b/lib/stdlib/test/lists_SUITE.erl index b56f0b39d8..cd7210f8ec 100644 --- a/lib/stdlib/test/lists_SUITE.erl +++ b/lib/stdlib/test/lists_SUITE.erl @@ -2532,8 +2532,8 @@ otp_5939(Config) when is_list(Config) -> ?line [] = lists:filter(Pred, []), ?line {'EXIT', _} = (catch lists:partition(func, [])), ?line {[],[]} = lists:partition(Pred, []), - ?line {'EXIT', _} = (catch lists:zf(func, [])), - ?line [] = lists:zf(Fun1, []), + ?line {'EXIT', _} = (catch lists:filtermap(func, [])), + ?line [] = lists:filtermap(Fun1, []), ?line {'EXIT', _} = (catch lists:foreach(func, [])), ?line ok = lists:foreach(Fun1, []), ?line {'EXIT', _} = (catch lists:mapfoldl(func, [], [])), diff --git a/lib/stdlib/test/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl index a9ea78a58b..5f9244b479 100644 --- a/lib/stdlib/test/qlc_SUITE.erl +++ b/lib/stdlib/test/qlc_SUITE.erl @@ -2544,7 +2544,7 @@ info(Config) when is_list(Config) -> ets:delete(E)">>, <<"Q1 = qlc:q([W || W <- [a,b]]), - Q2 = qlc:q([Z || Z <- qlc:sort([1,2,300])], unique), + Q2 = qlc:q([Z || Z <- qlc:sort([55296,56296,57296])], unique), Q3 = qlc:q([{X,Y} || X <- qlc:keysort([2], [{1,a}]), Y <- qlc:append([Q1, Q2]), X > Y]), @@ -2552,7 +2552,7 @@ info(Config) when is_list(Config) -> [{generate, P1, {list, [{1,a}]}}, {generate, P2, {append, [{list, [a,b]}, {qlc, T2, [{generate, P3, - {sort, {list,[1,2,300]},[]}}], + {sort, {list,[55296,56296,57296]},[]}}], [{cache,ets},{unique,true}]}]}},F], []} = i(Q3, cache_all), {tuple, _, [{var,_,'X'}, {var,_,'Y'}]} = binary_to_term(T1), @@ -2562,7 +2562,7 @@ info(Config) when is_list(Config) -> {var, _, 'Z'} = binary_to_term(T2), {op, _, '>', {var, _, 'X'}, {var, _, 'Y'}} = binary_to_term(F), true = binary_to_list(<< - \"beginV1=qlc:q([Z||Z<-qlc:sort([1,2,300],[])],[{unique,true}]),\" + \"beginV1=qlc:q([Z||Z<-qlc:sort([55296,56296,57296],[])],[{unique,true}]),\" \"qlc:q([{X,Y}||X<-[{1,a}],Y<-qlc:append([[a,b],V1]),X>Y])end\" >>) == format_info(Q3, true)">>, @@ -6607,12 +6607,12 @@ otp_7232(Config) when is_list(Config) -> {nil,_}]} = qlc:info(qlc:sort(L),{format,abstract_code})">>, - <<"Q1 = qlc:q([X || X <- [1000,2000]]), + <<"Q1 = qlc:q([X || X <- [55296,56296]]), Q = qlc:sort(Q1, {order, fun(A,B)-> A>B end}), - \"qlc:sort([1000,2000],[{order,fun'-function/0-fun-2-'/2}])\" = + \"qlc:sort([55296,56296],[{order,fun'-function/0-fun-2-'/2}])\" = format_info(Q, true), AC = qlc:info(Q, {format, abstract_code}), - \"qlc:sort([1000,2000], [{order,fun '-function/0-fun-2-'/2}])\" = + \"qlc:sort([55296,56296], [{order,fun '-function/0-fun-2-'/2}])\" = binary_to_list(iolist_to_binary(erl_pp:expr(AC)))">>, %% OTP-7234. erl_parse:abstract() handles bit strings diff --git a/lib/stdlib/test/qlc_SUITE_data/join_info_compat.erl b/lib/stdlib/test/qlc_SUITE_data/join_info_compat.erl index e0db132c47..56c998f761 100644 --- a/lib/stdlib/test/qlc_SUITE_data/join_info_compat.erl +++ b/lib/stdlib/test/qlc_SUITE_data/join_info_compat.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2008-2011. All Rights Reserved. +%% Copyright Ericsson AB 2008-2013. 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 @@ -515,7 +515,7 @@ create_handle() -> $.: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, $`:8/integer-unit:1-unsigned-big, $N:8/integer-unit:1-unsigned-big, $a:8/integer-unit:1-unsigned-big, @@ -523,16 +523,16 @@ create_handle() -> $-: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, + $ä: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, + $Ê: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, @@ -541,19 +541,19 @@ create_handle() -> $\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, + $¥: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, $":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, + $þ: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>>, <<$\203:8/integer-unit:1-unsigned-big, $P:8/integer-unit:1-unsigned-big, $\000:8/integer-unit:1-unsigned-big, @@ -562,7 +562,7 @@ create_handle() -> $<: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, $`:8/integer-unit:1-unsigned-big, $N:8/integer-unit:1-unsigned-big, $a:8/integer-unit:1-unsigned-big, @@ -570,16 +570,16 @@ create_handle() -> $-: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, + $ä: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, + $Î: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, @@ -588,22 +588,22 @@ create_handle() -> $\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, + $¥: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, + $ð: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, + $ñ: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, + $ª: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>>, + $ý: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, @@ -612,51 +612,51 @@ create_handle() -> $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, $`: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, $/:8/integer-unit:1-unsigned-big, $H: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, + $¶: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, + $Ò: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, + $£: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, + $Ç: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, + $È: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, + $¨: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, + $µ: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, @@ -664,7 +664,7 @@ create_handle() -> $\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, + $Ö: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, @@ -708,24 +708,24 @@ create_handle() -> $*: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, $`: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, $/:8/integer-unit:1-unsigned-big, $H:8/integer-unit:1-unsigned-big, - $�: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, + $¶: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, $):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, $e:8/integer-unit:1-unsigned-big, $\211:8/integer-unit:1-unsigned-big, $E:8/integer-unit:1-unsigned-big, @@ -737,7 +737,7 @@ create_handle() -> $/: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, + $Ì: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>>, @@ -749,33 +749,33 @@ create_handle() -> $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, $`: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, + $Ï: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, + $ú: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, + $æ: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, + $Ö:8/integer-unit:1-unsigned-big, $\222:8/integer-unit:1-unsigned-big, - $�: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, + $Ô:8/integer-unit:1-unsigned-big, $D:8/integer-unit:1-unsigned-big, - $�: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, @@ -791,7 +791,7 @@ create_handle() -> $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, + $£: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, @@ -800,18 +800,18 @@ create_handle() -> $\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, + $¤: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, + $¤: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, + $Ï: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, + $Ì: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, @@ -1398,7 +1398,7 @@ lookup_handle() -> $.: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, $`:8/integer-unit:1-unsigned-big, $N:8/integer-unit:1-unsigned-big, $a:8/integer-unit:1-unsigned-big, @@ -1406,16 +1406,16 @@ lookup_handle() -> $-: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, + $Ì: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, $\000:8/integer-unit:1-unsigned-big, $\n:8/integer-unit:1-unsigned-big, $0:8/integer-unit:1-unsigned-big, @@ -1424,19 +1424,19 @@ lookup_handle() -> $\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, + $¦: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, $":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>>, + $Þ: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, @@ -1445,7 +1445,7 @@ lookup_handle() -> $.: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, $`:8/integer-unit:1-unsigned-big, $N:8/integer-unit:1-unsigned-big, $a:8/integer-unit:1-unsigned-big, @@ -1453,16 +1453,16 @@ lookup_handle() -> $-: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, + $Ì: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, $\000:8/integer-unit:1-unsigned-big, $\n:8/integer-unit:1-unsigned-big, $0:8/integer-unit:1-unsigned-big, @@ -1471,19 +1471,19 @@ lookup_handle() -> $\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, + $¦: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, + $ :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>>, + $ä: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, @@ -1525,25 +1525,25 @@ lookup_handle() -> $+: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, $`: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, $/: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, + $µ: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, + $Ò: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, @@ -1555,10 +1555,10 @@ lookup_handle() -> $/: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, + $×: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>>, + $Û: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, @@ -1567,33 +1567,33 @@ lookup_handle() -> $\\: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, $`: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, + $Ï: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, + $ú: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, + $æ: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, + $Ö:8/integer-unit:1-unsigned-big, $\222:8/integer-unit:1-unsigned-big, - $�: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, + $Ô:8/integer-unit:1-unsigned-big, $D:8/integer-unit:1-unsigned-big, - $�: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, @@ -1605,7 +1605,7 @@ lookup_handle() -> $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, $`:8/integer-unit:1-unsigned-big, $\n:8/integer-unit:1-unsigned-big, $\003:8/integer-unit:1-unsigned-big, @@ -1616,7 +1616,7 @@ lookup_handle() -> $>: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, + $µ: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, @@ -1630,7 +1630,7 @@ lookup_handle() -> $\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, + $Ù:8/integer-unit:1-unsigned-big, $\031:8/integer-unit:1-unsigned-big, $M:8/integer-unit:1-unsigned-big>>} end, diff --git a/lib/stdlib/test/re_SUITE.erl b/lib/stdlib/test/re_SUITE.erl index 500f5fadb9..c05674b4f8 100644 --- a/lib/stdlib/test/re_SUITE.erl +++ b/lib/stdlib/test/re_SUITE.erl @@ -1,8 +1,7 @@ -%% -*- coding: utf-8 -*- %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2008-2012. All Rights Reserved. +%% Copyright Ericsson AB 2008-2013. 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/re_testoutput1_replacement_test.erl b/lib/stdlib/test/re_testoutput1_replacement_test.erl index 8f8d8762ad..30ebab277a 100644 --- a/lib/stdlib/test/re_testoutput1_replacement_test.erl +++ b/lib/stdlib/test/re_testoutput1_replacement_test.erl @@ -1,8 +1,7 @@ -%% -*- coding: utf-8 -*- %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2008-2012. All Rights Reserved. +%% Copyright Ericsson AB 2008-2013. 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/re_testoutput1_split_test.erl b/lib/stdlib/test/re_testoutput1_split_test.erl index 4fc85b95c0..0a7f54f2dc 100644 --- a/lib/stdlib/test/re_testoutput1_split_test.erl +++ b/lib/stdlib/test/re_testoutput1_split_test.erl @@ -1,8 +1,7 @@ -%% -*- coding: utf-8 -*- %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2008-2012. All Rights Reserved. +%% Copyright Ericsson AB 2008-2013. 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/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl index 681c154463..233ba0764f 100644 --- a/lib/stdlib/test/shell_SUITE.erl +++ b/lib/stdlib/test/shell_SUITE.erl @@ -2600,9 +2600,9 @@ otp_7232(doc) -> "OTP-7232. qlc:info() bug."; otp_7232(suite) -> []; otp_7232(Config) when is_list(Config) -> - Info = <<"qlc:info(qlc:sort(qlc:q([X || X <- [1000,2000]]), " + Info = <<"qlc:info(qlc:sort(qlc:q([X || X <- [55296,56296]]), " "{order, fun(A,B)-> A>B end})).">>, - "qlc:sort([1000,2000],\n" + "qlc:sort([55296,56296],\n" " [{order,\n" " fun(A, B) ->\n" " A > B\n" @@ -2820,7 +2820,7 @@ otp_10302(Config) when is_list(Config) -> "ok.\n** exception error: an error occurred when evaluating" " an arithmetic expression\n in operator '/'/2\n" - " called as <<\"�\">> / <<\"�\">>.\n" = t({Node,Test7}), + " called as <<\"ª\">> / <<\"ª\">>.\n" = t({Node,Test7}), Test8 = <<"begin A = [1089], diff --git a/lib/stdlib/test/string_SUITE.erl b/lib/stdlib/test/string_SUITE.erl index 96e653985f..fccd1bef95 100644 --- a/lib/stdlib/test/string_SUITE.erl +++ b/lib/stdlib/test/string_SUITE.erl @@ -1,8 +1,7 @@ -%% -*- coding: utf-8 -*- %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2004-2012. All Rights Reserved. +%% Copyright Ericsson AB 2004-2013. 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_3.erl b/lib/stdlib/test/supervisor_3.erl new file mode 100644 index 0000000000..31b3037d6f --- /dev/null +++ b/lib/stdlib/test/supervisor_3.erl @@ -0,0 +1,45 @@ +%% +%% %CopyrightBegin% +%% +%% Copyright Ericsson AB 1996-2011. All Rights Reserved. +%% +%% The contents of this file are subject to the Erlang Public License, +%% Version 1.1, (the "License"); you may not use this file except in +%% compliance with the License. You should have received a copy of the +%% Erlang Public License along with this software. If not, it can be +%% retrieved online at http://www.erlang.org/. +%% +%% Software distributed under the License is distributed on an "AS IS" +%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See +%% the License for the specific language governing rights and limitations +%% under the License. +%% +%% %CopyrightEnd% +%% +%% Description: Simulates the behaviour that a child process may have. +%% Is used by the supervisor_SUITE test suite. +-module(supervisor_3). + +-export([start_child/2, init/1]). + +-export([handle_call/3, handle_info/2, terminate/2]). + +start_child(Name, Caller) -> + gen_server:start_link(?MODULE, [Name, Caller], []). + +init([Name, Caller]) -> + Caller ! {Name, self()}, + receive + {Result, Caller} -> + Result + end. + +handle_call(Req, _From, State) -> + {reply, Req, State}. + +handle_info(_, State) -> + {noreply, State}. + +terminate(_Reason, Time) -> + timer:sleep(Time), + ok. diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl index 569c66959e..ff5be6bb95 100644 --- a/lib/stdlib/test/supervisor_SUITE.erl +++ b/lib/stdlib/test/supervisor_SUITE.erl @@ -53,9 +53,10 @@ %% Restart strategy tests -export([ one_for_one/1, one_for_one_escalation/1, one_for_all/1, - one_for_all_escalation/1, + one_for_all_escalation/1, one_for_all_other_child_fails_restart/1, simple_one_for_one/1, simple_one_for_one_escalation/1, rest_for_one/1, rest_for_one_escalation/1, + rest_for_one_other_child_fails_restart/1, simple_one_for_one_extra/1, simple_one_for_one_shutdown/1]). %% Misc tests @@ -107,12 +108,14 @@ groups() -> {restart_one_for_one, [], [one_for_one, one_for_one_escalation]}, {restart_one_for_all, [], - [one_for_all, one_for_all_escalation]}, + [one_for_all, one_for_all_escalation, + one_for_all_other_child_fails_restart]}, {restart_simple_one_for_one, [], [simple_one_for_one, simple_one_for_one_shutdown, simple_one_for_one_extra, simple_one_for_one_escalation]}, {restart_rest_for_one, [], - [rest_for_one, rest_for_one_escalation]}]. + [rest_for_one, rest_for_one_escalation, + rest_for_one_other_child_fails_restart]}]. init_per_suite(Config) -> Config. @@ -879,6 +882,57 @@ one_for_all_escalation(Config) when is_list(Config) -> %%------------------------------------------------------------------------- +%% Test that the supervisor terminates a restarted child when a different +%% child fails to start. +one_for_all_other_child_fails_restart(Config) when is_list(Config) -> + process_flag(trap_exit, true), + Self = self(), + Child1 = {child1, {supervisor_3, start_child, [child1, Self]}, + permanent, 1000, worker, []}, + Child2 = {child2, {supervisor_3, start_child, [child2, Self]}, + permanent, 1000, worker, []}, + Children = [Child1, Child2], + StarterFun = fun() -> + {ok, SupPid} = start_link({ok, {{one_for_all, 3, 3600}, Children}}), + Self ! {sup_pid, SupPid}, + receive {stop, Self} -> ok end + end, + StarterPid = spawn_link(StarterFun), + Ok = {{ok, undefined}, Self}, + %% Let the children start. + Child1Pid = receive {child1, Pid1} -> Pid1 end, + Child1Pid ! Ok, + Child2Pid = receive {child2, Pid2} -> Pid2 end, + Child2Pid ! Ok, + %% Supervisor started. + SupPid = receive {sup_pid, Pid} -> Pid end, + link(SupPid), + exit(Child1Pid, die), + %% Let child1 restart but don't let child2. + Child1Pid2 = receive {child1, Pid3} -> Pid3 end, + Child1Pid2Ref = erlang:monitor(process, Child1Pid2), + Child1Pid2 ! Ok, + Child2Pid2 = receive {child2, Pid4} -> Pid4 end, + Child2Pid2 ! {{stop, normal}, Self}, + %% Check child1 is terminated. + receive + {'DOWN', Child1Pid2Ref, _, _, shutdown} -> + ok; + {_childName, _Pid} -> + exit(SupPid, kill), + check_exit([StarterPid, SupPid]), + test_server:fail({restarting_child_not_terminated, Child1Pid2}) + end, + %% Let the restart complete. + Child1Pid3 = receive {child1, Pid5} -> Pid5 end, + Child1Pid3 ! Ok, + Child2Pid3 = receive {child2, Pid6} -> Pid6 end, + Child2Pid3 ! Ok, + StarterPid ! {stop, Self}, + check_exit([StarterPid, SupPid]). + + +%%------------------------------------------------------------------------- %% Test the simple_one_for_one base case. simple_one_for_one(Config) when is_list(Config) -> process_flag(trap_exit, true), @@ -1044,6 +1098,52 @@ rest_for_one_escalation(Config) when is_list(Config) -> terminate(SupPid, CPid1, child1, abnormal), check_exit([CPid2, SupPid]). + +%%------------------------------------------------------------------------- +%% Test that the supervisor terminates a restarted child when a different +%% child fails to start. +rest_for_one_other_child_fails_restart(Config) when is_list(Config) -> + process_flag(trap_exit, true), + Self = self(), + Child1 = {child1, {supervisor_3, start_child, [child1, Self]}, + permanent, 1000, worker, []}, + Child2 = {child2, {supervisor_3, start_child, [child2, Self]}, + permanent, 1000, worker, []}, + Children = [Child1, Child2], + StarterFun = fun() -> + {ok, SupPid} = start_link({ok, {{rest_for_one, 3, 3600}, Children}}), + Self ! {sup_pid, SupPid}, + receive {stop, Self} -> ok end + end, + StarterPid = spawn_link(StarterFun), + Ok = {{ok, undefined}, Self}, + %% Let the children start. + Child1Pid = receive {child1, Pid1} -> Pid1 end, + Child1Pid ! Ok, + Child2Pid = receive {child2, Pid2} -> Pid2 end, + Child2Pid ! Ok, + %% Supervisor started. + SupPid = receive {sup_pid, Pid} -> Pid end, + link(SupPid), + exit(Child1Pid, die), + %% Let child1 restart but don't let child2. + Child1Pid2 = receive {child1, Pid3} -> Pid3 end, + Child1Pid2 ! Ok, + Child2Pid2 = receive {child2, Pid4} -> Pid4 end, + Child2Pid2 ! {{stop, normal}, Self}, + %% Let child2 restart. + receive + {child2, Child2Pid3} -> + Child2Pid3 ! Ok; + {child1, _Child1Pid3} -> + exit(SupPid, kill), + check_exit([StarterPid, SupPid]), + test_server:fail({restarting_started_child, Child1Pid2}) + end, + StarterPid ! {stop, Self}, + check_exit([StarterPid, SupPid]). + + %%------------------------------------------------------------------------- %% Test that the supervisor does not hang forever if the child unliks %% and then is terminated by the supervisor. diff --git a/lib/stdlib/test/zip_SUITE.erl b/lib/stdlib/test/zip_SUITE.erl index 7233c061ef..a57641ef62 100644 --- a/lib/stdlib/test/zip_SUITE.erl +++ b/lib/stdlib/test/zip_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2006-2011. All Rights Reserved. +%% Copyright Ericsson AB 2006-2013. 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 @@ -109,13 +109,32 @@ borderline_test(Size, TempDir) -> ok. unzip_list(Archive, Name) -> - case os:find_executable("unzip") of - Unzip when is_list(Unzip) -> + case unix_unzip_exists() of + true -> unzip_list1(Archive, Name); _ -> ok end. +%% Used to do os:find_executable() to check if unzip exists, but on +%% some hosts that would give an unzip program which did not take the +%% "-Z" option. +%% Here we check that "unzip -Z" (which should display usage) and +%% check that it exists with status 0. +unix_unzip_exists() -> + case os:type() of + {unix,_} -> + Port = open_port({spawn,"unzip -Z > /dev/null"}, [exit_status]), + receive + {Port,{exit_status,0}} -> + true; + {Port,{exit_status,_Fail}} -> + false + end; + _ -> + false + end. + unzip_list1(Archive, Name) -> Expect = Name ++ "\n", cmd_expect("unzip -Z -1 " ++ Archive, Expect). |