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.erl2334
1 files changed, 1275 insertions, 1059 deletions
diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl
index cb96f8b575..f097552e8c 100644
--- a/lib/stdlib/test/io_SUITE.erl
+++ b/lib/stdlib/test/io_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1999-2014. 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.
@@ -19,25 +19,24 @@
%%
-module(io_SUITE).
--export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
- init_per_group/2,end_per_group/2]).
-
--export([init_per_testcase/2, end_per_testcase/2]).
+-export([all/0, suite/0]).
-export([error_1/1, float_g/1, otp_5403/1, otp_5813/1, otp_6230/1,
otp_6282/1, otp_6354/1, otp_6495/1, otp_6517/1, otp_6502/1,
- manpage/1, otp_6708/1, otp_7084/1, otp_7421/1,
+ manpage/1, otp_6708/1, otp_7084/0, 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, bad_printable_range/1,
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]).
+ maps/1, coverage/1, otp_14178_unicode_atoms/1, otp_14175/1,
+ otp_14285/1, limit_term/1, otp_14983/1, otp_15103/1, otp_15076/1,
+ otp_15159/1]).
--export([pretty/2]).
+-export([pretty/2, trf/3]).
-%-define(debug, true).
+%%-define(debug, true).
-ifdef(debug).
-define(format(S, A), io:format(S, A)).
@@ -46,24 +45,14 @@
-define(t, test_server).
-define(privdir(_), "./io_SUITE_priv").
-else.
--include_lib("test_server/include/test_server.hrl").
+-include_lib("common_test/include/ct.hrl").
-define(format(S, A), ok).
--define(privdir(Conf), ?config(priv_dir, Conf)).
+-define(privdir(Conf), proplists:get_value(priv_dir, Conf)).
-endif.
-
-% Default timetrap timeout (set in init_per_testcase).
--define(default_timeout, ?t:minutes(1)).
-
-init_per_testcase(_Case, Config) ->
- ?line Dog = ?t:timetrap(?default_timeout),
- [{watchdog, Dog} | Config].
-end_per_testcase(_Case, _Config) ->
- Dog = ?config(watchdog, _Config),
- test_server:timetrap_cancel(Dog),
- ok.
-
-suite() -> [{ct_hooks,[ts_install_cth]}].
+suite() ->
+ [{ct_hooks,[ts_install_cth]},
+ {timetrap,{minutes,1}}].
all() ->
[error_1, float_g, otp_5403, otp_5813, otp_6230,
@@ -74,873 +63,591 @@ 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].
-
-groups() ->
- [].
-
-init_per_suite(Config) ->
- Config.
+ format_string, maps, coverage, otp_14178_unicode_atoms, otp_14175,
+ otp_14285, limit_term, otp_14983, otp_15103, otp_15076, otp_15159].
-end_per_suite(_Config) ->
- ok.
-
-init_per_group(_GroupName, Config) ->
- Config.
-
-end_per_group(_GroupName, Config) ->
- Config.
-
-
-error_1(doc) ->
- ["Error cases for output"];
-error_1(suite) ->
- [];
+%% Error cases for output.
error_1(Config) when is_list(Config) ->
%% We don't do erroneous output on stdout - the test server
%% seems to catch that somehow.
- ?line PrivDir = ?privdir(Config),
- ?line File = filename:join(PrivDir, "slask"),
- ?line {ok, F1} = file:open(File, [write]),
- ?line {'EXIT', _} = (catch io:format(muttru, "hej", [])),
- ?line {'EXIT', _} = (catch io:format(F1, pelle, "hej")),
- ?line {'EXIT', _} = (catch io:format(F1, 1, "hej")),
- ?line {'EXIT', _} = (catch io:format(F1, "~p~", [kaka])),
- ?line {'EXIT', _} = (catch io:format(F1, "~m~n", [kaka])),
+ PrivDir = ?privdir(Config),
+ File = filename:join(PrivDir, "slask"),
+ {ok, F1} = file:open(File, [write]),
+ {'EXIT', _} = (catch io:format(muttru, "hej", [])),
+ {'EXIT', _} = (catch io:format(F1, pelle, "hej")),
+ {'EXIT', _} = (catch io:format(F1, 1, "hej")),
+ {'EXIT', _} = (catch io:format(F1, "~p~", [kaka])),
+ {'EXIT', _} = (catch io:format(F1, "~m~n", [kaka])),
%% This causes the file process to die, and it is linked to us,
%% so we can't catch the error this easily.
-% ?line {'EXIT', _} = (catch io:put_chars(F1, 666)),
+ %% {'EXIT', _} = (catch io:put_chars(F1, 666)),
- ?line file:close(F1),
- ?line {'EXIT', _} = (catch io:format(F1, "~p", ["hej"])),
+ file:close(F1),
+ {'EXIT', _} = (catch io:format(F1, "~p", ["hej"])),
ok.
float_g(Config) when is_list(Config) ->
- ?line ["5.00000e-2",
- "0.500000",
- "5.00000",
- "50.0000",
- "500.000",
- "5000.00",
- "5.00000e+4",
- "5.00000e+5"] = float_g_1("~g", 5.0, -2, 5),
-
- ?line ["-5.0000e-2",
- "-0.50000",
- "-5.0000",
- "-50.000",
- "-500.00",
- "-5000.0",
- "-5.0000e+4",
- "-5.0000e+5"] = float_g_1("~.5g", -5.0, -2, 5),
-
- ?line ["5.000e-2",
- "0.5000",
- "5.000",
- "50.00",
- "500.0",
- "5.000e+3",
- "5.000e+4",
- "5.000e+5"] = float_g_1("~.4g", 5.0, -2, 5),
-
- ?line ["-5.00e-2",
- "-0.500",
- "-5.00",
- "-50.0",
- "-5.00e+2",
- "-5.00e+3",
- "-5.00e+4",
- "-5.00e+5"] = float_g_1("~.3g", -5.0, -2, 5),
-
- ?line ["5.0e-2",
- "0.50",
- "5.0",
- "5.0e+1",
- "5.0e+2",
- "5.0e+3",
- "5.0e+4",
- "5.0e+5"] = float_g_1("~.2g", 5.0, -2, 5),
-
- ?line
- case catch fmt("~.1g", [0.5]) of
- "0.5" ->
- ?line
- ["5.0e-2",
- "0.5",
- "5.0e+0",
- "5.0e+1",
- "5.0e+2",
- "5.0e+3",
- "5.0e+4",
- "5.0e+5"] = float_g_1("~.1g", 5.0, -2, 5);
- {'EXIT',_} -> ok
- end,
-
- ?line ["4.99999e-2",
- "0.499999",
- "4.99999",
- "49.9999",
- "499.999",
- "4999.99",
- "4.99999e+4",
- "4.99999e+5"] = float_g_1("~g", 4.9999949999, -2, 5),
-
- ?line ["-5.00000e-2",
- "-0.500000",
- "-5.00000",
- "-50.0000",
- "-500.000",
- "-5000.00",
- "-5.00000e+4",
- "-5.00000e+5"] = float_g_1("~g", -4.9999950001, -2, 5),
+ ["5.00000e-2",
+ "0.500000",
+ "5.00000",
+ "50.0000",
+ "500.000",
+ "5000.00",
+ "5.00000e+4",
+ "5.00000e+5"] = float_g_1("~g", 5.0, -2, 5),
+
+ ["-5.0000e-2",
+ "-0.50000",
+ "-5.0000",
+ "-50.000",
+ "-500.00",
+ "-5000.0",
+ "-5.0000e+4",
+ "-5.0000e+5"] = float_g_1("~.5g", -5.0, -2, 5),
+
+ ["5.000e-2",
+ "0.5000",
+ "5.000",
+ "50.00",
+ "500.0",
+ "5.000e+3",
+ "5.000e+4",
+ "5.000e+5"] = float_g_1("~.4g", 5.0, -2, 5),
+
+ ["-5.00e-2",
+ "-0.500",
+ "-5.00",
+ "-50.0",
+ "-5.00e+2",
+ "-5.00e+3",
+ "-5.00e+4",
+ "-5.00e+5"] = float_g_1("~.3g", -5.0, -2, 5),
+
+ ["5.0e-2",
+ "0.50",
+ "5.0",
+ "5.0e+1",
+ "5.0e+2",
+ "5.0e+3",
+ "5.0e+4",
+ "5.0e+5"] = float_g_1("~.2g", 5.0, -2, 5),
+
+ case catch fmt("~.1g", [0.5]) of
+ "0.5" ->
+ ["5.0e-2",
+ "0.5",
+ "5.0e+0",
+ "5.0e+1",
+ "5.0e+2",
+ "5.0e+3",
+ "5.0e+4",
+ "5.0e+5"] = float_g_1("~.1g", 5.0, -2, 5);
+ {'EXIT',_} -> ok
+ end,
+
+ ["4.99999e-2",
+ "0.499999",
+ "4.99999",
+ "49.9999",
+ "499.999",
+ "4999.99",
+ "4.99999e+4",
+ "4.99999e+5"] = float_g_1("~g", 4.9999949999, -2, 5),
+
+ ["-5.00000e-2",
+ "-0.500000",
+ "-5.00000",
+ "-50.0000",
+ "-500.000",
+ "-5000.00",
+ "-5.00000e+4",
+ "-5.00000e+5"] = float_g_1("~g", -4.9999950001, -2, 5),
ok.
float_g_1(Fmt, V, Min, Max) ->
[fmt(Fmt, [V*math:pow(10, E)]) || E <- lists:seq(Min, Max)].
-otp_5403(doc) ->
- ["OTP-5403. ~s formats I/O lists and a single binary."];
-otp_5403(suite) ->
- [];
+%% OTP-5403. ~s formats I/O lists and a single binary.
otp_5403(Config) when is_list(Config) ->
- ?line "atom" = fmt("~s", [atom]),
- ?line "binary" = fmt("~s", [<<"binary">>]),
- ?line "atail" = fmt("~s", [["a" | <<"tail">>]]),
- ?line "deepcharlist" = fmt("~s", [["deep",["char",["list"]]]]),
- ?line "somebinaries" = fmt("~s", [[<<"some">>,[<<"binaries">>]]]),
+ "atom" = fmt("~s", [atom]),
+ "binary" = fmt("~s", [<<"binary">>]),
+ "atail" = fmt("~s", [["a" | <<"tail">>]]),
+ "deepcharlist" = fmt("~s", [["deep",["char",["list"]]]]),
+ "somebinaries" = fmt("~s", [[<<"some">>,[<<"binaries">>]]]),
ok.
-otp_5813(doc) ->
- ["OTP-5813. read/3 is new."];
-otp_5813(suite) ->
- [];
+%% OTP-5813. read/3 is new.
otp_5813(Config) when is_list(Config) ->
- ?line PrivDir = ?privdir(Config),
- ?line File = filename:join(PrivDir, "test"),
+ PrivDir = ?privdir(Config),
+ File = filename:join(PrivDir, "test"),
- ?line ok = file:write_file(File, <<"a. ">>),
- ?line {ok, Fd} = file:open(File, [read]),
- ?line {ok, a, 1} = io:read(Fd, '', 1),
- ?line {eof,1} = io:read(Fd, '', 1),
+ ok = file:write_file(File, <<"a. ">>),
+ {ok, Fd} = file:open(File, [read]),
+ {ok, a, 1} = io:read(Fd, '', 1),
+ {eof,1} = io:read(Fd, '', 1),
ok = file:close(Fd),
- ?line ok = file:write_file(File, <<"[}.">>),
- ?line {ok, Fd2} = file:open(File, [read]),
- ?line {error,{1,_,_},1} = io:read(Fd2, '', 1),
- ?line ok = file:close(Fd),
+ ok = file:write_file(File, <<"[}.">>),
+ {ok, Fd2} = file:open(File, [read]),
+ {error,{1,_,_},1} = io:read(Fd2, '', 1),
+ ok = file:close(Fd),
file:delete(File),
ok.
-otp_6230(doc) ->
- ["OTP-6230. ~p and ~P with (huge) binaries."];
-otp_6230(suite) ->
- [];
+%% OTP-6230. ~p and ~P with (huge) binaries.
otp_6230(Config) when is_list(Config) ->
%% The problem is actually huge binaries, but the small tests here
%% just run through most of the modified code.
- ?line "<<>>" = fmt("~P", [<<"">>,-1]),
- ?line "<<\"hej\">>" = fmt("~P", [<<"hej">>,-1]),
- ?line "{hej,...}" = fmt("~P", [{hej,<<"hej">>},2]),
- ?line "{hej,<<...>>}" = fmt("~P", [{hej,<<"hej">>},3]),
- ?line "{hej,<<\"hejs\"...>>}" = fmt("~P", [{hej,<<"hejsan">>},4]),
- ?line "{hej,<<\"hej\">>}" = fmt("~P", [{hej,<<"hej">>},6]),
- ?line "<<...>>" = fmt("~P", [<<"hej">>,1]),
- ?line "<<\"hejs\"...>>" = fmt("~P", [<<"hejsan">>,2]),
- ?line "<<\"hej\">>" = fmt("~P", [<<"hej">>,4]),
- ?line "{hej,<<127,...>>}" =
+ "<<>>" = fmt("~P", [<<"">>,-1]),
+ "<<\"hej\">>" = fmt("~P", [<<"hej">>,-1]),
+ "{hej,...}" = fmt("~P", [{hej,<<"hej">>},2]),
+ "{hej,<<...>>}" = fmt("~P", [{hej,<<"hej">>},3]),
+ "{hej,<<\"hejs\"...>>}" = fmt("~P", [{hej,<<"hejsan">>},4]),
+ "{hej,<<\"hej\">>}" = fmt("~P", [{hej,<<"hej">>},6]),
+ "<<...>>" = fmt("~P", [<<"hej">>,1]),
+ "<<\"hejs\"...>>" = fmt("~P", [<<"hejsan">>,2]),
+ "<<\"hej\">>" = fmt("~P", [<<"hej">>,4]),
+ "{hej,<<127,...>>}" =
fmt("~P", [{hej,<<127:8,<<"hej">>/binary>>},4]),
- ?line "{hej,<<127,104,101,...>>}" =
+ "{hej,<<127,104,101,...>>}" =
fmt("~P", [{hej,<<127:8,<<"hej">>/binary>>},6]),
B = list_to_binary(lists:duplicate(30000, $a)),
- ?line "<<\"aaaa"++_ = fmt("~P", [B, 20000]),
+ "<<\"aaaa"++_ = fmt("~P", [B, 20000]),
ok.
-otp_6282(doc) ->
- ["OTP-6282. ~p truncates strings (like binaries) depending on depth."];
-otp_6282(suite) ->
- [];
+%% OTP-6282. ~p truncates strings (like binaries) depending on depth.
otp_6282(Config) when is_list(Config) ->
- ?line "[]" = p("", 1, 20, 1),
- ?line "[]" = p("", 1, 20, -1),
- ?line "[...]" = p("a", 1, 20, 1),
- ?line "\"a\"" = p("a", 1, 20, 2),
- ?line "\"aa\"" = p("aa", 1, 20, 2),
- ?line "\"aaa\"" = p("aaa", 1, 20, 2),
- ?line "\"aaaa\"" = p("aaaa", 1, 20, 2),
- % ?line "\"aaaa\"..." = p("aaaaaa", 1, 20, 2),
- ?line "\"a\"" = p("a", 1, 20, -1),
- % ?line "\"aa\"..." = p([$a,$a,1000], 1, 20, 2),
- % ?line "\"aa\"..." = p([$a,$a,1000], 1, 20, 3),
- ?line "[97,97,1000]" = p([$a,$a,1000], 1, 20, 4),
+ "[]" = p("", 1, 20, 1),
+ "[]" = p("", 1, 20, -1),
+ "[...]" = p("a", 1, 20, 1),
+ "\"a\"" = p("a", 1, 20, 2),
+ "\"aa\"" = p("aa", 1, 20, 2),
+ "\"aaa\"" = p("aaa", 1, 20, 2),
+ "\"aaaa\"" = p("aaaa", 1, 20, 2),
+ "\"a\"" = p("a", 1, 20, -1),
+ "[97,97,1000]" = p([$a,$a,1000], 1, 20, 4),
S1 = lists:duplicate(200,$a),
- ?line "[...]" = p(S1, 1, 20, 1),
- % ?line "\"aaaaaaaaaaaaaaaa\"\n \"aaaaaaaaaaaaaaaa\"\n \"aaaa\"..." =
- % ?line "\"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa\"..." =
- % p(S1, 1, 20, 10),
- ?line true = "\"" ++ S1 ++ "\"" =:= p(S1, 1, 205, -1),
- ?line "[97,97,1000|...]" = p([$a,$a,1000,1000], 1, 20, 4),
-
- ?line "[[]]" = p([""], 1, 20, 2),
- ?line "[[]]" = p([""], 1, 20, -1),
- ?line "[[...]]" = p(["a"], 1, 20, 2),
- ?line "[\"a\"]" = p(["a"], 1, 20, 3),
- ?line "[\"aa\"]" = p(["aa"], 1, 20, 3),
- ?line "[\"aaa\"]" = p(["aaa"], 1, 20, 3),
- ?line "[\"a\"]" = p(["a"], 1, 20, -1),
- % ?line "[\"aa\"...]" = p([[$a,$a,1000]], 1, 20, 3),
- % ?line "[\"aa\"...]" = p([[$a,$a,1000]], 1, 20, 4),
- ?line "[[97,97,1000]]" = p([[$a,$a,1000]], 1, 20, 5),
- ?line "[[...]]" = p([S1], 1, 20, 2),
- % ?line "[\"aaaaaaaaaaaaaa\"\n \"aaaaaaaaaaaaaa\"\n \"aaaaaaaa\"...]" =
- % ?line "[\"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa\"...]" =
- % p([S1], 1, 20, 11),
- ?line true = "[\"" ++ S1 ++ "\"]" =:= p([S1], 1, 210, -1),
- ?line "[[97,97,1000|...]]" = p([[$a,$a,1000,1000]], 1, 20, 5),
-
- % ?line "[\"aaaa\"...]" = p(["aaaaa"], 1, 10, 3),
- ?line "[\"aaaaa\"]" = p(["aaaaa"], 1, 10, 6),
+ "[...]" = p(S1, 1, 20, 1),
+ true = "\"" ++ S1 ++ "\"" =:= p(S1, 1, 205, -1),
+ "[97,97,1000|...]" = p([$a,$a,1000,1000], 1, 20, 4),
+
+ "[[]]" = p([""], 1, 20, 2),
+ "[[]]" = p([""], 1, 20, -1),
+ "[[...]]" = p(["a"], 1, 20, 2),
+ "[\"a\"]" = p(["a"], 1, 20, 3),
+ "[\"aa\"]" = p(["aa"], 1, 20, 3),
+ "[\"aaa\"]" = p(["aaa"], 1, 20, 3),
+ "[\"a\"]" = p(["a"], 1, 20, -1),
+ "[[97,97,1000]]" = p([[$a,$a,1000]], 1, 20, 5),
+ "[[...]]" = p([S1], 1, 20, 2),
+ true = "[\"" ++ S1 ++ "\"]" =:= p([S1], 1, 210, -1),
+ "[[97,97,1000|...]]" = p([[$a,$a,1000,1000]], 1, 20, 5),
+
+ "[\"aaaaa\"]" = p(["aaaaa"], 1, 10, 6),
ok.
-otp_6354(doc) ->
- ["OTP-6354. io_lib_pretty rewritten."];
-otp_6354(suite) ->
- [];
+%% OTP-6354. io_lib_pretty rewritten.
otp_6354(Config) when is_list(Config) ->
%% A few tuples:
- ?line "{}" = p({}, 1, 20, -1),
- ?line "..." = p({}, 1, 20, 0),
- ?line "{}" = p({}, 1, 20, 1),
- ?line "{}" = p({}, 1, 20, 2),
- ?line "{a}" = p({a}, 1, 20, -1),
- ?line "..." = p({a}, 1, 20, 0),
- ?line "{...}" = p({a}, 1, 20, 1),
- ?line "{a}" = p({a}, 1, 20, 2),
- ?line "{a,b}" = p({a,b}, 1, 20, -1),
- ?line "..." = p({a,b}, 1, 20, 0),
- ?line "{...}" = p({a,b}, 1, 20, 1),
- ?line "{a,...}" = p({a,b}, 1, 20, 2),
- ?line "{a,b}" = p({a,b}, 1, 20, 3),
- ?line "{}" = p({}, 1, 1, -1),
- ?line "..." = p({}, 1, 1, 0),
- ?line "{}" = p({}, 1, 1, 1),
- ?line "{}" = p({}, 1, 1, 2),
- ?line "{a}" = p({a}, 1, 1, -1),
- ?line "..." = p({a}, 1, 1, 0),
- ?line "{...}" = p({a}, 1, 1, 1),
- ?line "{a}" = p({a}, 1, 1, 2),
- ?line "{a,\n b}" = p({a,b}, 1, 1, -1),
- ?line "{1,\n b}" = p({1,b}, 1, 1, -1),
- ?line "..." = p({a,b}, 1, 1, 0),
- ?line "{...}" = p({a,b}, 1, 1, 1),
- ?line "{a,...}" = p({a,b}, 1, 1, 2),
- ?line "{a,\n b}" = p({a,b}, 1, 1, 3),
- ?line "{{}}" = p({{}}, 1, 1, 2),
- ?line "{[]}" = p({[]}, 1, 1, 2),
- ?line bt(<<"{1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]}">>,
- p({1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]}, -1)),
- ?line bt(<<"{abcd,ddddd,\n ddddd}">>,
- p({abcd,ddddd,ddddd}, 1,16, -1)),
- ?line bt(<<"{1,2,a,b,\n {sfdsf,sdfdsfs},\n [sfsdf,sdfsdf]}">>,
- p({1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]}, 1, 35, 100)),
- % With other terms than atomic ones on the same line:
-% ?line bt(<<"{1,2,a,b,{sfdsf,sdfdsfs},\n [sfsdf,sdfsdf]}">>,
-% p({1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]}, 1, 35, 100)),
- % With line breaks:
-% ?line bt(<<"{1,\n"
-% " 2,\n"
-% " a,\n"
-% " b,\n"
-% " {sfdsf,sdfdsfs},\n"
-% " [sfsdf,sdfsdf]}">>,
-% p({1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]}, 1, 35, 100)),
- ?line "{1,{1,{2,3}}}" = p({1,{1,{2,3}}}, 1, 80, 100),
-
- ?line bt(<<"{wwwww,{wwwww,{wwwww,{wwwww,{wwwww,lkjsldfj,klsdjfjklds,\n"
- " sdkfjdsl,sdakfjdsklj,sdkljfsdj}}}}}">>,
- p({wwwww,{wwwww,{wwwww,{wwwww,{wwwww,lkjsldfj,klsdjfjklds,
- sdkfjdsl,sdakfjdsklj,sdkljfsdj}}}}}, -1)),
-
- % With no restriction on number of characters per line:
-% ?line bt(<<"{wwwww,{wwwww,{wwwww,{wwwww,{wwwww,lkjsldfj,klsdjfjklds,"
-% "sdkfjdsl,sdakfjdsklj,\n"
-% " sdkljfsdj}}}}}">>,
-% p({wwwww,{wwwww,{wwwww,{wwwww,{wwwww,lkjsldfj,klsdjfjklds,
-% sdkfjdsl,sdakfjdsklj,sdkljfsdj}}}}}, -1)),
-
- % With line breaks:
-% ?line bt(<<"{wwwww,{wwwww,{wwwww,{wwwww,{wwwww,lkjsldfj,\n"
-% " klsdjfjklds,\n"
-% " sdkfjdsl,\n"
-% " sdakfjdsklj,\n"
-% " sdkljfsdj}}}}}">>,
-% p({wwwww,{wwwww,{wwwww,{wwwww,{wwwww,lkjsldfj,klsdjfjklds,
-% sdkfjdsl,sdakfjdsklj,sdkljfsdj}}}}}, -1)),
- ?line bt(<<"{wwwww,\n"
- " {wwwww,\n"
- " {wwwww,\n"
- " {wwwww,\n"
- " {wwwww,\n"
- " {lkjsldfj,\n"
- " {klsdjfjklds,\n"
- " {klajsljls,\n"
- " #aaaaaaaaaaaaaaaaaaaaa"
- "aaaaaaaaaaaaaaaaaaaaaaaaaaaaa{}}}}}}}}}">>,
- p({wwwww,{wwwww,{wwwww,{wwwww,{wwwww,{lkjsldfj,
- {klsdjfjklds,{klajsljls,
- {aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa}}}}}}}}},
- -1)),
- ?line "{{...},...}" = p({{a,b},{a,b,c},{d,e,f}},1,8,2),
+ "{}" = p({}, 1, 20, -1),
+ "..." = p({}, 1, 20, 0),
+ "{}" = p({}, 1, 20, 1),
+ "{}" = p({}, 1, 20, 2),
+ "{a}" = p({a}, 1, 20, -1),
+ "..." = p({a}, 1, 20, 0),
+ "{...}" = p({a}, 1, 20, 1),
+ "{a}" = p({a}, 1, 20, 2),
+ "{a,b}" = p({a,b}, 1, 20, -1),
+ "..." = p({a,b}, 1, 20, 0),
+ "{...}" = p({a,b}, 1, 20, 1),
+ "{a,...}" = p({a,b}, 1, 20, 2),
+ "{a,b}" = p({a,b}, 1, 20, 3),
+ "{}" = p({}, 1, 1, -1),
+ "..." = p({}, 1, 1, 0),
+ "{}" = p({}, 1, 1, 1),
+ "{}" = p({}, 1, 1, 2),
+ "{a}" = p({a}, 1, 1, -1),
+ "..." = p({a}, 1, 1, 0),
+ "{...}" = p({a}, 1, 1, 1),
+ "{a}" = p({a}, 1, 1, 2),
+ "{a,\n b}" = p({a,b}, 1, 1, -1),
+ "{1,\n b}" = p({1,b}, 1, 1, -1),
+ "..." = p({a,b}, 1, 1, 0),
+ "{...}" = p({a,b}, 1, 1, 1),
+ "{a,...}" = p({a,b}, 1, 1, 2),
+ "{a,\n b}" = p({a,b}, 1, 1, 3),
+ "{{}}" = p({{}}, 1, 1, 2),
+ "{[]}" = p({[]}, 1, 1, 2),
+ bt(<<"{1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]}">>,
+ p({1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]}, -1)),
+ bt(<<"{abcd,ddddd,\n ddddd}">>,
+ p({abcd,ddddd,ddddd}, 1,16, -1)),
+ bt(<<"{1,2,a,b,\n {sfdsf,sdfdsfs},\n [sfsdf,sdfsdf]}">>,
+ p({1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]}, 1, 35, 100)),
+ "{1,{1,{2,3}}}" = p({1,{1,{2,3}}}, 1, 80, 100),
+
+ bt(<<"{wwwww,{wwwww,{wwwww,{wwwww,{wwwww,lkjsldfj,klsdjfjklds,\n"
+ " sdkfjdsl,sdakfjdsklj,sdkljfsdj}}}}}">>,
+ p({wwwww,{wwwww,{wwwww,{wwwww,{wwwww,lkjsldfj,klsdjfjklds,
+ sdkfjdsl,sdakfjdsklj,sdkljfsdj}}}}}, -1)),
+
+ bt(<<"{wwwww,\n"
+ " {wwwww,\n"
+ " {wwwww,\n"
+ " {wwwww,\n"
+ " {wwwww,\n"
+ " {lkjsldfj,\n"
+ " {klsdjfjklds,\n"
+ " {klajsljls,\n"
+ " #aaaaaaaaaaaaaaaaaaaaa"
+ "aaaaaaaaaaaaaaaaaaaaaaaaaaaaa{}}}}}}}}}">>,
+ p({wwwww,{wwwww,{wwwww,{wwwww,{wwwww,{lkjsldfj,
+ {klsdjfjklds,{klajsljls,
+ {aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa}}}}}}}}},
+ -1)),
+ "{{...},...}" = p({{a,b},{a,b,c},{d,e,f}},1,8,2),
%% Closing brackets and parentheses count:
- ?line "{{a,b,c},\n {{1,2,\n 3}}}" = p({{a,b,c},{{1,2,3}}},1,11,-1),
- % With line breaks:
-% ?line "{{a,b,c},\n {{1,\n 2,\n 3}}}" = p({{a,b,c},{{1,2,3}}},1,11,-1),
- ?line "{{a,b,c},\n [1,2,\n 3]}" = p({{a,b,c},[1,2,3]},1,10,-1),
- % With line breaks:
-% ?line "{{a,b,c},\n [1,\n 2,\n 3]}" = p({{a,b,c},[1,2,3]},1,10,-1),
- ?line "[{{a,b,c},\n {1,2,\n 3}}]" = p([{{a,b,c},{1,2,3}}],1,12,-1),
- % With line breaks:
-% ?line "[{{a,b,c},\n {1,\n 2,\n 3}}]" = p([{{a,b,c},{1,2,3}}],1,12,-1),
+ "{{a,b,c},\n {{1,2,\n 3}}}" = p({{a,b,c},{{1,2,3}}},1,11,-1),
+ %% With line breaks:
+ "{{a,b,c},\n [1,2,\n 3]}" = p({{a,b,c},[1,2,3]},1,10,-1),
+ %% With line breaks:
+ "[{{a,b,c},\n {1,2,\n 3}}]" = p([{{a,b,c},{1,2,3}}],1,12,-1),
%% A few lists:
- ?line "[]" = p([], 1, 20, -1),
- ?line "..." = p([], 1, 20, 0),
- ?line "[]" = p([], 1, 20, 1),
- ?line "[]" = p([], 1, 20, 2),
- ?line "[a]" = p([a], 1, 20, -1),
- ?line "..." = p([a], 1, 20, 0),
- ?line "[...]" = p([a], 1, 20, 1),
- ?line "[a]" = p([a], 1, 20, 2),
- ?line "[a,b]" = p([a,b], 1, 20, -1),
- ?line "..." = p([a,b], 1, 20, 0),
- ?line "[...]" = p([a,b], 1, 20, 1),
- ?line "[a|...]" = p([a,b], 1, 20, 2),
- ?line "[a,b]" = p([a,b], 1, 20, 3),
- ?line "[a|b]" = p([a|b], 1, 20, -1),
- ?line "..." = p([a|b], 1, 20, 0),
- ?line "[...]" = p([a|b], 1, 20, 1),
- ?line "[a|...]" = p([a|b], 1, 20, 2),
- ?line "[a|b]" = p([a|b], 1, 20, 3),
- ?line "[]" = p([], 1, 1, -1),
- ?line "..." = p([], 1, 1, 0),
- ?line "[]" = p([], 1, 1, 1),
- ?line "[]" = p([], 1, 1, 2),
- ?line "[a]" = p([a], 1, 1, -1),
- ?line "..." = p([a], 1, 1, 0),
- ?line "[...]" = p([a], 1, 1, 1),
- ?line "[a]" = p([a], 1, 1, 2),
- ?line "[a,\n b]" = p([a,b], 1, 1, -1),
- ?line "..." = p([a,b], 1, 1, 0),
- ?line "[...]" = p([a,b], 1, 1, 1),
- ?line "[a|...]" = p([a,b], 1, 1, 2),
- ?line "[a,\n b]" = p([a,b], 1, 1, 3),
- ?line "[a|\n b]" = p([a|b], 1, 1, -1),
- ?line "..." = p([a|b], 1, 1, 0),
- ?line "[...]" = p([a|b], 1, 1, 1),
- ?line "[a|...]" = p([a|b], 1, 1, 2),
- ?line "[a|\n b]" = p([a|b], 1, 1, 3),
- ?line "[{}]" = p([{}], 1, 1, 2),
- ?line "[[]]" = p([[]], 1, 1, 2),
- ?line bt(<<"[1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]]">>,
- p([1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]], -1)),
- ?line bt(<<"[1,2,a,b,\n {sfdsf,sdfdsfs},\n [sfsdf,sdfsdf]]">>,
- p([1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]], 1, 35, 100)),
- % With other terms than atomic ones on the same line:
-% ?line bt(<<"[1,2,a,b,{sfdsf,sdfdsfs},\n [sfsdf,sdfsdf]]">>,
-% p([1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]], 1, 35, 100)),
- % With line breaks:
-% ?line bt(<<"[1,\n"
-% " 2,\n"
-% " a,\n"
-% " b,\n"
-% " {sfdsf,sdfdsfs},\n"
-% " [sfsdf,sdfsdf]]">>,
-% p([1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]], 1, 35, 100)),
+ "[]" = p([], 1, 20, -1),
+ "..." = p([], 1, 20, 0),
+ "[]" = p([], 1, 20, 1),
+ "[]" = p([], 1, 20, 2),
+ "[a]" = p([a], 1, 20, -1),
+ "..." = p([a], 1, 20, 0),
+ "[...]" = p([a], 1, 20, 1),
+ "[a]" = p([a], 1, 20, 2),
+ "[a,b]" = p([a,b], 1, 20, -1),
+ "..." = p([a,b], 1, 20, 0),
+ "[...]" = p([a,b], 1, 20, 1),
+ "[a|...]" = p([a,b], 1, 20, 2),
+ "[a,b]" = p([a,b], 1, 20, 3),
+ "[a|b]" = p([a|b], 1, 20, -1),
+ "..." = p([a|b], 1, 20, 0),
+ "[...]" = p([a|b], 1, 20, 1),
+ "[a|...]" = p([a|b], 1, 20, 2),
+ "[a|b]" = p([a|b], 1, 20, 3),
+ "[]" = p([], 1, 1, -1),
+ "..." = p([], 1, 1, 0),
+ "[]" = p([], 1, 1, 1),
+ "[]" = p([], 1, 1, 2),
+ "[a]" = p([a], 1, 1, -1),
+ "..." = p([a], 1, 1, 0),
+ "[...]" = p([a], 1, 1, 1),
+ "[a]" = p([a], 1, 1, 2),
+ "[a,\n b]" = p([a,b], 1, 1, -1),
+ "..." = p([a,b], 1, 1, 0),
+ "[...]" = p([a,b], 1, 1, 1),
+ "[a|...]" = p([a,b], 1, 1, 2),
+ "[a,\n b]" = p([a,b], 1, 1, 3),
+ "[a|\n b]" = p([a|b], 1, 1, -1),
+ "..." = p([a|b], 1, 1, 0),
+ "[...]" = p([a|b], 1, 1, 1),
+ "[a|...]" = p([a|b], 1, 1, 2),
+ "[a|\n b]" = p([a|b], 1, 1, 3),
+ "[{}]" = p([{}], 1, 1, 2),
+ "[[]]" = p([[]], 1, 1, 2),
+ bt(<<"[1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]]">>,
+ p([1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]], -1)),
+ bt(<<"[1,2,a,b,\n {sfdsf,sdfdsfs},\n [sfsdf,sdfsdf]]">>,
+ p([1,2,a,b,{sfdsf,sdfdsfs},[sfsdf,sdfsdf]], 1, 35, 100)),
%% Element #8 is not printable:
- ?line "[49," ++ _ = p("1234567"++[3,4,5,6,7], 1, 100, 9),
- % ?line "\"1234567\"..." = p("1234567"++[3,4,5,6,7], 1, 100, 8),
+ "[49," ++ _ = p("1234567"++[3,4,5,6,7], 1, 100, 9),
+ %% "\"1234567\"..." = p("1234567"++[3,4,5,6,7], 1, 100, 8),
%% A few records:
%% -record(a, {}).
%% -record(a, {}).
- ?line "..." = p({a}, 0),
- ?line "{...}" = p({a}, 1),
- ?line "#a{}" = p({a}, 2),
- ?line "#a{}" = p({a}, -1),
+ "..." = p({a}, 0),
+ "{...}" = p({a}, 1),
+ "#a{}" = p({a}, 2),
+ "#a{}" = p({a}, -1),
%% -record(b, {f}).
- ?line "{...}" = p({b}, 1),
- ?line "..." = p({b,c}, 0),
- ?line "{...}" = p({b,c}, 1),
- ?line "#b{...}" = p({b,c}, 2),
- ?line "#b{f = c}" = p({b,c}, 3),
- ?line "#b{f = c}" = p({b,c}, -1),
- ?line "..." = p({b,{c,d}}, 0),
- ?line "{...}" = p({b,{c,d}}, 1),
- ?line "#b{...}" = p({b,{c,d}}, 2),
- ?line "#b{f = {...}}" = p({b,{c,d}}, 3),
- ?line "#b{f = {c,...}}" = p({b,{c,d}}, 4),
- ?line "#b{f = {c,d}}" = p({b,{c,d}}, 5),
- ?line "#b{f = {...}}" = p({b,{b,c}}, 3),
- ?line "#b{f = #b{...}}" = p({b,{b,c}}, 4),
- ?line "#b{f = #b{f = c}}" = p({b,{b,c}}, 5),
+ "{...}" = p({b}, 1),
+ "..." = p({b,c}, 0),
+ "{...}" = p({b,c}, 1),
+ "#b{...}" = p({b,c}, 2),
+ "#b{f = c}" = p({b,c}, 3),
+ "#b{f = c}" = p({b,c}, -1),
+ "..." = p({b,{c,d}}, 0),
+ "{...}" = p({b,{c,d}}, 1),
+ "#b{...}" = p({b,{c,d}}, 2),
+ "#b{f = {...}}" = p({b,{c,d}}, 3),
+ "#b{f = {c,...}}" = p({b,{c,d}}, 4),
+ "#b{f = {c,d}}" = p({b,{c,d}}, 5),
+ "#b{f = {...}}" = p({b,{b,c}}, 3),
+ "#b{f = #b{...}}" = p({b,{b,c}}, 4),
+ "#b{f = #b{f = c}}" = p({b,{b,c}}, 5),
%% -record(c, {f1, f2}).
- ?line "#c{f1 = d,f2 = e}" = p({c,d,e}, -1),
- ?line "..." = p({c,d,e}, 0),
- ?line "{...}" = p({c,d,e}, 1),
- ?line "#c{...}" = p({c,d,e}, 2),
- ?line "#c{f1 = d,...}" = p({c,d,e}, 3),
- ?line "#c{f1 = d,f2 = e}" = p({c,d,e}, 4),
+ "#c{f1 = d,f2 = e}" = p({c,d,e}, -1),
+ "..." = p({c,d,e}, 0),
+ "{...}" = p({c,d,e}, 1),
+ "#c{...}" = p({c,d,e}, 2),
+ "#c{f1 = d,...}" = p({c,d,e}, 3),
+ "#c{f1 = d,f2 = e}" = p({c,d,e}, 4),
%% -record(d, {a..., b..., c.., d...}).
- ?line bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,bbbbbbbbbbbbbbbbbbbb = 2,\n"
- " cccccccccccccccccccc = 3,dddddddddddddddddddd = 4,\n"
- " eeeeeeeeeeeeeeeeeeee = 5}">>,
- p({d,1,2,3,4,5}, -1)),
- % With no restriction on number of characters per line:
-% ?line bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,bbbbbbbbbbbbbbbbbbbb = 2,"
-% "cccccccccccccccccccc = 3,\n dddddddddddddddddddd = 4,"
-% "eeeeeeeeeeeeeeeeeeee = 5}">>,
-% p({d,1,2,3,4,5}, -1)),
- % With line breaks:
-% ?line bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,\n"
-% " bbbbbbbbbbbbbbbbbbbb = 2,\n"
-% " cccccccccccccccccccc = 3,\n"
-% " dddddddddddddddddddd = 4,\n"
-% " eeeeeeeeeeeeeeeeeeee = 5}">>,
-% p({d,1,2,3,4,5}, -1)),
- ?line "..." = p({d,1,2,3,4,5}, 0),
- ?line "{...}" = p({d,1,2,3,4,5}, 1),
- ?line "#d{...}" = p({d,1,2,3,4,5}, 2),
- ?line "#d{aaaaaaaaaaaaaaaaaaaa = 1,...}" = p({d,1,2,3,4,5}, 3),
- ?line bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,bbbbbbbbbbbbbbbbbbbb = 2,...}">>,
- p({d,1,2,3,4,5}, 4)),
- ?line bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,bbbbbbbbbbbbbbbbbbbb = 2,\n"
- " cccccccccccccccccccc = 3,...}">>,
- p({d,1,2,3,4,5}, 5)), % longer than 80 characters...
- % With no restriction on number of characters per line:
-% ?line bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,bbbbbbbbbbbbbbbbbbbb = 2,"
-% "cccccccccccccccccccc = 3,...}">>,
-% p({d,1,2,3,4,5}, 5)), % longer than 80 characters...
- % With line breaks:
-% ?line bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,\n"
-% " bbbbbbbbbbbbbbbbbbbb = 2,\n"
-% " cccccccccccccccccccc = 3,...}">>,
-% p({d,1,2,3,4,5}, 5)),
- ?line bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,bbbbbbbbbbbbbbbbbbbb = 2,\n"
- " cccccccccccccccccccc = 3,dddddddddddddddddddd = 4,...}">>,
- p({d,1,2,3,4,5}, 6)),
- % With no restriction on number of characters per line:
-% ?line bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,bbbbbbbbbbbbbbbbbbbb = 2,"
-% "cccccccccccccccccccc = 3,\n dddddddddddddddddddd = 4,...}">>,
-% p({d,1,2,3,4,5}, 6)),
- % With line breaks:
-% ?line bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,\n"
-% " bbbbbbbbbbbbbbbbbbbb = 2,\n"
-% " cccccccccccccccccccc = 3,\n"
-% " dddddddddddddddddddd = 4,...}">>,
-% p({d,1,2,3,4,5}, 6)),
- ?line bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,bbbbbbbbbbbbbbbbbbbb = 2,\n"
- " cccccccccccccccccccc = 3,dddddddddddddddddddd = 4,\n"
- " eeeeeeeeeeeeeeeeeeee = 5}">>,
- p({d,1,2,3,4,5}, 7)),
- % With no restriction on number of characters per line:
-% ?line bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,bbbbbbbbbbbbbbbbbbbb = 2,"
-% "cccccccccccccccccccc = 3,\n dddddddddddddddddddd = 4,"
-% "eeeeeeeeeeeeeeeeeeee = 5}">>,
-% p({d,1,2,3,4,5}, 7)),
- % With line breaks:
-% ?line bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,\n"
-% " bbbbbbbbbbbbbbbbbbbb = 2,\n"
-% " cccccccccccccccccccc = 3,\n"
-% " dddddddddddddddddddd = 4,\n"
-% " eeeeeeeeeeeeeeeeeeee = 5}">>,
-% p({d,1,2,3,4,5}, 7)),
- ?line bt(<<"#rrrrr{\n"
- " f1 = 1,\n"
- " f2 = #rrrrr{f1 = a,f2 = b,f3 = c},\n"
- " f3 = \n"
- " #rrrrr{\n"
- " f1 = h,f2 = i,\n"
- " f3 = \n"
- " #rrrrr{\n"
- " f1 = aa,\n"
- " f2 = \n"
- " #rrrrr{\n"
- " f1 = #rrrrr{f1 = a,f2 = b,f3 = c},\n"
- " f2 = 2,f3 = 3},\n"
- " f3 = bb}}}">>,
- p({rrrrr,1,{rrrrr,a,b,c},{rrrrr,h,i,
- {rrrrr,aa,{rrrrr,{rrrrr,a,b,c},
- 2,3},bb}}},
- -1)),
- % With other terms than atomic ones on the same line:
-% ?line bt(<<"#rrrrr{\n"
-% " f1 = 1,f2 = #rrrrr{f1 = a,f2 = b,f3 = c},\n"
-% " f3 = \n"
-% " #rrrrr{\n"
-% " f1 = h,f2 = i,\n"
-% " f3 = \n"
-% " #rrrrr{\n"
-% " f1 = aa,\n"
-% " f2 = \n"
-% " #rrrrr{\n"
-% " f1 = #rrrrr{f1 = a,f2 = b,"
-% "f3 = c},f2 = 2,f3 = 3},\n"
-% " f3 = bb}}}">>,
-% p({rrrrr,1,{rrrrr,a,b,c},{rrrrr,h,i,
-% {rrrrr,aa,{rrrrr,{rrrrr,a,b,c},
-% 2,3},bb}}},
-% -1)),
- % With line breaks:
-% ?line bt(<<"#rrrrr{\n"
-% " f1 = 1,\n"
-% " f2 = #rrrrr{f1 = a,f2 = b,f3 = c},\n"
-% " f3 = \n"
-% " #rrrrr{\n"
-% " f1 = h,\n"
-% " f2 = i,\n"
-% " f3 = \n"
-% " #rrrrr{\n"
-% " f1 = aa,\n"
-% " f2 = \n"
-% " #rrrrr{\n"
-% " f1 = #rrrrr{f1 = a,f2 = b,"
-% "f3 = c},\n"
-% " f2 = 2,\n"
-% " f3 = 3},\n"
-% " f3 = bb}}}">>,
-% p({rrrrr,1,{rrrrr,a,b,c},{rrrrr,h,i,
-% {rrrrr,aa,{rrrrr,{rrrrr,a,b,c},
-% 2,3},bb}}},
-% -1)),
- ?line bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,\n"
- " bbbbbbbbbbbbbbbbbbbb = \n"
- " #d{aaaaaaaaaaaaaaaaaaaa = a,bbbbbbbbbbbbbbbbbbbb = b,\n"
- " cccccccccccccccccccc = c,dddddddddddddddddddd = d,\n"
- " eeeeeeeeeeeeeeeeeeee = e},\n"
- " cccccccccccccccccccc = 3,\n"
- " dddddddddddddddddddd = \n"
- " #d{aaaaaaaaaaaaaaaaaaaa = h,bbbbbbbbbbbbbbbbbbbb = i,\n"
- " cccccccccccccccccccc = \n"
- " #d{aaaaaaaaaaaaaaaaaaaa = aa,"
- "bbbbbbbbbbbbbbbbbbbb = bb,\n"
- " cccccccccccccccccccc = \n"
- " #d{aaaaaaaaaaaaaaaaaaaa = 1,"
- "bbbbbbbbbbbbbbbbbbbb = 2,\n"
- " cccccccccccccccccccc = 3,"
- "dddddddddddddddddddd = 4,\n"
- " eeeeeeeeeeeeeeeeeeee = 5},\n"
- " dddddddddddddddddddd = dd,"
- "eeeeeeeeeeeeeeeeeeee = ee},\n"
- " dddddddddddddddddddd = k,"
- "eeeeeeeeeeeeeeeeeeee = l},\n"
- " eeeeeeeeeeeeeeeeeeee = 5}">>,
- p({d,1,{d,a,b,c,d,e},3,{d,h,i,{d,aa,bb,{d,1,2,3,4,5},dd,ee},
- k,l},5}, -1)),
- % With line breaks:
-% ?line bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,\n"
-% " bbbbbbbbbbbbbbbbbbbb = \n"
-% " #d{aaaaaaaaaaaaaaaaaaaa = a,\n"
-% " bbbbbbbbbbbbbbbbbbbb = b,\n"
-% " cccccccccccccccccccc = c,\n"
-% " dddddddddddddddddddd = d,\n"
-% " eeeeeeeeeeeeeeeeeeee = e},\n"
-% " cccccccccccccccccccc = 3,\n"
-% " dddddddddddddddddddd = \n"
-% " #d{aaaaaaaaaaaaaaaaaaaa = h,\n"
-% " bbbbbbbbbbbbbbbbbbbb = i,\n"
-% " cccccccccccccccccccc = \n"
-% " #d{aaaaaaaaaaaaaaaaaaaa = aa,\n"
-% " bbbbbbbbbbbbbbbbbbbb = bb,\n"
-% " cccccccccccccccccccc = \n"
-% " #d{aaaaaaaaaaaaaaaaaaaa = 1,\n"
-% " bbbbbbbbbbbbbbbbbbbb = 2,\n"
-% " cccccccccccccccccccc = 3,\n"
-% " dddddddddddddddddddd = 4,\n"
-% " eeeeeeeeeeeeeeeeeeee = 5},\n"
-% " dddddddddddddddddddd = dd,\n"
-% " eeeeeeeeeeeeeeeeeeee = ee},\n"
-% " dddddddddddddddddddd = k,\n"
-% " eeeeeeeeeeeeeeeeeeee = l},\n"
-% " eeeeeeeeeeeeeeeeeeee = 5}">>,
-% p({d,1,{d,a,b,c,d,e},3,{d,h,i,{d,aa,bb,{d,1,2,3,4,5},dd,ee},
-% k,l},5}, -1)),
+ bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,bbbbbbbbbbbbbbbbbbbb = 2,\n"
+ " cccccccccccccccccccc = 3,dddddddddddddddddddd = 4,\n"
+ " eeeeeeeeeeeeeeeeeeee = 5}">>,
+ p({d,1,2,3,4,5}, -1)),
+ "..." = p({d,1,2,3,4,5}, 0),
+ "{...}" = p({d,1,2,3,4,5}, 1),
+ "#d{...}" = p({d,1,2,3,4,5}, 2),
+ "#d{aaaaaaaaaaaaaaaaaaaa = 1,...}" = p({d,1,2,3,4,5}, 3),
+ bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,bbbbbbbbbbbbbbbbbbbb = 2,...}">>,
+ p({d,1,2,3,4,5}, 4)),
+ bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,bbbbbbbbbbbbbbbbbbbb = 2,\n"
+ " cccccccccccccccccccc = 3,...}">>,
+ p({d,1,2,3,4,5}, 5)), % longer than 80 characters...
+ bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,bbbbbbbbbbbbbbbbbbbb = 2,\n"
+ " cccccccccccccccccccc = 3,dddddddddddddddddddd = 4,...}">>,
+ p({d,1,2,3,4,5}, 6)),
+ bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,bbbbbbbbbbbbbbbbbbbb = 2,\n"
+ " cccccccccccccccccccc = 3,dddddddddddddddddddd = 4,\n"
+ " eeeeeeeeeeeeeeeeeeee = 5}">>,
+ p({d,1,2,3,4,5}, 7)),
+ bt(<<"#rrrrr{\n"
+ " f1 = 1,\n"
+ " f2 = #rrrrr{f1 = a,f2 = b,f3 = c},\n"
+ " f3 =\n"
+ " #rrrrr{\n"
+ " f1 = h,f2 = i,\n"
+ " f3 =\n"
+ " #rrrrr{\n"
+ " f1 = aa,\n"
+ " f2 =\n"
+ " #rrrrr{\n"
+ " f1 = #rrrrr{f1 = a,f2 = b,f3 = c},\n"
+ " f2 = 2,f3 = 3},\n"
+ " f3 = bb}}}">>,
+ p({rrrrr,1,{rrrrr,a,b,c},{rrrrr,h,i,
+ {rrrrr,aa,{rrrrr,{rrrrr,a,b,c},
+ 2,3},bb}}},
+ -1)),
+ bt(<<"#d{aaaaaaaaaaaaaaaaaaaa = 1,\n"
+ " bbbbbbbbbbbbbbbbbbbb =\n"
+ " #d{aaaaaaaaaaaaaaaaaaaa = a,bbbbbbbbbbbbbbbbbbbb = b,\n"
+ " cccccccccccccccccccc = c,dddddddddddddddddddd = d,\n"
+ " eeeeeeeeeeeeeeeeeeee = e},\n"
+ " cccccccccccccccccccc = 3,\n"
+ " dddddddddddddddddddd =\n"
+ " #d{aaaaaaaaaaaaaaaaaaaa = h,bbbbbbbbbbbbbbbbbbbb = i,\n"
+ " cccccccccccccccccccc =\n"
+ " #d{aaaaaaaaaaaaaaaaaaaa = aa,"
+ "bbbbbbbbbbbbbbbbbbbb = bb,\n"
+ " cccccccccccccccccccc =\n"
+ " #d{aaaaaaaaaaaaaaaaaaaa = 1,"
+ "bbbbbbbbbbbbbbbbbbbb = 2,\n"
+ " cccccccccccccccccccc = 3,"
+ "dddddddddddddddddddd = 4,\n"
+ " eeeeeeeeeeeeeeeeeeee = 5},\n"
+ " dddddddddddddddddddd = dd,"
+ "eeeeeeeeeeeeeeeeeeee = ee},\n"
+ " dddddddddddddddddddd = k,"
+ "eeeeeeeeeeeeeeeeeeee = l},\n"
+ " eeeeeeeeeeeeeeeeeeee = 5}">>,
+ p({d,1,{d,a,b,c,d,e},3,{d,h,i,{d,aa,bb,{d,1,2,3,4,5},dd,ee},
+ k,l},5}, -1)),
A = aaaaaaaaaaaaa,
%% Print the record with dots at the end of the line (Ll = 80).
- ?line "{aaaaaaa" ++ _ =
- p({A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,
- {A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,
- {A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,
- {A,{A,{ggg,{hhh,{ii,{jj,{kk,{ll,{mm,{nn,{oo,{d,1,2,3,4,5}
- }}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}
- }}}}}}}}}}}}}}}}, 146),
- ?line "{aaaaaaa" ++ _ =
- p({A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,
- {A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,
- {A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,
- {A,{A,{A,{A,{A,{ggg,{hhh,{ii,{jj,{kk,{ll,{mm,{nn,{oo,{a}
- }}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}
- }}}}}}}}}}}}}}}}}}}, 152),
-
- ?line bt(<<"{aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {g,{h,{i,{j,{k,{l,{m,{n,{o,#"
- "d{...}}}}}}}}}}}}}}}}">>,
- p({A,{A,{A,{A,{A,{A,
- {g,{h,{i,{j,{k,{l,{m,{n,{o,{d,1,2,3,4,5}}}}}}}}}}}}}}}}, 32)),
- ?line bt(<<"{a,#b{f = {c,{d,{e,{f,...}}}}}}">>,
- p({a,{b,{c,{d,{e,{f,g}}}}}}, 12)),
- ?line bt(<<"{aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,#c{f1 = ddd,"
- "f2 = eee}}}}}}}}}}">>,
- p({A,{A,{A,{A,{A,{A,{A,{A,{A,{c,ddd,eee}}}}}}}}}}, 100)),
- ?line bt(<<"{aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,{aaaaaaaaaaaaa,{aaaaaaaaaaaaa,...}}}}">>,
- p({A,{A,{A,{A,{b}}}}}, 8)),
- % With no restriction on number of characters per line:
-% ?line bt(<<"{aaaaaaaaaaaaa,{aaaaaaaaaaaaa,{aaaaaaaaaaaaa,"
-% "{aaaaaaaaaaaaa,...}}}}">>,
-% p({A,{A,{A,{A,{b}}}}}, 8)),
- ?line bt(<<"{aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,{aaaaaaaaaaaaa,{aaaaaaaaaaaaa,...}}}}}">>,
- p({A,{A,{A,{A,{A,{b}}}}}}, 10)),
- % With no restriction on number of characters per line:
-% ?line bt(<<"{aaaaaaaaaaaaa,\n"
-% " {aaaaaaaaaaaaa,{aaaaaaaaaaaaa,{aaaaaaaaaaaaa,"
-% "{aaaaaaaaaaaaa,...}}}}}">>,
-% p({A,{A,{A,{A,{A,{b}}}}}}, 10)),
- ?line bt(<<"{aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,"
- "{aaaaaaaaaaaaa,#a{}}}}}}}}}}}">>,
- p({A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{a}}}}}}}}}}}, 23)),
- ?line bt(<<"{aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n",
- " #rrrrr{\n"
- " f1 = kljlkjlksfdgkljlsdkjf,"
- "f2 = kljkljsdaflkjlkjsdf,...}}}}">>,
- p({A,{A,{A,{rrrrr, kljlkjlksfdgkljlsdkjf,
- kljkljsdaflkjlkjsdf,
- asdfkldsjfklkljsdklfds}}}}, 10)),
- % With no restriction on number of characters per line:
-% ?line bt(<<"{aaaaaaaaaaaaa,\n"
-% " {aaaaaaaaaaaaa,\n"
-% " {aaaaaaaaaaaaa,\n",
-% " #rrrrr{f1 = kljlkjlksfdgkljlsdkjf,f2 = "
-% "kljkljsdaflkjlkjsdf,...}}}}">>,
-% p({A,{A,{A,{rrrrr, kljlkjlksfdgkljlsdkjf,
-% kljkljsdaflkjlkjsdf,
-% asdfkldsjfklkljsdklfds}}}}, 10)),
- ?line bt(<<"{aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {aaaaaaaaaaaaa,\n"
- " {g,{h,{i,{j,{k,{l,{m,{n,"
- "{o,#a{}}}}}}}}}}}}}}}}}">>,
- p({A,{A,{A,{A,{A,{A,{A,
- {g,{h,{i,{j,{k,{l,{m,{n,{o,{a}}}}}}}}}}}}}}}}}, 100)),
- ?line bt(<<"#c{\n"
- " f1 = \n"
- " #c{\n"
- " f1 = \n"
- " #c{\n"
- " f1 = \n"
- " #c{\n"
- " f1 = \n"
- " #c{\n"
- " f1 = \n"
- " #c{\n"
- " f1 = \n"
- " #c{\n"
- " f1 = \n"
- " #c{\n"
- " f1 = \n"
- " #c{\n"
- " f1 = #c{f1 = #c{f1 = #c{f1 = a,"
- "f2 = b},f2 = b},f2 = b},\n"
- " f2 = b},\n"
- " f2 = b},\n"
- " f2 = b},\n"
- " f2 = b},\n"
- " f2 = b},\n"
- " f2 = b},\n"
- " f2 = b},\n"
- " f2 = b},\n"
- " f2 = b}">>,
- p({c,{c,{c,{c,{c,{c,{c,{c,{c,{c,{c,{c,a,b},b},b},b},b},b},
- b},b},b},b},b},b}, -1)),
- ?line bt(<<"#rrrrr{\n"
- " f1 = \n"
- " #rrrrr{\n"
- " f1 = \n"
- " #rrrrr{\n"
- " f1 = \n"
- " #rrrrr{\n"
- " f1 = \n"
- " {rrrrr,{rrrrr,a,#rrrrr{f1 = {rrrrr,1,2},f2 = a,"
- "f3 = b}},b},\n"
- " f2 = {rrrrr,c,d},\n"
- " f3 = {rrrrr,1,2}},\n"
- " f2 = 1,f3 = 2},\n"
- " f2 = 3,f3 = 4},\n"
- " f2 = 5,f3 = 6}">>,
- p({rrrrr,{rrrrr,{rrrrr,{rrrrr,{rrrrr,{rrrrr,a,{rrrrr,
- {rrrrr,1,2},a,b}},b},{rrrrr,c,d},{rrrrr,1,2}},
- 1,2},3,4},5,6}, -1)),
- % With other terms than atomic ones on the same line:
-% ?line bt(<<"#rrrrr{\n"
-% " f1 = \n"
-% " #rrrrr{\n"
-% " f1 = \n"
-% " #rrrrr{\n"
-% " f1 = \n"
-% " #rrrrr{\n"
-% " f1 = \n"
-% " {rrrrr,{rrrrr,a,#rrrrr{f1 = {rrrrr,1,2},f2 = a,"
-% "f3 = b}},b},\n"
-% " f2 = {rrrrr,c,d},f3 = {rrrrr,1,2}},\n"
-% " f2 = 1,f3 = 2},\n"
-% " f2 = 3,f3 = 4},\n"
-% " f2 = 5,f3 = 6}">>,
-% p({rrrrr,{rrrrr,{rrrrr,{rrrrr,{rrrrr,{rrrrr,a,{rrrrr,
-% {rrrrr,1,2},a,b}},b},{rrrrr,c,d},{rrrrr,1,2}},
-% 1,2},3,4},5,6}, -1)),
- % With no restriction on number of characters per line:
-% ?line bt(<<"#rrrrr{\n"
-% " f1 = \n"
-% " #rrrrr{\n"
-% " f1 = \n"
-% " #rrrrr{\n"
-% " f1 = \n"
-% " #rrrrr{\n"
-% " f1 = {rrrrr,{rrrrr,a,#rrrrr{f1 = {rrrrr,1,2},f2 = a,"
-% "f3 = b}},b},\n"
-% " f2 = {rrrrr,c,d},f3 = {rrrrr,1,2}},\n"
-% " f2 = 1,f3 = 2},\n"
-% " f2 = 3,f3 = 4},\n"
-% " f2 = 5,f3 = 6}">>,
-% p({rrrrr,{rrrrr,{rrrrr,{rrrrr,{rrrrr,{rrrrr,a,{rrrrr,
-% {rrrrr,1,2},a,b}},b},{rrrrr,c,d},{rrrrr,1,2}},
-% 1,2},3,4},5,6}, -1)),
- % With line breaks:
-% ?line bt(<<"#rrrrr{\n"
-% " f1 = \n"
-% " #rrrrr{\n"
-% " f1 = \n"
-% " #rrrrr{\n"
-% " f1 = \n"
-% " #rrrrr{\n"
-% " f1 = {rrrrr,{rrrrr,a,#rrrrr{f1 = {rrrrr,1,2},f2 = a,"
-% "f3 = b}},b},\n"
-% " f2 = {rrrrr,c,d},\n"
-% " f3 = {rrrrr,1,2}},\n"
-% " f2 = 1,\n"
-% " f3 = 2},\n"
-% " f2 = 3,\n"
-% " f3 = 4},\n"
-% " f2 = 5,\n"
-% " f3 = 6}">>,
-% p({rrrrr,{rrrrr,{rrrrr,{rrrrr,{rrrrr,{rrrrr,a,{rrrrr,
-% {rrrrr,1,2},a,b}},b},{rrrrr,c,d},{rrrrr,1,2}},
-% 1,2},3,4},5,6}, -1)),
- ?line "{aaa,\n {aaa," ++ _ =
+ "{aaaaaaa" ++ _ =
+ p({A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,
+ {A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,
+ {A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,
+ {A,{A,{ggg,{hhh,{ii,{jj,{kk,{ll,{mm,{nn,{oo,{d,1,2,3,4,5}
+ }}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}
+ }}}}}}}}}}}}}}}}, 146),
+ "{aaaaaaa" ++ _ =
+ p({A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,
+ {A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,
+ {A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{A,
+ {A,{A,{A,{A,{A,{ggg,{hhh,{ii,{jj,{kk,{ll,{mm,{nn,{oo,{a}
+ }}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}
+ }}}}}}}}}}}}}}}}}}}, 152),
+
+ bt(<<"{aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {g,{h,{i,{j,{k,{l,{m,{n,{o,#"
+ "d{...}}}}}}}}}}}}}}}}">>,
+ p({A,{A,{A,{A,{A,{A,
+ {g,{h,{i,{j,{k,{l,{m,{n,{o,{d,1,2,3,4,5}}}}}}}}}}}}}}}}, 32)),
+ bt(<<"{a,#b{f = {c,{d,{e,{f,...}}}}}}">>,
+ p({a,{b,{c,{d,{e,{f,g}}}}}}, 12)),
+ bt(<<"{aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,#c{f1 = ddd,"
+ "f2 = eee}}}}}}}}}}">>,
+ p({A,{A,{A,{A,{A,{A,{A,{A,{A,{c,ddd,eee}}}}}}}}}}, 100)),
+ bt(<<"{aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,{aaaaaaaaaaaaa,{aaaaaaaaaaaaa,...}}}}">>,
+ p({A,{A,{A,{A,{b}}}}}, 8)),
+ bt(<<"{aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,{aaaaaaaaaaaaa,{aaaaaaaaaaaaa,...}}}}}">>,
+ p({A,{A,{A,{A,{A,{b}}}}}}, 10)),
+ bt(<<"{aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,"
+ "{aaaaaaaaaaaaa,#a{}}}}}}}}}}}">>,
+ p({A,{A,{A,{A,{A,{A,{A,{A,{A,{A,{a}}}}}}}}}}}, 23)),
+ bt(<<"{aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n",
+ " #rrrrr{\n"
+ " f1 = kljlkjlksfdgkljlsdkjf,"
+ "f2 = kljkljsdaflkjlkjsdf,...}}}}">>,
+ p({A,{A,{A,{rrrrr, kljlkjlksfdgkljlsdkjf,
+ kljkljsdaflkjlkjsdf,
+ asdfkldsjfklkljsdklfds}}}}, 10)),
+ bt(<<"{aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {aaaaaaaaaaaaa,\n"
+ " {g,{h,{i,{j,{k,{l,{m,{n,"
+ "{o,#a{}}}}}}}}}}}}}}}}}">>,
+ p({A,{A,{A,{A,{A,{A,{A,
+ {g,{h,{i,{j,{k,{l,{m,{n,{o,{a}}}}}}}}}}}}}}}}}, 100)),
+ bt(<<"#c{\n"
+ " f1 =\n"
+ " #c{\n"
+ " f1 =\n"
+ " #c{\n"
+ " f1 =\n"
+ " #c{\n"
+ " f1 =\n"
+ " #c{\n"
+ " f1 =\n"
+ " #c{\n"
+ " f1 =\n"
+ " #c{\n"
+ " f1 =\n"
+ " #c{\n"
+ " f1 =\n"
+ " #c{\n"
+ " f1 = #c{f1 = #c{f1 = #c{f1 = a,"
+ "f2 = b},f2 = b},f2 = b},\n"
+ " f2 = b},\n"
+ " f2 = b},\n"
+ " f2 = b},\n"
+ " f2 = b},\n"
+ " f2 = b},\n"
+ " f2 = b},\n"
+ " f2 = b},\n"
+ " f2 = b},\n"
+ " f2 = b}">>,
+ p({c,{c,{c,{c,{c,{c,{c,{c,{c,{c,{c,{c,a,b},b},b},b},b},b},
+ b},b},b},b},b},b}, -1)),
+ bt(<<"#rrrrr{\n"
+ " f1 =\n"
+ " #rrrrr{\n"
+ " f1 =\n"
+ " #rrrrr{\n"
+ " f1 =\n"
+ " #rrrrr{\n"
+ " f1 =\n"
+ " {rrrrr,{rrrrr,a,#rrrrr{f1 = {rrrrr,1,2},f2 = a,"
+ "f3 = b}},b},\n"
+ " f2 = {rrrrr,c,d},\n"
+ " f3 = {rrrrr,1,2}},\n"
+ " f2 = 1,f3 = 2},\n"
+ " f2 = 3,f3 = 4},\n"
+ " f2 = 5,f3 = 6}">>,
+ p({rrrrr,{rrrrr,{rrrrr,{rrrrr,{rrrrr,{rrrrr,a,{rrrrr,
+ {rrrrr,1,2},a,b}},b},{rrrrr,c,d},{rrrrr,1,2}},
+ 1,2},3,4},5,6}, -1)),
+ "{aaa,\n {aaa," ++ _ =
p({aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,
- {aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,
- {aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,
- {aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,
- {aaa,a}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}},
+ {aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,
+ {aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,
+ {aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,{aaa,
+ {aaa,a}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}}},
1, 80, -1),
%% A few other cases...
- ?line "{a,#Fun<" ++ _ = lists:flatten(io_lib_pretty:print({a,fun fmt/2})),
- ?line "#Fun<" ++ _ = io_lib_pretty:print(fun() -> foo end),
- % ?line "[<<\"foobar\">>|<<\"barf\"...>>]" =
- % p([<<"foobar">>|<<"barfoo">>], 1, 30, 4),
+ "{a,#Fun<" ++ _ = lists:flatten(io_lib_pretty:print({a,fun fmt/2})),
+ "#Fun<" ++ _ = io_lib_pretty:print(fun() -> foo end),
%% No support for negative columns any more:
- ?line "[a,\n [b,\n c,\n d,\n [e,\n f]],\n c]" =
- p([a,[b,c,d,[e,f]],c], -1, 2, 10),
- ?line "[a,\n [b,\n c,\n d,\n [e,\n f]],\n c]" =
- p([a,[b,c,d,[e,f]],c], 0, 2, 10),
+ "[a,\n [b,\n c,\n d,\n [e,\n f]],\n c]" =
+ p([a,[b,c,d,[e,f]],c], -1, 2, 10),
+ "[a,\n [b,\n c,\n d,\n [e,\n f]],\n c]" =
+ p([a,[b,c,d,[e,f]],c], 0, 2, 10),
%% 20 bytes are tried first, then the rest. Try 21 bytes:
L = lists:duplicate(20, $a),
- % ?line bt(<<"<<\"aaaaaa\"\n \"aaaaaa\"\n \"aaaaaa\"\n \"aaa\">>">>,
- ?line bt(<<"<<\"aaaaaaaaaaaaaaaaaaaaa\">>">>,
- p(list_to_binary([$a | L]), 1, 10, -1)),
- ?line "<<97," ++ _ = p(list_to_binary(L ++ [3]), 1, 10, -1),
- % ?line "<<\"aaaa\"...>>" = p(list_to_binary(L ++ [3]), 1, 10, 2),
- % ?line "<<\"aaaaaa\"\n \"aa\"...>>" =
- % ?line "<<\"aaaaaaaa\"...>>" =
- % p(list_to_binary(L ++ [3]), 1, 10, 3),
- % ?line "<<\"aaaaaa\"\n \"aaaaaa\"\n \"aaaaaa\"\n \"aa\"...>>" =
- % ?line "<<\"aaaaaaaaaaaaaaaaaaaa\"...>>" =
- % p(list_to_binary(L ++ [3]), 1, 10, 21),
- ?line "<<97," ++ _ = p(list_to_binary(L ++ [3]), 1, 10, 22),
-
- ?line "\"\\b\\t\\n\\v\\f\\r\\e\250\"" =
- p([8,9,10,11,12,13,27,168], 1, 40, -1),
- % ?line "\"\\b\\t\\n\"\n \"\\v\\f\\r\"\n \"\\e\250\"" =
- ?line "\"\\b\\t\\n\\v\\f\\r\\e¨\"" =
- p([8,9,10,11,12,13,27,168], 1, 10, -1),
- ?line "\"\\b\\t\\n\\v\\f\\r\\e\250\"" =
- p([8,9,10,11,12,13,27,168], 1, 40, 100),
- % ?line "\"\\e\\t\\nab\"\n \"cd\"" =
- ?line "\"\\e\\t\\nabcd\"" =
- p("\e\t\nabcd", 1, 12, -1),
+ %% bt(<<"<<\"aaaaaa\"\n \"aaaaaa\"\n \"aaaaaa\"\n \"aaa\">>">>,
+ bt(<<"<<\"aaaaaaaaaaaaaaaaaaaaa\">>">>,
+ p(list_to_binary([$a | L]), 1, 10, -1)),
+ "<<97," ++ _ = p(list_to_binary(L ++ [3]), 1, 10, -1),
+ "<<97," ++ _ = p(list_to_binary(L ++ [3]), 1, 10, 22),
+
+ "\"\\b\\t\\n\\v\\f\\r\\e\250\"" =
+ p([8,9,10,11,12,13,27,168], 1, 40, -1),
+ %% "\"\\b\\t\\n\"\n \"\\v\\f\\r\"\n \"\\e\250\"" =
+ "\"\\b\\t\\n\\v\\f\\r\\e¨\"" =
+ p([8,9,10,11,12,13,27,168], 1, 10, -1),
+ "\"\\b\\t\\n\\v\\f\\r\\e\250\"" =
+ p([8,9,10,11,12,13,27,168], 1, 40, 100),
+ %% "\"\\e\\t\\nab\"\n \"cd\"" =
+ "\"\\e\\t\\nabcd\"" =
+ p("\e\t\nabcd", 1, 12, -1),
%% DEL (127) is special...
- ?line "[127]" = p("\d", 1, 10, -1),
- ?line "[127]" = p([127], 1, 10, 100),
+ "[127]" = p("\d", 1, 10, -1),
+ "[127]" = p([127], 1, 10, 100),
- ?line "<<\"\\b\\t\\n\\v\\f\\r\\e\250\">>" =
- p(<<8,9,10,11,12,13,27,168>>, 1, 40, -1),
- ?line "<<\"\\b\\t\\n\\v\\f\\r\\e\250\">>" =
- p(<<8,9,10,11,12,13,27,168>>, 1, 10, -1),
- ?line "<<127>>" = p(<<127>>, 1, 10, 100),
+ "<<\"\\b\\t\\n\\v\\f\\r\\e\250\">>" =
+ p(<<8,9,10,11,12,13,27,168>>, 1, 40, -1),
+ "<<\"\\b\\t\\n\\v\\f\\r\\e\250\">>" =
+ p(<<8,9,10,11,12,13,27,168>>, 1, 10, -1),
+ "<<127>>" = p(<<127>>, 1, 10, 100),
%% "Partial" string binaries:
- ?line "<<\"he\"...>>" = p(list_to_binary("he"++[3]), 1, 80, 2),
- ?line "<<\"he\"...>>" = p(list_to_binary("he"++[3]), 1, 80, 3),
- ?line "<<104,101,3>>" = p(list_to_binary("he"++[3]), 1, 80, 4),
- ?line "<<...>>" = p(list_to_binary([3] ++ "he"), 1, 80, 1),
- ?line "<<3,...>>" = p(list_to_binary([3] ++ "he"), 1, 80, 2),
- ?line "<<3,104,...>>" = p(list_to_binary([3] ++ "he"), 1, 80, 3),
-
- ?line "<<\"12345678901234567890\"...>>" =
- p(list_to_binary("12345678901234567890"++[3]), 1, 80, 8),
- ?line "<<\"12345678901234567890\"...>>" =
- p(list_to_binary("12345678901234567890"++[3]), 1, 80, 21),
- ?line "<<49," ++ _ =
- p(list_to_binary("12345678901234567890"++[3]), 1, 80, 22),
-
- ?line "{sdfsdfj,\n 23" ++ _ =
- p({sdfsdfj,23423423342.23432423}, 1, 17, -1),
-
- ?line bt(<<"kljkljlksdjjlf kljalkjlsdajafasjdfj [kjljklasdf,kjlljsfd,sdfsdkjfsd,kjjsdf,jl,
+ "<<\"he\"...>>" = p(list_to_binary("he"++[3]), 1, 80, 2),
+ "<<\"he\"...>>" = p(list_to_binary("he"++[3]), 1, 80, 3),
+ "<<104,101,3>>" = p(list_to_binary("he"++[3]), 1, 80, 4),
+ "<<...>>" = p(list_to_binary([3] ++ "he"), 1, 80, 1),
+ "<<3,...>>" = p(list_to_binary([3] ++ "he"), 1, 80, 2),
+ "<<3,104,...>>" = p(list_to_binary([3] ++ "he"), 1, 80, 3),
+
+ "<<\"12345678901234567890\"...>>" =
+ p(list_to_binary("12345678901234567890"++[3]), 1, 80, 8),
+ "<<\"12345678901234567890\"...>>" =
+ p(list_to_binary("12345678901234567890"++[3]), 1, 80, 21),
+ "<<49," ++ _ =
+ p(list_to_binary("12345678901234567890"++[3]), 1, 80, 22),
+
+ "{sdfsdfj,\n 23" ++ _ =
+ p({sdfsdfj,23423423342.23432423}, 1, 17, -1),
+
+ bt(<<"kljkljlksdjjlf kljalkjlsdajafasjdfj [kjljklasdf,kjlljsfd,sdfsdkjfsd,kjjsdf,jl,
lkjjlajsfd|jsdf]">>,
fmt("~w ~w ~p",
[kljkljlksdjjlf,
@@ -949,45 +656,36 @@ otp_6354(Config) when is_list(Config) ->
jsdf]])),
%% Binaries are split as well:
- ?line bt(<<"<<80,100,0,55,55,55,55,55,55,55,55,55,\n "
+ bt(<<"<<80,100,0,55,55,55,55,55,55,55,55,55,\n "
"55,55,55,55,55,55,55,...>>">>,
p(<<80,100,0,55,55,55,55,55,55,55,55,55,55,55,55,55,55,55,
55,55,55,55,55,55,55,55,55,55,55,55>>,1,40,20)),
- ?line bt(<<"<<80,100,0,55,55,55,55,55,55,55,55,55,\n "
+ bt(<<"<<80,100,0,55,55,55,55,55,55,55,55,55,\n "
"55,55,55,55,55,55,55,55,55,55,55,55,\n 55,55,55,55,55,55>>">>,
p(<<80,100,0,55,55,55,55,55,55,55,55,55,55,55,55,55,55,55,
55,55,55,55,55,55,55,55,55,55,55,55>>,1,40,-1)),
- ?line "<<0,0,0,\n ...>>" = p(<<0,0,0,0,0>>, 1, 10, 4),
+ "<<0,0,0,\n ...>>" = p(<<0,0,0,0,0>>, 1, 10, 4),
%% ~W now uses ",..." when printing tuples
- ?line "[a,b|...]" = fmt("~W", [[a,b,c,d,e], 3]),
- ?line "{a,b,...}" = fmt("~W", [{a,b,c,d,e}, 3]),
+ "[a,b|...]" = fmt("~W", [[a,b,c,d,e], 3]),
+ "{a,b,...}" = fmt("~W", [{a,b,c,d,e}, 3]),
ok.
-otp_6495(doc) ->
- ["OTP-6495. io_lib_pretty bugfix."];
-otp_6495(suite) ->
- [];
+%% OTP-6495. io_lib_pretty bugfix.
otp_6495(Config) when is_list(Config) ->
- ?line bt(<<"[120,120,120,120,120,120,120,120,120,120,120,120,120,120,"
+ bt(<<"[120,120,120,120,120,120,120,120,120,120,120,120,120,120,"
"120,120,120,120,120]<<1>>">>,
fmt("~w~p", ["xxxxxxxxxxxxxxxxxxx", <<1>>])),
ok.
-otp_6517(doc) ->
- ["OTP-6517. The Format argument of fwrite can be a binary."];
-otp_6517(suite) ->
- [];
+%% OTP-6517. The Format argument of fwrite can be a binary.
otp_6517(Config) when is_list(Config) ->
- ?line "string" = fmt(<<"~s">>, [<<"string">>]),
+ "string" = fmt(<<"~s">>, [<<"string">>]),
ok.
-otp_6502(doc) ->
- ["OTP-6502. Bits."];
-otp_6502(suite) ->
- [];
+%% OTP-6502. Bits.
otp_6502(Config) when is_list(Config) ->
- ?line bt(<<
+ bt(<<
"[0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25]"
"<<0,0,8,\n"
" "
@@ -995,10 +693,7 @@ otp_6502(Config) when is_list(Config) ->
fmt("~w~p", [lists:seq(0, 25), <<17:25>>])),
ok.
-otp_7421(doc) ->
- ["OTP-7421. Soft limit of 60 chars removed when pretty printing."];
-otp_7421(suite) ->
- [];
+%% OTP-7421. Soft limit of 60 chars removed when pretty printing.
otp_7421(Config) when is_list(Config) ->
bt(<<"{aa,bb,\n"
" c,dd,\n"
@@ -1020,7 +715,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).
@@ -1030,6 +725,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]),
@@ -1063,34 +760,33 @@ rfd(rrrrr, 3) ->
[f1, f2, f3];
rfd(aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa, 0) ->
[];
+rfd('\x{400}', 1) ->
+ ['\x{400}'];
rfd(_, _) ->
no.
-manpage(doc) ->
- ["The examples in io(3) and io_lib(3)."];
-manpage(suite) ->
- [];
+%% The examples in io(3) and io_lib(3).
manpage(Config) when is_list(Config) ->
%% The examples that write or print only, not the ones that read...
- ?line bt(<<"Hello world!\n">>,
+ bt(<<"Hello world!\n">>,
fmt("Hello world!~n", [])),
- ?line bt(<<"| aaaaa|bbbbb |ccccc|\n">>, % bugfix
+ bt(<<"| aaaaa|bbbbb |ccccc|\n">>, % bugfix
fmt("|~10.5c|~-10.5c|~5c|~n", [$a, $b, $c])),
- ?line bt(<<"|**********|\n">>,
+ bt(<<"|**********|\n">>,
fmt("|~10w|~n", [{hey, hey, hey}])),
- ?line bt(<<"|{hey,hey,h|\n">>,
+ bt(<<"|{hey,hey,h|\n">>,
fmt("|~10s|~n", [io_lib:write({hey, hey, hey})])),
T = [{attributes,[[{id,age,1.50000},{mode,explicit},
{typename,"INTEGER"}], [{id,cho},{mode,explicit},{typename,'Cho'}]]},
{typename,'Person'},{tag,{'PRIVATE',3}},{mode,implicit}],
- ?line bt(<<"[{attributes,[[{id,age,1.5},{mode,explicit},{typename,"
+ bt(<<"[{attributes,[[{id,age,1.5},{mode,explicit},{typename,"
"[73,78,84,69,71,69,82]}],[{id,cho},{mode,explicit},"
"{typename,'Cho'}]]},{typename,'Person'},{tag,{'PRIVATE',3}},"
"{mode,implicit}]\n">>,
fmt("~w~n", [T])),
- ?line bt(<<"[{attributes,[[{id,age,1.5},\n"
+ bt(<<"[{attributes,[[{id,age,1.5},\n"
" {mode,explicit},\n"
" {typename,\"INTEGER\"}],\n"
" [{id,cho},{mode,explicit},{typename,'Cho'}]]},\n"
@@ -1098,7 +794,7 @@ manpage(Config) when is_list(Config) ->
" {tag,{'PRIVATE',3}},\n"
" {mode,implicit}]\n">>,
fmt("~62p~n", [T])),
- ?line bt(<<"Here T = [{attributes,[[{id,age,1.5},\n"
+ bt(<<"Here T = [{attributes,[[{id,age,1.5},\n"
" {mode,explicit},\n"
" {typename,\"INTEGER\"}],\n"
" [{id,cho},\n"
@@ -1108,67 +804,64 @@ manpage(Config) when is_list(Config) ->
" {tag,{'PRIVATE',3}},\n"
" {mode,implicit}]\n">>,
fmt("Here T = ~62p~n", [T])),
- ?line bt(<<"[{attributes,[[{id,age,1.5},{mode,explicit},"
+ bt(<<"[{attributes,[[{id,age,1.5},{mode,explicit},"
"{typename,...}],[{id,cho},{mode,...},{...}]]},"
"{typename,'Person'},{tag,{'PRIVATE',3}},{mode,implicit}]\n">>,
fmt("~W~n", [T,9])),
- ?line bt(<<"[{attributes,[[{id,age,1.5},{mode,explicit},{typename,...}],"
+ bt(<<"[{attributes,[[{id,age,1.5},{mode,explicit},{typename,...}],"
"\n "
"[{id,cho},{mode,...},{...}]]},\n {typename,'Person'},\n "
"{tag,{'PRIVATE',3}},\n {mode,implicit}]\n">>,
fmt("~62P~n", [T,9])),
- ?line "1F\n" = fmt("~.16B~n", [31]),
- ?line "-10011\n" = fmt("~.2B~n", [-19]),
- ?line "5Z\n" = fmt("~.36B~n", [5*36+35]),
- ?line "10#31\n" = fmt("~X~n", [31,"10#"]),
- ?line "-0x1F\n" = fmt("~.16X~n", [-31,"0x"]),
- ?line "10#31\n" = fmt("~.10#~n", [31]),
- ?line "-16#1F\n" = fmt("~.16#~n", [-31]),
- ?line "abc def 'abc def' {foo,1} A \n" =
+ "1F\n" = fmt("~.16B~n", [31]),
+ "-10011\n" = fmt("~.2B~n", [-19]),
+ "5Z\n" = fmt("~.36B~n", [5*36+35]),
+ "10#31\n" = fmt("~X~n", [31,"10#"]),
+ "-0x1F\n" = fmt("~.16X~n", [-31,"0x"]),
+ "10#31\n" = fmt("~.10#~n", [31]),
+ "-16#1F\n" = fmt("~.16#~n", [-31]),
+ "abc def 'abc def' {foo,1} A \n" =
fmt("~s ~w ~i ~w ~c ~n",
['abc def', 'abc def', {foo, 1},{foo, 1}, 65]),
- % fmt("~s", [65]),
+ %% fmt("~s", [65]),
%% io_lib(3)
- ?line bt(<<"{1,[2],[3],[...],...}">>,
+ bt(<<"{1,[2],[3],[...],...}">>,
lists:flatten(io_lib:write({1,[2],[3],[4,5],6,7,8,9}, 5))),
ok.
-otp_6708(doc) ->
- ["OTP-6708. Fewer newlines when pretty-printing."];
-otp_6708(suite) ->
- [];
+%% OTP-6708. Fewer newlines when pretty-printing.
otp_6708(Config) when is_list(Config) ->
- ?line bt(<<"[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,\n"
+ bt(<<"[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,\n"
" 23,24,25,26,27,28,29|...]">>,
p(lists:seq(1,1000), 30)),
- ?line bt(<<"{lkjasklfjsdak,mlkasjdflksj,klasdjfklasd,jklasdfjkl,\n"
+ bt(<<"{lkjasklfjsdak,mlkasjdflksj,klasdjfklasd,jklasdfjkl,\n"
" jklsdjfklsd,masdfjkkl}">>,
p({lkjasklfjsdak,mlkasjdflksj,klasdjfklasd,jklasdfjkl,
jklsdjfklsd, masdfjkkl}, -1)),
- ?line bt(<<"#b{f = {lkjljalksdf,jklaskfjd,kljasdlf,kljasdf,kljsdlkf,\n"
+ bt(<<"#b{f = {lkjljalksdf,jklaskfjd,kljasdlf,kljasdf,kljsdlkf,\n"
" kjdd}}">>,
p({b, {lkjljalksdf,jklaskfjd,kljasdlf,kljasdf,kljsdlkf,kjdd}},
-1)),
- ?line bt(<<"#b{f = {lkjljalksdf,jklaskfjd,kljasdlf,kljasdf,kljsdlkf,\n"
+ bt(<<"#b{f = {lkjljalksdf,jklaskfjd,kljasdlf,kljasdf,kljsdlkf,\n"
" kdd}}">>,
p({b, {lkjljalksdf,jklaskfjd,kljasdlf,kljasdf,kljsdlkf,kdd}},
-1)),
- ?line bt(<<"#e{f = undefined,g = undefined,\n"
+ bt(<<"#e{f = undefined,g = undefined,\n"
" h = #e{f = 11,g = 22,h = 333}}">>,
p({e,undefined,undefined,{e,11,22,333}}, -1)),
- ?line bt(<<"[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21|\n"
+ bt(<<"[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21|\n"
" apa11]">>,
p(lists:seq(1,21) ++ apa11, -1)),
- ?line bt(<<"[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,\n"
+ bt(<<"[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,\n"
" 23,\n"
" {{abadalkjlasdjflksdajfksdklfsdjlkfdlskjflsdj"
"flsdjfldsdsdddd}}]">>,
p(lists:seq(1,23) ++
[{{abadalkjlasdjflksdajfksdklfsdjlkfdlskjflsdjflsdjfldsdsdddd}}],
-1)),
- ?line bt(<<"{lkjasdf,\n"
+ bt(<<"{lkjasdf,\n"
" {kjkjsd,\n"
" {kjsd,\n"
" {kljsdf,\n"
@@ -1180,7 +873,7 @@ otp_6708(Config) when is_list(Config) ->
{dkjsdf,{kjlds,
{kljsd,{kljs,{kljlkjsd}}}}}}}}}},
-1)),
- ?line bt(<<"{lkjasdf,\n"
+ bt(<<"{lkjasdf,\n"
" {kjkjsd,\n"
" {kjsd,{kljsdf,{kjlsd,{dkjsdf,{kjlds,"
"{kljsd,{kljs}}}}}}}}}">>,
@@ -1188,24 +881,24 @@ otp_6708(Config) when is_list(Config) ->
{kljsdf,{kjlsd,{dkjsdf,
{kjlds,{kljsd,{kljs}}}}}}}}},
-1)),
- ?line bt(<<"<<1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,\n"
+ bt(<<"<<1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,\n"
" 22,23>>">>,
p(list_to_binary(lists:seq(1,23)), -1)),
- ?line bt(<<"<<100,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26,\n"
+ bt(<<"<<100,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26,\n"
" 27>>">>,
p(list_to_binary([100|lists:seq(10,27)]), -1)),
- ?line bt(<<"<<100,101,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,\n"
+ bt(<<"<<100,101,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,\n"
" 26>>">>,
p(list_to_binary([100,101|lists:seq(10,26)]), -1)),
- ?line bt(<<"{{<<100,101,102,10,11,12,13,14,15,16,17,18,19,20,21,22,\n"
+ bt(<<"{{<<100,101,102,10,11,12,13,14,15,16,17,18,19,20,21,22,\n"
" 23>>}}">>,
p({{list_to_binary([100,101,102|lists:seq(10,23)])}}, -1)),
- ?line bt(<<"[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22|\n"
+ bt(<<"[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22|\n"
" ap]">>,
p(lists:seq(1,22) ++ ap, -1)),
- ?line bt(<<"[1,2,3,4,5,6,7,8,9,10,{},[],\n <<>>,11,12,13,14,15]">>,
+ bt(<<"[1,2,3,4,5,6,7,8,9,10,{},[],\n <<>>,11,12,13,14,15]">>,
p(lists:seq(1,10) ++ [{},[],<<>>] ++ lists:seq(11,15),1,30,-1)),
- ?line bt(<<"[ddd,ddd,\n"
+ bt(<<"[ddd,ddd,\n"
" {1},\n"
" [1,2],\n"
" ddd,kdfd,\n"
@@ -1215,7 +908,7 @@ otp_6708(Config) when is_list(Config) ->
p([ddd,ddd,{1},[1,2],ddd,kdfd,[[1,2],a,b,c],<<"foo">>,<<"bar">>,
1,{2}],1,50,-1)),
- ?line bt(<<"{dskljsadfkjsdlkjflksdjflksdjfklsdjklfjsdklfjlsdjfkl,jksd,\n"
+ bt(<<"{dskljsadfkjsdlkjflksdjflksdjfklsdjklfjsdklfjlsdjfkl,jksd,\n"
" "
"lkjsdf,kljsdf,kljsf,kljsdf,kljsdf,jkldf,jklsdf,kljsdf,\n"
" "
@@ -1226,7 +919,7 @@ otp_6708(Config) when is_list(Config) ->
lkjsdf,kljsdf,kljsf,kljsdf,kljsdf,jkldf,jklsdf,kljsdf,
kljsdf,jklsdf,lkjfd,lkjsdf,kljsdf,kljsdf,lkjsdf,kljsdf,
lkjsdfsd,kljsdf,kjsfj}, 1, 110, -1)),
- ?line bt(<<"{dskljsadfkjsdlkjflksdjflksdjfklsdjklfjsdklfjlsdjfkl,"
+ bt(<<"{dskljsadfkjsdlkjflksdjflksdjfklsdjklfjsdklfjlsdjfkl,"
"#d{aaaaaaaaaaaaaaaaaaaa = 1,\n"
" "
"bbbbbbbbbbbbbbbbbbbb = 2,cccccccccccccccccccc = 3,\n"
@@ -1239,15 +932,12 @@ otp_6708(Config) when is_list(Config) ->
-define(ONE(N), ((1 bsl N) - 1)).
-define(ALL_ONES, ((1 bsl 52) - 1)).
-otp_7084(doc) ->
- ["OTP-7084. Printing floating point numbers nicely."];
-otp_7084(suite) ->
- [];
+
+otp_7084() ->
+ [{timetrap,{minutes,6}}]. %% valgrind needs a lot of time
+
+%% OTP-7084. Printing floating point numbers nicely.
otp_7084(Config) when is_list(Config) ->
- OldDog=?config(watchdog, Config),
- test_server:timetrap_cancel(OldDog),
- Timeout = 180,
- ?line Dog = test_server:timetrap({seconds,Timeout}),
L = [{g_warm_up, fun g_warm_up/0},
{g_big_pos_float, fun g_big_pos_float/0},
{g_small_neg_float, fun g_small_neg_float/0},
@@ -1263,7 +953,6 @@ otp_7084(Config) when is_list(Config) ->
catch throw:Reason ->
Reason
end,
- ?line test_server:timetrap_cancel(Dog),
R.
g_warm_up() ->
@@ -1295,7 +984,7 @@ g_close_to_zero() ->
g_denormalized() ->
%% Denormalized floats (mantissa carry):
-% D = 5,
+%% D = 5,
%% Faster:
D = 1,
[ft({{S,0,?ONE(N)},D,D}) || S <- [0,1], N <- lists:seq(0, 52)],
@@ -1303,7 +992,7 @@ g_denormalized() ->
g_normalized() ->
%% Normalized floats (exponent carry):
-% D = 5,
+%% D = 5,
%% Faster:
D = 1,
[ft({{S,E,?ONE(52)},D,D}) || S <- [0,1], E <- lists:seq(0, 2045)],
@@ -1322,8 +1011,7 @@ g_choice() ->
g_misc() ->
L_0_308 = lists:seq(0, 308),
L_0_307 = lists:seq(0, 307),
-% L_1_9 = lists:seq(1, 9),
-% L_0_9 = lists:seq(0, 9),
+
%% Faster:
L_1_9 = [1,5,9],
L_0_9 = [0,1,5,9],
@@ -1798,10 +1486,10 @@ pack(Sign, Exp, Frac) ->
%% Whitebox test of io_lib:collect_line/3.
io_lib_collect_line_3_wb(Config) when is_list(Config) ->
- ?line do_collect_line(binary, "\n"),
- ?line do_collect_line(binary, "\r\n"),
- ?line do_collect_line(list, "\n"),
- ?line do_collect_line(list, "\r\n"),
+ do_collect_line(binary, "\n"),
+ do_collect_line(binary, "\r\n"),
+ do_collect_line(list, "\n"),
+ do_collect_line(list, "\r\n"),
ok.
do_collect_line(Mode, Eol) ->
@@ -1860,44 +1548,44 @@ do_collect_line_adjust_rest(Rest, [List|T]) when is_list(List) ->
cr_whitespace_in_string(Config) when is_list(Config) ->
- ?line {ok,["abc"],[]} = io_lib:fread("~s", "\rabc").
+ {ok,["abc"],[]} = io_lib:fread("~s", "\rabc").
io_fread_newlines(Config) when is_list(Config) ->
- ?line PrivDir = ?privdir(Config),
- ?line Fname = filename:join(PrivDir, "io_fread_newlines.txt"),
- ?line F0 = [[0,1,2,3,4,5,6,7,8,9]],
- ?line F1 = [[0,1,2,3,4,5,6,7,8],[9]],
- ?line F2 = [[0,1,2,3,4,5,6,7],[8,9]],
- ?line F3 = [[0,1,2,3,4,5,6],[7,8,9]],
- ?line F4 = [[0,1,2,3,4,5],[6,7,8,9]],
- ?line F5 = [[0,1,2,3,4],[5,6,7,8,9]],
- ?line F6 = [[0,1,2,3],[4,5,6,7],[8,9]],
- ?line F7 = [[0,1,2],[3,4,5],[6,7,8],[9]],
- ?line F8 = [[0,1],[2,3],[4,5],[6,7],[8,9]],
- ?line F9 = [[0],[1],[2],[3],[4],[5],[6],[7],[8],[9]],
- ?line Newlines = ["\n", "\r\n", "\r"],
+ PrivDir = ?privdir(Config),
+ Fname = filename:join(PrivDir, "io_fread_newlines.txt"),
+ F0 = [[0,1,2,3,4,5,6,7,8,9]],
+ F1 = [[0,1,2,3,4,5,6,7,8],[9]],
+ F2 = [[0,1,2,3,4,5,6,7],[8,9]],
+ F3 = [[0,1,2,3,4,5,6],[7,8,9]],
+ F4 = [[0,1,2,3,4,5],[6,7,8,9]],
+ F5 = [[0,1,2,3,4],[5,6,7,8,9]],
+ F6 = [[0,1,2,3],[4,5,6,7],[8,9]],
+ F7 = [[0,1,2],[3,4,5],[6,7,8],[9]],
+ F8 = [[0,1],[2,3],[4,5],[6,7],[8,9]],
+ F9 = [[0],[1],[2],[3],[4],[5],[6],[7],[8],[9]],
+ Newlines = ["\n", "\r\n", "\r"],
try
- ?line io_fread_newlines_1([F0,F1,F2,F3,F4,F5,F6,F7,F8,F9],
+ io_fread_newlines_1([F0,F1,F2,F3,F4,F5,F6,F7,F8,F9],
Fname, Newlines)
after
file:delete(Fname)
end.
io_fread_newlines_1(Fs, Fname, [Newline|Newlines]) ->
- ?line ok = io_fread_newlines_2(Fs, Fname, Newline),
- ?line io_fread_newlines_1(Fs, Fname, Newlines);
+ ok = io_fread_newlines_2(Fs, Fname, Newline),
+ io_fread_newlines_1(Fs, Fname, Newlines);
io_fread_newlines_1(_, _, []) -> ok.
io_fread_newlines_2([F|Fs], Fname, Newline) ->
- ?line N1 = write_newlines_file(Fname, F, Newline),
- ?line {F2,N2} = read_newlines_file(Fname),
- ?line io:format("~w ~p ~w~n~n", [N1,F,N2]),
- ?line F2 = lists:flatten(F),
+ N1 = write_newlines_file(Fname, F, Newline),
+ {F2,N2} = read_newlines_file(Fname),
+ io:format("~w ~p ~w~n~n", [N1,F,N2]),
+ F2 = lists:flatten(F),
%% Intermediate newlines are not counted
- ?line N2 = N1 - (length(F) - 1)*length(Newline),
- ?line io_fread_newlines_2(Fs, Fname, Newline);
+ N2 = N1 - (length(F) - 1)*length(Newline),
+ io_fread_newlines_2(Fs, Fname, Newline);
io_fread_newlines_2([], _, _) -> ok.
@@ -1939,111 +1627,108 @@ read_newlines(Fd, Acc, N0) ->
-otp_8989(doc) ->
- "OTP-8989 io:format for ~F.Ps ignores P in some cases";
+%% OTP-8989 io:format for ~F.Ps ignores P in some cases.
otp_8989(Suite) when is_list(Suite) ->
Hello = "Hello",
- ?line " Hello" = fmt("~6.6s", [Hello]),
- ?line " Hello" = fmt("~*.6s", [6,Hello]),
- ?line " Hello" = fmt("~6.*s", [6,Hello]),
- ?line " Hello" = fmt("~*.*s", [6,6,Hello]),
+ " Hello" = fmt("~6.6s", [Hello]),
+ " Hello" = fmt("~*.6s", [6,Hello]),
+ " Hello" = fmt("~6.*s", [6,Hello]),
+ " Hello" = fmt("~*.*s", [6,6,Hello]),
%%
- ?line " Hello" = fmt("~6.5s", [Hello]),
- ?line " Hello" = fmt("~*.5s", [6,Hello]),
- ?line " Hello" = fmt("~6.*s", [5,Hello]),
- ?line " Hello" = fmt("~*.*s", [6,5,Hello]),
+ " Hello" = fmt("~6.5s", [Hello]),
+ " Hello" = fmt("~*.5s", [6,Hello]),
+ " Hello" = fmt("~6.*s", [5,Hello]),
+ " Hello" = fmt("~*.*s", [6,5,Hello]),
%%
- ?line " Hell" = fmt("~6.4s", [Hello]),
- ?line " Hell" = fmt("~*.4s", [6,Hello]),
- ?line " Hell" = fmt("~6.*s", [4,Hello]),
- ?line " Hell" = fmt("~*.*s", [6,4,Hello]),
+ " Hell" = fmt("~6.4s", [Hello]),
+ " Hell" = fmt("~*.4s", [6,Hello]),
+ " Hell" = fmt("~6.*s", [4,Hello]),
+ " Hell" = fmt("~*.*s", [6,4,Hello]),
%%
- ?line "Hello" = fmt("~5.5s", [Hello]),
- ?line "Hello" = fmt("~*.5s", [5,Hello]),
- ?line "Hello" = fmt("~5.*s", [5,Hello]),
- ?line "Hello" = fmt("~*.*s", [5,5,Hello]),
+ "Hello" = fmt("~5.5s", [Hello]),
+ "Hello" = fmt("~*.5s", [5,Hello]),
+ "Hello" = fmt("~5.*s", [5,Hello]),
+ "Hello" = fmt("~*.*s", [5,5,Hello]),
%%
- ?line " Hell" = fmt("~5.4s", [Hello]),
- ?line " Hell" = fmt("~*.4s", [5,Hello]),
- ?line " Hell" = fmt("~5.*s", [4,Hello]),
- ?line " Hell" = fmt("~*.*s", [5,4,Hello]),
+ " Hell" = fmt("~5.4s", [Hello]),
+ " Hell" = fmt("~*.4s", [5,Hello]),
+ " Hell" = fmt("~5.*s", [4,Hello]),
+ " Hell" = fmt("~*.*s", [5,4,Hello]),
%%
- ?line "Hell" = fmt("~4.4s", [Hello]),
- ?line "Hell" = fmt("~*.4s", [4,Hello]),
- ?line "Hell" = fmt("~4.*s", [4,Hello]),
- ?line "Hell" = fmt("~*.*s", [4,4,Hello]),
+ "Hell" = fmt("~4.4s", [Hello]),
+ "Hell" = fmt("~*.4s", [4,Hello]),
+ "Hell" = fmt("~4.*s", [4,Hello]),
+ "Hell" = fmt("~*.*s", [4,4,Hello]),
%%
- ?line " Hel" = fmt("~4.3s", [Hello]),
- ?line " Hel" = fmt("~*.3s", [4,Hello]),
- ?line " Hel" = fmt("~4.*s", [3,Hello]),
- ?line " Hel" = fmt("~*.*s", [4,3,Hello]),
+ " Hel" = fmt("~4.3s", [Hello]),
+ " Hel" = fmt("~*.3s", [4,Hello]),
+ " Hel" = fmt("~4.*s", [3,Hello]),
+ " Hel" = fmt("~*.*s", [4,3,Hello]),
%%
%%
- ?line "Hello " = fmt("~-6.6s", [Hello]),
- ?line "Hello " = fmt("~*.6s", [-6,Hello]),
- ?line "Hello " = fmt("~-6.*s", [6,Hello]),
- ?line "Hello " = fmt("~*.*s", [-6,6,Hello]),
+ "Hello " = fmt("~-6.6s", [Hello]),
+ "Hello " = fmt("~*.6s", [-6,Hello]),
+ "Hello " = fmt("~-6.*s", [6,Hello]),
+ "Hello " = fmt("~*.*s", [-6,6,Hello]),
%%
- ?line "Hello " = fmt("~-6.5s", [Hello]),
- ?line "Hello " = fmt("~*.5s", [-6,Hello]),
- ?line "Hello " = fmt("~-6.*s", [5,Hello]),
- ?line "Hello " = fmt("~*.*s", [-6,5,Hello]),
+ "Hello " = fmt("~-6.5s", [Hello]),
+ "Hello " = fmt("~*.5s", [-6,Hello]),
+ "Hello " = fmt("~-6.*s", [5,Hello]),
+ "Hello " = fmt("~*.*s", [-6,5,Hello]),
%%
- ?line "Hell " = fmt("~-6.4s", [Hello]),
- ?line "Hell " = fmt("~*.4s", [-6,Hello]),
- ?line "Hell " = fmt("~-6.*s", [4,Hello]),
- ?line "Hell " = fmt("~*.*s", [-6,4,Hello]),
+ "Hell " = fmt("~-6.4s", [Hello]),
+ "Hell " = fmt("~*.4s", [-6,Hello]),
+ "Hell " = fmt("~-6.*s", [4,Hello]),
+ "Hell " = fmt("~*.*s", [-6,4,Hello]),
%%
- ?line "Hello" = fmt("~-5.5s", [Hello]),
- ?line "Hello" = fmt("~*.5s", [-5,Hello]),
- ?line "Hello" = fmt("~-5.*s", [5,Hello]),
- ?line "Hello" = fmt("~*.*s", [-5,5,Hello]),
+ "Hello" = fmt("~-5.5s", [Hello]),
+ "Hello" = fmt("~*.5s", [-5,Hello]),
+ "Hello" = fmt("~-5.*s", [5,Hello]),
+ "Hello" = fmt("~*.*s", [-5,5,Hello]),
%%
- ?line "Hell " = fmt("~-5.4s", [Hello]),
- ?line "Hell " = fmt("~*.4s", [-5,Hello]),
- ?line "Hell " = fmt("~-5.*s", [4,Hello]),
- ?line "Hell " = fmt("~*.*s", [-5,4,Hello]),
+ "Hell " = fmt("~-5.4s", [Hello]),
+ "Hell " = fmt("~*.4s", [-5,Hello]),
+ "Hell " = fmt("~-5.*s", [4,Hello]),
+ "Hell " = fmt("~*.*s", [-5,4,Hello]),
%%
- ?line "Hell" = fmt("~-4.4s", [Hello]),
- ?line "Hell" = fmt("~*.4s", [-4,Hello]),
- ?line "Hell" = fmt("~-4.*s", [4,Hello]),
- ?line "Hell" = fmt("~*.*s", [-4,4,Hello]),
+ "Hell" = fmt("~-4.4s", [Hello]),
+ "Hell" = fmt("~*.4s", [-4,Hello]),
+ "Hell" = fmt("~-4.*s", [4,Hello]),
+ "Hell" = fmt("~*.*s", [-4,4,Hello]),
%%
- ?line "Hel " = fmt("~-4.3s", [Hello]),
- ?line "Hel " = fmt("~*.3s", [-4,Hello]),
- ?line "Hel " = fmt("~-4.*s", [3,Hello]),
- ?line "Hel " = fmt("~*.*s", [-4,3,Hello]),
+ "Hel " = fmt("~-4.3s", [Hello]),
+ "Hel " = fmt("~*.3s", [-4,Hello]),
+ "Hel " = fmt("~-4.*s", [3,Hello]),
+ "Hel " = fmt("~*.*s", [-4,3,Hello]),
ok.
-io_lib_fread_literal(doc) ->
- "OTP-9439 io_lib:fread bug for literate at end";
+%% OTP-9439 io_lib:fread bug for literate at end.
io_lib_fread_literal(Suite) when is_list(Suite) ->
- ?line {more,"~d",0,""} = io_lib:fread("~d", ""),
- ?line {error,{fread,integer}} = io_lib:fread("~d", " "),
- ?line {more,"~d",1,""} = io_lib:fread(" ~d", " "),
- ?line {ok,[17],"X"} = io_lib:fread(" ~d", " 17X"),
+ {more,"~d",0,""} = io_lib:fread("~d", ""),
+ {error,{fread,integer}} = io_lib:fread("~d", " "),
+ {more,"~d",1,""} = io_lib:fread(" ~d", " "),
+ {ok,[17],"X"} = io_lib:fread(" ~d", " 17X"),
%%
- ?line {more,"d",0,""} = io_lib:fread("d", ""),
- ?line {error,{fread,input}} = io_lib:fread("d", " "),
- ?line {more,"d",1,""} = io_lib:fread(" d", " "),
- ?line {ok,[],"X"} = io_lib:fread(" d", " dX"),
+ {more,"d",0,""} = io_lib:fread("d", ""),
+ {error,{fread,input}} = io_lib:fread("d", " "),
+ {more,"d",1,""} = io_lib:fread(" d", " "),
+ {ok,[],"X"} = io_lib:fread(" d", " dX"),
%%
- ?line {done,eof,_} = io_lib:fread([], eof, "~d"),
- ?line {done,eof,_} = io_lib:fread([], eof, " ~d"),
- ?line {more,C1} = io_lib:fread([], " \n", " ~d"),
- ?line {done,{error,{fread,input}},_} = io_lib:fread(C1, eof, " ~d"),
- ?line {done,{ok,[18]},""} = io_lib:fread(C1, "18\n", " ~d"),
+ {done,eof,_} = io_lib:fread([], eof, "~d"),
+ {done,eof,_} = io_lib:fread([], eof, " ~d"),
+ {more,C1} = io_lib:fread([], " \n", " ~d"),
+ {done,{error,{fread,input}},_} = io_lib:fread(C1, eof, " ~d"),
+ {done,{ok,[18]},""} = io_lib:fread(C1, "18\n", " ~d"),
%%
- ?line {done,eof,_} = io_lib:fread([], eof, "d"),
- ?line {done,eof,_} = io_lib:fread([], eof, " d"),
- ?line {more,C2} = io_lib:fread([], " \n", " d"),
- ?line {done,{error,{fread,input}},_} = io_lib:fread(C2, eof, " d"),
- ?line {done,{ok,[]},[]} = io_lib:fread(C2, "d\n", " d"),
+ {done,eof,_} = io_lib:fread([], eof, "d"),
+ {done,eof,_} = io_lib:fread([], eof, " d"),
+ {more,C2} = io_lib:fread([], " \n", " d"),
+ {done,{error,{fread,input}},_} = io_lib:fread(C2, eof, " d"),
+ {done,{ok,[]},[]} = io_lib:fread(C2, "d\n", " d"),
ok.
-printable_range(doc) ->
- "Check that the printable range set by the user actually works";
+%% 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,
@@ -2066,7 +1751,7 @@ printable_range(Suite) when is_list(Suite) ->
PrettyOptions = [{column,1},
{line_length,109},
{depth,30},
- {max_chars,60},
+ {line_max_chars,60},
{record_print_fun,
fun(_,_) -> no end},
{encoding,unicode}],
@@ -2124,16 +1809,17 @@ rpc_call_max(Node, M, F, Args) ->
%% Make sure that a bad specification for a printable range is rejected.
bad_printable_range(Config) when is_list(Config) ->
- Cmd = lists:concat([lib:progname()," +pcunnnnnicode -run erlang halt"]),
+ Cmd = ct:get_progname() ++ " +pcunnnnnicode -run erlang halt",
P = open_port({spawn, Cmd}, [stderr_to_stdout, {line, 200}]),
ok = receive
- {P, {data, {eol , "bad range of printable characters" ++ _}}} ->
- ok;
- Other ->
- Other
- after 1000 ->
- timeout
- end,
+ {P, {data, {eol , "bad range of printable characters" ++ _}}} ->
+ ok;
+ Other ->
+ Other
+ %% valgrind needs a lot of time
+ after 6000 ->
+ timeout
+ end,
catch port_close(P),
flush_from_port(P),
ok.
@@ -2145,19 +1831,17 @@ flush_from_port(P) ->
ok
end.
-io_lib_print_binary_depth_one(doc) ->
- "Test binaries printed with a depth of one behave correctly";
+%% Test binaries printed with a depth of one behave correctly.
io_lib_print_binary_depth_one(Suite) when is_list(Suite) ->
- ?line "<<>>" = fmt("~W", [<<>>, 1]),
- ?line "<<>>" = fmt("~P", [<<>>, 1]),
- ?line "<<...>>" = fmt("~W", [<<1>>, 1]),
- ?line "<<...>>" = fmt("~P", [<<1>>, 1]),
- ?line "<<...>>" = fmt("~W", [<<1:7>>, 1]),
- ?line "<<...>>" = fmt("~P", [<<1:7>>, 1]),
+ "<<>>" = fmt("~W", [<<>>, 1]),
+ "<<>>" = fmt("~P", [<<>>, 1]),
+ "<<...>>" = fmt("~W", [<<1>>, 1]),
+ "<<...>>" = fmt("~P", [<<1>>, 1]),
+ "<<...>>" = fmt("~W", [<<1:7>>, 1]),
+ "<<...>>" = fmt("~P", [<<1:7>>, 1]),
ok.
-otp_10302(doc) ->
- "OTP-10302. Unicode";
+%% 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,
@@ -2203,7 +1887,8 @@ 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},
+ {depth, Depth}, {line_max_chars, 60},
+ {record_print_fun, fun rfd/2},
{encoding, unicode}],
pretty(Term, Opts);
pretty(Term, Opts) when is_list(Opts) ->
@@ -2213,39 +1898,69 @@ pretty(Term, Opts) when is_list(Opts) ->
is_latin1(S) ->
S >= 0 andalso S =< 255.
-otp_10836(doc) ->
- "OTP-10836. ~ts extended to latin1";
+%% OTP-10836. ~ts extended to latin1.
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. The 'l' modifier
otp_10755(Suite) when is_list(Suite) ->
+ %% printing plain ascii characters
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])),
+ %% printing latin1 chars, with and without modifiers
+ T = {[255],list_to_atom([255]),[a,b,c]},
+ "{\"ÿ\",ÿ,[a,b,c]}" = fmt("~p", [T]),
+ "{\"ÿ\",ÿ,[a,b,c]}" = fmt("~tp", [T]),
+ "{[255],ÿ,[a,b,c]}" = fmt("~lp", [T]),
+ "{[255],ÿ,[a,b,c]}" = fmt("~ltp", [T]),
+ "{[255],ÿ,[a,b,c]}" = fmt("~tlp", [T]),
+ "{\"ÿ\",ÿ,...}" = fmt("~P", [T,3]),
+ "{\"ÿ\",ÿ,...}" = fmt("~tP", [T,3]),
+ "{[255],ÿ,...}" = fmt("~lP", [T,3]),
+ "{[255],ÿ,...}" = fmt("~ltP", [T,3]),
+ "{[255],ÿ,...}" = fmt("~tlP", [T,3]),
+ %% printing unicode chars, with and without modifiers
+ U = {[666],list_to_atom([666]),[a,b,c]},
+ "{[666],'\\x{29A}',[a,b,c]}" = fmt("~p", [U]),
+ case io:printable_range() of
+ unicode ->
+ "{\"ʚ\",'ʚ',[a,b,c]}" = fmt("~tp", [U]),
+ "{\"ʚ\",'ʚ',...}" = fmt("~tP", [U,3]);
+ latin1 ->
+ "{[666],'ʚ',[a,b,c]}" = fmt("~tp", [U]),
+ "{[666],'ʚ',...}" = fmt("~tP", [U,3])
+ end,
+ "{[666],'\\x{29A}',[a,b,c]}" = fmt("~lp", [U]),
+ "{[666],'ʚ',[a,b,c]}" = fmt("~ltp", [U]),
+ "{[666],'ʚ',[a,b,c]}" = fmt("~tlp", [U]),
+ "{[666],'\\x{29A}',...}" = fmt("~P", [U,3]),
+ "{[666],'\\x{29A}',...}" = fmt("~lP", [U,3]),
+ "{[666],'ʚ',...}" = fmt("~ltP", [U,3]),
+ "{[666],'ʚ',...}" = fmt("~tlP", [U,3]),
+ %% the compiler should catch uses of ~l with other than pP
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",
+ " io:format(\"~lw\", [S]),\n"
+ " io:format(\"~lW\", [S, 1]),\n"
+ " io:format(\"~ltw\", [S]),\n"
+ " io:format(\"~tlw\", [S]),\n"
+ " io:format(\"~ltW\", [S, 1]),\n"
+ " io:format(\"~tlW\", [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)"] =
+ ["format string invalid (invalid control ~lw)",
+ "format string invalid (invalid control ~lW)",
+ "format string invalid (invalid control ~ltw)",
+ "format string invalid (invalid control ~ltw)",
+ "format string invalid (invalid control ~ltW)",
+ "format string invalid (invalid control ~ltW)"] =
[lists:flatten(M:format_error(E)) || {_L,M,E} <- Ws],
ok.
@@ -2300,7 +2015,7 @@ do_io_with_huge_message_queue(Config) ->
ok;
Q ->
io:format("Q = ~p", [Q]),
- ?t:fail()
+ ct:fail(failed)
end,
ok.
@@ -2323,6 +2038,7 @@ writes(N, F1) ->
format_string(_Config) ->
%% All but padding is tested by fmt/2.
+ "xxxxxxxsss" = fmt("~10..xs", ["sss"]),
"xxxxxxsssx" = fmt("~10.4.xs", ["sss"]),
"xxxxxxsssx" = fmt("~10.4.*s", [$x, "sss"]),
ok.
@@ -2338,19 +2054,19 @@ maps(_Config) ->
%% in a map with more than one element.
"#{}" = fmt("~w", [#{}]),
- "#{a=>b}" = fmt("~w", [#{a=>b}]),
- re_fmt(<<"#\\{(a=>b|c=>d),[.][.][.]=>[.][.][.]\\}">>,
- "~W", [#{a=>b,c=>d},2]),
- re_fmt(<<"#\\{(a=>b|c=>d|e=>f),[.][.][.]=>[.][.][.],[.][.][.]\\}">>,
- "~W", [#{a=>b,c=>d,e=>f},2]),
+ "#{a => b}" = fmt("~w", [#{a=>b}]),
+ re_fmt(<<"#\\{(a => b),[.][.][.]\\}">>,
+ "~W", [#{a => b,c => d},2]),
+ re_fmt(<<"#\\{(a => b),[.][.][.]\\}">>,
+ "~W", [#{a => b,c => d,e => f},2]),
"#{}" = fmt("~p", [#{}]),
- "#{a => b}" = fmt("~p", [#{a=>b}]),
- "#{...}" = fmt("~P", [#{a=>b},1]),
+ "#{a => b}" = fmt("~p", [#{a => b}]),
+ "#{...}" = fmt("~P", [#{a => b},1]),
re_fmt(<<"#\\{(a => b|c => d),[.][.][.]\\}">>,
- "~P", [#{a=>b,c=>d},2]),
+ "~P", [#{a => b,c => d},2]),
re_fmt(<<"#\\{(a => b|c => d|e => f),[.][.][.]\\}">>,
- "~P", [#{a=>b,c=>d,e=>f},2]),
+ "~P", [#{a => b,c => d,e => f},2]),
List = [{I,I*I} || I <- lists:seq(1, 20)],
Map = maps:from_list(List),
@@ -2373,7 +2089,7 @@ re_fmt(Pattern, Format, Args) ->
nomatch ->
io:format("Pattern: ~s", [Pattern]),
io:format("Result: ~s", [S]),
- ?t:fail();
+ ct:fail(failed);
match ->
ok
end.
@@ -2431,3 +2147,503 @@ coverage(_Config) ->
io:format("~s\n", [S2]),
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),
+ "#{...}" = p(#{a => 1}, 1),
+ "#{#{} => a}" = p(#{#{} => a}, 2),
+ mt("#{a => 1,...}", p(#{a => 1, b => 2}, 2)),
+ mt("#{a => 1,b => 2}", p(#{a => 1, b => 2}, -1)),
+
+ M = #{kaaaaaaaaaaaaaaaaaaa => v1,kbbbbbbbbbbbbbbbbbbb => v2,
+ kccccccccccccccccccc => v3,kddddddddddddddddddd => v4,
+ keeeeeeeeeeeeeeeeeee => v5},
+ "#{...}" = p(M, 1),
+ mt("#{kaaaaaaaaaaaaaaaaaaaa => v1,...}", p(M, 2)),
+ mt("#{kaaaaaaaaaaaaaaaaaaaa => 1,kbbbbbbbbbbbbbbbbbbbb => 2,...}",
+ p(M, 3)),
+
+ mt("#{kaaaaaaaaaaaaaaaaaaa => v1,kbbbbbbbbbbbbbbbbbbb => v2,\n"
+ " kccccccccccccccccccc => v3,...}", p(M, 4)),
+
+ mt("#{kaaaaaaaaaaaaaaaaaaa => v1,kbbbbbbbbbbbbbbbbbbb => v2,\n"
+ " kccccccccccccccccccc => v3,kddddddddddddddddddd => v4,...}",
+ p(M, 5)),
+
+ mt("#{kaaaaaaaaaaaaaaaaaaa => v1,kbbbbbbbbbbbbbbbbbbb => v2,\n"
+ " kccccccccccccccccccc => v3,kddddddddddddddddddd => v4,\n"
+ " keeeeeeeeeeeeeeeeeee => v5}", p(M, 6)),
+
+ weak("#{aaaaaaaaaaaaaaaaaaa => 1,bbbbbbbbbbbbbbbbbbbb => 2,\n"
+ " cccccccccccccccccccc => {3},\n"
+ " dddddddddddddddddddd => 4,eeeeeeeeeeeeeeeeeeee => 5}",
+ p(#{aaaaaaaaaaaaaaaaaaa => 1,bbbbbbbbbbbbbbbbbbbb => 2,
+ cccccccccccccccccccc => {3},
+ dddddddddddddddddddd => 4,eeeeeeeeeeeeeeeeeeee => 5}, -1)),
+
+ M2 = #{dddddddddddddddddddd => {1}, {aaaaaaaaaaaaaaaaaaaa} => 2,
+ {bbbbbbbbbbbbbbbbbbbb} => 3,{cccccccccccccccccccc} => 4,
+ {eeeeeeeeeeeeeeeeeeee} => 5},
+ "#{...}" = p(M2, 1),
+ weak("#{dddddddddddddddddddd => {...},...}", p(M2, 2)),
+ weak("#{dddddddddddddddddddd => {1},{...} => 2,...}", p(M2, 3)),
+
+ weak("#{dddddddddddddddddddd => {1},\n"
+ " {aaaaaaaaaaaaaaaaaaaa} => 2,\n"
+ " {...} => 3,...}", p(M2, 4)),
+
+ weak("#{dddddddddddddddddddd => {1},\n"
+ " {aaaaaaaaaaaaaaaaaaaa} => 2,\n"
+ " {bbbbbbbbbbbbbbbbbbbb} => 3,\n"
+ " {...} => 4,...}", p(M2, 5)),
+
+ weak("#{dddddddddddddddddddd => {1},\n"
+ " {aaaaaaaaaaaaaaaaaaaa} => 2,\n"
+ " {bbbbbbbbbbbbbbbbbbbb} => 3,\n"
+ " {cccccccccccccccccccc} => 4,\n"
+ " {...} => 5}", p(M2, 6)),
+
+ weak("#{dddddddddddddddddddd => {1},\n"
+ " {aaaaaaaaaaaaaaaaaaaa} => 2,\n"
+ " {bbbbbbbbbbbbbbbbbbbb} => 3,\n"
+ " {cccccccccccccccccccc} => 4,\n"
+ " {eeeeeeeeeeeeeeeeeeee} => 5}", p(M2, 7)),
+
+ M3 = #{kaaaaaaaaaaaaaaaaaaa => vuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuu,
+ kbbbbbbbbbbbbbbbbbbb => vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv,
+ kccccccccccccccccccc => vxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx,
+ kddddddddddddddddddd => vyyyyyyyyyyyyyyyyyyyyyyyyyyyyyyyyyyyyyyy,
+ keeeeeeeeeeeeeeeeeee => vzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzz},
+
+ mt("#{aaaaaaaaaaaaaaaaaaaa =>\n"
+ " uuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuuu,\n"
+ " bbbbbbbbbbbbbbbbbbbb =>\n"
+ " vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv,\n"
+ " cccccccccccccccccccc =>\n"
+ " xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx,\n"
+ " dddddddddddddddddddd =>\n"
+ " yyyyyyyyyyyyyyyyyyyyyyyyyyyyyyyyyyyyyyyy,\n"
+ " eeeeeeeeeeeeeeeeeeee =>\n"
+ " zzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzzz}", p(M3, -1)),
+
+ R4 = {c,{c,{c,{c,{c,{c,{c,{c,{c,{c,{c,{c,a,b},b},b},b},b},b},
+ b},b},b},b},b},b},
+ M4 = #{aaaaaaaaaaaaaaaaaaaa => R4,
+ bbbbbbbbbbbbbbbbbbbb => R4,
+ cccccccccccccccccccc => R4,
+ dddddddddddddddddddd => R4,
+ eeeeeeeeeeeeeeeeeeee => R4},
+
+ weak("#{aaaaaaaaaaaaaaaaaaaa =>\n"
+ " #c{f1 = #c{f1 = #c{...},f2 = b},f2 = b},\n"
+ " bbbbbbbbbbbbbbbbbbbb => #c{f1 = #c{f1 = {...},...},f2 = b},\n"
+ " cccccccccccccccccccc => #c{f1 = #c{...},f2 = b},\n"
+ " dddddddddddddddddddd => #c{f1 = {...},...},\n"
+ " eeeeeeeeeeeeeeeeeeee => #c{...}}", p(M4, 7)),
+
+ M5 = #{aaaaaaaaaaaaaaaaaaaa => R4},
+ mt("#{aaaaaaaaaaaaaaaaaaaa =>\n"
+ " #c{\n"
+ " f1 =\n"
+ " #c{\n"
+ " f1 =\n"
+ " #c{\n"
+ " f1 =\n"
+ " #c{\n"
+ " f1 =\n"
+ " #c{\n"
+ " f1 =\n"
+ " #c{\n"
+ " f1 =\n"
+ " #c{\n"
+ " f1 =\n"
+ " #c{\n"
+ " f1 =\n"
+ " #c{\n"
+ " f1 = #c{f1 = #c{f1 = #c{f1 = a,f2 = b},f2 = b},"
+ "f2 = b},\n"
+ " f2 = b},\n"
+ " f2 = b},\n"
+ " f2 = b},\n"
+ " f2 = b},\n"
+ " f2 = b},\n"
+ " f2 = b},\n"
+ " f2 = b},\n"
+ " f2 = b},\n"
+ " f2 = b}}", p(M5, -1)),
+ ok.
+
+%% Just check number of newlines and dots ('...').
+-define(WEAK, true).
+
+-ifdef(WEAK).
+
+weak(S, R) ->
+ (nl(S) =:= nl(R) andalso
+ dots(S) =:= dots(S)).
+
+nl(S) ->
+ [C || C <- S, C =:= $\n].
+
+dots(S) ->
+ [C || C <- S, C =:= $\.].
+
+-else. % WEAK
+
+weak(S, R) ->
+ mt(S, R).
+
+-endif. % WEAK
+
+%% If EXACT is defined: mt() matches strings exactly.
+%%
+%% if EXACT is not defined: do not match the strings exactly, but
+%% compare them assuming that all map keys and all map values are
+%% equal (by assuming all map keys and all map values have the same
+%% length and begin with $k and $v respectively).
+
+%-define(EXACT, true).
+
+-ifdef(EXACT).
+
+mt(S, R) ->
+ S =:= R.
+
+-else. % EXACT
+
+mt(S, R) ->
+ anon(S) =:= anon(R).
+
+anon(S) ->
+ {ok, Ts0, _} = erl_scan:string(S, 1, [text]),
+ Ts = anon1(Ts0),
+ text(Ts).
+
+anon1([]) -> [];
+anon1([{atom,Anno,Atom}=T|Ts]) ->
+ case erl_anno:text(Anno) of
+ "k" ++ _ ->
+ NewAnno = erl_anno:set_text("key", Anno),
+ [{atom,NewAnno,Atom}|anon1(Ts)];
+ "v" ++ _ ->
+ NewAnno = erl_anno:set_text("val", Anno),
+ [{atom,NewAnno,Atom}|anon1(Ts)];
+ _ ->
+ [T|anon1(Ts)]
+ end;
+anon1([T|Ts]) ->
+ [T|anon1(Ts)].
+
+text(Ts) ->
+ lists:append(text1(Ts)).
+
+text1([]) -> [];
+text1([T|Ts]) ->
+ Anno = element(2, T),
+ [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),
+ T0 = [1|{a,b,c}],
+ {_, 2} = limt(T0, 2),
+ {_, 2} = limt(T0, 3),
+ {_, 2} = limt(T0, 4),
+ {_, 1} = limt(<<"foo">>, 18),
+ {_, 2} = limt({"",[1,2]}, 3),
+ {_, 2} = limt({"",{1,2}}, 3),
+ true = limt_pp({"123456789012345678901234567890",{1,2}}, 3),
+ ok = blimt(<<"123456789012345678901234567890">>),
+ true = limt_pp(<<"123456789012345678901234567890">>, 3),
+ {_, 2} = limt({<<"kljlkjsl">>,[1,2,3,4]}, 4),
+ {_, 1} = limt(<<7:3>>, 2),
+ {_, 1} = limt(<<7:21>>, 2),
+ {_, 1} = limt([], 2),
+ {_, 1} = limt({}, 2),
+ {_, 1} = limt({"", ""}, 4),
+ {_, 1} = limt(#{}, 2),
+ {_, 2} = limt(#{[] => {}}, 1),
+ {_, 2} = limt(#{[] => {}}, 2),
+ {_, 1} = limt(#{[] => {}}, 3),
+ T = #{[] => {},[a] => [b]},
+ {_, 1} = limt(T, 0),
+ {_, 2} = limt(T, 1),
+ {_, 2} = limt(T, 2),
+ {_, 2} = limt(T, 3),
+ {_, 1} = limt(T, 4),
+ T2 = #{[] => {},{} => []},
+ {_, 2} = limt(T2, 1),
+ {_, 2} = limt(T2, 2),
+ {_, 1} = limt(T2, 3),
+ 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])).
+
+limt_pp(Term, Depth) when is_integer(Depth) ->
+ T1 = io_lib:limit_term(Term, Depth),
+ S = pp(Term, Depth),
+ S1 = pp(T1, Depth),
+ S1 =:= S.
+
+pp(Term, Depth) ->
+ lists:flatten(io_lib:format("~P", [Term, Depth])).
+
+otp_14983(_Config) ->
+ trunc_depth(-1, fun trp/3),
+ trunc_depth(10, fun trp/3),
+ trunc_depth(-1, fun trw/3),
+ trunc_depth(10, fun trw/3),
+ trunc_depth_p(-1),
+ trunc_depth_p(10),
+ trunc_string(),
+ ok.
+
+trunc_string() ->
+ "str " = trf("str ", [], 10),
+ "str ..." = trf("str ~s", ["str"], 6),
+ "str str" = trf("str ~s", ["str"], 7),
+ "str ..." = trf("str ~8s", ["str"], 6),
+ Pa = filename:dirname(code:which(?MODULE)),
+ {ok, UNode} = test_server:start_node(printable_range_unicode, slave,
+ [{args, " +pc unicode -pa " ++ Pa}]),
+ U = "кирилли́ческий атом",
+ UFun = fun(Format, Args, CharsLimit) ->
+ rpc:call(UNode,
+ ?MODULE, trf, [Format, Args, CharsLimit])
+ end,
+ "str кир" = UFun("str ~3ts", [U], 7),
+ "str ..." = UFun("str ~3ts", [U], 6),
+ "str ..." = UFun("str ~30ts", [U], 6),
+ "str кир..." = UFun("str ~30ts", [U], 10),
+ "str кирилл..." = UFun("str ~30ts", [U], 13),
+ "str кирилли́..." = UFun("str ~30ts", [U], 14),
+ "str кирилли́ч..." = UFun("str ~30ts", [U], 15),
+ "\"кирилли́ческ\"..." = UFun("~tp", [U], 13),
+ BU = <<"кирилли́ческий атом"/utf8>>,
+ "<<\"кирилли́\"/utf8...>>" = UFun("~tp", [BU], 20),
+ "<<\"кирилли́\"/utf8...>>" = UFun("~tp", [BU], 21),
+ "<<\"кирилли́ческ\"/utf8...>>" = UFun("~tp", [BU], 22),
+ test_server:stop_node(UNode).
+
+trunc_depth(D, Fun) ->
+ "..." = Fun("", D, 0),
+ "[]" = Fun("", D, 1),
+
+ "#{}" = Fun(#{}, D, 1),
+ "#{a => 1}" = Fun(#{a => 1}, D, 7),
+ "#{...}" = Fun(#{a => 1}, D, 5),
+ "#{a => 1}" = Fun(#{a => 1}, D, 6),
+ A = lists:seq(1, 1000),
+ M = #{A => A, {A,A} => {A,A}},
+ "#{...}" = Fun(M, D, 6),
+ "#{{...} => {...},...}" = Fun(M, D, 7),
+ "#{{[...],...} => {[...],...},...}" = Fun(M, D, 22),
+ "#{{[...],...} => {[...],...},[...] => [...]}" = Fun(M, D, 31),
+ "#{{[...],...} => {[...],...},[...] => [...]}" = Fun(M, D, 33),
+ "#{{[1|...],[...]} => {[1|...],[...]},[1,2|...] => [...]}" =
+ Fun(M, D, 50),
+
+ "..." = Fun({c, 1, 2}, D, 0),
+ "{...}" = Fun({c, 1, 2}, D, 1),
+
+ "..." = Fun({}, D, 0),
+ "{}" = Fun({}, D, 1),
+ T = {A, A, A},
+ "{...}" = Fun(T, D, 5),
+ "{[...],...}" = Fun(T, D, 6),
+ "{[1|...],[...],...}" = Fun(T, D, 12),
+ "{[1,2|...],[1|...],...}" = Fun(T, D, 20),
+ "{[1,2|...],[1|...],[...]}" = Fun(T, D, 21),
+ "{[1,2,3|...],[1,2|...],[1|...]}" = Fun(T, D, 28),
+
+ "{[1],[1,2|...]}" = Fun({[1],[1,2,3,4]}, D, 14).
+
+trunc_depth_p(D) ->
+ UOpts = [{record_print_fun, fun rfd/2},
+ {encoding, unicode}],
+ LOpts = [{record_print_fun, fun rfd/2},
+ {encoding, latin1}],
+ trunc_depth_p(D, UOpts),
+ trunc_depth_p(D, LOpts).
+
+trunc_depth_p(D, Opts) ->
+ "[...]" = trp("abcdefg", D, 4, Opts),
+ "\"abc\"..." = trp("abcdefg", D, 5, Opts),
+ "\"abcdef\"..." = trp("abcdefg", D, 8, Opts),
+ "\"abcdefg\"" = trp("abcdefg", D, 9, Opts),
+ "\"abcdefghijkl\"" = trp("abcdefghijkl", D, -1, Opts),
+ AZ = lists:seq($A, $Z),
+ AZb = list_to_binary(AZ),
+ AZbS = "<<\"" ++ AZ ++ "\">>",
+ AZbS = trp(AZb, D, -1),
+ "<<\"ABCDEFGH\"...>>" = trp(AZb, D, 17, Opts), % 4 chars even if D = -1...
+ "<<\"ABCDEFGHIJKL\"...>>" = trp(AZb, D, 18, Opts),
+ B1 = <<"abcdef",0:8>>,
+ "<<\"ab\"...>>" = trp(B1, D, 8, Opts),
+ "<<\"abcdef\"...>>" = trp(B1, D, 14, Opts),
+ "<<97,98,99,100,...>>" = trp(B1, D, 16, Opts),
+ "<<97,98,99,100,101,102,0>>" = trp(B1, D, -1, Opts),
+ B2 = <<AZb/binary,0:8>>,
+ "<<\"AB\"...>>" = trp(B2, D, 8, Opts),
+ "<<\"ABCDEFGH\"...>>" = trp(B2, D, 14, Opts),
+ "<<65,66,67,68,69,70,71,72,0>>" = trp(<<"ABCDEFGH",0:8>>, D, -1, Opts),
+ "<<97,0,107,108,...>>" = trp(<<"a",0:8,"kllkjlksdjfsj">>, D, 20, Opts),
+
+ A = lists:seq(1, 1000),
+ "#c{...}" = trp({c, 1, 2}, D, 6),
+ "#c{...}" = trp({c, 1, 2}, D, 7),
+ "#c{f1 = [...],...}" = trp({c, A, A}, D, 18),
+ "#c{f1 = [1|...],f2 = [...]}" = trp({c, A, A}, D, 19),
+ "#c{f1 = [1,2|...],f2 = [1|...]}" = trp({c, A, A}, D, 31),
+ "#c{f1 = [1,2,3|...],f2 = [1,2|...]}" = trp({c, A, A}, D, 32).
+
+trp(Term, D, T) ->
+ trp(Term, D, T, [{record_print_fun, fun rfd/2}]).
+
+trp(Term, D, T, Opts) ->
+ R = io_lib_pretty:print(Term, [{depth, D},
+ {chars_limit, T}|Opts]),
+ lists:flatten(io_lib:format("~s", [R])).
+
+trw(Term, D, T) ->
+ lists:flatten(io_lib:format("~W", [Term, D], [{chars_limit, T}])).
+
+trf(Format, Args, T) ->
+ trf(Format, Args, T, [{record_print_fun, fun rfd/2}]).
+
+trf(Format, Args, T, Opts) ->
+ lists:flatten(io_lib:format(Format, Args, [{chars_limit, T}|Opts])).
+
+otp_15103(_Config) ->
+ T = lists:duplicate(5, {a,b,c}),
+
+ S1 = io_lib:format("~0p", [T]),
+ "[{a,b,c},{a,b,c},{a,b,c},{a,b,c},{a,b,c}]" = lists:flatten(S1),
+ S2 = io_lib:format("~-0p", [T]),
+ "[{a,b,c},{a,b,c},{a,b,c},{a,b,c},{a,b,c}]" = lists:flatten(S2),
+ S3 = io_lib:format("~1p", [T]),
+ "[{a,\n b,\n c},\n {a,\n b,\n c},\n {a,\n b,\n c},\n {a,\n b,\n"
+ " c},\n {a,\n b,\n c}]" = lists:flatten(S3),
+
+ S4 = io_lib:format("~0P", [T, 5]),
+ "[{a,b,c},{a,b,...},{a,...},{...}|...]" = lists:flatten(S4),
+ S5 = io_lib:format("~1P", [T, 5]),
+ "[{a,\n b,\n c},\n {a,\n b,...},\n {a,...},\n {...}|...]" =
+ lists:flatten(S5),
+ ok.
+
+otp_15159(_Config) ->
+ "[atom]" =
+ lists:flatten(io_lib:format("~p", [[atom]], [{chars_limit,5}])),
+ ok.
+
+otp_15076(_Config) ->
+ {'EXIT', {badarg, _}} = (catch io_lib:format("~c", [a])),
+ L = io_lib:scan_format("~c", [a]),
+ {"~c", [a]} = io_lib:unscan_format(L),
+ {'EXIT', {badarg, _}} = (catch io_lib:build_text(L)),
+ {'EXIT', {badarg, _}} = (catch io_lib:build_text(L, [])),
+ ok.