aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test/epp_SUITE.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test/epp_SUITE.erl')
-rw-r--r--lib/stdlib/test/epp_SUITE.erl231
1 files changed, 173 insertions, 58 deletions
diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl
index 9a3ae0baf5..57f3f4eddb 100644
--- a/lib/stdlib/test/epp_SUITE.erl
+++ b/lib/stdlib/test/epp_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1998-2010. All Rights Reserved.
+%% Copyright Ericsson AB 1998-2011. 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
@@ -17,13 +17,15 @@
%% %CopyrightEnd%
-module(epp_SUITE).
--export([all/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2]).
--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,
+-export([rec_1/1, predef_mac/1,
+ upcase_mac_1/1, upcase_mac_2/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, otp_8911/1]).
-export([epp_parse_erl_form/2]).
@@ -38,13 +40,13 @@
-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").
-else.
--include("test_server.hrl").
--export([init_per_testcase/2, fin_per_testcase/2]).
+-include_lib("test_server/include/test_server.hrl").
+-export([init_per_testcase/2, end_per_testcase/2]).
% Default timetrap timeout (set in init_per_testcase).
-define(default_timeout, ?t:minutes(1)).
@@ -52,18 +54,36 @@ config(data_dir, _) ->
init_per_testcase(_, Config) ->
?line Dog = ?t:timetrap(?default_timeout),
[{watchdog, Dog} | Config].
-fin_per_testcase(_, Config) ->
+end_per_testcase(_, Config) ->
Dog = ?config(watchdog, Config),
test_server:timetrap_cancel(Dog),
ok.
-endif.
-all(doc) ->
- ["Test cases for epp."];
-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].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [rec_1, {group, upcase_mac}, predef_mac,
+ {group, variable}, otp_4870, otp_4871, otp_5362, pmod,
+ not_circular, skip_header, otp_6277, otp_7702, otp_8130,
+ overload_mac, otp_8388, otp_8470, otp_8503, otp_8562,
+ otp_8665, otp_8911].
+
+groups() ->
+ [{upcase_mac, [], [upcase_mac_1, upcase_mac_2]},
+ {variable, [], [variable_1]}].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
rec_1(doc) ->
["Recursive macros hang or crash epp (OTP-1398)."];
@@ -126,10 +146,6 @@ check_errors([{error, Info} | Rest]) ->
check_errors([_ | Rest]) ->
check_errors(Rest).
-upcase_mac(doc) ->
- ["Check that uppercase macro names are implicitly quoted (OTP-2608)"];
-upcase_mac(suite) ->
- [upcase_mac_1, upcase_mac_2].
upcase_mac_1(doc) ->
[];
@@ -175,10 +191,6 @@ predef_mac(Config) when is_list(Config) ->
end,
ok.
-variable(doc) ->
- ["Check variable as first file component of the include directives."];
-variable(suite) ->
- [variable_1].
variable_1(doc) ->
[];
@@ -191,7 +203,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 +230,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 +313,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 +344,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 +452,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 +505,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 +517,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 +628,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 +648,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 +692,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 +762,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 +786,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 +799,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 +826,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 +952,7 @@ ifdef(Config) ->
<<"\n-if.\n"
"-endif.\n">>,
{errors,[{{2,2},epp,{'NYI','if'}}],[]}},
-
+
{define_c7,
<<"-ifndef(a).\n"
"-elif.\n"
@@ -1047,13 +1066,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 +1139,121 @@ 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_8911(doc) ->
+ ["OTP-8911. -file and file inclusion bug"];
+otp_8911(suite) ->
+ [];
+otp_8911(Config) when is_list(Config) ->
+ ?line {ok, CWD} = file:get_cwd(),
+ ?line ok = file:set_cwd(?config(priv_dir, Config)),
+
+ File = "i.erl",
+ Cont = <<"-module(i).
+ -compile(export_all).
+ -file(\"fil1\", 100).
+ -include(\"i1.erl\").
+ t() ->
+ a.
+ ">>,
+ ?line ok = file:write_file(File, Cont),
+ Incl = <<"-file(\"fil2\", 35).
+ t1() ->
+ b.
+ ">>,
+ File1 = "i1.erl",
+ ?line ok = file:write_file(File1, Incl),
+
+ ?line {ok, i} = cover:compile(File),
+ ?line a = i:t(),
+ ?line {ok,[{{i,6},1}]} = cover:analyse(i, calls, line),
+ ?line cover:stop(),
+
+ file:delete(File),
+ file:delete(File1),
+ ?line file:set_cwd(CWD),
+ 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 +1270,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()
@@ -1165,20 +1280,20 @@ eval_tests(Config, Fun, Tests) ->
check_test(Config, Test) ->
- Filename = 'epp_test.erl',
+ Filename = "epp_test.erl",
?line PrivDir = ?config(priv_dir, Config),
?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.
compile_test(Config, Test0) ->
Test = [<<"-module(epp_test). -compile(export_all). ">>, Test0],
- Filename = 'epp_test.erl',
+ Filename = "epp_test.erl",
?line PrivDir = ?config(priv_dir, Config),
?line File = filename:join(PrivDir, Filename),
?line ok = file:write_file(File, Test),
@@ -1187,7 +1302,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 +1346,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}) ->