aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test/io_SUITE.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test/io_SUITE.erl')
-rw-r--r--lib/stdlib/test/io_SUITE.erl135
1 files changed, 131 insertions, 4 deletions
diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl
index 6e99619324..16e3dba969 100644
--- a/lib/stdlib/test/io_SUITE.erl
+++ b/lib/stdlib/test/io_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1999-2017. All Rights Reserved.
+%% Copyright Ericsson AB 1999-2018. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -30,7 +30,8 @@
io_lib_print_binary_depth_one/1, otp_10302/1, otp_10755/1,
otp_10836/1, io_lib_width_too_small/1,
io_with_huge_message_queue/1, format_string/1,
- maps/1, coverage/1, otp_14175/1]).
+ maps/1, coverage/1, otp_14178_unicode_atoms/1, otp_14175/1,
+ otp_14285/1, limit_term/1]).
-export([pretty/2]).
@@ -61,7 +62,8 @@ all() ->
printable_range, bad_printable_range,
io_lib_print_binary_depth_one, otp_10302, otp_10755, otp_10836,
io_lib_width_too_small, io_with_huge_message_queue,
- format_string, maps, coverage, otp_14175].
+ format_string, maps, coverage, otp_14178_unicode_atoms, otp_14175,
+ otp_14285, limit_term].
%% Error cases for output.
error_1(Config) when is_list(Config) ->
@@ -712,7 +714,7 @@ p(Term, D) ->
rp(Term, 1, 80, D).
p(Term, Col, Ll, D) ->
- rp(Term, Col, Ll, D, no_fun).
+ rp(Term, Col, Ll, D, none).
rp(Term, Col, Ll, D) ->
rp(Term, Col, Ll, D, fun rfd/2).
@@ -722,6 +724,8 @@ rp(Term, Col, Ll, D) ->
rp(Term, Col, Ll, D, RF) ->
rp(Term, Col, Ll, D, ?MAXCS, RF).
+rp(Term, Col, Ll, D, M, none) ->
+ rp(Term, Col, Ll, D, M, fun(_, _) -> no end);
rp(Term, Col, Ll, D, M, RF) ->
%% io:format("~n~n*** Col = ~p Ll = ~p D = ~p~n~p~n-->~n",
%% [Col, Ll, D, Term]),
@@ -755,6 +759,8 @@ rfd(rrrrr, 3) ->
[f1, f2, f3];
rfd(aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa, 0) ->
[];
+rfd('\x{400}', 1) ->
+ ['\x{400}'];
rfd(_, _) ->
no.
@@ -1881,6 +1887,7 @@ otp_10302(Suite) when is_list(Suite) ->
pretty(Term, Depth) when is_integer(Depth) ->
Opts = [{column, 1}, {line_length, 20},
{depth, Depth}, {max_chars, 60},
+ {record_print_fun, fun rfd/2},
{encoding, unicode}],
pretty(Term, Opts);
pretty(Term, Opts) when is_list(Opts) ->
@@ -2107,6 +2114,27 @@ coverage(_Config) ->
ok.
+%% Test UTF-8 atoms.
+otp_14178_unicode_atoms(_Config) ->
+ "atom" = fmt("~ts", ['atom']),
+ "кирилли́ческий атом" = fmt("~ts", ['кирилли́ческий атом']),
+ [16#10FFFF] = fmt("~ts", ['\x{10FFFF}']),
+
+ %% ~s must not accept code points greater than 255.
+ bad_io_lib_format("~s", ['\x{100}']),
+ bad_io_lib_format("~s", ['кирилли́ческий атом']),
+
+ ok.
+
+bad_io_lib_format(F, S) ->
+ try io_lib:format(F, S) of
+ _ ->
+ ct:fail({should_fail,F,S})
+ catch
+ error:badarg ->
+ ok
+ end.
+
otp_14175(_Config) ->
"..." = p(#{}, 0),
"#{}" = p(#{}, 1),
@@ -2303,3 +2331,102 @@ text1([T|Ts]) ->
[erl_anno:text(Anno) | text1(Ts)].
-endif. % EXACT
+
+otp_14285(_Config) ->
+ UOpts = [{record_print_fun, fun rfd/2},
+ {encoding, unicode}],
+ LOpts = [{record_print_fun, fun rfd/2},
+ {encoding, latin1}],
+
+ RT = {'\x{400}','\x{400}'},
+ "#'\x{400}'{'\x{400}' = '\x{400}'}" = pretty(RT, UOpts),
+ "#'\\x{400}'{'\\x{400}' = '\\x{400}'}" = pretty(RT, LOpts),
+
+ Chars = lists:seq(0, 512),
+ [] = [C ||
+ C <- Chars,
+ S <- io_lib:write_atom_as_latin1(list_to_atom([C])),
+ not is_latin1(S)],
+ L1 = [S || C <- Chars, S <- io_lib:write_atom(list_to_atom([C])),
+ not is_latin1(S)],
+ L1 = lists:seq(256, 512),
+
+ latin1_fmt("~w", ['кирилли́ческий атом']),
+ latin1_fmt("~w", ['\x{10FFFF}']),
+ "'кирилли́ческий атом'" = fmt("~tw", ['кирилли́ческий атом']),
+ [$',16#10FFFF,$'] = fmt("~tw", ['\x{10FFFF}']),
+
+ latin1_fmt("~W", ['кирилли́ческий атом', 13]),
+ latin1_fmt("~W", ['\x{10FFFF}', 13]),
+ "'кирилли́ческий атом'" = fmt("~tW", ['кирилли́ческий атом', 13]),
+ [$',16#10FFFF,$'] = fmt("~tW", ['\x{10FFFF}', 13]),
+
+ {ok, [an_atom],[]} = io_lib:fread("~a", "an_atom"),
+ {ok, [an_atom],[]} = io_lib:fread("~ta", "an_atom"),
+ Str = "\"ab" ++ [1089] ++ "cd\"",
+ {ok, ["\"ab"], [1089]++"cd\""} = io_lib:fread("~s", Str),
+ {ok, ['\"ab'], [1089]++"cd\""} = io_lib:fread("~a", Str),
+ {ok,[Str], []} = io_lib:fread("~ts", Str),
+ {ok,[Atom],[]} = io_lib:fread("~ta", Str),
+ Str = atom_to_list(Atom),
+
+ ok.
+
+latin1_fmt(Fmt, Args) ->
+ L = fmt(Fmt, Args),
+ true = lists:all(fun is_latin1/1, L).
+
+limit_term(_Config) ->
+ {_, 2} = limt([a,b,c], 2),
+ {_, 2} = limt([a,b,c], 3),
+ {_, 2} = limt([a,b|c], 2),
+ {_, 2} = limt([a,b|c], 3),
+ {_, 2} = limt({a,b,c,[d,e]}, 2),
+ {_, 2} = limt({a,b,c,[d,e]}, 3),
+ {_, 2} = limt({a,b,c,[d,e]}, 4),
+ {_, 1} = limt(<<"foo">>, 18),
+ ok = blimt(<<"123456789012345678901234567890">>),
+ {_, 1} = limt(<<7:3>>, 2),
+ {_, 1} = limt(<<7:21>>, 2),
+ {_, 1} = limt([], 2),
+ {_, 1} = limt({}, 2),
+ {_, 1} = limt(#{}, 2),
+ {_, 1} = limt(#{[] => {}}, 2),
+ {_, 1} = limt(#{[] => {}}, 3),
+ T = #{[] => {},[a] => [b]},
+ {_, 1} = limt(T, 2),
+ {_, 1} = limt(T, 3),
+ {_, 1} = limt(T, 4),
+ ok.
+
+blimt(Binary) ->
+ blimt(Binary, byte_size(Binary)).
+
+blimt(_B, 1) -> ok;
+blimt(B, D) ->
+ {_, 1} = limt(B, D),
+ blimt(B, D - 1).
+
+limt(Term, Depth) when is_integer(Depth) ->
+ T1 = io_lib:limit_term(Term, Depth),
+ S = form(Term, Depth),
+ S1 = form(T1, Depth),
+ OK1 = S1 =:= S,
+
+ T2 = io_lib:limit_term(Term, Depth+1),
+ S2 = form(T2, Depth),
+ OK2 = S2 =:= S,
+
+ T3 = io_lib:limit_term(Term, Depth-1),
+ S3 = form(T3, Depth),
+ OK3 = S3 =/= S,
+
+ R = case {OK1, OK2, OK3} of
+ {true, true, true} -> 2;
+ {true, true, false} -> 1;
+ _ -> 0
+ end,
+ {{S, S1, S2}, R}.
+
+form(Term, Depth) ->
+ lists:flatten(io_lib:format("~W", [Term, Depth])).