From 998a64b2237086ebc776de4c72b0df8733e1c4ef Mon Sep 17 00:00:00 2001 From: Hans Bolinder Date: Sat, 16 Feb 2013 19:04:29 +0100 Subject: Fix some Unicode issues Also let the Erlang shell use the new function io:printable_range(). --- lib/stdlib/test/epp_SUITE.erl | 33 +++++++++++++++++++++++++++++++-- lib/stdlib/test/erl_pp_SUITE.erl | 40 +++++++++++++++++++++++++++++++++++++--- lib/stdlib/test/shell_SUITE.erl | 30 +++++++++++++++++++----------- 3 files changed, 87 insertions(+), 16 deletions(-) (limited to 'lib/stdlib/test') 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/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl index f22df96697..cff394bf09 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) @@ -2815,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 <<170>> / <<170>>.\n" = t(Test7), + " called as <<170>> / <<170>>.\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) -> -- cgit v1.2.3 From d1b25f03be6c3c2bf1fd60b156f5974916f0a552 Mon Sep 17 00:00:00 2001 From: Patrik Nyblom Date: Thu, 14 Feb 2013 15:35:36 +0100 Subject: Add testcase for +pc and io:printable_range/0 Also fixed otp_10302 to test both on a node with +pc unicode and a node with +pc latin1. --- lib/stdlib/test/io_SUITE.erl | 96 ++++++++++++++++++++++++++++++++++++++++++-- 1 file changed, 93 insertions(+), 3 deletions(-) (limited to 'lib/stdlib/test') diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl index aa698ecaa2..3d4945f30e 100644 --- a/lib/stdlib/test/io_SUITE.erl +++ b/lib/stdlib/test/io_SUITE.erl @@ -29,9 +29,12 @@ 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, + 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). -ifdef(debug). @@ -66,6 +69,7 @@ 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, + printable_range, io_lib_print_binary_depth_one, otp_10302, otp_10755, otp_10836]. groups() -> @@ -2026,6 +2030,80 @@ 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) -> @@ -2040,10 +2118,22 @@ 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), -- cgit v1.2.3 From ae63487868032a31b7a8b2e44b49f4de07c9ec71 Mon Sep 17 00:00:00 2001 From: Patrik Nyblom Date: Thu, 14 Feb 2013 15:37:16 +0100 Subject: Fix io_proto_SUITE to handle the new io_lib_pretty:print --- lib/stdlib/test/io_proto_SUITE.erl | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) (limited to 'lib/stdlib/test') 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. -- cgit v1.2.3 From ef6269721f22015083d08209e99b402107382d37 Mon Sep 17 00:00:00 2001 From: Patrik Nyblom Date: Thu, 14 Feb 2013 16:34:37 +0100 Subject: Make shell_SUITE:otp_10302 use +pc unicode when needed --- lib/stdlib/test/shell_SUITE.erl | 19 +++++++++++++------ 1 file changed, 13 insertions(+), 6 deletions(-) (limited to 'lib/stdlib/test') diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl index f22df96697..fd64f9fc7e 100644 --- a/lib/stdlib/test/shell_SUITE.erl +++ b/lib/stdlib/test/shell_SUITE.erl @@ -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}]), @@ -2755,7 +2758,7 @@ otp_10302(Config) when is_list(Config) -> <<"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,7 +2779,7 @@ 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 = @@ -2785,9 +2788,10 @@ otp_10302(Config) when is_list(Config) -> 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) @@ -2839,7 +2843,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, @@ -2871,8 +2875,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 +2900,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) -> -- cgit v1.2.3 From 5fcb4b742820ab66e646f8561ed9f32b253bca9a Mon Sep 17 00:00:00 2001 From: Patrik Nyblom Date: Mon, 18 Feb 2013 16:42:51 +0100 Subject: Correct misspelled comments and space at lin ends --- lib/stdlib/test/io_SUITE.erl | 27 ++++++++++++++------------- 1 file changed, 14 insertions(+), 13 deletions(-) (limited to 'lib/stdlib/test') diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl index 3d4945f30e..1e095733cf 100644 --- a/lib/stdlib/test/io_SUITE.erl +++ b/lib/stdlib/test/io_SUITE.erl @@ -2035,24 +2035,24 @@ 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, + {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, + {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, + {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, + {ok, UNode} = test_server:start_node(printable_range_unicode, slave, [{args, " +pcunicode -pa " ++ Pa}]), - {ok, LNode} = test_server:start_node(printable_range_latin1, slave, + {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, + {error, _} = test_server:start_node(printable_range_unnicode, slave, [{args, " +pcunnicode -pa " ++ Pa}]), PrettyOptions = [{column,1}, {line_length,109}, @@ -2092,17 +2092,16 @@ printable_range(Suite) when is_list(Suite) -> <<1024/utf8,1025/utf8>>}]]))), 125 = lists:max(lists:flatten(rpc:call(LNode,io_lib,format, ["~tp", - [{hello, + [{hello, <<1024/utf8,1025/utf8>>}]]))), 125 = lists:max(lists:flatten(rpc:call(DNode,io_lib,format, ["~tp", - [{hello, + [{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"; @@ -2119,14 +2118,16 @@ otp_10302(doc) -> "OTP-10302. Unicode"; otp_10302(Suite) when is_list(Suite) -> Pa = filename:dirname(code:which(?MODULE)), - {ok, UNode} = test_server:start_node(printable_range_unicode, slave, + {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, + {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}\"/utf8>>" = rpc:call(UNode,?MODULE,pretty, + [<<"\x{400}"/utf8>>, -1]), - "<<\"\x{400}foo\"/utf8>>" = rpc:call(UNode,?MODULE,pretty,[<<"\x{400}foo"/utf8>>, 2]), + "<<\"\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]), -- cgit v1.2.3 From 2a79b74ac371387ce338bacf979f9ca32447b302 Mon Sep 17 00:00:00 2001 From: Patrik Nyblom Date: Tue, 19 Feb 2013 10:27:14 +0100 Subject: Adapt stdlib tests to ~tp detecting latin1 binaries --- lib/stdlib/test/escript_SUITE.erl | 2 +- lib/stdlib/test/escript_SUITE_data/unicode1 | 2 +- lib/stdlib/test/io_SUITE.erl | 4 ++-- lib/stdlib/test/shell_SUITE.erl | 4 ++-- 4 files changed, 6 insertions(+), 6 deletions(-) (limited to 'lib/stdlib/test') 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/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl index 1e095733cf..9f828c6d2d 100644 --- a/lib/stdlib/test/io_SUITE.erl +++ b/lib/stdlib/test/io_SUITE.erl @@ -2139,8 +2139,8 @@ otp_10302(Suite) when is_list(Suite) -> "<<\"ä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>>]), diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl index cff394bf09..990b1f5eb2 100644 --- a/lib/stdlib/test/shell_SUITE.erl +++ b/lib/stdlib/test/shell_SUITE.erl @@ -2817,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({Node,Test7}), + " called as <<\"ª\">> / <<\"ª\">>.\n" = t({Node,Test7}), Test8 = <<"begin A = [1089], -- cgit v1.2.3