diff options
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r-- | lib/stdlib/test/epp_SUITE.erl | 33 | ||||
-rw-r--r-- | lib/stdlib/test/erl_pp_SUITE.erl | 40 | ||||
-rw-r--r-- | lib/stdlib/test/escript_SUITE.erl | 2 | ||||
-rwxr-xr-x | lib/stdlib/test/escript_SUITE_data/unicode1 | 2 | ||||
-rw-r--r-- | lib/stdlib/test/ets_SUITE.erl | 116 | ||||
-rw-r--r-- | lib/stdlib/test/filelib_SUITE.erl | 40 | ||||
-rw-r--r-- | lib/stdlib/test/io_SUITE.erl | 143 | ||||
-rw-r--r-- | lib/stdlib/test/io_proto_SUITE.erl | 6 | ||||
-rw-r--r-- | lib/stdlib/test/shell_SUITE.erl | 32 |
9 files changed, 357 insertions, 57 deletions
diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl index 041d521514..b2f1aa955a 100644 --- a/lib/stdlib/test/epp_SUITE.erl +++ b/lib/stdlib/test/epp_SUITE.erl @@ -25,7 +25,7 @@ variable_1/1, otp_4870/1, otp_4871/1, otp_5362/1, pmod/1, not_circular/1, skip_header/1, otp_6277/1, otp_7702/1, otp_8130/1, overload_mac/1, otp_8388/1, otp_8470/1, otp_8503/1, - otp_8562/1, otp_8665/1, otp_8911/1, otp_10302/1]). + otp_8562/1, otp_8665/1, otp_8911/1, otp_10302/1, otp_10820/1]). -export([epp_parse_erl_form/2]). @@ -67,7 +67,7 @@ all() -> {group, variable}, otp_4870, otp_4871, otp_5362, pmod, not_circular, skip_header, otp_6277, otp_7702, otp_8130, overload_mac, otp_8388, otp_8470, otp_8503, otp_8562, - otp_8665, otp_8911, otp_10302]. + otp_8665, otp_8911, otp_10302, otp_10820]. groups() -> [{upcase_mac, [], [upcase_mac_1, upcase_mac_2]}, @@ -1359,6 +1359,30 @@ encoding_nocom(Enc, File) -> ok = file:close(Fd), E = epp:read_encoding(File, Options). +otp_10820(doc) -> + "OTP-10820. Unicode filenames."; +otp_10820(suite) -> + []; +otp_10820(Config) when is_list(Config) -> + L = [915,953,959,973,957,953,954,959,957,964], + Dir = ?config(priv_dir, Config), + File = filename:join(Dir, L++".erl"), + C1 = <<"%% coding: utf-8\n -module(any).">>, + ok = do_otp_10820(File, C1, "+pc latin1"), + ok = do_otp_10820(File, C1, "+pc unicode"), + C2 = <<"\n-module(any).">>, + ok = do_otp_10820(File, C2, "+pc latin1"), + ok = do_otp_10820(File, C2, "+pc unicode"). + +do_otp_10820(File, C, PC) -> + {ok,Node} = start_node(erl_pp_helper, "+fnu " ++ PC), + ok = rpc:call(Node, file, write_file, [File, C]), + {ok,[{attribute,1,file,{File,1}}, + {attribute,2,module,any}, + {eof,2}]} = rpc:call(Node, epp, parse_file, [File, [],[]]), + true = test_server:stop_node(Node), + ok. + check(Config, Tests) -> eval_tests(Config, fun check_test/2, Tests). @@ -1475,3 +1499,8 @@ ln2({error,M}) -> {error,ln2(M)}; ln2(M) -> M. + +%% +fnu means a peer node has to be started; slave will not do +start_node(Name, Xargs) -> + ?line PA = filename:dirname(code:which(?MODULE)), + test_server:start_node(Name, peer, [{args, "-pa " ++ PA ++ " " ++ Xargs}]). diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl index 37be61d665..9c0a43abcc 100644 --- a/lib/stdlib/test/erl_pp_SUITE.erl +++ b/lib/stdlib/test/erl_pp_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2006-2012. 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 @@ -49,7 +49,7 @@ 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_10302/1, otp_10820/1]). %% Internal export. -export([ehook/6]). @@ -80,7 +80,8 @@ groups() -> {attributes, [], [misc_attrs, import_export]}, {tickets, [], [otp_6321, otp_6911, otp_6914, otp_8150, otp_8238, - otp_8473, otp_8522, otp_8567, otp_8664, otp_9147, otp_10302]}]. + otp_8473, otp_8522, otp_8567, otp_8664, otp_9147, + otp_10302, otp_10820]}]. init_per_suite(Config) -> Config. @@ -1074,6 +1075,34 @@ otp_10302(Config) when is_list(Config) -> unicode_hook({foo,E}, I, P, H) -> erl_pp:expr({call,0,{atom,0,foo},[E]}, I, P, H). +otp_10820(doc) -> + "OTP-10820. Unicode filenames."; +otp_10820(suite) -> []; +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).">>, + ok = do_otp_10820(Config, C2, "+pc latin1"), + ok = do_otp_10820(Config, C2, "+pc unicode"). + +do_otp_10820(Config, C, PC) -> + {ok,Node} = start_node(erl_pp_helper, "+fnu " ++ PC), + L = [915,953,959,973,957,953,954,959,957,964], + FileName = filename(L++".erl", Config), + ok = rpc:call(Node, file, write_file, [FileName, C]), + {ok, _, []} = rpc:call(Node, compile, file, + [FileName, [return,'P',{outdir,?privdir}]]), + PFileName = filename(L++".P", Config), + {ok, Bin} = rpc:call(Node, file, read_file, [PFileName]), + true = test_server:stop_node(Node), + true = file_attr_is_string(binary_to_list(Bin)), + ok. + +file_attr_is_string("-file(\"" ++ _) -> true; +file_attr_is_string([_ | L]) -> + file_attr_is_string(L). + %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% compile(Config, Tests) -> @@ -1247,3 +1276,8 @@ filename(Name, Config) -> fail() -> io:format("failed~n"), ?t:fail(). + +%% +fnu means a peer node has to be started; slave will not do +start_node(Name, Xargs) -> + ?line PA = filename:dirname(code:which(?MODULE)), + test_server:start_node(Name, peer, [{args, "-pa " ++ PA ++ " " ++ Xargs}]). diff --git a/lib/stdlib/test/escript_SUITE.erl b/lib/stdlib/test/escript_SUITE.erl index be8fb1b37a..cf5fb12686 100644 --- a/lib/stdlib/test/escript_SUITE.erl +++ b/lib/stdlib/test/escript_SUITE.erl @@ -913,7 +913,7 @@ unicode(Config) when is_list(Config) -> run(Dir, "unicode1", [<<"escript: exception error: an error occurred when evaluating" " an arithmetic expression\n in operator '/'/2\n " - "called as <<170>> / <<170>>\nExitCode:127">>]), + "called as <<224,170,170>> / <<224,170,170>>\nExitCode:127">>]), run(Dir, "unicode2", [<<"escript: exception error: an error occurred when evaluating" " an arithmetic expression\n in operator '/'/2\n " diff --git a/lib/stdlib/test/escript_SUITE_data/unicode1 b/lib/stdlib/test/escript_SUITE_data/unicode1 index a77574625e..351bb785e5 100755 --- a/lib/stdlib/test/escript_SUITE_data/unicode1 +++ b/lib/stdlib/test/escript_SUITE_data/unicode1 @@ -6,7 +6,7 @@ main(_) -> ok = io:setopts([{encoding,unicode}]), _D = erlang:system_flag(backtrace_depth, 0), - A = <<"\x{aa}">>, + A = <<"\x{aaa}"/utf8>>, S = lists:flatten(io_lib:format("~p/~p.", [A, A])), {ok, Ts, _} = erl_scan:string(S, 1, [unicode]), {ok, Es} = erl_parse:parse_exprs(Ts), diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl index dc17e5d33c..4a51ef564c 100644 --- a/lib/stdlib/test/ets_SUITE.erl +++ b/lib/stdlib/test/ets_SUITE.erl @@ -96,7 +96,7 @@ misc1_do/1, safe_fixtable_do/1, info_do/1, dups_do/1, heavy_lookup_do/1, heavy_lookup_element_do/1, member_do/1, otp_5340_do/1, otp_7665_do/1, meta_wb_do/1, do_heavy_concurrent/1, tab2file2_do/2, exit_large_table_owner_do/2, - types_do/1, sleeper/0, rpc_externals/0, memory_do/1, + types_do/1, sleeper/0, memory_do/1, ms_tracee_dummy/1, ms_tracee_dummy/2, ms_tracee_dummy/3, ms_tracee_dummy/4 ]). @@ -5989,33 +5989,103 @@ make_ext_ref() -> init_externals() -> case get(externals) of undefined -> - SysDistSz = ets:info(sys_dist,size), - ?line Pa = filename:dirname(code:which(?MODULE)), - ?line {ok, Node} = test_server:start_node(plopp, slave, [{args, " -pa " ++ Pa}]), - ?line Res = case rpc:call(Node, ?MODULE, rpc_externals, []) of - {badrpc, {'EXIT', E}} -> - test_server:fail({rpcresult, E}); - R -> R - end, - ?line test_server:stop_node(Node), - - %% Wait for table 'sys_dist' to stabilize - repeat_while(fun() -> - case ets:info(sys_dist,size) of - SysDistSz -> false; - Sz -> - io:format("Waiting for sys_dist to revert size from ~p to size ~p\n", - [Sz, SysDistSz]), - receive after 1000 -> true end - end - end), + OtherNode = {gurka@sallad, 1}, + Res = {mk_pid(OtherNode, 7645, 8123), + mk_port(OtherNode, 187489773), + mk_ref(OtherNode, [262143, 1293964255, 3291964278])}, put(externals, Res); {_,_,_} -> ok end. -rpc_externals() -> - {self(), make_port(), make_ref()}. +%% +%% Node container constructor functions +%% + +-define(VERSION_MAGIC, 131). +-define(PORT_EXT, 102). +-define(PID_EXT, 103). +-define(NEW_REFERENCE_EXT, 114). + +uint32_be(Uint) when is_integer(Uint), 0 =< Uint, Uint < 1 bsl 32 -> + [(Uint bsr 24) band 16#ff, + (Uint bsr 16) band 16#ff, + (Uint bsr 8) band 16#ff, + Uint band 16#ff]; +uint32_be(Uint) -> + exit({badarg, uint32_be, [Uint]}). + +uint16_be(Uint) when is_integer(Uint), 0 =< Uint, Uint < 1 bsl 16 -> + [(Uint bsr 8) band 16#ff, + Uint band 16#ff]; +uint16_be(Uint) -> + exit({badarg, uint16_be, [Uint]}). + +uint8(Uint) when is_integer(Uint), 0 =< Uint, Uint < 1 bsl 8 -> + Uint band 16#ff; +uint8(Uint) -> + exit({badarg, uint8, [Uint]}). + +mk_pid({NodeName, Creation}, Number, Serial) when is_atom(NodeName) -> + <<?VERSION_MAGIC, NodeNameExt/binary>> = term_to_binary(NodeName), + mk_pid({NodeNameExt, Creation}, Number, Serial); +mk_pid({NodeNameExt, Creation}, Number, Serial) -> + case catch binary_to_term(list_to_binary([?VERSION_MAGIC, + ?PID_EXT, + NodeNameExt, + uint32_be(Number), + uint32_be(Serial), + uint8(Creation)])) of + Pid when is_pid(Pid) -> + Pid; + {'EXIT', {badarg, _}} -> + exit({badarg, mk_pid, [{NodeNameExt, Creation}, Number, Serial]}); + Other -> + exit({unexpected_binary_to_term_result, Other}) + end. + +mk_port({NodeName, Creation}, Number) when is_atom(NodeName) -> + <<?VERSION_MAGIC, NodeNameExt/binary>> = term_to_binary(NodeName), + mk_port({NodeNameExt, Creation}, Number); +mk_port({NodeNameExt, Creation}, Number) -> + case catch binary_to_term(list_to_binary([?VERSION_MAGIC, + ?PORT_EXT, + NodeNameExt, + uint32_be(Number), + uint8(Creation)])) of + Port when is_port(Port) -> + Port; + {'EXIT', {badarg, _}} -> + exit({badarg, mk_port, [{NodeNameExt, Creation}, Number]}); + Other -> + exit({unexpected_binary_to_term_result, Other}) + end. + +mk_ref({NodeName, Creation}, Numbers) when is_atom(NodeName), + is_integer(Creation), + is_list(Numbers) -> + <<?VERSION_MAGIC, NodeNameExt/binary>> = term_to_binary(NodeName), + mk_ref({NodeNameExt, Creation}, Numbers); +mk_ref({NodeNameExt, Creation}, Numbers) when is_binary(NodeNameExt), + is_integer(Creation), + is_list(Numbers) -> + case catch binary_to_term(list_to_binary([?VERSION_MAGIC, + ?NEW_REFERENCE_EXT, + uint16_be(length(Numbers)), + NodeNameExt, + uint8(Creation), + lists:map(fun (N) -> + uint32_be(N) + end, + Numbers)])) of + Ref when is_reference(Ref) -> + Ref; + {'EXIT', {badarg, _}} -> + exit({badarg, mk_ref, [{NodeNameExt, Creation}, Numbers]}); + Other -> + exit({unexpected_binary_to_term_result, Other}) + end. + make_sub_binary(Bin) when is_binary(Bin) -> {_,B} = split_binary(list_to_binary([0,1,3,Bin]), 3), diff --git a/lib/stdlib/test/filelib_SUITE.erl b/lib/stdlib/test/filelib_SUITE.erl index 27078f0914..4a67d68428 100644 --- a/lib/stdlib/test/filelib_SUITE.erl +++ b/lib/stdlib/test/filelib_SUITE.erl @@ -65,19 +65,26 @@ wildcard_one(Config) when is_list(Config) -> ?line {ok,OldCwd} = file:get_cwd(), ?line Dir = filename:join(?config(priv_dir, Config), "wildcard_one"), ?line ok = file:make_dir(Dir), + do_wildcard_1(Dir, + fun(Wc) -> + filelib:wildcard(Wc, Dir, erl_prim_loader) + end), ?line file:set_cwd(Dir), - ?line do_wildcard_1(Dir, fun(Wc) -> filelib:wildcard(Wc) end), + do_wildcard_1(Dir, + fun(Wc) -> + L = filelib:wildcard(Wc), + L = filelib:wildcard(Wc, erl_prim_loader), + L = filelib:wildcard(Wc, "."), + L = filelib:wildcard(Wc, Dir) + end), ?line file:set_cwd(OldCwd), ?line ok = file:del_dir(Dir), ok. wildcard_two(Config) when is_list(Config) -> ?line Dir = filename:join(?config(priv_dir, Config), "wildcard_two"), - ?line DirB = unicode:characters_to_binary(Dir, file:native_name_encoding()), ?line ok = file:make_dir(Dir), ?line do_wildcard_1(Dir, fun(Wc) -> io:format("~p~n",[{Wc,Dir, X = filelib:wildcard(Wc, Dir)}]),X end), - ?line do_wildcard_1(Dir, fun(Wc) -> io:format("~p~n",[{Wc,DirB, X = filelib:wildcard(Wc, DirB)}]), - [unicode:characters_to_list(Y,file:native_name_encoding()) || Y <- X] end), ?line do_wildcard_1(Dir, fun(Wc) -> filelib:wildcard(Wc, Dir++"/") end), case os:type() of {win32,_} -> @@ -130,6 +137,9 @@ do_wildcard_2(Dir, Wcf) -> ?line ["abc","abcdef"] = Wcf("a*{def,}"), ?line ["abc","abcdef"] = Wcf("a*{,def}"), + %% Constant wildcard. + ["abcdef"] = Wcf("abcdef"), + %% Negative tests. ?line [] = Wcf("b*"), ?line [] = Wcf("bufflig"), @@ -157,6 +167,8 @@ do_wildcard_4(Dir, Wcf) -> All = ["a-","aA","aB","aC","a[","a]"], ?line Files = mkfiles(lists:reverse(All), Dir), ?line All = Wcf("a[][A-C-]"), + ["a-"] = Wcf("a[-]"), + ["a["] = Wcf("a["), ?line del(Files), do_wildcard_5(Dir, Wcf). @@ -173,6 +185,7 @@ do_wildcard_5(Dir, Wcf) -> ?line ["blurf/nisse"] = Wcf("*/nisse"), ?line [] = Wcf("mountain/*"), ?line [] = Wcf("xa/gurka"), + ["blurf/nisse"] = Wcf("blurf/nisse"), %% Cleanup ?line del(Files), @@ -233,7 +246,24 @@ do_wildcard_8(Dir, Wcf) -> del(Files), foreach(fun(D) -> ok = file:del_dir(filename:join(Dir, D)) - end, Dirs2 ++ Dirs1 ++ Dirs0). + end, Dirs2 ++ Dirs1 ++ Dirs0), + do_wildcard_9(Dir, Wcf). + +do_wildcard_9(Dir, Wcf) -> + Dirs0 = ["lib","lib/app","lib/app/ebin"], + Dirs = [filename:join(Dir, D) || D <- Dirs0], + [ok = file:make_dir(D) || D <- Dirs], + Files0 = [filename:join("lib/app/ebin", F++".bar") || + F <- ["abc","foo","foobar"]], + Files = [filename:join(Dir, F) || F <- Files0], + [ok = file:write_file(F, <<"some content\n">>) || F <- Files], + Files0 = Wcf("lib/app/ebin/*.bar"), + + %% Cleanup. + del(Files), + [ok = file:del_dir(D) || D <- lists:reverse(Dirs)], + ok. + fold_files(Config) when is_list(Config) -> ?line Dir = filename:join(?config(priv_dir, Config), "fold_files"), diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl index 65a112c966..9f828c6d2d 100644 --- a/lib/stdlib/test/io_SUITE.erl +++ b/lib/stdlib/test/io_SUITE.erl @@ -29,7 +29,11 @@ manpage/1, otp_6708/1, otp_7084/1, otp_7421/1, io_lib_collect_line_3_wb/1, cr_whitespace_in_string/1, io_fread_newlines/1, otp_8989/1, io_lib_fread_literal/1, - io_lib_print_binary_depth_one/1, otp_10302/1, otp_10836/1]). + printable_range/1, + io_lib_print_binary_depth_one/1, otp_10302/1, otp_10755/1, + otp_10836/1]). + +-export([pretty/2]). %-define(debug, true). @@ -65,7 +69,8 @@ all() -> manpage, otp_6708, otp_7084, otp_7421, io_lib_collect_line_3_wb, cr_whitespace_in_string, io_fread_newlines, otp_8989, io_lib_fread_literal, - io_lib_print_binary_depth_one, otp_10302, otp_10836]. + printable_range, + io_lib_print_binary_depth_one, otp_10302, otp_10755, otp_10836]. groups() -> []. @@ -2025,6 +2030,79 @@ io_lib_fread_literal(Suite) when is_list(Suite) -> ?line {done,{ok,[]},[]} = io_lib:fread(C2, "d\n", " d"), ok. + +printable_range(doc) -> + "Check that the printable range set by the user actually works"; +printable_range(Suite) when is_list(Suite) -> + Pa = filename:dirname(code:which(?MODULE)), + {ok, UNode} = test_server:start_node(printable_range_unicode, slave, + [{args, " +pc unicode -pa " ++ Pa}]), + {ok, LNode} = test_server:start_node(printable_range_latin1, slave, + [{args, " +pc latin1 -pa " ++ Pa}]), + {ok, DNode} = test_server:start_node(printable_range_default, slave, + [{args, " -pa " ++ Pa}]), + unicode = rpc:call(UNode,io,printable_range,[]), + latin1 = rpc:call(LNode,io,printable_range,[]), + latin1 = rpc:call(DNode,io,printable_range,[]), + test_server:stop_node(UNode), + test_server:stop_node(LNode), + {ok, UNode} = test_server:start_node(printable_range_unicode, slave, + [{args, " +pcunicode -pa " ++ Pa}]), + {ok, LNode} = test_server:start_node(printable_range_latin1, slave, + [{args, " +pclatin1 -pa " ++ Pa}]), + unicode = rpc:call(UNode,io,printable_range,[]), + latin1 = rpc:call(LNode,io,printable_range,[]), + {error, _} = test_server:start_node(printable_range_unnicode, slave, + [{args, " +pcunnicode -pa " ++ Pa}]), + PrettyOptions = [{column,1}, + {line_length,109}, + {depth,30}, + {max_chars,60}, + {record_print_fun, + fun(_,_) -> no end}, + {encoding,unicode}], + 1025 = lists:max(lists:flatten(rpc:call(UNode,io_lib_pretty,print, + [{hello, [1024,1025]}, + PrettyOptions]))), + 125 = lists:max(lists:flatten(rpc:call(LNode,io_lib_pretty,print, + [{hello, [1024,1025]}, + PrettyOptions]))), + 125 = lists:max(lists:flatten(rpc:call(DNode,io_lib_pretty,print, + [{hello, [1024,1025]}, + PrettyOptions]))), + 1025 = lists:max(lists:flatten(rpc:call(UNode,io_lib_pretty,print, + [{hello, <<1024/utf8,1025/utf8>>}, + PrettyOptions]))), + 125 = lists:max(lists:flatten(rpc:call(LNode,io_lib_pretty,print, + [{hello, <<1024/utf8,1025/utf8>>}, + PrettyOptions]))), + 125 = lists:max(lists:flatten(rpc:call(DNode,io_lib_pretty,print, + [{hello, <<1024/utf8,1025/utf8>>}, + PrettyOptions]))), + + 1025 = lists:max(lists:flatten(rpc:call(UNode,io_lib,format, + ["~tp",[{hello, [1024,1025]}]]))), + 125 = lists:max(lists:flatten(rpc:call(LNode,io_lib,format, + ["~tp",[{hello, [1024,1025]}]]))), + 125 = lists:max(lists:flatten(rpc:call(DNode,io_lib,format, + ["~tp",[{hello, [1024,1025]}]]))), + 1025 = lists:max(lists:flatten(rpc:call(UNode,io_lib,format, + ["~tp", + [{hello, + <<1024/utf8,1025/utf8>>}]]))), + 125 = lists:max(lists:flatten(rpc:call(LNode,io_lib,format, + ["~tp", + [{hello, + <<1024/utf8,1025/utf8>>}]]))), + 125 = lists:max(lists:flatten(rpc:call(DNode,io_lib,format, + ["~tp", + [{hello, + <<1024/utf8,1025/utf8>>}]]))), + test_server:stop_node(UNode), + test_server:stop_node(LNode), + test_server:stop_node(DNode), + ok. + io_lib_print_binary_depth_one(doc) -> "Test binaries printed with a depth of one behave correctly"; io_lib_print_binary_depth_one(Suite) when is_list(Suite) -> @@ -2039,16 +2117,30 @@ io_lib_print_binary_depth_one(Suite) when is_list(Suite) -> otp_10302(doc) -> "OTP-10302. Unicode"; otp_10302(Suite) when is_list(Suite) -> - "\"\x{400}\"" = pretty("\x{400}", -1), - "<<\"\x{400}\"/utf8>>" = pretty(<<"\x{400}"/utf8>>, -1), + Pa = filename:dirname(code:which(?MODULE)), + {ok, UNode} = test_server:start_node(printable_range_unicode, slave, + [{args, " +pc unicode -pa " ++ Pa}]), + {ok, LNode} = test_server:start_node(printable_range_latin1, slave, + [{args, " +pc latin1 -pa " ++ Pa}]), + "\"\x{400}\"" = rpc:call(UNode,?MODULE,pretty,["\x{400}", -1]), + "<<\"\x{400}\"/utf8>>" = rpc:call(UNode,?MODULE,pretty, + [<<"\x{400}"/utf8>>, -1]), + + "<<\"\x{400}foo\"/utf8>>" = rpc:call(UNode,?MODULE,pretty, + [<<"\x{400}foo"/utf8>>, 2]), + "[1024]" = rpc:call(LNode,?MODULE,pretty,["\x{400}", -1]), + "<<208,128>>" = rpc:call(LNode,?MODULE,pretty,[<<"\x{400}"/utf8>>, -1]), + + "<<208,...>>" = rpc:call(LNode,?MODULE,pretty,[<<"\x{400}foo"/utf8>>, 2]), + test_server:stop_node(UNode), + test_server:stop_node(LNode), - "<<\"\x{400}foo\"/utf8>>" = pretty(<<"\x{400}foo"/utf8>>, 2), "<<\"äppl\"/utf8>>" = pretty(<<"äppl"/utf8>>, 2), "<<\"äppl\"/utf8...>>" = pretty(<<"äpple"/utf8>>, 2), "<<\"apel\">>" = pretty(<<"apel">>, 2), "<<\"apel\"...>>" = pretty(<<"apelsin">>, 2), - "<<228,112,112,108>>" = fmt("~tp", [<<"äppl">>]), - "<<228,...>>" = fmt("~tP", [<<"äppl">>, 2]), + "<<\"äppl\">>" = fmt("~tp", [<<"äppl">>]), + "<<\"äppl\"...>>" = fmt("~tP", [<<"äpple">>, 2]), "<<0,0,0,0,0,0,1,0>>" = fmt("~p", [<<256:64/unsigned-integer>>]), "<<0,0,0,0,0,0,1,0>>" = fmt("~tp", [<<256:64/unsigned-integer>>]), @@ -2085,3 +2177,40 @@ otp_10836(Suite) when is_list(Suite) -> S = io_lib:format("~ts", [[<<"äpple"/utf8>>, <<"äpple">>]]), "äppleäpple" = lists:flatten(S), ok. + +otp_10755(doc) -> + "OTP-10755. The 'l' modifier"; +otp_10755(Suite) when is_list(Suite) -> + S = "string", + "\"string\"" = fmt("~p", [S]), + "[115,116,114,105,110,103]" = fmt("~lp", [S]), + "\"string\"" = fmt("~P", [S, 2]), + "[115|...]" = fmt("~lP", [S, 2]), + {'EXIT',{badarg,_}} = (catch fmt("~ltp", [S])), + {'EXIT',{badarg,_}} = (catch fmt("~tlp", [S])), + {'EXIT',{badarg,_}} = (catch fmt("~ltP", [S])), + {'EXIT',{badarg,_}} = (catch fmt("~tlP", [S])), + Text = + "-module(l_mod).\n" + "-export([t/0]).\n" + "t() ->\n" + " S = \"string\",\n" + " io:format(\"~ltp\", [S]),\n" + " io:format(\"~tlp\", [S]),\n" + " io:format(\"~ltP\", [S, 1]),\n" + " io:format(\"~tlP\", [S, 1]).\n", + {ok,l_mod,[{_File,Ws}]} = compile_file("l_mod.erl", Text, Suite), + ["format string invalid (invalid control ~lt)", + "format string invalid (invalid control ~tl)", + "format string invalid (invalid control ~lt)", + "format string invalid (invalid control ~tl)"] = + [lists:flatten(M:format_error(E)) || {_L,M,E} <- Ws], + ok. + +compile_file(File, Text, Config) -> + PrivDir = ?privdir(Config), + Fname = filename:join(PrivDir, File), + ok = file:write_file(Fname, Text), + try compile:file(Fname, [return]) + after ok %file:delete(Fname) + end. diff --git a/lib/stdlib/test/io_proto_SUITE.erl b/lib/stdlib/test/io_proto_SUITE.erl index 299daf0e42..ddcc8dfdab 100644 --- a/lib/stdlib/test/io_proto_SUITE.erl +++ b/lib/stdlib/test/io_proto_SUITE.erl @@ -716,7 +716,7 @@ binary_options(Config) when is_list(Config) -> {getline, "<<\"hej\\n\">>"}, {putline, "io:get_line('')."}, {putline, binary_to_list(<<"\345\344\366"/utf8>>)}, - {getline, "<<\""++binary_to_list(unicode:characters_to_binary(<<"\345\344\366"/utf8>>,latin1,utf8))++"\\n\">>"} + {getline, "<<\""++binary_to_list(<<"\345\344\366"/utf8>>)++"\\n\"/utf8>>"} ],[]) end, %% And one with oldshell @@ -1784,8 +1784,8 @@ get_default_shell() -> {putline, "whereis(user_drv)."}, {getline, "undefined"}],[]), old - catch E:R -> - ?dbg({E,R}), + catch _E:_R -> + ?dbg({_E,_R}), new end. diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl index f22df96697..990b1f5eb2 100644 --- a/lib/stdlib/test/shell_SUITE.erl +++ b/lib/stdlib/test/shell_SUITE.erl @@ -1,7 +1,7 @@ %% %% %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 @@ -2742,6 +2742,9 @@ otp_10302(doc) -> "OTP-10302. Unicode."; otp_10302(suite) -> []; otp_10302(Config) when is_list(Config) -> + {ok,Node} = start_node(shell_suite_helper_2, + "-pa "++?config(priv_dir,Config)++ + " +pc unicode"), Test1 = <<"begin io:setopts([{encoding,utf8}]), @@ -2749,13 +2752,13 @@ otp_10302(Config) when is_list(Config) -> rd(rec, {a = \"\\x{400}\"}), ok = rl(rec) end.">>, - "-record(rec,{a = \"\x{400}\"}).\nok.\n" = t(Test1), + "-record(rec,{a = \"\x{400}\"}).\nok.\n" = t({Node,Test1}), Test3 = <<"io:setopts([{encoding,utf8}]). rd(rec, {a = \"\\x{400}\"}). ok = rp(#rec{}).">>, - "ok.\nrec\n#rec{a = \"\x{400}\"}.\nok.\n" = t(Test3), + "ok.\nrec\n#rec{a = \"\x{400}\"}.\nok.\n" = t({Node,Test3}), Test4 = <<"io:setopts([{encoding,utf8}]). @@ -2766,7 +2769,7 @@ otp_10302(Config) when is_list(Config) -> "ok.\n\"\x{400}\"\nA = \"\x{400}\".\nok.\n" "1: io:setopts([{encoding,utf8}])\n-> ok.\n" "2: A = [1024] = \"\x{400}\"\n-> \"\x{400}\"\n" - "3: b()\n-> ok.\nok.\n" = t(Test4), + "3: b()\n-> ok.\nok.\n" = t({Node,Test4}), Test5 = <<"begin @@ -2776,18 +2779,20 @@ otp_10302(Config) when is_list(Config) -> b(), h() end.">>, - "A = \"\x{400}\".\nok.\n" = t(Test5), + "A = \"\x{400}\".\nok.\n" = t({Node,Test5}), %% One $" is "lost": true = "\x{400}\": command not found" =:= - prompt_err({<<"io:setopts([{encoding,utf8}]). v(\"\x{400}\")."/utf8>>, + prompt_err({Node, + <<"io:setopts([{encoding,utf8}]). v(\"\x{400}\")."/utf8>>, unicode}), "ok.\ndefault\n* Bad prompt function: \"\x{400}\".\n" = - t({<<"io:setopts([{encoding,utf8}]). " + t({Node,<<"io:setopts([{encoding,utf8}]). " "shell:prompt_func(\"\x{400}\")."/utf8>>, unicode}), + rpc:call(Node,shell, prompt_func, [default]), _ = shell:prompt_func(default), %% Test lib:format_exception() (cf. OTP-6554) @@ -2812,10 +2817,10 @@ otp_10302(Config) when is_list(Config) -> {ok, Es} = erl_parse:parse_exprs(Ts), B = erl_eval:new_bindings(), erl_eval:exprs(Es, B).">>, - + "ok.\n** exception error: an error occurred when evaluating" " an arithmetic expression\n in operator '/'/2\n" - " called as <<170>> / <<170>>.\n" = t(Test7), + " called as <<\"�\">> / <<\"�\">>.\n" = t({Node,Test7}), Test8 = <<"begin A = [1089], @@ -2839,7 +2844,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 \"\x{441}\" / \"\x{441}\".\n" = t(Test9), + " called as \"\x{441}\" / \"\x{441}\".\n" = t({Node,Test9}), Test10 = <<"A = {\"1\\xaa\", $\\xaa, @@ -2861,7 +2866,7 @@ otp_10302(Config) when is_list(Config) -> "ok.\n** exception error: no function clause matching \n" " erl_eval:'-inside-an-interpreted-fun-'" "({\"1\xaa\",170,<<\"hi\">>,\n " - " <<\"1\xaa\"/utf8>>}) .\n" = t(Test11), + " <<\"1\xaa\"/utf8>>}) .\n" = t({Node,Test11}), Test12 = <<"fun(a, b) -> false end(65, [1089]).">>, "** exception error: no function clause matching \n" " erl_eval:'-inside-an-interpreted-fun-'(65,[1089])" @@ -2871,8 +2876,9 @@ otp_10302(Config) when is_list(Config) -> fun(a, b) -> false end(65, [1089]).">>, "ok.\n** exception error: no function clause matching \n" " erl_eval:'-inside-an-interpreted-fun-'(65,\"\x{441}\")" - " .\n" = t(Test13), + " .\n" = t({Node,Test13}), + test_server:stop_node(Node), ok. scan(B) -> @@ -2895,6 +2901,8 @@ scan(S0, F) -> [] end. +t({Node,Bin,Enc}) when is_atom(Node),is_binary(Bin), is_atom(Enc) -> + t0({Bin,Enc}, fun() -> start_new_shell(Node) end); t({Node,Bin}) when is_atom(Node),is_binary(Bin) -> t0({Bin,latin1}, fun() -> start_new_shell(Node) end); t(Bin) when is_binary(Bin) -> |