From 2f4f61352a5f6a0b73c3fe250c1293a1fbdb425b Mon Sep 17 00:00:00 2001 From: Anthony Ramine Date: Sat, 25 Aug 2012 11:40:51 +0200 Subject: [PATCH 01/14] Create a new "file" token attribute in erl_scan Used to properly zip file and line information in erl_lint without breaking the attributes() type. --- lib/stdlib/doc/src/erl_scan.xml | 17 +++++++-- lib/stdlib/src/erl_lint.erl | 27 ++++++++------ lib/stdlib/src/erl_scan.erl | 60 ++++++++++++++++++++++++++---- lib/stdlib/test/erl_scan_SUITE.erl | 31 +++++++++++++++ 4 files changed, 111 insertions(+), 24 deletions(-) diff --git a/lib/stdlib/doc/src/erl_scan.xml b/lib/stdlib/doc/src/erl_scan.xml index 54240dea19d2..cfaa1702d242 100644 --- a/lib/stdlib/doc/src/erl_scan.xml +++ b/lib/stdlib/doc/src/erl_scan.xml @@ -284,6 +284,9 @@ column()}

The column where the token begins.

+ {file, string()} +

The file in which the token is.

+
{length, integer() > 0}

The length of the token's text.

@@ -351,6 +354,9 @@ column()}

The column where the token begins.

+ {file, string()} +

The file in which the token is.

+
{length, integer() > 0}

The length of the token's text.

@@ -373,11 +379,14 @@ Set a token attribute value -

Sets the value of the line attribute of the token - attributes Attributes.

+

Sets the value of the line or file attribute of the + token attributes Attributes.

The SetAttributeFun is called with the value of - the line attribute, and is to return the new value of - the line attribute.

+ the line or file attribute, and is to return its new + value.

+

When setting the value of the file attribute, + SetAttributeFun may be given or return + undefined as an absence of value.

diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index 648ff349a4af..8059c91bcf60 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -595,12 +595,9 @@ add_warning(FileLine, W, St) -> add_warning({Location,erl_lint,W}, St#lint{file = File}). loc(L) -> - case erl_parse:get_attribute(L, location) of - {location,{{File,Line},Column}} -> - {File,{Line,Column}}; - {location,{File,Line}} -> - {File,Line} - end. + {file,File} = erl_parse:get_attribute(L, file), + {location,Loc} = erl_parse:get_attribute(L, location), + {File,Loc}. %% forms([Form], State) -> State' @@ -653,8 +650,8 @@ eval_file_attr([], _File) -> []. zip_file_and_line(T, File) -> - F0 = fun(Line) -> {File,Line} end, - F = fun(L) -> erl_parse:set_line(L, F0) end, + F0 = fun(_OldFile) -> File end, + F = fun(Attrs) -> erl_scan:set_attribute(file, Attrs, F0) end, modify_line(T, F). %% form(Form, State) -> State' @@ -817,10 +814,16 @@ not_deprecated(Forms, St0) -> %% The nowarn_bif_clash directive is not only deprecated, it's actually an error from R14A disallowed_compile_flags(Forms, St0) -> %% There are (still) no line numbers in St0#lint.compile. - Errors0 = [ {St0#lint.file,{L,erl_lint,disallowed_nowarn_bif_clash}} || - {attribute,[{line,{_,L}}],compile,nowarn_bif_clash} <- Forms ], - Errors1 = [ {St0#lint.file,{L,erl_lint,disallowed_nowarn_bif_clash}} || - {attribute,[{line,{_,L}}],compile,{nowarn_bif_clash, {_,_}}} <- Forms ], + Errors0 = [ begin + {location,Loc} = erl_scan:attributes_info(Attrs, location), + {St0#lint.file,{Loc,erl_lint,disallowed_nowarn_bif_clash}} + end || + {attribute,Attrs,compile,nowarn_bif_clash} <- Forms ], + Errors1 = [ begin + {location,Loc} = erl_scan:attributes_info(Attrs, location), + {St0#lint.file,{Loc,erl_lint,disallowed_nowarn_bif_clash}} + end || + {attribute,Attrs,compile,{nowarn_bif_clash, {_,_}}} <- Forms ], Disabled = (not is_warn_enabled(bif_clash, St0)), Errors = if Disabled andalso Errors0 =:= [] -> diff --git a/lib/stdlib/src/erl_scan.erl b/lib/stdlib/src/erl_scan.erl index 8e59e01f4800..af68ef806b3e 100644 --- a/lib/stdlib/src/erl_scan.erl +++ b/lib/stdlib/src/erl_scan.erl @@ -79,7 +79,8 @@ -type symbol() :: atom() | float() | integer() | string(). -type info_line() :: integer() | term(). -type attributes_data() - :: [{'column', column()} | {'line', info_line()} | {'text', string()}] + :: [{'column', column()} | {'line', info_line()} | {'text', string()} + | {'file', string()}] | {line(), column()}. %% The fact that {line(),column()} is a possible attributes() type %% is hidden. @@ -184,12 +185,13 @@ tokens({erl_scan_continuation,Cs,Col,Toks,Line,St,Any,Fun}, tokens1(Cs++CharSpec, St, Line, Col, Toks, Fun, Any). -type attribute_item() :: 'column' | 'length' | 'line' - | 'location' | 'text'. + | 'location' | 'text' | 'file'. -type info_location() :: location() | term(). -type attribute_info() :: {'column', column()}| {'length', pos_integer()} | {'line', info_line()} | {'location', info_location()} - | {'text', string()}. + | {'text', string()} + | {'file', string()}. -type token_item() :: 'category' | 'symbol' | attribute_item(). -type token_info() :: {'category', category()} | {'symbol', symbol()} | attribute_info(). @@ -198,7 +200,7 @@ tokens({erl_scan_continuation,Cs,Col,Toks,Line,St,Any,Fun}, Token :: token(), TokenInfo :: [TokenInfoTuple :: token_info()]. token_info(Token) -> - Items = [category,column,length,line,symbol,text], % undefined order + Items = [category,column,length,line,symbol,text,file], % undefined order token_info(Token, Items). -spec token_info(Token, TokenItem) -> TokenInfo | 'undefined' when @@ -236,7 +238,7 @@ token_info({_Category,Attrs,_Symbol}, Item) -> Attributes :: attributes(), AttributesInfo :: [AttributeInfoTuple :: attribute_info()]. attributes_info(Attributes) -> - Items = [column,length,line,text], % undefined order + Items = [column,length,line,text,file], % undefined order attributes_info(Attributes, Items). -spec attributes_info(Attributes, AttributeItem) -> @@ -302,13 +304,19 @@ attributes_info(Line, text) when ?ALINE(Line) -> undefined; attributes_info(Attrs, text=Item) -> attr_info(Attrs, Item); +attributes_info({Line,Column}, file) when ?ALINE(Line), ?COLUMN(Column) -> + undefined; +attributes_info(Line, file) when ?ALINE(Line) -> + undefined; +attributes_info(Attrs, file=Item) -> + attr_info(Attrs, Item); attributes_info(T1, T2) -> erlang:error(badarg, [T1,T2]). -spec set_attribute(AttributeItem, Attributes, SetAttributeFun) -> Attributes when - AttributeItem :: 'line', + AttributeItem :: 'line' | 'file', Attributes :: attributes(), - SetAttributeFun :: fun((info_line()) -> info_line()). + SetAttributeFun :: fun((term()) -> term()). set_attribute(Tag, Attributes, Fun) when ?SETATTRFUN(Fun) -> set_attr(Tag, Attributes, Fun). @@ -388,7 +396,10 @@ attr_info(Attrs, Item) -> erlang:error(badarg, [Attrs, Item]) end. --spec set_attr('line', attributes(), fun((line()) -> line())) -> attributes(). +-spec set_attr('line', attributes(), fun((line()) -> line())) -> attributes(); + ('file', attributes(), + fun(('undefined' | string()) -> 'undefined' | string())) + -> attributes(). set_attr(line, Line, Fun) when ?ALINE(Line) -> Ln = Fun(Line), @@ -414,6 +425,39 @@ set_attr(line=Tag, Attrs, Fun) when is_list(Attrs) -> As -> As end; +set_attr(file, Line, Fun) when ?ALINE(Line) -> + case Fun(undefined) of + undefined -> + Line; + File -> + [{file,File},{line,Line}] + end; +set_attr(file, {Line,Column}=Loc, Fun) when ?ALINE(Line), ?COLUMN(Column) -> + case Fun(undefined) of + undefined -> + Loc; + File -> + [{file,File},{line,Line},{column,Column}] + end; +set_attr(file=Tag, Attrs, Fun) when is_list(Attrs) -> + case lists:keyfind(Tag, 1, Attrs) of + {file, OldFile} -> + case Fun(OldFile) of + undefined -> + lists:keydelete(Tag, 1, Attrs); + OldFile -> + Attrs; + File -> + lists:keyreplace(Tag, 1, Attrs, {Tag,File}) + end; + false -> + case Fun(undefined) of + undefined -> + Attrs; + File -> + [{file,File}|Attrs] + end + end; set_attr(T1, T2, T3) -> erlang:error(badarg, [T1,T2,T3]). diff --git a/lib/stdlib/test/erl_scan_SUITE.erl b/lib/stdlib/test/erl_scan_SUITE.erl index 4298b2c701aa..5819938d7d13 100644 --- a/lib/stdlib/test/erl_scan_SUITE.erl +++ b/lib/stdlib/test/erl_scan_SUITE.erl @@ -741,6 +741,37 @@ set_attribute() -> %% OTP-9412 ?line 8 = erl_scan:set_attribute(line, [{line,{nos,'X',8}}], fun({nos,_V,VL}) -> VL end), + + % file + ?line 8 = erl_scan:set_attribute(file, 8, + fun (undefined) -> undefined end), + ?line {8,1} = erl_scan:set_attribute(file, {8,1}, + fun (undefined) -> undefined end), + ?line [{line,8},{text,""}] = + erl_scan:set_attribute(file, [{line,8},{text,""}], + fun (undefined) -> undefined end), + ?line [{line,8},{column,1},{text,""}] = + erl_scan:set_attribute(file, [{line,8},{column,1},{text,""}], + fun (undefined) -> undefined end), + ?line [{file,"file.erl"},{line,8}] = + erl_scan:set_attribute(file, 8, + fun (undefined) -> "file.erl" end), + ?line [{file,"file.erl"},{line,8},{column,1}] = + erl_scan:set_attribute(file, {8,1}, + fun (undefined) -> "file.erl" end), + ?line [{line,8}] = + erl_scan:set_attribute(file, [{file,"file.erl"},{line,8}], + fun ("file.erl") -> undefined end), + ?line [{line,8},{column,1}] = + erl_scan:set_attribute(file, [{file,"file.erl"},{line,8},{column,1}], + fun ("file.erl") -> undefined end), + ?line [{file,"file2.erl"},{line,8}] = + erl_scan:set_attribute(file, [{file,"file.erl"},{line,8}], + fun ("file.erl") -> "file2.erl" end), + ?line [{file,"file2.erl"},{line,8},{column,1}] = + erl_scan:set_attribute(file, [{file,"file.erl"},{line,8},{column,1}], + fun ("file.erl") -> "file2.erl" end), + ok. column_errors() -> From a79026758b6d1f59d1315fdcd16c0e549f453a41 Mon Sep 17 00:00:00 2001 From: Anthony Ramine Date: Sat, 25 Aug 2012 21:40:30 +0200 Subject: [PATCH 02/14] Handle column numbers in erl_scan test suite --- lib/stdlib/test/erl_scan_SUITE.erl | 216 +++++++++++++++++------------ 1 file changed, 129 insertions(+), 87 deletions(-) diff --git a/lib/stdlib/test/erl_scan_SUITE.erl b/lib/stdlib/test/erl_scan_SUITE.erl index 5819938d7d13..30c4f8de0dd3 100644 --- a/lib/stdlib/test/erl_scan_SUITE.erl +++ b/lib/stdlib/test/erl_scan_SUITE.erl @@ -202,7 +202,7 @@ reserved_words() -> [begin ?line {RW, true} = {RW, erl_scan:reserved_word(RW)}, S = atom_to_list(RW), - Ts = [{RW,1}], + Ts = [{RW,{1,1}}], ?line test_string(S, Ts) end || RW <- L], ok. @@ -210,12 +210,12 @@ reserved_words() -> atoms() -> ?line test_string("a - b", [{atom,1,a},{atom,2,b}]), - ?line test_string("'a b'", [{atom,1,'a b'}]), - ?line test_string("a", [{atom,1,a}]), - ?line test_string("a@2", [{atom,1,a@2}]), - ?line test_string([39,65,200,39], [{atom,1,'AÈ'}]), - ?line test_string("ärlig östen", [{atom,1,ärlig},{atom,1,östen}]), + b", [{atom,{1,1},a},{atom,{2,18},b}]), + ?line test_string("'a b'", [{atom,{1,1},'a b'}]), + ?line test_string("a", [{atom,{1,1},a}]), + ?line test_string("a@2", [{atom,{1,1},a@2}]), + ?line test_string([39,65,200,39], [{atom,{1,1},'AÈ'}]), + ?line test_string("ärlig östen", [{atom,{1,1},ärlig},{atom,{1,7},östen}]), ?line {ok,[{atom,_,'$a'}],{1,6}} = erl_scan:string("'$\\a'", {1,1}), ?line test("'$\\a'"), @@ -228,7 +228,7 @@ punctuations() -> %% One token at a time: [begin W = list_to_atom(S), - Ts = [{W,1}], + Ts = [{W,{1,1}}], ?line test_string(S, Ts) end || S <- L], Three = ["/=:=", "<=:=", "==:=", ">=:="], % three tokens... @@ -244,53 +244,60 @@ punctuations() -> [begin W1 = list_to_atom(S1), W2 = list_to_atom(S2), - Ts = [{W1,1},{W2,1}], + Ts = [{W1,{1,1}},{W2,{1,-L2+1}}], ?line test_string(S, Ts) - end || {S,[{_,S1,S2}|_]} <- SL], + end || {S,[{L2,S1,S2}|_]} <- SL], - PTs1 = [{'!',1},{'(',1},{')',1},{',',1},{';',1},{'=',1},{'[',1}, - {']',1},{'{',1},{'|',1},{'}',1}], + PTs1 = [{'!',{1,1}},{'(',{1,2}},{')',{1,3}},{',',{1,4}},{';',{1,5}}, + {'=',{1,6}},{'[',{1,7}},{']',{1,8}},{'{',{1,9}},{'|',{1,10}}, + {'}',{1,11}}], ?line test_string("!(),;=[]{|}", PTs1), - PTs2 = [{'#',1},{'&',1},{'*',1},{'+',1},{'/',1}, - {':',1},{'<',1},{'>',1},{'?',1},{'@',1}, - {'\\',1},{'^',1},{'`',1},{'~',1}], + PTs2 = [{'#',{1,1}},{'&',{1,2}},{'*',{1,3}},{'+',{1,4}},{'/',{1,5}}, + {':',{1,6}},{'<',{1,7}},{'>',{1,8}},{'?',{1,9}},{'@',{1,10}}, + {'\\',{1,11}},{'^',{1,12}},{'`',{1,13}},{'~',{1,14}}], ?line test_string("#&*+/:<>?@\\^`~", PTs2), - ?line test_string(".. ", [{'..',1}]), - ?line test("1 .. 2"), - ?line test_string("...", [{'...',1}]), + ?line test_string(".. ", [{'..',{1,1}}]), + ?line test_string("1 .. 2", + [{integer,{1,1},1},{'..',{1,3}},{integer,{1,6},2}]), + ?line test_string("...", [{'...',{1,1}}]), ok. comments() -> ?line test("a %%\n b"), ?line {ok,[],1} = erl_scan:string("%"), ?line test("a %%\n b"), - ?line {ok,[{atom,_,a},{atom,_,b}],{2,3}} = + ?line {ok,[{atom,{1,1},a},{atom,{2,2},b}],{2,3}} = erl_scan:string("a %%\n b",{1,1}), - ?line {ok,[{atom,_,a},{comment,_,"%%"},{atom,_,b}],{2,3}} = + ?line {ok,[{atom,{1,1},a},{comment,{1,3},"%%"},{atom,{2,2},b}],{2,3}} = erl_scan:string("a %%\n b",{1,1}, [return_comments]), - ?line {ok,[{atom,_,a}, - {white_space,_," "}, - {white_space,_,"\n "}, - {atom,_,b}], + ?line {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]), - ?line {ok,[{atom,_,a}, - {white_space,_," "}, - {comment,_,"%%"}, - {white_space,_,"\n "}, - {atom,_,b}], + ?line {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]), ok. errors() -> ?line {error,{1,erl_scan,{string,$',"qa"}},1} = erl_scan:string("'qa"), %' + ?line {error,{{1,1},erl_scan,{string,$',"qa"}},{1,4}} = %' + erl_scan:string("'qa", {1,1}, []), %' ?line {error,{1,erl_scan,{string,$","str"}},1} = %" erl_scan:string("\"str"), %" + ?line {error,{{1,1},erl_scan,{string,$","str"}},{1,5}} = %" + erl_scan:string("\"str", {1,1}, []), %" ?line {error,{1,erl_scan,char},1} = erl_scan:string("$"), - ?line test_string([34,65,200,34], [{string,1,"AÈ"}]), - ?line test_string("\\", [{'\\',1}]), + ?line {error,{{1,1},erl_scan,char},{1,2}} = erl_scan:string("$", {1,1}, []), + ?line test_string([34,65,200,34], [{string,{1,1},"AÈ"}]), + ?line test_string("\\", [{'\\',{1,1}}]), ?line {'EXIT',_} = (catch {foo, erl_scan:string('$\\a', {1,1})}), % type error ?line {'EXIT',_} = @@ -302,7 +309,7 @@ errors() -> integers() -> [begin I = list_to_integer(S), - Ts = [{integer,1,I}], + Ts = [{integer,{1,1},I}], ?line test_string(S, Ts) end || S <- [[N] || N <- lists:seq($0, $9)] ++ ["2323","000"] ], ok. @@ -311,14 +318,16 @@ base_integers() -> [begin B = list_to_integer(BS), I = erlang:list_to_integer(S, B), - Ts = [{integer,1,I}], + Ts = [{integer,{1,1},I}], ?line test_string(BS++"#"++S, Ts) end || {BS,S} <- [{"2","11"}, {"5","23234"}, {"12","05a"}, {"16","abcdef"}, {"16","ABCDEF"}] ], ?line {error,{1,erl_scan,{base,1}},1} = erl_scan:string("1#000"), + ?line {error,{{1,1},erl_scan,{base,1}},{1,2}} = + erl_scan:string("1#000", {1,1}, []), - ?line test_string("12#bc", [{integer,1,11},{atom,1,c}]), + ?line test_string("12#bc", [{integer,{1,1},11},{atom,{1,5},c}]), [begin Str = BS ++ "#" ++ S, @@ -327,40 +336,53 @@ base_integers() -> end || {BS,S} <- [{"3","3"},{"15","f"}, {"12","c"}] ], ?line {ok,[{integer,1,239},{'@',1}],1} = erl_scan:string("16#ef@"), - ?line {ok,[{integer,1,14},{atom,1,g@}],1} = erl_scan:string("16#eg@"), + ?line {ok,[{integer,{1,1},239},{'@',{1,6}}],{1,7}} = + erl_scan:string("16#ef@", {1,1}, []), + ?line {ok,[{integer,{1,1},14},{atom,{1,5},g@}],{1,7}} = + erl_scan:string("16#eg@", {1,1}, []), ok. floats() -> [begin F = list_to_float(FS), - Ts = [{float,1,F}], + Ts = [{float,{1,1},F}], ?line test_string(FS, Ts) end || FS <- ["1.0","001.17","3.31200","1.0e0","1.0E17", "34.21E-18", "17.0E+14"]], - ?line test_string("1.e2", [{integer,1,1},{'.',1},{atom,1,e2}]), + ?line test_string("1.e2", [{integer,{1,1},1},{'.',{1,2}},{atom,{1,3},e2}]), ?line {error,{1,erl_scan,{illegal,float}},1} = erl_scan:string("1.0e400"), + ?line {error,{{1,1},erl_scan,{illegal,float}},{1,8}} = + erl_scan:string("1.0e400", {1,1}, []), [begin - ?line {error,{1,erl_scan,{illegal,float}},1} = erl_scan:string(S) + ?line {error,{1,erl_scan,{illegal,float}},1} = erl_scan:string(S), + ?line {error,{{1,1},erl_scan,{illegal,float}},{1,_}} = + erl_scan:string(S, {1,1}, []) end || S <- ["1.14Ea"]], ok. dots() -> - Dot = [{".", {ok,[{dot,1}],1}}, - {". ", {ok,[{dot,1}],1}}, - {".\n", {ok,[{dot,1}],2}}, - {".%", {ok,[{dot,1}],1}}, - {".\210",{ok,[{dot,1}],1}}, - {".% öh",{ok,[{dot,1}],1}}, - {".%\n", {ok,[{dot,1}],2}}, - {".$", {error,{1,erl_scan,char},1}}, - {".$\\", {error,{1,erl_scan,char},1}}, - {".a", {ok,[{'.',1},{atom,1,a}],1}} + Dot = [{".", {ok,[{dot,1}],1}, {ok,[{dot,{1,1}}],{1,2}}}, + {". ", {ok,[{dot,1}],1}, {ok,[{dot,{1,1}}],{1,3}}}, + {".\n", {ok,[{dot,1}],2}, {ok,[{dot,{1,1}}],{2,1}}}, + {".%", {ok,[{dot,1}],1}, {ok,[{dot,{1,1}}],{1,3}}}, + {".\210",{ok,[{dot,1}],1}, {ok,[{dot,{1,1}}],{1,3}}}, + {".% öh",{ok,[{dot,1}],1}, {ok,[{dot,{1,1}}],{1,6}}}, + {".%\n", {ok,[{dot,1}],2}, {ok,[{dot,{1,1}}],{2,1}}}, + {".$", {error,{1,erl_scan,char},1}, + {error,{{1,2},erl_scan,char},{1,3}}}, + {".$\\", {error,{1,erl_scan,char},1}, + {error,{{1,2},erl_scan,char},{1,4}}}, + {".a", {ok,[{'.',1},{atom,1,a}],1}, + {ok,[{'.',{1,1}},{atom,{1,2},a}],{1,3}}} ], - ?line [R = erl_scan:string(S) || {S, R} <- Dot], + ?line [begin + 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), ?line [{column,1},{length,1},{line,1},{text,"."}] = @@ -377,55 +399,55 @@ dots() -> ?line {error,{{1,2},erl_scan,char},{1,4}} = erl_scan:string(".$\\", {1,1}), - ?line test(". "), - ?line test(". "), - ?line test(".\n"), - ?line test(".\n\n"), - ?line test(".\n\r"), - ?line test(".\n\n\n"), - ?line test(".\210"), - ?line test(".%\n"), - ?line test(".a"), - - ?line test("%. \n. "), + ?line test_string(". ", [{dot,{1,1}}]), + ?line test_string(". ", [{dot,{1,1}}]), + ?line test_string(".\n", [{dot,{1,1}}]), + ?line test_string(".\n\n", [{dot,{1,1}}]), + ?line test_string(".\n\r", [{dot,{1,1}}]), + ?line test_string(".\n\n\n", [{dot,{1,1}}]), + ?line test_string(".\210", [{dot,{1,1}}]), + ?line test_string(".%\n", [{dot,{1,1}}]), + ?line test_string(".a", [{'.',{1,1}},{atom,{1,2},a}]), + + ?line test_string("%. \n. ", [{dot,{2,1}}]), ?line {more,C} = erl_scan:tokens([], "%. ",{1,1}, return), - ?line {done,{ok,[{comment,_,"%. "}, - {white_space,_,"\n"}, - {dot,_}], + ?line {done,{ok,[{comment,{1,1},"%. "}, + {white_space,{1,4},"\n"}, + {dot,{2,1}}], {2,3}}, ""} = erl_scan:tokens(C, "\n. ", {1,1}, return), % any loc, any options ?line [test_string(S, R) || - {S, R} <- [{".$\n", [{'.',1},{char,1,$\n}]}, - {"$\\\n", [{char,1,$\n}]}, - {"'\\\n'", [{atom,1,'\n'}]}, - {"$\n", [{char,1,$\n}]}] ], + {S, R} <- [{".$\n", [{'.',{1,1}},{char,{1,2},$\n}]}, + {"$\\\n", [{char,{1,1},$\n}]}, + {"'\\\n'", [{atom,{1,1},'\n'}]}, + {"$\n", [{char,{1,1},$\n}]}] ], ok. chars() -> [begin L = lists:flatten(io_lib:format("$\\~.8b", [C])), - Ts = [{char,1,C}], + Ts = [{char,{1,1},C}], ?line test_string(L, Ts) end || C <- lists:seq(0, 255)], %% Leading zeroes... [begin L = lists:flatten(io_lib:format("$\\~3.8.0b", [C])), - Ts = [{char,1,C}], + Ts = [{char,{1,1},C}], ?line test_string(L, Ts) end || C <- lists:seq(0, 255)], %% $\^\n now increments the line... [begin L = "$\\^" ++ [C], - Ts = [{char,1,C band 2#11111}], + Ts = [{char,{1,1},C band 2#11111}], ?line test_string(L, Ts) end || C <- lists:seq(0, 255)], [begin L = "$\\" ++ [C], - Ts = [{char,1,V}], + Ts = [{char,{1,1},V}], ?line test_string(L, Ts) end || {C,V} <- [{$n,$\n}, {$r,$\r}, {$t,$\t}, {$v,$\v}, {$b,$\b}, {$f,$\f}, {$e,$\e}, {$s,$\s}, @@ -438,45 +460,45 @@ chars() -> No = EC ++ Ds ++ X ++ New, [begin L = "$\\" ++ [C], - Ts = [{char,1,C}], + Ts = [{char,{1,1},C}], ?line test_string(L, Ts) end || C <- lists:seq(0, 255) -- No], [begin L = "'$\\" ++ [C] ++ "'", - Ts = [{atom,1,list_to_atom("$"++[C])}], + Ts = [{atom,{1,1},list_to_atom("$"++[C])}], ?line test_string(L, Ts) end || C <- lists:seq(0, 255) -- No], - ?line test_string("\"\\013a\\\n\"", [{string,1,"\va\n"}]), + ?line test_string("\"\\013a\\\n\"", [{string,{1,1},"\va\n"}]), - ?line test_string("'\n'", [{atom,1,'\n'}]), - ?line test_string("\"\n\a\"", [{string,1,"\na"}]), + ?line test_string("'\n'", [{atom,{1,1},'\n'}]), + ?line test_string("\"\n\a\"", [{string,{1,1},"\na"}]), %% No escape [begin L = "$" ++ [C], - Ts = [{char,1,C}], + Ts = [{char,{1,1},C}], ?line test_string(L, Ts) end || C <- lists:seq(0, 255) -- (No ++ [$\\])], - ?line test_string("$\n", [{char,1,$\n}]), + ?line test_string("$\n", [{char,{1,1},$\n}]), ?line {error,{{1,1},erl_scan,char},{1,4}} = erl_scan:string("$\\^",{1,1}), - ?line test_string("$\\\n", [{char,1,$\n}]), + ?line test_string("$\\\n", [{char,{1,1},$\n}]), %% Robert's scanner returns line 1: - ?line test_string("$\\\n", [{char,1,$\n}]), - ?line test_string("$\n\n", [{char,1,$\n}]), + ?line test_string("$\\\n", [{char,{1,1},$\n}]), + ?line test_string("$\n\n", [{char,{1,1},$\n}]), ?line test("$\n\n"), ok. variables() -> - ?line test_string(" \237_Aouåeiyäö", [{var,1,'_Aouåeiyäö'}]), - ?line test_string("A_b_c@", [{var,1,'A_b_c@'}]), - ?line test_string("V@2", [{var,1,'V@2'}]), - ?line test_string("ABDÀ", [{var,1,'ABDÀ'}]), - ?line test_string("Ärlig Östen", [{var,1,'Ärlig'},{var,1,'Östen'}]), + ?line test_string(" \237_Aouåeiyäö", [{var,{1,7},'_Aouåeiyäö'}]), + ?line test_string("A_b_c@", [{var,{1,1},'A_b_c@'}]), + ?line test_string("V@2", [{var,{1,1},'V@2'}]), + ?line test_string("ABDÀ", [{var,{1,1},'ABDÀ'}]), + ?line test_string("Ärlig Östen", [{var,{1,1},'Ärlig'},{var,{1,7},'Östen'}]), ok. eof() -> @@ -506,11 +528,25 @@ eof() -> ?line {done,{ok,[{atom,1,a}],1},eof} = erl_scan:tokens(C5,eof,1), + %% With column. + ?line {more, C6} = erl_scan:tokens([], "a", {1,1}), + %% An error before R13A. + %% ?line {done,{error,{1,erl_scan,scan},1},eof} = + ?line {done,{ok,[{atom,{1,1},a}],{1,2}},eof} = + 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."), + %% With column. + ?line {more, CCol} = erl_scan:tokens([], "a.", {1,1}), + ?line {done,{ok,[{atom,{1,1},a},{dot,{1,2}}],{1,3}},eof} = + erl_scan:tokens(CCol,eof,1), + ?line {ok,[{atom,{1,1},foo},{dot,{1,4}}],{1,5}} = + erl_scan:string("foo.", {1,1}, []), + ok. illegal() -> @@ -989,7 +1025,13 @@ more_chars() -> erl_scan:string("$\\xg", {1,1}), ok. -test_string(String, Expected) -> +test_string(String, ExpectedWithCol) -> + {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), test(String). From 590946b9fb9c433c3d17cdbcf2bc94cc4221616d Mon Sep 17 00:00:00 2001 From: Anthony Ramine Date: Wed, 6 Jun 2012 13:31:10 +0200 Subject: [PATCH 03/14] Use erl_scan:error_info() in compile, erl_lint and erl_parse --- lib/compiler/doc/src/compile.xml | 17 ----------------- lib/compiler/src/compile.erl | 2 +- lib/stdlib/doc/src/erl_lint.xml | 28 ++++------------------------ lib/stdlib/doc/src/erl_parse.xml | 26 ++++---------------------- lib/stdlib/doc/src/erl_scan.xml | 1 + lib/stdlib/src/erl_lint.erl | 10 ++++------ lib/stdlib/src/erl_parse.yrl | 3 +-- 7 files changed, 15 insertions(+), 72 deletions(-) diff --git a/lib/compiler/doc/src/compile.xml b/lib/compiler/doc/src/compile.xml index 27d750f929e9..eedae94e8287 100644 --- a/lib/compiler/doc/src/compile.xml +++ b/lib/compiler/doc/src/compile.xml @@ -823,23 +823,6 @@ pi() -> 3.1416. code is then transformed into other Erlang code.

-
- Error Information - -

The ErrorInfo mentioned above is the standard - ErrorInfo structure which is returned from all IO modules. - It has the following format:

- -{ErrorLine, Module, ErrorDescriptor} - - -

A string describing the error is obtained with the following - call:

- -Module:format_error(ErrorDescriptor) - -
-
See Also

diff --git a/lib/compiler/src/compile.erl b/lib/compiler/src/compile.erl index 0a368df5d6d7..2c20262e29ed 100644 --- a/lib/compiler/src/compile.erl +++ b/lib/compiler/src/compile.erl @@ -41,7 +41,7 @@ -type option() :: atom() | {atom(), term()} | {'d', atom(), term()}. --type err_info() :: {erl_scan:line(), module(), term()}. %% ErrorDescriptor +-type err_info() :: erl_scan:error_info(). %% ErrorDescriptor -type errors() :: [{file:filename(), [err_info()]}]. -type warnings() :: [{file:filename(), [err_info()]}]. -type mod_ret() :: {'ok', module()} diff --git a/lib/stdlib/doc/src/erl_lint.xml b/lib/stdlib/doc/src/erl_lint.xml index b7fbdd87990b..7a5a38fa704c 100644 --- a/lib/stdlib/doc/src/erl_lint.xml +++ b/lib/stdlib/doc/src/erl_lint.xml @@ -60,14 +60,6 @@ functions separately unless you have written your own Erlang compiler.

- - - - - - - - @@ -125,29 +117,17 @@

Takes an ErrorDescriptor and returns a string which describes the error or warning. This function is usually called implicitly when processing an ErrorInfo - structure (see below).

+ structure (see + erl_scan(3)). +

-
- Error Information -

The ErrorInfo mentioned above is the standard - ErrorInfo structure which is returned from all IO - modules. It has the following format: -

- - {ErrorLine, Module, ErrorDescriptor} -

A string which describes the error is obtained with the following call: -

- - Module:format_error(ErrorDescriptor) -
-
See Also

erl_parse(3), - epp(3)

+ epp(3), erl_scan(3)

diff --git a/lib/stdlib/doc/src/erl_parse.xml b/lib/stdlib/doc/src/erl_parse.xml index bafc2e074656..0943ef128a99 100644 --- a/lib/stdlib/doc/src/erl_parse.xml +++ b/lib/stdlib/doc/src/erl_parse.xml @@ -57,12 +57,6 @@

Parse tree for Erlang form.

- - - - - - @@ -130,14 +124,16 @@ Format an error descriptor ErrorDescriptor = error_description() + marker="erl_scan#type-error_description">erl_scan:error_description() Chars = [char() | Chars]

Uses an ErrorDescriptor and returns a string which describes the error. This function is usually called implicitly when an ErrorInfo structure is processed - (see below).

+ (see + erl_scan(3)). +

@@ -171,20 +167,6 @@ -
- Error Information -

The ErrorInfo mentioned above is the standard - ErrorInfo structure which is returned from all IO - modules. It has the format: -

- - {ErrorLine, Module, ErrorDescriptor} -

A string which describes the error is obtained with the following call: -

- - Module:format_error(ErrorDescriptor) -
-
See Also

io(3), diff --git a/lib/stdlib/doc/src/erl_scan.xml b/lib/stdlib/doc/src/erl_scan.xml index cfaa1702d242..cd3e11ecc464 100644 --- a/lib/stdlib/doc/src/erl_scan.xml +++ b/lib/stdlib/doc/src/erl_scan.xml @@ -403,6 +403,7 @@

+ Error Information

The ErrorInfo mentioned above is the standard ErrorInfo structure which is returned from all IO diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index 8059c91bcf60..a926bb7fc4a2 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -129,14 +129,12 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) -> }). -type lint_state() :: #lint{}. --type error_description() :: term(). --type error_info() :: {erl_scan:line(), module(), error_description()}. %% format_error(Error) %% Return a string describing the error. -spec format_error(ErrorDescriptor) -> io_lib:chars() when - ErrorDescriptor :: error_description(). + ErrorDescriptor :: erl_scan:error_description(). format_error(undefined_module) -> "no module definition"; @@ -436,7 +434,7 @@ used_vars(Exprs, BindingsList) -> AbsForms :: [erl_parse:abstract_form()], Warnings :: [{file:filename(),[ErrorInfo]}], Errors :: [{FileName2 :: file:filename(),[ErrorInfo]}], - ErrorInfo :: error_info()). + ErrorInfo :: erl_scan:error_info()). module(Forms) -> Opts = compiler_options(Forms), @@ -449,7 +447,7 @@ module(Forms) -> FileName :: atom() | string(), Warnings :: [{file:filename(),[ErrorInfo]}], Errors :: [{FileName2 :: file:filename(),[ErrorInfo]}], - ErrorInfo :: error_info()). + ErrorInfo :: erl_scan:error_info()). module(Forms, FileName) -> Opts = compiler_options(Forms), @@ -463,7 +461,7 @@ module(Forms, FileName) -> CompileOptions :: [compile:option()], Warnings :: [{file:filename(),[ErrorInfo]}], Errors :: [{FileName2 :: file:filename(),[ErrorInfo]}], - ErrorInfo :: error_info()). + ErrorInfo :: erl_scan:error_info()). module(Forms, FileName, Opts0) -> %% We want the options given on the command line to take diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl index 928c10f7f2cb..17bf0338922c 100644 --- a/lib/stdlib/src/erl_parse.yrl +++ b/lib/stdlib/src/erl_parse.yrl @@ -524,8 +524,7 @@ Erlang code. -type abstract_clause() :: term(). -type abstract_expr() :: term(). -type abstract_form() :: term(). --type error_description() :: term(). --type error_info() :: {erl_scan:line(), module(), error_description()}. +-type error_info() :: erl_scan:error_info(). -type token() :: {Tag :: atom(), Line :: erl_scan:line()}. %% mkop(Op, Arg) -> {op,Line,Op,Arg}. From 2d1c3d041c44d97486c668e1257ac31291f1fb4d Mon Sep 17 00:00:00 2001 From: Anthony Ramine Date: Sat, 25 Aug 2012 21:29:41 +0200 Subject: [PATCH 04/14] Properly handle columns in v3_core:add_warning/2 Locations with column numbers and negative line numbers where not correctly silenced. --- lib/compiler/src/v3_core.erl | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/lib/compiler/src/v3_core.erl b/lib/compiler/src/v3_core.erl index 01042cc56f1a..3a69ece1aa8c 100644 --- a/lib/compiler/src/v3_core.erl +++ b/lib/compiler/src/v3_core.erl @@ -2158,6 +2158,10 @@ format_error(nomatch) -> format_error(bad_binary) -> "binary construction will fail because of a type mismatch". -add_warning(Line, Term, #core{ws=Ws,file=[{file,File}]}=St) when Line >= 0 -> +add_warning({Line,_}=Loc, Term, #core{ws=Ws,file=[{file,File}]}=St) + when Line >= 0 -> + St#core{ws=[{File,[{location(Loc),?MODULE,Term}]}|Ws]}; +add_warning(Line, Term, #core{ws=Ws,file=[{file,File}]}=St) + when is_integer(Line), Line >= 0 -> St#core{ws=[{File,[{location(Line),?MODULE,Term}]}|Ws]}; add_warning(_, _, St) -> St. From 22027c4aa9670d6bdedf0370dc98ad4c9ce3ec89 Mon Sep 17 00:00:00 2001 From: Anthony Ramine Date: Sat, 25 Aug 2012 21:35:00 +0200 Subject: [PATCH 05/14] Rewrite qlc_pt:no_duplicates/5 Duplicate errors need to be compared without taking into account column numbers. --- lib/stdlib/src/qlc_pt.erl | 31 +++++++++++++++++++++++-------- 1 file changed, 23 insertions(+), 8 deletions(-) diff --git a/lib/stdlib/src/qlc_pt.erl b/lib/stdlib/src/qlc_pt.erl index 21504d707b68..a034abef7ef3 100644 --- a/lib/stdlib/src/qlc_pt.erl +++ b/lib/stdlib/src/qlc_pt.erl @@ -170,14 +170,15 @@ mforms(Tag, L) -> no_duplicates(Forms, Errors, Warnings0, ExtraWarnings, Options) -> %% Some mistakes such as "{X} =:= {}" are found by strong %% validation as well as by qlc. Prefer the warnings from qlc: - Warnings1 = mforms(Warnings0) -- - ([{File,[{L,v3_core,nomatch}]} || - {File,[{L,qlc,M}]} <- mforms(ExtraWarnings), - lists:member(M, [nomatch_pattern,nomatch_filter])] - ++ - [{File,[{L,sys_core_fold,nomatch_guard}]} || - {File,[{L,qlc,M}]} <- mforms(ExtraWarnings), - M =:= nomatch_filter]), + EWs = mforms(ExtraWarnings), + NoMatchLines = + [{File,get_line(Loc)} || + {File,[{Loc,qlc,M}]} <- EWs, + lists:member(M, [nomatch_pattern,nomatch_filter])], + NoMatchGuardLines = + [{File,get_line(Loc)} || + {File,[{Loc,qlc,nomatch_filter}]} <- EWs], + Warnings1 = filter_dupes(Warnings0, NoMatchLines, NoMatchGuardLines), Warnings = Warnings1 ++ ExtraWarnings, {Es1,Ws1} = compile_forms(Forms, Options), Es = mforms(Errors) -- mforms(Es1), @@ -195,6 +196,20 @@ mforms2(Tag, L) -> end, lists:sort(L)), lists:flatten(lists:sort(ML)). +filter_dupes(Ws, NoMatchLines, NoMatchGuardLines) -> + lists:filter( + fun ({File,[{Loc,v3_core,nomatch}]}) -> + not lists:member({File,get_line(Loc)}, NoMatchLines); + ({File,[{Loc,sys_core_fold,nomatch_guard}]}) -> + not lists:member({File,get_line(Loc)}, NoMatchGuardLines); + (_) -> + true + end, Ws). + +get_line(Loc) -> + {line,Line} = erl_scan:attributes_info(Loc, line), + Line. + is_qlc_q_imported(Forms) -> [[] || {attribute,_,import,{?APIMOD,FAs}} <- Forms, {?Q,1} <- FAs] =/= []. From 5e2c6bf27bb649c5faf89edf3f0e4af74dae2687 Mon Sep 17 00:00:00 2001 From: Anthony Ramine Date: Sat, 25 Aug 2012 21:38:23 +0200 Subject: [PATCH 06/14] Fix locations of QLC too_many_joins errors Full locations with line and columns crashed the parse transform. --- lib/stdlib/src/qlc_pt.erl | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/lib/stdlib/src/qlc_pt.erl b/lib/stdlib/src/qlc_pt.erl index a034abef7ef3..f592a7c87fee 100644 --- a/lib/stdlib/src/qlc_pt.erl +++ b/lib/stdlib/src/qlc_pt.erl @@ -641,12 +641,12 @@ join_kind(Qs, LcL, AllIVs, Dependencies, State) -> if EqualColsN =/= []; MatchColsN =/= [] -> {[], - [{get(?QLC_FILE),[{abs(LcL),?APIMOD,too_complex_join}]}]}; + [{get(?QLC_FILE),[{abs_loc(LcL),?APIMOD,too_complex_join}]}]}; EqualCols2 =:= [], MatchCols2 =:= [] -> {[], []}; length(Tables) > 2 -> {[], - [{get(?QLC_FILE),[{abs(LcL),?APIMOD,too_many_joins}]}]}; + [{get(?QLC_FILE),[{abs_loc(LcL),?APIMOD,too_many_joins}]}]}; EqualCols2 =:= MatchCols2 -> {EqualCols2, []}; true -> From 9356e9cb76fff60781a21e315451e60baa035b6c Mon Sep 17 00:00:00 2001 From: Anthony Ramine Date: Sat, 25 Aug 2012 21:39:09 +0200 Subject: [PATCH 07/14] Fix qlc_pt:get_lcid_line/1 with column numbers --- lib/stdlib/src/qlc_pt.erl | 9 +++++++-- 1 file changed, 7 insertions(+), 2 deletions(-) diff --git a/lib/stdlib/src/qlc_pt.erl b/lib/stdlib/src/qlc_pt.erl index f592a7c87fee..636f05a65cb5 100644 --- a/lib/stdlib/src/qlc_pt.erl +++ b/lib/stdlib/src/qlc_pt.erl @@ -2694,9 +2694,14 @@ get_lcid_no(IdAttrs) -> {line,Id} = erl_parse:get_attribute(IdAttrs, line), abs(Id) bsr ?MAX_NUM_OF_LINES. + get_lcid_line(IdAttrs) -> - {line,Id} = erl_parse:get_attribute(IdAttrs, line), - sgn(Id) * (abs(Id) band ((1 bsl ?MAX_NUM_OF_LINES) - 1)). + {location,Loc} = erl_parse:get_attribute(IdAttrs, location), + erl_parse:set_line( + Loc, + fun (Id) -> + sgn(Id) * (abs(Id) band ((1 bsl ?MAX_NUM_OF_LINES) - 1)) + end). sgn(X) when X >= 0 -> 1; From 9efb5464090800c98751d8bc9d1a61847ad2295d Mon Sep 17 00:00:00 2001 From: Anthony Ramine Date: Sun, 26 Aug 2012 14:00:17 +0200 Subject: [PATCH 08/14] Fix locations of shadowing warnings in ms_transform A shadowed variable in an ms_transform match expression emits a warning located at the match expression instead of the variable. --- lib/stdlib/src/ms_transform.erl | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/lib/stdlib/src/ms_transform.erl b/lib/stdlib/src/ms_transform.erl index 4389fd457c5c..dcef5a3c54f4 100644 --- a/lib/stdlib/src/ms_transform.erl +++ b/lib/stdlib/src/ms_transform.erl @@ -718,10 +718,10 @@ transform_head([V],OuterBound) -> th(NewV,NewBind,OuterBound). -toplevel_head_match({match,Line,{var,_,VName},Expr},B,OB) -> +toplevel_head_match({match,_,{var,Line,VName},Expr},B,OB) -> warn_var_clash(Line,VName,OB), {Expr,new_bind({VName,'$_'},B)}; -toplevel_head_match({match,Line,Expr,{var,_,VName}},B,OB) -> +toplevel_head_match({match,_,Expr,{var,Line,VName}},B,OB) -> warn_var_clash(Line,VName,OB), {Expr,new_bind({VName,'$_'},B)}; toplevel_head_match(Other,B,_OB) -> From 5903337bbed4f52460443beb5445f9a9a4a69da3 Mon Sep 17 00:00:00 2001 From: Anthony Ramine Date: Sat, 2 Jun 2012 18:37:19 +0200 Subject: [PATCH 09/14] Allow setting of initial position in epp --- lib/stdlib/doc/src/epp.xml | 6 ++-- lib/stdlib/src/epp.erl | 74 +++++++++++++++++++++++--------------- 2 files changed, 50 insertions(+), 30 deletions(-) diff --git a/lib/stdlib/doc/src/epp.xml b/lib/stdlib/doc/src/epp.xml index 386ed89fe13b..dcbacd6e0657 100644 --- a/lib/stdlib/doc/src/epp.xml +++ b/lib/stdlib/doc/src/epp.xml @@ -51,6 +51,7 @@ + Open a file for preprocessing

