diff options
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r-- | lib/stdlib/test/Makefile | 1 | ||||
-rw-r--r-- | lib/stdlib/test/epp_SUITE.erl | 52 | ||||
-rw-r--r-- | lib/stdlib/test/erl_lint_SUITE.erl | 40 | ||||
-rw-r--r-- | lib/stdlib/test/erl_pp_SUITE.erl | 97 | ||||
-rw-r--r-- | lib/stdlib/test/erl_scan_SUITE.erl | 285 | ||||
-rw-r--r-- | lib/stdlib/test/qlc_SUITE.erl | 15 | ||||
-rw-r--r-- | lib/stdlib/test/shell_SUITE.erl | 11 |
7 files changed, 308 insertions, 193 deletions
diff --git a/lib/stdlib/test/Makefile b/lib/stdlib/test/Makefile index a271229c59..9bf10ea494 100644 --- a/lib/stdlib/test/Makefile +++ b/lib/stdlib/test/Makefile @@ -23,6 +23,7 @@ MODULES= \ dummy_via \ edlin_expand_SUITE \ epp_SUITE \ + erl_anno_SUITE \ erl_eval_SUITE \ erl_expand_records_SUITE \ erl_internal_SUITE \ diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl index b17e8bd186..9ab170c826 100644 --- a/lib/stdlib/test/epp_SUITE.erl +++ b/lib/stdlib/test/epp_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1998-2014. All Rights Reserved. +%% Copyright Ericsson AB 1998-2015. 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 @@ -211,7 +211,7 @@ 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, LineCol1, l, Line1}, + {attribute, Anno, l, Line1}, {attribute, _, f, File}, {attribute, _, machine1, _}, {attribute, _, module, mac3}, @@ -219,13 +219,9 @@ predef_mac(Config) when is_list(Config) -> {attribute, _, ms, "mac3"}, {attribute, _, machine2, _} | _] = List, - ?line case LineCol1 of - Line1 -> ok; - {Line1,_} -> ok - end, + Line1 = erl_anno:line(Anno), ok. - variable_1(doc) -> []; variable_1(suite) -> @@ -553,11 +549,7 @@ otp_7702(Config) when is_list(Config) -> {ok, AC} = beam_lib:chunks(BeamFile, [abstract_code]), {file_7702,[{abstract_code,{_,Forms}}]} = AC, - Fun = fun(Attrs) -> - {line, L} = erl_parse:get_attribute(Attrs, line), - L - end, - Forms2 = [erl_lint:modify_line(Form, Fun) || Form <- Forms], + Forms2 = unopaque_forms(Forms), ?line [{attribute,1,file,_}, _, @@ -1395,9 +1387,10 @@ otp_10820(Config) when is_list(Config) -> do_otp_10820(File, C, PC) -> {ok,Node} = start_node(erl_pp_helper, "+fnu " ++ PC), ok = rpc:call(Node, file, write_file, [File, C]), - {ok,[{attribute,1,file,{File,1}}, - {attribute,2,module,any}, - {eof,2}]} = rpc:call(Node, epp, parse_file, [File, [],[]]), + {ok, Forms} = rpc:call(Node, epp, parse_file, [File, [],[]]), + [{attribute,1,file,{File,1}}, + {attribute,2,module,any}, + {eof,2}] = unopaque_forms(Forms), true = test_server:stop_node(Node), ok. @@ -1440,15 +1433,15 @@ encoding(Config) when is_list(Config) -> {attribute,1,module,encoding}, {error,_}, {error,{2,epp,cannot_parse}}, - {eof,2}]} = epp:parse_file(ErlFile, []), + {eof,2}]} = epp_parse_file(ErlFile, []), {ok,[{attribute,1,file,_}, {attribute,1,module,encoding}, {eof,3}]} = - epp:parse_file(ErlFile, [{default_encoding,latin1}]), + epp_parse_file(ErlFile, [{default_encoding,latin1}]), {ok,[{attribute,1,file,_}, {attribute,1,module,encoding}, {eof,3}],[{encoding,none}]} = - epp:parse_file(ErlFile, [{default_encoding,latin1},extra]), + epp_parse_file(ErlFile, [{default_encoding,latin1},extra]), %% Try a latin-1 file with encoding given in a comment. C2 = <<"-module(encoding). @@ -1459,27 +1452,27 @@ encoding(Config) when is_list(Config) -> {ok,[{attribute,1,file,_}, {attribute,1,module,encoding}, {eof,4}]} = - epp:parse_file(ErlFile, []), + epp_parse_file(ErlFile, []), {ok,[{attribute,1,file,_}, {attribute,1,module,encoding}, {eof,4}]} = - epp:parse_file(ErlFile, [{default_encoding,latin1}]), + epp_parse_file(ErlFile, [{default_encoding,latin1}]), {ok,[{attribute,1,file,_}, {attribute,1,module,encoding}, {eof,4}]} = - epp:parse_file(ErlFile, [{default_encoding,utf8}]), + epp_parse_file(ErlFile, [{default_encoding,utf8}]), {ok,[{attribute,1,file,_}, {attribute,1,module,encoding}, {eof,4}],[{encoding,latin1}]} = - epp:parse_file(ErlFile, [extra]), + epp_parse_file(ErlFile, [extra]), {ok,[{attribute,1,file,_}, {attribute,1,module,encoding}, {eof,4}],[{encoding,latin1}]} = - epp:parse_file(ErlFile, [{default_encoding,latin1},extra]), + epp_parse_file(ErlFile, [{default_encoding,latin1},extra]), {ok,[{attribute,1,file,_}, {attribute,1,module,encoding}, {eof,4}],[{encoding,latin1}]} = - epp:parse_file(ErlFile, [{default_encoding,utf8},extra]), + epp_parse_file(ErlFile, [{default_encoding,utf8},extra]), ok. @@ -1552,6 +1545,17 @@ errs([_|L], File) -> errs([], _File) -> []. +epp_parse_file(File, Opts) -> + case epp:parse_file(File, Opts) of + {ok, Forms} -> + {ok, unopaque_forms(Forms)}; + {ok, Forms, Other} -> + {ok, unopaque_forms(Forms), Other} + end. + +unopaque_forms(Forms) -> + [erl_parse:anno_to_term(Form) || Form <- Forms]. + run_test(Config, Test0) -> Test = [<<"-module(epp_test). -compile(export_all). ">>, Test0], Filename = "epp_test.erl", diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl index a7c3fd3c2e..c0d9b7c466 100644 --- a/lib/stdlib/test/erl_lint_SUITE.erl +++ b/lib/stdlib/test/erl_lint_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1999-2014. All Rights Reserved. +%% Copyright Ericsson AB 1999-2015. 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 @@ -64,7 +64,7 @@ too_many_arguments/1, basic_errors/1,bin_syntax_errors/1, predef/1, - maps/1,maps_type/1,otp_11851/1 + maps/1,maps_type/1,otp_11851/1,otp_12195/1 ]). % Default timetrap timeout (set in init_per_testcase). @@ -93,7 +93,7 @@ all() -> bif_clash, behaviour_basic, behaviour_multiple, otp_11861, otp_7550, otp_8051, format_warn, {group, on_load}, too_many_arguments, basic_errors, bin_syntax_errors, predef, - maps, maps_type, otp_11851]. + maps, maps_type, otp_11851, otp_12195]. groups() -> [{unused_vars_warn, [], @@ -3834,6 +3834,40 @@ otp_11851(Config) when is_list(Config) -> [] = run(Config, Ts), ok. +otp_12195(doc) -> + "OTP-12195: Check obsolete types (tailor made for OTP 18)."; +otp_12195(Config) when is_list(Config) -> + Ts = [{otp_12195_1, + <<"-export_type([r1/0]). + -type r1() :: erl_scan:line() + | erl_scan:column() + | erl_scan:location() + | erl_anno:line().">>, + [], + {warnings,[{2,erl_lint, + {deprecated_type,{erl_scan,line,0}, + "deprecated (will be removed in OTP 19); " + "use erl_anno:line() instead"}}, + {3,erl_lint, + {deprecated_type,{erl_scan,column,0}, + "deprecated (will be removed in OTP 19); use " + "erl_anno:column() instead"}}, + {4,erl_lint, + {deprecated_type,{erl_scan,location,0}, + "deprecated (will be removed in OTP 19); " + "use erl_anno:location() instead"}}]}}, + {otp_12195_2, + <<"-export_type([r1/0]). + -compile(nowarn_deprecated_type). + -type r1() :: erl_scan:line() + | erl_scan:column() + | erl_scan:location() + | erl_anno:line().">>, + [], + []}], + [] = run(Config, Ts), + ok. + run(Config, Tests) -> F = fun({N,P,Ws,E}, BadL) -> case catch run_test(Config, P, Ws) of diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl index f71446dd64..1d63c8e17e 100644 --- a/lib/stdlib/test/erl_pp_SUITE.erl +++ b/lib/stdlib/test/erl_pp_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2006-2014. All Rights Reserved. +%% Copyright Ericsson AB 2006-2015. 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 @@ -490,7 +490,7 @@ cond1(Config) when is_list(Config) -> [{cons,3,{atom,3,a},{cons,3,{atom,3,b},{nil,3}}}]}, {clause,4,[],[[{atom,4,true}]], [{tuple,5,[{atom,5,x},{atom,5,y}]}]}]}, - ?line CChars = lists:flatten(erl_pp:expr(C)), + CChars = flat_expr1(C), % ?line "cond {foo,bar} -> [a,b]; true -> {x,y} end" = CChars, ?line "cond\n" " {foo,bar} ->\n" @@ -557,7 +557,7 @@ messages(Config) when is_list(Config) -> lists:flatten(erl_pp:form({error,{some,"error"}})), ?line true = "{warning,{some,\"warning\"}}\n" =:= lists:flatten(erl_pp:form({warning,{some,"warning"}})), - ?line true = "\n" =:= lists:flatten(erl_pp:form({eof,0})), + "\n" = flat_form({eof,0}), ok. import_export(suite) -> @@ -616,27 +616,29 @@ hook(Config) when is_list(Config) -> do_hook(HookFun) -> Lc = parse_expr(binary_to_list(<<"[X || X <- [1,2,3]].">>)), H = HookFun(fun hook/4), - Expr = {call,0,{atom,0,fff},[{foo,Lc},{foo,Lc},{foo,Lc}]}, + A0 = erl_anno:new(0), + Expr = {call,A0,{atom,A0,fff},[{foo,Lc},{foo,Lc},{foo,Lc}]}, EChars = lists:flatten(erl_pp:expr(Expr, 0, H)), - Call = {call,0,{atom,0,foo},[Lc]}, - Expr2 = {call,0,{atom,0,fff},[Call,Call,Call]}, + Call = {call,A0,{atom,A0,foo},[Lc]}, + Expr2 = {call,A0,{atom,A0,fff},[Call,Call,Call]}, EChars2 = erl_pp:exprs([Expr2]), ?line true = EChars =:= lists:flatten(EChars2), EsChars = erl_pp:exprs([Expr], H), ?line true = EChars =:= lists:flatten(EsChars), - F = {function,1,ffff,0,[{clause,1,[],[],[Expr]}]}, + A1 = erl_anno:new(1), + F = {function,A1,ffff,0,[{clause,A1,[],[],[Expr]}]}, FuncChars = lists:flatten(erl_pp:function(F, H)), - F2 = {function,1,ffff,0,[{clause,1,[],[],[Expr2]}]}, + F2 = {function,A1,ffff,0,[{clause,A1,[],[],[Expr2]}]}, FuncChars2 = erl_pp:function(F2), ?line true = FuncChars =:= lists:flatten(FuncChars2), FFormChars = erl_pp:form(F, H), ?line true = FuncChars =:= lists:flatten(FFormChars), - A = {attribute,1,record,{r,[{record_field,1,{atom,1,a},Expr}]}}, + A = {attribute,A1,record,{r,[{record_field,A1,{atom,A1,a},Expr}]}}, AChars = lists:flatten(erl_pp:attribute(A, H)), - A2 = {attribute,1,record,{r,[{record_field,1,{atom,1,a},Expr2}]}}, + A2 = {attribute,A1,record,{r,[{record_field,A1,{atom,A1,a},Expr2}]}}, AChars2 = erl_pp:attribute(A2), ?line true = AChars =:= lists:flatten(AChars2), AFormChars = erl_pp:form(A, H), @@ -645,10 +647,10 @@ do_hook(HookFun) -> ?line "INVALID-FORM:{foo,bar}:" = lists:flatten(erl_pp:expr({foo,bar})), %% A list (as before R6), not a list of lists. - G = [{op,1,'>',{atom,1,a},{foo,{atom,1,b}}}], % not a proper guard + G = [{op,A1,'>',{atom,A1,a},{foo,{atom,A1,b}}}], % not a proper guard GChars = lists:flatten(erl_pp:guard(G, H)), - G2 = [{op,1,'>',{atom,1,a}, - {call,0,{atom,0,foo},[{atom,1,b}]}}], % not a proper guard + G2 = [{op,A1,'>',{atom,A1,a}, + {call,A0,{atom,A0,foo},[{atom,A1,b}]}}], % not a proper guard GChars2 = erl_pp:guard(G2), ?line true = GChars =:= lists:flatten(GChars2), @@ -659,14 +661,14 @@ do_hook(HookFun) -> ?line true = EChars =:= lists:flatten(XEChars2), %% Note: no leading spaces before "begin". - Block = {block,0,[{match,0,{var,0,'A'},{integer,0,3}}, - {atom,0,true}]}, + Block = {block,A0,[{match,A0,{var,A0,'A'},{integer,A0,3}}, + {atom,A0,true}]}, ?line "begin\n A =" ++ _ = lists:flatten(erl_pp:expr(Block, 17, none)), %% Special... ?line true = - "{some,value}" =:= lists:flatten(erl_pp:expr({value,0,{some,value}})), + "{some,value}" =:= lists:flatten(erl_pp:expr({value,A0,{some,value}})), %% Silly... ?line true = @@ -674,8 +676,8 @@ do_hook(HookFun) -> flat_expr({'if',0,[{clause,0,[],[],[{atom,0,0}]}]}), %% More compatibility: before R6 - OldIf = {'if',0,[{clause,0,[],[{atom,0,true}],[{atom,0,b}]}]}, - NewIf = {'if',0,[{clause,0,[],[[{atom,0,true}]],[{atom,0,b}]}]}, + OldIf = {'if',A0,[{clause,A0,[],[{atom,A0,true}],[{atom,A0,b}]}]}, + NewIf = {'if',A0,[{clause,A0,[],[[{atom,A0,true}]],[{atom,A0,b}]}]}, OldIfChars = lists:flatten(erl_pp:expr(OldIf)), NewIfChars = lists:flatten(erl_pp:expr(NewIf)), ?line true = OldIfChars =:= NewIfChars, @@ -691,7 +693,8 @@ ehook(HE, I, P, H, foo, bar) -> hook(HE, I, P, H). hook({foo,E}, I, P, H) -> - erl_pp:expr({call,0,{atom,0,foo},[E]}, I, P, H). + A = erl_anno:new(0), + erl_pp:expr({call,A,{atom,A,foo},[E]}, I, P, H). neg_indent(suite) -> []; @@ -774,7 +777,7 @@ otp_6911(Config) when is_list(Config) -> {var,6,'X'}, [{clause,7,[{atom,7,true}],[],[{integer,7,12}]}, {clause,8,[{atom,8,false}],[],[{integer,8,14}]}]}]}]}, - ?line Chars = lists:flatten(erl_pp:form(F)), + Chars = flat_form(F), ?line "thomas(X) ->\n" " case X of\n" " true ->\n" @@ -1084,10 +1087,11 @@ otp_10302(Config) when is_list(Config) -> Opts = [{hook, fun unicode_hook/4},{encoding,unicode}], Lc = parse_expr("[X || X <- [\"\x{400}\",\"\xFF\"]]."), - Expr = {call,0,{atom,0,fff},[{foo,{foo,Lc}},{foo,{foo,Lc}}]}, + A0 = erl_anno:new(0), + Expr = {call,A0,{atom,A0,fff},[{foo,{foo,Lc}},{foo,{foo,Lc}}]}, EChars = lists:flatten(erl_pp:expr(Expr, 0, Opts)), - Call = {call,0,{atom,0,foo},[{call,0,{atom,0,foo},[Lc]}]}, - Expr2 = {call,0,{atom,0,fff},[Call,Call]}, + Call = {call,A0,{atom,A0,foo},[{call,A0,{atom,A0,foo},[Lc]}]}, + Expr2 = {call,A0,{atom,A0,fff},[Call,Call]}, EChars2 = erl_pp:exprs([Expr2], U), EChars = lists:flatten(EChars2), [$\x{400},$\x{400}] = [C || C <- EChars, C > 255], @@ -1097,7 +1101,8 @@ otp_10302(Config) when is_list(Config) -> ok. unicode_hook({foo,E}, I, P, H) -> - erl_pp:expr({call,0,{atom,0,foo},[E]}, I, P, H). + A = erl_anno:new(0), + erl_pp:expr({call,A,{atom,A,foo},[E]}, I, P, H). otp_10820(doc) -> "OTP-10820. Unicode filenames."; @@ -1137,29 +1142,30 @@ otp_11100(Config) when is_list(Config) -> %% Cannot trigger the use of the hook function with export/import. "-export([{fy,a}/b]).\n" = pf({attribute,1,export,[{{fy,a},b}]}), + A1 = erl_anno:new(1), "-type foo() :: integer(INVALID-FORM:{foo,bar}:).\n" = - pf({attribute,1,type,{foo,{type,1,integer,[{foo,bar}]},[]}}), - pf({attribute,1,type, - {a,{type,1,range,[{integer,1,1},{foo,bar}]},[]}}), + pf({attribute,A1,type,{foo,{type,A1,integer,[{foo,bar}]},[]}}), + pf({attribute,A1,type, + {a,{type,A1,range,[{integer,A1,1},{foo,bar}]},[]}}), "-type foo(INVALID-FORM:{foo,bar}:) :: A.\n" = - pf({attribute,1,type,{foo,{var,1,'A'},[{foo,bar}]}}), + pf({attribute,A1,type,{foo,{var,A1,'A'},[{foo,bar}]}}), "-type foo() :: (INVALID-FORM:{foo,bar}: :: []).\n" = - pf({attribute,1,type, - {foo,{paren_type,1, - [{ann_type,1,[{foo,bar},{type,1,nil,[]}]}]}, + pf({attribute,A1,type, + {foo,{paren_type,A1, + [{ann_type,A1,[{foo,bar},{type,A1,nil,[]}]}]}, []}}), "-type foo() :: <<_:INVALID-FORM:{foo,bar}:>>.\n" = - pf({attribute,1,type, - {foo,{type,1,binary,[{foo,bar},{integer,1,0}]},[]}}), + pf({attribute,A1,type, + {foo,{type,A1,binary,[{foo,bar},{integer,A1,0}]},[]}}), "-type foo() :: <<_:10, _:_*INVALID-FORM:{foo,bar}:>>.\n" = - pf({attribute,1,type, - {foo,{type,1,binary,[{integer,1,10},{foo,bar}]},[]}}), + pf({attribute,A1,type, + {foo,{type,A1,binary,[{integer,A1,10},{foo,bar}]},[]}}), "-type foo() :: #r{INVALID-FORM:{foo,bar}: :: integer()}.\n" = - pf({attribute,1,type, - {foo,{type,1,record, - [{atom,1,r}, - {type,1,field_type, - [{foo,bar},{type,1,integer,[]}]}]}, + pf({attribute,A1,type, + {foo,{type,A1,record, + [{atom,A1,r}, + {type,A1,field_type, + [{foo,bar},{type,A1,integer,[]}]}]}, []}}), ok. @@ -1239,9 +1245,18 @@ strip_module_info(Bin) -> <<R:Start/binary,_/binary>> = Bin, R. -flat_expr(Expr) -> +flat_expr1(Expr0) -> + Expr = erl_parse:new_anno(Expr0), + lists:flatten(erl_pp:expr(Expr)). + +flat_expr(Expr0) -> + Expr = erl_parse:new_anno(Expr0), lists:flatten(erl_pp:expr(Expr, -1, none)). +flat_form(Form0) -> + Form = erl_parse:new_anno(Form0), + lists:flatten(erl_pp:form(Form)). + pp_forms(Bin) -> pp_forms(Bin, none). diff --git a/lib/stdlib/test/erl_scan_SUITE.erl b/lib/stdlib/test/erl_scan_SUITE.erl index 6ef947f0e3..fb85055b6c 100644 --- a/lib/stdlib/test/erl_scan_SUITE.erl +++ b/lib/stdlib/test/erl_scan_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1998-2014. All Rights Reserved. +%% Copyright Ericsson AB 1998-2015. 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 @@ -138,7 +138,7 @@ iso88591(Config) when is_list(Config) -> A1s = [$h,$ä,$r], A2s = [$ö,$r,$e], %% Test parsing atom and variable characters. - {ok,Ts1,_} = erl_scan:string(V1s ++ " " ++ V2s ++ + {ok,Ts1,_} = erl_scan_string(V1s ++ " " ++ V2s ++ "\327" ++ A1s ++ " " ++ A2s), V1s = atom_to_list(element(3, nth(1, Ts1))), @@ -151,7 +151,7 @@ iso88591(Config) when is_list(Config) -> %% Test parsing and printing strings. S1 = V1s ++ "\327" ++ A1s ++ "\250" ++ A2s, S1s = "\"" ++ S1 ++ "\"", - {ok,Ts2,_} = erl_scan:string(S1s), + {ok,Ts2,_} = erl_scan_string(S1s), S1 = element(3, nth(1, Ts2)), S1s = flatten(print(element(3, nth(1, Ts2)))), ok %It all worked @@ -219,7 +219,7 @@ atoms() -> test_string([39,65,200,39], [{atom,{1,1},'AÈ'}]), test_string("ärlig östen", [{atom,{1,1},ärlig},{atom,{1,7},östen}]), ?line {ok,[{atom,_,'$a'}],{1,6}} = - erl_scan:string("'$\\a'", {1,1}), + erl_scan_string("'$\\a'", {1,1}), ?line test("'$\\a'"), ok. @@ -268,24 +268,24 @@ punctuations() -> comments() -> ?line test("a %%\n b"), - ?line {ok,[],1} = erl_scan:string("%"), + {ok,[],1} = erl_scan_string("%"), ?line test("a %%\n b"), {ok,[{atom,{1,1},a},{atom,{2,2},b}],{2,3}} = - erl_scan:string("a %%\n b",{1,1}), + erl_scan_string("a %%\n b", {1,1}), {ok,[{atom,{1,1},a},{comment,{1,3},"%%"},{atom,{2,2},b}],{2,3}} = - erl_scan:string("a %%\n b",{1,1}, [return_comments]), + erl_scan_string("a %%\n b",{1,1}, [return_comments]), {ok,[{atom,{1,1},a}, {white_space,{1,2}," "}, {white_space,{1,5},"\n "}, {atom,{2,2},b}], {2,3}} = - erl_scan:string("a %%\n b",{1,1},[return_white_spaces]), + erl_scan_string("a %%\n b",{1,1},[return_white_spaces]), {ok,[{atom,{1,1},a}, {white_space,{1,2}," "}, {comment,{1,3},"%%"}, {white_space,{1,5},"\n "}, {atom,{2,2},b}], - {2,3}} = erl_scan:string("a %%\n b",{1,1},[return]), + {2,3}} = erl_scan_string("a %%\n b",{1,1},[return]), ok. errors() -> @@ -337,11 +337,11 @@ base_integers() -> erl_scan:string(Str) end || {BS,S} <- [{"3","3"},{"15","f"}, {"12","c"}] ], - ?line {ok,[{integer,1,239},{'@',1}],1} = erl_scan:string("16#ef@"), + {ok,[{integer,1,239},{'@',1}],1} = erl_scan_string("16#ef@"), {ok,[{integer,{1,1},239},{'@',{1,6}}],{1,7}} = - erl_scan:string("16#ef@", {1,1}, []), + erl_scan_string("16#ef@", {1,1}, []), {ok,[{integer,{1,1},14},{atom,{1,5},g@}],{1,7}} = - erl_scan:string("16#eg@", {1,1}, []), + erl_scan_string("16#eg@", {1,1}, []), ok. @@ -382,8 +382,8 @@ dots() -> {ok,[{'.',{1,1}},{atom,{1,2},a}],{1,3}}} ], [begin - R = erl_scan:string(S), - R2 = erl_scan:string(S, {1,1}, []) + R = erl_scan_string(S), + R2 = erl_scan_string(S, {1,1}, []) end || {S, R, R2} <- Dot], ?line {ok,[{dot,_}=T1],{1,2}} = erl_scan:string(".", {1,1}, text), @@ -417,7 +417,7 @@ dots() -> {white_space,{1,4},"\n"}, {dot,{2,1}}], {2,3}}, ""} = - erl_scan:tokens(C, "\n. ", {1,1}, return), % any loc, any options + erl_scan_tokens(C, "\n. ", {1,1}, return), % any loc, any options ?line [test_string(S, R) || {S, R} <- [{".$\n", [{'.',{1,1}},{char,{1,2},$\n}]}, @@ -511,7 +511,7 @@ eof() -> %% An error before R13A. %% ?line {done,Err={error,{1,erl_scan,scan},1},eof} = ?line {done,{ok,[{atom,1,abra}],1},eof} = - erl_scan:tokens(C2, eof, 1), + erl_scan_tokens(C2, eof, 1), %% With column. ?line {more, C3} = erl_scan:tokens([]," \n",{1,1}), @@ -520,7 +520,7 @@ eof() -> %% An error before R13A. %% ?line {done,{error,{{1,1},erl_scan,scan},{1,5}},eof} = ?line {done,{ok,[{atom,_,abra}],{1,5}},eof} = - erl_scan:tokens(C4, eof, 1), + erl_scan_tokens(C4, eof, 1), %% Robert's scanner returns "" as LeftoverChars; %% the R12B scanner returns eof as LeftoverChars: (eof is correct) @@ -528,26 +528,26 @@ eof() -> %% An error before R13A. %% ?line {done,{error,{1,erl_scan,scan},1},eof} = ?line {done,{ok,[{atom,1,a}],1},eof} = - erl_scan:tokens(C5,eof,1), + erl_scan_tokens(C5,eof,1), %% With column. {more, C6} = erl_scan:tokens([], "a", {1,1}), %% An error before R13A. %% {done,{error,{1,erl_scan,scan},1},eof} = {done,{ok,[{atom,{1,1},a}],{1,2}},eof} = - erl_scan:tokens(C6,eof,1), + erl_scan_tokens(C6,eof,1), %% A dot followed by eof is special: ?line {more, C} = erl_scan:tokens([], "a.", 1), - ?line {done,{ok,[{atom,1,a},{dot,1}],1},eof} = erl_scan:tokens(C,eof,1), - ?line {ok,[{atom,1,foo},{dot,1}],1} = erl_scan:string("foo."), + {done,{ok,[{atom,1,a},{dot,1}],1},eof} = erl_scan_tokens(C,eof,1), + {ok,[{atom,1,foo},{dot,1}],1} = erl_scan_string("foo."), %% With column. {more, CCol} = erl_scan:tokens([], "a.", {1,1}), {done,{ok,[{atom,{1,1},a},{dot,{1,2}}],{1,3}},eof} = - erl_scan:tokens(CCol,eof,1), + erl_scan_tokens(CCol,eof,1), {ok,[{atom,{1,1},foo},{dot,{1,4}}],{1,5}} = - erl_scan:string("foo.", {1,1}, []), + erl_scan_string("foo.", {1,1}, []), ok. @@ -628,23 +628,23 @@ crashes() -> options() -> %% line and column are not options, but tested here ?line {ok,[{atom,1,foo},{white_space,1," "},{comment,1,"% bar"}], 1} = - erl_scan:string("foo % bar", 1, return), + erl_scan_string("foo % bar", 1, return), ?line {ok,[{atom,1,foo},{white_space,1," "}],1} = - erl_scan:string("foo % bar", 1, return_white_spaces), + erl_scan_string("foo % bar", 1, return_white_spaces), ?line {ok,[{atom,1,foo},{comment,1,"% bar"}],1} = - erl_scan:string("foo % bar", 1, return_comments), + erl_scan_string("foo % bar", 1, return_comments), ?line {ok,[{atom,17,foo}],17} = - erl_scan:string("foo % bar", 17), + erl_scan_string("foo % bar", 17), ?line {'EXIT',{function_clause,_}} = (catch {foo, erl_scan:string("foo % bar", {a,1}, [])}), % type error ?line {ok,[{atom,_,foo}],{17,18}} = - erl_scan:string("foo % bar", {17,9}, []), + erl_scan_string("foo % bar", {17,9}, []), ?line {'EXIT',{function_clause,_}} = (catch {foo, erl_scan:string("foo % bar", {1,0}, [])}), % type error ?line {ok,[{foo,1}],1} = - erl_scan:string("foo % bar",1, [{reserved_word_fun, + erl_scan_string("foo % bar",1, [{reserved_word_fun, fun(W) -> W =:= foo end}]), ?line {'EXIT',{badarg,_}} = (catch {foo, @@ -706,8 +706,9 @@ token_info() -> attributes_info() -> ?line {'EXIT',_} = (catch {foo,erl_scan:attributes_info(foo)}), % type error - ?line [{line,18}] = erl_scan:attributes_info(18), - ?line {location,19} = erl_scan:attributes_info(19, location), + [{line,18}] = erl_scan:attributes_info(erl_anno:new(18)), + {location,19} = + erl_scan:attributes_info(erl_anno:new(19), location), ?line {ok,[{atom,A0,foo}],_} = erl_scan:string("foo", 19, [text]), ?line {location,19} = erl_scan:attributes_info(A0, location), @@ -735,7 +736,9 @@ attributes_info() -> set_attribute() -> F = fun(Line) -> -Line end, - ?line -2 = erl_scan:set_attribute(line, 2, F), + Anno2 = erl_anno:new(2), + A0 = erl_scan:set_attribute(line, Anno2, F), + {line, -2} = erl_scan:attributes_info(A0, line), ?line {ok,[{atom,A1,foo}],_} = erl_scan:string("foo", {9,17}), ?line A2 = erl_scan:set_attribute(line, A1, F), ?line {line,-9} = erl_scan:attributes_info(A2, line), @@ -765,10 +768,15 @@ set_attribute() -> ?line {ok,[{atom,A6,foo}],_} = erl_scan:string("foo", 11, [text]), ?line A7 = erl_scan:set_attribute(line, A6, F2), - ?line {line,{17,11}} = erl_scan:attributes_info(A7, line), + %% Incompatible with pre 18: + %% {line,{17,11}} = erl_scan:attributes_info(A7, line), + {line,17} = erl_scan:attributes_info(A7, line), ?line {location,{17,11}} = % mixed up erl_scan:attributes_info(A7, location), - ?line [{line,{17,11}},{text,"foo"}] = + %% Incompatible with pre 18: + %% [{line,{17,11}},{text,"foo"}] = + %% erl_scan:attributes_info(A7, [line,column,text]), + [{line,17},{column,11},{text,"foo"}] = erl_scan:attributes_info(A7, [line,column,text]), ?line {'EXIT',_} = @@ -776,9 +784,13 @@ set_attribute() -> ?line {'EXIT',{badarg,_}} = (catch {foo, erl_scan:set_attribute(column, [], F2)}), % type error + Attr10 = erl_anno:new(8), + Attr20 = erl_scan:set_attribute(line, Attr10, + fun(L) -> {nos,'X',L} end), %% OTP-9412 - ?line 8 = erl_scan:set_attribute(line, [{line,{nos,'X',8}}], - fun({nos,_V,VL}) -> VL end), + Attr30 = erl_scan:set_attribute(line, Attr20, + fun({nos,_V,VL}) -> VL end), + 8 = erl_anno:to_term(Attr30), ok. column_errors() -> @@ -812,7 +824,7 @@ white_spaces() -> {white_space,_," "}, {atom,_,a}, {white_space,_,"\n"}], - _} = erl_scan:string("\r a\n", {1,1}, return), + _} = erl_scan_string("\r a\n", {1,1}, return), ?line test("\r a\n"), L = "{\"a\nb\", \"a\\nb\",\nabc\r,def}.\n\n", ?line {ok,[{'{',_}, @@ -829,7 +841,7 @@ white_spaces() -> {'}',_}, {dot,_}, {white_space,_,"\n"}], - _} = erl_scan:string(L, {1,1}, return), + _} = erl_scan_string(L, {1,1}, return), ?line test(L), ?line test("\"\n\"\n"), ?line test("\n\r\n"), @@ -846,7 +858,7 @@ white_spaces() -> unicode() -> ?line {ok,[{char,1,83},{integer,1,45}],1} = - erl_scan:string("$\\12345"), % not unicode + erl_scan_string("$\\12345"), % not unicode ?line {error,{1,erl_scan,{illegal,character}},1} = erl_scan:string([1089]), @@ -858,7 +870,7 @@ unicode() -> erl_scan:string("'a"++[1089]++"b'", {1,1}), ?line test("\"a"++[1089]++"b\""), {ok,[{char,1,1}],1} = - erl_scan:string([$$,$\\,$^,1089], 1), + erl_scan_string([$$,$\\,$^,1089], 1), {error,{1,erl_scan,Error},1} = erl_scan:string("\"qa\x{aaa}", 1), @@ -870,13 +882,13 @@ unicode() -> erl_scan:string("'qa\\x{aaa}'",{1,1}), {ok,[{char,1,1089}],1} = - erl_scan:string([$$,1089], 1), + erl_scan_string([$$,1089], 1), {ok,[{char,1,1089}],1} = - erl_scan:string([$$,$\\,1089], 1), + erl_scan_string([$$,$\\,1089], 1), Qs = "$\\x{aaa}", {ok,[{char,1,$\x{aaa}}],1} = - erl_scan:string(Qs, 1), + erl_scan_string(Qs, 1), {ok,[Q2],{1,9}} = erl_scan:string("$\\x{aaa}", {1,1}, [text]), [{category,char},{column,1},{length,8}, @@ -884,19 +896,19 @@ unicode() -> erl_scan:token_info(Q2), U1 = "\"\\x{aaa}\"", - {ok, - [{string,[{line,1},{column,1},{text,"\"\\x{aaa}\""}],[2730]}], - {1,10}} = erl_scan:string(U1, {1,1}, [text]), - {ok,[{string,1,[2730]}],1} = erl_scan:string(U1, 1), + {ok,[{string,A1,[2730]}],{1,10}} = erl_scan:string(U1, {1,1}, [text]), + [{line,1},{column,1},{text,"\"\\x{aaa}\""}] = + erl_scan:attributes_info(A1, [line, column, text]), + {ok,[{string,1,[2730]}],1} = erl_scan_string(U1, 1), U2 = "\"\\x41\\x{fff}\\x42\"", - {ok,[{string,1,[$\x41,$\x{fff},$\x42]}],1} = erl_scan:string(U2, 1), + {ok,[{string,1,[$\x41,$\x{fff},$\x42]}],1} = erl_scan_string(U2, 1), U3 = "\"a\n\\x{fff}\n\"", - {ok,[{string,1,[$a,$\n,$\x{fff},$\n]}],3} = erl_scan:string(U3, 1), + {ok,[{string,1,[$a,$\n,$\x{fff},$\n]}],3} = erl_scan_string(U3, 1), U4 = "\"\\^\n\\x{aaa}\\^\n\"", - {ok,[{string,1,[$\n,$\x{aaa},$\n]}],3} = erl_scan:string(U4, 1), + {ok,[{string,1,[$\n,$\x{aaa},$\n]}],3} = erl_scan_string(U4, 1), %% Keep these tests: ?line test(Qs), @@ -906,15 +918,15 @@ unicode() -> ?line test(U4), Str1 = "\"ab" ++ [1089] ++ "cd\"", - {ok,[{string,1,[$a,$b,1089,$c,$d]}],1} = erl_scan:string(Str1, 1), + {ok,[{string,1,[$a,$b,1089,$c,$d]}],1} = erl_scan_string(Str1, 1), {ok,[{string,{1,1},[$a,$b,1089,$c,$d]}],{1,8}} = - erl_scan:string(Str1, {1,1}), + erl_scan_string(Str1, {1,1}), ?line test(Str1), Comment = "%% "++[1089], {ok,[{comment,1,[$%,$%,$\s,1089]}],1} = - erl_scan:string(Comment, 1, [return]), + erl_scan_string(Comment, 1, [return]), {ok,[{comment,{1,1},[$%,$%,$\s,1089]}],{1,5}} = - erl_scan:string(Comment, {1,1}, [return]), + erl_scan_string(Comment, {1,1}, [return]), ok. more_chars() -> @@ -923,12 +935,12 @@ more_chars() -> %% All kinds of tests... ?line {ok,[{char,_,123}],{1,4}} = - erl_scan:string("$\\{",{1,1}), + erl_scan_string("$\\{",{1,1}), ?line {more, C1} = erl_scan:tokens([], "$\\{", {1,1}), ?line {done,{ok,[{char,_,123}],{1,4}},eof} = - erl_scan:tokens(C1, eof, 1), + erl_scan_tokens(C1, eof, 1), ?line {ok,[{char,1,123},{atom,1,a},{'}',1}],1} = - erl_scan:string("$\\{a}"), + erl_scan_string("$\\{a}"), ?line {error,{{1,1},erl_scan,char},{1,4}} = erl_scan:string("$\\x", {1,1}), @@ -993,11 +1005,11 @@ otp_10302(Config) when is_list(Config) -> {error,{{1,1},erl_scan,{illegal,atom}},{1,12}} = erl_scan:string("'qa\\x{aaa}'",{1,1}), - {ok,[{char,1,1089}],1} = erl_scan:string([$$,1089], 1), - {ok,[{char,1,1089}],1} = erl_scan:string([$$,$\\,1089],1), + {ok,[{char,1,1089}],1} = erl_scan_string([$$,1089], 1), + {ok,[{char,1,1089}],1} = erl_scan_string([$$,$\\,1089],1), Qs = "$\\x{aaa}", - {ok,[{char,1,2730}],1} = erl_scan:string(Qs,1), + {ok,[{char,1,2730}],1} = erl_scan_string(Qs, 1), {ok,[Q2],{1,9}} = erl_scan:string(Qs,{1,1},[text]), [{category,char},{column,1},{length,8}, {line,1},{symbol,16#aaa},{text,Qs}] = @@ -1011,19 +1023,19 @@ otp_10302(Config) when is_list(Config) -> {symbol,[16#aaa]},{text,U1}] = erl_scan:token_info(T1, Tags), U2 = "\"\\x41\\x{fff}\\x42\"", - {ok,[{string,1,[65,4095,66]}],1} = erl_scan:string(U2, 1), + {ok,[{string,1,[65,4095,66]}],1} = erl_scan_string(U2, 1), U3 = "\"a\n\\x{fff}\n\"", - {ok,[{string,1,[97,10,4095,10]}],3} = erl_scan:string(U3, 1), + {ok,[{string,1,[97,10,4095,10]}],3} = erl_scan_string(U3, 1), U4 = "\"\\^\n\\x{aaa}\\^\n\"", - {ok,[{string,1,[10,2730,10]}],3} = erl_scan:string(U4, 1,[]), + {ok,[{string,1,[10,2730,10]}],3} = erl_scan_string(U4, 1,[]), Str1 = "\"ab" ++ [1089] ++ "cd\"", {ok,[{string,1,[97,98,1089,99,100]}],1} = - erl_scan:string(Str1,1), + erl_scan_string(Str1,1), {ok,[{string,{1,1},[97,98,1089,99,100]}],{1,8}} = - erl_scan:string(Str1, {1,1}), + erl_scan_string(Str1, {1,1}), OK1 = 16#D800-1, OK2 = 16#DFFF+1, @@ -1038,19 +1050,19 @@ otp_10302(Config) when is_list(Config) -> IllegalL = [Illegal1,Illegal2,Illegal3,Illegal4], [{ok,[{comment,1,[$%,$%,$\s,OK]}],1} = - erl_scan:string("%% "++[OK], 1, [return]) || + erl_scan_string("%% "++[OK], 1, [return]) || OK <- OKL], {ok,[{comment,_,[$%,$%,$\s,OK1]}],{1,5}} = - erl_scan:string("%% "++[OK1], {1,1}, [return]), + erl_scan_string("%% "++[OK1], {1,1}, [return]), [{error,{1,erl_scan,{illegal,character}},1} = erl_scan:string("%% "++[Illegal], 1, [return]) || Illegal <- IllegalL], {error,{{1,1},erl_scan,{illegal,character}},{1,5}} = erl_scan:string("%% "++[Illegal1], {1,1}, [return]), - [{ok,[],1} = erl_scan:string("%% "++[OK], 1, []) || + [{ok,[],1} = erl_scan_string("%% "++[OK], 1, []) || OK <- OKL], - {ok,[],{1,5}} = erl_scan:string("%% "++[OK1], {1,1}, []), + {ok,[],{1,5}} = erl_scan_string("%% "++[OK1], {1,1}, []), [{error,{1,erl_scan,{illegal,character}},1} = erl_scan:string("%% "++[Illegal], 1, []) || Illegal <- IllegalL], @@ -1058,7 +1070,7 @@ otp_10302(Config) when is_list(Config) -> erl_scan:string("%% "++[Illegal1], {1,1}, []), [{ok,[{string,{1,1},[OK]}],{1,4}} = - erl_scan:string("\""++[OK]++"\"",{1,1}) || + erl_scan_string("\""++[OK]++"\"",{1,1}) || OK <- OKL], [{error,{{1,2},erl_scan,{illegal,character}},{1,3}} = erl_scan:string("\""++[OK]++"\"",{1,1}) || @@ -1069,93 +1081,93 @@ otp_10302(Config) when is_list(Config) -> Illegal <- IllegalL], {ok,[{char,{1,1},OK1}],{1,3}} = - erl_scan:string([$$,OK1],{1,1}), + erl_scan_string([$$,OK1],{1,1}), {error,{{1,1},erl_scan,{illegal,character}},{1,2}} = erl_scan:string([$$,Illegal1],{1,1}), {ok,[{char,{1,1},OK1}],{1,4}} = - erl_scan:string([$$,$\\,OK1],{1,1}), + erl_scan_string([$$,$\\,OK1],{1,1}), {error,{{1,1},erl_scan,{illegal,character}},{1,4}} = erl_scan:string([$$,$\\,Illegal1],{1,1}), {ok,[{string,{1,1},[55295]}],{1,5}} = - erl_scan:string("\"\\"++[OK1]++"\"",{1,1}), + erl_scan_string("\"\\"++[OK1]++"\"",{1,1}), {error,{{1,2},erl_scan,{illegal,character}},{1,4}} = erl_scan:string("\"\\"++[Illegal1]++"\"",{1,1}), {ok,[{char,{1,1},OK1}],{1,10}} = - erl_scan:string("$\\x{D7FF}",{1,1}), + erl_scan_string("$\\x{D7FF}",{1,1}), {error,{{1,1},erl_scan,{illegal,character}},{1,10}} = erl_scan:string("$\\x{D800}",{1,1}), %% Not erl_scan, but erl_parse. - {integer,0,1} = erl_parse:abstract(1), - Float = 3.14, {float,0,Float} = erl_parse:abstract(Float), - {nil,0} = erl_parse:abstract([]), + {integer,0,1} = erl_parse_abstract(1), + Float = 3.14, {float,0,Float} = erl_parse_abstract(Float), + {nil,0} = erl_parse_abstract([]), {bin,0, [{bin_element,0,{integer,0,1},default,default}, {bin_element,0,{integer,0,2},default,default}]} = - erl_parse:abstract(<<1,2>>), + erl_parse_abstract(<<1,2>>), {cons,0,{tuple,0,[{atom,0,a}]},{atom,0,b}} = - erl_parse:abstract([{a} | b]), - {string,0,"str"} = erl_parse:abstract("str"), + erl_parse_abstract([{a} | b]), + {string,0,"str"} = erl_parse_abstract("str"), {cons,0, {integer,0,$a}, {cons,0,{integer,0,55296},{string,0,"c"}}} = - erl_parse:abstract("a"++[55296]++"c"), + erl_parse_abstract("a"++[55296]++"c"), Line = 17, - {integer,Line,1} = erl_parse:abstract(1, Line), - Float = 3.14, {float,Line,Float} = erl_parse:abstract(Float, Line), - {nil,Line} = erl_parse:abstract([], Line), + {integer,Line,1} = erl_parse_abstract(1, Line), + Float = 3.14, {float,Line,Float} = erl_parse_abstract(Float, Line), + {nil,Line} = erl_parse_abstract([], Line), {bin,Line, [{bin_element,Line,{integer,Line,1},default,default}, {bin_element,Line,{integer,Line,2},default,default}]} = - erl_parse:abstract(<<1,2>>, Line), + erl_parse_abstract(<<1,2>>, Line), {cons,Line,{tuple,Line,[{atom,Line,a}]},{atom,Line,b}} = - erl_parse:abstract([{a} | b], Line), - {string,Line,"str"} = erl_parse:abstract("str", Line), + erl_parse_abstract([{a} | b], Line), + {string,Line,"str"} = erl_parse_abstract("str", Line), {cons,Line, {integer,Line,$a}, {cons,Line,{integer,Line,55296},{string,Line,"c"}}} = - erl_parse:abstract("a"++[55296]++"c", Line), + erl_parse_abstract("a"++[55296]++"c", Line), Opts1 = [{line,17}], - {integer,Line,1} = erl_parse:abstract(1, Opts1), - Float = 3.14, {float,Line,Float} = erl_parse:abstract(Float, Opts1), - {nil,Line} = erl_parse:abstract([], Opts1), + {integer,Line,1} = erl_parse_abstract(1, Opts1), + Float = 3.14, {float,Line,Float} = erl_parse_abstract(Float, Opts1), + {nil,Line} = erl_parse_abstract([], Opts1), {bin,Line, [{bin_element,Line,{integer,Line,1},default,default}, {bin_element,Line,{integer,Line,2},default,default}]} = - erl_parse:abstract(<<1,2>>, Opts1), + erl_parse_abstract(<<1,2>>, Opts1), {cons,Line,{tuple,Line,[{atom,Line,a}]},{atom,Line,b}} = - erl_parse:abstract([{a} | b], Opts1), - {string,Line,"str"} = erl_parse:abstract("str", Opts1), + erl_parse_abstract([{a} | b], Opts1), + {string,Line,"str"} = erl_parse_abstract("str", Opts1), {cons,Line, {integer,Line,$a}, {cons,Line,{integer,Line,55296},{string,Line,"c"}}} = - erl_parse:abstract("a"++[55296]++"c", Opts1), + erl_parse_abstract("a"++[55296]++"c", Opts1), [begin - {integer,Line,1} = erl_parse:abstract(1, Opts2), - Float = 3.14, {float,Line,Float} = erl_parse:abstract(Float, Opts2), - {nil,Line} = erl_parse:abstract([], Opts2), + {integer,Line,1} = erl_parse_abstract(1, Opts2), + Float = 3.14, {float,Line,Float} = erl_parse_abstract(Float, Opts2), + {nil,Line} = erl_parse_abstract([], Opts2), {bin,Line, [{bin_element,Line,{integer,Line,1},default,default}, {bin_element,Line,{integer,Line,2},default,default}]} = - erl_parse:abstract(<<1,2>>, Opts2), + erl_parse_abstract(<<1,2>>, Opts2), {cons,Line,{tuple,Line,[{atom,Line,a}]},{atom,Line,b}} = - erl_parse:abstract([{a} | b], Opts2), - {string,Line,"str"} = erl_parse:abstract("str", Opts2), + erl_parse_abstract([{a} | b], Opts2), + {string,Line,"str"} = erl_parse_abstract("str", Opts2), {string,Line,[97,1024,99]} = - erl_parse:abstract("a"++[1024]++"c", Opts2) + erl_parse_abstract("a"++[1024]++"c", Opts2) end || Opts2 <- [[{encoding,unicode},{line,Line}], [{encoding,utf8},{line,Line}]]], {cons,0, {integer,0,97}, {cons,0,{integer,0,1024},{string,0,"c"}}} = - erl_parse:abstract("a"++[1024]++"c", [{encoding,latin1}]), + erl_parse_abstract("a"++[1024]++"c", [{encoding,latin1}]), ok. otp_10990(doc) -> @@ -1172,13 +1184,13 @@ otp_10992(suite) -> []; otp_10992(Config) when is_list(Config) -> {cons,0,{float,0,42.0},{nil,0}} = - erl_parse:abstract([42.0], [{encoding,unicode}]), + erl_parse_abstract([42.0], [{encoding,unicode}]), {cons,0,{float,0,42.0},{nil,0}} = - erl_parse:abstract([42.0], [{encoding,utf8}]), + erl_parse_abstract([42.0], [{encoding,utf8}]), {cons,0,{integer,0,65},{cons,0,{float,0,42.0},{nil,0}}} = - erl_parse:abstract([$A,42.0], [{encoding,unicode}]), + erl_parse_abstract([$A,42.0], [{encoding,unicode}]), {cons,0,{integer,0,65},{cons,0,{float,0,42.0},{nil,0}}} = - erl_parse:abstract([$A,42.0], [{encoding,utf8}]), + erl_parse_abstract([$A,42.0], [{encoding,utf8}]), ok. otp_11807(doc) -> @@ -1187,29 +1199,72 @@ otp_11807(suite) -> []; otp_11807(Config) when is_list(Config) -> {cons,0,{integer,0,97},{cons,0,{integer,0,98},{nil,0}}} = - erl_parse:abstract("ab", [{encoding,none}]), + erl_parse_abstract("ab", [{encoding,none}]), {cons,0,{integer,0,-1},{nil,0}} = - erl_parse:abstract([-1], [{encoding,latin1}]), + erl_parse_abstract([-1], [{encoding,latin1}]), ASCII = fun(I) -> I >= 0 andalso I < 128 end, - {string,0,"xyz"} = erl_parse:abstract("xyz", [{encoding,ASCII}]), + {string,0,"xyz"} = erl_parse_abstract("xyz", [{encoding,ASCII}]), {cons,0,{integer,0,228},{nil,0}} = - erl_parse:abstract([228], [{encoding,ASCII}]), + erl_parse_abstract([228], [{encoding,ASCII}]), {cons,0,{integer,0,97},{atom,0,a}} = - erl_parse:abstract("a"++a, [{encoding,latin1}]), + erl_parse_abstract("a"++a, [{encoding,latin1}]), {'EXIT', {{badarg,bad},_}} = % minor backward incompatibility (catch erl_parse:abstract("string", [{encoding,bad}])), ok. test_string(String, ExpectedWithCol) -> - {ok, ExpectedWithCol, _EndWithCol} = erl_scan:string(String, {1, 1}, []), + {ok, ExpectedWithCol, _EndWithCol} = erl_scan_string(String, {1, 1}, []), Expected = [ begin {L,_C} = element(2, T), setelement(2, T, L) end || T <- ExpectedWithCol ], - {ok, Expected, _End} = erl_scan:string(String), + {ok, Expected, _End} = erl_scan_string(String), test(String). +erl_scan_string(String) -> + erl_scan_string(String, 1, []). + +erl_scan_string(String, StartLocation) -> + erl_scan_string(String, StartLocation, []). + +erl_scan_string(String, StartLocation, Options) -> + case erl_scan:string(String, StartLocation, Options) of + {ok, Tokens, EndLocation} -> + {ok, unopaque_tokens(Tokens), EndLocation}; + Else -> + Else + end. + +erl_scan_tokens(C, S, L) -> + erl_scan_tokens(C, S, L, []). + +erl_scan_tokens(C, S, L, O) -> + case erl_scan:tokens(C, S, L, O) of + {done, {ok, Ts, End}, R} -> + {done, {ok, unopaque_tokens(Ts), End}, R}; + Else -> + Else + end. + +unopaque_tokens([]) -> + []; +unopaque_tokens([Token|Tokens]) -> + Attrs = element(2, Token), + Term = erl_anno:to_term(Attrs), + T = setelement(2, Token, Term), + [T | unopaque_tokens(Tokens)]. + +erl_parse_abstract(Term) -> + erl_parse_abstract(Term, []). + +erl_parse_abstract(Term, Options) -> + Abstr = erl_parse:abstract(Term, Options), + unopaque_abstract(Abstr). + +unopaque_abstract(Abstr) -> + erl_parse:anno_to_term(Abstr). + %% test_string(String, Expected, StartLocation, Options) -> %% {ok, Expected, _End} = erl_scan:string(String, StartLocation, Options), %% test(String). @@ -1359,7 +1414,7 @@ select_tokens(Tokens, Tags) -> simplify([Token|Tokens]) -> {line,Line} = erl_scan:token_info(Token, line), - [setelement(2, Token, Line) | simplify(Tokens)]; + [setelement(2, Token, erl_anno:new(Line)) | simplify(Tokens)]; simplify([]) -> []. diff --git a/lib/stdlib/test/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl index 0a1b6dd2ba..e5ea61a48c 100644 --- a/lib/stdlib/test/qlc_SUITE.erl +++ b/lib/stdlib/test/qlc_SUITE.erl @@ -2487,8 +2487,11 @@ info(Config) when is_list(Config) -> (catch qlc:info([X || {X} <- []], {n_elements, 0})), L = lists:seq(1, 1000), \"[1,2,3,4,5,6,7,8,9,10|'...']\" = qlc:info(L, {n_elements, 10}), - {cons,1,{integer,1,1},{atom,1,'...'}} = + {cons,A1,{integer,A2,1},{atom,A3,'...'}} = qlc:info(L, [{n_elements, 1},{format,abstract_code}]), + 1 = erl_anno:line(A1), + 1 = erl_anno:line(A2), + 1 = erl_anno:line(A3), Q = qlc:q([{X} || X <- [a,b,c,d,e,f]]), {call,_,_,[{cons,_,{atom,_,a},{cons,_,{atom,_,b},{cons,_,{atom,_,c}, {atom,_,'...'}}}}, @@ -6825,7 +6828,8 @@ otp_6674(Config) when is_list(Config) -> A == 192, B =:= 192.0, {Y} <- [{0},{1},{2}], X == Y]), - {block,0, + A0 = erl_anno:new(0), + {block,A0, [{match,_,_, {call,_,_, [{lc,_,_, @@ -7395,7 +7399,8 @@ try_old_join_info(Config) -> {ok, M} = compile:file(File, [{outdir, ?datadir}]), {module, M} = code:load_abs(filename:rootname(File)), H = M:create_handle(), - {block,0, + A0 = erl_anno:new(0), + {block,A0, [{match,_,_, {call,_,_, [{lc,_,_, @@ -7775,8 +7780,8 @@ table(List, Indices, KeyPos, ParentFun) -> end, FormatFun = fun(all) -> - L = 17, - {call,L,{remote,L,{atom,1,?MODULE},{atom,L,the_list}}, + L = erl_anno:new(17), + {call,L,{remote,L,{atom,L,?MODULE},{atom,L,the_list}}, [erl_parse:abstract(List, 17)]}; ({lookup, Column, Values}) -> {?MODULE, list_keys, [Values, Column, List]} diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl index f841e2c4a6..7c18560498 100644 --- a/lib/stdlib/test/shell_SUITE.erl +++ b/lib/stdlib/test/shell_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2004-2013. All Rights Reserved. +%% Copyright Ericsson AB 2004-2015. 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 @@ -404,13 +404,14 @@ records(Config) when is_list(Config) -> ?line ok = file:write_file(Test, Contents), RR5 = "rr(\"" ++ Test ++ "\", '_', {d,test1}), rl([test1,test2]).", - ?line [{attribute,1,record,{test1,_}},ok] = scan(RR5), + A1 = erl_anno:new(1), + [{attribute,A1,record,{test1,_}},ok] = scan(RR5), RR6 = "rr(\"" ++ Test ++ "\", '_', {d,test2}), rl([test1,test2]).", - ?line [{attribute,1,record,{test2,_}},ok] = scan(RR6), + [{attribute,A1,record,{test2,_}},ok] = scan(RR6), RR7 = "rr(\"" ++ Test ++ "\", '_', [{d,test1},{d,test2,17}]), rl([test1,test2]).", - ?line [{attribute,1,record,{test1,_}},{attribute,1,record,{test2,_}}, - ok] = scan(RR7), + [{attribute,A1,record,{test1,_}},{attribute,A1,record,{test2,_}},ok] = + scan(RR7), ?line PreReply = scan(<<"rr(prim_file).">>), % preloaded... ?line true = is_list(PreReply), ?line Dir = filename:join(?config(priv_dir, Config), "*.erl"), |