diff options
Diffstat (limited to 'lib/stdlib/test/epp_SUITE.erl')
-rw-r--r-- | lib/stdlib/test/epp_SUITE.erl | 305 |
1 files changed, 152 insertions, 153 deletions
diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl index 447480a1bd..d18f99acf5 100644 --- a/lib/stdlib/test/epp_SUITE.erl +++ b/lib/stdlib/test/epp_SUITE.erl @@ -87,24 +87,24 @@ end_per_group(_GroupName, Config) -> %% Recursive macros hang or crash epp (OTP-1398). rec_1(Config) when is_list(Config) -> - ?line File = filename:join(?config(data_dir, Config), "mac.erl"), - ?line {ok, List} = epp_parse_file(File, [], []), + File = filename:join(?config(data_dir, Config), "mac.erl"), + {ok, List} = epp_parse_file(File, [], []), %% we should encounter errors - ?line {value, _} = lists:keysearch(error, 1, List), - ?line check_errors(List), + {value, _} = lists:keysearch(error, 1, List), + check_errors(List), ok. include_local(Config) when is_list(Config) -> - ?line DataDir = ?config(data_dir, Config), - ?line File = filename:join(DataDir, "include_local.erl"), + DataDir = ?config(data_dir, Config), + File = filename:join(DataDir, "include_local.erl"), FooHrl = filename:join([DataDir,"include","foo.hrl"]), BarHrl = filename:join([DataDir,"include","bar.hrl"]), %% include_local.erl includes include/foo.hrl which %% includes bar.hrl (also in include/) without requiring %% any additional include path, and overriding any file %% of the same name that the path points to - ?line {ok, List} = epp:parse_file(File, [DataDir], []), - ?line {value, {attribute,_,a,{true,true}}} = + {ok, List} = epp:parse_file(File, [DataDir], []), + {value, {attribute,_,a,{true,true}}} = lists:keysearch(a,3,List), [{File,1},{FooHrl,1},{BarHrl,1},{FooHrl,5},{File,5}] = [ FileLine || {attribute,_,file,FileLine} <- List ], @@ -160,55 +160,55 @@ epp_parse_erl_form(Epp, Parent) -> check_errors([]) -> ok; check_errors([{error, Info} | Rest]) -> - ?line {Line, Mod, Desc} = Info, - ?line case Line of - I when is_integer(I) -> ok; - {L,C} when is_integer(L), is_integer(C), C >= 1 -> ok - end, - ?line Str = lists:flatten(Mod:format_error(Desc)), - ?line [Str] = io_lib:format("~s", [Str]), + {Line, Mod, Desc} = Info, + case Line of + I when is_integer(I) -> ok; + {L,C} when is_integer(L), is_integer(C), C >= 1 -> ok + end, + Str = lists:flatten(Mod:format_error(Desc)), + [Str] = io_lib:format("~s", [Str]), check_errors(Rest); check_errors([_ | Rest]) -> check_errors(Rest). upcase_mac_1(Config) when is_list(Config) -> - ?line File = filename:join(?config(data_dir, Config), "mac2.erl"), - ?line {ok, List} = epp:parse_file(File, [], []), - ?line [_, {attribute, _, plupp, Tuple} | _] = List, - ?line Tuple = {1, 1, 3, 3}, + File = filename:join(?config(data_dir, Config), "mac2.erl"), + {ok, List} = epp:parse_file(File, [], []), + [_, {attribute, _, plupp, Tuple} | _] = List, + Tuple = {1, 1, 3, 3}, ok. upcase_mac_2(Config) when is_list(Config) -> - ?line File = filename:join(?config(data_dir, Config), "mac2.erl"), - ?line {ok, List} = epp:parse_file(File, [], [{p, 5}, {'P', 6}]), - ?line [_, {attribute, _, plupp, Tuple} | _] = List, - ?line Tuple = {5, 5, 6, 6}, + File = filename:join(?config(data_dir, Config), "mac2.erl"), + {ok, List} = epp:parse_file(File, [], [{p, 5}, {'P', 6}]), + [_, {attribute, _, plupp, Tuple} | _] = List, + Tuple = {5, 5, 6, 6}, ok. predef_mac(Config) when is_list(Config) -> - ?line File = filename:join(?config(data_dir, Config), "mac3.erl"), - ?line {ok, List} = epp:parse_file(File, [], []), - ?line [_, - {attribute, Anno, l, Line1}, - {attribute, _, f, File}, - {attribute, _, machine1, _}, - {attribute, _, module, mac3}, - {attribute, _, m, mac3}, - {attribute, _, ms, "mac3"}, - {attribute, _, machine2, _} - | _] = List, + File = filename:join(?config(data_dir, Config), "mac3.erl"), + {ok, List} = epp:parse_file(File, [], []), + [_, + {attribute, Anno, l, Line1}, + {attribute, _, f, File}, + {attribute, _, machine1, _}, + {attribute, _, module, mac3}, + {attribute, _, m, mac3}, + {attribute, _, ms, "mac3"}, + {attribute, _, machine2, _} + | _] = List, Line1 = erl_anno:line(Anno), ok. variable_1(Config) when is_list(Config) -> - ?line DataDir = ?config(data_dir, Config), - ?line File = filename:join(DataDir, "variable_1.erl"), - ?line true = os:putenv("VAR", DataDir), + DataDir = ?config(data_dir, Config), + File = filename:join(DataDir, "variable_1.erl"), + true = os:putenv("VAR", DataDir), %% 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}}} = + {ok, List} = epp:parse_file(File, [], []), + {value, {attribute,_,a,{value1,value2}}} = lists:keysearch(a,3,List), ok. @@ -218,28 +218,28 @@ otp_4870(Config) when is_list(Config) -> <<"-undef(foo). ">>, []}], - ?line [] = check(Config, Ts), + [] = check(Config, Ts), ok. %% crashing erl_scan otp_4871(Config) when is_list(Config) -> - ?line Dir = ?config(priv_dir, Config), - ?line File = filename:join(Dir, "otp_4871.erl"), - ?line ok = file:write_file(File, "-module(otp_4871)."), + Dir = ?config(priv_dir, Config), + File = filename:join(Dir, "otp_4871.erl"), + ok = file:write_file(File, "-module(otp_4871)."), %% 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, %% so there are some sanity checks before killing. - ?line {ok,Epp} = epp:open(File, []), + {ok,Epp} = epp:open(File, []), timer:sleep(1), - ?line true = current_module(Epp, epp), - ?line {monitored_by,[Io]} = process_info(Epp, monitored_by), - ?line true = current_module(Io, file_io_server), - ?line exit(Io, emulate_crash), + true = current_module(Epp, epp), + {monitored_by,[Io]} = process_info(Epp, monitored_by), + true = current_module(Io, file_io_server), + exit(Io, emulate_crash), timer:sleep(1), - ?line {error,{_Line,epp,cannot_parse}} = otp_4871_parse_file(Epp), - ?line epp:close(Epp), + {error,{_Line,epp,cannot_parse}} = otp_4871_parse_file(Epp), + epp:close(Epp), ok. current_module(Pid, Mod) -> @@ -282,12 +282,12 @@ otp_5362(Config) when is_list(Config) -> Incl3 = <<"glurk(Foo) -> % line 1 bar. ">>, - ?line ok = file:write_file(File_Incl, Incl), - ?line ok = file:write_file(File_Incl2, Incl2), - ?line ok = file:write_file(File_Incl3, Incl3), + ok = file:write_file(File_Incl, Incl), + ok = file:write_file(File_Incl2, Incl2), + ok = file:write_file(File_Incl3, Incl3), - ?line {ok, incl_5362, InclWarnings} = compile:file(File_Incl, Copts), - ?line true = message_compare( + {ok, incl_5362, InclWarnings} = compile:file(File_Incl, Copts), + true = message_compare( [{File_Incl3,[{{1,1},erl_lint,{unused_function,{glurk,1}}}, {{1,7},erl_lint,{unused_var,'Foo'}}]}, {File_Incl,[{{7,15},erl_lint,{unused_function,{hi,1}}}, @@ -317,11 +317,11 @@ otp_5362(Config) when is_list(Config) -> -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)), + ok = file:write_file(File_Back, Back), + ok = file:write_file(File_Back_hrl, list_to_binary(Back_hrl)), - ?line {ok, back_5362, BackWarnings} = compile:file(File_Back, Copts), - ?line true = message_compare( + {ok, back_5362, BackWarnings} = compile:file(File_Back, Copts), + true = message_compare( [{File_Back,[{{4,19},erl_lint,{unused_var,'V'}}]}], BackWarnings), file:delete(File_Back), @@ -345,11 +345,11 @@ otp_5362(Config) when is_list(Config) -> foo. ">>], - ?line ok = file:write_file(File_Change, list_to_binary(Change)), + ok = file:write_file(File_Change, list_to_binary(Change)), - ?line {ok, change_5362, ChangeWarnings} = + {ok, change_5362, ChangeWarnings} = compile:file(File_Change, Copts), - ?line true = message_compare( + true = message_compare( [{File_Change,[{{1002,21},erl_lint,{unused_var,'B'}}]}, {"other.file",[{{105,21},erl_lint,{unused_var,'A'}}]}], lists:usort(ChangeWarnings)), @@ -377,9 +377,9 @@ otp_5362(Config) when is_list(Config) -> -file(?FILE, ?LINE). c(C) -> % line 47 3. ">>, - ?line ok = file:write_file(File_Blank, Blank), - ?line {ok, blank_5362, BlankWarnings} = compile:file(File_Blank, Copts), - ?line true = message_compare( + ok = file:write_file(File_Blank, Blank), + {ok, blank_5362, BlankWarnings} = compile:file(File_Blank, Copts), + true = message_compare( [{File_Blank,[{{18,3},erl_lint,{unused_var,'Q'}}, {{20,18},erl_lint,{unused_var,'A'}}, {{44,18},erl_lint,{unused_var,'B'}}, @@ -403,16 +403,16 @@ otp_5362(Config) when is_list(Config) -> FILE1 = <<"ii() -> ?FILE. ">>, FILE_Mod = file_5362, - ?line ok = file:write_file(FILE_incl, FILE), - ?line ok = file:write_file(FILE_incl1, FILE1), + ok = file:write_file(FILE_incl, FILE), + ok = file:write_file(FILE_incl1, FILE1), FILE_Copts = [return, {i,Dir},{outdir,Dir}], - ?line {ok, file_5362, []} = compile:file(FILE_incl, FILE_Copts), + {ok, file_5362, []} = compile:file(FILE_incl, FILE_Copts), AbsFile = filename:rootname(FILE_incl, ".erl"), - ?line {module, FILE_Mod} = code:load_abs(AbsFile, FILE_Mod), - ?line II = FILE_Mod:ii(), - ?line "file_incl_5362.erl" = filename:basename(II), - ?line FF = FILE_Mod:ff(), - ?line "other_file" = filename:basename(FF), + {module, FILE_Mod} = code:load_abs(AbsFile, FILE_Mod), + II = FILE_Mod:ii(), + "file_incl_5362.erl" = filename:basename(II), + FF = FILE_Mod:ff(), + "other_file" = filename:basename(FF), code:purge(file_5362), file:delete(FILE_incl), @@ -421,12 +421,12 @@ otp_5362(Config) when is_list(Config) -> ok. pmod(Config) when is_list(Config) -> - ?line DataDir = ?config(data_dir, Config), - ?line Pmod = filename:join(DataDir, "pmod.erl"), - ?line case epp:parse_file([Pmod], [], []) of + DataDir = ?config(data_dir, Config), + Pmod = filename:join(DataDir, "pmod.erl"), + case epp:parse_file([Pmod], [], []) of {ok,Forms} -> - %% ?line io:format("~p\n", [Forms]), - ?line [] = [F || {error,_}=F <- Forms], + %% io:format("~p\n", [Forms]), + [] = [F || {error,_}=F <- Forms], ok end, ok. @@ -439,14 +439,14 @@ not_circular(Config) when is_list(Config) -> <<"-define(S(S), ??S).\n" "t() -> \"string\" = ?S(string), ok.\n">>, ok}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. %% Skip some bytes in the beginning of the file. skip_header(Config) when is_list(Config) -> - ?line PrivDir = ?config(priv_dir, Config), - ?line File = filename:join([PrivDir, "epp_test_skip_header.erl"]), - ?line ok = file:write_file(File, + PrivDir = ?config(priv_dir, Config), + File = filename:join([PrivDir, "epp_test_skip_header.erl"]), + ok = file:write_file(File, <<"some bytes in the beginning of the file that should be skipped @@ -456,16 +456,16 @@ skip_header(Config) when is_list(Config) -> main(_) -> ?MODULE. ">>), - ?line {ok, Fd} = file:open(File, [read]), - ?line io:get_line(Fd, ''), - ?line io:get_line(Fd, ''), - ?line io:get_line(Fd, ''), - ?line {ok, Epp} = epp:open(list_to_atom(File), Fd, 4, [], []), - - ?line Forms = epp:parse_file(Epp), - ?line [] = [Reason || {error, Reason} <- Forms], - ?line ok = epp:close(Epp), - ?line ok = file:close(Fd), + {ok, Fd} = file:open(File, [read]), + io:get_line(Fd, ''), + io:get_line(Fd, ''), + io:get_line(Fd, ''), + {ok, Epp} = epp:open(list_to_atom(File), Fd, 4, [], []), + + Forms = epp:parse_file(Epp), + [] = [Reason || {error, Reason} <- Forms], + ok = epp:close(Epp), + ok = file:close(Fd), ok. @@ -477,7 +477,7 @@ otp_6277(Config) when is_list(Config) -> ?ASSERT().">>, [{error,{{4,16},epp,{undefined,'MODULE', none}}}]}], - ?line [] = check(Config, Ts), + [] = check(Config, Ts), ok. %% OTP-7702. Wrong line number in stringifying macro expansion. @@ -498,8 +498,8 @@ otp_7702(Config) when is_list(Config) -> end). t() -> ?RECEIVE(foo, bar).">>, - ?line ok = file:write_file(File, Contents), - ?line {ok, file_7702, []} = + ok = file:write_file(File, Contents), + {ok, file_7702, []} = compile:file(File, [debug_info,return,{outdir,Dir}]), BeamFile = filename:join(Dir, "file_7702.beam"), @@ -507,8 +507,7 @@ otp_7702(Config) when is_list(Config) -> {file_7702,[{abstract_code,{_,Forms}}]} = AC, Forms2 = unopaque_forms(Forms), - ?line - [{attribute,1,file,_}, + [{attribute,1,file,_}, _, _, {function,_,t,0, @@ -642,7 +641,7 @@ otp_8130(Config) when is_list(Config) -> {1,1}} ], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), Cs = [{otp_8130_c1, <<"-define(M1(A), if\n" @@ -776,7 +775,7 @@ otp_8130(Config) when is_list(Config) -> {{3,19},epp,{undefined,'A',none}}],[]}} ], - ?line [] = compile(Config, Cs), + [] = compile(Config, Cs), Cks = [{otp_check_1, <<"\n-include_lib(\"epp_test.erl\").\n">>, @@ -786,25 +785,25 @@ otp_8130(Config) when is_list(Config) -> <<"\n-include(\"epp_test.erl\").\n">>, [{error,{{2,2},epp,{depth,"include"}}}]} ], - ?line [] = check(Config, Cks), + [] = check(Config, Cks), - ?line Dir = ?config(priv_dir, Config), - ?line File = filename:join(Dir, "otp_8130.erl"), - ?line ok = file:write_file(File, + Dir = ?config(priv_dir, Config), + File = filename:join(Dir, "otp_8130.erl"), + ok = file:write_file(File, "-module(otp_8130).\n" "-define(a, 3.14).\n" "t() -> ?a.\n"), - ?line {ok,Epp} = epp:open(File, []), + {ok,Epp} = epp:open(File, []), PreDefMacs = macs(Epp), ['BASE_MODULE','BASE_MODULE_STRING','BEAM','FILE', 'FUNCTION_ARITY','FUNCTION_NAME', 'LINE','MACHINE','MODULE','MODULE_STRING'] = PreDefMacs, - ?line {ok,[{'-',_},{atom,_,file}|_]} = epp:scan_erl_form(Epp), - ?line {ok,[{'-',_},{atom,_,module}|_]} = epp:scan_erl_form(Epp), - ?line {ok,[{atom,_,t}|_]} = epp:scan_erl_form(Epp), - ?line {eof,_} = epp:scan_erl_form(Epp), + {ok,[{'-',_},{atom,_,file}|_]} = epp:scan_erl_form(Epp), + {ok,[{'-',_},{atom,_,module}|_]} = epp:scan_erl_form(Epp), + {ok,[{atom,_,t}|_]} = epp:scan_erl_form(Epp), + {eof,_} = epp:scan_erl_form(Epp), [a] = macs(Epp) -- PreDefMacs, - ?line epp:close(Epp), + epp:close(Epp), %% escript ModuleStr = "any_name", @@ -813,27 +812,27 @@ otp_8130(Config) when is_list(Config) -> PreDefMacros = [{'MODULE', Module, redefine}, {'MODULE_STRING', ModuleStr, redefine}, a, {b,2}], - ?line {ok,Epp2} = epp:open(File, [], PreDefMacros), - ?line [{atom,_,true}] = macro(Epp2, a), - ?line [{integer,_,2}] = macro(Epp2, b), - ?line false = macro(Epp2, c), - ?line epp:close(Epp2) + {ok,Epp2} = epp:open(File, [], PreDefMacros), + [{atom,_,true}] = macro(Epp2, a), + [{integer,_,2}] = macro(Epp2, b), + false = macro(Epp2, c), + epp:close(Epp2) end(), fun() -> PreDefMacros = [{a,b,c}], - ?line {error,{bad,{a,b,c}}} = epp:open(File, [], PreDefMacros) + {error,{bad,{a,b,c}}} = epp:open(File, [], PreDefMacros) end(), fun() -> PreDefMacros = [a, {a,1}], - ?line {error,{redefine,a}} = epp:open(File, [], PreDefMacros) + {error,{redefine,a}} = epp:open(File, [], PreDefMacros) end(), fun() -> PreDefMacros = [{a,1},a], - ?line {error,{redefine,a}} = epp:open(File, [], PreDefMacros) + {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", [], []), + {error,enoent} = epp:open("no such file", []), + {error,enoent} = epp:parse_file("no such file", [], []), _ = ifdef(Config), @@ -973,7 +972,7 @@ ifdef(Config) -> "t() -> a.\n">>, {errors,[{{2,2},epp,{'NYI','if'}}],[]}} ], - ?line [] = compile(Config, Cs), + [] = compile(Config, Cs), Ts = [{ifdef_1, <<"-ifdef(a).\n" @@ -1054,7 +1053,7 @@ ifdef(Config) -> ok} ], - ?line [] = run(Config, Ts). + [] = run(Config, Ts). @@ -1089,7 +1088,7 @@ overload_mac(Config) when is_list(Config) -> "t() -> ?A(1).">>, {errors,[{{4,9},epp,{mismatch,'A'}}],[]}} ], - ?line [] = compile(Config, Cs), + [] = compile(Config, Cs), Ts = [ {overload_mac_r1, @@ -1113,24 +1112,24 @@ overload_mac(Config) when is_list(Config) -> "t() -> ?A(1).">>, 1} ], - ?line [] = run(Config, Ts). + [] = run(Config, Ts). %% OTP-8388. More tests on overloaded macros. otp_8388(Config) when is_list(Config) -> Dir = ?config(priv_dir, Config), - ?line File = filename:join(Dir, "otp_8388.erl"), - ?line ok = file:write_file(File, <<"-module(otp_8388)." + File = filename:join(Dir, "otp_8388.erl"), + ok = file:write_file(File, <<"-module(otp_8388)." "-define(LINE, a).">>), fun() -> PreDefMacros = [{'LINE', a}], - ?line {error,{redefine_predef,'LINE'}} = + {error,{redefine_predef,'LINE'}} = epp:open(File, [], PreDefMacros) end(), fun() -> PreDefMacros = ['LINE'], - ?line {error,{redefine_predef,'LINE'}} = + {error,{redefine_predef,'LINE'}} = epp:open(File, [], PreDefMacros) end(), @@ -1160,7 +1159,7 @@ otp_8388(Config) when is_list(Config) -> "test() -> ?BAR(1).\n">>, {errors,[{{4,12},epp,{undefined,'FOO',1}}],[]}} ], - ?line [] = compile(Config, Ts), + [] = compile(Config, Ts), ok. %% OTP-8470. Bugfix (one request - two replies). @@ -1168,11 +1167,11 @@ 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 = filename:join(Dir, "otp_8470.erl"), + ok = file:write_file(File, C), + {ok, _List} = epp:parse_file(File, [], []), file:delete(File), - ?line receive _ -> fail() after 0 -> ok end, + receive _ -> fail() after 0 -> ok end, ok. %% OTP-8562. Record with no fields is considered typed. @@ -1183,7 +1182,7 @@ otp_8562(Config) when is_list(Config) -> {errors,[{{1,60},epp,missing_parenthesis}, {{2,13},epp,missing_parenthesis}], []}} ], - ?line [] = compile(Config, Cs), + [] = compile(Config, Cs), ok. %% OTP-8911. -file and file inclusion bug. @@ -1195,8 +1194,8 @@ otp_8911(Config) when is_list(Config) -> do_otp_8911(Config) end. do_otp_8911(Config) -> - ?line {ok, CWD} = file:get_cwd(), - ?line ok = file:set_cwd(?config(priv_dir, Config)), + {ok, CWD} = file:get_cwd(), + ok = file:set_cwd(?config(priv_dir, Config)), File = "i.erl", Cont = <<"-module(i). @@ -1206,22 +1205,22 @@ do_otp_8911(Config) -> t() -> a. ">>, - ?line ok = file:write_file(File, Cont), + ok = file:write_file(File, Cont), Incl = <<"-file(\"fil2\", 35). t1() -> b. ">>, File1 = "i1.erl", - ?line ok = file:write_file(File1, Incl), + 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(), + {ok, i} = cover:compile(File), + a = i:t(), + {ok,[{{i,6},1}]} = cover:analyse(i, calls, line), + cover:stop(), file:delete(File), file:delete(File1), - ?line file:set_cwd(CWD), + file:set_cwd(CWD), ok. %% OTP-8665. Bugfix premature end. @@ -1230,7 +1229,7 @@ otp_8665(Config) when is_list(Config) -> <<"-define(A, a)\n">>, {errors,[{{1,54},epp,premature_end}],[]}} ], - ?line [] = compile(Config, Cs), + [] = compile(Config, Cs), ok. %% OTP-10302. Unicode characters scanner/parser. @@ -1543,9 +1542,9 @@ check_test(Config, Test) -> compile_test(Config, Test0) -> Test = [<<"-module(epp_test). -compile(export_all). ">>, Test0], Filename = "epp_test.erl", - ?line PrivDir = ?config(priv_dir, Config), - ?line File = filename:join(PrivDir, Filename), - ?line ok = file:write_file(File, Test), + PrivDir = ?config(priv_dir, Config), + File = filename:join(PrivDir, Filename), + ok = file:write_file(File, Test), Opts = [export_all,return,nowarn_unused_record,{outdir,PrivDir}], case compile_file(File, Opts) of {ok, Ws} -> warnings(File, Ws); @@ -1597,14 +1596,14 @@ unopaque_forms(Forms) -> run_test(Config, Test0) -> Test = [<<"-module(epp_test). -compile(export_all). ">>, Test0], Filename = "epp_test.erl", - ?line PrivDir = ?config(priv_dir, Config), - ?line File = filename:join(PrivDir, Filename), - ?line ok = file:write_file(File, Test), + PrivDir = ?config(priv_dir, Config), + File = filename:join(PrivDir, Filename), + ok = file:write_file(File, Test), Opts = [return, {i,PrivDir},{outdir,PrivDir}], - ?line {ok, epp_test, []} = compile:file(File, Opts), + {ok, epp_test, []} = compile:file(File, Opts), AbsFile = filename:rootname(File, ".erl"), - ?line {module, epp_test} = code:load_abs(AbsFile, epp_test), - ?line Reply = epp_test:t(), + {module, epp_test} = code:load_abs(AbsFile, epp_test), + Reply = epp_test:t(), code:purge(epp_test), Reply. @@ -1643,5 +1642,5 @@ ln2(M) -> %% +fnu means a peer node has to be started; slave will not do start_node(Name, Xargs) -> - ?line PA = filename:dirname(code:which(?MODULE)), + PA = filename:dirname(code:which(?MODULE)), test_server:start_node(Name, peer, [{args, "-pa " ++ PA ++ " " ++ Xargs}]). |