Opens a file for preprocessing.

@@ -68,17 +69,18 @@ Return the next Erlang form from the opened Erlang source file

Returns the next Erlang form from the opened Erlang source file. - The tuple {eof, Line} is returned at end-of-file. The first + The tuple {eof, Loc} is returned at end-of-file. The first form corresponds to an implicit attribute -file(File,1)., where File is the name of the file.

+ Preprocess and parse an Erlang source file

Preprocesses and parses an Erlang source file. - Note that the tuple {eof, Line} returned at end-of-file is + Note that the tuple {eof, Loc} returned at end-of-file is included as a "form".

diff --git a/lib/stdlib/src/epp.erl b/lib/stdlib/src/epp.erl index 2c8d84a9e1f3..418db3392b8d 100644 --- a/lib/stdlib/src/epp.erl +++ b/lib/stdlib/src/epp.erl @@ -20,9 +20,9 @@ %% An Erlang code preprocessor. --export([open/2,open/3,open/5,close/1,format_error/1]). +-export([open/2,open/3,open/4, open/5,close/1,format_error/1]). -export([scan_erl_form/1,parse_erl_form/1,macro_defs/1]). --export([parse_file/1, parse_file/3]). +-export([parse_file/1, parse_file/3, parse_file/4]). -export([interpret_file_attribute/1]). -export([normalize_typed_record_fields/1,restore_typed_record_fields/1]). @@ -54,12 +54,14 @@ %% open(FileName, IncludePath) %% open(FileName, IncludePath, PreDefMacros) +%% open(FileName, StartLocation, IncludePath, PredefMacros) %% open(FileName, IoDevice, StartLocation, IncludePath, PreDefMacros) %% close(Epp) %% scan_erl_form(Epp) %% parse_erl_form(Epp) %% parse_file(Epp) %% parse_file(FileName, IncludePath, PreDefMacros) +%% parse_file(FileName, StartLocation, IncludePath, PreDefMacros) %% macro_defs(Epp) -spec open(FileName, IncludePath) -> @@ -81,8 +83,20 @@ open(Name, Path) -> ErrorDescriptor :: term(). open(Name, Path, Pdm) -> + open(Name, 1, Path, Pdm). + +-spec open(FileName, StartLocation, IncludePath, PredefMacros) -> + {'ok', Epp} | {'error', ErrorDescriptor} when + FileName :: file:name(), + StartLocation :: erl_scan:location(), + IncludePath :: [DirectoryName :: file:name()], + PredefMacros :: macros(), + Epp :: epp_handle(), + ErrorDescriptor :: term(). + +open(Name, StartLocation, Path, Pdm) -> Self = self(), - Epp = spawn(fun() -> server(Self, Name, Path, Pdm) end), + Epp = spawn(fun() -> server(Self, Name, StartLocation, Path, Pdm) end), epp_request(Epp). open(Name, File, StartLocation, Path, Pdm) -> @@ -105,10 +119,10 @@ scan_erl_form(Epp) -> epp_request(Epp, scan_erl_form). -spec parse_erl_form(Epp) -> - {'ok', AbsForm} | {'eof', Line} | {error, ErrorInfo} when + {'ok', AbsForm} | {'eof', Loc} | {error, ErrorInfo} when Epp :: epp_handle(), AbsForm :: erl_parse:abstract_form(), - Line :: erl_scan:line(), + Loc :: erl_scan:location(), ErrorInfo :: erl_scan:error_info() | erl_parse:error_info(). parse_erl_form(Epp) -> @@ -171,14 +185,28 @@ format_error(E) -> file:format_error(E). {'ok', [Form]} | {error, OpenError} when FileName :: file:name(), IncludePath :: [DirectoryName :: file:name()], - Form :: erl_parse:abstract_form() | {'error', ErrorInfo} | {'eof',Line}, + Form :: erl_parse:abstract_form() | {'error', ErrorInfo} | {'eof', Loc}, PredefMacros :: macros(), - Line :: erl_scan:line(), + Loc :: erl_scan:location(), ErrorInfo :: erl_scan:error_info() | erl_parse:error_info(), OpenError :: file:posix() | badarg | system_limit. parse_file(Ifile, Path, Predefs) -> - case open(Ifile, Path, Predefs) of + parse_file(Ifile, 1, Path, Predefs). + +-spec parse_file(FileName, StartLocation, IncludePath, PredefMacros) -> + {'ok', [Form]} | {error, OpenError} when + FileName :: file:name(), + StartLocation :: erl_scan:location(), + IncludePath :: [DirectoryName :: file:name()], + Form :: erl_parse:abstract_form() | {'error', ErrorInfo} | {'eof', Loc}, + PredefMacros :: macros(), + Loc :: erl_scan:location(), + ErrorInfo :: erl_scan:error_info() | erl_parse:error_info(), + OpenError :: file:posix() | badarg | system_limit. + +parse_file(Ifile, StartLocation, Path, Predefs) -> + case open(Ifile, StartLocation, Path, Predefs) of {ok,Epp} -> Forms = parse_file(Epp), close(Epp), @@ -245,14 +273,12 @@ restore_typed_record_fields([{attribute,La,type,{{record,Record},Fields,[]}}| restore_typed_record_fields([Form|Forms]) -> [Form|restore_typed_record_fields(Forms)]. -%% server(StarterPid, FileName, Path, PreDefMacros) - -server(Pid, Name, Path, Pdm) -> +%% server(StarterPid, FileName, Location, Path, PreDefMacros) +server(Pid, Name, AtLocation, Path, Pdm) -> process_flag(trap_exit, true), case file:open(Name, [read]) of {ok,File} -> - Location = 1, - init_server(Pid, Name, File, Location, Path, Pdm, false); + init_server(Pid, Name, File, AtLocation, Path, Pdm, false); {error,E} -> epp_reply(Pid, {error,E}) end. @@ -400,10 +426,11 @@ enter_file2(NewF, Pname, From, St, AtLocation) -> sstk=[St|St#epp.sstk],path=Path,macs=Ms}. enter_file_reply(From, Name, Location, AtLocation) -> - Attr = loc_attr(AtLocation), + {line,Attr} = erl_scan:attributes_info(AtLocation, line), + {line,Line} = erl_scan:attributes_info(Location, line), Rep = {ok, [{'-',Attr},{atom,Attr,file},{'(',Attr}, {string,Attr,file_name(Name)},{',',Attr}, - {integer,Attr,get_line(Location)},{')',Location}, + {integer,Attr,Line},{')',Location}, {dot,Attr}]}, epp_reply(From, Rep). @@ -814,7 +841,8 @@ scan_file([{'(',_Llp},{string,_Ls,Name},{',',_Lc},{integer,_Li,Ln},{')',_Lrp}, Ms = dict:store({atom,'FILE'}, {none,[{string,1,Name}]}, St#epp.macs), Locf = loc(Tf), NewLoc = new_location(Ln, St#epp.location, Locf), - Delta = abs(get_line(element(2, Tf)))-Ln + St#epp.delta, + {line, Line} = erl_scan:token_info(Tf, line), + Delta = abs(Line) - Ln + St#epp.delta, wait_req_scan(St#epp{name2=Name,location=NewLoc,delta=Delta,macs=Ms}); scan_file(_Toks, Tf, From, St) -> epp_reply(From, {error,{loc(Tf),epp,{bad,file}}}), @@ -1165,18 +1193,13 @@ fname_join(["." | [_|_]=Rest]) -> fname_join(Components) -> filename:join(Components). -%% The line only. (Other tokens may have the column and text as well...) -loc_attr(Line) when is_integer(Line) -> - Line; -loc_attr({Line,_Column}) -> - Line. - loc(Token) -> {location,Location} = erl_scan:token_info(Token, location), Location. abs_loc(Token) -> - loc(setelement(2, Token, abs_line(element(2, Token)))). + {location,Loc} = erl_scan:token_info(Token, location), + abs_line(Loc). neg_line(L) -> erl_scan:set_attribute(line, L, fun(Line) -> -abs(Line) end). @@ -1192,11 +1215,6 @@ start_loc(Line) when is_integer(Line) -> start_loc({_Line, _Column}) -> {1,1}. -get_line(Line) when is_integer(Line) -> - Line; -get_line({Line,_Column}) -> - Line. - %% epp has always output -file attributes when entering and leaving %% included files (-include, -include_lib). Starting with R11B the %% -file attribute is also recognized in the input file. This is From ffc8ebff9e55d5d2fffdc8a4fcdba884f1276b72 Mon Sep 17 00:00:00 2001 From: Anthony Ramine Date: Sat, 2 Jun 2012 18:37:53 +0200 Subject: [PATCH 10/14] Create a new "column" option in compile If set, compile will call epp with a full location {1, 1} instead of 1, thus making it keep the column numbers in the parsed AST. --- lib/compiler/doc/src/compile.xml | 5 +++++ lib/compiler/src/compile.erl | 9 ++++++++- lib/compiler/test/error_SUITE.erl | 15 +++++++++++++-- 3 files changed, 26 insertions(+), 3 deletions(-) diff --git a/lib/compiler/doc/src/compile.xml b/lib/compiler/doc/src/compile.xml index eedae94e8287..2b003ed26510 100644 --- a/lib/compiler/doc/src/compile.xml +++ b/lib/compiler/doc/src/compile.xml @@ -108,6 +108,11 @@ See the Efficiency Guide for further information.

+ column + +

The compiler will keep the column numbers while parsing.

+
+ compressed

The compiler will compress the generated object code, diff --git a/lib/compiler/src/compile.erl b/lib/compiler/src/compile.erl index 2c20262e29ed..c310d5893b5c 100644 --- a/lib/compiler/src/compile.erl +++ b/lib/compiler/src/compile.erl @@ -773,7 +773,8 @@ parse_module(St) -> Opts = St#compile.options, Cwd = ".", IncludePath = [Cwd, St#compile.dir|inc_paths(Opts)], - R = epp:parse_file(St#compile.ifile, IncludePath, pre_defs(Opts)), + AtPos = initial_position(Opts), + R = epp:parse_file(St#compile.ifile, AtPos, IncludePath, pre_defs(Opts)), case R of {ok,Forms} -> {ok,St#compile{code=Forms}}; @@ -1479,6 +1480,12 @@ objfile(Base, St) -> tmpfile(Ofile) -> reverse([$#|tl(reverse(Ofile))]). +initial_position(Opts) -> + case lists:member(column, Opts) of + true -> {1, 1}; + false -> 1 + end. + %% pre_defs(Options) %% inc_paths(Options) %% Extract the predefined macros and include paths from the option list. diff --git a/lib/compiler/test/error_SUITE.erl b/lib/compiler/test/error_SUITE.erl index fb51e013ce0e..412958baf343 100644 --- a/lib/compiler/test/error_SUITE.erl +++ b/lib/compiler/test/error_SUITE.erl @@ -22,13 +22,15 @@ -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, init_per_group/2,end_per_group/2, - head_mismatch_line/1,warnings_as_errors/1, bif_clashes/1]). + head_mismatch_line/1,warnings_as_errors/1, bif_clashes/1, + column_number/1 + ]). suite() -> [{ct_hooks,[ts_install_cth]}]. all() -> test_lib:recompile(?MODULE), - [head_mismatch_line, warnings_as_errors, bif_clashes]. + [head_mismatch_line, warnings_as_errors, bif_clashes, column_number]. groups() -> []. @@ -166,6 +168,15 @@ bif_clashes(Config) when is_list(Config) -> +%% Tests that messages are correctly reported with column numbers +%% if the column option is set. +column_number(Config) when is_list(Config) -> + Ts1 = [{column_number_warning, + <<"\nt(X) -> ok.">>, + [return_warnings, export_all, column], + {warning, [{{2, 3}, erl_lint, {unused_var, 'X'}}]}}], + ?line [] = run(Config, Ts1), + ok. %% Tests that a head mismatch is reported on the correct line (OTP-2125). head_mismatch_line(Config) when is_list(Config) -> From ea969a61c3fa2e8308505bbe388815045bbff45d Mon Sep 17 00:00:00 2001 From: Anthony Ramine Date: Sat, 25 Aug 2012 11:42:36 +0200 Subject: [PATCH 11/14] Handle column numbers in erl_lint test suite --- lib/stdlib/test/erl_lint_SUITE.erl | 1088 +++++++++++++++------------- 1 file changed, 571 insertions(+), 517 deletions(-) diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl index 9f9d97b6192a..efeeb4ca9ff8 100644 --- a/lib/stdlib/test/erl_lint_SUITE.erl +++ b/lib/stdlib/test/erl_lint_SUITE.erl @@ -144,12 +144,12 @@ unused_vars_warn_basic(Config) when is_list(Config) -> end. ">>, [warn_unused_vars], - {warnings,[{1,erl_lint,{unused_var,'F'}}, - {15,erl_lint,{unused_var,'Y'}}, - {22,erl_lint,{unused_var,'N'}}, - {23,erl_lint,{shadowed_var,'N','fun'}}, - {28,erl_lint,{unused_var,'B'}}, - {29,erl_lint,{unused_var,'B'}}]}}], + {warnings,[{{1,3},erl_lint,{unused_var,'F'}}, + {{15,24},erl_lint,{unused_var,'Y'}}, + {{22,15},erl_lint,{unused_var,'N'}}, + {{23,31},erl_lint,{shadowed_var,'N','fun'}}, + {{28,26},erl_lint,{unused_var,'B'}}, + {{29,26},erl_lint,{unused_var,'B'}}]}}], ?line [] = run(Config, Ts), ok. @@ -168,22 +168,8 @@ unused_vars_warn_lc(Config) when is_list(Config) -> [C || <> <- Z, <> <- Z, <> <- Z]. ">>, [warn_unused_vars], - {warnings, [{4,erl_lint,{shadowed_var,'X',generate}}, - {7,erl_lint,{unused_var,'Y'}}]}}, - - {lc2, - <<"bin([X]) -> - [A || <> <- []]; % X used, not shadowed. - bin({X}) -> - [X || <> <- []]; % X used, and shadowed. - bin({X,Y,Z}) -> - [{A,B} || <> <- Z, <> <- Z]; - bin([X,Y,Z]) -> % Y unused. - [C || <> <- Z, <> <- Z, <> <- Z]. - ">>, - [warn_unused_vars], - {warnings,[{4,erl_lint,{shadowed_var,'X',generate}}, - {7,erl_lint,{unused_var,'Y'}}]}}, + {warnings, [{{4,27},erl_lint,{shadowed_var,'X',generate}}, + {{7,22},erl_lint,{unused_var,'Y'}}]}}, {lc3, <<"a([A]) -> @@ -205,7 +191,7 @@ unused_vars_warn_lc(Config) when is_list(Config) -> [C || {C,_} <- A]. ">>, [warn_unused_vars], - {warnings,[{2,erl_lint,{unused_var,'B'}}]}}, + {warnings,[{{2,19},erl_lint,{unused_var,'B'}}]}}, {lc5, <<"c(A) -> @@ -222,7 +208,7 @@ unused_vars_warn_lc(Config) when is_list(Config) -> [{A,B} || {Id,_} <- A]. % Id unused. ">>, [warn_unused_vars], - {warnings,[{3,erl_lint,{unused_var,'Id'}}]}}, + {warnings,[{{3,30},erl_lint,{unused_var,'Id'}}]}}, {lc7, <<"e(A) -> @@ -230,8 +216,8 @@ unused_vars_warn_lc(Config) when is_list(Config) -> [B || B <- A]. % B shadowed. ">>, [warn_unused_vars], - {warnings,[{2,erl_lint,{unused_var,'B'}}, - {3,erl_lint,{shadowed_var,'B',generate}}]}}, + {warnings,[{{2,19},erl_lint,{unused_var,'B'}}, + {{3,25},erl_lint,{shadowed_var,'B',generate}}]}}, {lc8, <<"f(A) -> @@ -240,7 +226,7 @@ unused_vars_warn_lc(Config) when is_list(Config) -> B. ">>, [warn_unused_vars], - {warnings,[{3,erl_lint,{shadowed_var,'B',generate}}]}}, + {warnings,[{{3,25},erl_lint,{shadowed_var,'B',generate}}]}}, {lc9, <<"g(A) -> @@ -248,9 +234,9 @@ unused_vars_warn_lc(Config) when is_list(Config) -> [A || B <- A]. % B shadowed, B unused. ">>, [warn_unused_vars], - {warnings,[{2,erl_lint,{unused_var,'B'}}, - {3,erl_lint,{unused_var,'B'}}, - {3,erl_lint,{shadowed_var,'B',generate}}]}}, + {warnings,[{{2,19},erl_lint,{unused_var,'B'}}, + {{3,25},erl_lint,{unused_var,'B'}}, + {{3,25},erl_lint,{shadowed_var,'B',generate}}]}}, {lc10, <<"h(A) -> @@ -259,8 +245,8 @@ unused_vars_warn_lc(Config) when is_list(Config) -> B. ">>, [warn_unused_vars], - {warnings,[{3,erl_lint,{unused_var,'B'}}, - {3,erl_lint,{shadowed_var,'B',generate}}]}}, + {warnings,[{{3,25},erl_lint,{unused_var,'B'}}, + {{3,25},erl_lint,{shadowed_var,'B',generate}}]}}, {lc11, <<"i(X) -> @@ -268,10 +254,10 @@ unused_vars_warn_lc(Config) when is_list(Config) -> Z = X <- [foo]]. % X and Z shadowed. X unused! ">>, [warn_unused_vars], - {warnings,[{2,erl_lint,{unused_var,'Z'}}, - {3,erl_lint,{unused_var,'X'}}, - {3,erl_lint,{shadowed_var,'X',generate}}, - {3,erl_lint,{shadowed_var,'Z',generate}}]}}, + {warnings,[{{2,25},erl_lint,{unused_var,'Z'}}, + {{3,29},erl_lint,{unused_var,'X'}}, + {{3,29},erl_lint,{shadowed_var,'X',generate}}, + {{3,25},erl_lint,{shadowed_var,'Z',generate}}]}}, {lc12, <<"j({X}) -> @@ -288,19 +274,19 @@ unused_vars_warn_lc(Config) when is_list(Config) -> X <- X]. % X shadowed. X unused. ">>, [warn_unused_vars], - {warnings,[{2,erl_lint,{unused_var,'Z'}}, - {3,erl_lint,{unused_var,'Z'}}, - {3,erl_lint,{shadowed_var,'Z',generate}}, - {4,erl_lint,{unused_var,'Z'}}, - {4,erl_lint,{shadowed_var,'Z',generate}}, - {5,erl_lint,{shadowed_var,'Z',generate}}, - {7,erl_lint,{shadowed_var,'X',generate}}, - {8,erl_lint,{unused_var,'X'}}, - {8,erl_lint,{shadowed_var,'X',generate}}, - {10,erl_lint,{unused_var,'Y'}}, - {11,erl_lint,{shadowed_var,'X',generate}}, - {12,erl_lint,{unused_var,'X'}}, - {12,erl_lint,{shadowed_var,'X',generate}}]}}, + {warnings,[{{2,25},erl_lint,{unused_var,'Z'}}, + {{3,25},erl_lint,{unused_var,'Z'}}, + {{3,25},erl_lint,{shadowed_var,'Z',generate}}, + {{4,25},erl_lint,{unused_var,'Z'}}, + {{4,25},erl_lint,{shadowed_var,'Z',generate}}, + {{5,25},erl_lint,{shadowed_var,'Z',generate}}, + {{7,27},erl_lint,{shadowed_var,'X',generate}}, + {{8,25},erl_lint,{unused_var,'X'}}, + {{8,25},erl_lint,{shadowed_var,'X',generate}}, + {{10,34},erl_lint,{unused_var,'Y'}}, + {{11,25},erl_lint,{shadowed_var,'X',generate}}, + {{12,25},erl_lint,{unused_var,'X'}}, + {{12,25},erl_lint,{shadowed_var,'X',generate}}]}}, {lc13, <<"k(X) -> @@ -320,14 +306,14 @@ unused_vars_warn_lc(Config) when is_list(Config) -> [Z || Y = X > 3, Z = X]. % Y unused. ">>, [warn_unused_vars], - {error,[{8,erl_lint,{unbound_var,'Y'}}, - {11,erl_lint,{unbound_var,'Y'}}], - [{2,erl_lint,{unused_var,'Y'}}, - {4,erl_lint,{unused_var,'Y'}}, - {8,erl_lint,{unused_var,'Y'}}, - {10,erl_lint,{unused_var,'Y'}}, - {13,erl_lint,{unused_var,'Z'}}, - {15,erl_lint,{unused_var,'Y'}}]}}, + {error,[{{8,21},erl_lint,{unbound_var,'Y'}}, + {{11,24},erl_lint,{unbound_var,'Y'}}], + [{{2,30},erl_lint,{unused_var,'Y'}}, + {{4,34},erl_lint,{unused_var,'Y'}}, + {{8,34},erl_lint,{unused_var,'Y'}}, + {{10,31},erl_lint,{unused_var,'Y'}}, + {{13,36},erl_lint,{unused_var,'Z'}}, + {{15,25},erl_lint,{unused_var,'Y'}}]}}, {lc14, <<"lc2() -> @@ -336,7 +322,7 @@ unused_vars_warn_lc(Config) when is_list(Config) -> X <- Z]. ">>, [warn_unused_vars], - {warnings,[{3,erl_lint,{shadowed_var,'Z',generate}}]}}, + {warnings,[{{3,25},erl_lint,{shadowed_var,'Z',generate}}]}}, {lc15, <<"lc3() -> @@ -345,8 +331,8 @@ unused_vars_warn_lc(Config) when is_list(Config) -> Z <- Z]. % Z shadowed. Z unused. ">>, [warn_unused_vars], - {warnings,[{4,erl_lint,{unused_var,'Z'}}, - {4,erl_lint,{shadowed_var,'Z',generate}}]}}, + {warnings,[{{4,25},erl_lint,{unused_var,'Z'}}, + {{4,25},erl_lint,{shadowed_var,'Z',generate}}]}}, {lc16, <<"bin(Z) -> @@ -379,13 +365,13 @@ unused_vars_warn_lc(Config) when is_list(Config) -> end. ">>, [warn_unused_vars], - {error,[{22,erl_lint,{unsafe_var,'U',{'case',2}}}, - {27,erl_lint,{unsafe_var,'U',{'case',2}}}], - [{16,erl_lint,{unused_var,'Y'}}, - % {24,erl_lint,{exported_var,'X',{'case',8}}}, - {24,erl_lint,{unused_var,'U'}}, - % {26,erl_lint,{exported_var,'X',{'case',8}}}, - {26,erl_lint,{unused_var,'U'}}]}}, + {error,[{{22,27},erl_lint,{unsafe_var,'U',{'case',{2,19}}}}, + {{27,27},erl_lint,{unsafe_var,'U',{'case',{2,19}}}}], + [{{16,27},erl_lint,{unused_var,'Y'}}, + % {{24,37},erl_lint,{exported_var,'X',{'case',{8,19}}}}, + {{24,35},erl_lint,{unused_var,'U'}}, + % {{26,37},erl_lint,{exported_var,'X',{'case',{8,19}}}}, + {{26,35},erl_lint,{unused_var,'U'}}]}}, {lc17, <<"bin(Z) -> @@ -412,10 +398,10 @@ unused_vars_warn_lc(Config) when is_list(Config) -> U. % U unsafe. ">>, [warn_unused_vars], - {error,[{22,erl_lint,{unsafe_var,'U',{'case',3}}}], - [{17,erl_lint,{unused_var,'Y'}}, - % {21,erl_lint,{exported_var,'X',{'case',9}}}, - {21,erl_lint,{unused_var,'U'}}]}}, + {error,[{{22,19},erl_lint,{unsafe_var,'U',{'case',{3,19}}}}], + [{{17,27},erl_lint,{unused_var,'Y'}}, + % {{21,29},erl_lint,{exported_var,'X',{'case',{9,5}}}}, + {{21,27},erl_lint,{unused_var,'U'}}]}}, {lc18, <<"bin(Z) -> @@ -442,11 +428,11 @@ unused_vars_warn_lc(Config) when is_list(Config) -> % U shadowed. (X exported.) ">>, [warn_unused_vars], - {error,[{21,erl_lint,{unsafe_var,'U',{'case',2}}}, - {21,erl_lint,{unsafe_var,'Y',{'case',14}}}], - [{20,erl_lint,{unused_var,'U'}} - % ,{21,erl_lint,{exported_var,'X',{'case',8}}} - % ,{21,erl_lint,{shadowed_var,'U',generate}} + {error,[{{21,27},erl_lint,{unsafe_var,'U',{'case',{2,19}}}}, + {{21,41},erl_lint,{unsafe_var,'Y',{'case',{14,19}}}}], + [{{20,27},erl_lint,{unused_var,'U'}} + % ,{{21,34},erl_lint,{exported_var,'X',{'case',{8,19}}}} + % ,{{21,27},erl_lint,{shadowed_var,'U',generate}} ]}}, {lc19, @@ -456,7 +442,7 @@ unused_vars_warn_lc(Config) when is_list(Config) -> <> = <<17:32>>. % A unused. ">>, [warn_unused_vars], - {warnings,[{4,erl_lint,{unused_var,'A'}}]}}, + {warnings,[{{4,21},erl_lint,{unused_var,'A'}}]}}, {lc20, <<"c({I1,I2}) -> @@ -473,9 +459,9 @@ unused_vars_warn_lc(Config) when is_list(Config) -> ">>, [warn_unused_vars], - {warnings,[{6,erl_lint,{unused_var,'C1'}}, + {warnings,[{{6,18},erl_lint,{unused_var,'C1'}}, {7,sys_core_fold,no_clause_match}, - {9,erl_lint,{unused_var,'C3'}}]}}, + {{9,25},erl_lint,{unused_var,'C3'}}]}}, {lc21, <<"t() -> @@ -496,8 +482,8 @@ unused_vars_warn_lc(Config) when is_list(Config) -> end. ">>, [warn_unused_vars], - {error,[{6,erl_lint,{unbound_var,'X'}}], - [{14,erl_lint,{unused_var,'Q'}}]}} + {error,[{{6,27},erl_lint,{unbound_var,'X'}}], + [{{14,25},erl_lint,{unused_var,'Q'}}]}} ], ?line [] = run(Config, Ts), @@ -535,7 +521,7 @@ unused_vars_warn_rec(Config) when is_list(Config) -> end. ">>, [warn_unused_vars], - {warnings,[{22,erl_lint,{unused_var,'Same'}}]}}], + {warnings,[{{22,41},erl_lint,{unused_var,'Same'}}]}}], ?line [] = run(Config, Ts), ok. @@ -561,16 +547,16 @@ unused_vars_warn_fun(Config) when is_list(Config) -> end. ">>, [warn_unused_vars], - {warnings,[{1,erl_lint,{unused_var,'A'}}, - {2,erl_lint,{unused_var,'A'}}, - {2,erl_lint,{shadowed_var,'A','fun'}}, - {4,erl_lint,{unused_var,'A'}}, - {4,erl_lint,{shadowed_var,'A','fun'}}, - {5,erl_lint,{unused_var,'Q'}}, - {8,erl_lint,{unused_var,'E'}}, - {8,erl_lint,{shadowed_var,'E','fun'}}, + {warnings,[{{1,4},erl_lint,{unused_var,'A'}}, + {{2,23},erl_lint,{unused_var,'A'}}, + {{2,23},erl_lint,{shadowed_var,'A','fun'}}, + {{4,25},erl_lint,{unused_var,'A'}}, + {{4,25},erl_lint,{shadowed_var,'A','fun'}}, + {{5,26},erl_lint,{unused_var,'Q'}}, + {{8,23},erl_lint,{unused_var,'E'}}, + {{8,23},erl_lint,{shadowed_var,'E','fun'}}, {8,sys_core_fold,useless_building}, - {12,erl_lint,{unused_var,'E'}}]}}, + {{12,26},erl_lint,{unused_var,'E'}}]}}, {fun2, <<"u() -> @@ -601,14 +587,14 @@ unused_vars_warn_fun(Config) when is_list(Config) -> fun(U) -> foo end. % U shadowed. U unused. ">>, [warn_unused_vars], - {error,[{9,erl_lint,{unsafe_var,'U',{'case',2}}}], - [{8,erl_lint,{unused_var,'U'}}, - {17,erl_lint,{unused_var,'U'}}, - {17,erl_lint,{shadowed_var,'U','fun'}}, - {22,erl_lint,{unused_var,'U'}}, - {24,erl_lint,{unused_var,'U'}}, - {26,erl_lint,{unused_var,'U'}}, - {26,erl_lint,{shadowed_var,'U','fun'}}]}} + {error,[{{9,19},erl_lint,{unsafe_var,'U',{'case',{2,19}}}}], + [{{8,23},erl_lint,{unused_var,'U'}}, + {{17,23},erl_lint,{unused_var,'U'}}, + {{17,23},erl_lint,{shadowed_var,'U','fun'}}, + {{22,27},erl_lint,{unused_var,'U'}}, + {{24,27},erl_lint,{unused_var,'U'}}, + {{26,23},erl_lint,{unused_var,'U'}}, + {{26,23},erl_lint,{shadowed_var,'U','fun'}}]}} ], ?line [] = run(Config, Ts), ok. @@ -628,11 +614,11 @@ unused_vars_OTP_4858(Config) when is_list(Config) -> <> = <<2,\"AB\",3,\"CDE\">>. ">>, [warn_unused_vars], - {error,[{4,erl_lint,{unbound_var,'BadSize'}}], - [{4,erl_lint,{unused_var,'B'}}, - {4,erl_lint,{unused_var,'Size'}}, - {8,erl_lint,{unused_var,'B'}}, - {8,erl_lint,{unused_var,'Rest'}}]}} + {error,[{{4,38},erl_lint,{unbound_var,'BadSize'}}], + [{{4,36},erl_lint,{unused_var,'B'}}, + {{4,21},erl_lint,{unused_var,'Size'}}, + {{8,26},erl_lint,{unused_var,'B'}}, + {{8,40},erl_lint,{unused_var,'Rest'}}]}} ], ?line [] = run(Config, Ts), ok. @@ -671,15 +657,15 @@ export_vars_warn(Config) when is_list(Config) -> end. ">>, [warn_unused_vars], - {error,[{14,erl_lint,{unsafe_var,'A',{'case',2}}}], - [{6,erl_lint,{unused_var,'W'}}, - {7,erl_lint,{unused_var,'Z'}}, - {10,erl_lint,{unused_var,'Z'}}, - {15,erl_lint,{unused_var,'X'}}, - {19,erl_lint,{exported_var,'B',{'case',2}}}, - {20,erl_lint,{unused_var,'U'}}, - {25,erl_lint,{unused_var,'X'}}, - {26,erl_lint,{unused_var,'U'}}]}}, + {error,[{{14,27},erl_lint,{unsafe_var,'A',{'case',{2,19}}}}], + [{{6,27},erl_lint,{unused_var,'W'}}, + {{7,27},erl_lint,{unused_var,'Z'}}, + {{10,27},erl_lint,{unused_var,'Z'}}, + {{15,27},erl_lint,{unused_var,'X'}}, + {{19,27},erl_lint,{exported_var,'B',{'case',{2,19}}}}, + {{20,27},erl_lint,{unused_var,'U'}}, + {{25,27},erl_lint,{unused_var,'X'}}, + {{26,27},erl_lint,{unused_var,'U'}}]}}, {exp2, <<"bin(A) -> @@ -694,11 +680,11 @@ export_vars_warn(Config) when is_list(Config) -> [B || B <- Z]. % Z exported. B shadowed. ">>, [warn_export_vars], - {error,[{9,erl_lint,{unbound_var,'B'}}], - [{8,erl_lint,{exported_var,'X',{'receive',2}}}, - {9,erl_lint,{exported_var,'Y',{'receive',2}}}, - {10,erl_lint,{exported_var,'Z',{'receive',2}}}, - {10,erl_lint,{shadowed_var,'B',generate}}]}}, + {error,[{{9,23},erl_lint,{unbound_var,'B'}}], + [{{8,29},erl_lint,{exported_var,'X',{'receive',{2,19}}}}, + {{9,19},erl_lint,{exported_var,'Y',{'receive',{2,19}}}}, + {{10,30},erl_lint,{exported_var,'Z',{'receive',{2,19}}}}, + {{10,25},erl_lint,{shadowed_var,'B',generate}}]}}, {exp3, <<"bin(A) -> @@ -713,9 +699,9 @@ export_vars_warn(Config) when is_list(Config) -> [B || B <- Z]. % (Z exported.) B shadowed. ">>, [], - {error,[{9,erl_lint,{unbound_var,'B'}}], - [{9,erl_lint,{exported_var,'Y',{'receive',2}}}, - {10,erl_lint,{shadowed_var,'B',generate}}]}} + {error,[{{9,23},erl_lint,{unbound_var,'B'}}], + [{{9,19},erl_lint,{exported_var,'Y',{'receive',{2,19}}}}, + {{10,25},erl_lint,{shadowed_var,'B',generate}}]}} ], ?line [] = run(Config, Ts), ok. @@ -738,8 +724,8 @@ shadow_vars(Config) when is_list(Config) -> [B || B <- Z]. % B shadowed. ">>, [nowarn_shadow_vars], - {error,[{9,erl_lint,{unbound_var,'B'}}], - [{9,erl_lint,{exported_var,'Y',{'receive',2}}}]}}], + {error,[{{9,23},erl_lint,{unbound_var,'B'}}], + [{{9,19},erl_lint,{exported_var,'Y',{'receive',{2,19}}}}]}}], ?line [] = run(Config, Ts), ok. @@ -754,7 +740,7 @@ unused_import(Config) when is_list(Config) -> map(fun(X) -> 2*X end, L). ">>, [warn_unused_import], - {warnings,[{1,erl_lint,{unused_import,{{foldl,3},lists}}}]}}], + {warnings,[{{1,2},erl_lint,{unused_import,{{foldl,3},lists}}}]}}], ?line [] = run(Config, Ts), ok. @@ -774,8 +760,8 @@ unused_function(Config) when is_list(Config) -> fact_1(N, P) -> fact_1(N-1, P*N). ">>, {[]}, %Tuple indicates no 'export_all'. - {warnings,[{5,erl_lint,{unused_function,{fact,1}}}, - {8,erl_lint,{unused_function,{fact_1,2}}}]}}, + {warnings,[{{5,15},erl_lint,{unused_function,{fact,1}}}, + {{8,15},erl_lint,{unused_function,{fact_1,2}}}]}}, %% Turn off warnings for unused functions. {func2, @@ -816,23 +802,23 @@ unsafe_vars(Config) when is_list(Config) -> Y. ">>, [warn_unused_vars], - {error,[{3,erl_lint,{unsafe_var,'Y',{'orelse',2}}}], - [{2,erl_lint,{unused_var,'X'}}]}}, + {error,[{{3,19},erl_lint,{unsafe_var,'Y',{'orelse',{2,29}}}}], + [{{2,19},erl_lint,{unused_var,'X'}}]}}, {unsafe2, <<"t2() -> (X = true) orelse (Y = false), X. ">>, [warn_unused_vars], - {warnings,[{2,erl_lint,{unused_var,'Y'}}]}}, + {warnings,[{{2,38},erl_lint,{unused_var,'Y'}}]}}, {unsafe3, <<"t3() -> (X = true) andalso (Y = false), Y. ">>, [warn_unused_vars], - {error,[{3,erl_lint,{unsafe_var,'Y',{'andalso',2}}}], - [{2,erl_lint,{unused_var,'X'}}]}}, + {error,[{{3,19},erl_lint,{unsafe_var,'Y',{'andalso',{2,30}}}}], + [{{2,20},erl_lint,{unused_var,'X'}}]}}, {unsafe4, <<"t4() -> (X = true) andalso (true = X), @@ -863,8 +849,8 @@ unsafe_vars(Config) when is_list(Config) -> X. ">>, [warn_unused_vars], - {errors,[{3,erl_lint,{unsafe_var,'X',{'if',2}}}, - {4,erl_lint,{unsafe_var,'X',{'if',2}}}], + {errors,[{{3,32},erl_lint,{unsafe_var,'X',{'if',{2,20}}}}, + {{4,19},erl_lint,{unsafe_var,'X',{'if',{2,20}}}}], []}} ], ?line [] = run(Config, Ts), @@ -886,7 +872,7 @@ unsafe_vars2(Config) when is_list(Config) -> State1. % unsafe ">>, [warn_unused_vars], - {errors,[{9,erl_lint,{unsafe_var,'State1',{'if',4}}}],[]}}, + {errors,[{{9,19},erl_lint,{unsafe_var,'State1',{'if',{4,27}}}}],[]}}, {unsafe2_2, <<"foo(State) -> case State of @@ -899,7 +885,7 @@ unsafe_vars2(Config) when is_list(Config) -> State1. % unsafe ">>, [], - {errors,[{9,erl_lint,{unsafe_var,'State1',{'if',4}}}],[]}} + {errors,[{{9,19},erl_lint,{unsafe_var,'State1',{'if',{4,27}}}}],[]}} ], ?line [] = run(Config, Ts), ok. @@ -931,9 +917,9 @@ unsafe_vars_try(Config) when is_list(Config) -> Result. ">>, [], - {errors,[{6,erl_lint,{unsafe_var,'Result',{'try',2}}}, - {13,erl_lint,{unsafe_var,'Result',{'try',8}}}, - {20,erl_lint,{unsafe_var,'Result',{'try',15}}}], + {errors,[{{6,17},erl_lint,{unsafe_var,'Result',{'try',{2,17}}}}, + {{13,17},erl_lint,{unsafe_var,'Result',{'try',{8,17}}}}, + {{20,17},erl_lint,{unsafe_var,'Result',{'try',{15,17}}}}], []}}, {unsafe_try2, <<"foo1a() -> @@ -977,19 +963,19 @@ unsafe_vars_try(Config) when is_list(Config) -> {Try,R,Ro,Rc,Ra}. ">>, [], - {errors,[{9,erl_lint,{unsafe_var,'Ra',{'try',3}}}, - {9,erl_lint,{unsafe_var,'Rc',{'try',3}}}, - {17,erl_lint,{unsafe_var,'R',{'try',12}}}, - {19,erl_lint,{unsafe_var,'Ra',{'try',12}}}, - {19,erl_lint,{unsafe_var,'Rc',{'try',12}}}, - {27,erl_lint,{unsafe_var,'R',{'try',22}}}, - {29,erl_lint,{unsafe_var,'Ra',{'try',22}}}, - {29,erl_lint,{unsafe_var,'Ro',{'try',22}}}, - {37,erl_lint,{unsafe_var,'R',{'try',32}}}, - {39,erl_lint,{unsafe_var,'R',{'try',32}}}, - {39,erl_lint,{unsafe_var,'Ra',{'try',32}}}, - {39,erl_lint,{unsafe_var,'Rc',{'try',32}}}, - {39,erl_lint,{unsafe_var,'Ro',{'try',32}}}], + {errors,[{{9,25},erl_lint,{unsafe_var,'Ra',{'try',{3,19}}}}, + {{9,22},erl_lint,{unsafe_var,'Rc',{'try',{3,19}}}}, + {{17,24},erl_lint,{unsafe_var,'R',{'try',{12,19}}}}, + {{19,25},erl_lint,{unsafe_var,'Ra',{'try',{12,19}}}}, + {{19,22},erl_lint,{unsafe_var,'Rc',{'try',{12,19}}}}, + {{27,24},erl_lint,{unsafe_var,'R',{'try',{22,19}}}}, + {{29,25},erl_lint,{unsafe_var,'Ra',{'try',{22,19}}}}, + {{29,22},erl_lint,{unsafe_var,'Ro',{'try',{22,19}}}}, + {{37,24},erl_lint,{unsafe_var,'R',{'try',{32,19}}}}, + {{39,22},erl_lint,{unsafe_var,'R',{'try',{32,19}}}}, + {{39,30},erl_lint,{unsafe_var,'Ra',{'try',{32,19}}}}, + {{39,27},erl_lint,{unsafe_var,'Rc',{'try',{32,19}}}}, + {{39,24},erl_lint,{unsafe_var,'Ro',{'try',{32,19}}}}], []}}, {unsafe_try3, <<"foo1(X) -> @@ -1019,29 +1005,29 @@ unsafe_vars_try(Config) when is_list(Config) -> {X,Try,R,RR,Ra,Class,Data}. ">>, [], - {errors,[{5,erl_lint,{unsafe_var,'R',{'try',3}}}, - {7,erl_lint,{unsafe_var,'Rc',{'try',3}}}, - {11,erl_lint,{unsafe_var,'R',{'try',10}}}, - {13,erl_lint,{unbound_var,'RR'}}, - {13,erl_lint,{unbound_var,'Ro'}}, - {13,erl_lint,{unsafe_var,'R',{'try',10}}}, - {15,erl_lint,{unsafe_var,'Class',{'try',10}}}, - {15,erl_lint,{unsafe_var,'Data',{'try',10}}}, - {15,erl_lint,{unsafe_var,'R',{'try',10}}}, - {15,erl_lint,{unsafe_var,'RR',{'try',10}}}, - {15,erl_lint,{unsafe_var,'Ro',{'try',10}}}, - {19,erl_lint,{unsafe_var,'R',{'try',18}}}, - {21,erl_lint,{unbound_var,'RR'}}, - {21,erl_lint,{unsafe_var,'R',{'try',18}}}, - {23,erl_lint,{unsafe_var,'Class',{'try',18}}}, - {23,erl_lint,{unsafe_var,'Data',{'try',18}}}, - {23,erl_lint,{unsafe_var,'R',{'try',18}}}, - {23,erl_lint,{unsafe_var,'RR',{'try',18}}}, - {25,erl_lint,{unsafe_var,'Class',{'try',18}}}, - {25,erl_lint,{unsafe_var,'Data',{'try',18}}}, - {25,erl_lint,{unsafe_var,'R',{'try',18}}}, - {25,erl_lint,{unsafe_var,'RR',{'try',18}}}, - {25,erl_lint,{unsafe_var,'Ra',{'try',18}}}], + {errors,[{{5,41},erl_lint,{unsafe_var,'R',{'try',{3,19}}}}, + {{7,24},erl_lint,{unsafe_var,'Rc',{'try',{3,19}}}}, + {{11,33},erl_lint,{unsafe_var,'R',{'try',{10,19}}}}, + {{13,40},erl_lint,{unbound_var,'RR'}}, + {{13,43},erl_lint,{unbound_var,'Ro'}}, + {{13,38},erl_lint,{unsafe_var,'R',{'try',{10,19}}}}, + {{15,32},erl_lint,{unsafe_var,'Class',{'try',{10,19}}}}, + {{15,38},erl_lint,{unsafe_var,'Data',{'try',{10,19}}}}, + {{15,24},erl_lint,{unsafe_var,'R',{'try',{10,19}}}}, + {{15,26},erl_lint,{unsafe_var,'RR',{'try',{10,19}}}}, + {{15,29},erl_lint,{unsafe_var,'Ro',{'try',{10,19}}}}, + {{19,30},erl_lint,{unsafe_var,'R',{'try',{18,19}}}}, + {{21,40},erl_lint,{unbound_var,'RR'}}, + {{21,38},erl_lint,{unsafe_var,'R',{'try',{18,19}}}}, + {{23,32},erl_lint,{unsafe_var,'Class',{'try',{18,19}}}}, + {{23,38},erl_lint,{unsafe_var,'Data',{'try',{18,19}}}}, + {{23,27},erl_lint,{unsafe_var,'R',{'try',{18,19}}}}, + {{23,29},erl_lint,{unsafe_var,'RR',{'try',{18,19}}}}, + {{25,32},erl_lint,{unsafe_var,'Class',{'try',{18,19}}}}, + {{25,38},erl_lint,{unsafe_var,'Data',{'try',{18,19}}}}, + {{25,24},erl_lint,{unsafe_var,'R',{'try',{18,19}}}}, + {{25,26},erl_lint,{unsafe_var,'RR',{'try',{18,19}}}}, + {{25,29},erl_lint,{unsafe_var,'Ra',{'try',{18,19}}}}], []}}, {unsafe_try4, <<"foo1(X) -> @@ -1056,23 +1042,23 @@ unsafe_vars_try(Config) when is_list(Config) -> {X,Try,R,RR,Ro,Rc,Ra,Class,Data}. ">>, [], - {errors,[{4,erl_lint,{unsafe_var,'R',{'try',3}}}, - {6,erl_lint,{unbound_var,'RR'}}, - {6,erl_lint,{unbound_var,'Ro'}}, - {6,erl_lint,{unsafe_var,'R',{'try',3}}}, - {8,erl_lint,{unsafe_var,'Class',{'try',3}}}, - {8,erl_lint,{unsafe_var,'Data',{'try',3}}}, - {8,erl_lint,{unsafe_var,'R',{'try',3}}}, - {8,erl_lint,{unsafe_var,'RR',{'try',3}}}, - {8,erl_lint,{unsafe_var,'Rc',{'try',3}}}, - {8,erl_lint,{unsafe_var,'Ro',{'try',3}}}, - {10,erl_lint,{unsafe_var,'Class',{'try',3}}}, - {10,erl_lint,{unsafe_var,'Data',{'try',3}}}, - {10,erl_lint,{unsafe_var,'R',{'try',3}}}, - {10,erl_lint,{unsafe_var,'RR',{'try',3}}}, - {10,erl_lint,{unsafe_var,'Ra',{'try',3}}}, - {10,erl_lint,{unsafe_var,'Rc',{'try',3}}}, - {10,erl_lint,{unsafe_var,'Ro',{'try',3}}}], + {errors,[{{4,33},erl_lint,{unsafe_var,'R',{'try',{3,19}}}}, + {{6,43},erl_lint,{unbound_var,'RR'}}, + {{6,46},erl_lint,{unbound_var,'Ro'}}, + {{6,41},erl_lint,{unsafe_var,'R',{'try',{3,19}}}}, + {{8,38},erl_lint,{unsafe_var,'Class',{'try',{3,19}}}}, + {{8,44},erl_lint,{unsafe_var,'Data',{'try',{3,19}}}}, + {{8,27},erl_lint,{unsafe_var,'R',{'try',{3,19}}}}, + {{8,29},erl_lint,{unsafe_var,'RR',{'try',{3,19}}}}, + {{8,35},erl_lint,{unsafe_var,'Rc',{'try',{3,19}}}}, + {{8,32},erl_lint,{unsafe_var,'Ro',{'try',{3,19}}}}, + {{10,38},erl_lint,{unsafe_var,'Class',{'try',{3,19}}}}, + {{10,44},erl_lint,{unsafe_var,'Data',{'try',{3,19}}}}, + {{10,24},erl_lint,{unsafe_var,'R',{'try',{3,19}}}}, + {{10,26},erl_lint,{unsafe_var,'RR',{'try',{3,19}}}}, + {{10,35},erl_lint,{unsafe_var,'Ra',{'try',{3,19}}}}, + {{10,32},erl_lint,{unsafe_var,'Rc',{'try',{3,19}}}}, + {{10,29},erl_lint,{unsafe_var,'Ro',{'try',{3,19}}}}], []}}], ?line [] = run(Config, Ts), ok. @@ -1141,8 +1127,9 @@ guard(Config) when is_list(Config) -> ">>, [nowarn_obsolete_guard], {error, - [{6,erl_lint,illegal_guard_expr},{18,erl_lint,illegal_guard_expr}], - [{18,erl_lint,{removed,{erlang,is_constant,1}, + [{{6,25},erl_lint,illegal_guard_expr}, + {{18,25},erl_lint,illegal_guard_expr}], + [{{18,25},erl_lint,{removed,{erlang,is_constant,1}, "Removed in R13B"}}]}}, {guard2, <<"-record(apa,{}). @@ -1202,13 +1189,13 @@ guard(Config) when is_list(Config) -> tuple. ">>, [nowarn_obsolete_guard], - {error,[{6,erl_lint,illegal_guard_expr}, - {6,erl_lint,illegal_guard_expr}, - {18,erl_lint,illegal_guard_expr}, - {18,erl_lint,illegal_guard_expr}], - [{18,erl_lint,{removed,{erlang,is_constant,1}, + {error,[{{6,26},erl_lint,illegal_guard_expr}, + {{6,39},erl_lint,illegal_guard_expr}, + {{18,26},erl_lint,illegal_guard_expr}, + {{18,42},erl_lint,illegal_guard_expr}], + [{{18,26},erl_lint,{removed,{erlang,is_constant,1}, "Removed in R13B"}}, - {18,erl_lint,{removed,{erlang,is_constant,1}, + {{18,42},erl_lint,{removed,{erlang,is_constant,1}, "Removed in R13B"}}]}}, {guard3, <<"-record(apa,{}). @@ -1331,20 +1318,20 @@ guard(Config) when is_list(Config) -> foo. ">>, [warn_unused_vars, nowarn_obsolete_guard], - {error,[{2,erl_lint,illegal_guard_expr}, - {4,erl_lint,illegal_guard_expr}, - {6,erl_lint,illegal_guard_expr}, - {8,erl_lint,illegal_guard_expr}, - {10,erl_lint,illegal_guard_expr}, - {12,erl_lint,illegal_guard_expr}, - {14,erl_lint,illegal_guard_expr}, - {16,erl_lint,illegal_guard_expr}, - {18,erl_lint,illegal_guard_expr}, - {20,erl_lint,illegal_guard_expr}], - [{8,erl_lint,deprecated_tuple_fun}, - {14,erl_lint,deprecated_tuple_fun}, - {20,erl_lint,deprecated_tuple_fun}, - {28,erl_lint,deprecated_tuple_fun}]}}, + {error,[{{2,27},erl_lint,illegal_guard_expr}, + {{4,27},erl_lint,illegal_guard_expr}, + {{6,33},erl_lint,illegal_guard_expr}, + {{8,27},erl_lint,illegal_guard_expr}, + {{10,27},erl_lint,illegal_guard_expr}, + {{12,33},erl_lint,illegal_guard_expr}, + {{14,27},erl_lint,illegal_guard_expr}, + {{16,27},erl_lint,illegal_guard_expr}, + {{18,33},erl_lint,illegal_guard_expr}, + {{20,27},erl_lint,illegal_guard_expr}], + [{{8,27},erl_lint,deprecated_tuple_fun}, + {{14,27},erl_lint,deprecated_tuple_fun}, + {{20,27},erl_lint,deprecated_tuple_fun}, + {{28,27},erl_lint,deprecated_tuple_fun}]}}, {guard6, <<"-record(apa,{a=a,b=foo:bar()}). apa() -> @@ -1355,7 +1342,7 @@ guard(Config) when is_list(Config) -> [X || X <- [], #ful{a = a} == {r,X,foo}]. ">>, [], - {errors,[{7,erl_lint,{undefined_record,ful}}], + {errors,[{{7,33},erl_lint,{undefined_record,ful}}], []}}, {guard7, <<"-record(apa,{}). @@ -1385,9 +1372,9 @@ otp_4886(Config) when is_list(Config) -> {erlang,is_record}(X, foo, 1). ">>, [], - {errors,[{3,erl_lint,{undefined_record,foo}}, - {4,erl_lint,{undefined_record,foo}}, - {5,erl_lint,{undefined_record,foo}}], + {errors,[{{3,32},erl_lint,{undefined_record,foo}}, + {{4,39},erl_lint,{undefined_record,foo}}, + {{5,41},erl_lint,{undefined_record,foo}}], []}}], ?line [] = run(Config, Ts), ok. @@ -1410,11 +1397,11 @@ otp_4988(Config) when is_list(Config) -> {A}. ">>, [], - {errors,[{1,erl_lint,{bad_inline,{1,foo}}}, - {1,erl_lint,{bad_inline,{f,3}}}, - {1,erl_lint,{bad_inline,{f,4}}}, - {1,erl_lint,{bad_inline,{f,a}}}, - {3,erl_lint,{bad_inline,{g,12}}}], + {errors,[{{1,2},erl_lint,{bad_inline,{1,foo}}}, + {{1,2},erl_lint,{bad_inline,{f,3}}}, + {{1,2},erl_lint,{bad_inline,{f,4}}}, + {{1,2},erl_lint,{bad_inline,{f,a}}}, + {{3,16},erl_lint,{bad_inline,{g,12}}}], []}}], ?line [] = run(Config, Ts), ok. @@ -1465,13 +1452,13 @@ otp_5091(Config) when is_list(Config) -> F(<<16:8, 7:16>>). ">>, [], - {warnings,[{3,erl_lint,{shadowed_var,'L','fun'}}]}}, + {warnings,[{{3,28},erl_lint,{shadowed_var,'L','fun'}}]}}, {otp_5091_6, <<"t(A) -> (fun(<>) -> ok end)(A). ">>, [], - {warnings,[{2,erl_lint,{unused_var,'N'}}]}}, + {warnings,[{{2,34},erl_lint,{unused_var,'N'}}]}}, {otp_5091_7, <<"t() -> U = 8, @@ -1479,7 +1466,7 @@ otp_5091(Config) when is_list(Config) -> U>>) -> U end)(<<32:8>>). ">>, [], - {warnings,[{3,erl_lint,{shadowed_var,'U','fun'}}]}}, + {warnings,[{{3,26},erl_lint,{shadowed_var,'U','fun'}}]}}, {otp_5091_8, <<"t() -> [X || < F(<<16:8, 8:16, 32:8>>). ">>, [], - {warnings,[{3,erl_lint,{shadowed_var,'L','fun'}}]}}, + {warnings,[{{3,29},erl_lint,{shadowed_var,'L','fun'}}]}}, {otp_5091_10, <<"t() -> L = 8, <> = <<16:8, 7:16>>, B. @@ -1523,9 +1510,9 @@ otp_5091(Config) when is_list(Config) -> end. ">>, [], - {warnings,[{2,erl_lint,{unused_var,'A'}}, - {2,erl_lint,{shadowed_var,'A','fun'}}, - {3,erl_lint,{unused_var,'Q'}}]}}, + {warnings,[{{2,24},erl_lint,{unused_var,'A'}}, + {{2,24},erl_lint,{shadowed_var,'A','fun'}}, + {{3,24},erl_lint,{unused_var,'Q'}}]}}, {otp_5091_13, <<"t([A,B]) -> % A unused, B unused fun({A,B}, % A shadowed, B unused, B shadowed @@ -1533,12 +1520,12 @@ otp_5091(Config) when is_list(Config) -> end. ">>, [], - {warnings,[{1,erl_lint,{unused_var,'A'}}, - {1,erl_lint,{unused_var,'B'}}, - {2,erl_lint,{unused_var,'B'}}, - {2,erl_lint,{shadowed_var,'A','fun'}}, - {2,erl_lint,{shadowed_var,'B','fun'}}, - {3,erl_lint,{unused_var,'Q'}}]}}, + {warnings,[{{1,4},erl_lint,{unused_var,'A'}}, + {{1,6},erl_lint,{unused_var,'B'}}, + {{2,25},erl_lint,{unused_var,'B'}}, + {{2,23},erl_lint,{shadowed_var,'A','fun'}}, + {{2,25},erl_lint,{shadowed_var,'B','fun'}}, + {{3,23},erl_lint,{unused_var,'Q'}}]}}, {otp_5091_14, <<"t() -> A = 4, @@ -1546,8 +1533,8 @@ otp_5091(Config) when is_list(Config) -> A>>) -> 2 end. ">>, [], - {warnings,[{3,erl_lint,{unused_var,'A'}}, - {3,erl_lint,{shadowed_var,'A','fun'}}]}}, + {warnings,[{{3,24},erl_lint,{unused_var,'A'}}, + {{3,24},erl_lint,{shadowed_var,'A','fun'}}]}}, {otp_5091_15, <<"t() -> A = 4, % unused @@ -1555,8 +1542,8 @@ otp_5091(Config) when is_list(Config) -> 16:A>>) -> 2 end. ">>, [], - {warnings,[{2,erl_lint,{unused_var,'A'}}, - {3,erl_lint,{shadowed_var,'A','fun'}}]}}, + {warnings,[{{2,18},erl_lint,{unused_var,'A'}}, + {{3,24},erl_lint,{shadowed_var,'A','fun'}}]}}, {otp_5091_16, <<"t() -> A = 4, @@ -1564,8 +1551,8 @@ otp_5091(Config) when is_list(Config) -> A:8>>) -> 7 end. % shadowed, unused ">>, [], - {warnings,[{4,erl_lint,{unused_var,'A'}}, - {4,erl_lint,{shadowed_var,'A','fun'}}]}}, + {warnings,[{{4,24},erl_lint,{unused_var,'A'}}, + {{4,24},erl_lint,{shadowed_var,'A','fun'}}]}}, {otp_5091_17, <<"t() -> L = 16, @@ -1577,7 +1564,7 @@ otp_5091(Config) when is_list(Config) -> end. ">>, [], - {warnings,[{3,erl_lint,{shadowed_var,'L','fun'}}]}}, + {warnings,[{{3,24},erl_lint,{shadowed_var,'L','fun'}}]}}, {otp_5091_18, <<"t() -> L = 4, % L unused @@ -1589,8 +1576,8 @@ otp_5091(Config) when is_list(Config) -> end. ">>, [], - {warnings,[{2,erl_lint,{unused_var,'L'}}, - {3,erl_lint,{shadowed_var,'L','fun'}}]}}, + {warnings,[{{2,18},erl_lint,{unused_var,'L'}}, + {{3,23},erl_lint,{shadowed_var,'L','fun'}}]}}, {otp_5091_19, <<"t() -> L = 4, @@ -1600,32 +1587,32 @@ otp_5091(Config) when is_list(Config) -> L>> <- []]. ">>, [], - {warnings,[{3,erl_lint,{shadowed_var,'L',generate}}]}}, + {warnings,[{{3,26},erl_lint,{shadowed_var,'L',generate}}]}}, {otp_5091_20, <<"t() -> L = 4, % L unused. [1 || L <- []]. % L unused, L shadowed. ">>, [], - {warnings,[{2,erl_lint,{unused_var,'L'}}, - {3,erl_lint,{unused_var,'L'}}, - {3,erl_lint,{shadowed_var,'L',generate}}]}}, + {warnings,[{{2,18},erl_lint,{unused_var,'L'}}, + {{3,24},erl_lint,{unused_var,'L'}}, + {{3,24},erl_lint,{shadowed_var,'L',generate}}]}}, {otp_5091_21, <<"t() -> L = 4, [1 || L <- [L]]. % L shadowed. L unused. ">>, [], - {warnings,[{3,erl_lint,{unused_var,'L'}}, - {3,erl_lint,{shadowed_var,'L',generate}}]}}, + {warnings,[{{3,24},erl_lint,{unused_var,'L'}}, + {{3,24},erl_lint,{shadowed_var,'L',generate}}]}}, {otp_5091_22, <<"t() -> L = 4, % unused fun(L) -> L end. % shadowed ">>, [], - {warnings,[{2,erl_lint,{unused_var,'L'}}, - {3,erl_lint,{shadowed_var,'L','fun'}}]}}, + {warnings,[{{2,18},erl_lint,{unused_var,'L'}}, + {{3,22},erl_lint,{shadowed_var,'L','fun'}}]}}, {otp_5091_23, <<"t([A,A]) -> a.">>, [], []}, {otp_5091_24, @@ -1657,13 +1644,13 @@ otp_5276(Config) when is_list(Config) -> t() -> ok. ">>, {[]}, - {error,[{1,erl_lint,{bad_deprecated,{frutt,0}}}, - {2,erl_lint,{bad_deprecated,{does_not_exist,1}}}, - {3,erl_lint,{invalid_deprecated,'foo bar'}}, - {5,erl_lint,{bad_deprecated,{f,'_'}}}, - {8,erl_lint,{invalid_deprecated,{'_','_',never}}}, - {9,erl_lint,{invalid_deprecated,{{badly,formed},1}}}], - [{12,erl_lint,{unused_function,{frutt,0}}}]}}], + {error,[{{1,2},erl_lint,{bad_deprecated,{frutt,0}}}, + {{2,15},erl_lint,{bad_deprecated,{does_not_exist,1}}}, + {{3,15},erl_lint,{invalid_deprecated,'foo bar'}}, + {{5,15},erl_lint,{bad_deprecated,{f,'_'}}}, + {{8,15},erl_lint,{invalid_deprecated,{'_','_',never}}}, + {{9,15},erl_lint,{invalid_deprecated,{{badly,formed},1}}}], + [{{12,14},erl_lint,{unused_function,{frutt,0}}}]}}], ?line [] = run(Config, Ts), ok. @@ -1701,9 +1688,9 @@ otp_6585(Config) when is_list(Config) -> f([]). ">>, [warn_obsolete_guard], - {warnings,[{5,erl_lint,{obsolete_guard,{list,1}}}, - {6,erl_lint,{obsolete_guard,{record,2}}}, - {7,erl_lint,{obsolete_guard,{pid,1}}}]}}], + {warnings,[{{5,24},erl_lint,{obsolete_guard,{list,1}}}, + {{6,24},erl_lint,{obsolete_guard,{record,2}}}, + {{7,24},erl_lint,{obsolete_guard,{pid,1}}}]}}], ?line [] = run(Config, Ts), ok. @@ -1719,8 +1706,8 @@ otp_5338(Config) when is_list(Config) -> #c{}. ">>, [], - {error,[{1,erl_lint,{unbound_var,'X'}}], - [{3,erl_lint,{unused_var,'X'}}]}}], + {error,[{{1,19},erl_lint,{unbound_var,'X'}}], + [{{3,19},erl_lint,{unused_var,'X'}}]}}], ?line [] = run(Config, Ts), ok. @@ -1739,8 +1726,8 @@ otp_5362(Config) when is_list(Config) -> begin A = 3, true end]). ">>, {[warn_unused_vars]}, - {warnings,[{1002,erl_lint,{unused_function,{t,0}}}, - {1004,erl_lint,{unused_var,'A'}}]}}, + {warnings,[{{1002,14},erl_lint,{unused_function,{t,0}}}, + {{1004,36},erl_lint,{unused_var,'A'}}]}}, {otp_5362_2, <<"-export([inline/0]). @@ -1773,14 +1760,15 @@ otp_5362(Config) when is_list(Config) -> ok. ">>, {[warn_unused_vars, warn_unused_import]}, - {error,[{5,erl_lint,{bad_inline,{inl,7}}}, - {6,erl_lint,{bad_inline,{inl,17}}}, - {11,erl_lint,{undefined_function,{fipp,0}}}, - {22,erl_lint,{bad_nowarn_unused_function,{and_not_used,2}}}], - [{3,erl_lint,{unused_import,{{b,1},'lists.foo'}}}, - {9,erl_lint,{unused_function,{foop,0}}}, - {19,erl_lint,{unused_function,{not_used,0}}}, - {23,erl_lint,{unused_function,{and_not_used,1}}}]}}, + {error,[{{5,15},erl_lint,{bad_inline,{inl,7}}}, + {{6,15},erl_lint,{bad_inline,{inl,17}}}, + {{11,18},erl_lint,{undefined_function,{fipp,0}}}, + {{22,15},erl_lint,{bad_nowarn_unused_function, + {and_not_used,2}}}], + [{{3,15},erl_lint,{unused_import,{{b,1},'lists.foo'}}}, + {{9,14},erl_lint,{unused_function,{foop,0}}}, + {{19,14},erl_lint,{unused_function,{not_used,0}}}, + {{23,14},erl_lint,{unused_function,{and_not_used,1}}}]}}, {otp_5362_3, <<"-record(a, {x, @@ -1803,12 +1791,12 @@ otp_5362(Config) when is_list(Config) -> }. ">>, {[nowarn_unused_function]}, - {errors2, [{4,erl_parse,"bad record field"}, - {5,erl_parse,"bad record declaration"}], - [{2,erl_lint,{redefine_field,a,x}}, - {14,erl_lint,{undefined_record,nix}}, - {15,erl_lint,{undefined_field,ok,nix}}, - {16,erl_lint,{field_name_is_variable,ok,'Var'}}]}}, + {errors2, [{{4,27},erl_parse,"bad record field"}, + {{5,26},erl_parse,"bad record declaration"}], + [{{2,27},erl_lint,{redefine_field,a,x}}, + {{14,20},erl_lint,{undefined_record,nix}}, + {{15,24},erl_lint,{undefined_field,ok,nix}}, + {{16,24},erl_lint,{field_name_is_variable,ok,'Var'}}]}}, %% Nowarn_bif_clash has changed behaviour as local functions %% nowdays supersede auto-imported BIFs, why nowarn_bif_clash in itself generates an error @@ -1824,8 +1812,8 @@ otp_5362(Config) when is_list(Config) -> warn_deprecated_function, warn_bif_clash]}, {error, - [{5,erl_lint,{call_to_redefined_old_bif,{spawn,1}}}], - [{4,erl_lint,{deprecated,{erlang,hash,2},{erlang,phash2,2}, + [{{5,19},erl_lint,{call_to_redefined_old_bif,{spawn,1}}}], + [{{4,25},erl_lint,{deprecated,{erlang,hash,2},{erlang,phash2,2}, "in a future release"}}]}}, {otp_5362_5, @@ -1837,7 +1825,7 @@ otp_5362(Config) when is_list(Config) -> ">>, {[nowarn_unused_function]}, {errors, - [{2,erl_lint,disallowed_nowarn_bif_clash}],[]}}, + [{{2,16},erl_lint,disallowed_nowarn_bif_clash}],[]}}, %% The special nowarn_X are not affected by general warn_X. {otp_5362_6, @@ -1851,7 +1839,7 @@ otp_5362(Config) when is_list(Config) -> warn_deprecated_function, warn_bif_clash]}, {errors, - [{2,erl_lint,disallowed_nowarn_bif_clash}],[]}}, + [{{2,16},erl_lint,disallowed_nowarn_bif_clash}],[]}}, {otp_5362_7, <<"-export([spawn/1]). @@ -1866,12 +1854,13 @@ otp_5362(Config) when is_list(Config) -> spawn(A). ">>, {[nowarn_unused_function]}, - {error,[{3,erl_lint,disallowed_nowarn_bif_clash}, - {4,erl_lint,disallowed_nowarn_bif_clash}, - {4,erl_lint,{bad_nowarn_bif_clash,{spawn,2}}}], - [{5,erl_lint,{bad_nowarn_deprecated_function,{3,hash,-1}}}, - {5,erl_lint,{bad_nowarn_deprecated_function,{erlang,hash,-1}}}, - {5,erl_lint,{bad_nowarn_deprecated_function,{{a,b,c},hash,-1}}}]} + {error,[{{3,16},erl_lint,disallowed_nowarn_bif_clash}, + {{4,16},erl_lint,disallowed_nowarn_bif_clash}, + {{4,16},erl_lint,{bad_nowarn_bif_clash,{spawn,2}}}], + [{{5,16},erl_lint,{bad_nowarn_deprecated_function,{3,hash,-1}}}, + {{5,16},erl_lint,{bad_nowarn_deprecated_function,{erlang,hash,-1}}}, + {{5,16},erl_lint,{bad_nowarn_deprecated_function, + {{a,b,c},hash,-1}}}]} }, {otp_5362_8, @@ -1885,7 +1874,7 @@ otp_5362(Config) when is_list(Config) -> {[nowarn_unused_function, {nowarn_bif_clash,{spawn,1}}]}, % has no effect {warnings, - [{5,erl_lint,{deprecated,{erlang,hash,2},{erlang,phash2,2}, + [{{5,25},erl_lint,{deprecated,{erlang,hash,2},{erlang,phash2,2}, "in a future release"}}]}}, {otp_5362_9, @@ -1909,7 +1898,7 @@ otp_5362(Config) when is_list(Config) -> warn_deprecated_function, warn_bif_clash]}, {errors, - [{2,erl_lint,disallowed_nowarn_bif_clash}],[]}} + [{{2,16},erl_lint,disallowed_nowarn_bif_clash}],[]}} ], @@ -1925,7 +1914,7 @@ otp_5371(Config) when is_list(Config) -> {A,B}. ">>, [], - {errors,[{1,erl_lint,illegal_bin_pattern}],[]}}, + {errors,[{{1,3},erl_lint,illegal_bin_pattern}],[]}}, {otp_5371_2, <<"x([<>] = [<>]) -> {A,B}. @@ -1933,8 +1922,8 @@ otp_5371(Config) when is_list(Config) -> {A,B}. ">>, [], - {errors,[{1,erl_lint,illegal_bin_pattern}, - {3,erl_lint,illegal_bin_pattern}],[]}}, + {errors,[{{1,4},erl_lint,illegal_bin_pattern}, + {{3,20},erl_lint,illegal_bin_pattern}],[]}}, {otp_5371_3, <<"-record(foo, {a,b,c}). -record(bar, {x,y,z}). @@ -1951,11 +1940,11 @@ otp_5371(Config) when is_list(Config) -> {X,Y}. ">>, [], - {errors,[{4,erl_lint,illegal_bin_pattern}, - {6,erl_lint,illegal_bin_pattern}, - {8,erl_lint,illegal_bin_pattern}, - {10,erl_lint,illegal_bin_pattern}, - {12,erl_lint,illegal_bin_pattern}],[]}}, + {errors,[{{4,26},erl_lint,illegal_bin_pattern}, + {{6,26},erl_lint,illegal_bin_pattern}, + {{8,26},erl_lint,illegal_bin_pattern}, + {{10,30},erl_lint,illegal_bin_pattern}, + {{12,30},erl_lint,illegal_bin_pattern}],[]}}, {otp_5371_4, <<"-record(foo, {a,b,c}). -record(bar, {x,y,z}). @@ -1968,9 +1957,9 @@ otp_5371(Config) when is_list(Config) -> {X,Y}. ">>, [], - {warnings,[{4,v3_core,nomatch}, - {6,v3_core,nomatch}, - {8,v3_core,nomatch}]}} + {warnings,[{{4,15},v3_core,nomatch}, + {{6,15},v3_core,nomatch}, + {{8,15},v3_core,nomatch}]}} ], ?line [] = run(Config, Ts), ok. @@ -1982,35 +1971,35 @@ otp_7227(Config) when is_list(Config) -> {A,B,C,D}. ">>, [], - {errors,[{1,erl_lint,illegal_bin_pattern}],[]}}, + {errors,[{{1,22},erl_lint,illegal_bin_pattern}],[]}}, {otp_7227_2, <<"t([(<> = {C,D}) = <>]) -> {A,B,C,D}. ">>, [], - {errors,[{1,erl_lint,illegal_bin_pattern}],[]}}, + {errors,[{{1,5},erl_lint,illegal_bin_pattern}],[]}}, {otp_7227_3, <<"t([(<> = {C,D}) = (<> = <>)]) -> {A,B,C,D}. ">>, [], - {errors,[{1,erl_lint,illegal_bin_pattern}, - {1,erl_lint,illegal_bin_pattern}, - {1,erl_lint,illegal_bin_pattern}],[]}}, + {errors,[{{1,25},erl_lint,illegal_bin_pattern}, + {{1,25},erl_lint,illegal_bin_pattern}, + {{1,35},erl_lint,illegal_bin_pattern}],[]}}, {otp_7227_4, <<"t(Val) -> <> = <> = Val, {A,B}. ">>, [], - {errors,[{2,erl_lint,illegal_bin_pattern}],[]}}, + {errors,[{{2,19},erl_lint,illegal_bin_pattern}],[]}}, {otp_7227_5, <<"t(Val) -> <> = X = <> = Val, {A,B,X}. ">>, [], - {errors,[{2,erl_lint,illegal_bin_pattern}],[]}}, + {errors,[{{2,19},erl_lint,illegal_bin_pattern}],[]}}, {otp_7227_6, <<"t(X, Y) -> <> = <>, @@ -2024,23 +2013,23 @@ otp_7227(Config) when is_list(Config) -> {A,B,X}. ">>, [], - {errors,[{2,erl_lint,illegal_bin_pattern}, - {2,erl_lint,illegal_bin_pattern}, - {2,erl_lint,illegal_bin_pattern}],[]}}, + {errors,[{{2,36},erl_lint,illegal_bin_pattern}, + {{2,36},erl_lint,illegal_bin_pattern}, + {{2,46},erl_lint,illegal_bin_pattern}],[]}}, {otp_7227_8, <<"t(Val) -> (<> = X) = (Y = <>) = Val, {A,B,X,Y}. ">>, [], - {errors,[{2,erl_lint,illegal_bin_pattern}],[]}}, + {errors,[{{2,40},erl_lint,illegal_bin_pattern}],[]}}, {otp_7227_9, <<"t(Val) -> (Z = <> = X) = (Y = <> = W) = Val, {A,B,X,Y,Z,W}. ">>, [], - {errors,[{2,erl_lint,illegal_bin_pattern}],[]}} + {errors,[{{2,44},erl_lint,illegal_bin_pattern}],[]}} ], ?line [] = run(Config, Ts), ok. @@ -2055,7 +2044,7 @@ otp_5494(Config) when is_list(Config) -> t() -> a. ">>, [], - {warnings,[{2,erl_lint,{duplicated_export,{t,0}}}]}}], + {warnings,[{{2,16},erl_lint,{duplicated_export,{t,0}}}]}}], ?line [] = run(Config, Ts), ok. @@ -2090,8 +2079,8 @@ otp_5878(Config) when is_list(Config) -> t() ->#rec1{}. ">>, [warn_unused_record], - {error,[{1,erl_lint,{undefined_record,rec2}}], - [{2,erl_lint,{unused_record,rec2}}]}}, + {error,[{{1,20},erl_lint,{undefined_record,rec2}}], + [{{2,15},erl_lint,{unused_record,rec2}}]}}, {otp_5878_20, <<"-record(r1, {a = begin A = 4, {A,B} end}). % B unbound @@ -2099,10 +2088,10 @@ otp_5878(Config) when is_list(Config) -> t() -> #r2{}. ">>, [warn_unused_record], - {error,[{1,erl_lint,{unbound_var,'B'}}, - {1,erl_lint,{variable_in_record_def,'A'}}, - {2,erl_lint,{variable_in_record_def,'A'}}], - [{1,erl_lint,{unused_record,r1}}]}}, + {error,[{{1,34},erl_lint,{unbound_var,'B'}}, + {{1,24},erl_lint,{variable_in_record_def,'A'}}, + {{2,38},erl_lint,{variable_in_record_def,'A'}}], + [{{1,2},erl_lint,{unused_record,r1}}]}}, {otp_5878_30, <<"-record(r1, {t = case foo of _ -> 3 end}). @@ -2111,8 +2100,8 @@ otp_5878(Config) when is_list(Config) -> t() -> {#r1{},#r2{},#r3{}}. ">>, [warn_unused_record], - {errors,[{2,erl_lint,{variable_in_record_def,'A'}}, - {3,erl_lint,{variable_in_record_def,'A'}}], + {errors,[{{2,44},erl_lint,{variable_in_record_def,'A'}}, + {{3,44},erl_lint,{variable_in_record_def,'A'}}], []}}, {otp_5878_40, @@ -2122,7 +2111,7 @@ otp_5878(Config) when is_list(Config) -> t() -> {#r1{},#r2{},#r3{}}. ">>, [warn_unused_record], - {errors,[{1,erl_lint,{unbound_var,'A'}}],[]}}, + {errors,[{{1,20},erl_lint,{unbound_var,'A'}}],[]}}, {otp_5878_50, <<"-record(r1, {a = {A, % A unbound @@ -2149,11 +2138,11 @@ otp_5878(Config) when is_list(Config) -> t() -> {#r1{},#r2{},#r3{},#r4{}}. ">>, [warn_unused_record], - {error,[{1,erl_lint,{unbound_var,'A'}}, - {2,erl_lint,{unbound_var,'A'}}, - {4,erl_lint,{variable_in_record_def,'A'}}, - {17,erl_lint,{variable_in_record_def,'A'}}], - [{8,erl_lint,{unused_var,'X'}}]}}, + {error,[{{1,19},erl_lint,{unbound_var,'A'}}, + {{2,33},erl_lint,{unbound_var,'A'}}, + {{4,42},erl_lint,{variable_in_record_def,'A'}}, + {{17,44},erl_lint,{variable_in_record_def,'A'}}], + [{{8,36},erl_lint,{unused_var,'X'}}]}}, {otp_5878_60, <<"-record(r1, {a = fun(NotShadowing) -> NotShadowing end}). @@ -2174,8 +2163,8 @@ otp_5878(Config) when is_list(Config) -> t() -> #r1{}. ">>, [warn_unused_record], - {errors,[{3,erl_lint,{unbound_var,'Y'}}, - {4,erl_lint,{variable_in_record_def,'Y'}}], + {errors,[{{3,40},erl_lint,{unbound_var,'Y'}}, + {{4,38},erl_lint,{variable_in_record_def,'Y'}}], []}}, {otp_5878_80, @@ -2185,7 +2174,7 @@ otp_5878(Config) when is_list(Config) -> t() ->#r{}. ">>, [warn_unused_record], - {warnings,[{1,erl_lint,{unused_var,'V'}}]}}, + {warnings,[{{1,39},erl_lint,{unused_var,'V'}}]}}, {otp_5878_90, <<"-record(r, {a = foo()}). % unused @@ -2193,38 +2182,34 @@ otp_5878(Config) when is_list(Config) -> t() -> ok. ">>, [warn_unused_record], - {error,[{1,erl_lint,{undefined_function,{foo,0}}}], - [{1,erl_lint,{unused_record,r}}]}} + {error,[{{1,17},erl_lint,{undefined_function,{foo,0}}}], + [{{1,2},erl_lint,{unused_record,r}}]}}, - ], - ?line [] = run(Config, Ts), + {otp_5878_abstr, + <<"-module(lint_test, [A, B]). - Abstr = <<"-module(lint_test, [A, B]). + -record(r, {a = A, b = THIS}). % A and THIS are unbound - -export([args/1]). + %% param:args(compile,param:new(1,2)). - -record(r, {a = A, b = THIS}). % A and THIS are unbound + args(C) -> + X = local(C), + Z = new(A, B), + F = fun(THIS) -> {x, A} end, % THIS unused and shadowed + {X, Z, THIS, F, #r{}}. - %% param:args(compile,param:new(1,2)). + local(C) -> + module_info(C). + ">>, + [warn_unused_record], + {error,[{{3,31},erl_lint,{unbound_var,'A'}}, + {{3,38},erl_lint,{unbound_var,'THIS'}}], + [{{10,26},erl_lint,{unused_var,'THIS'}}, + {{10,26},erl_lint,{shadowed_var,'THIS','fun'}}]}}, - args(C) -> - X = local(C), - Z = new(A, B), - F = fun(THIS) -> {x, A} end, % THIS unused and shadowed - {X, Z, THIS, F, #r{}}. - local(C) -> - module_info(C). - ">>, - ?line {error,[{5,erl_lint,{unbound_var,'A'}}, - {5,erl_lint,{unbound_var,'THIS'}}], - [{12,erl_lint,{unused_var,'THIS'}}, - {12,erl_lint,{shadowed_var,'THIS','fun'}}]} - = run_test2(Config, Abstr, [warn_unused_record]), - - QLC1 = <<"-module(lint_test). - -include_lib(\"stdlib/include/qlc.hrl\"). - -export([t/0]). + {otp_5878_qlc1, + <<"-include_lib(\"stdlib/include/qlc.hrl\"). -record(r1, {a = qlc:e(qlc:q([X || X <- [1,2,3]]))}). -record(r2, {a = qlc:q([X || X <- [1,2,3]])}). -record(r3, {a = qlc:q([X || {A,Y} <- [{1,2},V={3,4}], @@ -2232,15 +2217,14 @@ otp_5878(Config) when is_list(Config) -> X <- Z ++ [A,Y]])}). t() -> {#r1{},#r2{},#r3{}}. ">>, - ?line {error,[{8,qlc,{used_generator_variable,'A'}}, - {8,qlc,{used_generator_variable,'Y'}}, - {8,qlc,{used_generator_variable,'Z'}}], - [{6,erl_lint,{unused_var,'V'}}]} = - run_test2(Config, QLC1, [warn_unused_record]), + [warn_unused_record], + {error,[{{6,55},qlc,{used_generator_variable,'A'}}, + {{6,57},qlc,{used_generator_variable,'Y'}}, + {{6,49},qlc,{used_generator_variable,'Z'}}], + [{{4,60},erl_lint,{unused_var,'V'}}]}}, - Ill1 = <<"-module(lint_test). - -export([t/0]). - -record(r, {a = true}). + {otp_5878_ill1, + <<"-record(r, {a = true}). -record(r1, {a,b}). -record(r2, {a = #r1{a = true}}). -record(r3, {a = A}). % A is unbound @@ -2271,20 +2255,18 @@ otp_5878(Config) when is_list(Config) -> x() -> bar. - ">>, - - ?line {errors,[{6,erl_lint,{unbound_var,'A'}}, - {13,erl_lint,illegal_guard_expr}, - {15,erl_lint,{undefined_field,r3,q}}, - {17,erl_lint,{undefined_field,r,q}}, - {21,erl_lint,illegal_guard_expr}, - {23,erl_lint,{illegal_guard_local_call,{l,0}}}], - []} = - run_test2(Config, Ill1, [warn_unused_record]), - - Ill2 = <<"-module(lint_test). - -export([t/0]). - t() -> + ">>, + [warn_unused_record], + {errors,[{{4,32},erl_lint,{unbound_var,'A'}}, + {{11,31},erl_lint,illegal_guard_expr}, + {{13,35},erl_lint,{undefined_field,r3,q}}, + {{15,34},erl_lint,{undefined_field,r,q}}, + {{19,41},erl_lint,illegal_guard_expr}, + {{21,30},erl_lint,{illegal_guard_local_call,{l,0}}}], + []}}, + + {otp_5878_ill2, + <<"t() -> case x() of _ when l() or @@ -2292,29 +2274,47 @@ otp_5878(Config) when is_list(Config) -> foo end. ">>, - ?line {errors,[{4,erl_lint,{undefined_function,{x,0}}}, - {5,erl_lint,illegal_guard_expr}, - {7,erl_lint,illegal_guard_expr}], - []} = - run_test2(Config, Ill2, [warn_unused_record]), - + [warn_unused_record], + {errors,[{{2,24},erl_lint,{undefined_function,{x,0}}}, + {{3,30},erl_lint,illegal_guard_expr}, + {{5,30},erl_lint,illegal_guard_expr}], + []}}, + + {otp_5878_usage1, + <<"-record(u1, {a}). + -record(u2, {a = #u1{}}). + -record(u3, {a}). % unused + -record(u4, {a = #u3{}}). % unused + + t() -> + {#u2{}}. + ">>, + [warn_unused_record], + {warnings,[{{3,16},erl_lint,{unused_record,u3}}, + {{4,16},erl_lint,{unused_record,u4}}]}}, + + {otp_5878_qlc2, + <<"-import(qlc, [q/2]). + + t() -> + H1 = qlc:q([X || X <- [1,2]]), + H2 = qlc:q([X || X <- [1,2]], []), + H3 = q([X || X <- [1,2]], []), + {H1,H2,H3}. + ">>, + [warn_unused_record], + {warnings,[{{4,27},erl_lint,{missing_qlc_hrl,1}}, + {{5,27},erl_lint,{missing_qlc_hrl,2}}, + {{6,24},erl_lint,{missing_qlc_hrl,2}}]}} + ], + ?line [] = run(Config, Ts), + Ill3 = <<"t() -> ok.">>, ?line {errors,[{1,erl_lint,undefined_module}],[]} = run_test2(Config, Ill3, [warn_unused_record]), - Usage1 = <<"-module(lint_test). - -export([t/0]). - -record(u1, {a}). - -record(u2, {a = #u1{}}). - -record(u3, {a}). % unused - -record(u4, {a = #u3{}}). % unused - - t() -> - {#u2{}}. - ">>, - ?line {warnings,[{5,erl_lint,{unused_record,u3}}, - {6,erl_lint,{unused_record,u4}}]} = - run_test2(Config, Usage1, [warn_unused_record]), + ?line {errors,[{{1,1},erl_lint,undefined_module}],[]} = + run_test2(Config, Ill3, [column, warn_unused_record]), Usage2 = <<"-module(lint_test). -export([t/0]). @@ -2329,23 +2329,6 @@ otp_5878(Config) when is_list(Config) -> ">>, ?line [] = run_test2(Config, Usage2, [warn_unused_record]), - %% This a completely different story... - %% The linter checks if qlc.hrl hasn't been included - QLC2 = <<"-module(lint_test). - -import(qlc, [q/2]). - -export([t/0]). - - t() -> - H1 = qlc:q([X || X <- [1,2]]), - H2 = qlc:q([X || X <- [1,2]], []), - H3 = q([X || X <- [1,2]], []), - {H1,H2,H3}. - ">>, - ?line {warnings,[{6,erl_lint,{missing_qlc_hrl,1}}, - {7,erl_lint,{missing_qlc_hrl,2}}, - {8,erl_lint,{missing_qlc_hrl,2}}]} = - run_test2(Config, QLC2, [warn_unused_record]), - %% Records that are used by types are not unused. %% (Thanks to Fredrik Thulin and Kostis Sagonas.) UsedByType = <<"-module(t). @@ -2365,52 +2348,55 @@ otp_6885(doc) -> "OTP-6885. Binary fields in bit syntax matching is now only allowed at the end."; otp_6885(suite) -> []; otp_6885(Config) when is_list(Config) -> - Ts = <<"-module(otp_6885). - -export([t/1]). - t(<<_/binary,I>>) -> I; - t(<>) -> I; - t(<>) -> {B,T}. - - build(A, B) -> - <>. - - foo(<<\"abc\"/binary>>) -> - ok; - foo(<<\"abc\":13/integer>>) -> - ok; - foo(<<\"abc\"/float>>) -> - ok; - foo(<<\"abc\":19>>) -> - ok; - foo(<<\"abc\"/utf8>>) -> - ok; - foo(<<\"abc\"/utf16>>) -> - ok; - foo(<<\"abc\"/utf32>>) -> - ok. - - ">>, - ?line {errors,[{3,erl_lint,unsized_binary_not_at_end}, - {4,erl_lint,unsized_binary_not_at_end}, - {5,erl_lint,unsized_binary_not_at_end}, - {10,erl_lint,typed_literal_string}, - {12,erl_lint,typed_literal_string}, - {14,erl_lint,typed_literal_string}, - {16,erl_lint,typed_literal_string}], - []} = run_test2(Config, Ts, []), + Ts = [{otp_6885, + <<"t(<<_/binary,I>>) -> I; + t(<>) -> I; + t(<>) -> {B,T}. + + build(A, B) -> + <>. + + foo(<<\"abc\"/binary>>) -> + ok; + foo(<<\"abc\":13/integer>>) -> + ok; + foo(<<\"abc\"/float>>) -> + ok; + foo(<<\"abc\":19>>) -> + ok; + foo(<<\"abc\"/utf8>>) -> + ok; + foo(<<\"abc\"/utf16>>) -> + ok; + foo(<<\"abc\"/utf32>>) -> + ok. + ">>, + [], + {errors,[{{1,14},erl_lint,unsized_binary_not_at_end}, + {{2,28},erl_lint,unsized_binary_not_at_end}, + {{3,28},erl_lint,unsized_binary_not_at_end}, + {{8,21},erl_lint,typed_literal_string}, + {{10,21},erl_lint,typed_literal_string}, + {{12,21},erl_lint,typed_literal_string}, + {{14,21},erl_lint,typed_literal_string}], + []}} + ], + ?line [] = run(Config, Ts), ok. export_all(doc) -> "OTP-7392. Warning for export_all."; export_all(Config) when is_list(Config) -> - Ts = <<"-module(export_all_module). - -compile([export_all]). + Ts = [{export_all, + <<"-module(export_all_module). + -compile([export_all]). - id(I) -> I. - ">>, - ?line [] = run_test2(Config, Ts, []), - ?line {warnings,[{2,erl_lint,export_all}]} = - run_test2(Config, Ts, [warn_export_all]), + id(I) -> I. + ">>, + {[warn_export_all]}, + {warnings,[{{2,16},erl_lint,export_all}]}} + ], + ?line [] = run(Config, Ts), ok. bif_clash(doc) -> @@ -2433,7 +2419,7 @@ bif_clash(Config) when is_list(Config) -> N. ">>, [], - {errors,[{2,erl_lint,{call_to_redefined_old_bif,{size,1}}}],[]}}, + {errors,[{{2,19},erl_lint,{call_to_redefined_old_bif,{size,1}}}],[]}}, %% Verify that warnings can not be turned off in the old way. {clash2, @@ -2471,7 +2457,7 @@ bif_clash(Config) when is_list(Config) -> size(X). ">>, [], - {errors,[{5,erl_lint,{call_to_redefined_old_bif,{size,1}}}],[]}}, + {errors,[{{5,17},erl_lint,{call_to_redefined_old_bif,{size,1}}}],[]}}, %% For a post R14 bif, its only a warning {clash5, <<"-export([binary_part/2]). @@ -2481,7 +2467,7 @@ bif_clash(Config) when is_list(Config) -> binary:part(B,X,Y). ">>, [], - {warnings,[{3,erl_lint,{call_to_redefined_bif,{binary_part,2}}}]}}, + {warnings,[{{3,17},erl_lint,{call_to_redefined_bif,{binary_part,2}}}]}}, %% If you really mean to call yourself here, you can "unimport" size/1 {clash6, <<"-export([size/1]). @@ -2518,7 +2504,7 @@ bif_clash(Config) when is_list(Config) -> binary:part(B,X,Y). ">>, [], - {errors,[{3,erl_lint,{illegal_guard_local_call,{binary_part,2}}}],[]}}, + {errors,[{{3,25},erl_lint,{illegal_guard_local_call,{binary_part,2}}}],[]}}, %% no_auto_import is not like nowarn_bif_clash, it actually removes the autoimport {clash9, <<"-export([x/1]). @@ -2527,7 +2513,7 @@ bif_clash(Config) when is_list(Config) -> binary_part(X,{1,2}) =:= <<1,2>>. ">>, [], - {errors,[{4,erl_lint,{undefined_function,{binary_part,2}}}],[]}}, + {errors,[{{4,18},erl_lint,{undefined_function,{binary_part,2}}}],[]}}, %% but we could import it again... {clash10, <<"-export([x/1]). @@ -2558,7 +2544,7 @@ bif_clash(Config) when is_list(Config) -> binary_part(X,{1,2}) =:= fun binary_part/2. ">>, [], - {errors,[{5,erl_lint,{undefined_function,{binary_part,2}}}],[]}}, + {errors,[{{5,43},erl_lint,{undefined_function,{binary_part,2}}}],[]}}, %% Not from erlang and not from anywhere else {clash13, <<"-export([x/1]). @@ -2568,7 +2554,7 @@ bif_clash(Config) when is_list(Config) -> binary_part(X,{1,2}) =:= fun binary_part/2. ">>, [], - {errors,[{5,erl_lint,{undefined_function,{binary_part,2}}}],[]}}, + {errors,[{{5,43},erl_lint,{undefined_function,{binary_part,2}}}],[]}}, %% ...while real auto-import is OK. {clash14, <<"-export([x/1]). @@ -2585,7 +2571,7 @@ bif_clash(Config) when is_list(Config) -> binary_part(X,{1,2}). ">>, [], - {errors,[{2,erl_lint,{redefine_old_bif_import,{abs,1}}}],[]}}, + {errors,[{{2,16},erl_lint,{redefine_old_bif_import,{abs,1}}}],[]}}, %% For a new BIF, it's only a warning {clash16, <<"-export([x/1]). @@ -2594,7 +2580,7 @@ bif_clash(Config) when is_list(Config) -> abs(X). ">>, [], - {warnings,[{2,erl_lint,{redefine_bif_import,{binary_part,3}}}]}}, + {warnings,[{{2,16},erl_lint,{redefine_bif_import,{binary_part,3}}}]}}, %% And, you cannot redefine already imported things that aren't auto-imported {clash17, <<"-export([x/1]). @@ -2604,7 +2590,7 @@ bif_clash(Config) when is_list(Config) -> abs(X). ">>, [], - {errors,[{3,erl_lint,{redefine_import,{{binary_port,3},x}}}],[]}}, + {errors,[{{3,16},erl_lint,{redefine_import,{{binary_port,3},x}}}],[]}}, %% Not with local functions either {clash18, <<"-export([x/1]). @@ -2615,7 +2601,7 @@ bif_clash(Config) when is_list(Config) -> abs(X). ">>, [], - {errors,[{3,erl_lint,{define_import,{binary_port,3}}}],[]}}, + {errors,[{{3,15},erl_lint,{define_import,{binary_port,3}}}],[]}}, %% Like clash8: Dont accept a guard if it's explicitly module-name called either {clash19, <<"-export([binary_port/3]). @@ -2625,7 +2611,7 @@ bif_clash(Config) when is_list(Config) -> binary_part(A,B,C+1). ">>, [], - {errors,[{4,erl_lint,illegal_guard_expr}],[]}}, + {errors,[{{4,40},erl_lint,illegal_guard_expr}],[]}}, %% Not with local functions either {clash20, <<"-export([binary_port/3]). @@ -2634,7 +2620,7 @@ bif_clash(Config) when is_list(Config) -> binary_part(A,B,C). ">>, [warn_unused_import], - {warnings,[{2,erl_lint,{redefine_bif_import,{binary_part,3}}}]}}, + {warnings,[{{2,16},erl_lint,{redefine_bif_import,{binary_part,3}}}]}}, %% Don't accept call to a guard BIF if there is a local definition %% or an import with the same name. Note: is_record/2 is an %% exception, since it is more of syntatic sugar than a real BIF. @@ -2657,12 +2643,13 @@ bif_clash(Config) when is_list(Config) -> ok. ">>, [{no_auto_import,[{is_tuple,1}]}], - {errors,[{4,erl_lint,{illegal_guard_local_call,{is_tuple,1}}}, - {5,erl_lint,{illegal_guard_local_call,{is_list,1}}}, - {6,erl_lint,{illegal_guard_local_call,{is_tuple,1}}}, - {7,erl_lint,{illegal_guard_local_call,{is_list,1}}}, - {8,erl_lint,{illegal_guard_local_call,{is_record,3}}}, - {9,erl_lint,{illegal_guard_local_call,{is_record,3}}}],[]}} + {errors,[{{4,25},erl_lint,{illegal_guard_local_call,{is_tuple,1}}}, + {{5,25},erl_lint,{illegal_guard_local_call,{is_list,1}}}, + {{6,25},erl_lint,{illegal_guard_local_call,{is_tuple,1}}}, + {{7,25},erl_lint,{illegal_guard_local_call,{is_list,1}}}, + {{8,25},erl_lint,{illegal_guard_local_call,{is_record,3}}}, + {{9,25},erl_lint,{illegal_guard_local_call,{is_record,3}}}], + []}} ], ?line [] = run(Config, Ts), @@ -2676,8 +2663,10 @@ behaviour_basic(Config) when is_list(Config) -> <<"-behaviour(application). ">>, [], - {warnings,[{1,erl_lint,{undefined_behaviour_func,{start,2},application}}, - {1,erl_lint,{undefined_behaviour_func,{stop,1},application}}]}}, + {warnings,[{{1,2},erl_lint,{undefined_behaviour_func,{start,2}, + application}}, + {{1,2},erl_lint,{undefined_behaviour_func,{stop,1}, + application}}]}}, {behaviour2, <<"-behaviour(application). @@ -2685,7 +2674,8 @@ behaviour_basic(Config) when is_list(Config) -> stop(_) -> ok. ">>, [], - {warnings,[{1,erl_lint,{undefined_behaviour_func,{start,2},application}}]}}, + {warnings,[{{1,2},erl_lint,{undefined_behaviour_func,{start,2}, + application}}]}}, {behaviour3, <<"-behavior(application). %% Test American spelling. @@ -2708,9 +2698,11 @@ behaviour_multiple(Config) when is_list(Config) -> -behaviour(supervisor). ">>, [], - {warnings,[{1,erl_lint,{undefined_behaviour_func,{start,2},application}}, - {1,erl_lint,{undefined_behaviour_func,{stop,1},application}}, - {2,erl_lint,{undefined_behaviour_func,{init,1},supervisor}}]}}, + {warnings,[{{1,2},erl_lint,{undefined_behaviour_func,{start,2}, + application}}, + {{1,2},erl_lint,{undefined_behaviour_func,{stop,1},application}}, + {{2,16},erl_lint,{undefined_behaviour_func,{init,1}, + supervisor}}]}}, {behaviour2, <<"-behaviour(application). @@ -2743,14 +2735,17 @@ behaviour_multiple(Config) when is_list(Config) -> handle_info(_, _) -> ok. ">>, [], - {warnings,[{1,erl_lint, + {warnings,[{{1,2},erl_lint, {undefined_behaviour_func,{code_change,3},gen_server}}, - {1,erl_lint,{undefined_behaviour_func,{init,1},gen_server}}, - {1,erl_lint,{undefined_behaviour_func,{terminate,2},gen_server}}, - {2,erl_lint,{undefined_behaviour_func,{init,1},supervisor}}, - {2, + {{1,2},erl_lint, + {undefined_behaviour_func,{init,1},gen_server}}, + {{1,2},erl_lint, + {undefined_behaviour_func,{terminate,2},gen_server}}, + {{2,16},erl_lint, + {undefined_behaviour_func,{init,1},supervisor}}, + {{2,16}, erl_lint, - {conflicting_behaviours,{init,1},supervisor,1,gen_server}}]}}, + {conflicting_behaviours,{init,1},supervisor,{1,2},gen_server}}]}}, {american_behavior3, <<"-behavior(gen_server). -behavior(supervisor). @@ -2760,14 +2755,17 @@ behaviour_multiple(Config) when is_list(Config) -> handle_info(_, _) -> ok. ">>, [], - {warnings,[{1,erl_lint, + {warnings,[{{1,2},erl_lint, {undefined_behaviour_func,{code_change,3},gen_server}}, - {1,erl_lint,{undefined_behaviour_func,{init,1},gen_server}}, - {1,erl_lint,{undefined_behaviour_func,{terminate,2},gen_server}}, - {2,erl_lint,{undefined_behaviour_func,{init,1},supervisor}}, - {2, + {{1,2},erl_lint, + {undefined_behaviour_func,{init,1},gen_server}}, + {{1,2},erl_lint, + {undefined_behaviour_func,{terminate,2},gen_server}}, + {{2,16},erl_lint, + {undefined_behaviour_func,{init,1},supervisor}}, + {{2,16}, erl_lint, - {conflicting_behaviours,{init,1},supervisor,1,gen_server}}]}}, + {conflicting_behaviours,{init,1},supervisor,{1,2},gen_server}}]}}, {behaviour4, <<"-behaviour(gen_server). @@ -2792,12 +2790,12 @@ behaviour_multiple(Config) when is_list(Config) -> terminate(_, _, _, _) -> ok. ">>, [], - {warnings,[{2, + {warnings,[{{2,16}, erl_lint, - {conflicting_behaviours,{init,1},gen_fsm,1,gen_server}}, - {3, + {conflicting_behaviours,{init,1},gen_fsm,{1,2},gen_server}}, + {{3,16}, erl_lint, - {conflicting_behaviours,{init,1},supervisor,1,gen_server}}]}} + {conflicting_behaviours,{init,1},supervisor,{1,2},gen_server}}]}} ], ?line [] = run(Config, Ts), ok. @@ -2828,15 +2826,15 @@ otp_7550(Config) when is_list(Config) -> <>. ">>, [], - {errors,[{2,erl_lint,utf_bittype_size_or_unit}, - {4,erl_lint,utf_bittype_size_or_unit}, - {6,erl_lint,utf_bittype_size_or_unit}, - {9,erl_lint,utf_bittype_size_or_unit}, - {11,erl_lint,utf_bittype_size_or_unit}, - {13,erl_lint,utf_bittype_size_or_unit}, - {16,erl_lint,utf_bittype_size_or_unit}, - {18,erl_lint,utf_bittype_size_or_unit}, - {20,erl_lint,utf_bittype_size_or_unit} + {errors,[{{2,21},erl_lint,utf_bittype_size_or_unit}, + {{4,21},erl_lint,utf_bittype_size_or_unit}, + {{6,21},erl_lint,utf_bittype_size_or_unit}, + {{9,21},erl_lint,utf_bittype_size_or_unit}, + {{11,21},erl_lint,utf_bittype_size_or_unit}, + {{13,21},erl_lint,utf_bittype_size_or_unit}, + {{16,21},erl_lint,utf_bittype_size_or_unit}, + {{18,21},erl_lint,utf_bittype_size_or_unit}, + {{20,21},erl_lint,utf_bittype_size_or_unit} ], []}}], ?line [] = run(Config, Ts), @@ -2850,8 +2848,8 @@ otp_8051(Config) when is_list(Config) -> <<"-opaque foo() :: bar(). ">>, [], - {error,[{1,erl_lint,{undefined_type,{bar,0}}}], - [{1,erl_lint,{unused_type,{foo,0}}}]}}], + {error,[{{1,18},erl_lint,{undefined_type,{bar,0}}}], + [{{1,2},erl_lint,{unused_type,{foo,0}}}]}}], ?line [] = run(Config, Ts), ok. @@ -2924,7 +2922,7 @@ on_load_failing(Config) when is_list(Config) -> ">>, {[]}, %Tuple indicates no 'export_all'. {errors, - [{1,erl_lint,{bad_on_load,atom}}],[]}}, + [{{1,2},erl_lint,{bad_on_load,atom}}],[]}}, {on_load_2, %% Badly formed. @@ -2932,7 +2930,7 @@ on_load_failing(Config) when is_list(Config) -> ">>, {[]}, %Tuple indicates no 'export_all'. {errors, - [{1,erl_lint,{bad_on_load,{42,0}}}],[]}}, + [{{1,2},erl_lint,{bad_on_load,{42,0}}}],[]}}, {on_load_3, %% Multiple on_load attributes. @@ -2943,7 +2941,7 @@ on_load_failing(Config) when is_list(Config) -> ">>, {[]}, %Tuple indicates no 'export_all'. {errors, - [{2,erl_lint,multiple_on_loads}],[]}}, + [{{2,16},erl_lint,multiple_on_loads}],[]}}, {on_load_4, %% Wrong arity. @@ -2952,7 +2950,7 @@ on_load_failing(Config) when is_list(Config) -> ">>, {[]}, %Tuple indicates no 'export_all'. {errors, - [{1,erl_lint,{bad_on_load_arity,{foo,1}}}],[]}}, + [{{1,2},erl_lint,{bad_on_load_arity,{foo,1}}}],[]}}, {on_load_5, %% Non-existing function. @@ -2960,7 +2958,7 @@ on_load_failing(Config) when is_list(Config) -> ">>, {[]}, %Tuple indicates no 'export_all'. {errors, - [{1,erl_lint,{undefined_on_load,{non_existing,0}}}],[]}} + [{{1,2},erl_lint,{undefined_on_load,{non_existing,0}}}],[]}} ], ?line [] = run(Config, Ts), ok. @@ -2973,7 +2971,7 @@ too_many_arguments(Config) when is_list(Config) -> <<"f(_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_) -> ok.">>, [], {errors, - [{1,erl_lint,{too_many_arguments,256}}],[]}} + [{{1,1},erl_lint,{too_many_arguments,256}}],[]}} ], ?line [] = run(Config, Ts), @@ -2981,18 +2979,71 @@ too_many_arguments(Config) when is_list(Config) -> run(Config, Tests) -> - F = fun({N,P,Ws,E}, BadL) -> - case catch run_test(Config, P, Ws) of + F = fun({N,P,Ws,E0}, BadL) -> + E = strip_columns(E0), + BadL1 = case catch run_test(Config, P, Ws) of E -> BadL; Bad -> ?t:format("~nTest ~p failed. Expected~n ~p~n" "but got~n ~p~n", [N, E, Bad]), fail() + end, + ESorted = sort_warnings(E0), + case catch run_test(Config, P, add_column_opt(Ws)) of + ESorted -> + BadL1; + Bad2 -> + ?t:format("~nTest ~p failed with columns. " + "Expected~n ~p~n" + "but got~n ~p~n", [N, ESorted, Bad2]), + fail() end end, lists:foldl(F, [], Tests). +strip_columns({warnings, Ws}) -> + {warnings, strip_columns_2(Ws)}; +strip_columns({errors, Es, []}) -> + {errors, strip_columns_2(Es), []}; +strip_columns({error, Es, Ws}) -> + {error, strip_columns_2(Es), strip_columns_2(Ws)}; +strip_columns({errors2, Es1, Es2}) -> + {errors2, strip_columns_2(Es1), strip_columns_2(Es2)}; +strip_columns([]) -> + []. + +strip_columns_2(Ws) -> + lists:map(fun ({{Line,_Col},erl_lint,{unsafe_var,Var,{Tag,{L2,_C2}}}}) -> + {Line, erl_lint,{unsafe_var,Var,{Tag,L2}}}; + ({{Line,_Col},erl_lint,{exported_var,Var,{Tag,{L2,_C2}}}}) -> + {Line,erl_lint,{exported_var,Var,{Tag,L2}}}; + ({{Line,_Col},erl_lint, + {conflicting_behaviours,F,M1,{L2,_C2},M2}}) -> + {Line,erl_lint,{conflicting_behaviours,F,M1,L2,M2}}; + ({{Line,_Col},Mod,Info}) -> + {Line,Mod,Info}; + (W) -> + W + end, + Ws). + +add_column_opt({Opts}) -> + {[column|Opts]}; +add_column_opt(Opts) -> + [column|Opts]. + +sort_warnings({warnings, Ws}) -> + {warnings, lists:keysort(1, Ws)}; +sort_warnings({errors, Es, []}) -> + {errors, lists:keysort(1, Es), []}; +sort_warnings({error, Es, Ws}) -> + {error, lists:keysort(1, Es), lists:keysort(1, Ws)}; +sort_warnings({errors2, Es1, Es2}) -> + {errors2, lists:keysort(1, Es1), lists:keysort(1, Es2)}; +sort_warnings([]) -> + []. + %% Compiles a test file and returns the list of warnings. get_compilation_warnings(Conf, Filename, Warnings) -> @@ -3007,8 +3058,11 @@ get_compilation_warnings(Conf, Filename, Warnings) -> %% Compiles a test module and returns the list of errors and warnings. +run_test(Conf, Test = <<"-module", _/binary>>, Warnings0) -> + run_test2(Conf, Test, Warnings0); run_test(Conf, Test0, Warnings0) -> - Test = list_to_binary(["-module(lint_test). ", Test0]), + Test = list_to_binary(["-module(lint_test). -file(?FILE, 0).\n", + Test0]), run_test2(Conf, Test, Warnings0). run_test2(Conf, Test, Warnings0) -> From ee971e66408ad54f15ae6ce4fb2a881f9f39c98a Mon Sep 17 00:00:00 2001 From: Anthony Ramine Date: Sat, 25 Aug 2012 21:40:14 +0200 Subject: [PATCH 12/14] Handle column numbers in QLC test suite --- lib/stdlib/test/qlc_SUITE.erl | 77 ++++++++++++++++------------------- 1 file changed, 35 insertions(+), 42 deletions(-) diff --git a/lib/stdlib/test/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl index 192268f90e00..60d8b0560cf9 100644 --- a/lib/stdlib/test/qlc_SUITE.erl +++ b/lib/stdlib/test/qlc_SUITE.erl @@ -173,10 +173,10 @@ badarg(Config) when is_list(Config) -> q(bar, cache_all, extra). ">>, [], - {errors,[{5,?QLC,not_a_query_list_comprehension}, - {6,?QLC,not_a_query_list_comprehension}, - {8,?QLC,not_a_query_list_comprehension}, - {9,?QLC,not_a_query_list_comprehension}], + {errors,[{{5,18},?QLC,not_a_query_list_comprehension}, + {{6,18},?QLC,not_a_query_list_comprehension}, + {{8,15},?QLC,not_a_query_list_comprehension}, + {{9,15},?QLC,not_a_query_list_comprehension}], []}}], ?line [] = compile(Config, Ts), ok. @@ -441,7 +441,7 @@ nomatch(Config) when is_list(Config) -> end, [{\"ab\"}]). ">>, [], - {warnings,[{3,v3_core,nomatch}]}} + {warnings,[{{3,38},v3_core,nomatch}]}} ], ?line [] = compile(Config, Ts), @@ -3211,8 +3211,8 @@ lookup2(Config) when is_list(Config) -> false = lookup_keys(Q) end, [{1,b},{2,3}])">>, {warnings,[{2,sys_core_fold,nomatch_guard}, - {3,qlc,nomatch_filter}, - {3,sys_core_fold,{eval_failure,badarg}}]}}, + {3,sys_core_fold,{eval_failure,badarg}}, + {{3,48},qlc,nomatch_filter}]}}, <<"etsc(fun(E) -> Q = qlc:q([X || {X} <- ets:table(E), element(1,{X}) =:= 1]), @@ -5705,7 +5705,7 @@ join_complex(Config) when is_list(Config) -> ]), qlc:e(Q).">>, [], - {warnings,[{3,qlc,too_complex_join}]}}, + {warnings,[{{3,26},qlc,too_complex_join}]}}, {two, <<"two() -> @@ -5718,7 +5718,7 @@ join_complex(Config) when is_list(Config) -> Z =:= W],{join,merge}), qlc:e(Q).">>, [], - {warnings,[{2,qlc,too_many_joins}]}} + {warnings,[{{2,26},qlc,too_many_joins}]}} ], ?line compile(Config, Ts), @@ -5960,7 +5960,7 @@ otp_6562(Config) when is_list(Config) -> qlc:info(Q). ">>, [], - {errors,[{2,qlc,binary_generator}], + {errors,[{{2,40},qlc,binary_generator}], []}} ], ?line [] = compile(Config, Bits), @@ -8007,7 +8007,7 @@ compile_file(Config, Test0, Opts0) -> Test0]), Opts = [export_all,return,nowarn_unused_record,{outdir,?privdir}|Opts0], ok = file:write_file(File, Test), - case compile:file(File, Opts) of + case compile:file(File, [column|Opts]) of {ok, _M, Ws} -> warnings(File, Ws); {error, [{File,Es}], []} -> {errors, Es, []}; {error, [{File,Es}], [{File,Ws}]} -> {error, Es, Ws} @@ -8017,9 +8017,7 @@ comp_compare(T, T) -> true; comp_compare(T1, T2_0) -> T2 = wskip(T2_0), - T1 =:= T2 - %% This clause should eventually be removed. - orelse ln(T1) =:= T2 orelse T1 =:= ln(T2). + T1 =:= T2. wskip([]) -> []; @@ -8034,34 +8032,29 @@ wskip([M|L]) -> wskip(T) -> T. -%% Replaces locations like {Line,Column} with Line. -ln({warnings,L}) -> - {warnings,ln0(L)}; -ln({errors,EL,WL}) -> - {errors,ln0(EL),ln0(WL)}; -ln(L) -> - ln0(L). - -ln0(L) -> - lists:sort(ln1(L)). - -ln1([]) -> - []; -ln1([{File,Ms}|MsL]) when is_list(File) -> - [{File,ln0(Ms)}|ln1(MsL)]; -ln1([{{L,_C},Mod,Mess0}|Ms]) -> - Mess = case Mess0 of - {exported_var,V,{Where,{L1,_C1}}} -> - {exported_var,V,{Where,L1}}; - {unsafe_var,V,{Where,{L1,_C1}}} -> - {unsafe_var,V,{Where,L1}}; - %% There are more... - M -> - M - end, - [{L,Mod,Mess}|ln1(Ms)]; -ln1([M|Ms]) -> - [M|ln1(Ms)]. +% sort_warnings({warnings, Ws}) -> +% {warnings, sort_columns(Ws)}; +% sort_warnings({errors, Es, []}) -> +% {errors, sort_columns(Es), []}; +% sort_warnings({error, Es, Ws}) -> +% {error, sort_columns(Es), sort_columns(Ws)}; +% sort_warnings({errors2, Es1, Es2}) -> +% {errors2, sort_columns(Es1), sort_columns(Es2)}; +% sort_warnings([]) -> +% []. + +% sort_columns(Ws) -> +% lists:sort(fun ({{_,_}=L1,_,_},{{_,_}=L2,_,_}) when L1 > L2 -> +% false; +% ({{L1,_},_,_},{L2,_,_}) when L1 >= L2 -> +% false; +% ({L1,_,_},{{L2,_},_,_}) when L1 > L2 -> +% false; +% ({L1,_,_},{L2,_,_}) when L1 > L2 -> +% false; +% (_,_) -> +% true +% end, Ws). %% -> {FileName, Module}; {string(), atom()} compile_file_mod(Config) -> From e4120f4517a596f284d32ce0d20c9baa7d9596e3 Mon Sep 17 00:00:00 2001 From: Anthony Ramine Date: Sun, 26 Aug 2012 14:01:55 +0200 Subject: [PATCH 13/14] Handle column numbers in ms_transform test suite --- lib/stdlib/test/ms_transform_SUITE.erl | 123 ++++++++++++------------- 1 file changed, 61 insertions(+), 62 deletions(-) diff --git a/lib/stdlib/test/ms_transform_SUITE.erl b/lib/stdlib/test/ms_transform_SUITE.erl index a17307b07be6..2d0a32722b5e 100644 --- a/lib/stdlib/test/ms_transform_SUITE.erl +++ b/lib/stdlib/test/ms_transform_SUITE.erl @@ -83,76 +83,74 @@ warnings(doc) -> ["Check that shadowed variables in fun head generate warning"]; warnings(Config) when is_list(Config) -> ?line setup(Config), - Prog = <<"A=5, " - "ets:fun2ms(fun({A,B}) " - " when is_integer(A) and (A+5 > B) -> " - " A andalso B " - " end)">>, - ?line [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'A'}}]}] = + Prog = <<"A=5, + ets:fun2ms(fun ({A,B}) when is_integer(A) and (A+5 > B) -> + A andalso B + end)">>, + ?line [{_,[{{2,32},ms_transform,{?WARN_NUMBER_SHADOW,'A'}}]}] = compile_ww(Prog), - Prog2 = <<"C=5, " - "ets:fun2ms(fun({A,B} = C) " - " when is_integer(A) and (A+5 > B) -> " - " {A andalso B,C} " - " end)">>, - ?line [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'C'}}]}] = + Prog2 = <<"C=5, + ets:fun2ms(fun ({A,B} = C) when is_integer(A) and (A+5 > B) -> + {A andalso B,C} + end)">>, + ?line [{_,[{{2,40},ms_transform,{?WARN_NUMBER_SHADOW,'C'}}]}] = compile_ww(Prog2), Rec3 = <<"-record(a,{a,b,c,d=foppa}).">>, - Prog3 = <<"A=3,C=5, " - "ets:fun2ms(fun(#a{a = A, b = B} = C) " - " when is_integer(A) and (A+5 > B) -> " - " {A andalso B,C} " - " end)">>, - ?line [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'A'}}, - {_,ms_transform,{?WARN_NUMBER_SHADOW,'C'}}]}] = + Prog3 = <<"A=3,C=5, + ets:fun2ms(fun (#a{a = A, b = B} = C) + when is_integer(A) and (A+5 > B) -> + {A andalso B,C} + end)">>, + ?line [{_,[{{2,39},ms_transform,{?WARN_NUMBER_SHADOW,'A'}}, + {{2,51},ms_transform,{?WARN_NUMBER_SHADOW,'C'}}]}] = compile_ww(Rec3,Prog3), Rec4 = <<"-record(a,{a,b,c,d=foppa}).">>, - Prog4 = <<"A=3,C=5, " - "F = fun(B) -> B*3 end," - "erlang:display(F(A))," - "ets:fun2ms(fun(#a{a = A, b = B} = C) " - " when is_integer(A) and (A+5 > B) -> " - " {A andalso B,C} " - " end)">>, - ?line [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'A'}}, - {_,ms_transform,{?WARN_NUMBER_SHADOW,'C'}}]}] = + Prog4 = <<"A=3,C=5, + F = fun(B) -> B*3 end, + erlang:display(F(A)), + ets:fun2ms(fun (#a{a = A, b = B} = C) + when is_integer(A) and (A+5 > B) -> + {A andalso B,C} + end)">>, + ?line [{_,[{{4,39},ms_transform,{?WARN_NUMBER_SHADOW,'A'}}, + {{4,51},ms_transform,{?WARN_NUMBER_SHADOW,'C'}}]}] = compile_ww(Rec4,Prog4), Rec5 = <<"-record(a,{a,b,c,d=foppa}).">>, - Prog5 = <<"A=3,C=5, " - "F = fun(B) -> B*3 end," - "erlang:display(F(A))," - "B = ets:fun2ms(fun(#a{a = A, b = B} = C) " - " when is_integer(A) and (A+5 > B) -> " - " {A andalso B,C} " - " end)">>, - ?line [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'A'}}, - {_,ms_transform,{?WARN_NUMBER_SHADOW,'C'}}]}] = + Prog5 = <<"A=3,C=5, + F = fun(B) -> B*3 end, + erlang:display(F(A)), + B = ets:fun2ms(fun (#a{a = A, b = B} = C) + when is_integer(A) and (A+5 > B) -> + {A andalso B,C} + end)">>, + ?line [{_,[{{4,43},ms_transform,{?WARN_NUMBER_SHADOW,'A'}}, + {{4,55},ms_transform,{?WARN_NUMBER_SHADOW,'C'}}]}] = compile_ww(Rec5,Prog5), - Prog6 = <<" X=bar, " - " A = case X of" - " foo ->" - " foo;" - " Y ->" - " ets:fun2ms(fun(Y) ->" % This is a warning - " 3*Y" - " end)" - " end," - " ets:fun2ms(fun(Y) ->" % Y out of "scope" here, so no warning - " {3*Y,A}" - " end)">>, - ?line [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'Y'}}]}] = + Prog6 = <<"X=bar, + A = case X of + foo -> + foo; + Y -> + ets:fun2ms(fun (Y) -> % This is a warning + 3*Y + end) + end, + ets:fun2ms(fun (Y) -> % Y out of 'scope' here, so no warning + {3*Y,A} + end)">>, + ?line [{_,[{{6,44},ms_transform,{?WARN_NUMBER_SHADOW,'Y'}}]}] = compile_ww(Prog6), - Prog7 = <<" X=bar, " - " A = case X of" - " foo ->" - " Y = foo;" - " Y ->" - " bar" - " end," - " ets:fun2ms(fun(Y) ->" % Y exported from case and safe, so warn - " {3*Y,A}" - " end)">>, - ?line [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'Y'}}]}] = + Prog7 = <<"X=bar, + A = case X of + foo -> + Y = foo; + Y -> + bar + end, + ets:fun2ms(fun (Y) -> % Y exported from case and safe, so warn + {3*Y,A} + end)">>, + ?line [{_,[{{8,32},ms_transform,{?WARN_NUMBER_SHADOW,'Y'}}]}] = compile_ww(Prog7), ok. @@ -858,11 +856,12 @@ compile_ww(Records,Expr) -> "-include_lib(\"stdlib/include/ms_transform.hrl\").\n", "-export([tmp/0]).\n", Records/binary,"\n", + "-file(?FILE, 0). " "tmp() ->\n", Expr/binary,".\n">>, FN=temp_name(), file:write_file(FN,Prog), - {ok,Forms} = epp:parse_file(FN,"",""), + {ok,Forms} = epp:parse_file(FN,{1,1},"",""), {ok,tmp,_Bin,Wlist} = compile:forms(Forms,[return_warnings, nowarn_unused_vars, nowarn_unused_record]), From e869e223f1349c3cdb9f1fef2ef2f9ebfa083faf Mon Sep 17 00:00:00 2001 From: Anthony Ramine Date: Sat, 1 Sep 2012 13:35:36 +0200 Subject: [PATCH 14/14] Document locations with column numbers in the AST doc --- erts/doc/src/absform.xml | 178 ++++++++++++++++++++------------------- 1 file changed, 90 insertions(+), 88 deletions(-) diff --git a/erts/doc/src/absform.xml b/erts/doc/src/absform.xml index 4455d0ac92f9..925ff8794e5d 100644 --- a/erts/doc/src/absform.xml +++ b/erts/doc/src/absform.xml @@ -49,10 +49,12 @@ construct to its abstract format representation , and write .

-

The word below represents an integer, and denotes the - number of the line in the source file where the construction occurred. - Several instances of in the same construction may denote - different lines.

+

The word below represents a location, and + denotes where the construction occured in the source file, it may be the + bare number of the line as an integer or the number of the line and of the + column as a pair of two integers. + Several instances of in the same construction + may denote different locations.

Since operators are not terms in their own right, when operators are mentioned below, the representation of an operator should be taken to be the atom with a printname consisting of the same characters as the @@ -68,25 +70,25 @@ , ..., , then Rep(D) = . If F is an attribute , then - Rep(F) = . + Rep(F) = . If F is an attribute , then - Rep(F) = . + Rep(F) = . If F is an attribute , then - Rep(F) = . + Rep(F) = . If F is an attribute , then - Rep(F) = . + Rep(F) = . If F is an attribute , then - Rep(F) = . + Rep(F) = . If F is a record declaration , then Rep(F) = - . For Rep(V), see below. + . For Rep(V), see below. If F is a wild attribute , then - Rep(F) = . + Rep(F) = .

If F is a function declaration , where each is a function clause with a pattern sequence of the same length , then - Rep(F) = . + Rep(F) = .

@@ -95,9 +97,9 @@ explicit default initializer expression

If V is , then - Rep(V) = . + Rep(V) = . If V is , then - Rep(V) = . + Rep(V) = .
@@ -106,7 +108,7 @@

In addition to the representations of forms, the list that represents a module declaration (as returned by functions in and ) may contain tuples and , denoting - syntactically incorrect forms and warnings, and , denoting an end + syntactically incorrect forms and warnings, and , denoting an end of stream encountered before a complete form had been parsed.

@@ -117,14 +119,14 @@ same way in patterns, expressions and guards:

If L is an integer or character literal, then - Rep(L) = . + Rep(L) = . If L is a float literal, then - Rep(L) = . + Rep(L) = . If L is a string literal consisting of the characters , ..., , then - Rep(L) = . + Rep(L) = . If L is an atom literal, then - Rep(L) = . + Rep(L) = .

Note that negative integer and float literals do not occur as such; they are parsed as an application of the unary negation operator.

@@ -139,21 +141,21 @@ If P is an atomic literal L, then Rep(P) = Rep(L). If P is a compound pattern , then - Rep(P) = . + Rep(P) = . If P is a variable pattern , then - Rep(P) = , + Rep(P) = , where A is an atom with a printname consisting of the same characters as . If P is a universal pattern , then - Rep(P) = . + Rep(P) = . If P is a tuple pattern , then - Rep(P) = . + Rep(P) = . If P is a nil pattern , then - Rep(P) = . + Rep(P) = . If P is a cons pattern , then - Rep(P) = . + Rep(P) = . If E is a binary pattern >]]>, then - Rep(E) = . + Rep(E) = . For Rep(TSL), see below. An omitted is represented by . An omitted (type specifier list) is represented by . @@ -161,15 +163,15 @@ is either an occurrence of applied to a literal string or character list, or an occurrence of an expression that can be evaluated to a number at compile time), - then Rep(P) = . + then Rep(P) = . If P is , where is a unary operator (this is an occurrence of an expression that can be evaluated to a number at compile - time), then Rep(P) = . + time), then Rep(P) = . If P is a record pattern , then Rep(P) = - . + . If P is , then - Rep(P) = . + Rep(P) = . If P is , then Rep(P) = , i.e., patterns cannot be distinguished from their bodies. @@ -187,116 +189,116 @@ If P is an atomic literal , then Rep(P) = Rep(L). If E is , then - Rep(E) = . + Rep(E) = . If E is a variable , then - Rep(E) = , + Rep(E) = , where is an atom with a printname consisting of the same characters as . If E is a tuple skeleton , then - Rep(E) = . + Rep(E) = . If E is , then - Rep(E) = . + Rep(E) = . If E is a cons skeleton , then - Rep(E) = . + Rep(E) = . If E is a binary constructor >]]>, then - Rep(E) = . + Rep(E) = . For Rep(TSL), see below. An omitted is represented by . An omitted (type specifier list) is represented by . If E is , where is a binary operator, - then Rep(E) = . + then Rep(E) = . If E is , where is a unary operator, then - Rep(E) = . + Rep(E) = . If E is , then Rep(E) = - . + . If E is , then Rep(E) = - . + . If E is , then - Rep(E) = . + Rep(E) = . If E is , then - Rep(E) = . + Rep(E) = . If E is , then - Rep(E) = . + Rep(E) = . If E is , then - Rep(E) = . + Rep(E) = . If E is , then Rep(E) = - . + . If E is a list comprehension , where each is a generator or a filter, then - Rep(E) = . For Rep(W), see + Rep(E) = . For Rep(W), see below. If E is a binary comprehension >]]>, where each is a generator or a filter, then - Rep(E) = . For Rep(W), see + Rep(E) = . For Rep(W), see below. If E is , where is a body, then - Rep(E) = . + Rep(E) = . If E is , where each is an if clause then Rep(E) = - . + . If E is , where is an expression and each is a case clause then Rep(E) = - . + . If E is , where is a body and each is a catch clause then Rep(E) = - . + . If E is , where is a body, each is a case clause and each is a catch clause then Rep(E) = - . + . If E is , where and are bodies then Rep(E) = - . + . If E is , where and are a bodies and each is a case clause then Rep(E) = - . + . If E is , where and are bodies and each is a catch clause then Rep(E) = - . + . If E is , where and are a bodies, each is a case clause and each is a catch clause then Rep(E) = - . + . If E is , where each is a case clause then Rep(E) = - . + . If E is B_t end]]>, where each is a case clause, is an expression and is a body, then Rep(E) = - . + . If E is , then - Rep(E) = . + Rep(E) = . If E is , then - Rep(E) = . - (Before the R15 release: Rep(E) = .) + Rep(E) = . + (Before the R15 release: Rep(E) = .) If E is where each is a function clause then Rep(E) = - . + . If E is , where each is a generator or a filter, then - Rep(E) = . + Rep(E) = . For Rep(W), see below. If E is , a Mnesia record access inside a query, then - Rep(E) = . + Rep(E) = . If E is , then Rep(E) = , i.e., parenthesized expressions cannot be distinguished from their bodies. @@ -308,10 +310,10 @@ If W is a generator , where is a pattern and is an expression, then - Rep(W) = . + Rep(W) = . If W is a generator , where is a pattern and is an expression, then - Rep(W) = . + Rep(W) = . If W is a filter , which is an expression, then Rep(W) = . @@ -339,37 +341,37 @@ If C is a function clause B]]> where is a pattern sequence and is a body, then - Rep(C) = . + Rep(C) = . If C is a function clause B]]> where is a pattern sequence, is a guard sequence and is a body, then - Rep(C) = . + Rep(C) = . If C is an if clause B]]> where is a guard sequence and is a body, then - Rep(C) = . + Rep(C) = . If C is a case clause B]]> where is a pattern and is a body, then - Rep(C) = . + Rep(C) = . If C is a case clause B]]> where is a pattern, is a guard sequence and is a body, then - Rep(C) = . + Rep(C) = . If C is a catch clause B]]> where is a pattern and is a body, then - Rep(C) = . + Rep(C) = . If C is a catch clause B]]> where is an atomic literal or a variable pattern, is a pattern and is a body, then - Rep(C) = . + Rep(C) = . If C is a catch clause B]]> where is a pattern, is a guard sequence and is a body, then - Rep(C) = . + Rep(C) = . If C is a catch clause B]]> where is an atomic literal or a variable pattern, is a pattern, is a guard sequence and is a body, then - Rep(C) = . + Rep(C) = .
@@ -384,39 +386,39 @@ If Gt is an atomic literal L, then Rep(Gt) = Rep(L). If Gt is a variable pattern , then - Rep(Gt) = , + Rep(Gt) = , where A is an atom with a printname consisting of the same characters as . If Gt is a tuple skeleton , then - Rep(Gt) = . + Rep(Gt) = . If Gt is , then - Rep(Gt) = . + Rep(Gt) = . If Gt is a cons skeleton , then - Rep(Gt) = . + Rep(Gt) = . If Gt is a binary constructor >]]>, then - Rep(Gt) = . + Rep(Gt) = . For Rep(TSL), see above. An omitted is represented by . An omitted (type specifier list) is represented by . If Gt is , where - is a binary operator, then Rep(Gt) = . + is a binary operator, then Rep(Gt) = . If Gt is , where is a unary operator, then - Rep(Gt) = . + Rep(Gt) = . If Gt is , then Rep(E) = - . + . If Gt is , then - Rep(Gt) = . + Rep(Gt) = . If Gt is , then - Rep(Gt) = . + Rep(Gt) = . If Gt is , where is an atom, then - Rep(Gt) = . + Rep(Gt) = . If Gt is , where is the atom and is an atom or an operator, then - Rep(Gt) = . + Rep(Gt) = . If Gt is , where is the atom and is an atom or an operator, then - Rep(Gt) = . + Rep(Gt) = . If Gt is , then Rep(Gt) = , i.e., parenthesized guard tests cannot be distinguished from their bodies.