aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test
diff options
context:
space:
mode:
authorHans Bolinder <[email protected]>2012-10-04 15:58:26 +0200
committerHans Bolinder <[email protected]>2013-01-02 10:15:17 +0100
commit300c5466a7c9cfe3ed22bba2a88ba21058406402 (patch)
treeb8c30800b17d5ae98255de2fd2818d8b5d4d6eba /lib/stdlib/test
parent7a884a31cfcaaf23f7920ba1a006aa2855529030 (diff)
downloadotp-300c5466a7c9cfe3ed22bba2a88ba21058406402.tar.gz
otp-300c5466a7c9cfe3ed22bba2a88ba21058406402.tar.bz2
otp-300c5466a7c9cfe3ed22bba2a88ba21058406402.zip
[stdlib, kernel] Introduce Unicode support for Erlang source files
Expect modifications, additions and corrections. There is a kludge in file_io_server and erl_scan:continuation_location() that's not so pleasing.
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r--lib/stdlib/test/epp_SUITE.erl82
-rw-r--r--lib/stdlib/test/erl_pp_SUITE.erl91
-rw-r--r--lib/stdlib/test/erl_scan_SUITE.erl189
-rw-r--r--lib/stdlib/test/escript_SUITE.erl21
-rwxr-xr-xlib/stdlib/test/escript_SUITE_data/unicode114
-rwxr-xr-xlib/stdlib/test/escript_SUITE_data/unicode214
-rwxr-xr-xlib/stdlib/test/escript_SUITE_data/unicode313
-rw-r--r--lib/stdlib/test/io_SUITE.erl47
-rw-r--r--lib/stdlib/test/io_proto_SUITE.erl2
-rw-r--r--lib/stdlib/test/shell_SUITE.erl209
10 files changed, 628 insertions, 54 deletions
diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl
index 77c615d6d9..606bbbcbb2 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_8562/1, otp_8665/1, otp_8911/1, otp_10302/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_8665, otp_8911, otp_10302].
groups() ->
[{upcase_mac, [], [upcase_mac_1, upcase_mac_2]},
@@ -582,12 +582,13 @@ otp_8130(suite) ->
otp_8130(Config) when is_list(Config) ->
true = os:putenv("epp_inc1", "stdlib"),
Ts = [{otp_8130_1,
- %% The scanner handles UNICODE in a special way. Hopefully
- %% temporarily.
<<"-define(M(A), ??A). "
"t() -> "
- " \"{ 34 , [ $1 , 2730 ] , \\\"34\\\" , X . a , 2730 }\" = "
- " ?M({34,\"1\\x{aaa}\",\"34\",X.a,$\\x{aaa}}), ok. ">>,
+ " L = \"{ 34 , \\\"1\\\\x{AAA}\\\" , \\\"34\\\" , X . a , $\\\\x{AAA} }\", "
+ " R = ?M({34,\"1\\x{aaa}\",\"34\",X.a,$\\x{aaa}}),"
+ " Lt = erl_scan:string(L, 1, [unicode]),"
+ " Rt = erl_scan:string(R, 1, [unicode]),"
+ " Lt = Rt, ok. ">>,
ok},
{otp_8130_2,
@@ -1284,6 +1285,75 @@ otp_8665(Config) when is_list(Config) ->
?line [] = compile(Config, Cs),
ok.
+otp_10302(doc) ->
+ "OTP-10302. Unicode characters scanner/parser.";
+otp_10302(suite) ->
+ [];
+otp_10302(Config) when is_list(Config) ->
+ %% Two messages (one too many). Keeps otp_4871 happy.
+ Cs = [{otp_8562,
+ <<"%% coding: utf-8\n \n \x{E4}">>,
+ {errors,[{3,epp,cannot_parse},
+ {3,file_io_server,invalid_unicode}],[]}}
+ ],
+ [] = compile(Config, Cs),
+ Dir = ?config(priv_dir, Config),
+ File = filename:join(Dir, "otp_10302.erl"),
+ utf8 = encoding("coding: utf-8", File),
+ utf8 = encoding("coding: UTF-8", File),
+ latin1 = encoding("coding: Latin-1", File),
+ latin1 = encoding("coding: latin-1", File),
+ none = encoding_com("coding: utf-8", File),
+ none = encoding_com("\n\n%% coding: utf-8", File),
+ none = encoding_nocom("\n\n coding: utf-8", File),
+ utf8 = encoding_com("\n%% coding: utf-8", File),
+ utf8 = encoding_nocom("\n coding: utf-8", File),
+ none = encoding("coding: \nutf-8", File),
+ latin1 = encoding("Encoding : latin-1", File),
+ utf8 = encoding("ccoding: UTF-8", File),
+ utf8 = encoding("coding= utf-8", File),
+ utf8 = encoding_com(" %% coding= utf-8", File),
+ utf8 = encoding("coding = utf-8", File),
+ none = encoding("coding: utf-16 coding: utf-8", File), %first is bad
+ none = encoding("Coding: utf-8", File), %capital c
+ utf8 = encoding("-*- coding: utf-8 -*-", File),
+ utf8 = encoding("-*-coding= utf-8-*-", File),
+ utf8 = encoding("codingcoding= utf-8", File),
+ ok = prefix("coding: utf-8", File, utf8),
+
+ "coding: latin-1" = epp:encoding_to_string(latin1),
+ "coding: utf-8" = epp:encoding_to_string(utf8),
+ true = lists:member(epp:default_encoding(), [latin1, utf8]),
+
+ ok.
+
+prefix(S, File, Enc) ->
+ prefix(0, S, File, Enc).
+
+prefix(100, _S, _File, _) ->
+ ok;
+prefix(N, S, File, Enc) ->
+ Enc = encoding(lists:duplicate(N, $\s) ++ S, File),
+ prefix(N+1, S, File, Enc).
+
+encoding(Enc, File) ->
+ E = encoding_com("%% " ++ Enc, File),
+ none = encoding_com(Enc, File),
+ E = encoding_nocom(Enc, File).
+
+encoding_com(Enc, File) ->
+ ok = file:write_file(File, Enc),
+ {ok, Fd} = file:open(File, [read]),
+ E = epp:set_encoding(Fd),
+ ok = file:close(Fd),
+ E = epp:read_encoding(File).
+
+encoding_nocom(Enc, File) ->
+ ok = file:write_file(File, Enc),
+ {ok, Fd} = file:open(File, [read]),
+ ok = file:close(Fd),
+ epp:read_encoding(File, [{in_comment_only, false}]).
+
check(Config, Tests) ->
eval_tests(Config, fun check_test/2, Tests).
diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl
index 64853ca078..07303174f1 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-2011. All Rights Reserved.
+%% Copyright Ericsson AB 2006-2012. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -48,7 +48,8 @@
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_8473/1, otp_8522/1, otp_8567/1, otp_8664/1, otp_9147/1,
+ otp_10302/1]).
%% Internal export.
-export([ehook/6]).
@@ -79,7 +80,7 @@ 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_8473, otp_8522, otp_8567, otp_8664, otp_9147, otp_10302]}].
init_per_suite(Config) ->
Config.
@@ -634,8 +635,12 @@ misc_attrs(Config) when is_list(Config) ->
hook(suite) ->
[];
hook(Config) when is_list(Config) ->
+ F = fun(H) -> H end,
+ do_hook(F).
+
+do_hook(HookFun) ->
Lc = parse_expr(binary_to_list(<<"[X || X <- [1,2,3]].">>)),
- H = fun hook/4,
+ H = HookFun(fun hook/4),
Expr = {call,0,{atom,0,fff},[{foo,Lc},{foo,Lc},{foo,Lc}]},
EChars = lists:flatten(erl_pp:expr(Expr, 0, H)),
Call = {call,0,{atom,0,foo},[Lc]},
@@ -692,7 +697,7 @@ hook(Config) when is_list(Config) ->
GChars2 = erl_pp:guard(G2),
?line true = GChars =:= lists:flatten(GChars2),
- EH = {?MODULE, ehook, [foo,bar]},
+ EH = HookFun({?MODULE, ehook, [foo,bar]}),
XEChars = erl_pp:expr(Expr, -1, EH),
?line true = remove_indentation(EChars) =:= lists:flatten(XEChars),
XEChars2 = erl_pp:expr(Expr, EH),
@@ -1068,6 +1073,43 @@ otp_9147(Config) when is_list(Config) ->
string:tokens(binary_to_list(Bin), "\n")),
ok.
+otp_10302(doc) ->
+ "OTP-10302. Unicode characters scanner/parser.";
+otp_10302(suite) -> [];
+otp_10302(Config) when is_list(Config) ->
+ Ts = [{uni_1,
+ <<"t() -> <<(<<\"abc\\x{aaa}\">>):3/binary>>.">>}
+ ],
+ compile(Config, Ts),
+ ok = pp_expr(<<"$\\x{aaa}">>),
+ ok = pp_expr(<<"\"1\\x{aaa}\"">>),
+ ok = pp_expr(<<"<<<<\"hej\">>/binary>>">>),
+ ok = pp_expr(<<"<< <<\"1\\x{aaa}\">>/binary>>">>),
+
+ U = [{encoding,unicode}],
+
+ do_hook(fun(H) -> [{hook,H}] end),
+ do_hook(fun(H) -> [{hook,H}]++U end),
+
+ ok = pp_expr(<<"$\\x{aaa}">>, [{hook,fun hook/4}]),
+
+ Opts = [{hook, fun unicode_hook/4},{encoding,unicode}],
+ Lc = parse_expr("[X || X <- [\"\x{400}\",\"\xFF\"]]."),
+ Expr = {call,0,{atom,0,fff},[{foo,{foo,Lc}},{foo,{foo,Lc}}]},
+ EChars = lists:flatten(erl_pp:expr(Expr, 0, Opts)),
+ Call = {call,0,{atom,0,foo},[{call,0,{atom,0,foo},[Lc]}]},
+ Expr2 = {call,0,{atom,0,fff},[Call,Call]},
+ EChars2 = erl_pp:exprs([Expr2], U),
+ EChars = lists:flatten(EChars2),
+ [$\x{400},$\x{400}] = [C || C <- EChars, C > 255],
+
+ ok = pp_forms(<<"function() -> {\"\x{400}\",$\x{400}}. "/utf8>>, U),
+ ok = pp_forms("function() -> {\"\x{400}\",$\x{400}}. ", []),
+ ok.
+
+unicode_hook({foo,E}, I, P, H) ->
+ erl_pp:expr({call,0,{atom,0,foo},[E]}, I, P, H).
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
compile(Config, Tests) ->
@@ -1137,9 +1179,11 @@ flat_expr(Expr) ->
pp_forms(Bin) ->
pp_forms(Bin, none).
-pp_forms(Bin, Hook) ->
- PP1 = (catch parse_and_pp_forms(binary_to_list(Bin), Hook)),
- PP2 = (catch parse_and_pp_forms(PP1, Hook)),
+pp_forms(Bin, Options) when is_binary(Bin) ->
+ pp_forms(to_list(Bin, Options), Options);
+pp_forms(List, Options) when is_list(List) ->
+ PP1 = (catch parse_and_pp_forms(List, Options)),
+ PP2 = (catch parse_and_pp_forms(PP1, Options)),
case PP1 =:= PP2 of % same line numbers
true ->
test_max_line(PP1);
@@ -1147,8 +1191,8 @@ pp_forms(Bin, Hook) ->
not_ok
end.
-parse_and_pp_forms(String, Hook) ->
- lists:append(lists:map(fun(AF) -> erl_pp:form(AF, Hook)
+parse_and_pp_forms(String, Options) ->
+ lists:append(lists:map(fun(AF) -> erl_pp:form(AF, Options)
end, parse_forms(String))).
parse_forms(Chars) ->
@@ -1158,7 +1202,7 @@ parse_forms(Chars) ->
parse_forms2([], _Cont, _Line, Forms) ->
lists:reverse(Forms);
parse_forms2(String, Cont0, Line, Forms) ->
- case erl_scan:tokens(Cont0, String, Line) of
+ case erl_scan:tokens(Cont0, String, Line, [unicode]) of
{done, {ok, Tokens, EndLine}, Chars} ->
{ok, Form} = erl_parse:parse_form(Tokens),
parse_forms2(Chars, [], EndLine, [Form | Forms]);
@@ -1174,10 +1218,12 @@ pp_expr(Bin) ->
pp_expr(Bin, none).
%% Final dot is added.
-pp_expr(Bin, Hook) ->
- PP1 = (catch parse_and_pp_expr(binary_to_list(Bin), 0, Hook)),
- PPneg = (catch parse_and_pp_expr(binary_to_list(Bin), -1, Hook)),
- PP2 = (catch parse_and_pp_expr(PPneg, 0, Hook)),
+pp_expr(Bin, Options) when is_binary(Bin) ->
+ pp_expr(to_list(Bin, Options), Options);
+pp_expr(List, Options) when is_list(List) ->
+ PP1 = (catch parse_and_pp_expr(List, 0, Options)),
+ PPneg = (catch parse_and_pp_expr(List, -1, Options)),
+ PP2 = (catch parse_and_pp_expr(PPneg, 0, Options)),
if
PP1 =:= PP2 -> % same line numbers
case
@@ -1192,15 +1238,24 @@ pp_expr(Bin, Hook) ->
not_ok
end.
-parse_and_pp_expr(String, Indent, Hook) ->
+parse_and_pp_expr(String, Indent, Options) ->
StringDot = lists:flatten(String) ++ ".",
- erl_pp:expr(parse_expr(StringDot), Indent, Hook).
+ erl_pp:expr(parse_expr(StringDot), Indent, Options).
parse_expr(Chars) ->
- {ok, Tokens, _} = erl_scan:string(Chars),
+ {ok, Tokens, _} = erl_scan:string(Chars, 1, [unicode]),
{ok, [Expr]} = erl_parse:parse_exprs(Tokens),
Expr.
+to_list(Bin, Options) when is_list(Options) ->
+ case proplists:get_value(encoding, Options) of
+ unicode -> unicode:characters_to_list(Bin);
+ encoding -> binary_to_list(Bin);
+ undefined -> binary_to_list(Bin)
+ end;
+to_list(Bin, _Hook) ->
+ binary_to_list(Bin).
+
test_new_line(String) ->
case string:chr(String, $\n) of
0 -> ok;
diff --git a/lib/stdlib/test/erl_scan_SUITE.erl b/lib/stdlib/test/erl_scan_SUITE.erl
index 4298b2c701..7994146d67 100644
--- a/lib/stdlib/test/erl_scan_SUITE.erl
+++ b/lib/stdlib/test/erl_scan_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1998-2011. All Rights Reserved.
+%% Copyright Ericsson AB 1998-2012. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -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([ error_1/1, error_2/1, iso88591/1, otp_7810/1]).
+-export([ error_1/1, error_2/1, iso88591/1, otp_7810/1, otp_10302/1]).
-import(lists, [nth/2,flatten/1]).
-import(io_lib, [print/1]).
@@ -59,7 +59,7 @@ end_per_testcase(_Case, Config) ->
suite() -> [{ct_hooks,[ts_install_cth]}].
all() ->
- [{group, error}, iso88591, otp_7810].
+ [{group, error}, iso88591, otp_7810, otp_10302].
groups() ->
[{error, [], [error_1, error_2]}].
@@ -823,7 +823,7 @@ unicode() ->
?line {ok,[{char,1,1}],1} = erl_scan:string([$$,$\\,$^,1089]),
?line {error,{1,erl_scan,Error},1} = erl_scan:string("\"qa\x{aaa}"),
- ?line "unterminated string starting with \"qa\\x{AAA}\"" =
+ ?line "unterminated string starting with \"qa"++[2730]++"\"" =
erl_scan:format_error(Error),
?line {error,{{1,1},erl_scan,_},{1,11}} =
erl_scan:string("\"qa\\x{aaa}",{1,1}),
@@ -887,9 +887,10 @@ unicode() ->
{char,_,$d},{']',_}],{1,8}} = erl_scan:string(Str1, {1,1}),
?line test(Str1),
Comment = "%% "++[1089],
- ?line {ok,[{comment,1,[$%,$%,$\s,1089]}],1} =
+ %% Returned a comment In R15B03:
+ {error,{1,erl_scan,{illegal,character}},1} =
erl_scan:string(Comment, 1, return),
- ?line {ok,[{comment,_,[$%,$%,$\s,1089]}],{1,5}} =
+ {error,{{1,1},erl_scan,{illegal,character}},{1,5}} =
erl_scan:string(Comment, {1,1}, return),
ok.
@@ -958,6 +959,182 @@ more_chars() ->
erl_scan:string("$\\xg", {1,1}),
ok.
+otp_10302(doc) ->
+ "OTP-10302. Unicode characters scanner/parser.";
+otp_10302(suite) ->
+ [];
+otp_10302(Config) when is_list(Config) ->
+ %% From unicode():
+ {error,{1,erl_scan,{illegal,atom}},1} =
+ erl_scan:string("'a"++[1089]++"b'", 1, unicode),
+ {error,{{1,1},erl_scan,{illegal,atom}},{1,12}} =
+ erl_scan:string("'qa\\x{aaa}'",{1,1},unicode),
+
+ {ok,[{char,1,1089}],1} = erl_scan:string([$$,1089], 1, unicode),
+ {ok,[{char,1,1089}],1} = erl_scan:string([$$,$\\,1089],1,unicode),
+
+ Qs = "$\\x{aaa}",
+ {ok,[{char,1,2730}],1} = erl_scan:string(Qs,1,unicode),
+ {ok,[Q2],{1,9}} = erl_scan:string(Qs,{1,1},[unicode,text]),
+ [{category,char},{column,1},{length,8},
+ {line,1},{symbol,16#aaa},{text,Qs}] =
+ erl_scan:token_info(Q2),
+
+ Tags = [category, column, length, line, symbol, text],
+
+ U1 = "\"\\x{aaa}\"",
+ {ok,[T1],{1,10}} = erl_scan:string(U1, {1,1}, [unicode,text]),
+ [{category,string},{column,1},{length,9},{line,1},
+ {symbol,[16#aaa]},{text,U1}] = erl_scan:token_info(T1, Tags),
+
+ U2 = "\"\\x41\\x{fff}\\x42\"",
+ {ok,[{string,1,[65,4095,66]}],1} = erl_scan:string(U2, 1, unicode),
+
+ U3 = "\"a\n\\x{fff}\n\"",
+ {ok,[{string,1,[97,10,4095,10]}],3} = erl_scan:string(U3, 1,unicode),
+
+ U4 = "\"\\^\n\\x{aaa}\\^\n\"",
+ {ok,[{string,1,[10,2730,10]}],3} = erl_scan:string(U4, 1,[unicode]),
+
+ Str1 = "\"ab" ++ [1089] ++ "cd\"",
+ {ok,[{string,1,[97,98,1089,99,100]}],1} =
+ erl_scan:string(Str1,1,unicode),
+ {ok,[{string,{1,1},[97,98,1089,99,100]}],{1,8}} =
+ erl_scan:string(Str1, {1,1},unicode),
+
+ OK1 = 16#D800-1,
+ OK2 = 16#DFFF+1,
+ OK3 = 16#FFFE-1,
+ OK4 = 16#FFFF+1,
+ OKL = [OK1,OK2,OK3,OK4],
+
+ Illegal1 = 16#D800,
+ Illegal2 = 16#DFFF,
+ Illegal3 = 16#FFFE,
+ Illegal4 = 16#FFFF,
+ IllegalL = [Illegal1,Illegal2,Illegal3,Illegal4],
+
+ [{ok,[{comment,1,[$%,$%,$\s,OK]}],1} =
+ erl_scan:string("%% "++[OK], 1, [unicode,return]) ||
+ OK <- OKL],
+ {ok,[{comment,_,[$%,$%,$\s,OK1]}],{1,5}} =
+ erl_scan:string("%% "++[OK1], {1,1}, [unicode,return]),
+ [{error,{1,erl_scan,{illegal,character}},1} =
+ erl_scan:string("%% "++[Illegal], 1, [unicode,return]) ||
+ Illegal <- IllegalL],
+ {error,{{1,1},erl_scan,{illegal,character}},{1,5}} =
+ erl_scan:string("%% "++[Illegal1], {1,1}, [unicode,return]),
+
+ [{ok,[],1} = erl_scan:string("%% "++[OK], 1, [unicode]) ||
+ OK <- OKL],
+ {ok,[],{1,5}} = erl_scan:string("%% "++[OK1], {1,1}, [unicode]),
+ [{error,{1,erl_scan,{illegal,character}},1} =
+ erl_scan:string("%% "++[Illegal], 1, [unicode]) ||
+ Illegal <- IllegalL],
+ {error,{{1,1},erl_scan,{illegal,character}},{1,5}} =
+ erl_scan:string("%% "++[Illegal1], {1,1}, [unicode]),
+
+ [{ok,[{string,{1,1},[OK]}],{1,4}} =
+ erl_scan:string("\""++[OK]++"\"",{1,1},unicode) ||
+ OK <- OKL],
+ [{error,{{1,2},erl_scan,{illegal,character}},{1,3}} =
+ erl_scan:string("\""++[OK]++"\"",{1,1},unicode) ||
+ OK <- IllegalL],
+
+ [{error,{{1,1},erl_scan,{illegal,character}},{1,2}} =
+ erl_scan:string([Illegal],{1,1},unicode) ||
+ Illegal <- IllegalL],
+
+ {ok,[{char,{1,1},OK1}],{1,3}} =
+ erl_scan:string([$$,OK1],{1,1},unicode),
+ {error,{{1,1},erl_scan,{illegal,character}},{1,2}} =
+ erl_scan:string([$$,Illegal1],{1,1},unicode),
+
+ {ok,[{char,{1,1},OK1}],{1,4}} =
+ erl_scan:string([$$,$\\,OK1],{1,1},unicode),
+ {error,{{1,1},erl_scan,{illegal,character}},{1,4}} =
+ erl_scan:string([$$,$\\,Illegal1],{1,1},unicode),
+
+ {ok,[{string,{1,1},[55295]}],{1,5}} =
+ erl_scan:string("\"\\"++[OK1]++"\"",{1,1},unicode),
+ {error,{{1,2},erl_scan,{illegal,character}},{1,4}} =
+ erl_scan:string("\"\\"++[Illegal1]++"\"",{1,1},unicode),
+
+ {ok,[{char,{1,1},OK1}],{1,10}} =
+ erl_scan:string("$\\x{D7FF}",{1,1},unicode),
+ {error,{{1,1},erl_scan,{illegal,character}},{1,10}} =
+ erl_scan:string("$\\x{D800}",{1,1},unicode),
+
+ %% Not erl_scan, but erl_parse.
+ {integer,0,1} = erl_parse:abstract(1),
+ Float = 3.14, {float,0,Float} = erl_parse:abstract(Float),
+ {nil,0} = erl_parse:abstract([]),
+ {bin,0,
+ [{bin_element,0,{integer,0,1},default,default},
+ {bin_element,0,{integer,0,2},default,default}]} =
+ erl_parse:abstract(<<1,2>>),
+ {cons,0,{tuple,0,[{atom,0,a}]},{atom,0,b}} =
+ erl_parse:abstract([{a} | b]),
+ {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"),
+
+ Line = 17,
+ {integer,Line,1} = erl_parse:abstract(1, Line),
+ Float = 3.14, {float,Line,Float} = erl_parse:abstract(Float, Line),
+ {nil,Line} = erl_parse:abstract([], Line),
+ {bin,Line,
+ [{bin_element,Line,{integer,Line,1},default,default},
+ {bin_element,Line,{integer,Line,2},default,default}]} =
+ erl_parse:abstract(<<1,2>>, Line),
+ {cons,Line,{tuple,Line,[{atom,Line,a}]},{atom,Line,b}} =
+ erl_parse:abstract([{a} | b], Line),
+ {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),
+
+ Opts1 = [{line,17}],
+ {integer,Line,1} = erl_parse:abstract(1, Opts1),
+ Float = 3.14, {float,Line,Float} = erl_parse:abstract(Float, Opts1),
+ {nil,Line} = erl_parse:abstract([], Opts1),
+ {bin,Line,
+ [{bin_element,Line,{integer,Line,1},default,default},
+ {bin_element,Line,{integer,Line,2},default,default}]} =
+ erl_parse:abstract(<<1,2>>, Opts1),
+ {cons,Line,{tuple,Line,[{atom,Line,a}]},{atom,Line,b}} =
+ erl_parse:abstract([{a} | b], Opts1),
+ {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),
+
+ [begin
+ {integer,Line,1} = erl_parse:abstract(1, Opts2),
+ Float = 3.14, {float,Line,Float} = erl_parse:abstract(Float, Opts2),
+ {nil,Line} = erl_parse:abstract([], Opts2),
+ {bin,Line,
+ [{bin_element,Line,{integer,Line,1},default,default},
+ {bin_element,Line,{integer,Line,2},default,default}]} =
+ erl_parse:abstract(<<1,2>>, Opts2),
+ {cons,Line,{tuple,Line,[{atom,Line,a}]},{atom,Line,b}} =
+ erl_parse:abstract([{a} | b], Opts2),
+ {string,Line,"str"} = erl_parse:abstract("str", Opts2),
+ {string,Line,[97,1024,99]} =
+ erl_parse:abstract("a"++[1024]++"c", Opts2)
+ end || Opts2 <- [[{encoding,unicode},{line,Line}],
+ [{encoding,utf8},{line,Line}]]],
+
+ {cons,0,
+ {integer,0,97},
+ {cons,0,{integer,0,1024},{string,0,"c"}}} =
+ erl_parse:abstract("a"++[1024]++"c", [{encoding,latin1}]),
+ 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 5b592c65cc..7634c21a17 100644
--- a/lib/stdlib/test/escript_SUITE.erl
+++ b/lib/stdlib/test/escript_SUITE.erl
@@ -34,7 +34,8 @@
create_and_extract/1,
foldl/1,
overflow/1,
- verify_sections/3
+ verify_sections/3,
+ unicode/1
]).
-include_lib("test_server/include/test_server.hrl").
@@ -46,7 +47,7 @@ all() ->
[basic, errors, strange_name, emulator_flags,
module_script, beam_script, archive_script, epp,
create_and_extract, foldl, overflow,
- archive_script_file_access].
+ archive_script_file_access, unicode].
groups() ->
[].
@@ -810,6 +811,8 @@ normalize_sections(Sections) ->
end.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+
foldl(Config) when is_list(Config) ->
{NewFile, _FileInfo,
_EmuArg, _Source,
@@ -887,6 +890,20 @@ emulate_escript_foldl(Fun, Acc, File) ->
{error, Reason}
end.
+unicode(Config) when is_list(Config) ->
+ Data = ?config(data_dir, Config),
+ Dir = filename:absname(Data), %Get rid of trailing slash.
+ 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">>]),
+ run(Dir, "unicode2",
+ [<<"escript: exception error: an error occurred when evaluating"
+ " an arithmetic expression\n in operator '/'/2\n "
+ "called as <<\"\xaa\">> / <<\"\xaa\">>\nExitCode:127">>]),
+ run(Dir, "unicode3", [<<"ExitCode:0">>]),
+ ok.
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
overflow(Config) when is_list(Config) ->
diff --git a/lib/stdlib/test/escript_SUITE_data/unicode1 b/lib/stdlib/test/escript_SUITE_data/unicode1
new file mode 100755
index 0000000000..a77574625e
--- /dev/null
+++ b/lib/stdlib/test/escript_SUITE_data/unicode1
@@ -0,0 +1,14 @@
+#!/usr/bin/env escript
+%% -*- erlang -*-
+
+-export([main/1]).
+
+main(_) ->
+ ok = io:setopts([{encoding,unicode}]),
+ _D = erlang:system_flag(backtrace_depth, 0),
+ A = <<"\x{aa}">>,
+ 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),
+ B = erl_eval:new_bindings(),
+ erl_eval:exprs(Es, B).
diff --git a/lib/stdlib/test/escript_SUITE_data/unicode2 b/lib/stdlib/test/escript_SUITE_data/unicode2
new file mode 100755
index 0000000000..495188f6f0
--- /dev/null
+++ b/lib/stdlib/test/escript_SUITE_data/unicode2
@@ -0,0 +1,14 @@
+#!/usr/bin/env escript
+%% -*- erlang -*-
+
+-export([main/1]).
+
+main(_) ->
+ ok = io:setopts([{encoding,latin1}]),
+ _D = erlang:system_flag(backtrace_depth, 0),
+ A = <<"\x{aa}">>,
+ 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),
+ B = erl_eval:new_bindings(),
+ erl_eval:exprs(Es, B).
diff --git a/lib/stdlib/test/escript_SUITE_data/unicode3 b/lib/stdlib/test/escript_SUITE_data/unicode3
new file mode 100755
index 0000000000..944487dcae
--- /dev/null
+++ b/lib/stdlib/test/escript_SUITE_data/unicode3
@@ -0,0 +1,13 @@
+#!/usr/bin/env escript
+%% -*- erlang; coding: utf-8 -*-
+
+-export([main/1]).
+
+main(_) ->
+ ok = io:setopts([{encoding,unicode}]),
+ Bin1 = <<"örn_Ѐ שלום-שלום+של 日本語">>,
+
+ L = [246,114,110,95,1024,32,1513,1500,1493,1501,45,1513,1500,1493,
+ 1501,43,1513,1500,32,26085,26412,35486],
+ L = unicode:characters_to_list(Bin1, utf8),
+ ok.
diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl
index 74fcdcc7d2..4f030053aa 100644
--- a/lib/stdlib/test/io_SUITE.erl
+++ b/lib/stdlib/test/io_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1999-2011. All Rights Reserved.
+%% Copyright Ericsson AB 1999-2012. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -28,7 +28,7 @@
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]).
+ io_lib_print_binary_depth_one/1, otp_10302/1]).
%-define(debug, true).
@@ -64,7 +64,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,
- io_lib_print_binary_depth_one].
+ io_lib_print_binary_depth_one, otp_10302].
groups() ->
[].
@@ -2034,3 +2034,44 @@ io_lib_print_binary_depth_one(Suite) when is_list(Suite) ->
?line "<<...>>" = fmt("~W", [<<1:7>>, 1]),
?line "<<...>>" = fmt("~P", [<<1:7>>, 1]),
ok.
+
+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),
+
+ "<<\"\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]),
+
+ Chars = lists:seq(0, 512), % just a few...
+ [] = [C || C <- Chars, S <- io_lib:write_unicode_char_as_latin1(C),
+ not is_latin1(S)],
+ L1 = [S || C <- Chars, S <- io_lib:write_unicode_char(C),
+ not is_latin1(S)],
+ L1 = lists:seq(256, 512),
+
+ [] = [C || C <- Chars, S <- io_lib:write_unicode_string_as_latin1([C]),
+ not is_latin1(S)],
+ L2 = [S || C <- Chars, S <- io_lib:write_unicode_string([C]),
+ not is_latin1(S)],
+ L2 = lists:seq(256, 512),
+
+ ok.
+
+pretty(Term, Depth) when is_integer(Depth) ->
+ Opts = [{column, 1}, {line_length, 20},
+ {depth, Depth}, {max_chars, 60},
+ {encoding, unicode}],
+ pretty(Term, Opts);
+pretty(Term, Opts) when is_list(Opts) ->
+ R = io_lib_pretty:print(Term, Opts),
+ lists:flatten(io_lib:format("~ts", [R])).
+
+is_latin1(S) ->
+ S >= 0 andalso S =< 255.
diff --git a/lib/stdlib/test/io_proto_SUITE.erl b/lib/stdlib/test/io_proto_SUITE.erl
index 17e69f7c1c..299daf0e42 100644
--- a/lib/stdlib/test/io_proto_SUITE.erl
+++ b/lib/stdlib/test/io_proto_SUITE.erl
@@ -736,7 +736,7 @@ binary_options(Config) when is_list(Config) ->
{getline_re, ".*<<\"hej\\\\n\">>"},
{putline, "io:get_line('')."},
{putline, binary_to_list(<<"\345\344\366"/utf8>>)},
- {getline_re, ".*<<\""++binary_to_list(unicode:characters_to_binary(<<"\345\344\366"/utf8>>,latin1,utf8))++"\\\\n\">>"}
+ {getline_re, ".*<<\""++binary_to_list(<<"\345\344\366"/utf8>>)++"\\\\n\"/utf8>>"}
],[],[],"-oldshell"),
ok.
diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl
index d49416c150..a32f846bd2 100644
--- a/lib/stdlib/test/shell_SUITE.erl
+++ b/lib/stdlib/test/shell_SUITE.erl
@@ -29,7 +29,7 @@
progex_bit_syntax/1, progex_records/1,
progex_lc/1, progex_funs/1,
otp_5990/1, otp_6166/1, otp_6554/1, otp_6785/1,
- otp_7184/1, otp_7232/1, otp_8393/1]).
+ otp_7184/1, otp_7232/1, otp_8393/1, otp_10302/1]).
-export([ start_restricted_from_shell/1,
start_restricted_on_command_line/1,restricted_local/1]).
@@ -93,7 +93,7 @@ groups() ->
progex_funs]},
{tickets, [],
[otp_5990, otp_6166, otp_6554, otp_6785, otp_7184,
- otp_7232, otp_8393]}].
+ otp_7232, otp_8393, otp_10302]}].
init_per_suite(Config) ->
Config.
@@ -108,7 +108,7 @@ end_per_group(_GroupName, Config) ->
Config.
--record(state, {bin, reply, leader}).
+-record(state, {bin, reply, leader, unic = latin1}).
start_restricted_from_shell(doc) ->
@@ -374,15 +374,18 @@ records(Config) when is_list(Config) ->
MS = ?MODULE_STRING,
RR1 = "rr(" ++ MS ++ "). #state{}.",
?line "[state]\n"
- "#state{bin = undefined,reply = undefined,leader = undefined}.\n" =
+ "#state{bin = undefined,reply = undefined,leader = undefined,\n"
+ " unic = latin1}.\n" =
t(RR1),
RR2 = "rr(" ++ MS ++ ",[state]). #state{}.",
?line "[state]\n"
- "#state{bin = undefined,reply = undefined,leader = undefined}.\n" =
+ "#state{bin = undefined,reply = undefined,leader = undefined,\n"
+ " unic = latin1}.\n" =
t(RR2),
RR3 = "rr(" ++ MS ++ ",'_'). #state{}.",
?line "[state]\n"
- "#state{bin = undefined,reply = undefined,leader = undefined}.\n" =
+ "#state{bin = undefined,reply = undefined,leader = undefined,\n"
+ " unic = latin1}.\n" =
t(RR3),
RR4 = "rr(" ++ MS ++ ", '_', {d,test1}).",
?line [[state]] = scan(RR4),
@@ -2748,6 +2751,143 @@ prompt_err(B) ->
S = string:strip(S2, both, $"),
string:strip(S, right, $.).
+otp_10302(doc) ->
+ "OTP-10302. Unicode.";
+otp_10302(suite) -> [];
+otp_10302(Config) when is_list(Config) ->
+ Test1 =
+ <<"begin
+ io:setopts([{encoding,utf8}]),
+ [1024] = \"\\x{400}\",
+ rd(rec, {a = \"\\x{400}\"}),
+ ok = rl(rec)
+ end.">>,
+ "-record(rec,{a = \"\x{400}\"}).\nok.\n" = t(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),
+
+ Test4 =
+ <<"io:setopts([{encoding,utf8}]).
+ A = [1024] = \"\\x{400}\".
+ b().
+ h().">>,
+
+ "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),
+
+ Test5 =
+ <<"begin
+ io:setopts([{encoding,utf8}]),
+ results(0),
+ A = [1024] = \"\\x{400}\",
+ b(),
+ h()
+ end.">>,
+ "A = \"\x{400}\".\nok.\n" = t(Test5),
+
+ %% One $" is "lost":
+ true =
+ "\x{400}\": command not found" =:=
+ prompt_err({<<"io:setopts([{encoding,utf8}]). v(\"\x{400}\")."/utf8>>,
+ unicode}),
+
+ "ok.\ndefault\n* Bad prompt function: \"\x{400}\".\n" =
+ t({<<"io:setopts([{encoding,utf8}]). "
+ "shell:prompt_func(\"\x{400}\")."/utf8>>,
+ unicode}),
+ _ = shell:prompt_func(default),
+
+ %% Test lib:format_exception() (cf. OTP-6554)
+ Test6 =
+ <<"begin
+ A = <<\"\\xaa\">>,
+ 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),
+ B = erl_eval:new_bindings(),
+ erl_eval:exprs(Es, B)
+ end.">>,
+
+ "** exception error: an error occurred when evaluating"
+ " an arithmetic expression\n in operator '/'/2\n"
+ " called as <<\"\xaa\">> / <<\"\xaa\">>.\n" = t(Test6),
+ Test7 =
+ <<"io:setopts([{encoding,utf8}]).
+ A = <<\"\\xaa\">>,
+ 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),
+ 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),
+ Test8 =
+ <<"begin
+ A = [1089],
+ S = lists:flatten(io_lib:format(\"~tp/~tp.\", [A, A])),
+ {ok, Ts, _} = erl_scan:string(S, 1, [unicode]),
+ {ok, Es} = erl_parse:parse_exprs(Ts),
+ B = erl_eval:new_bindings(),
+ erl_eval:exprs(Es, B)
+ end.">>,
+ "** exception error: an error occurred when evaluating"
+ " an arithmetic expression\n in operator '/'/2\n"
+ " called as [1089] / [1089].\n" = t(Test8),
+ Test9 =
+ <<"io:setopts([{encoding,utf8}]).
+ A = [1089],
+ S = lists:flatten(io_lib:format(\"~tp/~tp.\", [A, A])),
+ {ok, Ts, _} = erl_scan:string(S, 1, [unicode]),
+ {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 \"\x{441}\" / \"\x{441}\".\n" = t(Test9),
+ Test10 =
+ <<"A = {\"1\\xaa\",
+ $\\xaa,
+ << <<\"hi\">>/binary >>,
+ <<\"1\xaa\">>},
+ fun(a) -> true end(A).">>,
+ "** exception error: no function clause matching \n"
+ " erl_eval:'-inside-an-interpreted-fun-'"
+ "({\"1\xc2\xaa\",170,<<\"hi\">>,\n "
+ " <<\"1\xc2\xaa\">>}) .\n" = t(Test10),
+ Test11 =
+ <<"io:setopts([{encoding,utf8}]).
+ A = {\"1\\xaa\",
+ $\\xaa,
+ << <<\"hi\">>/binary >>,
+ <<\"1\xaa\">>},
+ fun(a) -> true end(A).">>,
+
+ "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),
+ Test12 = <<"fun(a, b) -> false end(65, [1089]).">>,
+ "** exception error: no function clause matching \n"
+ " erl_eval:'-inside-an-interpreted-fun-'(65,[1089])"
+ " .\n" = t(Test12),
+ Test13 =
+ <<"io:setopts([{encoding,utf8}]).
+ 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),
+
+ ok.
+
scan(B) ->
F = fun(Ts) ->
case erl_parse:parse_term(Ts) of
@@ -2761,7 +2901,7 @@ scan(B) ->
scan(t(B), F).
scan(S0, F) ->
- case erl_scan:tokens([], S0, 1) of
+ case erl_scan:tokens([], S0, 1, [unicode]) of
{done,{ok,Ts,_},S} ->
[F(Ts) | scan(S, F)];
_Else ->
@@ -2769,29 +2909,36 @@ scan(S0, F) ->
end.
t({Node,Bin}) when is_atom(Node),is_binary(Bin) ->
- t0(Bin, fun() -> start_new_shell(Node) end);
+ t0({Bin,latin1}, fun() -> start_new_shell(Node) end);
t(Bin) when is_binary(Bin) ->
- t0(Bin, fun() -> start_new_shell() end);
+ t0({Bin,latin1}, fun() -> start_new_shell() end);
+t({Bin,Enc}) when is_binary(Bin), is_atom(Enc) ->
+ t0({Bin,Enc}, fun() -> start_new_shell() end);
t(L) ->
t(list_to_binary(L)).
-t0(Bin, F) ->
+t0({Bin,Enc}, F) ->
%% Spawn a process so that io_request messages do not interfer.
P = self(),
- C = spawn(fun() -> t1(P, Bin, F) end),
+ C = spawn(fun() -> t1(P, {Bin, Enc}, F) end),
receive {C, R} -> R end.
-t1(Parent, Bin, F) ->
- %% io:format("*** Testing ~s~n", [binary_to_list(Bin)]),
- S = #state{bin = Bin, reply = [], leader = group_leader()},
+t1(Parent, {Bin,Enc}, F) ->
+ io:format("*** Testing ~s~n", [binary_to_list(Bin)]),
+ S = #state{bin = Bin, unic = Enc, reply = [], leader = group_leader()},
group_leader(self(), self()),
_Shell = F(),
try
server_loop(S)
catch exit:R -> Parent ! {self(), R};
- throw:{?MODULE,LoopReply} ->
+ throw:{?MODULE,LoopReply,latin1} ->
L0 = binary_to_list(list_to_binary(LoopReply)),
[$\n | L1] = lists:dropwhile(fun(X) -> X =/= $\n end, L0),
+ Parent ! {self(), dotify(L1)};
+ throw:{?MODULE,LoopReply,_Uni} ->
+ Tmp = unicode:characters_to_binary(LoopReply),
+ L0 = unicode:characters_to_list(Tmp),
+ [$\n | L1] = lists:dropwhile(fun(X) -> X =/= $\n end, L0),
Parent ! {self(), dotify(L1)}
after group_leader(S#state.leader, self())
end.
@@ -2835,7 +2982,7 @@ do_io_request(Req, From, S, ReplyAs) ->
case io_requests([Req], [], S) of
{_Status,{eof,_},S1} ->
io_reply(From, ReplyAs, {error,terminated}),
- throw({?MODULE,S1#state.reply});
+ throw({?MODULE,S1#state.reply,S1#state.unic});
{_Status,Reply,S1} ->
io_reply(From, ReplyAs, Reply),
S1
@@ -2858,13 +3005,34 @@ io_requests([], [Rs|Cont], S) ->
io_requests([], [], S) ->
{ok,ok,S}.
+io_request({setopts, Opts}, S) ->
+ #state{unic = OldEnc, bin = Bin} = S,
+ NewEnc = case proplists:get_value(encoding, Opts) of
+ undefined -> OldEnc;
+ utf8 -> unicode;
+ New -> New
+ end,
+ NewBin = case {OldEnc, NewEnc} of
+ {E, E} -> Bin;
+ {latin1, _} ->
+ unicode:characters_to_binary(Bin, latin1, unicode);
+ {_, latin1} ->
+ unicode:characters_to_binary(Bin, unicode, latin1);
+ {_, _} -> Bin
+ end,
+ {ok, ok, S#state{unic = NewEnc, bin = NewBin}};
+io_request(getopts, S) ->
+ {ok,[{encoding,S#state.unic}],S};
io_request({get_geometry,columns}, S) ->
{ok,80,S};
io_request({get_geometry,rows}, S) ->
{ok,24,S};
io_request({put_chars,Chars}, S) ->
{ok,ok,S#state{reply = [S#state.reply | Chars]}};
-io_request({put_chars,_,Chars}, S) ->
+io_request({put_chars,latin1,Chars}, S) ->
+ {ok,ok,S#state{reply = [S#state.reply | Chars]}};
+io_request({put_chars,unicode,Chars0}, S) ->
+ Chars = unicode:characters_to_list(Chars0),
{ok,ok,S#state{reply = [S#state.reply | Chars]}};
io_request({put_chars,Mod,Func,Args}, S) ->
case catch apply(Mod, Func, Args) of
@@ -2890,9 +3058,12 @@ get_until_loop(M, F, As, S, {more,Cont}, Enc) ->
0 ->
get_until_loop(M, F, As, S,
catch apply(M, F, [Cont,eof|As]), Enc);
+ _ when S#state.unic =:= latin1 ->
+ get_until_loop(M, F, As, S#state{bin = <<>>},
+ catch apply(M, F, [Cont,binary_to_list(Bin)|As]), Enc);
_ ->
get_until_loop(M, F, As, S#state{bin = <<>>},
- catch apply(M, F, [Cont,binary_to_list(Bin)|As]), Enc)
+ catch apply(M, F, [Cont,unicode:characters_to_list(Bin)|As]), Enc)
end;
get_until_loop(_M, _F, _As, S, {done,Res,Buf}, Enc) ->
{ok,Res,S#state{bin = buf2bin(Buf, Enc)}};
@@ -2903,6 +3074,8 @@ buf2bin(eof,_) ->
<<>>;
buf2bin(Buf,latin1) ->
list_to_binary(Buf);
+buf2bin(Buf,utf8) ->
+ unicode:characters_to_binary(Buf,unicode,unicode);
buf2bin(Buf,unicode) ->
unicode:characters_to_binary(Buf,unicode,unicode).