diff options
Diffstat (limited to 'lib/stdlib/test/epp_SUITE.erl')
-rw-r--r-- | lib/stdlib/test/epp_SUITE.erl | 142 |
1 files changed, 106 insertions, 36 deletions
diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl index 9a3ae0baf5..e31dfdd764 100644 --- a/lib/stdlib/test/epp_SUITE.erl +++ b/lib/stdlib/test/epp_SUITE.erl @@ -19,11 +19,12 @@ -module(epp_SUITE). -export([all/1]). --export([rec_1/1, predef_mac/1, +-export([rec_1/1, predef_mac/1, upcase_mac/1, upcase_mac_1/1, upcase_mac_2/1, variable/1, variable_1/1, otp_4870/1, otp_4871/1, otp_5362/1, pmod/1, not_circular/1, skip_header/1, otp_6277/1, otp_7702/1, - otp_8130/1, overload_mac/1, otp_8388/1]). + otp_8130/1, overload_mac/1, otp_8388/1, otp_8470/1, otp_8503/1, + otp_8562/1, otp_8665/1]). -export([epp_parse_erl_form/2]). @@ -38,7 +39,7 @@ -define(config(A,B),config(A,B)). %% -define(t, test_server). -define(t, io). -config(priv_dir, _) -> +config(priv_dir, _) -> filename:absname("./epp_SUITE_priv"); config(data_dir, _) -> filename:absname("./epp_SUITE_data"). @@ -63,7 +64,7 @@ all(doc) -> all(suite) -> [rec_1, upcase_mac, predef_mac, variable, otp_4870, otp_4871, otp_5362, pmod, not_circular, skip_header, otp_6277, otp_7702, otp_8130, - overload_mac, otp_8388]. + overload_mac, otp_8388, otp_8470, otp_8503, otp_8562, otp_8665]. rec_1(doc) -> ["Recursive macros hang or crash epp (OTP-1398)."]; @@ -191,7 +192,7 @@ variable_1(Config) when is_list(Config) -> %% variable_1.erl includes variable_1_include.hrl and %% variable_1_include_dir.hrl. ?line {ok, List} = epp:parse_file(File, [], []), - ?line {value, {attribute,_,a,{value1,value2}}} = + ?line {value, {attribute,_,a,{value1,value2}}} = lists:keysearch(a,3,List), ok. @@ -218,13 +219,13 @@ otp_4871(Config) when is_list(Config) -> %% Testing crash in erl_scan. Unfortunately there currently is %% no known way to crash erl_scan so it is emulated by killing the %% file io server. This assumes lots of things about how - %% the processes are started and how monitors are set up, + %% the processes are started and how monitors are set up, %% so there are some sanity checks before killing. ?line {ok,Epp} = epp:open(File, []), timer:sleep(1), ?line {current_function,{epp,_,_}} = process_info(Epp, current_function), ?line {monitored_by,[Io]} = process_info(Epp, monitored_by), - ?line {current_function,{file_io_server,_,_}} = + ?line {current_function,{file_io_server,_,_}} = process_info(Io, current_function), ?line exit(Io, emulate_crash), timer:sleep(1), @@ -301,7 +302,7 @@ otp_5362(Config) when is_list(Config) -> Back_hrl = [<<" -file(\"">>,File_Back,<<"\", 2). ">>], - + ?line ok = file:write_file(File_Back, Back), ?line ok = file:write_file(File_Back_hrl, list_to_binary(Back_hrl)), @@ -332,7 +333,7 @@ otp_5362(Config) when is_list(Config) -> ?line ok = file:write_file(File_Change, list_to_binary(Change)), - ?line {ok, change_5362, ChangeWarnings} = + ?line {ok, change_5362, ChangeWarnings} = compile:file(File_Change, Copts), ?line true = message_compare( [{File_Change,[{{1002,21},erl_lint,{unused_var,'B'}}]}, @@ -440,9 +441,9 @@ skip_header(Config) when is_list(Config) -> that should be skipped -module(epp_test_skip_header). -export([main/1]). - + main(_) -> ?MODULE. - + ">>), ?line {ok, Fd} = file:open(File, [read]), ?line io:get_line(Fd, ''), @@ -493,9 +494,9 @@ otp_7702(Config) when is_list(Config) -> t() -> ?RECEIVE(foo, bar).">>, ?line ok = file:write_file(File, Contents), - ?line {ok, file_7702, []} = + ?line {ok, file_7702, []} = compile:file(File, [debug_info,return,{outdir,Dir}]), - + BeamFile = filename:join(Dir, "file_7702.beam"), {ok, AC} = beam_lib:chunks(BeamFile, [abstract_code]), @@ -505,7 +506,7 @@ otp_7702(Config) when is_list(Config) -> L end, Forms2 = [erl_lint:modify_line(Form, Fun) || Form <- Forms], - ?line + ?line [{attribute,1,file,_}, _, _, @@ -616,9 +617,9 @@ otp_8130(Config) when is_list(Config) -> "t() -> 14 = (#file_info{size = 14})#file_info.size, ok.\n">>, ok}, - {otp_8130_7, + {otp_8130_7_new, <<"-record(b, {b}).\n" - "-define(A, {{a,#b.b.\n" + "-define(A, {{a,#b.b).\n" "t() -> {{a,2}} = ?A}}, ok.">>, ok}, @@ -636,7 +637,7 @@ otp_8130(Config) when is_list(Config) -> ], ?line [] = run(Config, Ts), - + Cs = [{otp_8130_c1, <<"-define(M1(A), if\n" "A =:= 1 -> B;\n" @@ -680,7 +681,7 @@ otp_8130(Config) when is_list(Config) -> <<"\n-include_lib(\"$apa/foo.hrl\").\n">>, {errors,[{{2,2},epp,{include,lib,"$apa/foo.hrl"}}],[]}}, - + {otp_8130_c9, <<"-define(S, ?S).\n" "t() -> ?S.\n">>, @@ -750,7 +751,14 @@ otp_8130(Config) when is_list(Config) -> {otp_8130_c24, <<"\n-include(\"no such file.erl\").\n">>, - {errors,[{{2,2},epp,{include,file,"no such file.erl"}}],[]}} + {errors,[{{2,2},epp,{include,file,"no such file.erl"}}],[]}}, + + {otp_8130_7, + <<"-record(b, {b}).\n" + "-define(A, {{a,#b.b.\n" + "t() -> {{a,2}} = ?A}}, ok.">>, + {errors,[{{2,20},epp,missing_parenthesis}, + {{3,19},epp,{undefined,'A',none}}],[]}} ], ?line [] = compile(Config, Cs), @@ -767,7 +775,7 @@ otp_8130(Config) when is_list(Config) -> ?line Dir = ?config(priv_dir, Config), ?line File = filename:join(Dir, "otp_8130.erl"), - ?line ok = file:write_file(File, + ?line ok = file:write_file(File, "-module(otp_8130).\n" "-define(a, 3.14).\n" "t() -> ?a.\n"), @@ -780,7 +788,7 @@ otp_8130(Config) when is_list(Config) -> ?line {eof,_} = epp:scan_erl_form(Epp), ?line ['BASE_MODULE','BASE_MODULE_STRING','BEAM','FILE','LINE', 'MACHINE','MODULE','MODULE_STRING',a] = macs(Epp), - ?line epp:close(Epp), + ?line epp:close(Epp), %% escript ModuleStr = "any_name", @@ -807,7 +815,7 @@ otp_8130(Config) when is_list(Config) -> PreDefMacros = [{a,1},a], ?line {error,{redefine,a}} = epp:open(File, [], PreDefMacros) end(), - + ?line {error,enoent} = epp:open("no such file", []), ?line {error,enoent} = epp:parse_file("no such file", [], []), @@ -933,7 +941,7 @@ ifdef(Config) -> <<"\n-if.\n" "-endif.\n">>, {errors,[{{2,2},epp,{'NYI','if'}}],[]}}, - + {define_c7, <<"-ifndef(a).\n" "-elif.\n" @@ -1047,13 +1055,13 @@ overload_mac(Config) when is_list(Config) -> "-undef(A).\n" "t1() -> ?A.\n", "t2() -> ?A(1).">>, - {errors,[{{4,9},epp,{undefined,'A', none}}, - {{5,9},epp,{undefined,'A', 1}}],[]}}, + {errors,[{{4,10},epp,{undefined,'A', none}}, + {{5,10},epp,{undefined,'A', 1}}],[]}}, %% cannot overload predefined macros {overload_mac_c2, <<"-define(MODULE(X), X).">>, - {errors,[{{1,9},epp,{redefine_predef,'MODULE'}}],[]}}, + {errors,[{{1,50},epp,{redefine_predef,'MODULE'}}],[]}}, %% cannot overload macros with same arity {overload_mac_c3, @@ -1120,25 +1128,87 @@ otp_8388(Config) when is_list(Config) -> {macro_1, <<"-define(m(A), A).\n" "t() -> ?m(,).\n">>, - {errors,[{{2,11},epp,{arg_error,m}}],[]}}, + {errors,[{{2,9},epp,{arg_error,m}}],[]}}, {macro_2, <<"-define(m(A), A).\n" "t() -> ?m(a,).\n">>, - {errors,[{{2,12},epp,{arg_error,m}}],[]}}, + {errors,[{{2,9},epp,{arg_error,m}}],[]}}, {macro_3, <<"-define(LINE, a).\n">>, - {errors,[{{1,9},epp,{redefine_predef,'LINE'}}],[]}}, + {errors,[{{1,50},epp,{redefine_predef,'LINE'}}],[]}}, {macro_4, <<"-define(A(B, C, D), {B,C,D}).\n" "t() -> ?A(a,,3).\n">>, - {errors,[{{2,8},epp,{mismatch,'A'}}],[]}}, + {errors,[{{2,9},epp,{mismatch,'A'}}],[]}}, {macro_5, <<"-define(Q, {?F0(), ?F1(,,4)}).\n">>, - {errors,[{{1,24},epp,{arg_error,'F1'}}],[]}} + {errors,[{{1,62},epp,{arg_error,'F1'}}],[]}}, + {macro_6, + <<"-define(FOO(X), ?BAR(X)).\n" + "-define(BAR(X), ?FOO(X)).\n" + "-undef(FOO).\n" + "test() -> ?BAR(1).\n">>, + {errors,[{{4,12},epp,{undefined,'FOO',1}}],[]}} ], ?line [] = compile(Config, Ts), ok. +otp_8470(doc) -> + ["OTP-8470. Bugfix (one request - two replies)."]; +otp_8470(suite) -> + []; +otp_8470(Config) when is_list(Config) -> + Dir = ?config(priv_dir, Config), + C = <<"-file(\"erl_parse.yrl\", 486).\n" + "-file(\"erl_parse.yrl\", 488).\n">>, + ?line File = filename:join(Dir, "otp_8470.erl"), + ?line ok = file:write_file(File, C), + ?line {ok, _List} = epp:parse_file(File, [], []), + file:delete(File), + ?line receive _ -> fail() after 0 -> ok end, + ok. + +otp_8503(doc) -> + ["OTP-8503. Record with no fields is considered typed."]; +otp_8503(suite) -> + []; +otp_8503(Config) when is_list(Config) -> + Dir = ?config(priv_dir, Config), + C = <<"-record(r, {}).">>, + ?line File = filename:join(Dir, "otp_8503.erl"), + ?line ok = file:write_file(File, C), + ?line {ok, List} = epp:parse_file(File, [], []), + ?line [_] = [F || {attribute,_,type,{{record,r},[],[]}}=F <- List], + file:delete(File), + ?line receive _ -> fail() after 0 -> ok end, + ok. + +otp_8562(doc) -> + ["OTP-8503. Record with no fields is considered typed."]; +otp_8562(suite) -> + []; +otp_8562(Config) when is_list(Config) -> + Cs = [{otp_8562, + <<"-define(P(), {a,b}.\n" + "-define(P3, .\n">>, + {errors,[{{1,60},epp,missing_parenthesis}, + {{2,13},epp,missing_parenthesis}], []}} + ], + ?line [] = compile(Config, Cs), + ok. + +otp_8665(doc) -> + ["OTP-8665. Bugfix premature end."]; +otp_8665(suite) -> + []; +otp_8665(Config) when is_list(Config) -> + Cs = [{otp_8562, + <<"-define(A, a)\n">>, + {errors,[{{1,54},epp,premature_end}],[]}} + ], + ?line [] = compile(Config, Cs), + ok. + check(Config, Tests) -> eval_tests(Config, fun check_test/2, Tests). @@ -1155,7 +1225,7 @@ eval_tests(Config, Fun, Tests) -> case message_compare(E, Return) of true -> BadL; - false -> + false -> ?t:format("~nTest ~p failed. Expected~n ~p~n" "but got~n ~p~n", [N, E, Return]), fail() @@ -1170,9 +1240,9 @@ check_test(Config, Test) -> ?line File = filename:join(PrivDir, Filename), ?line ok = file:write_file(File, Test), ?line case epp:parse_file(File, [PrivDir], []) of - {ok,Forms} -> + {ok,Forms} -> [E || E={error,_} <- Forms]; - {error,Error} -> + {error,Error} -> Error end. @@ -1187,7 +1257,7 @@ compile_test(Config, Test0) -> {ok, Ws} -> warnings(File, Ws); Else -> Else end. - + warnings(File, Ws) -> case lists:append([W || {F, W} <- Ws, F =:= File]) of [] -> []; @@ -1231,7 +1301,7 @@ message_compare(T, T) -> message_compare(T1, T2) -> ln(T1) =:= T2. -%% Replaces locations like {Line,Column} with Line. +%% Replaces locations like {Line,Column} with Line. ln({warnings,L}) -> {warnings,ln0(L)}; ln({errors,EL,WL}) -> |