diff options
Diffstat (limited to 'lib/stdlib/test/erl_pp_SUITE.erl')
-rw-r--r-- | lib/stdlib/test/erl_pp_SUITE.erl | 110 |
1 files changed, 101 insertions, 9 deletions
diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl index f5d80e7e68..c0cfd26925 100644 --- a/lib/stdlib/test/erl_pp_SUITE.erl +++ b/lib/stdlib/test/erl_pp_SUITE.erl @@ -47,11 +47,12 @@ hook/1, neg_indent/1, maps_syntax/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_13662/1, otp_14285/1, otp_15592/1, otp_15751/1, otp_15755/1]). %% Internal export. -export([ehook/6]). @@ -74,14 +75,14 @@ groups() -> [{expr, [], [func, call, recs, try_catch, if_then, receive_after, bits, head_tail, cond1, block, case1, ops, - messages, maps_syntax + messages, maps_syntax, quoted_atom_types ]}, {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_14285, otp_15592, otp_15751, otp_15755]}]. init_per_suite(Config) -> Config. @@ -473,10 +474,10 @@ cond1(Config) when is_list(Config) -> [{tuple,5,[{atom,5,x},{atom,5,y}]}]}]}, CChars = flat_expr1(C), "cond\n" - " {foo,bar} ->\n" - " [a,b];\n" + " {foo, bar} ->\n" + " [a, b];\n" " true ->\n" - " {x,y}\n" + " {x, y}\n" "end" = CChars, ok. @@ -711,7 +712,7 @@ otp_6321(Config) when is_list(Config) -> Str = "S = hopp, {hej, S}. ", {done, {ok, Tokens, _EndLine}, ""} = erl_scan:tokens("", Str, _L=1), {ok, Exprs} = erl_parse:parse_exprs(Tokens), - "S = hopp, {hej,S}" = lists:flatten(erl_pp:exprs(Exprs)), + "S = hopp, {hej, S}" = lists:flatten(erl_pp:exprs(Exprs)), ok. %% OTP_6911. More newlines. @@ -828,7 +829,7 @@ type_examples() -> "(t24()) -> D when is_subtype(D, atom())," " is_subtype(D, t14())," " is_subtype(D, '\\'t::4'()).">>}, - {ex32,<<"-spec mod:t2() -> any(). ">>}, + {ex32,<<"-spec erl_pp_test:t2() -> any(). ">>}, {ex33,<<"-opaque attributes_data() :: " "[{'column', column()} | {'line', info_line()} |" " {'text', string()}] | {line(),column()}. ">>}, @@ -912,6 +913,21 @@ maps_syntax(Config) when is_list(Config) -> ok = pp_forms(F), ok. +quoted_atom_types(Config) when is_list(Config) -> + Q = [{quote_singleton_atom_types, true}], + U = [{encoding,unicode}], + L = [{encoding,latin1}], + F = "-type t() :: a | a().", + "-type t() :: 'a' | a().\n" = + lists:flatten(parse_and_pp_forms(F, Q ++ L)), + "-type t() :: 'a' | a().\n" = + lists:flatten(parse_and_pp_forms(F, Q ++ U)), + UF = "-type t() :: '\x{400}' | '\x{400}'().", + "-type t() :: '\\x{400}' | '\\x{400}'().\n" = + lists:flatten(parse_and_pp_forms(UF, Q ++ L)), + "-type t() :: '\x{400}' | '\x{400}'().\n" = + lists:flatten(parse_and_pp_forms(UF, Q ++ U)), + ok. %% OTP_8567. Avoid duplicated 'undefined' in record field types. otp_8567(Config) when is_list(Config) -> @@ -1096,7 +1112,7 @@ otp_11861(Config) when is_list(Config) -> A3 = erl_anno:new(3), "-optional_callbacks([bar/0]).\n" = pf({attribute,A3,optional_callbacks,[{bar,0}]}), - "-optional_callbacks([{bar,1,bad}]).\n" = + "-optional_callbacks([{bar, 1, bad}]).\n" = pf({attribute,A3,optional_callbacks,[{bar,1,bad}]}), ok. @@ -1172,6 +1188,79 @@ otp_15592(_Config) -> "56789012345678901234:f(<<>>)">>), ok. +otp_15751(_Config) -> + ok = pp_expr(<<"try foo:bar() + catch + Reason : Stacktrace -> + {Reason, Stacktrace} + end">>), + ok = pp_expr(<<"try foo:bar() + catch + throw: Reason : Stacktrace -> + {Reason, Stacktrace} + end">>), + ok = pp_expr(<<"try foo:bar() + catch + Reason : _ -> + Reason + end">>), + ok = pp_expr(<<"try foo:bar() + catch + throw: Reason : _ -> + Reason + end">>), + ok = pp_expr(<<"try foo:bar() + catch + Reason -> + Reason + end">>), + ok = pp_expr(<<"try foo:bar() + catch + throw: Reason -> + Reason + end">>), + ok. + +otp_15755(_Config) -> + "[{a, b}, c, {d, e} | t]" = + flat_parse_and_pp_expr("[{a, b}, c, {d, e} | t]", 0, []), + "[{a, b},\n c, d,\n {d, e},\n 1, 2.0,\n {d, e},\n <<>>, {},\n {d, e},\n" + " [], [],\n {d, e} |\n t]" = + flat_parse_and_pp_expr("[{a,b},c,d,{d,e},1,2.0,{d,e},<<>>," + "{},{d,e},[],[],{d,e}|t]", 0, []), + "[{a, b},\n c, d,\n {d, e},\n 1, 2.0,\n {d, e},\n <<>>, {},\n {d, e},\n" + " [], [], d, e | t]" = + flat_parse_and_pp_expr("[{a,b},c,d,{d,e},1,2.0,{d,e},<<>>," + "{},{d,e},[],[],d,e|t]", 0, []), + + "-type t() :: + a | b | c | a | b | a | b | a | b | a | b | a | b | a | b | + a | b | a | b | a | b.\n" = + lists:flatten(parse_and_pp_forms( + "-type t() :: a | b | c| a | b | a | b | a | b | a |" + " b | a | b | a | b | a | b | a | b |a | b.", [])), + + "-type t() :: + {dict, 0, 16, 16, 8, 80, 48, + {[], [], [], [], [], [], [], [], [], [], [], [], [], [], [], + []}, + {{[], [], [], [], [], [], [], [], [], [], [], [], [], [], []}}}.\n" = + lists:flatten(parse_and_pp_forms( + "-type t() :: {dict,0,16,16,8,80,48," + "{[],[],[],[],[],[],[],[],[],[],[],[],[],[],[],[]}," + "{{[],[],[],[],[],[],[],[],[],[],[],[],[],[],[]}}}.", [])), + + "-type t() :: + {{a}, + 0, 16, + {16}, + 8, 80, 48, a, b, e, f, 'sf s sdf', [], {}, + {[]}}.\n" = + lists:flatten(parse_and_pp_forms( + "-type t() :: {{a}, 0, 16, {16}, 8, 80, 48, a, b, e, f," + " 'sf s sdf', [], {}, {[]}}.", [])), + ok. + %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% compile(Config, Tests) -> @@ -1303,6 +1392,9 @@ pp_expr(List, Options) when is_list(List) -> not_ok end. +flat_parse_and_pp_expr(String, Indent, Options) -> + lists:flatten(parse_and_pp_expr(String, Indent, Options)). + parse_and_pp_expr(String, Indent, Options) -> StringDot = lists:flatten(String) ++ ".", erl_pp:expr(parse_expr(StringDot), Indent, Options). |