1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 1998-2018. All Rights Reserved.
5%%
6%% Licensed under the Apache License, Version 2.0 (the "License");
7%% you may not use this file except in compliance with the License.
8%% You may obtain a copy of the License at
9%%
10%%     http://www.apache.org/licenses/LICENSE-2.0
11%%
12%% Unless required by applicable law or agreed to in writing, software
13%% distributed under the License is distributed on an "AS IS" BASIS,
14%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15%% See the License for the specific language governing permissions and
16%% limitations under the License.
17%%
18%% %CopyrightEnd%
19
20-module(epp_SUITE).
21-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
22	 init_per_group/2,end_per_group/2]).
23
24-export([rec_1/1, include_local/1, predef_mac/1,
25	 upcase_mac_1/1, upcase_mac_2/1,
26	 variable_1/1, otp_4870/1, otp_4871/1, otp_5362/1,
27         pmod/1, not_circular/1, skip_header/1, otp_6277/1, gh_4995/1, otp_7702/1,
28         otp_8130/1, overload_mac/1, otp_8388/1, otp_8470/1,
29         otp_8562/1, otp_8665/1, otp_8911/1, otp_10302/1, otp_10820/1,
30         otp_11728/1, encoding/1, extends/1,  function_macro/1,
31	 test_error/1, test_warning/1, otp_14285/1,
32	 test_if/1,source_name/1,otp_16978/1,otp_16824/1,scan_file/1,file_macro/1]).
33
34-export([epp_parse_erl_form/2]).
35
36%%
37%% Define to run outside of test server
38%%
39%%-define(STANDALONE,1).
40
41-ifdef(STANDALONE).
42-compile(export_all).
43-define(line, put(line, ?LINE), ).
44-define(config(A,B),config(A,B)).
45%% -define(t, test_server).
46-define(t, io).
47config(priv_dir, _) ->
48    filename:absname("./epp_SUITE_priv");
49config(data_dir, _) ->
50    filename:absname("./epp_SUITE_data").
51-else.
52-include_lib("common_test/include/ct.hrl").
53-export([init_per_testcase/2, end_per_testcase/2]).
54
55init_per_testcase(_, Config) ->
56    Config.
57
58end_per_testcase(_, _Config) ->
59    ok.
60-endif.
61
62suite() ->
63    [{ct_hooks,[ts_install_cth]},
64     {timetrap,{minutes,1}}].
65
66all() ->
67    [rec_1, {group, upcase_mac}, include_local, predef_mac,
68     {group, variable}, otp_4870, otp_4871, otp_5362, pmod,
69     not_circular, skip_header, otp_6277, gh_4995, otp_7702, otp_8130,
70     overload_mac, otp_8388, otp_8470, otp_8562,
71     otp_8665, otp_8911, otp_10302, otp_10820, otp_11728,
72     encoding, extends, function_macro, test_error, test_warning,
73     otp_14285, test_if, source_name, otp_16978, otp_16824, scan_file, file_macro].
74
75groups() ->
76    [{upcase_mac, [], [upcase_mac_1, upcase_mac_2]},
77     {variable, [], [variable_1]}].
78
79init_per_suite(Config) ->
80    Config.
81
82end_per_suite(_Config) ->
83    ok.
84
85init_per_group(_GroupName, Config) ->
86    Config.
87
88end_per_group(_GroupName, Config) ->
89    Config.
90
91%% Recursive macros hang or crash epp (OTP-1398).
92rec_1(Config) when is_list(Config) ->
93    File = filename:join(proplists:get_value(data_dir, Config), "mac.erl"),
94    {ok, List} = epp_parse_file(File, [], []),
95    %% we should encounter errors
96    {value, _} = lists:keysearch(error, 1, List),
97    check_errors(List),
98    ok.
99
100include_local(Config) when is_list(Config) ->
101    DataDir = proplists:get_value(data_dir, Config),
102    File = filename:join(DataDir, "include_local.erl"),
103    FooHrl = filename:join([DataDir,"include","foo.hrl"]),
104    BarHrl = filename:join([DataDir,"include","bar.hrl"]),
105    %% include_local.erl includes include/foo.hrl which
106    %% includes bar.hrl (also in include/) without requiring
107    %% any additional include path, and overriding any file
108    %% of the same name that the path points to
109    {ok, List} = epp:parse_file(File, [DataDir], []),
110    {value, {attribute,_,a,{true,true}}} =
111	lists:keysearch(a,3,List),
112    [{File,1},{FooHrl,1},{BarHrl,1},{FooHrl,5},{File,5}] =
113        [ FileLine || {attribute,_,file,FileLine} <- List ],
114    ok.
115
116file_macro(Config) when is_list(Config) ->
117    DataDir = proplists:get_value(data_dir, Config),
118    File = filename:join(DataDir, "file_macro.erl"),
119    {ok, List} = epp:parse_file(File, [{includes, [DataDir]},
120                                       {source_name, "Other source"}]),
121    %% Both attribute a and b are defined as ?FILE, they should be the same
122    {attribute,_,a,FileA} = lists:keyfind(a, 3, List),
123    {attribute,_,b,FileB} = lists:keyfind(b, 3, List),
124    "Other source" = FileA = FileB,
125    ok.
126
127%%% Here is a little reimplementation of epp:parse_file, which times out
128%%% after 4 seconds if the epp server doesn't respond. If we use the
129%%% regular epp:parse_file, the test case will time out, and then epp
130%%% server will go on growing until we dump core.
131epp_parse_file(File, Inc, Predef) ->
132    List = do_epp_parse_file(fun() ->
133				     epp:open(File, Inc, Predef)
134			     end),
135    List = do_epp_parse_file(fun() ->
136				     Opts = [{name, File},
137					     {includes, Inc},
138					     {macros, Predef}],
139				     epp:open(Opts)
140			     end),
141    {ok, List}.
142
143do_epp_parse_file(Open) ->
144    {ok, Epp} = Open(),
145    List = collect_epp_forms(Epp),
146    epp:close(Epp),
147    List.
148
149collect_epp_forms(Epp) ->
150    Result = epp_parse_erl_form(Epp),
151    case Result of
152	{error, _Error} ->
153	    [Result | collect_epp_forms(Epp)];
154	{ok, Form} ->
155	    [Form | collect_epp_forms(Epp)];
156	{eof, _} ->
157	    [Result]
158    end.
159
160epp_parse_erl_form(Epp) ->
161    P = spawn(?MODULE, epp_parse_erl_form, [Epp, self()]),
162    receive
163	{P, Result} ->
164	    Result
165    after 4000 ->
166	    exit(Epp, kill),
167	    exit(P, kill),
168	    timeout
169    end.
170
171epp_parse_erl_form(Epp, Parent) ->
172    Parent ! {self(), epp:parse_erl_form(Epp)}.
173
174check_errors([]) ->
175    ok;
176check_errors([{error, Info} | Rest]) ->
177    {Line, Mod, Desc} = Info,
178    case Line of
179	I when is_integer(I) -> ok;
180	{L,C} when is_integer(L), is_integer(C), C >= 1 -> ok
181    end,
182    Str = lists:flatten(Mod:format_error(Desc)),
183    [Str] = io_lib:format("~s", [Str]),
184    check_errors(Rest);
185check_errors([_ | Rest]) ->
186    check_errors(Rest).
187
188
189upcase_mac_1(Config) when is_list(Config) ->
190    File = filename:join(proplists:get_value(data_dir, Config), "mac2.erl"),
191    {ok, List} = epp:parse_file(File, [], []),
192    [_, {attribute, _, plupp, Tuple} | _] = List,
193    Tuple = {1, 1, 3, 3},
194    ok.
195
196upcase_mac_2(Config) when is_list(Config) ->
197    File = filename:join(proplists:get_value(data_dir, Config), "mac2.erl"),
198    {ok, List} = epp:parse_file(File, [], [{p, 5}, {'P', 6}]),
199    [_, {attribute, _, plupp, Tuple} | _] = List,
200    Tuple = {5, 5, 6, 6},
201    ok.
202
203predef_mac(Config) when is_list(Config) ->
204    File = filename:join(proplists:get_value(data_dir, Config), "mac3.erl"),
205    {ok, List} = epp:parse_file(File, [], []),
206    [_,
207     {attribute, Anno, l, Line1},
208     {attribute, _, f, File},
209     {attribute, _, machine1, _},
210     {attribute, _, module, mac3},
211     {attribute, _, m, mac3},
212     {attribute, _, ms, "mac3"},
213     {attribute, _, machine2, _}
214     | _] = List,
215    Line1 = erl_anno:line(Anno),
216    ok.
217
218variable_1(Config) when is_list(Config) ->
219    DataDir = proplists:get_value(data_dir, Config),
220    File = filename:join(DataDir, "variable_1.erl"),
221    true = os:putenv("VAR", DataDir),
222    %% variable_1.erl includes variable_1_include.hrl and
223    %% variable_1_include_dir.hrl.
224    {ok, List} = epp:parse_file(File, [], []),
225    {value, {attribute,_,a,{value1,value2}}} =
226	lists:keysearch(a,3,List),
227    ok.
228
229%% undef without module declaration.
230otp_4870(Config) when is_list(Config) ->
231    Ts = [{otp_4870,
232           <<"-undef(foo).
233           ">>,
234           []}],
235    [] = check(Config, Ts),
236    ok.
237
238%% crashing erl_scan
239otp_4871(Config) when is_list(Config) ->
240    Dir = proplists:get_value(priv_dir, Config),
241    File = filename:join(Dir, "otp_4871.erl"),
242    ok = file:write_file(File, "-module(otp_4871)."),
243    %% Testing crash in erl_scan. Unfortunately there currently is
244    %% no known way to crash erl_scan so it is emulated by killing the
245    %% file io server. This assumes lots of things about how
246    %% the processes are started and how monitors are set up,
247    %% so there are some sanity checks before killing.
248    {ok,Epp} = epp:open(File, []),
249    timer:sleep(1),
250    true = current_module(Epp, epp),
251    {monitored_by,[Io]} = process_info(Epp, monitored_by),
252    true = current_module(Io, file_io_server),
253    exit(Io, emulate_crash),
254    timer:sleep(1),
255    {error,{_Line,epp,cannot_parse}} = otp_4871_parse_file(Epp),
256    epp:close(Epp),
257    ok.
258
259current_module(Pid, Mod) ->
260    {current_function, {Mod, _, _}} = process_info(Pid, current_function),
261    true.
262
263otp_4871_parse_file(Epp) ->
264    case epp:parse_erl_form(Epp) of
265	{ok,_} -> otp_4871_parse_file(Epp);
266	Other -> Other
267    end.
268
269%% OTP-5362. The -file attribute is recognized.
270otp_5362(Config) when is_list(Config) ->
271    Dir = proplists:get_value(priv_dir, Config),
272
273    Copts = [return, strong_validation,{i,Dir}],
274
275    File_Incl = filename:join(Dir, "incl_5362.erl"),
276    File_Incl2 = filename:join(Dir, "incl2_5362.erl"),
277    File_Incl3 = filename:join(Dir, "incl3_5362.erl"),
278    Incl = <<"-module(incl_5362).
279
280              -include(\"incl2_5362.erl\").
281
282              -include_lib(\"incl3_5362.erl\").
283
284              hi(There) -> % line 7
285                   a.
286           ">>,
287    Incl2 = <<"-file(\"some.file\", 100).
288
289               foo(Bar) -> % line 102
290                   foo.
291            ">>,
292    Incl3 = <<"glurk(Foo) -> % line 1
293                  bar.
294            ">>,
295    ok = file:write_file(File_Incl, Incl),
296    ok = file:write_file(File_Incl2, Incl2),
297    ok = file:write_file(File_Incl3, Incl3),
298
299    {ok, incl_5362, InclWarnings} = compile:file(File_Incl, Copts),
300    true = message_compare(
301                   [{File_Incl3,[{{1,1},erl_lint,{unused_function,{glurk,1}}},
302                                 {{1,7},erl_lint,{unused_var,'Foo'}}]},
303                    {File_Incl,[{{7,15},erl_lint,{unused_function,{hi,1}}},
304                                {{7,18},erl_lint,{unused_var,'There'}}]},
305                    {"some.file",[{{102,16},erl_lint,{unused_function,{foo,1}}},
306                                  {{102,20},erl_lint,{unused_var,'Bar'}}]}],
307                   lists:usort(InclWarnings)),
308
309    file:delete(File_Incl),
310    file:delete(File_Incl2),
311    file:delete(File_Incl3),
312
313    %% A -file attribute referring back to the including file.
314    File_Back = filename:join(Dir, "back_5362.erl"),
315    File_Back_hrl = filename:join(Dir, "back_5362.hrl"),
316    Back = <<"-module(back_5362).
317
318              -export([foo/1]).
319
320              -file(?FILE, 1).
321              -include(\"back_5362.hrl\").
322
323              foo(V) -> % line 4
324                  bar.
325              ">>,
326    Back_hrl = [<<"
327                  -file(\"">>,File_Back,<<"\", 2).
328                 ">>],
329
330    ok = file:write_file(File_Back, Back),
331    ok = file:write_file(File_Back_hrl, list_to_binary(Back_hrl)),
332
333    {ok, back_5362, BackWarnings} = compile:file(File_Back, Copts),
334    true = message_compare(
335                   [{File_Back,[{{4,19},erl_lint,{unused_var,'V'}}]}],
336                   BackWarnings),
337    file:delete(File_Back),
338    file:delete(File_Back_hrl),
339
340    %% Set filename but keep line.
341    File_Change = filename:join(Dir, "change_5362.erl"),
342    Change = [<<"-module(change_5362).
343
344                -file(?FILE, 100).
345
346                -export([foo/1,bar/1]).
347
348                -file(\"other.file\", ?LINE). % like an included file...
349                foo(A) -> % line 105
350                    bar.
351
352                -file(\"">>,File_Change,<<"\", 1000).
353
354                bar(B) -> % line 1002
355                    foo.
356              ">>],
357
358    ok = file:write_file(File_Change, list_to_binary(Change)),
359
360    {ok, change_5362, ChangeWarnings} =
361        compile:file(File_Change, Copts),
362    true = message_compare(
363                   [{File_Change,[{{1002,21},erl_lint,{unused_var,'B'}}]},
364                    {"other.file",[{{105,21},erl_lint,{unused_var,'A'}}]}],
365                   lists:usort(ChangeWarnings)),
366
367    file:delete(File_Change),
368
369    %% -file attribute ending with a blank (not a newline).
370    File_Blank = filename:join(Dir, "blank_5362.erl"),
371
372    Blank = <<"-module(blank_5362).
373
374               -export([q/1,a/1,b/1,c/1]).
375
376               -
377               file(?FILE, 18). q(Q) -> foo. % line 18
378
379               a(A) -> % line 20
380                   1.
381
382               -file(?FILE, 42).
383
384               b(B) -> % line 44
385                   2.
386
387               -file(?FILE, ?LINE). c(C) -> % line 47
388                   3.
389            ">>,
390    ok = file:write_file(File_Blank, Blank),
391    {ok, blank_5362, BlankWarnings} = compile:file(File_Blank, Copts),
392    true = message_compare(
393             [{File_Blank,[{{18,3},erl_lint,{unused_var,'Q'}},
394                           {{20,18},erl_lint,{unused_var,'A'}},
395                           {{44,18},erl_lint,{unused_var,'B'}},
396                           {{47,3},erl_lint,{unused_var,'C'}}]}],
397              lists:usort(BlankWarnings)),
398    file:delete(File_Blank),
399
400    %% __FILE__ is set by inclusion and by -file attribute
401    FILE_incl = filename:join(Dir, "file_5362.erl"),
402    FILE_incl1 = filename:join(Dir, "file_incl_5362.erl"),
403    FILE = <<"-module(file_5362).
404
405              -export([ff/0, ii/0]).
406
407              -include(\"file_incl_5362.erl\").
408
409              -file(\"other_file\", 100).
410
411              ff() ->
412                  ?FILE.">>,
413    FILE1 = <<"ii() -> ?FILE.
414              ">>,
415    FILE_Mod = file_5362,
416    ok = file:write_file(FILE_incl, FILE),
417    ok = file:write_file(FILE_incl1, FILE1),
418    FILE_Copts = [return, {i,Dir},{outdir,Dir}],
419    {ok, file_5362, []} = compile:file(FILE_incl, FILE_Copts),
420    AbsFile = filename:rootname(FILE_incl, ".erl"),
421    {module, FILE_Mod} = code:load_abs(AbsFile, FILE_Mod),
422    II = FILE_Mod:ii(),
423    "file_incl_5362.erl" = filename:basename(II),
424    FF = FILE_Mod:ff(),
425    "other_file" = filename:basename(FF),
426    code:purge(file_5362),
427
428    file:delete(FILE_incl),
429    file:delete(FILE_incl1),
430
431    ok.
432
433pmod(Config) when is_list(Config) ->
434    DataDir = proplists:get_value(data_dir, Config),
435    Pmod = filename:join(DataDir, "pmod.erl"),
436    case epp:parse_file([Pmod], [], []) of
437	      {ok,Forms} ->
438		  %% io:format("~p\n", [Forms]),
439		  [] = [F || {error,_}=F <- Forms],
440		  ok
441	  end,
442    ok.
443
444not_circular(Config) when is_list(Config) ->
445    %% Used to generate a compilation error, wrongly saying that it
446    %% was a circular definition.
447
448    Ts = [{circular_1,
449           <<"-define(S(S), ??S).\n"
450             "t() -> \"string\" = ?S(string), ok.\n">>,
451           ok}],
452    [] = run(Config, Ts),
453    ok.
454
455%% Skip some bytes in the beginning of the file.
456skip_header(Config) when is_list(Config) ->
457    PrivDir = proplists:get_value(priv_dir, Config),
458    File = filename:join([PrivDir, "epp_test_skip_header.erl"]),
459    ok = file:write_file(File,
460			       <<"some bytes
461                                  in the beginning of the file
462                                  that should be skipped
463                                  -module(epp_test_skip_header).
464                                  -export([main/1]).
465
466                                  main(_) -> ?MODULE.
467
468                                  ">>),
469    {ok, Fd} = file:open(File, [read]),
470    io:get_line(Fd, ''),
471    io:get_line(Fd, ''),
472    io:get_line(Fd, ''),
473    {ok, Epp} = epp:open([{fd, Fd}, {name, list_to_atom(File)}, {location, 4}]),
474
475    Forms = epp:parse_file(Epp),
476    [] = [Reason || {error, Reason} <- Forms],
477    ok = epp:close(Epp),
478    ok = file:close(Fd),
479
480    ok.
481
482%% ?MODULE before module declaration.
483otp_6277(Config) when is_list(Config) ->
484    Ts = [{otp_6277,
485           <<"-undef(ASSERT).
486              -define(ASSERT, ?MODULE).
487
488              ?ASSERT().">>,
489           [{error,{4,epp,{undefined,'MODULE', none}}}]}],
490    [] = check(Config, Ts),
491    ok.
492
493%% Test -ifdef(MODULE) before module declaration. Should not be
494%% considered defined.
495gh_4995(Config) when is_list(Config) ->
496    Ts = [{gh_4995,
497           <<"-ifdef(MODULE).
498              -record(r, {x = ?MODULE}).
499              -endif.">>,
500           []}],
501    [] = check(Config, Ts),
502    ok.
503
504%% OTP-7702. Wrong line number in stringifying macro expansion.
505otp_7702(Config) when is_list(Config) ->
506    Dir = proplists:get_value(priv_dir, Config),
507    File = filename:join(Dir, "file_7702.erl"),
508    Contents = <<"-module(file_7702).
509
510                  -export([t/0]).
511
512                  -define(RECEIVE(Msg,Body),
513                       receive
514                           Msg -> Body;
515                           M ->
516                exit({unexpected_message,M,on_line,?LINE,was_expecting,??Msg})
517                       after 10000 ->
518                            exit({timeout,on_line,?LINE,was_expecting,??Msg})
519                       end).
520                   t() ->
521                       ?RECEIVE(foo, bar).">>,
522    ok = file:write_file(File, Contents),
523    {ok, file_7702, []} =
524        compile:file(File, [debug_info,return,{outdir,Dir}]),
525
526    BeamFile = filename:join(Dir, "file_7702.beam"),
527    {ok, AC} = beam_lib:chunks(BeamFile, [abstract_code]),
528
529    {file_7702,[{abstract_code,{_,Forms}}]} = AC,
530    Forms2 = unopaque_forms(Forms),
531        [{attribute,{1,1},file,_},
532         _,
533         _,
534         {function,_,t,0,
535          [{clause,_,[],[],
536            [{'receive',{14,25},
537              [_,
538               {clause,{14,38},
539                [{var,{14,38},'M'}],
540                [],
541                [{_,_,_,
542                  [{tuple,{14,38},
543                    [{atom,{14,38},unexpected_message},
544                     {var,{14,38},'M'},
545                     {atom,{14,38},on_line},
546                     {integer,{14,38},14},
547                     {atom,{14,38},was_expecting},
548                     {string,{14,38},"foo"}]}]}]}],
549              {integer,{14,38},10000},
550              [{call,{14,38},
551                {atom,{14,38},exit},
552                [{tuple,{14,38},
553                  [{atom,{14,38},timeout},
554                   {atom,{14,38},on_line},
555                   {integer,{14,38},14},
556                   {atom,{14,38},was_expecting},
557                   {string,{14,38},"foo"}]}]}]}]}]},
558         {eof,{14,43}}] = Forms2,
559
560    file:delete(File),
561    file:delete(BeamFile),
562
563    ok.
564
565%% OTP-8130. Misc tests.
566otp_8130(Config) when is_list(Config) ->
567    true = os:putenv("epp_inc1", "stdlib"),
568    Ts = [{otp_8130_1,
569           <<"-define(M(A), ??A). "
570             "t() ->  "
571             "   L = \"{ 34 , \\\"1\\\\x{AAA}\\\" , \\\"34\\\" , X . a , $\\\\x{AAA} }\", "
572             "   R = ?M({34,\"1\\x{aaa}\",\"34\",X.a,$\\x{aaa}}),"
573             "   Lt = erl_scan:string(L, 1),"
574             "   Rt = erl_scan:string(R, 1),"
575             "   Lt = Rt, ok. ">>,
576          ok},
577
578          {otp_8130_2,
579           <<"-define(M(A), ??B). "
580             "t() -> B = 18, 18 = ?M(34), ok. ">>,
581           ok},
582
583          {otp_8130_2a,
584           <<"-define(m(A), ??B). "
585             "t() -> B = 18, 18 = ?m(34), ok. ">>,
586           ok},
587
588          {otp_8130_3,
589           <<"-define(M1(A, B), {A,B}).\n"
590             "t0() -> 1.\n"
591             "t() ->\n"
592             "   {2,7} =\n"
593             "      ?M1(begin 1 = fun() -> 1 end(),\n" % Bug -R13B01
594             "                2 end,\n"
595             "          7),\n"
596             "   {2,7} =\n"
597             "      ?M1(begin 1 = fun _Name () -> 1 end(),\n"
598             "                2 end,\n"
599             "          7),\n"
600             "   {2,7} =\n"
601             "      ?M1(begin 1 = fun t0/0(),\n"
602             "                2 end,\n"
603             "          7),\n"
604             "   {2,7} =\n"
605             "      ?M1(begin 2 = byte_size(<<\"34\">>),\n"
606             "                2 end,\n"
607             "          7),\n"
608             "   R2 = math:sqrt(2.0),\n"
609             "   {2,7} =\n"
610             "      ?M1(begin yes = if R2 > 1 -> yes end,\n"
611             "                2 end,\n"
612             "          7),\n"
613             "   {2,7} =\n"
614             "      ?M1(begin yes = case R2 > 1  of true -> yes end,\n"
615             "                2 end,\n"
616             "          7),\n"
617             "   {2,7} =\n"
618             "      ?M1(begin yes = receive 1 -> 2 after 0 -> yes end,\n"
619             "                2 end,\n"
620             "          7),\n"
621             "   {2,7} =\n"
622             "      ?M1(begin yes = try 1 of 1 -> yes after foo end,\n"
623             "                2 end,\n"
624             "          7),\n"
625             "   {[42],7} =\n"
626             "      ?M1([42],\n"
627             "          7),\n"
628             "ok.\n">>,
629           ok},
630
631          {otp_8130_4,
632           <<"-define(M3(), A).\n"
633             "t() -> A = 1, ?M3(), ok.\n">>,
634           ok},
635
636          {otp_8130_5,
637           <<"-include_lib(\"$epp_inc1/include/qlc.hrl\").\n"
638             "t() -> [1] = qlc:e(qlc:q([X || X <- [1]])), ok.\n">>,
639           ok},
640
641          {otp_8130_6,
642           <<"-include_lib(\"kernel/include/file.hrl\").\n"
643             "t() -> 14 = (#file_info{size = 14})#file_info.size, ok.\n">>,
644           ok},
645
646          {otp_8130_7_new,
647           <<"-record(b, {b}).\n"
648             "-define(A, {{a,#b.b).\n"
649             "t() -> {{a,2}} = ?A}}, ok.">>,
650           ok},
651
652          {otp_8130_8,
653           <<"\n-define(A(B), B).\n"
654             "-undef(A).\n"
655             "-define(A, ok).\n"
656             "t() -> ?A.\n">>,
657           ok},
658          {otp_8130_9,
659           <<"-define(a, 1).\n"
660             "-define(b, {?a,?a}).\n"
661             "t() -> ?b.\n">>,
662           {1,1}}
663
664         ],
665    [] = run(Config, Ts),
666
667    Cs = [{otp_8130_c1,
668           <<"-define(M1(A), if\n"
669             "A =:= 1 -> B;\n"
670             "true -> 2\n"
671             "end).\n"
672            "t() -> {?M1(1), ?M1(2)}. \n">>,
673           {errors,[{{5,13},erl_lint,{unbound_var,'B'}},
674                    {{5,21},erl_lint,{unbound_var,'B'}}],
675            []}},
676
677          {otp_8130_c2,
678           <<"-define(M(A), A).\n"
679             "t() -> ?M(1\n">>,
680           {errors,[{{2,9},epp,{arg_error,'M'}}],[]}},
681
682          {otp_8130_c3,
683           <<"-define(M(A), A).\n"
684             "t() -> ?M.\n">>,
685           {errors,[{{2,9},epp,{mismatch,'M'}}],[]}},
686
687          {otp_8130_c4,
688           <<"-define(M(A), A).\n"
689             "t() -> ?M(1, 2).\n">>,
690           {errors,[{{2,9},epp,{mismatch,'M'}}],[]}},
691
692          {otp_8130_c5,
693           <<"-define(M(A), A).\n"
694             "t() -> ?M().\n">>,
695           {errors,[{{2,9},epp,{mismatch,'M'}}],[]}},
696
697          {otp_8130_c6,
698           <<"-define(M3(), A).\n"
699             "t() -> A = 1, ?3.14159}.\n">>,
700           {errors,[{{2,16},epp,{call,[$?,"3.14159"]}}],[]}},
701
702          {otp_8130_c7,
703           <<"\nt() -> ?A.\n">>,
704           {errors,[{{2,9},epp,{undefined,'A', none}}],[]}},
705
706          {otp_8130_c8,
707           <<"\n-include_lib(\"$apa/foo.hrl\").\n">>,
708           {errors,[{{2,14},epp,{include,lib,"$apa/foo.hrl"}}],[]}},
709
710
711          {otp_8130_c9a,
712           <<"-define(S, ?S).\n"
713             "t() -> ?S.\n">>,
714           {errors,[{{2,9},epp,{circular,'S', none}}],[]}},
715
716          {otp_8130_c9b,
717           <<"-define(S(), ?S()).\n"
718             "t() -> ?S().\n">>,
719           {errors,[{{2,9},epp,{circular,'S', 0}}],[]}},
720
721          {otp_8130_c10,
722           <<"\n-file.">>,
723           {errors,[{{2,6},epp,{bad,file}}],[]}},
724
725          {otp_8130_c11,
726           <<"\n-include_lib 92.">>,
727           {errors,[{{2,14},epp,{bad,include_lib}}],[]}},
728
729          {otp_8130_c12,
730           <<"\n-include_lib(\"kernel/include/fopp.hrl\").\n">>,
731           {errors,[{{2,14},epp,{include,lib,"kernel/include/fopp.hrl"}}],[]}},
732
733          {otp_8130_c13,
734           <<"\n-include(foo).\n">>,
735           {errors,[{{2,10},epp,{bad,include}}],[]}},
736
737          {otp_8130_c14,
738           <<"\n-undef({foo}).\n">>,
739           {errors,[{{2,8},epp,{bad,undef}}],[]}},
740
741          {otp_8130_c15,
742           <<"\n-define(a, 1).\n"
743            "-define(a, 1).\n">>,
744           {errors,[{{3,9},epp,{redefine,a}}],[]}},
745
746          {otp_8130_c16,
747           <<"\n-define(A, 1).\n"
748            "-define(A, 1).\n">>,
749           {errors,[{{3,9},epp,{redefine,'A'}}],[]}},
750
751          {otp_8130_c17,
752           <<"\n-define(A(B), B).\n"
753            "-define(A, 1).\n">>,
754           []},
755
756          {otp_8130_c18,
757           <<"\n-define(A, 1).\n"
758            "-define(A(B), B).\n">>,
759           []},
760
761          {otp_8130_c19,
762           <<"\n-define(a(B), B).\n"
763            "-define(a, 1).\n">>,
764           []},
765
766          {otp_8130_c20,
767           <<"\n-define(a, 1).\n"
768            "-define(a(B), B).\n">>,
769           []},
770
771          {otp_8130_c21,
772           <<"\n-define(A(B, B), B).\n">>,
773           {errors,[{{2,14},epp,{duplicated_argument,'B'}}],[]}},
774
775          {otp_8130_c22,
776           <<"\n-define(a(B, B), B).\n">>,
777           {errors,[{{2,14},epp,{duplicated_argument,'B'}}],[]}},
778
779          {otp_8130_c23,
780           <<"\n-file(?b, 3).\n">>,
781           {errors,[{{2,8},epp,{undefined,b, none}}],[]}},
782
783          {otp_8130_c24,
784           <<"\n-include(\"no such file.erl\").\n">>,
785           {errors,[{{2,10},epp,{include,file,"no such file.erl"}}],[]}},
786
787          {otp_8130_c25,
788           <<"\n-define(A.\n">>,
789           {errors,[{{2,10},epp,{bad,define}}],[]}},
790
791          {otp_8130_7,
792           <<"-record(b, {b}).\n"
793             "-define(A, {{a,#b.b.\n"
794             "t() -> {{a,2}} = ?A}}, ok.">>,
795           {errors,[{{2,20},epp,missing_parenthesis},
796                    {{3,19},epp,{undefined,'A',none}}],[]}}
797
798          ],
799    [] = compile(Config, Cs),
800
801    Cks = [{otp_check_1,
802            <<"\n-include_lib(\"epp_test.erl\").\n">>,
803            [{error,{2,epp,{depth,"include_lib"}}}]},
804
805           {otp_check_2,
806            <<"\n-include(\"epp_test.erl\").\n">>,
807            [{error,{2,epp,{depth,"include"}}}]}
808           ],
809    [] = check(Config, Cks),
810
811    Dir = proplists:get_value(priv_dir, Config),
812    File = filename:join(Dir, "otp_8130.erl"),
813    ok = file:write_file(File,
814                               "-module(otp_8130).\n"
815                               "-define(a, 3.14).\n"
816                               "t() -> ?a.\n"),
817    {ok,Epp} = epp:open(File, []),
818    PreDefMacs = macs(Epp),
819    ['BASE_MODULE','BASE_MODULE_STRING','BEAM','FILE',
820     'FUNCTION_ARITY','FUNCTION_NAME',
821     'LINE','MACHINE','MODULE','MODULE_STRING',
822     'OTP_RELEASE'] = PreDefMacs,
823    {ok,[{'-',_},{atom,_,file}|_]} = epp:scan_erl_form(Epp),
824    {ok,[{'-',_},{atom,_,module}|_]} = epp:scan_erl_form(Epp),
825    {ok,[{atom,_,t}|_]} = epp:scan_erl_form(Epp),
826    {eof,_} = epp:scan_erl_form(Epp),
827    [a] = macs(Epp) -- PreDefMacs,
828    epp:close(Epp),
829
830    %% escript
831    ModuleStr = "any_name",
832    Module = list_to_atom(ModuleStr),
833    fun() ->
834            PreDefMacros = [{'MODULE', Module, redefine},
835                            {'MODULE_STRING', ModuleStr, redefine},
836                            a, {b,2}],
837            {ok,Epp2} = epp:open(File, [], PreDefMacros),
838            [{atom,_,true}] = macro(Epp2, a),
839            [{integer,_,2}] = macro(Epp2, b),
840            false = macro(Epp2, c),
841            epp:close(Epp2)
842    end(),
843    fun() ->
844            PreDefMacros = [{a,b,c}],
845            {error,{bad,{a,b,c}}} = epp:open(File, [], PreDefMacros)
846    end(),
847    fun() ->
848            PreDefMacros = [a, {a,1}],
849            {error,{redefine,a}} = epp:open(File, [], PreDefMacros)
850    end(),
851    fun() ->
852            PreDefMacros = [{a,1},a],
853            {error,{redefine,a}} = epp:open(File, [], PreDefMacros)
854    end(),
855
856    {error,enoent} = epp:open("no such file", []),
857    {error,enoent} = epp:parse_file("no such file", [], []),
858
859    _ = ifdef(Config),
860
861    ok.
862
863scan_file(Config) when is_list(Config) ->
864    DataDir = proplists:get_value(data_dir, Config),
865    File = filename:join(DataDir, "source_name.erl"),
866
867    {ok, Toks, [{encoding, _}]} = epp:scan_file(File, []),
868    [FileForm1, ModuleForm, ExportForm,
869     FileForm2, FileForm3, FunctionForm,
870     {eof,_}] = Toks,
871    [{'-',_}, {atom,_,file}, {'(',_} | _ ] = FileForm1,
872    [{'-',_}, {atom,_,module}, {'(',_} | _ ] = ModuleForm,
873    [{'-',_}, {atom,_,export}, {'(',_} | _ ] = ExportForm,
874    [{'-',_}, {atom,_,file}, {'(',_} | _ ] = FileForm2,
875    [{'-',_}, {atom,_,file}, {'(',_} | _ ] = FileForm3,
876    ok.
877
878macs(Epp) ->
879    Macros = epp:macro_defs(Epp), % not documented
880    lists:sort([MName || {{atom,MName},_} <- Macros]).
881
882macro(Epp, N) ->
883    case lists:keyfind({atom,N}, 1, epp:macro_defs(Epp)) of
884        false -> false;
885        {{atom,N},{_,V}} -> V;
886        {{atom,N},Defs} -> lists:append([V || {_,{_,V}} <- Defs])
887    end.
888
889ifdef(Config) ->
890    Cs = [{ifdef_c1,
891           <<"-ifdef(a).\n"
892             "a bug.\n"
893             "-else.\n"
894             "-ifdef(A).\n"
895             "a bug.\n"
896             "-endif.\n"
897             "-else.\n"
898             "t() -> ok.\n"
899             "-endif.">>,
900           {errors,[{{7,2},epp,{illegal,"repeated",'else'}}],[]}},
901
902          {ifdef_c2,
903           <<"-define(a, true).\n"
904             "-ifdef(a).\n"
905             "a bug.\n"
906             "-endif.">>,
907           {errors,[{{3,3},erl_parse,["syntax error before: ","bug"]}],[]}},
908
909          {ifdef_c3,
910           <<"-define(a, true).\n"
911             "-ifdef(a).\n"
912             "-endif">>,
913
914           {errors,[{{3,2},epp,{bad,endif}},
915                    {{3,7},epp,{illegal,"unterminated",ifdef}}],
916          []}},
917
918          {ifdef_c4,
919           <<"\n-ifdef a.\n"
920             "-endif.\n">>,
921           {errors,[{{2,8},epp,{bad,ifdef}}],[]}},
922
923          {ifdef_c5,
924           <<"-ifdef(a).\n"
925             "-else.\n"
926             "-endif.\n"
927             "-endif.\n">>,
928           {errors,[{{4,2},epp,{illegal,"unbalanced",endif}}],[]}},
929
930          {ifdef_c6,
931           <<"-ifdef(a).\n"
932             "-else.\n"
933             "-endif.\n"
934             "-else.\n">>,
935           {errors,[{{4,2},epp,{illegal,"unbalanced",'else'}}],[]}},
936
937          {ifdef_c7,
938           <<"-ifndef(a).\n"
939             "-else\n"
940             "foo bar\n"
941             "-else.\n"
942             "t() -> a.\n"
943             "-endif.\n">>,
944           {errors,[{{3,1},epp,{bad,else}}],[]}},
945
946          {ifdef_c8,
947           <<"-ifdef(a).\n"
948              "-foo bar.">>,
949           {errors,[{{2,10},epp,{illegal,"unterminated",ifdef}}],[]}},
950
951          {ifdef_c9,
952           <<"-ifdef(a).\n"
953              "3.3e12000.\n"
954              "-endif.\n">>,
955           []},
956
957          {ifdef_c10,
958           <<"\nt() -> 3.3e12000.\n">>,
959           {errors,[{{2,8},erl_scan,{illegal,float}},
960                    {{2,17},erl_parse,["syntax error before: ","'.'"]}], % ...
961            []}},
962
963          {ifndef_c1,
964           <<"-ifndef(a).\n"
965             "-ifndef(A).\n"
966             "t() -> ok.\n"
967             "-endif.\n"
968             "-else.\n"
969             "a bug.\n"
970             "-else.\n"
971             "a bug.\n"
972             "-endif.">>,
973           {errors,[{{7,2},epp,{illegal,"repeated",'else'}}],[]}},
974
975          {ifndef_c3,
976           <<"-ifndef(a).\n"
977             "-endif">>,
978
979           {errors,[{{2,2},epp,{bad,endif}},
980                    {{2,7},epp,{illegal,"unterminated",ifndef}}],
981          []}},
982
983          {ifndef_c4,
984           <<"\n-ifndef a.\n"
985             "-endif.\n">>,
986           {errors,[{{2,9},epp,{bad,ifndef}}],[]}},
987
988          {define_c5,
989           <<"-\ndefine a.\n">>,
990           {errors,[{{2,8},epp,{bad,define}}],[]}}
991          ],
992    [] = compile(Config, Cs),
993
994    Ts =  [{ifdef_1,
995            <<"-ifdef(a).\n"
996              "a bug.\n"
997              "-else.\n"
998              "-ifdef(A).\n"
999              "a bug.\n"
1000              "-endif.\n"
1001              "t() -> ok.\n"
1002              "-endif.">>,
1003           ok},
1004
1005           {ifdef_2,
1006            <<"-define(a, true).\n"
1007              "-ifdef(a).\n"
1008              "-define(A, true).\n"
1009              "-ifdef(A).\n"
1010              "t() -> ok.\n"
1011              "-else.\n"
1012              "a bug.\n"
1013              "-endif.\n"
1014              "-else.\n"
1015              "a bug.\n"
1016              "-endif.">>,
1017           ok},
1018
1019           {ifdef_3,
1020            <<"\n-define(a, true).\n"
1021              "-ifndef(a).\n"
1022              "a bug.\n"
1023              "-else.\n"
1024              "-define(A, true).\n"
1025              "-ifndef(A).\n"
1026              "a bug.\n"
1027              "-else.\n"
1028              "t() -> ok.\n"
1029              "-endif.\n"
1030              "-endif.">>,
1031           ok},
1032
1033           {ifdef_4,
1034                       <<"-ifdef(a).\n"
1035              "a bug.\n"
1036              "-ifdef(a).\n"
1037               "a bug.\n"
1038              "-else.\n"
1039              "-endif.\n"
1040             "-ifdef(A).\n"
1041              "a bug.\n"
1042             "-endif.\n"
1043             "-else.\n"
1044             "t() -> ok.\n"
1045             "-endif.">>,
1046            ok},
1047
1048           {ifdef_5,
1049           <<"-ifdef(a).\n"
1050              "-ifndef(A).\n"
1051              "a bug.\n"
1052              "-else.\n"
1053              "-endif.\n"
1054             "a bug.\n"
1055             "-else.\n"
1056              "t() -> ok.\n"
1057             "-endif.">>,
1058            ok},
1059
1060           {ifdef_6,
1061           <<"-ifdef(a).\n"
1062              "-if(A).\n"
1063              "a bug.\n"
1064              "-else.\n"
1065              "-endif.\n"
1066             "a bug.\n"
1067             "-else.\n"
1068              "t() -> ok.\n"
1069             "-endif.">>,
1070            ok}
1071
1072           ],
1073    [] = run(Config, Ts).
1074
1075%% OTP-12847: Test the -error directive.
1076test_error(Config) ->
1077    Cs = [{error_c1,
1078           <<"-error(\"string and macro: \" ?MODULE_STRING).\n"
1079	     "-ifdef(NOT_DEFINED).\n"
1080	     " -error(\"this one will be skipped\").\n"
1081	     "-endif.\n">>,
1082           {errors,[{{1,21},epp,{error,"string and macro: epp_test"}}],[]}},
1083
1084	  {error_c2,
1085	   <<"-ifdef(CONFIG_A).\n"
1086	     " t() -> a.\n"
1087	     "-else.\n"
1088	     "-ifdef(CONFIG_B).\n"
1089	     " t() -> b.\n"
1090	     "-else.\n"
1091	     "-error(\"Neither CONFIG_A nor CONFIG_B are available\").\n"
1092	     "-endif.\n"
1093	     "-endif.\n">>,
1094	   {errors,[{{7,2},epp,{error,"Neither CONFIG_A nor CONFIG_B are available"}}],[]}},
1095
1096	  {error_c3,
1097	   <<"-error(a b c).\n">>,
1098	   {errors,[{{1,21},epp,{bad,error}}],[]}}
1099
1100	 ],
1101
1102    [] = compile(Config, Cs),
1103    ok.
1104
1105%% OTP-12847: Test the -warning directive.
1106test_warning(Config) ->
1107    Cs = [{warn_c1,
1108           <<"-warning({a,term,?MODULE}).\n"
1109	     "-ifdef(NOT_DEFINED).\n"
1110	     "-warning(\"this one will be skipped\").\n"
1111	     "-endif.\n">>,
1112           {warnings,[{{1,21},epp,{warning,{a,term,epp_test}}}]}},
1113
1114	  {warn_c2,
1115	   <<"-ifdef(CONFIG_A).\n"
1116	     " t() -> a.\n"
1117	     "-else.\n"
1118	     "-ifdef(CONFIG_B).\n"
1119	     " t() -> b.\n"
1120	     "-else.\n"
1121	     " t() -> c.\n"
1122	     "-warning(\"Using fallback\").\n"
1123	     "-endif.\n"
1124	     "-endif.\n">>,
1125	   {warnings,[{{8,2},epp,{warning,"Using fallback"}}]}},
1126
1127	  {warn_c3,
1128	   <<"-warning(a b c).\n">>,
1129	   {errors,[{{1,21},epp,{bad,warning}}],[]}}
1130	 ],
1131
1132    [] = compile(Config, Cs),
1133    ok.
1134
1135%% OTP-12847: Test the -if and -elif directives and the built-in
1136%% function defined(Symbol).
1137test_if(Config) ->
1138    Cs = [{if_1c,
1139	   <<"-if.\n"
1140	     "-endif.\n"
1141	     "-if no_parentheses.\n"
1142	     "-endif.\n"
1143	     "-if(syntax error.\n"
1144	     "-endif.\n"
1145	     "-if(true).\n"
1146	     "-if(a+3).\n"
1147	     "syntax error not triggered here.\n"
1148	     "-endif.\n">>,
1149           {errors,[{{1,23},epp,{bad,'if'}},
1150		    {{3,5},epp,{bad,'if'}},
1151		    {{5,12},erl_parse,["syntax error before: ","error"]},
1152		    {{11,1},epp,{illegal,"unterminated",'if'}}],
1153	    []}},
1154
1155	  {if_2c,			       	%Bad guard expressions.
1156	   <<"-if(is_list(integer_to_list(42))).\n" %Not guard BIF.
1157	     "-endif.\n"
1158	     "-if(begin true end).\n"
1159	     "-endif.\n">>,
1160	   {errors,[{{1,21},epp,{bad,'if'}},
1161		    {{3,2},epp,{bad,'if'}}],
1162	    []}},
1163
1164	  {if_3c,			       	%Invalid use of defined/1.
1165	   <<"-if defined(42).\n"
1166	     "-endif.\n">>,
1167	   {errors,[{{1,24},epp,{bad,'if'}}],[]}},
1168
1169	  {if_4c,
1170	   <<"-elif OTP_RELEASE > 18.\n">>,
1171	   {errors,[{{1,21},epp,{illegal,"unbalanced",'elif'}}],[]}},
1172
1173	  {if_5c,
1174	   <<"-ifdef(not_defined_today).\n"
1175	     "-else.\n"
1176	     "-elif OTP_RELEASE > 18.\n"
1177	     "-endif.\n">>,
1178	   {errors,[{{3,2},epp,{illegal,"unbalanced",'elif'}}],[]}},
1179
1180	  {if_6c,
1181	   <<"-if(defined(OTP_RELEASE)).\n"
1182	     "-else.\n"
1183	     "-elif(true).\n"
1184	     "-endif.\n">>,
1185	   {errors,[{{3,2},epp,elif_after_else}],[]}},
1186
1187	  {if_7c,
1188	   <<"-if(begin true end).\n"		%Not a guard expression.
1189	     "-endif.\n">>,
1190	   {errors,[{{1,21},epp,{bad,'if'}}],[]}},
1191
1192	  {if_8c,
1193	   <<"-if(?foo).\n"                     %Undefined symbol.
1194	     "-endif.\n">>,
1195	   {errors,[{{1,25},epp,{undefined,foo,none}}],[]}}
1196
1197	 ],
1198    [] = compile(Config, Cs),
1199
1200    Ts = [{if_1,
1201	   <<"-if(?OTP_RELEASE > 18).\n"
1202	     "t() -> ok.\n"
1203	     "-else.\n"
1204	     "a bug.\n"
1205	     "-endif.\n">>,
1206           ok},
1207
1208	  {if_2,
1209	   <<"-if(false).\n"
1210	     "a bug.\n"
1211	     "-elif(?OTP_RELEASE > 18).\n"
1212	     "t() -> ok.\n"
1213	     "-else.\n"
1214	     "a bug.\n"
1215	     "-endif.\n">>,
1216           ok},
1217
1218	  {if_3,
1219	   <<"-if(true).\n"
1220	     "t() -> ok.\n"
1221	     "-elif(?OTP_RELEASE > 18).\n"
1222	     "a bug.\n"
1223	     "-else.\n"
1224	     "a bug.\n"
1225	     "-endif.\n">>,
1226           ok},
1227
1228	  {if_4,
1229	   <<"-define(a, 1).\n"
1230	     "-if(defined(a) andalso defined(OTP_RELEASE)).\n"
1231	     "t() -> ok.\n"
1232	     "-else.\n"
1233	     "a bug.\n"
1234	     "-endif.\n">>,
1235           ok},
1236
1237	  {if_5,
1238	   <<"-if(defined(a)).\n"
1239	     "a bug.\n"
1240	     "-else.\n"
1241	     "t() -> ok.\n"
1242	     "-endif.\n">>,
1243           ok},
1244
1245	  {if_6,
1246	   <<"-if(defined(not_defined_today)).\n"
1247	     " -if(true).\n"
1248	     "  bug1.\n"
1249	     " -elif(true).\n"
1250	     "  bug2.\n"
1251	     " -elif(true).\n"
1252	     "  bug3.\n"
1253	     " -else.\n"
1254	     "  bug4.\n"
1255	     " -endif.\n"
1256	     "-else.\n"
1257	     "t() -> ok.\n"
1258	     "-endif.\n">>,
1259           ok},
1260
1261	  {if_7,
1262	   <<"-if(not_builtin()).\n"
1263	     "a bug.\n"
1264	     "-else.\n"
1265	     "t() -> ok.\n"
1266	     "-endif.\n">>,
1267           ok},
1268
1269	  {if_8,
1270	   <<"-if(42).\n"			%Not boolean.
1271	     "a bug.\n"
1272	     "-else.\n"
1273	     "t() -> ok.\n"
1274	     "-endif.\n">>,
1275	   ok}
1276	 ],
1277    [] = run(Config, Ts),
1278
1279    ok.
1280
1281%% Advanced test on overloading macros.
1282overload_mac(Config) when is_list(Config) ->
1283    Cs = [
1284          %% '-undef' removes all definitions of a macro
1285          {overload_mac_c1,
1286           <<"-define(A, a).\n"
1287            "-define(A(X), X).\n"
1288            "-undef(A).\n"
1289            "t1() -> ?A.\n",
1290            "t2() -> ?A(1).">>,
1291           {errors,[{{4,10},epp,{undefined,'A', none}},
1292                    {{5,10},epp,{undefined,'A', 1}}],[]}},
1293
1294          %% cannot overload predefined macros
1295          {overload_mac_c2,
1296           <<"\n-define(MODULE(X), X).">>,
1297           {errors,[{{2,9},epp,{redefine_predef,'MODULE'}}],[]}},
1298
1299          %% cannot overload macros with same arity
1300          {overload_mac_c3,
1301           <<"-define(A(X), X).\n"
1302            "-define(A(Y), Y).">>,
1303           {errors,[{{2,9},epp,{redefine,'A'}}],[]}},
1304
1305          {overload_mac_c4,
1306           <<"-define(A, a).\n"
1307            "-define(A(X,Y), {X,Y}).\n"
1308            "a(X) -> X.\n"
1309            "t() -> ?A(1).">>,
1310           {errors,[{{4,9},epp,{mismatch,'A'}}],[]}}
1311         ],
1312    [] = compile(Config, Cs),
1313
1314    Ts = [
1315          {overload_mac_r1,
1316           <<"-define(A, 1).\n"
1317            "-define(A(X), X).\n"
1318            "-define(A(X, Y), {X, Y}).\n"
1319            "t() -> {?A, ?A(2), ?A(3, 4)}.">>,
1320           {1, 2, {3, 4}}},
1321
1322          {overload_mac_r2,
1323           <<"-define(A, 1).\n"
1324            "-define(A(X), X).\n"
1325            "t() -> ?A(?A).">>,
1326           1},
1327
1328          {overload_mac_r3,
1329           <<"-define(A, ?B).\n"
1330            "-define(B, a).\n"
1331            "-define(B(X), {b,X}).\n"
1332            "a(X) -> X.\n"
1333            "t() -> ?A(1).">>,
1334           1}
1335          ],
1336    [] = run(Config, Ts).
1337
1338
1339%% OTP-8388. More tests on overloaded macros.
1340otp_8388(Config) when is_list(Config) ->
1341    Dir = proplists:get_value(priv_dir, Config),
1342    File = filename:join(Dir, "otp_8388.erl"),
1343    ok = file:write_file(File, <<"-module(otp_8388)."
1344                                       "-define(LINE, a).">>),
1345    fun() ->
1346            PreDefMacros = [{'LINE', a}],
1347            {error,{redefine_predef,'LINE'}} =
1348                epp:open(File, [], PreDefMacros)
1349    end(),
1350
1351    fun() ->
1352            PreDefMacros = ['LINE'],
1353            {error,{redefine_predef,'LINE'}} =
1354                epp:open(File, [], PreDefMacros)
1355    end(),
1356
1357    Ts = [
1358          {macro_1,
1359           <<"-define(m(A), A).\n"
1360             "t() -> ?m(,).\n">>,
1361           {errors,[{{2,9},epp,{arg_error,m}}],[]}},
1362          {macro_2,
1363           <<"-define(m(A), A).\n"
1364             "t() -> ?m(a,).\n">>,
1365           {errors,[{{2,9},epp,{arg_error,m}}],[]}},
1366          {macro_3,
1367           <<"\n-define(LINE, a).\n">>,
1368           {errors,[{{2,9},epp,{redefine_predef,'LINE'}}],[]}},
1369          {macro_4,
1370           <<"-define(A(B, C, D), {B,C,D}).\n"
1371             "t() -> ?A(a,,3).\n">>,
1372           {errors,[{{2,9},epp,{mismatch,'A'}}],[]}},
1373          {macro_5,
1374           <<"-define(Q, {?F0(), ?F1(,,4)}).\n">>,
1375           {errors,[{{1,40},epp,{arg_error,'F1'}}],[]}},
1376          {macro_6,
1377           <<"-define(FOO(X), ?BAR(X)).\n"
1378             "-define(BAR(X), ?FOO(X)).\n"
1379             "-undef(FOO).\n"
1380             "test() -> ?BAR(1).\n">>,
1381           {errors,[{{4,12},epp,{undefined,'FOO',1}}],[]}}
1382         ],
1383    [] = compile(Config, Ts),
1384    ok.
1385
1386%% OTP-8470. Bugfix (one request - two replies).
1387otp_8470(Config) when is_list(Config) ->
1388    Dir = proplists:get_value(priv_dir, Config),
1389    C = <<"-file(\"erl_parse.yrl\", 486).\n"
1390          "-file(\"erl_parse.yrl\", 488).\n">>,
1391    File = filename:join(Dir, "otp_8470.erl"),
1392    ok = file:write_file(File, C),
1393    {ok, _List} = epp:parse_file(File, [], []),
1394    file:delete(File),
1395    receive _ -> fail() after 0 -> ok end,
1396    ok.
1397
1398%% OTP-8562. Record with no fields is considered typed.
1399otp_8562(Config) when is_list(Config) ->
1400    Cs = [{otp_8562,
1401           <<"\n-define(P(), {a,b}.\n"
1402             "-define(P3, .\n">>,
1403           {errors,[{{2,19},epp,missing_parenthesis},
1404                    {{3,13},epp,missing_parenthesis}], []}}
1405         ],
1406    [] = compile(Config, Cs),
1407    ok.
1408
1409%% OTP-8911. -file and file inclusion bug.
1410otp_8911(Config) when is_list(Config) ->
1411    case test_server:is_cover() of
1412	true ->
1413	    {skip, "Testing cover, so cannot run when cover is already running"};
1414	false ->
1415	    do_otp_8911(Config)
1416    end.
1417do_otp_8911(Config) ->
1418    {ok, CWD} = file:get_cwd(),
1419    ok = file:set_cwd(proplists:get_value(priv_dir, Config)),
1420
1421    File = "i.erl",
1422    Cont = <<"-module(i).
1423              -export([t/0]).
1424              -file(\"fil1\", 100).
1425              -include(\"i1.erl\").
1426              t() ->
1427                  a.
1428           ">>,
1429    ok = file:write_file(File, Cont),
1430    Incl = <<"-file(\"fil2\", 35).
1431              t1() ->
1432                  b.
1433           ">>,
1434    File1 = "i1.erl",
1435    ok = file:write_file(File1, Incl),
1436
1437    {ok, i} = cover:compile(File),
1438    a = i:t(),
1439    {ok,[{{i,6},1}]} = cover:analyse(i, calls, line),
1440    cover:stop(),
1441
1442    file:delete(File),
1443    file:delete(File1),
1444    file:set_cwd(CWD),
1445    ok.
1446
1447%% OTP-8665. Bugfix premature end.
1448otp_8665(Config) when is_list(Config) ->
1449    Cs = [{otp_8665,
1450           <<"\n-define(A, a)\n">>,
1451           {errors,[{{2,13},epp,premature_end}],[]}}
1452         ],
1453    [] = compile(Config, Cs),
1454    ok.
1455
1456%% OTP-10302. Unicode characters scanner/parser.
1457otp_10302(Config) when is_list(Config) ->
1458    %% Two messages (one too many). Keeps otp_4871 happy.
1459    Cs = [{otp_10302,
1460           <<"%% coding: utf-8\n \n \x{E4}">>,
1461           {errors,[{{3,1},epp,cannot_parse},
1462                    {{3,1},file_io_server,invalid_unicode}],[]}}
1463         ],
1464    [] = compile(Config, Cs),
1465    Dir = proplists:get_value(priv_dir, Config),
1466    File = filename:join(Dir, "otp_10302.erl"),
1467    utf8 = encoding("coding: utf-8", File),
1468    utf8 = encoding("coding: UTF-8", File),
1469    latin1 = encoding("coding: Latin-1", File),
1470    latin1 = encoding("coding: latin-1", File),
1471    none = encoding_com("coding: utf-8", File),
1472    none = encoding_com("\n\n%% coding: utf-8", File),
1473    none = encoding_nocom("\n\n coding: utf-8", File),
1474    utf8 = encoding_com("\n%% coding: utf-8", File),
1475    utf8 = encoding_nocom("\n coding: utf-8", File),
1476    none = encoding("coding: \nutf-8", File),
1477    latin1 = encoding("Encoding :  latin-1", File),
1478    utf8 = encoding("ccoding: UTF-8", File),
1479    utf8 = encoding("coding= utf-8", File),
1480    utf8 = encoding_com(" %% coding= utf-8", File),
1481    utf8 = encoding("coding  =  utf-8", File),
1482    none = encoding("coding: utf-16 coding: utf-8", File), %first is bad
1483    none = encoding("Coding: utf-8", File),    %capital c
1484    utf8 = encoding("-*- coding: utf-8 -*-", File),
1485    utf8 = encoding("-*-coding= utf-8-*-", File),
1486    utf8 = encoding("codingcoding= utf-8", File),
1487    ok = prefix("coding: utf-8", File, utf8),
1488
1489    "coding: latin-1" = epp:encoding_to_string(latin1),
1490    "coding: utf-8" = epp:encoding_to_string(utf8),
1491    true = lists:member(epp:default_encoding(), [latin1, utf8]),
1492
1493    ok.
1494
1495prefix(S, File, Enc) ->
1496    prefix(0, S, File, Enc).
1497
1498prefix(100, _S, _File, _) ->
1499    ok;
1500prefix(N, S, File, Enc) ->
1501    Enc = encoding(lists:duplicate(N, $\s) ++ S, File),
1502    prefix(N+1, S, File, Enc).
1503
1504encoding(Enc, File) ->
1505    E = encoding_com("%% " ++ Enc, File),
1506    none = encoding_com(Enc, File),
1507    E = encoding_nocom(Enc, File).
1508
1509encoding_com(Enc, File) ->
1510    B = list_to_binary(Enc),
1511    E = epp:read_encoding_from_binary(B),
1512    ok = file:write_file(File, Enc),
1513    {ok, Fd} = file:open(File, [read]),
1514    E = epp:set_encoding(Fd),
1515    ok = file:close(Fd),
1516    E = epp:read_encoding(File).
1517
1518encoding_nocom(Enc, File) ->
1519    Options = [{in_comment_only, false}],
1520    B = list_to_binary(Enc),
1521    E = epp:read_encoding_from_binary(B, Options),
1522    ok = file:write_file(File, Enc),
1523    {ok, Fd} = file:open(File, [read]),
1524    ok = file:close(Fd),
1525    E = epp:read_encoding(File, Options).
1526
1527%% OTP-10820. Unicode filenames.
1528otp_10820(Config) when is_list(Config) ->
1529    L = [915,953,959,973,957,953,954,959,957,964],
1530    Dir = proplists:get_value(priv_dir, Config),
1531    File = filename:join(Dir, L++".erl"),
1532    C1 = <<"%% coding: utf-8\n -module(any).">>,
1533    ok = do_otp_10820(File, C1, "+pc latin1"),
1534    ok = do_otp_10820(File, C1, "+pc unicode"),
1535    C2 = <<"\n-module(any).">>,
1536    ok = do_otp_10820(File, C2, "+pc latin1"),
1537    ok = do_otp_10820(File, C2, "+pc unicode").
1538
1539do_otp_10820(File, C, PC) ->
1540    {ok,Node} = start_node(erl_pp_helper, "+fnu " ++ PC),
1541    ok = rpc:call(Node, file, write_file, [File, C]),
1542    {ok, Forms} = rpc:call(Node, epp, parse_file, [File, [],[]]),
1543    [{attribute,1,file,{File,1}},
1544     {attribute,2,module,any},
1545     {eof,2}] = unopaque_forms(Forms),
1546    true = test_server:stop_node(Node),
1547    ok.
1548
1549%% OTP_14285: Unicode atoms.
1550otp_14285(Config) when is_list(Config) ->
1551    %% This is just a sample of errors.
1552    Cs = [{otp_14285,
1553           <<"-export([f/0]).
1554              -define('a\x{400}b', 'a\x{400}d').
1555              f() ->
1556                  ?'a\x{400}b'.
1557              g() ->
1558                  ?\"a\x{400}b\".
1559              h() ->
1560                  ?'a\x{400}no'().
1561              "/utf8>>,
1562           {errors,[{{6,20},epp,{call,[63,[91,["97",44,"1024",44,"98"],93]]}},
1563                    {{8,20},epp,{undefined,'a\x{400}no',0}}],
1564            []}}
1565         ],
1566    [] = compile(Config, Cs),
1567    ok.
1568
1569%% OTP-11728. Bugfix circular macro.
1570otp_11728(Config) when is_list(Config) ->
1571    Dir = proplists:get_value(priv_dir, Config),
1572    H = <<"-define(MACRO,[[]++?MACRO]).">>,
1573    HrlFile = filename:join(Dir, "otp_11728.hrl"),
1574    ok = file:write_file(HrlFile, H),
1575    C = <<"-module(otp_11728).
1576           -export([function_name/0]).
1577
1578           -include(\"otp_11728.hrl\").
1579
1580           function_name()->
1581               A=?MACRO, % line 7
1582               ok">>,
1583    ErlFile = filename:join(Dir, "otp_11728.erl"),
1584    ok = file:write_file(ErlFile, C),
1585    {ok, L} = epp:parse_file(ErlFile, [Dir], []),
1586    true = lists:member({error,{7,epp,{circular,'MACRO',none}}}, L),
1587    _ = file:delete(HrlFile),
1588    _ = file:delete(ErlFile),
1589    ok.
1590
1591%% Check the new API for setting the default encoding.
1592encoding(Config) when is_list(Config) ->
1593    Dir = proplists:get_value(priv_dir, Config),
1594    ErlFile = filename:join(Dir, "encoding.erl"),
1595
1596    %% Try a latin-1 file with no encoding given.
1597    C1 = <<"-module(encoding).
1598           %% ",246,"
1599	  ">>,
1600    ok = file:write_file(ErlFile, C1),
1601    {ok,[{attribute,{1,1},file,_},
1602	 {attribute,{1,2},module,encoding},
1603	 {error,_},
1604	 {error,{{2,12},epp,cannot_parse}},
1605	 {eof,{2,12}}]} = epp_parse_file(ErlFile, [{location, {1,1}}]),
1606    {ok,[{attribute,1,file,_},
1607	 {attribute,1,module,encoding},
1608	 {eof,3}]} =
1609	epp_parse_file(ErlFile, [{default_encoding,latin1}]),
1610    {ok,[{attribute,1,file,_},
1611	 {attribute,1,module,encoding},
1612	 {eof,3}],[{encoding,none}]} =
1613	epp_parse_file(ErlFile, [{default_encoding,latin1},extra]),
1614
1615    %% Try a latin-1 file with encoding given in a comment.
1616    C2 = <<"-module(encoding).
1617           %% encoding: latin-1
1618           %% ",246,"
1619	  ">>,
1620    ok = file:write_file(ErlFile, C2),
1621    {ok,[{attribute,1,file,_},
1622	 {attribute,1,module,encoding},
1623	 {eof,4}]} =
1624	epp_parse_file(ErlFile, []),
1625    {ok,[{attribute,1,file,_},
1626	 {attribute,1,module,encoding},
1627	 {eof,4}]} =
1628	epp_parse_file(ErlFile, [{default_encoding,latin1}]),
1629    {ok,[{attribute,1,file,_},
1630	 {attribute,1,module,encoding},
1631	 {eof,4}]} =
1632	epp_parse_file(ErlFile, [{default_encoding,utf8}]),
1633    {ok,[{attribute,1,file,_},
1634	 {attribute,1,module,encoding},
1635	 {eof,4}],[{encoding,latin1}]} =
1636	epp_parse_file(ErlFile, [extra]),
1637    {ok,[{attribute,1,file,_},
1638	 {attribute,1,module,encoding},
1639	 {eof,4}],[{encoding,latin1}]} =
1640	epp_parse_file(ErlFile, [{default_encoding,latin1},extra]),
1641    {ok,[{attribute,1,file,_},
1642	 {attribute,1,module,encoding},
1643	 {eof,4}],[{encoding,latin1}]} =
1644	epp_parse_file(ErlFile, [{default_encoding,utf8},extra]),
1645    ok.
1646
1647extends(Config) ->
1648    Cs = [{extends_c1,
1649	   <<"-extends(some.other.module).\n">>,
1650	   {errors,[{{1,33},erl_parse,["syntax error before: ","'.'"]}],[]}}],
1651    [] = compile(Config, Cs),
1652
1653    Ts = [{extends_1,
1654	   <<"-extends(some_other_module).\n"
1655	     "t() -> {?BASE_MODULE,?BASE_MODULE_STRING}.\n">>,
1656	   {some_other_module,"some_other_module"}}],
1657
1658    [] = run(Config, Ts),
1659    ok.
1660
1661function_macro(Config) ->
1662    Cs = [{f_c1,
1663	   <<"-define(FUNCTION_NAME, a).\n"
1664	     "-define(FUNCTION_ARITY, a).\n"
1665	     "-define(FS,\n"
1666	     " atom_to_list(?FUNCTION_NAME) ++ \"/\" ++\n"
1667	     " integer_to_list(?FUNCTION_ARITY)).\n"
1668	     "-attr({f,?FUNCTION_NAME}).\n"
1669	     "-attr2(?FS).\n"
1670	     "-file(?FUNCTION_ARITY, 1).\n"
1671	     "f1() ?FUNCTION_NAME/?FUNCTION_ARITY.\n"
1672	     "f2(?FUNCTION_NAME.\n">>,
1673	   {errors,[{{1,28},epp,{redefine_predef,'FUNCTION_NAME'}},
1674		    {{2,9},epp,{redefine_predef,'FUNCTION_ARITY'}},
1675		    {{6,11},epp,{illegal_function,'FUNCTION_NAME'}},
1676		    {{7,9},epp,{illegal_function,'FUNCTION_NAME'}},
1677		    {{8,8},epp,{illegal_function,'FUNCTION_ARITY'}},
1678		    {{9,7},erl_parse,["syntax error before: ","f1"]},
1679		    {{10,18},erl_parse,["syntax error before: ","'.'"]}],
1680	    []}},
1681
1682	  {f_c2,
1683	   <<"a({a) -> ?FUNCTION_NAME.\n"
1684	     "b(}{) -> ?FUNCTION_ARITY.\n"
1685	     "c(?FUNCTION_NAME, ?not_defined) -> ok.\n">>,
1686	   {errors,[{{1,24},erl_parse,["syntax error before: ","')'"]},
1687		    {{2,3},erl_parse,["syntax error before: ","'}'"]},
1688		    {{3,20},epp,{undefined,not_defined,none}}],
1689	    []}},
1690
1691	  {f_c3,
1692	   <<"?FUNCTION_NAME() -> ok.\n"
1693	     "?FUNCTION_ARITY() -> ok.\n">>,
1694	   {errors,[{{1,21},epp,{illegal_function_usage,'FUNCTION_NAME'}},
1695		    {{2,2},epp,{illegal_function_usage,'FUNCTION_ARITY'}}],
1696	    []}}
1697	 ],
1698
1699    [] = compile(Config, Cs),
1700
1701    Ts = [{f_1,
1702	   <<"t() -> {a,0} = a(), {b,1} = b(1), {c,2} = c(1, 2),\n"
1703	     "  {d,1} = d({d,1}), {foo,1} = foo(foo), ok.\n"
1704	     "a() -> {?FUNCTION_NAME,?FUNCTION_ARITY}.\n"
1705	     "b(_) -> {?FUNCTION_NAME,?FUNCTION_ARITY}.\n"
1706	     "c(_, (_)) -> {?FUNCTION_NAME,?FUNCTION_ARITY}.\n"
1707	     "d({?FUNCTION_NAME,?FUNCTION_ARITY}=F) -> F.\n"
1708	     "-define(FOO, foo).\n"
1709	     "?FOO(?FOO) -> {?FUNCTION_NAME,?FUNCTION_ARITY}.\n">>,
1710	   ok},
1711
1712	  {f_2,
1713	   <<"t() ->\n"
1714             "  A = {a,[<<0:24>>,#{a=>1,b=>2}]},\n"
1715	     "  1 = a(A),\n"
1716	     "  ok.\n"
1717	     "a({a,[<<_,_,_>>,#{a:=1,b:=2}]}) -> ?FUNCTION_ARITY.\n">>,
1718	   ok},
1719
1720	  {f_3,
1721	   <<"-define(FS,\n"
1722	     " atom_to_list(?FUNCTION_NAME) ++ \"/\" ++\n"
1723	     " integer_to_list(?FUNCTION_ARITY)).\n"
1724	     "t() ->\n"
1725	     "  {t,0} = {?FUNCTION_NAME,?FUNCTION_ARITY},\n"
1726	     "  \"t/0\" = ?FS,\n"
1727	     "  ok.\n">>,
1728	   ok},
1729
1730	  {f_4,
1731	   <<"-define(__, _, _).\n"
1732	     "-define(FF, ?FUNCTION_NAME, ?FUNCTION_ARITY).\n"
1733	     "a(?__) -> 2 = ?FUNCTION_ARITY.\n"
1734	     "b(?FUNCTION_ARITY, ?__) -> ok.\n"
1735	     "c(?FF) -> ok.\n"
1736	     "t() -> a(1, 2), b(3, 1, 2), c(c, 2), ok.\n">>,
1737	   ok}
1738	 ],
1739    [] = run(Config, Ts),
1740
1741    ok.
1742
1743source_name(Config) when is_list(Config) ->
1744    DataDir = proplists:get_value(data_dir, Config),
1745    File = filename:join(DataDir, "source_name.erl"),
1746
1747    source_name_1(File, "/test/gurka.erl"),
1748    source_name_1(File, "gaffel.erl"),
1749
1750    ok.
1751
1752source_name_1(File, Expected) ->
1753    Res = epp:parse_file(File, [{source_name, Expected}]),
1754    {ok, [{attribute,_,file,{Expected,_}} | _Forms]} = Res.
1755
1756otp_16978(Config) when is_list(Config) ->
1757    %% A test of erl_parse:tokens().
1758    P = <<"t() -> ?a.">>,
1759    Vs = [#{},
1760          #{k => 1,[[a],[{}]] => "str"},
1761          #{#{} => [{#{x=>#{3=>$3}}},{3.14,#{}}]}],
1762    Ts = [{erl_parse_tokens,
1763           P,
1764           [{d,{a,V}}],
1765           V} || V <- Vs],
1766    [] = run(Config, Ts),
1767
1768    ok.
1769
1770otp_16824(Config) when is_list(Config) ->
1771    Cs = [{otp_16824_1,
1772           <<"\n-file(.">>,
1773           {errors,[{{2,7},epp,{bad,file}}],[]}},
1774
1775          {otp_16824_2,
1776           <<"\n-file(foo, a).">>,
1777           {errors,[{{2,7},epp,{bad,file}}],[]}},
1778
1779          {otp_16824_3,
1780           <<"\n-file(\"foo\" + a).">>,
1781           {errors,[{{2,13},epp,{bad,file}}],[]}},
1782
1783          {otp_16824_4,
1784           <<"\n-file(\"foo\", a).">>,
1785           {errors,[{{2,14},epp,{bad,file}}],[]}},
1786
1787          %% The location before "foo", not after, unfortunately.
1788          {otp_16824_5,
1789           <<"\n-file(\"foo\"">>,
1790           {errors,[{{2,7},epp,{bad,file}}],[]}},
1791
1792          {otp_16824_6,
1793           <<"\n-endif()">>,
1794           {errors,[{{2,7},epp,{bad,endif}}],[]}},
1795
1796          {otp_16824_7,
1797           <<"\n-if[.\n"
1798             "-endif.">>,
1799           {errors,[{{2,4},epp,{bad,'if'}}],
1800            []}},
1801
1802          {otp_16824_8,
1803           <<"\n-else\n"
1804             "-endif.">>,
1805           {errors,[{{3,1},epp,{bad,else}}],[]}},
1806
1807          {otp_16824_9,
1808           <<"\n-ifndef.\n"
1809             "-endif.">>,
1810           {errors,[{{2,8},epp,{bad,ifndef}}],[]}},
1811
1812          {otp_16824_10,
1813           <<"\n-ifndef(.\n"
1814             "-endif.">>,
1815           {errors,[{{2,9},epp,{bad,ifndef}}],[]}},
1816
1817          {otp_16824_11,
1818           <<"\n-ifndef(a.\n"
1819             "-endif.">>,
1820           {errors,[{{2,10},epp,{bad,ifndef}}],[]}},
1821
1822          {otp_16824_12,
1823           <<"\n-ifndef(A.\n"
1824             "-endif.">>,
1825           {errors,[{{2,10},epp,{bad,ifndef}}],[]}},
1826
1827          {otp_16824_13,
1828           <<"\n-ifndef(a,A).\n"
1829             "-endif.">>,
1830           {errors,[{{2,10},epp,{bad,ifndef}}],[]}},
1831
1832          {otp_16824_14,
1833           <<"\n-ifndef(A,a).\n"
1834             "-endif.">>,
1835           {errors,[{{2,10},epp,{bad,ifndef}}],[]}},
1836
1837          {otp_16824_15,
1838           <<"\n-ifdef.\n"
1839             "-endif.">>,
1840           {errors,[{{2,7},epp,{bad,ifdef}}],[]}},
1841
1842          {otp_16824_16,
1843           <<"\n-ifdef(.\n"
1844             "-endif.">>,
1845           {errors,[{{2,8},epp,{bad,ifdef}}],[]}},
1846
1847          {otp_16824_17,
1848           <<"\n-ifdef(a.\n"
1849             "-endif.">>,
1850           {errors,[{{2,9},epp,{bad,ifdef}}],[]}},
1851
1852          {otp_16824_18,
1853           <<"\n-ifdef(A.\n"
1854             "-endif.">>,
1855           {errors,[{{2,9},epp,{bad,ifdef}}],[]}},
1856
1857          {otp_16824_19,
1858           <<"\n-ifdef(a,A).\n"
1859             "-endif.">>,
1860           {errors,[{{2,9},epp,{bad,ifdef}}],[]}},
1861
1862          {otp_16824_20,
1863           <<"\n-ifdef(A,a).\n"
1864             "-endif.">>,
1865           {errors,[{{2,9},epp,{bad,ifdef}}],[]}},
1866
1867          {otp_16824_21,
1868           <<"\n-include_lib.\n">>,
1869           {errors,[{{2,13},epp,{bad,include_lib}}],[]}},
1870
1871          {otp_16824_22,
1872           <<"\n-include_lib(.\n">>,
1873           {errors,[{{2,14},epp,{bad,include_lib}}],[]}},
1874
1875          {otp_16824_23,
1876           <<"\n-include_lib(a.\n">>,
1877           {errors,[{{2,14},epp,{bad,include_lib}}],[]}},
1878
1879          {otp_16824_24,
1880           <<"\n-include_lib(\"a\"].\n">>,
1881           {errors,[{{2,17},epp,{bad,include_lib}}],[]}},
1882
1883          {otp_16824_25,
1884           <<"\n-include_lib(\"a\", 1).\n">>,
1885           {errors,[{{2,17},epp,{bad,include_lib}}],[]}},
1886
1887          {otp_16824_26,
1888           <<"\n-include.\n">>,
1889           {errors,[{{2,9},epp,{bad,include}}],[]}},
1890
1891          {otp_16824_27,
1892           <<"\n-include(.\n">>,
1893           {errors,[{{2,10},epp,{bad,include}}],[]}},
1894
1895          {otp_16824_28,
1896           <<"\n-include(a.\n">>,
1897           {errors,[{{2,10},epp,{bad,include}}],[]}},
1898
1899          {otp_16824_29,
1900           <<"\n-include(\"a\"].\n">>,
1901           {errors,[{{2,13},epp,{bad,include}}],[]}},
1902
1903          {otp_16824_30,
1904           <<"\n-include(\"a\", 1).\n">>,
1905           {errors,[{{2,13},epp,{bad,include}}],[]}},
1906
1907          {otp_16824_31,
1908           <<"\n-undef.\n">>,
1909           {errors,[{{2,7},epp,{bad,undef}}],[]}},
1910
1911          {otp_16824_32,
1912           <<"\n-undef(.\n">>,
1913           {errors,[{{2,8},epp,{bad,undef}}],[]}},
1914
1915          {otp_16824_33,
1916           <<"\n-undef(a.\n">>,
1917           {errors,[{{2,9},epp,{bad,undef}}],[]}},
1918
1919          {otp_16824_34,
1920           <<"\n-undef(A.\n">>,
1921           {errors,[{{2,9},epp,{bad,undef}}],[]}},
1922
1923          {otp_16824_35,
1924           <<"\n-undef(a,A).\n">>,
1925           {errors,[{{2,9},epp,{bad,undef}}],[]}},
1926
1927          {otp_16824_36,
1928           <<"\n-undef(A,a).\n">>,
1929           {errors,[{{2,9},epp,{bad,undef}}],[]}},
1930
1931          {otp_16824_37,
1932           <<"\n-define.\n">>,
1933           {errors,[{{2,8},epp,{bad,define}}],[]}},
1934
1935          {otp_16824_38,
1936           <<"\n-define(.\n">>,
1937           {errors,[{{2,9},epp,{bad,define}}],[]}},
1938
1939          {otp_16824_39,
1940           <<"\n-define(1.\n">>,
1941           {errors,[{{2,9},epp,{bad,define}}],[]}},
1942
1943          {otp_16824_40,
1944           <<"\n-define(a b.\n">>,
1945           {errors,[{{2,11},epp,{bad,define}}],[]}},
1946
1947          {otp_16824_41,
1948           <<"\n-define(A b.\n">>,
1949           {errors,[{{2,11},epp,{bad,define}}],[]}},
1950
1951          {otp_16824_42,
1952           <<"\n-define(a(A, A), 1).\n">>,
1953           {errors,[{{2,14},epp,{duplicated_argument,'A'}}],[]}},
1954
1955          {otp_16824_43,
1956           <<"\n-define(a(A, A, B), 1).\n">>,
1957           {errors,[{{2,14},epp,{duplicated_argument,'A'}}],[]}},
1958
1959          {otp_16824_44,
1960           <<"\n-define(a(.">>,
1961           {errors,[{{2,11},epp,{bad,define}}],[]}},
1962
1963          {otp_16824_45,
1964           <<"\n-define(a(1.">>,
1965           {errors,[{{2,11},epp,{bad,define}}],[]}},
1966
1967          {otp_16824_46,
1968           <<"\n-define(a().">>,
1969           {errors,[{{2,12},epp,missing_comma}],[]}},
1970
1971          {otp_16824_47,
1972           <<"\n-define(a())">>,
1973           {errors,[{{2,12},epp,missing_comma}],[]}},
1974
1975          {otp_16824_48,
1976           <<"\n-define(A(A,), foo).\n">>,
1977           {errors,[{{2,12},epp,{bad,define}}],[]}},
1978
1979          {otp_16824_49,
1980           <<"\n-warning.">>,
1981           {errors,[{{2,9},epp,{bad,warning}}],[]}},
1982
1983          {otp_16824_50,
1984           <<"\n-warning">>,
1985           {errors,[{{2,2},epp,{bad,warning}}],[]}}
1986
1987          ],
1988    [] = compile(Config, Cs),
1989    ok.
1990
1991%% Start location is 1.
1992check(Config, Tests) ->
1993    eval_tests(Config, fun check_test/3, Tests).
1994
1995%% Start location is {1,1}.
1996compile(Config, Tests) ->
1997    eval_tests(Config, fun compile_test/3, Tests).
1998
1999run(Config, Tests) ->
2000    eval_tests(Config, fun run_test/3, Tests).
2001
2002eval_tests(Config, Fun, Tests) ->
2003    TestsWithOpts =
2004        [case Test of
2005             {N,P,E} ->
2006                 {N,P,[],E};
2007             {_,_,_,_} ->
2008                 Test
2009         end || Test <- Tests],
2010    F = fun({N,P,Opts,E}, BadL) ->
2011                %% io:format("Testing ~p~n", [P]),
2012                Return = Fun(Config, P, Opts),
2013                case message_compare(E, Return) of
2014                    true ->
2015                        case E of
2016                            {errors, Errors} ->
2017                                call_format_error(Errors);
2018                            _ ->
2019                                ok
2020                        end,
2021                        BadL;
2022                    false ->
2023                        io:format("~nTest ~p failed. Expected~n  ~p~n"
2024                                  "but got~n  ~p~n", [N, E, Return]),
2025			fail()
2026                end
2027        end,
2028    lists:foldl(F, [], TestsWithOpts).
2029
2030check_test(Config, Test, Opts) ->
2031    Filename = "epp_test.erl",
2032    PrivDir = proplists:get_value(priv_dir, Config),
2033    File = filename:join(PrivDir, Filename),
2034    ok = file:write_file(File, Test),
2035    case epp:parse_file(File, [PrivDir], Opts) of
2036	{ok,Forms} ->
2037	    Errors = [E || E={error,_} <- Forms],
2038	    call_format_error([E || {error,E} <- Errors]),
2039	    Errors;
2040	{error,Error} ->
2041	    Error
2042    end.
2043
2044compile_test(Config, Test0, Opts0) ->
2045    Test = [<<"-module(epp_test). ">>, Test0],
2046    Filename = "epp_test.erl",
2047    PrivDir = proplists:get_value(priv_dir, Config),
2048    File = filename:join(PrivDir, Filename),
2049    ok = file:write_file(File, Test),
2050    Opts = [export_all,nowarn_export_all,return,nowarn_unused_record,{outdir,PrivDir}] ++ Opts0,
2051    case compile_file(File, Opts) of
2052        {ok, Ws} -> warnings(File, Ws);
2053        {errors, Errors}=Else ->
2054            call_format_error(Errors),
2055            Else;
2056        Else -> Else
2057    end.
2058
2059warnings(File, Ws) ->
2060    case lists:append([W || {F, W} <- Ws, F =:= File]) of
2061        [] ->
2062	    [];
2063        L ->
2064	    call_format_error(L),
2065	    {warnings, L}
2066    end.
2067
2068compile_file(File, Opts) ->
2069    case compile:file(File, Opts) of
2070        {ok, _M, Ws} -> {ok, Ws};
2071        {error, FEs, []} -> {errors, errs(FEs, File), []};
2072        {error, FEs, [{File,Ws}]} -> {error, errs(FEs, File), Ws}
2073    end.
2074
2075errs([{File,Es}|L], File) ->
2076    call_format_error(Es),
2077    Es ++ errs(L, File);
2078errs([_|L], File) ->
2079    errs(L, File);
2080errs([], _File) ->
2081    [].
2082
2083%% Smoke test and coverage of format_error/1.
2084call_format_error([{_,M,E}|T]) ->
2085    _ = M:format_error(E),
2086    call_format_error(T);
2087call_format_error([]) ->
2088    ok.
2089
2090epp_parse_file(File, Opts) ->
2091    case epp:parse_file(File, Opts) of
2092        {ok, Forms} ->
2093            {ok, unopaque_forms(Forms)};
2094        {ok, Forms, Other} ->
2095            {ok, unopaque_forms(Forms), Other}
2096    end.
2097
2098unopaque_forms(Forms) ->
2099    [erl_parse:anno_to_term(Form) || Form <- Forms].
2100
2101run_test(Config, Test0, Opts0) ->
2102    Test = [<<"-module(epp_test). -export([t/0]). ">>, Test0],
2103    Filename = "epp_test.erl",
2104    PrivDir = proplists:get_value(priv_dir, Config),
2105    File = filename:join(PrivDir, Filename),
2106    ok = file:write_file(File, Test),
2107    Opts = [return, {i,PrivDir},{outdir,PrivDir}] ++ Opts0,
2108    {ok, epp_test, []} = compile:file(File, Opts),
2109    AbsFile = filename:rootname(File, ".erl"),
2110    {module, epp_test} = code:load_abs(AbsFile, epp_test),
2111    Reply = epp_test:t(),
2112    code:purge(epp_test),
2113    Reply.
2114
2115fail() ->
2116    ct:fail(failed).
2117
2118message_compare(T, T) ->
2119    T =:= T.
2120
2121%% +fnu means a peer node has to be started; slave will not do
2122start_node(Name, Xargs) ->
2123    PA = filename:dirname(code:which(?MODULE)),
2124    test_server:start_node(Name, peer, [{args, "-pa " ++ PA ++ " " ++ Xargs}]).
2125