summaryrefslogtreecommitdiff
path: root/lib/stdlib/test/erl_pp_SUITE.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test/erl_pp_SUITE.erl')
-rw-r--r--lib/stdlib/test/erl_pp_SUITE.erl98
1 files changed, 83 insertions, 15 deletions
diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl
index ce0abd213e..c8c1a206ca 100644
--- a/lib/stdlib/test/erl_pp_SUITE.erl
+++ b/lib/stdlib/test/erl_pp_SUITE.erl
@@ -48,13 +48,15 @@
neg_indent/1,
maps_syntax/1,
format_options/1,
- quoted_atom_types/1,
+ form_vars/1,
+ quoted_atom_types/1,
otp_6321/1, otp_6911/1, otp_6914/1, otp_8150/1, otp_8238/1,
otp_8473/1, otp_8522/1, otp_8567/1, otp_8664/1, otp_9147/1,
otp_10302/1, otp_10820/1, otp_11100/1, otp_11861/1, pr_1014/1,
otp_13662/1, otp_14285/1, otp_15592/1, otp_15751/1, otp_15755/1,
- otp_16435/1]).
+ otp_16435/1, gh_5093/1,
+ eep49/1]).
%% Internal export.
-export([ehook/6]).
@@ -78,14 +80,15 @@ groups() ->
[func, call, recs, try_catch, if_then, receive_after,
bits, head_tail, cond1, block, case1, ops,
messages, maps_syntax, quoted_atom_types,
- format_options
+ format_options, form_vars
]},
{attributes, [], [misc_attrs, import_export, dialyzer_attrs]},
{tickets, [],
[otp_6321, otp_6911, otp_6914, otp_8150, otp_8238,
otp_8473, otp_8522, otp_8567, otp_8664, otp_9147,
otp_10302, otp_10820, otp_11100, otp_11861, pr_1014, otp_13662,
- otp_14285, otp_15592, otp_15751, otp_15755, otp_16435]}].
+ otp_14285, otp_15592, otp_15751, otp_15755, otp_16435,
+ gh_5093, eep49]}].
init_per_suite(Config) ->
Config.
@@ -577,6 +580,37 @@ format_options(Config) when is_list(Config) ->
)
).
+form_vars(Config) when is_list(Config) ->
+ %% Check that erl_pp:legalize_vars/1 does its job. If
+ %% legalize_vars/1 fails to convert variable names starting with a
+ %% lower case letter, the compiler will detect that `X` is an atom
+ %% and report that the `+` operation will fail. If legalize_vars/1
+ %% fails to generate unique variable names and just converts the
+ %% name to uppercase, the variable named `REC0` will be used in an
+ %% unsafe way.
+ String = <<"-module(erl_pp_test).
+ -export([f/1]).
+ -record(r, {a, b}).
+ f(#r{b = B} = C) ->
+ receive
+ B ->
+ X = C#r.a,
+ REC0 = X + X,
+ REC0
+ end.">>,
+ FileName = filename('erl_pp_test.erl', Config),
+ ok = file:write_file(FileName, String),
+ Opts = [binary,deterministic,nowarn_unused_record],
+ {ok, [], Forms} = compile:file(FileName, ['E'|Opts]),
+ Forms1 = lists:map(fun(F={function,_,_,_,_}) ->
+ erl_pp:legalize_vars(F);
+ (F) ->
+ F
+ end, Forms),
+ ok = file:write_file(FileName, [erl_pp:form(F) || F <- Forms1]),
+ {ok, _, _, []} = compile:file(FileName, [return|Opts]),
+ ok.
+
misc_attrs(Config) when is_list(Config) ->
ok = pp_forms(<<"-module(m). ">>),
ok = pp_forms(<<"-module(m, [Aafjlksfjdlsjflsdfjlsdjflkdsfjlk,"
@@ -1085,14 +1119,14 @@ unicode_hook({foo,E}, I, P, H) ->
%% OTP-10820. Unicode filenames.
otp_10820(Config) when is_list(Config) ->
C1 = <<"%% coding: utf-8\n -module(any).">>,
- ok = do_otp_10820(Config, C1, "+pc latin1"),
- ok = do_otp_10820(Config, C1, "+pc unicode"),
+ ok = do_otp_10820(Config, C1, ["+pc", "latin1"]),
+ ok = do_otp_10820(Config, C1, ["+pc", "unicode"]),
C2 = <<"%% coding: latin-1\n -module(any).">>,
- ok = do_otp_10820(Config, C2, "+pc latin1"),
- ok = do_otp_10820(Config, C2, "+pc unicode").
+ ok = do_otp_10820(Config, C2, ["+pc", "latin1"]),
+ ok = do_otp_10820(Config, C2, ["+pc", "unicode"]).
do_otp_10820(Config, C, PC) ->
- {ok,Node} = start_node(erl_pp_helper, "+fnu " ++ PC),
+ {ok,Peer,Node} = ?CT_PEER(["+fnu"] ++ PC),
L = [915,953,959,973,957,953,954,959,957,964],
FileName = filename(L++".erl", Config),
ok = rpc:call(Node, file, write_file, [FileName, C]),
@@ -1100,7 +1134,7 @@ do_otp_10820(Config, C, PC) ->
[FileName, [return,'P',{outdir,?privdir}]]),
PFileName = filename(L++".P", Config),
{ok, Bin} = rpc:call(Node, file, read_file, [PFileName]),
- true = test_server:stop_node(Node),
+ peer:stop(Peer),
true = file_attr_is_string(binary_to_list(Bin)),
ok.
@@ -1335,6 +1369,30 @@ otp_16435(_Config) ->
ok.
+gh_5093(_Config) ->
+ assert_same("f() ->\n -1.\n"),
+ assert_same("f() ->\n +1.\n"),
+ assert_same("f() ->\n +1.1.\n"),
+ assert_same("f() ->\n +(+1).\n"),
+ assert_same("f(X) ->\n -X.\n"),
+ assert_same("f(X) ->\n +X.\n"),
+ assert_same("f(X, Y) ->\n X + Y.\n"),
+ assert_same("f(X, Y) ->\n X + +Y.\n"),
+ assert_same("f(X, Y) ->\n X - Y.\n"),
+ ok.
+
+eep49(_Config) ->
+ assert_same("f() ->\n"
+ " maybe ok ?= ok end.\n"),
+ assert_same("f() ->\n"
+ " maybe\n"
+ " ok ?= ok\n"
+ " else\n"
+ " {error, _} ->\n"
+ " error\n"
+ " end.\n"),
+ ok.
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
compile(Config, Tests) ->
@@ -1430,7 +1488,15 @@ parse_forms(Chars) ->
parse_forms2([], _Cont, _Line, Forms) ->
lists:reverse(Forms);
parse_forms2(String, Cont0, Line, Forms) ->
- case erl_scan:tokens(Cont0, String, Line) of
+ %% FIXME: When the experimental features EEP has been implemented, we should
+ %% dig out all keywords defined in all features.
+ ResWordFun =
+ fun('maybe') -> true;
+ ('else') -> true;
+ (Other) -> erl_scan:reserved_word(Other)
+ end,
+ Options = [{reserved_word_fun,ResWordFun}],
+ case erl_scan:tokens(Cont0, String, Line, Options) of
{done, {ok, Tokens, EndLine}, Chars} ->
{ok, Form} = erl_parse:parse_form(Tokens),
parse_forms2(Chars, [], EndLine, [Form | Forms]);
@@ -1514,7 +1580,9 @@ filename(Name, Config) ->
fail() ->
ct:fail(failed).
-%% +fnu means a peer node has to be started; slave will not do
-start_node(Name, Xargs) ->
- PA = filename:dirname(code:which(?MODULE)),
- test_server:start_node(Name, peer, [{args, "-pa " ++ PA ++ " " ++ Xargs}]).
+assert_same(Expected) when is_list(Expected) ->
+ Actual = binary_to_list(iolist_to_binary(parse_and_pp_forms(Expected, []))),
+ case Expected == Actual of
+ true -> ok;
+ false -> error({Expected, Actual})
+ end.