diff options
author | Sverker Eriksson <[email protected]> | 2017-08-30 20:55:08 +0200 |
---|---|---|
committer | Sverker Eriksson <[email protected]> | 2017-08-30 20:55:08 +0200 |
commit | 7c67bbddb53c364086f66260701bc54a61c9659c (patch) | |
tree | 92ab0d4b91d5e2f6e7a3f9d61ea25089e8a71fe0 /lib/stdlib/test/erl_pp_SUITE.erl | |
parent | 97dc5e7f396129222419811c173edc7fa767b0f8 (diff) | |
parent | 3b7a6ffddc819bf305353a593904cea9e932e7dc (diff) | |
download | otp-7c67bbddb53c364086f66260701bc54a61c9659c.tar.gz otp-7c67bbddb53c364086f66260701bc54a61c9659c.tar.bz2 otp-7c67bbddb53c364086f66260701bc54a61c9659c.zip |
Merge tag 'OTP-19.0' into sverker/19/binary_to_atom-utf8-crash/ERL-474/OTP-14590
Diffstat (limited to 'lib/stdlib/test/erl_pp_SUITE.erl')
-rw-r--r-- | lib/stdlib/test/erl_pp_SUITE.erl | 641 |
1 files changed, 321 insertions, 320 deletions
diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl index 2b7cec87df..a103f6dc53 100644 --- a/lib/stdlib/test/erl_pp_SUITE.erl +++ b/lib/stdlib/test/erl_pp_SUITE.erl @@ -1,18 +1,19 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2006-2013. All Rights Reserved. +%% Copyright Ericsson AB 2006-2016. All Rights Reserved. %% -%% The contents of this file are subject to the Erlang Public License, -%% Version 1.1, (the "License"); you may not use this file except in -%% compliance with the License. You should have received a copy of the -%% Erlang Public License along with this software. If not, it can be -%% retrieved online at http://www.erlang.org/. +%% Licensed under the Apache License, Version 2.0 (the "License"); +%% you may not use this file except in compliance with the License. +%% You may obtain a copy of the License at %% -%% Software distributed under the License is distributed on an "AS IS" -%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See -%% the License for the specific language governing rights and limitations -%% under the License. +%% http://www.apache.org/licenses/LICENSE-2.0 +%% +%% Unless required by applicable law or agreed to in writing, software +%% distributed under the License is distributed on an "AS IS" BASIS, +%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. +%% See the License for the specific language governing permissions and +%% limitations under the License. %% %% %CopyrightEnd% %% @@ -21,7 +22,7 @@ %%%----------------------------------------------------------------- -module(erl_pp_SUITE). -%-define(debug, true). +%%-define(debug, true). -ifdef(debug). -define(line, put(line, ?LINE), ). @@ -30,9 +31,9 @@ -define(privdir, "erl_pp_SUITE_priv"). -define(t, test_server). -else. --include_lib("test_server/include/test_server.hrl"). --define(datadir, ?config(data_dir, Config)). --define(privdir, ?config(priv_dir, Config)). +-include_lib("common_test/include/ct.hrl"). +-define(datadir, proplists:get_value(data_dir, Config)). +-define(privdir, proplists:get_value(priv_dir, Config)). -endif. -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, @@ -42,31 +43,28 @@ -export([ func/1, call/1, recs/1, try_catch/1, if_then/1, receive_after/1, bits/1, head_tail/1, cond1/1, block/1, case1/1, ops/1, messages/1, - old_mnemosyne_syntax/1, import_export/1, misc_attrs/1, dialyzer_attrs/1, hook/1, neg_indent/1, + maps_syntax/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_10302/1, otp_10820/1, otp_11100/1, otp_11861/1, pr_1014/1, + otp_13662/1]). %% Internal export. -export([ehook/6]). -% Default timetrap timeout (set in init_per_testcase). --define(default_timeout, ?t:minutes(2)). - init_per_testcase(_Case, Config) -> - ?line Dog = ?t:timetrap(?default_timeout), - [{watchdog, Dog} | Config]. + 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,2}}]. all() -> [{group, expr}, {group, attributes}, hook, neg_indent, @@ -76,12 +74,13 @@ groups() -> [{expr, [], [func, call, recs, try_catch, if_then, receive_after, bits, head_tail, cond1, block, case1, ops, - messages, old_mnemosyne_syntax]}, + messages, maps_syntax + ]}, {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_10302, otp_10820, otp_11100, otp_11861, pr_1014, otp_13662]}]. init_per_suite(Config) -> Config. @@ -97,8 +96,6 @@ end_per_group(_GroupName, Config) -> -func(suite) -> - []; func(Config) when is_list(Config) -> Ts = [{func_1, <<"-record(r1, {a,b}). @@ -130,13 +127,31 @@ func(Config) when is_list(Config) -> true end)().">>}, {func_7, - <<"t(M, F, A) -> fun M:F/A.">>} + <<"t(M, F, A) -> fun M:F/A.">>}, + {func_8, + <<"-record(r1, {a,b}). + -record(r3, {a = fun Id(_) -> #r1{} end(1), b}). + + t() -> + fun Id(A) when record(A#r3.a, r1) -> 7 end(#r3{}). + ">>}, + {func_9, + <<"-record(r1, {a,b}). + -record(r3, {a = fun Id(_) -> #r1{} end(1), b}). + + t() -> + fsdfsdfjsdfjkljf:sdlfjdsfjlf( + fun Id(sdfsd) -> {sdkjsdf,sdfjsdkljfsdl,sdfkjdklf} end). + ">>}, + {func_10, + <<"t() -> + (fun True() -> + true + end)().">>} ], - ?line compile(Config, Ts), + compile(Config, Ts), ok. -call(suite) -> - []; call(Config) when is_list(Config) -> Ts = [{call_1, <<"t() -> @@ -145,11 +160,9 @@ call(Config) when is_list(Config) -> sfds,sdfsdf,sfds). ">>} ], - ?line compile(Config, Ts), + compile(Config, Ts), ok. -recs(suite) -> - []; recs(Config) when is_list(Config) -> %% Evolved while testing strict record tests in guards... Ts = [{recs_1, @@ -158,6 +171,7 @@ recs(Config) when is_list(Config) -> -record(r1, {a,b}). -record(r2, {a = #r1{},b,c=length([1,2,3])}). -record(r3, {a = fun(_) -> #r1{} end(1), b}). + -record(r4, {a = fun R1(_) -> #r1{} end(1), b}). t() -> foo = fun(A) when A#r1.a > A#r1.b -> foo end(#r1{b = 2}), @@ -305,18 +319,16 @@ recs(Config) when is_list(Config) -> R = #r2{}, R#r2{c = R, d = #r1{}}.">>} ], - ?line compile(Config, Ts), + compile(Config, Ts), - ?line ok = pp_expr(<<"case #r{a={1,2},b=#r{}} of + ok = pp_expr(<<"case #r{a={1,2},b=#r{}} of X=Y=#r{a=foo,b=bar} -> {(foooo:baaaar(X))#r{a = rep},Y,#r.b} end">>), - ?line ok = pp_expr(<<"R#r{a = {kljasdklf,sdkfjsdl,sdafjkllsdf,sdfkjsd, + ok = pp_expr(<<"R#r{a = {kljasdklf,sdkfjsdl,sdafjkllsdf,sdfkjsd, sdafjsd,sdf,sdafsd,sdfdsf,sdfdsf,dsfds}}">>), ok. -try_catch(suite) -> - []; try_catch(Config) when is_list(Config) -> Ts = [{try_1, % copied from erl_eval_SUITE <<"t() -> try 1 of 1 -> 2 catch _:_ -> 3 end.">>}, @@ -358,8 +370,8 @@ try_catch(Config) when is_list(Config) -> <<"t() -> catch begin begin foo, bar, foo:bar(kljsldkfjdls,kljsdl), (catch bar:foo(foo)) end end.">>} ], - ?line compile(Config, Ts), - ?line ok = pp_expr(<<"try + compile(Config, Ts), + ok = pp_expr(<<"try erl_internal:bif(M,F,length(Args)) of true -> @@ -369,8 +381,6 @@ try_catch(Config) when is_list(Config) -> after foo end">>), ok. -if_then(suite) -> - []; if_then(Config) when is_list(Config) -> Ts = [{if_1, <<"t() -> if 1 > 2 -> 1; true -> b end.">>}, @@ -379,11 +389,9 @@ if_then(Config) when is_list(Config) -> {if_3, <<"t() -> if 1 == 2 -> a; 1 > 2 -> b; 1 < 2 -> c end.">>} ], - ?line compile(Config, Ts), + compile(Config, Ts), ok. -receive_after(suite) -> - []; receive_after(Config) when is_list(Config) -> Ts = [{rec_1, <<"t() -> receive foo -> bar; bar -> foo end.">>}, @@ -404,11 +412,9 @@ receive_after(Config) when is_list(Config) -> {3,4} end.">>} ], - ?line compile(Config, Ts), + compile(Config, Ts), ok. -bits(suite) -> - []; bits(Config) when is_list(Config) -> Ts = [{bit_1, % copied from shell_SUITE <<"t() -> <<(<<\"abc\">>):3/binary>>.">>}, @@ -429,21 +435,19 @@ bits(Config) when is_list(Config) -> {bit_9, <<"">>} ], - ?line compile(Config, Ts), - ?line ok = pp_expr(<<"<<(list_to_binary([1,2]))/binary>>">>), - ?line ok = pp_expr( + compile(Config, Ts), + ok = pp_expr(<<"<<(list_to_binary([1,2]))/binary>>">>), + ok = pp_expr( <<"<<(list_to_binary([1,2])):all/binary-unit:8-unsigned-big>>">>), - ?line ok = pp_expr(<<"<<<<\"hej\">>/binary>>">>), - ?line ok = pp_expr(<<"<<(foo:bar())/binary>>">>), - ?line ok = pp_expr(<<"<<(a)/binary>>">>), - ?line ok = pp_expr(<<"<<a/binary>>">>), - ?line ok = pp_expr(<<"<<{a,b}/binary>>">>), - ?line ok = pp_expr(<<"<<{foo:bar(),b}/binary>>">>), - ?line ok = pp_expr(<<"<<(foo:bar()):(foo:bar())/binary>>">>), + ok = pp_expr(<<"<<<<\"hej\">>/binary>>">>), + ok = pp_expr(<<"<<(foo:bar())/binary>>">>), + ok = pp_expr(<<"<<(a)/binary>>">>), + ok = pp_expr(<<"<<a/binary>>">>), + ok = pp_expr(<<"<<{a,b}/binary>>">>), + ok = pp_expr(<<"<<{foo:bar(),b}/binary>>">>), + ok = pp_expr(<<"<<(foo:bar()):(foo:bar())/binary>>">>), ok. -head_tail(suite) -> - []; head_tail(Config) when is_list(Config) -> Ts = [{list_1, <<"t() -> [a | b].">>}, @@ -458,43 +462,30 @@ head_tail(Config) when is_list(Config) -> [foo:bar(lkjljlskdfj, klsdajflds, sdafkljsdlfkjdas, kjlsdadjl), bar:foo(kljlkjsdf, lkjsdlfj, [kljsfj, sdfdsfsad])].">>} ], - ?line compile(Config, Ts), + compile(Config, Ts), ok. -cond1(suite) -> - []; cond1(Config) when is_list(Config) -> C = {'cond',1,[{clause,2,[],[[{tuple,2,[{atom,2,foo},{atom,2,bar}]}]], [{cons,3,{atom,3,a},{cons,3,{atom,3,b},{nil,3}}}]}, {clause,4,[],[[{atom,4,true}]], [{tuple,5,[{atom,5,x},{atom,5,y}]}]}]}, - ?line CChars = lists:flatten(erl_pp:expr(C)), -% ?line "cond {foo,bar} -> [a,b]; true -> {x,y} end" = CChars, - ?line "cond\n" + CChars = flat_expr1(C), + "cond\n" " {foo,bar} ->\n" " [a,b];\n" " true ->\n" " {x,y}\n" "end" = CChars, -% ?line ok = pp_expr(<<"cond -% {foo,bar} -> -% [a,b]; -% true -> -% {x,y} -% end">>), ok. -block(suite) -> - []; block(Config) when is_list(Config) -> Ts = [{block_1, <<"t() -> begin a,{c,d} end.">>} ], - ?line compile(Config, Ts), + compile(Config, Ts), ok. -case1(suite) -> - []; case1(Config) when is_list(Config) -> Ts = [{case_1, <<"t() -> case {foo,bar} of @@ -504,8 +495,8 @@ case1(Config) when is_list(Config) -> foo end.">>} ], - ?line compile(Config, Ts), - ?line ok = pp_expr(<<"case + compile(Config, Ts), + ok = pp_expr(<<"case erl_internal:bif(M,F,length(Args)) of true -> @@ -515,8 +506,6 @@ case1(Config) when is_list(Config) -> end">>), ok. -ops(suite) -> - []; ops(Config) when is_list(Config) -> Ts = [{ops_1, <<"t() -> {a,b} + (3 - 2) + 4.">>}, @@ -525,42 +514,17 @@ ops(Config) when is_list(Config) -> {ops_3, <<"t() -> - (- (- (- (- 3)))).">>} ], - ?line compile(Config, Ts), + compile(Config, Ts), ok. -messages(suite) -> - []; messages(Config) when is_list(Config) -> - ?line true = "{error,{some,\"error\"}}\n" =:= + true = "{error,{some,\"error\"}}\n" =:= lists:flatten(erl_pp:form({error,{some,"error"}})), - ?line true = "{warning,{some,\"warning\"}}\n" =:= + true = "{warning,{some,\"warning\"}}\n" =:= lists:flatten(erl_pp:form({warning,{some,"warning"}})), - ?line true = "\n" =:= lists:flatten(erl_pp:form({eof,0})), - ok. - -old_mnemosyne_syntax(Config) when is_list(Config) -> - %% Since we have kept the ':-' token, - %% better test that we can pretty print it. - R = {rule,12,sales,2, - [{clause,12, - [{var,12,'E'},{atom,12,employee}], - [], - [{generate,13, - {var,13,'E'}, - {call,13,{atom,13,table},[{atom,13,employee}]}}, - {match,14, - {record_field,14,{var,14,'E'},{atom,14,salary}}, - {atom,14,sales}}]}]}, - ?line "sales(E, employee) :-\n" - " E <- table(employee),\n" - " E.salary = sales.\n" = - lists:flatten(erl_pp:form(R)), + "\n" = flat_form({eof,0}), ok. - - -import_export(suite) -> - []; import_export(Config) when is_list(Config) -> Ts = [{import_1, <<"-import(lists, [max/1, reverse/1]). @@ -575,30 +539,26 @@ import_export(Config) when is_list(Config) -> <<"-include_lib(\"stdlib/include/qlc.hrl\"). t() -> qlc:q([X || X <- []]).">>} ], - ?line compile(Config, Ts), + compile(Config, Ts), ok. -misc_attrs(suite) -> - []; misc_attrs(Config) when is_list(Config) -> - ?line ok = pp_forms(<<"-module(m). ">>), - ?line ok = pp_forms(<<"-module(m, [Aafjlksfjdlsjflsdfjlsdjflkdsfjlk," - "Blsjfdlslfjsdf]). ">>), - ?line ok = pp_forms(<<"-export([]). ">>), - ?line ok = pp_forms(<<"-export([foo/2, bar/0]). ">>), - ?line ok = pp_forms(<<"-export([bar/0]). ">>), - ?line ok = pp_forms(<<"-import(lists, []). ">>), - ?line ok = pp_forms(<<"-import(lists, [map/2]). ">>), - ?line ok = pp_forms(<<"-import(lists, [map/2, foreach/2]). ">>), - ?line ok = pp_forms(<<"-'wild '({attr2,3}). ">>), - ?line ok = pp_forms(<<"-record(a, {b,c}). ">>), - ?line ok = pp_forms(<<"-record(' a ', {}). ">>), - ?line ok = pp_forms(<<"-record(' a ', {foo = foo:bar()}). ">>), - + ok = pp_forms(<<"-module(m). ">>), + ok = pp_forms(<<"-module(m, [Aafjlksfjdlsjflsdfjlsdjflkdsfjlk," + "Blsjfdlslfjsdf]). ">>), + ok = pp_forms(<<"-export([]). ">>), + ok = pp_forms(<<"-export([foo/2, bar/0]). ">>), + ok = pp_forms(<<"-export([bar/0]). ">>), + ok = pp_forms(<<"-import(lists, []). ">>), + ok = pp_forms(<<"-import(lists, [map/2]). ">>), + ok = pp_forms(<<"-import(lists, [map/2, foreach/2]). ">>), + ok = pp_forms(<<"-'wild '({attr2,3}). ">>), + ok = pp_forms(<<"-record(a, {b,c}). ">>), + ok = pp_forms(<<"-record(' a ', {}). ">>), + ok = pp_forms(<<"-record(' a ', {foo = foo:bar()}). ">>), + ok = pp_forms(<<"-custom1(#{test1 => init/2, test2 => [val/1, val/2]}). ">>), ok. -dialyzer_attrs(suite) -> - []; dialyzer_attrs(Config) when is_list(Config) -> ok = pp_forms(<<"-type foo() :: #bar{}. ">>), ok = pp_forms(<<"-opaque foo() :: {bar, fun((X, [42,...]) -> X)}. ">>), @@ -606,8 +566,6 @@ dialyzer_attrs(Config) when is_list(Config) -> ok = pp_forms(<<"-callback foo(<<_:32,_:_*4>>, T) -> T. ">>), ok. -hook(suite) -> - []; hook(Config) when is_list(Config) -> F = fun(H) -> H end, do_hook(F). @@ -615,89 +573,71 @@ hook(Config) when is_list(Config) -> do_hook(HookFun) -> Lc = parse_expr(binary_to_list(<<"[X || X <- [1,2,3]].">>)), H = HookFun(fun hook/4), - Expr = {call,0,{atom,0,fff},[{foo,Lc},{foo,Lc},{foo,Lc}]}, + A0 = erl_anno:new(0), + Expr = {call,A0,{atom,A0,fff},[{foo,Lc},{foo,Lc},{foo,Lc}]}, EChars = lists:flatten(erl_pp:expr(Expr, 0, H)), - Call = {call,0,{atom,0,foo},[Lc]}, - Expr2 = {call,0,{atom,0,fff},[Call,Call,Call]}, + Call = {call,A0,{atom,A0,foo},[Lc]}, + Expr2 = {call,A0,{atom,A0,fff},[Call,Call,Call]}, EChars2 = erl_pp:exprs([Expr2]), - ?line true = EChars =:= lists:flatten(EChars2), + true = EChars =:= lists:flatten(EChars2), EsChars = erl_pp:exprs([Expr], H), - ?line true = EChars =:= lists:flatten(EsChars), + true = EChars =:= lists:flatten(EsChars), - F = {function,1,ffff,0,[{clause,1,[],[],[Expr]}]}, + A1 = erl_anno:new(1), + F = {function,A1,ffff,0,[{clause,A1,[],[],[Expr]}]}, FuncChars = lists:flatten(erl_pp:function(F, H)), - F2 = {function,1,ffff,0,[{clause,1,[],[],[Expr2]}]}, + F2 = {function,A1,ffff,0,[{clause,A1,[],[],[Expr2]}]}, FuncChars2 = erl_pp:function(F2), - ?line true = FuncChars =:= lists:flatten(FuncChars2), + true = FuncChars =:= lists:flatten(FuncChars2), FFormChars = erl_pp:form(F, H), - ?line true = FuncChars =:= lists:flatten(FFormChars), + true = FuncChars =:= lists:flatten(FFormChars), - A = {attribute,1,record,{r,[{record_field,1,{atom,1,a},Expr}]}}, + A = {attribute,A1,record,{r,[{record_field,A1,{atom,A1,a},Expr}]}}, AChars = lists:flatten(erl_pp:attribute(A, H)), - A2 = {attribute,1,record,{r,[{record_field,1,{atom,1,a},Expr2}]}}, + A2 = {attribute,A1,record,{r,[{record_field,A1,{atom,A1,a},Expr2}]}}, AChars2 = erl_pp:attribute(A2), - ?line true = AChars =:= lists:flatten(AChars2), + true = AChars =:= lists:flatten(AChars2), AFormChars = erl_pp:form(A, H), - ?line true = AChars =:= lists:flatten(AFormChars), - - R = {rule,0,sales,0, - [{clause,0,[{var,0,'E'},{atom,0,employee}],[], - [{generate,2,{var,2,'E'}, - {call,2,{atom,2,table},[{atom,2,employee}]}}, - {match,3, - {record_field,3,{var,3,'E'},{atom,3,salary}}, - {foo,Expr}}]}]}, - RChars = lists:flatten(erl_pp:rule(R, H)), - R2 = {rule,0,sales,0, - [{clause,0,[{var,0,'E'},{atom,0,employee}],[], - [{generate,2,{var,2,'E'}, - {call,2,{atom,2,table},[{atom,2,employee}]}}, - {match,3, - {record_field,3,{var,3,'E'},{atom,3,salary}}, - {call,0,{atom,0,foo},[Expr2]}}]}]}, - RChars2 = erl_pp:rule(R2), - ?line true = RChars =:= lists:flatten(RChars2), - ARChars = erl_pp:form(R, H), - ?line true = RChars =:= lists:flatten(ARChars), - - ?line "INVALID-FORM:{foo,bar}:" = lists:flatten(erl_pp:expr({foo,bar})), + true = AChars =:= lists:flatten(AFormChars), + + "INVALID-FORM:{foo,bar}:" = lists:flatten(erl_pp:expr({foo,bar})), %% A list (as before R6), not a list of lists. - G = [{op,1,'>',{atom,1,a},{foo,{atom,1,b}}}], % not a proper guard + G = [{op,A1,'>',{atom,A1,a},{foo,{atom,A1,b}}}], % not a proper guard GChars = lists:flatten(erl_pp:guard(G, H)), - G2 = [{op,1,'>',{atom,1,a}, - {call,0,{atom,0,foo},[{atom,1,b}]}}], % not a proper guard + G2 = [{op,A1,'>',{atom,A1,a}, + {call,A0,{atom,A0,foo},[{atom,A1,b}]}}], % not a proper guard GChars2 = erl_pp:guard(G2), - ?line true = GChars =:= lists:flatten(GChars2), + true = GChars =:= lists:flatten(GChars2), EH = HookFun({?MODULE, ehook, [foo,bar]}), XEChars = erl_pp:expr(Expr, -1, EH), - ?line true = remove_indentation(EChars) =:= lists:flatten(XEChars), + true = remove_indentation(EChars) =:= lists:flatten(XEChars), XEChars2 = erl_pp:expr(Expr, EH), - ?line true = EChars =:= lists:flatten(XEChars2), + true = EChars =:= lists:flatten(XEChars2), %% Note: no leading spaces before "begin". - Block = {block,0,[{match,0,{var,0,'A'},{integer,0,3}}, - {atom,0,true}]}, - ?line "begin\n A =" ++ _ = + Block = {block,A0,[{match,A0,{var,A0,'A'},{integer,A0,3}}, + {atom,A0,true}]}, + "begin\n A =" ++ _ = lists:flatten(erl_pp:expr(Block, 17, none)), %% Special... - ?line true = - "{some,value}" =:= lists:flatten(erl_pp:expr({value,0,{some,value}})), + true = + "{some,value}" =:= lists:flatten(erl_pp:expr({value,A0,{some,value}})), %% Silly... - ?line true = + true = "if true -> 0 end" =:= flat_expr({'if',0,[{clause,0,[],[],[{atom,0,0}]}]}), %% More compatibility: before R6 - OldIf = {'if',0,[{clause,0,[],[{atom,0,true}],[{atom,0,b}]}]}, - NewIf = {'if',0,[{clause,0,[],[[{atom,0,true}]],[{atom,0,b}]}]}, + OldIf = {'if',A0,[{clause,A0,[],[{atom,A0,true}],[{atom,A0,b}]}]}, + NewIf = {'if',A0,[{clause,A0,[],[[{atom,A0,true}]],[{atom,A0,b}]}]}, OldIfChars = lists:flatten(erl_pp:expr(OldIf)), NewIfChars = lists:flatten(erl_pp:expr(NewIf)), - ?line true = OldIfChars =:= NewIfChars, + true = OldIfChars =:= NewIfChars, ok. @@ -710,20 +650,19 @@ ehook(HE, I, P, H, foo, bar) -> hook(HE, I, P, H). hook({foo,E}, I, P, H) -> - erl_pp:expr({call,0,{atom,0,foo},[E]}, I, P, H). + A = erl_anno:new(0), + erl_pp:expr({call,A,{atom,A,foo},[E]}, I, P, H). -neg_indent(suite) -> - []; neg_indent(Config) when is_list(Config) -> - ?line ok = pp_expr(<<"begin a end">>), - ?line ok = pp_expr(<<"begin a,b end">>), - ?line ok = pp_expr(<<"try a,b,c + ok = pp_expr(<<"begin a end">>), + ok = pp_expr(<<"begin a,b end">>), + ok = pp_expr(<<"try a,b,c catch exit:_ -> d; throw:_ -> t; error:{foo,bar} -> foo, bar end">>), - ?line ok = pp_expr( + ok = pp_expr( <<"fun() -> F = fun(A, B) when ((A#r1.a) orelse (B#r2.a)) or (B#r2.b) or (A#r1.b) -> @@ -737,39 +676,41 @@ neg_indent(Config) when is_list(Config) -> ok end()">>), - ?line ok = pp_expr(<<"[X || X <- a, true]">>), - ?line ok = pp_expr(<<"{[a,b,c],[d,e|f]}">>), - ?line ok = pp_expr(<<"f(a,b,c)">>), - ?line ok = pp_expr(<<"fun() when a,b;c,d -> a end">>), - ?line ok = pp_expr(<<"<<34:32,17:32>>">>), - ?line ok = pp_expr(<<"if a,b,c -> d; e,f,g -> h,i end">>), - ?line ok = pp_expr(<<"if a -> d; c -> d end">>), - ?line ok = pp_expr(<<"receive after 1 -> 2 end">>), - ?line ok = pp_expr(<<"begin a,b,c end">>), - - ?line "\"\"" = flat_expr({string,0,""}), - ?line ok = pp_expr(<<"\"abc\"">>), - ?line ok = pp_expr(<<"\"abc\n\n\n\n\nkjsd\n\n\n\n\nkljsddf\n\n\n\n\n" - "klafd\n\n\n\n\nkljsdf\n\n\n\n\nsdf\n\n\n\n\n\"">>), - ?line ok = pp_expr(<<"fkjlskljklkkljlkjlkjkljlkjsljklf" - "lsdjlfdsjlfjsdlfjdslfjdlsjfsdjfklsdkfjsdf(" - "\"abc\n\n\n\n\nkjsd\n\n\n\n\nkljsddf\n\n\n\n\n" - "kljsafd\n\n\n\n\nkljsdf\n\n\n\n\nkjsdf" - "\n\n\n\n\n\")">>), + ok = pp_expr(<<"[X || X <- a, true]">>), + ok = pp_expr(<<"{[a,b,c],[d,e|f]}">>), + ok = pp_expr(<<"f(a,b,c)">>), + ok = pp_expr(<<"fun() when a,b;c,d -> a end">>), + ok = pp_expr(<<"fun A() when a,b;c,d -> a end">>), + ok = pp_expr(<<"<<34:32,17:32>>">>), + ok = pp_expr(<<"if a,b,c -> d; e,f,g -> h,i end">>), + ok = pp_expr(<<"if a -> d; c -> d end">>), + ok = pp_expr(<<"receive after 1 -> 2 end">>), + ok = pp_expr(<<"begin a,b,c end">>), + + "\"\"" = flat_expr({string,0,""}), + ok = pp_expr(<<"\"abc\"">>), + ok = pp_expr(<<"\"abc\n\n\n\n\nkjsd\n\n\n\n\nkljsddf\n\n\n\n\n" + "klafd\n\n\n\n\nkljsdf\n\n\n\n\nsdf\n\n\n\n\n\"">>), + ok = pp_expr(<<"fkjlskljklkkljlkjlkjkljlkjsljklf" + "lsdjlfdsjlfjsdlfjdslfjdlsjfsdjfklsdkfjsdf(" + "\"abc\n\n\n\n\nkjsd\n\n\n\n\nkljsddf\n\n\n\n\n" + "kljsafd\n\n\n\n\nkljsdf\n\n\n\n\nkjsdf" + "\n\n\n\n\n\")">>), %% fun-info is skipped when everything is to fit on one single line Fun1 = {'fun',1,{function,t,0},{0,45353021,'-t/0-fun-0-'}}, - ?line "fun t/0" = flat_expr(Fun1), + "fun t/0" = flat_expr(Fun1), Fun2 = {'fun',2,{clauses,[{clause,2,[],[],[{atom,3,true}]}]}, {0,108059557,'-t/0-fun-0-'}}, - ?line "fun() -> true end" = flat_expr(Fun2), + "fun() -> true end" = flat_expr(Fun2), + Fun3 = {named_fun,3,'True',[{clause,3,[],[],[{atom,3,true}]}], + {0,424242424,'-t/0-True-0-'}}, + "fun True() -> true end" = flat_expr(Fun3), ok. -otp_6321(doc) -> - "OTP_6321. Bug fix of exprs()."; -otp_6321(suite) -> []; +%% OTP_6321. Bug fix of exprs(). otp_6321(Config) when is_list(Config) -> Str = "S = hopp, {hej, S}. ", {done, {ok, Tokens, _EndLine}, ""} = erl_scan:tokens("", Str, _L=1), @@ -777,9 +718,7 @@ otp_6321(Config) when is_list(Config) -> "S = hopp, {hej,S}" = lists:flatten(erl_pp:exprs(Exprs)), ok. -otp_6911(doc) -> - "OTP_6911. More newlines."; -otp_6911(suite) -> []; +%% OTP_6911. More newlines. otp_6911(Config) when is_list(Config) -> F = {function,5,thomas,1, [{clause,5, @@ -789,39 +728,33 @@ otp_6911(Config) when is_list(Config) -> {var,6,'X'}, [{clause,7,[{atom,7,true}],[],[{integer,7,12}]}, {clause,8,[{atom,8,false}],[],[{integer,8,14}]}]}]}]}, - ?line Chars = lists:flatten(erl_pp:form(F)), - ?line "thomas(X) ->\n" + Chars = flat_form(F), + "thomas(X) ->\n" " case X of\n" " true ->\n" " 12;\n" " false ->\n" " 14\n" " end.\n" = Chars, - ?line ok = pp_expr(<<"case X of true -> 12; false -> 14 end">>), - ?line ok = pp_expr(<<"receive after 1 -> ok end">>), + ok = pp_expr(<<"case X of true -> 12; false -> 14 end">>), + ok = pp_expr(<<"receive after 1 -> ok end">>), ok. -otp_6914(doc) -> - "OTP_6914. Binary comprehensions."; -otp_6914(suite) -> []; +%% OTP_6914. Binary comprehensions. otp_6914(Config) when is_list(Config) -> - ?line ok = pp_expr(<<"<< <<B:1>> || B <- [0,1,1] >>">>), - ?line ok = pp_expr(<<"[ B || <<B:1>> <= <<\"hi\">>]">>), - ?line ok = pp_expr(<<"<< <<1:1>> || true >>">>), + ok = pp_expr(<<"<< <<B:1>> || B <- [0,1,1] >>">>), + ok = pp_expr(<<"[ B || <<B:1>> <= <<\"hi\">>]">>), + ok = pp_expr(<<"<< <<1:1>> || true >>">>), ok. -otp_8150(doc) -> - "OTP_8150. Types."; -otp_8150(suite) -> []; +%% OTP_8150. Types. otp_8150(Config) when is_list(Config) -> - ?line _ = [{N,ok} = {N,pp_forms(B)} || + _ = [{N,ok} = {N,pp_forms(B)} || {N,B} <- type_examples() ], ok. -otp_8238(doc) -> - "OTP_8238. Bugfix 'E'."; -otp_8238(suite) -> []; +%% OTP_8238. Bugfix 'E'. otp_8238(Config) when is_list(Config) -> Ex = [<<"-record(rec1, {}).\n" "-record(rec2, {a, b}).\n" @@ -836,7 +769,7 @@ otp_8238(Config) when is_list(Config) -> "t2() ->\n" " #r{}.\n">> ], - ?line compile(Config, [{otp_8238,iolist_to_binary(Ex)}]), + compile(Config, [{otp_8238,iolist_to_binary(Ex)}]), ok. type_examples() -> @@ -847,6 +780,7 @@ type_examples() -> {ex3,<<"-type paren() :: (ann2()). ">>}, {ex4,<<"-type t1() :: atom(). ">>}, {ex5,<<"-type t2() :: [t1()]. ">>}, + {ex56,<<"-type integer(A) :: A. ">>}, {ex6,<<"-type t3(Atom) :: integer(Atom). ">>}, {ex7,<<"-type '\\'t::4'() :: t3('\\'foobar'). ">>}, {ex8,<<"-type t5() :: {t1(), t3(foo)}. ">>}, @@ -886,14 +820,17 @@ type_examples() -> {ex30,<<"-type t99() ::" "{t2(),'\\'t::4'(),t5(),t6(),t7(),t8(),t10(),t14()," "t15(),t20(),t21(), t22(),t25()}. ">>}, + %% Writing constraints as is_subtype(V, T) is not supported since + %% Erlang/OTP 19.0, but as long as the parser recognizes the + %% is_subtype(V, T) syntax, we need a few examples of the syntax. {ex31,<<"-spec t1(FooBar :: t99()) -> t99();" - "(t2()) -> t2();" - "('\\'t::4'()) -> '\\'t::4'() when is_subtype('\\'t::4'(), t24);" - "(t23()) -> t23() when is_subtype(t23(), atom())," - " is_subtype(t23(), t14());" - "(t24()) -> t24() when is_subtype(t24(), atom())," - " is_subtype(t24(), t14())," - " is_subtype(t24(), '\\'t::4'()).">>}, + "(t2()) -> t2();" + "('\\'t::4'()) -> '\\'t::4'() when is_subtype('\\'t::4'(), t24);" + "(t23()) -> t23() when is_subtype(t23(), atom())," + " is_subtype(t23(), t14());" + "(t24()) -> t24() when is_subtype(t24(), atom())," + " is_subtype(t24(), t14())," + " is_subtype(t24(), '\\'t::4'()).">>}, {ex32,<<"-spec mod:t2() -> any(). ">>}, {ex33,<<"-opaque attributes_data() :: " "[{'column', column()} | {'line', info_line()} |" @@ -913,19 +850,15 @@ type_examples() -> "f19 = 3 :: integer()|undefined," "f5 = 3 :: undefined|integer()}). ">>}]. -otp_8473(doc) -> - "OTP_8473. Bugfix abstract type 'fun'."; -otp_8473(suite) -> []; +%% OTP_8473. Bugfix abstract type 'fun'. otp_8473(Config) when is_list(Config) -> Ex = [{ex1,<<"-type 'fun'(A) :: A.\n" "-type funkar() :: 'fun'(fun((integer()) -> atom())).\n">>}], - ?line _ = [{N,ok} = {N,pp_forms(B)} || + _ = [{N,ok} = {N,pp_forms(B)} || {N,B} <- Ex], ok. -otp_8522(doc) -> - "OTP_8522. Avoid duplicated 'undefined' in record field types."; -otp_8522(suite) -> []; +%% OTP_8522. Avoid duplicated 'undefined' in record field types. otp_8522(Config) when is_list(Config) -> FileName = filename('otp_8522.erl', Config), C = <<"-module(otp_8522).\n" @@ -934,11 +867,13 @@ otp_8522(Config) when is_list(Config) -> " f3 :: (undefined),\n" " f4 :: x | y | undefined | z,\n" " f5 :: a}).\n">>, - ?line ok = file:write_file(FileName, C), - ?line {ok, _} = compile:file(FileName, [{outdir,?privdir},debug_info]), + ok = file:write_file(FileName, C), + {ok, _} = compile:file(FileName, [{outdir,?privdir},debug_info]), BF = filename("otp_8522", Config), - ?line {ok, A} = beam_lib:chunks(BF, [abstract_code]), - ?line 5 = count_atom(A, undefined), + {ok, A} = beam_lib:chunks(BF, [abstract_code]), + %% OTP-12719: Since 'undefined' is no longer added by the Erlang + %% Parser, the number of 'undefined' is 4. It used to be 5. + 4 = count_atom(A, undefined), ok. count_atom(A, A) -> @@ -950,9 +885,38 @@ count_atom(L, A) when is_list(L) -> count_atom(_, _) -> 0. -otp_8567(doc) -> - "OTP_8567. Avoid duplicated 'undefined' in record field types."; -otp_8567(suite) -> []; +maps_syntax(Config) when is_list(Config) -> + Ts = [{map_fun_1, + <<"t() ->\n" + " M0 = #{ 1 => hi, hi => 42, 1.0 => {hi,world}},\n" + " M1 = M0#{ 1 := hello, new_val => 1337 },\n" + " map_fun_2:val(M1).\n">>}, + {map_fun_2, + <<"val(#{ 1 := V1, hi := V2, new_val := V3}) -> {V1,V2,V3}.\n">>}], + compile(Config, Ts), + + ok = pp_expr(<<"#{}">>), + ok = pp_expr(<<"#{ a => 1, <<\"hi\">> => \"world\", 33 => 1.0 }">>), + ok = pp_expr(<<"#{ a := V1, <<\"hi\">> := V2 } = M">>), + ok = pp_expr(<<"M#{ a => V1, <<\"hi\">> := V2 }">>), + F = <<"-module(maps_type_syntax).\n" + "-compile(export_all).\n" + "-type t1() :: map().\n" + "-type t2() :: #{ atom() => integer(), atom() => float() }.\n" + "-type t3() :: #{ atom() := integer(), atom() := float() }.\n" + "-type u() :: #{a => (I :: integer()) | (A :: atom()),\n" + " (X :: atom()) | (Y :: atom()) =>\n" + " (I :: integer()) | (A :: atom())}.\n" + "-spec f1(t1()) -> 'true'.\n" + "f1(M) when is_map(M) -> true.\n" + "-spec f2(t2()) -> integer().\n" + "f2(#{a := V1,b := V2}) -> V1 + V2.\n" + "\n">>, + ok = pp_forms(F), + ok. + + +%% OTP_8567. Avoid duplicated 'undefined' in record field types. otp_8567(Config) when is_list(Config) -> FileName = filename('otp_8567.erl', Config), C = <<"-module otp_8567.\n" @@ -961,8 +925,8 @@ otp_8567(Config) when is_list(Config) -> "-record r, {a}.\n" "-record s, {a :: integer()}.\n" "-type t() :: {#r{},#s{}}.\n">>, - ?line ok = file:write_file(FileName, C), - ?line {error,[{_,[{3,erl_parse,["syntax error before: ","')'"]}]}],_} = + ok = file:write_file(FileName, C), + {error,[{_,[{3,erl_parse,["syntax error before: ","')'"]}]}],_} = compile:file(FileName, [return]), F = <<"-module(otp_8567).\n" @@ -976,28 +940,18 @@ otp_8567(Config) when is_list(Config) -> "t() ->\n" " 3.\n" "\n" - "-spec(t1/1 :: (ot()) -> ot1()).\n" - "t1(A) ->\n" - " A.\n" - "\n" "-spec(t2 (ot()) -> ot1()).\n" "t2(A) ->\n" " A.\n" "\n" - "-spec(otp_8567:t3/1 :: (ot()) -> ot1()).\n" - "t3(A) ->\n" - " A.\n" - "\n" "-spec(otp_8567:t4 (ot()) -> ot1()).\n" "t4(A) ->\n" " A.\n">>, - ?line ok = pp_forms(F), + ok = pp_forms(F), ok. -otp_8664(doc) -> - "OTP_8664. Types with integer expressions."; -otp_8664(suite) -> []; +%% OTP_8664. Types with integer expressions. otp_8664(Config) when is_list(Config) -> FileName = filename('otp_8664.erl', Config), C1 = <<"-module(otp_8664).\n" @@ -1014,42 +968,38 @@ otp_8664(Config) when is_list(Config) -> "-type t() :: t1() | t2() | t3() | b1() | u().\n" "-spec t() -> t().\n" "t() -> 3.\n">>, - ?line ok = file:write_file(FileName, C1), - ?line {ok, _, []} = compile:file(FileName, [return]), + ok = file:write_file(FileName, C1), + {ok, _, []} = compile:file(FileName, [return]), C2 = <<"-module(otp_8664).\n" "-export([t/0]).\n" "-spec t() -> 9 and 4.\n" "t() -> 0.\n">>, - ?line ok = file:write_file(FileName, C2), - ?line {error,[{_,[{3,erl_lint,{type_syntax,integer}}]}],_} = + ok = file:write_file(FileName, C2), + {error,[{_,[{3,erl_lint,{type_syntax,integer}}]}],_} = compile:file(FileName, [return]), ok. -otp_9147(doc) -> - "OTP_9147. Create well-formed types when adding 'undefined'."; -otp_9147(suite) -> []; +%% OTP-9147. Create well-formed types when adding 'undefined'. otp_9147(Config) when is_list(Config) -> FileName = filename('otp_9147.erl', Config), C1 = <<"-module(otp_9147).\n" "-export_type([undef/0]).\n" "-record(undef, {f1 :: F1 :: a | b}).\n" "-type undef() :: #undef{}.\n">>, - ?line ok = file:write_file(FileName, C1), - ?line {ok, _, []} = + ok = file:write_file(FileName, C1), + {ok, _, []} = compile:file(FileName, [return,'P',{outdir,?privdir}]), PFileName = filename('otp_9147.P', Config), - ?line {ok, Bin} = file:read_file(PFileName), + {ok, Bin} = file:read_file(PFileName), %% The parentheses around "F1 :: a | b" are new (bugfix). - ?line true = - lists:member("-record(undef,{f1 :: undefined | (F1 :: a | b)}).", + true = + lists:member("-record(undef,{f1 :: F1 :: a | b}).", string:tokens(binary_to_list(Bin), "\n")), ok. -otp_10302(doc) -> - "OTP-10302. Unicode characters scanner/parser."; -otp_10302(suite) -> []; +%% OTP-10302. Unicode characters scanner/parser. otp_10302(Config) when is_list(Config) -> Ts = [{uni_1, <<"t() -> <<(<<\"abc\\x{aaa}\">>):3/binary>>.">>} @@ -1069,10 +1019,11 @@ otp_10302(Config) when is_list(Config) -> Opts = [{hook, fun unicode_hook/4},{encoding,unicode}], Lc = parse_expr("[X || X <- [\"\x{400}\",\"\xFF\"]]."), - Expr = {call,0,{atom,0,fff},[{foo,{foo,Lc}},{foo,{foo,Lc}}]}, + A0 = erl_anno:new(0), + Expr = {call,A0,{atom,A0,fff},[{foo,{foo,Lc}},{foo,{foo,Lc}}]}, EChars = lists:flatten(erl_pp:expr(Expr, 0, Opts)), - Call = {call,0,{atom,0,foo},[{call,0,{atom,0,foo},[Lc]}]}, - Expr2 = {call,0,{atom,0,fff},[Call,Call]}, + Call = {call,A0,{atom,A0,foo},[{call,A0,{atom,A0,foo},[Lc]}]}, + Expr2 = {call,A0,{atom,A0,fff},[Call,Call]}, EChars2 = erl_pp:exprs([Expr2], U), EChars = lists:flatten(EChars2), [$\x{400},$\x{400}] = [C || C <- EChars, C > 255], @@ -1082,16 +1033,15 @@ otp_10302(Config) when is_list(Config) -> ok. unicode_hook({foo,E}, I, P, H) -> - erl_pp:expr({call,0,{atom,0,foo},[E]}, I, P, H). + A = erl_anno:new(0), + erl_pp:expr({call,A,{atom,A,foo},[E]}, I, P, H). -otp_10820(doc) -> - "OTP-10820. Unicode filenames."; -otp_10820(suite) -> []; +%% 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"), - C2 = <<"-module(any).">>, + C2 = <<"%% coding: latin-1\n -module(any).">>, ok = do_otp_10820(Config, C2, "+pc latin1"), ok = do_otp_10820(Config, C2, "+pc unicode"). @@ -1112,9 +1062,7 @@ file_attr_is_string("-file(\"" ++ _) -> true; file_attr_is_string([_ | L]) -> file_attr_is_string(L). -otp_11100(doc) -> - "OTP-11100. Fix printing of invalid forms."; -otp_11100(suite) -> []; +%% OTP-11100. Fix printing of invalid forms. otp_11100(Config) when is_list(Config) -> %% There are a few places where the added code ("options(none)") %% doesn't make a difference (pp:bit_elem_type/1 is an example). @@ -1122,34 +1070,79 @@ otp_11100(Config) when is_list(Config) -> %% Cannot trigger the use of the hook function with export/import. "-export([{fy,a}/b]).\n" = pf({attribute,1,export,[{{fy,a},b}]}), + A1 = erl_anno:new(1), "-type foo() :: integer(INVALID-FORM:{foo,bar}:).\n" = - pf({attribute,1,type,{foo,{type,1,integer,[{foo,bar}]},[]}}), - pf({attribute,1,type, - {a,{type,1,range,[{integer,1,1},{foo,bar}]},[]}}), + pf({attribute,A1,type,{foo,{type,A1,integer,[{foo,bar}]},[]}}), + pf({attribute,A1,type, + {a,{type,A1,range,[{integer,A1,1},{foo,bar}]},[]}}), "-type foo(INVALID-FORM:{foo,bar}:) :: A.\n" = - pf({attribute,1,type,{foo,{var,1,'A'},[{foo,bar}]}}), - "-type foo() :: (INVALID-FORM:{foo,bar}: :: []).\n" = - pf({attribute,1,type, - {foo,{paren_type,1, - [{ann_type,1,[{foo,bar},{type,1,nil,[]}]}]}, + pf({attribute,A1,type,{foo,{var,A1,'A'},[{foo,bar}]}}), + "-type foo() :: INVALID-FORM:{foo,bar}: :: [].\n" = + pf({attribute,A1,type, + {foo,{paren_type,A1, + [{ann_type,A1,[{foo,bar},{type,A1,nil,[]}]}]}, []}}), "-type foo() :: <<_:INVALID-FORM:{foo,bar}:>>.\n" = - pf({attribute,1,type, - {foo,{type,1,binary,[{foo,bar},{integer,1,0}]},[]}}), + pf({attribute,A1,type, + {foo,{type,A1,binary,[{foo,bar},{integer,A1,0}]},[]}}), "-type foo() :: <<_:10, _:_*INVALID-FORM:{foo,bar}:>>.\n" = - pf({attribute,1,type, - {foo,{type,1,binary,[{integer,1,10},{foo,bar}]},[]}}), + pf({attribute,A1,type, + {foo,{type,A1,binary,[{integer,A1,10},{foo,bar}]},[]}}), "-type foo() :: #r{INVALID-FORM:{foo,bar}: :: integer()}.\n" = - pf({attribute,1,type, - {foo,{type,1,record, - [{atom,1,r}, - {type,1,field_type, - [{foo,bar},{type,1,integer,[]}]}]}, + pf({attribute,A1,type, + {foo,{type,A1,record, + [{atom,A1,r}, + {type,A1,field_type, + [{foo,bar},{type,A1,integer,[]}]}]}, []}}), ok. +%% OTP-11861. behaviour_info() and -callback. +otp_11861(Config) when is_list(Config) -> + "-optional_callbacks([bar/0]).\n" = + pf({attribute,3,optional_callbacks,[{bar,0}]}), + "-optional_callbacks([{bar,1,bad}]).\n" = + pf({attribute,4,optional_callbacks,[{bar,1,bad}]}), + ok. + pf(Form) -> - lists:flatten(erl_pp:form(Form,none)). + lists:flatten(erl_pp:form(Form, none)). + +pr_1014(Config) -> + ok = pp_forms(<<"-type t() :: #{_ => _}. ">>), + ok = pp_forms(<<"-type t() :: #{any() => _}. ">>), + ok = pp_forms(<<"-type t() :: #{_ => any()}. ">>), + ok = pp_forms(<<"-type t() :: #{any() => any()}. ">>), + ok = pp_forms(<<"-type t() :: #{atom() := integer(), any() => any()}. ">>), + + FileName = filename('pr_1014.erl', Config), + C = <<"-module pr_1014.\n" + "-compile export_all.\n" + "-type m() :: #{..., a := integer()}.\n">>, + ok = file:write_file(FileName, C), + {error,[{_,[{3,erl_parse,["syntax error before: ","'...'"]}]}],_} = + compile:file(FileName, [return]), + + ok. + +otp_13662(Config) -> + Include = "abcdefghijabcdefghijabcdefghijabcdefghijabcde" + "fghij-xxxxxxxxxxxxxxxxxxxxxxxxxxxxxx.hrl", + IncludeFile = filename(Include, Config), + ok = file:write_file(IncludeFile, <<>>), + Ts = [{otp_13662, + <<"-file(\"abcdefghijabcdefghijabcdefghijabcdefghijabcde\"\n + \"fghij-xxxxxxxxxxxxxxxxxxxxxxxxxxxxxx.erl\", 0).\n + -include(\"abcdefghijabcdefghijabcdefghijabcdefghijabcde\" + \"fghij-xxxxxxxxxxxxxxxxxxxxxxxxxxxxxx.hrl\").\n + -include_lib(\"abcdefghijabcdefghijabcdefghijabcdefghijabcde\" + \"fghij-xxxxxxxxxxxxxxxxxxxxxxxxxxxxxx.hrl\"). + -compile(export_all).\n + t() ->\n + \"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa\"\n + \"aaaaaaaaaaaaaaaaaaaaaa\".\n">>} + ], + compile(Config, Ts). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% @@ -1161,11 +1154,11 @@ compile(Config, Tests) -> ok -> BadL; not_ok -> - ?t:format("~nTest ~p failed.~n", [N]), + io:format("~nTest ~p failed.~n", [N]), fail() end; Bad -> - ?t:format("~nTest ~p failed. got~n ~p~n", + io:format("~nTest ~p failed. got~n ~p~n", [N, Bad]), fail() end @@ -1214,9 +1207,18 @@ strip_module_info(Bin) -> <<R:Start/binary,_/binary>> = Bin, R. -flat_expr(Expr) -> +flat_expr1(Expr0) -> + Expr = erl_parse:new_anno(Expr0), + lists:flatten(erl_pp:expr(Expr)). + +flat_expr(Expr0) -> + Expr = erl_parse:new_anno(Expr0), lists:flatten(erl_pp:expr(Expr, -1, none)). +flat_form(Form0) -> + Form = erl_parse:new_anno(Form0), + lists:flatten(erl_pp:form(Form)). + pp_forms(Bin) -> pp_forms(Bin, none). @@ -1322,10 +1324,9 @@ filename(Name, Config) -> filename:join(?privdir, Name). fail() -> - io:format("failed~n"), - ?t:fail(). + ct:fail(failed). %% +fnu means a peer node has to be started; slave will not do start_node(Name, Xargs) -> - ?line PA = filename:dirname(code:which(?MODULE)), + PA = filename:dirname(code:which(?MODULE)), test_server:start_node(Name, peer, [{args, "-pa " ++ PA ++ " " ++ Xargs}]). |