diff options
Diffstat (limited to 'lib/stdlib/src')
| -rw-r--r-- | lib/stdlib/src/Makefile | 4 | ||||
| -rw-r--r-- | lib/stdlib/src/beam_lib.erl | 27 | ||||
| -rw-r--r-- | lib/stdlib/src/edlin.erl | 16 | ||||
| -rw-r--r-- | lib/stdlib/src/epp.erl | 171 | ||||
| -rw-r--r-- | lib/stdlib/src/erl_anno.erl | 460 | ||||
| -rw-r--r-- | lib/stdlib/src/erl_eval.erl | 55 | ||||
| -rw-r--r-- | lib/stdlib/src/erl_expand_records.erl | 65 | ||||
| -rw-r--r-- | lib/stdlib/src/erl_lint.erl | 141 | ||||
| -rw-r--r-- | lib/stdlib/src/erl_parse.yrl | 738 | ||||
| -rw-r--r-- | lib/stdlib/src/erl_pp.erl | 59 | ||||
| -rw-r--r-- | lib/stdlib/src/erl_scan.erl | 227 | ||||
| -rw-r--r-- | lib/stdlib/src/escript.erl | 28 | ||||
| -rw-r--r-- | lib/stdlib/src/gb_sets.erl | 12 | ||||
| -rw-r--r-- | lib/stdlib/src/io.erl | 4 | ||||
| -rw-r--r-- | lib/stdlib/src/ms_transform.erl | 5 | ||||
| -rw-r--r-- | lib/stdlib/src/orddict.erl | 20 | ||||
| -rw-r--r-- | lib/stdlib/src/otp_internal.erl | 68 | ||||
| -rw-r--r-- | lib/stdlib/src/qlc.erl | 96 | ||||
| -rw-r--r-- | lib/stdlib/src/qlc_pt.erl | 662 | ||||
| -rw-r--r-- | lib/stdlib/src/shell.erl | 35 | ||||
| -rw-r--r-- | lib/stdlib/src/slave.erl | 22 | ||||
| -rw-r--r-- | lib/stdlib/src/stdlib.app.src | 3 | ||||
| -rw-r--r-- | lib/stdlib/src/supervisor.erl | 9 | ||||
| -rw-r--r-- | lib/stdlib/src/timer.erl | 21 | ||||
| -rw-r--r-- | lib/stdlib/src/zip.erl | 2 | 
25 files changed, 1973 insertions, 977 deletions
| diff --git a/lib/stdlib/src/Makefile b/lib/stdlib/src/Makefile index c983f0ed87..55bda60da5 100644 --- a/lib/stdlib/src/Makefile +++ b/lib/stdlib/src/Makefile @@ -1,7 +1,7 @@  #  # %CopyrightBegin%  # -# Copyright Ericsson AB 1996-2013. All Rights Reserved. +# Copyright Ericsson AB 1996-2015. All Rights Reserved.  #  # The contents of this file are subject to the Erlang Public License,  # Version 1.1, (the "License"); you may not use this file except in @@ -58,6 +58,7 @@ MODULES= \  	edlin \  	edlin_expand \  	epp \ +	erl_anno \  	erl_bits \  	erl_compile \  	erl_eval \ @@ -169,6 +170,7 @@ docs:  # specifications.  primary_bootstrap_compiler: \    $(BOOTSTRAP_COMPILER)/ebin/epp.beam \ +  $(BOOTSTRAP_COMPILER)/ebin/erl_anno.beam \    $(BOOTSTRAP_COMPILER)/ebin/erl_scan.beam \    $(BOOTSTRAP_COMPILER)/ebin/erl_parse.beam \    $(BOOTSTRAP_COMPILER)/ebin/erl_lint.beam \ diff --git a/lib/stdlib/src/beam_lib.erl b/lib/stdlib/src/beam_lib.erl index 1a7b7d5a5e..4a6b489204 100644 --- a/lib/stdlib/src/beam_lib.erl +++ b/lib/stdlib/src/beam_lib.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %% -%% Copyright Ericsson AB 2000-2013. All Rights Reserved. +%% Copyright Ericsson AB 2000-2015. All Rights Reserved.  %%  %% The contents of this file are subject to the Erlang Public License,  %% Version 1.1, (the "License"); you may not use this file except in @@ -652,7 +652,13 @@ chunk_to_data(abstract_code=Id, Chunk, File, _Cs, AtomTable, Mod) ->  		{'EXIT', _} ->  		    error({invalid_chunk, File, chunk_name_to_id(Id, File)});  		Term -> -		    {AtomTable, {Id, Term}} +                    try +                        {AtomTable, {Id, anno_from_term(Term)}} +                    catch +                        _:_ -> +                            error({invalid_chunk, File, +                                   chunk_name_to_id(Id, File)}) +                    end  	    end      end;  chunk_to_data(atoms=Id, _Chunk, _File, Cs, AtomTable0, _Mod) -> @@ -878,7 +884,22 @@ decrypt_abst(Type, Module, File, Id, AtomTable, Bin) ->  decrypt_abst_1({Type,Key,IVec,_BlockSize}, Bin) ->      ok = start_crypto(),      NewBin = crypto:block_decrypt(Type, Key, IVec, Bin), -    binary_to_term(NewBin). +    Term = binary_to_term(NewBin), +    anno_from_term(Term). + +anno_from_term({raw_abstract_v1, Forms}) -> +    {raw_abstract_v1, anno_from_forms(Forms)}; +anno_from_term({Tag, Forms}) when Tag =:= abstract_v1; Tag =:= abstract_v2 -> +    try {Tag, anno_from_forms(Forms)} +    catch +        _:_ -> +            {Tag, Forms} +    end; +anno_from_term(T) -> +    T. + +anno_from_forms(Forms) -> +    [erl_parse:anno_from_term(Form) || Form <- Forms].  start_crypto() ->      case crypto:start() of diff --git a/lib/stdlib/src/edlin.erl b/lib/stdlib/src/edlin.erl index b3bc5f6d92..362669545e 100644 --- a/lib/stdlib/src/edlin.erl +++ b/lib/stdlib/src/edlin.erl @@ -21,7 +21,7 @@  %% A simple Emacs-like line editor.  %% About Latin-1 characters: see the beginning of erl_scan.erl. --export([init/0,start/1,start/2,edit_line/2,prefix_arg/1]). +-export([init/0,init/1,start/1,start/2,edit_line/2,prefix_arg/1]).  -export([erase_line/1,erase_inp/1,redraw_line/1]).  -export([length_before/1,length_after/1,prompt/1]).  -export([current_line/1, current_chars/1]). @@ -44,6 +44,20 @@  init() ->      put(kill_buffer, []). +init(Pid) -> +    %% copy the kill_buffer from the process Pid +    CopiedKillBuf = +	case erlang:process_info(Pid, dictionary) of +	    {dictionary,Dict} -> +		case proplists:get_value(kill_buffer, Dict) of +		    undefined -> []; +		    Buf       -> Buf +		end; +	    undefined -> +		[] +	end, +    put(kill_buffer, CopiedKillBuf). +  %% start(Prompt)  %% edit(Characters, Continuation)  %%  Return diff --git a/lib/stdlib/src/epp.erl b/lib/stdlib/src/epp.erl index 5f8637c118..7866b5f792 100644 --- a/lib/stdlib/src/epp.erl +++ b/lib/stdlib/src/epp.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %% -%% Copyright Ericsson AB 1996-2014. All Rights Reserved. +%% Copyright Ericsson AB 1996-2015. All Rights Reserved.  %%  %% The contents of this file are subject to the Erlang Public License,  %% Version 1.1, (the "License"); you may not use this file except in @@ -158,7 +158,7 @@ scan_erl_form(Epp) ->          {'ok', AbsForm} | {'eof', Line} | {error, ErrorInfo} when        Epp :: epp_handle(),        AbsForm :: erl_parse:abstract_form(), -      Line :: erl_scan:line(), +      Line :: erl_anno:line(),        ErrorInfo :: erl_scan:error_info() | erl_parse:error_info().  parse_erl_form(Epp) -> @@ -220,7 +220,7 @@ format_error(E) -> file:format_error(E).        IncludePath :: [DirectoryName :: file:name()],        Form :: erl_parse:abstract_form() | {'error', ErrorInfo} | {'eof',Line},        PredefMacros :: macros(), -      Line :: erl_scan:line(), +      Line :: erl_anno:line(),        ErrorInfo :: erl_scan:error_info() | erl_parse:error_info(),        OpenError :: file:posix() | badarg | system_limit. @@ -235,7 +235,7 @@ parse_file(Ifile, Path, Predefs) ->  		  {'default_encoding', DefEncoding :: source_encoding()} |  		  'extra'],        Form :: erl_parse:abstract_form() | {'error', ErrorInfo} | {'eof',Line}, -      Line :: erl_scan:line(), +      Line :: erl_anno:line(),        ErrorInfo :: erl_scan:error_info() | erl_parse:error_info(),        Extra :: [{'encoding', source_encoding() | 'none'}],        OpenError :: file:posix() | badarg | system_limit. @@ -257,7 +257,7 @@ parse_file(Ifile, Options) ->  -spec parse_file(Epp) -> [Form] when        Epp :: epp_handle(),        Form :: erl_parse:abstract_form() | {'error', ErrorInfo} | {'eof',Line}, -      Line :: erl_scan:line(), +      Line :: erl_anno:line(),        ErrorInfo :: erl_scan:error_info() | erl_parse:error_info().  parse_file(Epp) -> @@ -280,7 +280,7 @@ parse_file(Epp) ->  	{error,E} ->  	    [{error,E}|parse_file(Epp)];  	{eof,Location} -> -	    [{eof,Location}] +	    [{eof,erl_anno:new(Location)}]      end.  -spec default_encoding() -> source_encoding(). @@ -547,7 +547,8 @@ init_server(Pid, Name, Options, St0) ->  			 path=Path, macs=Ms1,  			 default_encoding=DefEncoding},              From = wait_request(St), -            enter_file_reply(From, Name, AtLocation, AtLocation), +            Anno = erl_anno:new(AtLocation), +            enter_file_reply(From, Name, Anno, AtLocation, code),              wait_req_scan(St);  	{error,E} ->  	    epp_reply(Pid, {error,E}) @@ -559,15 +560,16 @@ init_server(Pid, Name, Options, St0) ->  predef_macros(File) ->       Machine = list_to_atom(erlang:system_info(machine)), +     Anno = line1(),       dict:from_list([ -	{{atom,'FILE'}, 	      {none,[{string,1,File}]}}, -	{{atom,'LINE'},		      {none,[{integer,1,1}]}}, +	{{atom,'FILE'}, 	      {none,[{string,Anno,File}]}}, +	{{atom,'LINE'},		      {none,[{integer,Anno,1}]}},  	{{atom,'MODULE'},	      undefined},  	{{atom,'MODULE_STRING'},      undefined},  	{{atom,'BASE_MODULE'},	      undefined},  	{{atom,'BASE_MODULE_STRING'}, undefined}, -	{{atom,'MACHINE'},	      {none,[{atom,1,Machine}]}}, -	{{atom,Machine},	      {none,[{atom,1,true}]}} +	{{atom,'MACHINE'},	      {none,[{atom,Anno,Machine}]}}, +	{{atom,Machine},	      {none,[{atom,Anno,true}]}}       ]).  %% user_predef(PreDefMacros, Macros) -> @@ -595,8 +597,9 @@ user_predef([M|Pdm], Ms) when is_atom(M) ->  	{ok,_Def} -> %% Predefined macros  	    {error,{redefine_predef,M}};  	error -> +            A = line1(),  	    user_predef(Pdm, -	                dict:store({atom,M}, [{none, {none,[{atom,1,true}]}}], Ms)) +	                dict:store({atom,M}, [{none, {none,[{atom,A,true}]}}], Ms))      end;  user_predef([Md|_Pdm], _Ms) -> {error,{bad,Md}};  user_predef([], Ms) -> {ok,Ms}. @@ -645,7 +648,7 @@ wait_req_skip(St, Sis) ->  enter_file(_NewName, Inc, From, St)    when length(St#epp.sstk) >= 8 -> -    epp_reply(From, {error,{abs_loc(Inc),epp,{depth,"include"}}}), +    epp_reply(From, {error,{loc(Inc),epp,{depth,"include"}}}),      wait_req_scan(St);  enter_file(NewName, Inc, From, St) ->      case file:path_open(St#epp.path, NewName, [read]) of @@ -653,7 +656,7 @@ enter_file(NewName, Inc, From, St) ->              Loc = start_loc(St#epp.location),  	    wait_req_scan(enter_file2(NewF, Pname, From, St, Loc));  	{error,_E} -> -	    epp_reply(From, {error,{abs_loc(Inc),epp,{include,file,NewName}}}), +	    epp_reply(From, {error,{loc(Inc),epp,{include,file,NewName}}}),  	    wait_req_scan(St)      end. @@ -661,9 +664,9 @@ enter_file(NewName, Inc, From, St) ->  %%  Set epp to use this file and "enter" it.  enter_file2(NewF, Pname, From, St0, AtLocation) -> -    Loc = start_loc(AtLocation), -    enter_file_reply(From, Pname, Loc, AtLocation), -    Ms = dict:store({atom,'FILE'}, {none,[{string,Loc,Pname}]}, St0#epp.macs), +    Anno = erl_anno:new(AtLocation), +    enter_file_reply(From, Pname, Anno, AtLocation, code), +    Ms = dict:store({atom,'FILE'}, {none,[{string,Anno,Pname}]}, St0#epp.macs),      %% update the head of the include path to be the directory of the new      %% source file, so that an included file can always include other files      %% relative to its current location (this is also how C does it); note @@ -673,16 +676,20 @@ enter_file2(NewF, Pname, From, St0, AtLocation) ->      Path = [filename:dirname(Pname) | tl(St0#epp.path)],      DefEncoding = St0#epp.default_encoding,      _ = set_encoding(NewF, DefEncoding), -    #epp{file=NewF,location=Loc,name=Pname,name2=Pname,delta=0, +    #epp{file=NewF,location=AtLocation,name=Pname,name2=Pname,delta=0,           sstk=[St0|St0#epp.sstk],path=Path,macs=Ms,           default_encoding=DefEncoding}. -enter_file_reply(From, Name, Location, AtLocation) -> -    Attr = loc_attr(AtLocation), -    Rep = {ok, [{'-',Attr},{atom,Attr,file},{'(',Attr}, -		{string,Attr,file_name(Name)},{',',Attr}, -		{integer,Attr,get_line(Location)},{')',Location}, -                {dot,Attr}]}, +enter_file_reply(From, Name, LocationAnno, AtLocation, Where) -> +    Anno0 = loc_anno(AtLocation), +    Anno = case Where of +               code -> Anno0; +               generated -> erl_anno:set_generated(true, Anno0) +           end, +    Rep = {ok, [{'-',Anno},{atom,Anno,file},{'(',Anno}, +		{string,Anno,file_name(Name)},{',',Anno}, +		{integer,Anno,get_line(LocationAnno)},{')',LocationAnno}, +                {dot,Anno}]},      epp_reply(From, Rep).  %% Flatten filename to a string. Must be a valid filename. @@ -710,18 +717,20 @@ leave_file(From, St) ->                      #epp{location=OldLoc, delta=Delta, name=OldName,                           name2=OldName2} = OldSt,                      CurrLoc = add_line(OldLoc, Delta), +                    Anno = erl_anno:new(CurrLoc),  		    Ms = dict:store({atom,'FILE'}, -				    {none,[{string,CurrLoc,OldName2}]}, +				    {none,[{string,Anno,OldName2}]},  				    St#epp.macs),                      NextSt = OldSt#epp{sstk=Sts,macs=Ms,uses=St#epp.uses}, -		    enter_file_reply(From, OldName, CurrLoc, CurrLoc), +		    enter_file_reply(From, OldName, Anno, CurrLoc, code),                      case OldName2 =:= OldName of                          true ->                              ok;                          false ->                              NFrom = wait_request(NextSt), -                            enter_file_reply(NFrom, OldName2, OldLoc, -                                             neg_line(CurrLoc)) +                            OldAnno = erl_anno:new(OldLoc), +                            enter_file_reply(NFrom, OldName2, OldAnno, +                                             CurrLoc, generated)                          end,                      wait_req_scan(NextSt);  		[] -> @@ -818,9 +827,9 @@ scan_extends(_Ts, _As, Ms) -> Ms.  %% scan_define(Tokens, DefineToken, From, EppState) -scan_define([{'(',_Lp},{Type,_Lm,M}=Mac,{',',Lc}|Toks], _Def, From, St) +scan_define([{'(',_Lp},{Type,_Lm,M}=Mac,{',',_}=Comma|Toks], _Def, From, St)    when Type =:= atom; Type =:= var -> -    case catch macro_expansion(Toks, Lc) of +    case catch macro_expansion(Toks, Comma) of          Expansion when is_list(Expansion) ->              case dict:find({atom,M}, St#epp.macs) of                  {ok, Defs} when is_list(Defs) -> @@ -910,10 +919,12 @@ macro_ref([]) ->      [];  macro_ref([{'?', _}, {'?', _} | Rest]) ->      macro_ref(Rest); -macro_ref([{'?', _}, {atom, Lm, A} | Rest]) -> +macro_ref([{'?', _}, {atom, _, A}=Atom | Rest]) -> +    Lm = loc(Atom),      Arity = count_args(Rest, Lm, A),      [{{atom, A}, Arity} | macro_ref(Rest)]; -macro_ref([{'?', _}, {var, Lm, A} | Rest]) -> +macro_ref([{'?', _}, {var, _, A}=Var | Rest]) -> +    Lm = loc(Var),      Arity = count_args(Rest, Lm, A),      [{{atom, A}, Arity} | macro_ref(Rest)];  macro_ref([_Token | Rest]) -> @@ -940,7 +951,7 @@ scan_include([{'(',_Llp},{string,_Lf,NewName0},{')',_Lrp},{dot,_Ld}], Inc,      NewName = expand_var(NewName0),      enter_file(NewName, Inc, From, St);  scan_include(_Toks, Inc, From, St) -> -    epp_reply(From, {error,{abs_loc(Inc),epp,{bad,include}}}), +    epp_reply(From, {error,{loc(Inc),epp,{bad,include}}}),      wait_req_scan(St).  %% scan_include_lib(Tokens, IncludeToken, From, EppState) @@ -955,7 +966,7 @@ find_lib_dir(NewName) ->  scan_include_lib([{'(',_Llp},{string,_Lf,_NewName0},{')',_Lrp},{dot,_Ld}],                   Inc, From, St)    when length(St#epp.sstk) >= 8 -> -    epp_reply(From, {error,{abs_loc(Inc),epp,{depth,"include_lib"}}}), +    epp_reply(From, {error,{loc(Inc),epp,{depth,"include_lib"}}}),      wait_req_scan(St);  scan_include_lib([{'(',_Llp},{string,_Lf,NewName0},{')',_Lrp},{dot,_Ld}],                   Inc, From, St) -> @@ -974,18 +985,18 @@ scan_include_lib([{'(',_Llp},{string,_Lf,NewName0},{')',_Lrp},{dot,_Ld}],                                                        St, Loc));  			{error,_E2} ->  			    epp_reply(From, -				      {error,{abs_loc(Inc),epp, +				      {error,{loc(Inc),epp,                                                {include,lib,NewName}}}),  			    wait_req_scan(St)  		    end;  		_Error -> -		    epp_reply(From, {error,{abs_loc(Inc),epp, +		    epp_reply(From, {error,{loc(Inc),epp,                                              {include,lib,NewName}}}),  		    wait_req_scan(St)  	    end      end;  scan_include_lib(_Toks, Inc, From, St) -> -    epp_reply(From, {error,{abs_loc(Inc),epp,{bad,include_lib}}}), +    epp_reply(From, {error,{loc(Inc),epp,{bad,include_lib}}}),      wait_req_scan(St).  %% scan_ifdef(Tokens, IfdefToken, From, EppState) @@ -1088,11 +1099,12 @@ scan_endif(_Toks, Endif, From, St) ->  scan_file([{'(',_Llp},{string,_Ls,Name},{',',_Lc},{integer,_Li,Ln},{')',_Lrp},             {dot,_Ld}], Tf, From, St) -> -    enter_file_reply(From, Name, Ln, neg_line(abs_loc(Tf))), -    Ms = dict:store({atom,'FILE'}, {none,[{string,1,Name}]}, St#epp.macs), +    Anno = erl_anno:new(Ln), +    enter_file_reply(From, Name, Anno, loc(Tf), generated), +    Ms = dict:store({atom,'FILE'}, {none,[{string,line1(),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,  +    Delta = get_line(element(2, Tf))-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}}}), @@ -1153,7 +1165,7 @@ skip_else(_Else, From, St, Sis) ->      skip_toks(From, St, Sis).  %% macro_pars(Tokens, ArgStack) -%% macro_expansion(Tokens, Line) +%% macro_expansion(Tokens, Anno)  %%  Extract the macro parameters and the expansion from a macro definition.  macro_pars([{')',_Lp}, {',',Ld}|Ex], Args) -> @@ -1165,11 +1177,12 @@ macro_pars([{var,_L,Name}, {',',_}|Ts], Args) ->      false = lists:member(Name, Args),      macro_pars(Ts, [Name|Args]). -macro_expansion([{')',_Lp},{dot,_Ld}], _L0) -> []; -macro_expansion([{dot,Ld}], _L0) -> throw({error,Ld,missing_parenthesis}); -macro_expansion([T|Ts], _L0) -> -    [T|macro_expansion(Ts, element(2, T))]; -macro_expansion([], L0) -> throw({error,L0,premature_end}). +macro_expansion([{')',_Lp},{dot,_Ld}], _Anno0) -> []; +macro_expansion([{dot,_}=Dot], _Anno0) -> +    throw({error,loc(Dot),missing_parenthesis}); +macro_expansion([T|Ts], _Anno0) -> +    [T|macro_expansion(Ts, T)]; +macro_expansion([], Anno0) -> throw({error,loc(Anno0),premature_end}).  %% expand_macros(Tokens, Macros)  %% expand_macro(Tokens, MacroToken, RestTokens) @@ -1239,17 +1252,17 @@ expand_macros([{'?',_Lq},{atom,_Lm,M}=MacT|Toks], Ms) ->      expand_macros(atom, MacT, M, Toks, Ms);  %% Special macros  expand_macros([{'?',_Lq},{var,Lm,'LINE'}=Tok|Toks], Ms) -> -    {line,Line} = erl_scan:token_info(Tok, line), +    Line = erl_scan:line(Tok),      [{integer,Lm,Line}|expand_macros(Toks, Ms)];  expand_macros([{'?',_Lq},{var,_Lm,M}=MacT|Toks], Ms) ->      expand_macros(atom, MacT, M, Toks, Ms);  %% Illegal macros  expand_macros([{'?',_Lq},Token|_Toks], _Ms) -> -    T = case erl_scan:token_info(Token, text) of -            {text,Text} -> +    T = case erl_scan:text(Token) of +            Text when is_list(Text) ->                  Text;              undefined -> -                {symbol,Symbol} = erl_scan:token_info(Token, symbol), +                Symbol = erl_scan:symbol(Token),                  io_lib:write(Symbol)          end,      throw({error,loc(Token),{call,[$?|T]}}); @@ -1383,7 +1396,7 @@ expand_arg([], Ts, L, Rest, Bs) ->  %%% stringify(Ts, L) returns a list of one token: a string which when  %%% tokenized would yield the token list Ts. -%% erl_scan:token_info(T, text) is not backward compatible with this. +%% erl_scan:text(T) is not backward compatible with this.  %% Note that escaped characters will be replaced by themselves.  token_src({dot, _}) ->      "."; @@ -1456,36 +1469,29 @@ 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_anno(Line) when is_integer(Line) -> +    erl_anno:new(Line); +loc_anno({Line,_Column}) -> +    erl_anno:new(Line).  loc(Token) -> -    {location,Location} = erl_scan:token_info(Token, location), -    Location. +    erl_scan:location(Token). -abs_loc(Token) -> -    loc(setelement(2, Token, abs_line(element(2, Token)))). - -neg_line(L) -> -    erl_scan:set_attribute(line, L, fun(Line) -> -abs(Line) end). - -abs_line(L) -> -    erl_scan:set_attribute(line, L, fun(Line) -> abs(Line) end). - -add_line(L, Offset) -> -    erl_scan:set_attribute(line, L, fun(Line) -> Line+Offset end). +add_line(Line, Offset) when is_integer(Line) -> +    Line+Offset; +add_line({Line, Column}, Offset) -> +    {Line+Offset, Column}.  start_loc(Line) when is_integer(Line) ->      1;  start_loc({_Line, _Column}) -> -    {1,1}. +    {1, 1}. -get_line(Line) when is_integer(Line) -> -    Line; -get_line({Line,_Column}) -> -    Line. +line1() -> +    erl_anno:new(1). + +get_line(Anno) -> +    erl_anno:line(Anno).  %% epp has always output -file attributes when entering and leaving  %% included files (-include, -include_lib). Starting with R11B the @@ -1525,14 +1531,15 @@ get_line({Line,_Column}) ->  interpret_file_attribute(Forms) ->      interpret_file_attr(Forms, 0, []). -interpret_file_attr([{attribute,Loc,file,{File,Line}}=Form | Forms], +interpret_file_attr([{attribute,Anno,file,{File,Line}}=Form | Forms],                      Delta, Fs) -> -    {line, L} = erl_scan:attributes_info(Loc, line), +    L = get_line(Anno), +    Generated = erl_anno:generated(Anno),      if -        L < 0 -> +        Generated ->              %% -file attribute -            interpret_file_attr(Forms, (abs(L) + Delta) - Line, Fs); -        true -> +            interpret_file_attr(Forms, (L + Delta) - Line, Fs); +        not Generated ->              %% -include or -include_lib              % true = L =:= Line,              case Fs of @@ -1543,11 +1550,11 @@ interpret_file_attr([{attribute,Loc,file,{File,Line}}=Form | Forms],              end      end;  interpret_file_attr([Form0 | Forms], Delta, Fs) -> -    F = fun(Attrs) -> -                F2 = fun(L) -> abs(L) + Delta end, -                erl_scan:set_attribute(line, Attrs, F2) +    F = fun(Anno) -> +                Line = erl_anno:line(Anno), +                erl_anno:set_line(Line + Delta, Anno)          end, -    Form = erl_lint:modify_line(Form0, F), +    Form = erl_parse:map_anno(F, Form0),      [Form | interpret_file_attr(Forms, Delta, Fs)];  interpret_file_attr([], _Delta, _Fs) ->      []. diff --git a/lib/stdlib/src/erl_anno.erl b/lib/stdlib/src/erl_anno.erl new file mode 100644 index 0000000000..963b7278a6 --- /dev/null +++ b/lib/stdlib/src/erl_anno.erl @@ -0,0 +1,460 @@ +%% +%% %CopyrightBegin% +%% +%% Copyright Ericsson AB 1996-2015. All Rights Reserved. +%% +%% The contents of this file are subject to the Erlang Public License, +%% Version 1.1, (the "License"); you may not use this file except in +%% compliance with the License. You should have received a copy of the +%% Erlang Public License along with this software. If not, it can be +%% retrieved online at http://www.erlang.org/. +%% +%% Software distributed under the License is distributed on an "AS IS" +%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See +%% the License for the specific language governing rights and limitations +%% under the License. +%% +%% %CopyrightEnd% +%% + +-module(erl_anno). + +-export([new/1, is_anno/1]). +-export([column/1, end_location/1, file/1, generated/1, +         line/1, location/1, record/1, text/1]). +-export([set_file/2, set_generated/2, set_line/2, set_location/2, +         set_record/2, set_text/2]). + +%% To be used when necessary to avoid Dialyzer warnings. +-export([to_term/1, from_term/1]). + +-export_type([anno/0, line/0, column/0, location/0, text/0]). + +-export_type([anno_term/0]). + +-define(LN(L), is_integer(L)). +-define(COL(C), (is_integer(C) andalso C >= 1)). + +%% Location. +-define(LCOLUMN(C), ?COL(C)). +-define(LLINE(L), ?LN(L)). + +%% Debug: define DEBUG to make sure that annotations are handled as an +%% opaque type. Note that all abstract code need to be compiled with +%% DEBUG=true. See also ./erl_pp.erl. + +%-define(DEBUG, true). + +-type annotation() :: {'file', filename()} +                    | {'generated', generated()} +                    | {'location', location()} +                    | {'record', record()} +                    | {'text', string()}. + +-type anno() :: location() | [annotation(), ...]. +-type anno_term() :: term(). + +-type column() :: pos_integer(). +-type generated() :: boolean(). +-type filename() :: file:filename_all(). +-type line() :: integer(). +-type location() :: line() | {line(), column()}. +-type record() :: boolean(). +-type text() :: string(). + +-ifdef(DEBUG). +%% Anything 'false' accepted by the compiler. +-define(ALINE(A), is_reference(A)). +-define(ACOLUMN(A), is_reference(A)). +-else. +-define(ALINE(L), ?LN(L)). +-define(ACOLUMN(C), ?COL(C)). +-endif. + +-spec to_term(Anno) -> anno_term() when +      Anno :: anno(). + +-ifdef(DEBUG). +to_term(Anno) -> +    simplify(Anno). +-else. +to_term(Anno) -> +    Anno. +-endif. + +-spec from_term(Term) -> Anno when +      Term :: anno_term(), +      Anno :: anno(). + +-ifdef(DEBUG). +from_term(Term) when is_list(Term) -> +    Term; +from_term(Term) -> +    [{location, Term}]. +-else. +from_term(Term) -> +    Term. +-endif. + +-spec new(Location) -> anno() when +      Location :: location(). + +new(Line) when ?LLINE(Line) -> +    new_location(Line); +new({Line, Column}=Loc) when ?LLINE(Line), ?LCOLUMN(Column) -> +    new_location(Loc); +new(Term) -> +    erlang:error(badarg, [Term]). + +-ifdef(DEBUG). +new_location(Location) -> +    [{location, Location}]. +-else. +new_location(Location) -> +    Location. +-endif. + +-spec is_anno(Term) -> boolean() when +      Term :: any(). + +is_anno(Line) when ?ALINE(Line) -> +    true; +is_anno({Line, Column}) when ?ALINE(Line), ?ACOLUMN(Column) -> +    true; +is_anno(Anno) -> +    (Anno =/= [] andalso +     is_anno1(Anno) andalso +     lists:keymember(location, 1, Anno)). + +is_anno1([{Item, Value}|Anno]) -> +    is_anno2(Item, Value) andalso is_anno1(Anno); +is_anno1(A) -> +    A =:= []. + +is_anno2(location, Line) when ?LN(Line) -> +    true; +is_anno2(location, {Line, Column}) when ?LN(Line), ?COL(Column) -> +    true; +is_anno2(generated, true) -> +    true; +is_anno2(file, Filename) -> +    is_filename(Filename); +is_anno2(record, true) -> +    true; +is_anno2(text, Text) -> +    is_string(Text); +is_anno2(_, _) -> +    false. + +is_filename(T) -> +    is_string(T) orelse is_binary(T). + +is_string(T) -> +    try lists:all(fun(C) when is_integer(C), C >= 0 -> true end, T) +    catch _:_ -> false +    end. + +-spec column(Anno) -> column() | 'undefined' when +      Anno :: anno(). + +column({Line, Column}) when ?ALINE(Line), ?ACOLUMN(Column) -> +    Column; +column(Line) when ?ALINE(Line) -> +    undefined; +column(Anno) -> +    case location(Anno) of +        {_Line, Column} -> +            Column; +        _Line -> +            undefined +    end. + +-spec end_location(Anno) -> location() | 'undefined' when +      Anno :: anno(). + +end_location(Anno) -> +    case text(Anno) of +        undefined -> +            undefined; +        Text -> +            case location(Anno) of +                {Line, Column} -> +                    end_location(Text, Line, Column); +                Line -> +                    end_location(Text, Line) +            end +    end. + +-spec file(Anno) -> filename() | 'undefined' when +      Anno :: anno(). + +file(Line) when ?ALINE(Line) -> +    undefined; +file({Line, Column}) when ?ALINE(Line), ?ACOLUMN(Column) -> +    undefined; +file(Anno) -> +    anno_info(Anno, file). + +-spec generated(Anno) -> generated() when +      Anno :: anno(). + +generated(Line) when ?ALINE(Line) -> +    Line =< 0; +generated({Line, Column}) when ?ALINE(Line), ?ACOLUMN(Column) -> +    Line =< 0; +generated(Anno) -> +    _ = anno_info(Anno, generated, false), +    {location, Location} = lists:keyfind(location, 1, Anno), +    case Location of +        {Line, _Column} -> +            Line =< 0; +        Line -> +            Line =< 0 +    end. + +-spec line(Anno) -> line() when +      Anno :: anno(). + +line(Anno) -> +    case location(Anno) of +        {Line, _Column} -> +            Line; +        Line -> +            Line +    end. + +-spec location(Anno) -> location() when +      Anno :: anno(). + +location(Line) when ?ALINE(Line) -> +    abs(Line); +location({Line, Column}) when ?ALINE(Line), ?ACOLUMN(Column) -> +    {abs(Line), Column}; +location(Anno) -> +    case anno_info(Anno, location) of +        Line when Line < 0 -> +            -Line; +        {Line, Column} when Line < 0 -> +            {-Line, Column}; +        Location -> +            Location +    end. + +-spec record(Anno) -> record() when +      Anno :: anno(). + +record(Line) when ?ALINE(Line) -> +    false; +record({Line, Column}) when ?ALINE(Line), ?ACOLUMN(Column) -> +    false; +record(Anno) -> +    anno_info(Anno, record, false). + +-spec text(Anno) -> text() | 'undefined' when +      Anno :: anno(). + +text(Line) when ?ALINE(Line) -> +    undefined; +text({Line, Column}) when ?ALINE(Line), ?ACOLUMN(Column) -> +    undefined; +text(Anno) -> +    anno_info(Anno, text). + +-spec set_file(File, Anno) -> Anno when +      File :: filename(), +      Anno :: anno(). + +set_file(File, Anno) -> +    set(file, File, Anno). + +-spec set_generated(Generated, Anno) -> Anno when +      Generated :: generated(), +      Anno :: anno(). + +set_generated(true, Line) when ?ALINE(Line) -> +    -abs(Line); +set_generated(false, Line) when ?ALINE(Line) -> +    abs(Line); +set_generated(true, {Line, Column}) when ?ALINE(Line), +                                         ?ACOLUMN(Column) -> +    {-abs(Line),Column}; +set_generated(false, {Line, Column}) when ?ALINE(Line), +                                          ?ACOLUMN(Column) -> +    {abs(Line),Column}; +set_generated(Generated, Anno) -> +    _ = set(generated, Generated, Anno), +    {location, Location} = lists:keyfind(location, 1, Anno), +    NewLocation = +        case Location of +            {Line, Column} when Generated -> +                {-abs(Line), Column}; +            {Line, Column} when not Generated -> +                {abs(Line), Column}; +            Line when Generated -> +                -abs(Line); +            Line when not Generated -> +                abs(Line) +        end, +    lists:keyreplace(location, 1, Anno, {location, NewLocation}). + +-spec set_line(Line, Anno) -> Anno when +      Line :: line(), +      Anno :: anno(). + +set_line(Line, Anno) -> +    case location(Anno) of +        {_Line, Column} -> +            set_location({Line, Column}, Anno); +        _Line -> +            set_location(Line, Anno) +    end. + +-spec set_location(Location, Anno) -> Anno when +      Location :: location(), +      Anno :: anno(). + +set_location(Line, L) when ?ALINE(L), ?LLINE(Line) -> +    new_location(fix_line(Line, L)); +set_location(Line, {L, Column}) when ?ALINE(L), ?ACOLUMN(Column), +                                     ?LLINE(Line) -> +    new_location(fix_line(Line, L)); +set_location({L, C}=Loc, Line) when ?ALINE(Line), ?LLINE(L), ?LCOLUMN(C) -> +    new_location(fix_location(Loc, Line)); +set_location({L, C}=Loc, {Line, Column}) when ?ALINE(Line), ?ACOLUMN(Column), +                                              ?LLINE(L), ?LCOLUMN(C) -> +    new_location(fix_location(Loc, Line)); +set_location(Location, Anno) -> +    _ = set(location, Location, Anno), +    {location, OldLocation} = lists:keyfind(location, 1, Anno), +    NewLocation = +        case {Location, OldLocation} of +            {{_Line, _Column}=Loc, {L, _C}} -> +                fix_location(Loc, L); +            {Line, {L, _C}} -> +                fix_line(Line, L); +            {{_Line, _Column}=Loc, L} -> +                fix_location(Loc, L); +            {Line, L} -> +                fix_line(Line, L) +        end, +    lists:keyreplace(location, 1, Anno, {location, NewLocation}). + +fix_location({Line, Column}, OldLine) -> +    {fix_line(Line, OldLine), Column}. + +fix_line(Line, OldLine) when OldLine < 0, Line > 0 -> +    -Line; +fix_line(Line, _OldLine) -> +    Line. + +-spec set_record(Record, Anno) -> Anno when +      Record :: record(), +      Anno :: anno(). + +set_record(Record, Anno) -> +    set(record, Record, Anno). + +-spec set_text(Text, Anno) -> Anno when +      Text :: text(), +      Anno :: anno(). + +set_text(Text, Anno) -> +    set(text, Text, Anno). + +set(Item, Value, Anno) -> +    case {is_settable(Item, Value), Anno} of +        {true, Line} when ?ALINE(Line) -> +            set_anno(Item, Value, [{location, Line}]); +        {true, {L, C}=Location} when ?ALINE(L), ?ACOLUMN(C) -> +            set_anno(Item, Value, [{location, Location}]); +        {true, A} when is_list(A), A =/= [] -> +            set_anno(Item, Value, Anno); +        _ -> +            erlang:error(badarg, [Item, Value, Anno]) +    end. + +set_anno(Item, Value, Anno) -> +    case default(Item, Value) of +        true -> +            reset(Anno, Item); +        false -> +            R = case anno_info(Anno, Item) of +                    undefined -> +                        [{Item, Value}|Anno]; +                    _ -> +                        lists:keyreplace(Item, 1, Anno, {Item, Value}) +                end, +            simplify(R) +    end. + +reset(Anno, Item) -> +    A = lists:keydelete(Item, 1, Anno), +    reset_simplify(A). + +-ifdef(DEBUG). +reset_simplify(A) -> +    A. +-else. +reset_simplify(A) -> +    simplify(A). +-endif. + +simplify([{location, Location}]) -> +    Location; +simplify(Anno) -> +    Anno. + +anno_info(Anno, Item, Default) -> +    try lists:keyfind(Item, 1, Anno) of +        false -> +            Default; +        {Item, Value} -> +            Value +    catch +        _:_ -> +            erlang:error(badarg, [Anno]) +    end. + +anno_info(Anno, Item) -> +    try lists:keyfind(Item, 1, Anno) of +        {Item, Value} -> +            Value; +        false -> +            undefined +    catch +        _:_ -> +            erlang:error(badarg, [Anno]) +    end. + +end_location("", Line, Column) -> +    {Line, Column}; +end_location([$\n|String], Line, _Column) -> +    end_location(String, Line+1, 1); +end_location([_|String], Line, Column) -> +    end_location(String, Line, Column+1). + +end_location("", Line) -> +    Line; +end_location([$\n|String], Line) -> +    end_location(String, Line+1); +end_location([_|String], Line) -> +    end_location(String, Line). + +is_settable(file, File) -> +    is_filename(File); +is_settable(generated, Boolean) when Boolean; not Boolean -> +    true; +is_settable(location, Line) when ?LLINE(Line) -> +    true; +is_settable(location, {Line, Column}) when ?LLINE(Line), ?LCOLUMN(Column) -> +    true; +is_settable(record, Boolean) when Boolean; not Boolean -> +    true; +is_settable(text, Text) -> +    is_string(Text); +is_settable(_, _) -> +    false. + +default(generated, false) -> true; +default(record, false) -> true; +default(_, _) -> false. diff --git a/lib/stdlib/src/erl_eval.erl b/lib/stdlib/src/erl_eval.erl index 371573dc23..39f833009f 100644 --- a/lib/stdlib/src/erl_eval.erl +++ b/lib/stdlib/src/erl_eval.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %%  -%% Copyright Ericsson AB 1996-2013. All Rights Reserved. +%% Copyright Ericsson AB 1996-2015. All Rights Reserved.  %%   %% The contents of this file are subject to the Erlang Public License,  %% Version 1.1, (the "License"); you may not use this file except in @@ -246,18 +246,14 @@ expr({record,_,_,Name,_}, _Bs, _Lf, _Ef, _RBs) ->  %% map  expr({map,_,Binding,Es}, Bs0, Lf, Ef, RBs) ->      {value, Map0, Bs1} = expr(Binding, Bs0, Lf, Ef, none), -    case Map0 of -        #{} -> -            {Vs,Bs2} = eval_map_fields(Es, Bs0, Lf, Ef), -            Map1 = lists:foldl(fun ({map_assoc,K,V}, Mi) -> -                                       maps:put(K, V, Mi); -                                   ({map_exact,K,V}, Mi) -> -                                       maps:update(K, V, Mi) -                               end, Map0, Vs), -            ret_expr(Map1, merge_bindings(Bs2, Bs1), RBs); -        _ -> -            erlang:raise(error, {badarg,Map0}, stacktrace()) -    end; +    {Vs,Bs2} = eval_map_fields(Es, Bs0, Lf, Ef), +    _ = maps:put(k, v, Map0),			%Validate map. +    Map1 = lists:foldl(fun ({map_assoc,K,V}, Mi) -> +			       maps:put(K, V, Mi); +			   ({map_exact,K,V}, Mi) -> +			       maps:update(K, V, Mi) +		       end, Map0, Vs), +    ret_expr(Map1, merge_bindings(Bs2, Bs1), RBs);  expr({map,_,Es}, Bs0, Lf, Ef, RBs) ->      {Vs,Bs} = eval_map_fields(Es, Bs0, Lf, Ef),      ret_expr(lists:foldl(fun @@ -483,12 +479,13 @@ expr({value,_,Val}, Bs, _Lf, _Ef, RBs) ->    % Special case straight values.  find_maxline(LC) ->      put('$erl_eval_max_line', 0), -    F = fun(L) -> +    F = fun(A) -> +                L = erl_anno:line(A),                  case is_integer(L) and (L > get('$erl_eval_max_line')) of                      true -> put('$erl_eval_max_line', L);                      false -> ok                  end end, -    _ = erl_lint:modify_line(LC, F), +    _ = erl_parse:map_anno(F, LC),      erase('$erl_eval_max_line').  hide_calls(LC, MaxLine) -> @@ -498,14 +495,16 @@ hide_calls(LC, MaxLine) ->  %% v/1 and local calls are hidden.  hide({value,L,V}, Id, D) -> -    {{atom,Id,ok}, Id+1, dict:store(Id, {value,L,V}, D)}; +    A = erl_anno:new(Id), +    {{atom,A,ok}, Id+1, dict:store(Id, {value,L,V}, D)};  hide({call,L,{atom,_,N}=Atom,Args}, Id0, D0) ->      {NArgs, Id, D} = hide(Args, Id0, D0),      C = case erl_internal:bif(N, length(Args)) of              true ->                  {call,L,Atom,NArgs};              false ->  -                {call,Id,{remote,L,{atom,L,m},{atom,L,f}},NArgs} +                A = erl_anno:new(Id), +                {call,A,{remote,L,{atom,L,m},{atom,L,f}},NArgs}          end,      {C, Id+1, dict:store(Id, {call,Atom}, D)};  hide(T0, Id0, D0) when is_tuple(T0) ->  @@ -518,11 +517,23 @@ hide([E0 | Es0], Id0, D0) ->  hide(E, Id, D) ->       {E, Id, D}. -unhide_calls({atom,Id,ok}, MaxLine, D) when Id > MaxLine -> -    dict:fetch(Id, D); -unhide_calls({call,Id,{remote,L,_M,_F},Args}, MaxLine, D) when Id > MaxLine -> -    {call,Atom} = dict:fetch(Id, D), -    {call,L,Atom,unhide_calls(Args, MaxLine, D)}; +unhide_calls({atom,A,ok}=E, MaxLine, D) -> +    L = erl_anno:line(A), +    if +        L > MaxLine -> +            dict:fetch(L, D); +        true -> +            E +    end; +unhide_calls({call,A,{remote,L,{atom,L,m},{atom,L,f}}=F,Args}, MaxLine, D) -> +    Line = erl_anno:line(A), +    if +        Line > MaxLine -> +            {call,Atom} = dict:fetch(Line, D), +            {call,L,Atom,unhide_calls(Args, MaxLine, D)}; +        true -> +            {call,A,F,unhide_calls(Args, MaxLine, D)} +    end;  unhide_calls(T, MaxLine, D) when is_tuple(T) ->       list_to_tuple(unhide_calls(tuple_to_list(T), MaxLine, D));  unhide_calls([E | Es], MaxLine, D) ->  diff --git a/lib/stdlib/src/erl_expand_records.erl b/lib/stdlib/src/erl_expand_records.erl index 64a00acd88..0d3debae22 100644 --- a/lib/stdlib/src/erl_expand_records.erl +++ b/lib/stdlib/src/erl_expand_records.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %% -%% Copyright Ericsson AB 2005-2014. All Rights Reserved. +%% Copyright Ericsson AB 2005-2015. All Rights Reserved.  %%  %% The contents of this file are subject to the Erlang Public License,  %% Version 1.1, (the "License"); you may not use this file except in @@ -38,8 +38,6 @@                   checked_ra=[]        % successfully accessed records                  }). --define(REC_OFFSET, 100000000). % A hundred millions. Also in v3_core. -  -spec(module(AbsForms, CompileOptions) -> AbsForms when        AbsForms :: [erl_parse:abstract_form()],        CompileOptions :: [compile:option()]). @@ -149,7 +147,7 @@ pattern({record_index,Line,Name,Field}, St) ->  pattern({record,Line0,Name,Pfs}, St0) ->      Fs = record_fields(Name, St0),      {TMs,St1} = pattern_list(pattern_fields(Fs, Pfs), St0), -    Line = record_offset(Line0, St1), +    Line = mark_record(Line0, St1),      {{tuple,Line,[{atom,Line0,Name} | TMs]},St1};  pattern({bin,Line,Es0}, St0) ->      {Es1,St1} = pattern_bin(Es0, St0), @@ -243,7 +241,7 @@ record_test_in_guard(Line, Term, Name, St) ->              expr({atom,Line,false}, St);          false ->              Fs = record_fields(Name, St), -            NLine = neg_line(Line), +            NLine = no_compiler_warning(Line),              expr({call,NLine,{remote,NLine,{atom,NLine,erlang},{atom,NLine,is_record}},                    [Term,{atom,Line,Name},{integer,Line,length(Fs)+1}]},                   St) @@ -269,7 +267,7 @@ record_test_in_body(Line, Expr, Name, St0) ->      %% evaluate to a tuple properly.      Fs = record_fields(Name, St0),      {Var,St} = new_var(Line, St0), -    NLine = neg_line(Line), +    NLine = no_compiler_warning(Line),      expr({block,Line,            [{match,Line,Var,Expr},             {call,NLine,{remote,NLine,{atom,NLine,erlang}, @@ -333,7 +331,7 @@ expr({record_index,Line,Name,F}, St) ->      I = index_expr(Line, F, Name, record_fields(Name, St)),      expr(I, St);  expr({record,Line0,Name,Is}, St) -> -    Line = record_offset(Line0, St), +    Line = mark_record(Line0, St),      expr({tuple,Line,[{atom,Line0,Name} |                        record_inits(record_fields(Name, St), Is)]},           St); @@ -384,21 +382,11 @@ expr({call,Line,{tuple,_,[{atom,_,erlang},{atom,_,is_record}]},  expr({call,Line,{atom,_La,N}=Atom,As0}, St0) ->      {As,St1} = expr_list(As0, St0),      Ar = length(As), -    case erl_internal:bif(N, Ar) of -        true -> -            {{call,Line,Atom,As},St1}; -        false -> -            case imported(N, Ar, St1) of -                {yes,_Mod} -> -                    {{call,Line,Atom,As},St1}; -                no -> -                    case {N,Ar} of -                        {record_info,2} -> -                            record_info_call(Line, As, St1); -                        _ -> -                            {{call,Line,Atom,As},St1} -                    end -            end +    case {N,Ar} =:= {record_info,2} andalso not imported(N, Ar, St1) of +	true -> +	    record_info_call(Line, As, St1); +	false -> +	    {{call,Line,Atom,As},St1}      end;  expr({call,Line,{remote,Lr,M,F},As0}, St0) ->      {[M1,F1 | As1],St1} = expr_list([M,F | As0], St0), @@ -469,7 +457,7 @@ strict_record_access(E0, St0) ->  conj([], _E) ->      empty;  conj([{{Name,_Rp},L,R,Sz} | AL], E) -> -    NL = neg_line(L), +    NL = no_compiler_warning(L),      T1 = {op,NL,'orelse',            {call,NL,  	   {remote,NL,{atom,NL,erlang},{atom,NL,is_record}}, @@ -585,8 +573,8 @@ strict_get_record_field(Line, R, {atom,_,F}=Index, Name, St0) ->              Fs = record_fields(Name, St),              I = index_expr(F, Fs, 2),              P = record_pattern(2, I, Var, length(Fs)+1, Line, [{atom,Line,Name}]), -            NLine = neg_line(Line), -            RLine = record_offset(NLine, St), +            NLine = no_compiler_warning(Line), +            RLine = mark_record(NLine, St),  	    E = {'case',NLine,R,  		     [{clause,NLine,[{tuple,RLine,P}],[],[Var]},  		      {clause,NLine,[{var,NLine,'_'}],[], @@ -600,7 +588,8 @@ strict_get_record_field(Line, R, {atom,_,F}=Index, Name, St0) ->              I = index_expr(Line, Index, Name, Fs),              {ExpR,St1}  = expr(R, St0),              %% Just to make comparison simple: -            ExpRp = erl_lint:modify_line(ExpR, fun(_L) -> 0 end), +            A0 = erl_anno:new(0), +            ExpRp = erl_parse:map_anno(fun(_A) -> A0 end, ExpR),              RA = {{Name,ExpRp},Line,ExpR,length(Fs)+1},              St2 = St1#exprec{strict_ra = [RA | St1#exprec.strict_ra]},              {{call,Line, @@ -701,8 +690,8 @@ record_update(R, Name, Fs, Us0, St0) ->  record_match(R, Name, Lr, Fs, Us, St0) ->      {Ps,News,St1} = record_upd_fs(Fs, Us, St0), -    NLr = neg_line(Lr), -    RLine = record_offset(Lr, St1), +    NLr = no_compiler_warning(Lr), +    RLine = mark_record(Lr, St1),      {{'case',Lr,R,        [{clause,Lr,[{tuple,RLine,[{atom,Lr,Name} | Ps]}],[],          [{tuple,RLine,[{atom,Lr,Name} | News]}]}, @@ -733,8 +722,8 @@ record_setel(R, Name, Fs, Us0) ->      Us = [T || {_,T} <- Us2],      Lr = element(2, hd(Us)),      Wildcards = duplicate(length(Fs), {var,Lr,'_'}), -    NLr = neg_line(Lr), -    %% Note: calling record_offset() here is not necessary since it is +    NLr = no_compiler_warning(Lr), +    %% Note: calling mark_record() here is not necessary since it is      %% targeted at Dialyzer which always calls the compiler with      %% 'strict_record_updates' meaning that record_setel() will never      %% be called. @@ -832,10 +821,7 @@ add_imports(Mod, [F | Fs], Is) ->  add_imports(_, [], Is) -> Is.  imported(F, A, St) -> -    case orddict:find({F,A}, St#exprec.imports) of -        {ok,Mod} -> {yes,Mod}; -        error -> no -    end. +    orddict:is_key({F,A}, St#exprec.imports).  %%%  %%% Replace is_record/3 in guards with matching if possible. @@ -969,12 +955,11 @@ opt_remove_2({call,Line,{atom,_,is_record},      end;  opt_remove_2(A, _) -> A. -neg_line(L) -> -    erl_parse:set_line(L, fun(Line) -> -abs(Line) end). +no_compiler_warning(Anno) -> +    erl_anno:set_generated(true, Anno). -record_offset(L, St) -> +mark_record(Anno, St) ->      case lists:member(dialyzer, St#exprec.compile) of -        true when L >= 0 -> L+?REC_OFFSET; -        true when L < 0  -> L-?REC_OFFSET; -        false -> L +        true -> erl_anno:set_record(true, Anno); +        false -> Anno      end. diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index cbe6eeec3c..821d81a6b4 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -2,7 +2,7 @@  %%  %% %CopyrightBegin%  %% -%% Copyright Ericsson AB 1996-2014. All Rights Reserved. +%% Copyright Ericsson AB 1996-2015. All Rights Reserved.  %%  %% The contents of this file are subject to the Erlang Public License,  %% Version 1.1, (the "License"); you may not use this file except in @@ -34,6 +34,8 @@  -import(lists, [member/2,map/2,foldl/3,foldr/3,mapfoldl/3,all/2,reverse/1]). +-deprecated([{modify_line, 2, next_major_release}]). +  %% bool_option(OnOpt, OffOpt, Default, Options) -> boolean().  %% value_option(Flag, Default, Options) -> Value.  %% value_option(Flag, Default, OnOpt, OnVal, OffOpt, OffVal, Options) -> @@ -76,7 +78,7 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) ->  %%-define(DEBUGF(X,Y), io:format(X, Y)).  -define(DEBUGF(X,Y), void). --type line() :: erl_scan:line().     % a convenient alias +-type line() :: erl_anno:line().     % a convenient alias  -type fa()   :: {atom(), arity()}.   % function+arity  -type ta()   :: {atom(), arity()}.   % type+arity @@ -111,7 +113,8 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) ->                 defined=gb_sets:empty()          %Defined fuctions                     :: gb_sets:set(fa()),  	       on_load=[] :: [fa()],		%On-load function -	       on_load_line=0 :: line(),	%Line for on_load +	       on_load_line=erl_anno:new(0)	%Line for on_load +                   :: erl_anno:anno(),  	       clashes=[],			%Exported functions named as BIFs                 not_deprecated=[],               %Not considered deprecated                 func=[],                         %Current function @@ -140,7 +143,7 @@ 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()}. +-type error_info() :: {erl_anno:line(), module(), error_description()}.  %% format_error(Error)  %%  Return a string describing the error. @@ -227,6 +230,8 @@ format_error({deprecated, MFA, ReplacementMFA, Rel}) ->  		  [format_mfa(MFA), Rel, format_mfa(ReplacementMFA)]);  format_error({deprecated, {M1, F1, A1}, String}) when is_list(String) ->      io_lib:format("~p:~p/~p: ~s", [M1, F1, A1, String]); +format_error({deprecated_type, {M1, F1, A1}, String}) when is_list(String) -> +    io_lib:format("~p:~p~s: ~s", [M1, F1, gen_type_paren(A1), String]);  format_error({removed, MFA, ReplacementMFA, Rel}) ->      io_lib:format("call to ~s will fail, since it was removed in ~s; "  		  "use ~s", [format_mfa(MFA), Rel, format_mfa(ReplacementMFA)]); @@ -425,13 +430,13 @@ exprs(Exprs, BindingsList) ->  exprs_opt(Exprs, BindingsList, Opts) ->      {St0,Vs} = foldl(fun({{record,_SequenceNumber,_Name},Attr0}, {St1,Vs1}) -> -                             Attr = zip_file_and_line(Attr0, "none"), +                             Attr = set_file(Attr0, "none"),  			     {attribute_state(Attr, St1),Vs1};                          ({V,_}, {St1,Vs1}) ->  			     {St1,[{V,{bound,unused,[]}} | Vs1]}  		     end, {start("nofile",Opts),[]}, BindingsList),      Vt = orddict:from_list(Vs), -    {_Evt,St} = exprs(zip_file_and_line(Exprs, "nofile"), Vt, St0), +    {_Evt,St} = exprs(set_file(Exprs, "nofile"), Vt, St0),      return_status(St).  used_vars(Exprs, BindingsList) -> @@ -439,7 +444,7 @@ used_vars(Exprs, BindingsList) ->  		  ({V,_Val}, Vs0) -> [{V,{bound,unused,[]}} | Vs0]  	       end, [], BindingsList),      Vt = orddict:from_list(Vs), -    {Evt,_St} = exprs(zip_file_and_line(Exprs, "nofile"), Vt, start()), +    {Evt,_St} = exprs(set_file(Exprs, "nofile"), Vt, start()),      {ok, foldl(fun({V,{_,used,_}}, L) -> [V | L];                    (_, L) -> L  	       end, [], Evt)}. @@ -605,8 +610,8 @@ pack_warnings(Ws) ->  add_error(E, St) -> St#lint{errors=[{St#lint.file,E}|St#lint.errors]}. -add_error(FileLine, E, St) -> -    {File,Location} = loc(FileLine), +add_error(Anno, E, St) -> +    {File,Location} = loc(Anno),      add_error({Location,erl_lint,E}, St#lint{file = File}).  add_warning(W, St) -> St#lint{warnings=[{St#lint.file,W}|St#lint.warnings]}. @@ -615,22 +620,19 @@ add_warning(FileLine, W, St) ->      {File,Location} = loc(FileLine),      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. +loc(Anno) -> +    File = erl_anno:file(Anno), +    Location = erl_anno:location(Anno), +    {File,Location}.  %% forms([Form], State) -> State'  forms(Forms0, St0) ->      Forms = eval_file_attribute(Forms0, St0), +    %% Annotations from now on include the 'file' item.      Locals = local_functions(Forms),      AutoImportSuppressed = auto_import_suppressed(St0#lint.compile),      StDeprecated = disallowed_compile_flags(Forms,St0), -    %% Line numbers are from now on pairs {File,Line}.      St1 = includes_qlc_hrl(Forms, StDeprecated#lint{locals = Locals,  						    no_auto = AutoImportSuppressed}),      St2 = bif_clashes(Forms, St1), @@ -666,15 +668,14 @@ eval_file_attribute(Forms, St) ->  eval_file_attr([{attribute,_L,file,{File,_Line}}=Form | Forms], _File) ->      [Form | eval_file_attr(Forms, File)];  eval_file_attr([Form0 | Forms], File) -> -    Form = zip_file_and_line(Form0, File), +    Form = set_file(Form0, File),      [Form | eval_file_attr(Forms, File)];  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, -    modify_line(T, F). +set_file(T, File) -> +    F = fun(Anno) -> erl_anno:set_file(File, Anno) end, +    erl_parse:map_anno(F, T).  %% form(Form, State) -> State'  %%  Check a form returning the updated State. Handle generic cases here. @@ -796,9 +797,11 @@ not_deprecated(Forms, St0) ->  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 ], +		    {attribute,A,compile,nowarn_bif_clash} <- Forms, +                   {_,L} <- [loc(A)] ],      Errors1 = [ {St0#lint.file,{L,erl_lint,disallowed_nowarn_bif_clash}} || -		    {attribute,[{line,{_,L}}],compile,{nowarn_bif_clash, {_,_}}} <- Forms ], +		    {attribute,A,compile,{nowarn_bif_clash, {_,_}}} <- Forms, +                   {_,L} <- [loc(A)] ],      Disabled = (not is_warn_enabled(bif_clash, St0)),      Errors = if  		   Disabled andalso Errors0 =:= [] -> @@ -1299,7 +1302,7 @@ imported(F, A, St) ->          error -> no      end. --spec on_load(line(), fa(), lint_state()) -> lint_state(). +-spec on_load(erl_anno:anno(), fa(), lint_state()) -> lint_state().  %%  Check an on_load directive and remember it.  on_load(Line, {Name,Arity}=Fa, #lint{on_load=OnLoad0}=St0) @@ -1954,10 +1957,10 @@ is_guard_test(E) ->  is_guard_test(Expression, Forms) ->      RecordAttributes = [A || A = {attribute, _, record, _D} <- Forms],      St0 = foldl(fun(Attr0, St1) -> -                        Attr = zip_file_and_line(Attr0, "none"), +                        Attr = set_file(Attr0, "none"),                          attribute_state(Attr, St1)                  end, start(), RecordAttributes), -    is_guard_test2(zip_file_and_line(Expression, "nofile"), St0#lint.records). +    is_guard_test2(set_file(Expression, "nofile"), St0#lint.records).  %% is_guard_test2(Expression, RecordDefs :: dict:dict()) -> boolean().  is_guard_test2({call,Line,{atom,Lr,record},[E,A]}, RDs) -> @@ -2619,7 +2622,7 @@ type_def(_Attr, _Line, {record, _RecName}, Fields, [], St0) ->      %% The record field names and such are checked in the record format.      %% We only need to check the types.      Types = [T || {typed_record_field, _, T} <- Fields], -    check_type({type, -1, product, Types}, St0); +    check_type({type, nowarn(), product, Types}, St0);  type_def(Attr, Line, TypeName, ProtoType, Args, St0) ->      TypeDefs = St0#lint.types,      Arity = length(Args), @@ -2628,7 +2631,7 @@ type_def(Attr, Line, TypeName, ProtoType, Args, St0) ->      StoreType =          fun(St) ->                  NewDefs = dict:store(TypePair, Info, TypeDefs), -                CheckType = {type, -1, product, [ProtoType|Args]}, +                CheckType = {type, nowarn(), product, [ProtoType|Args]},                  check_type(CheckType, St#lint{types=NewDefs})          end,      case is_default_type(TypePair) of @@ -2684,7 +2687,9 @@ check_type({ann_type, _L, [_Var, Type]}, SeenVars, St) ->  check_type({paren_type, _L, [Type]}, SeenVars, St) ->      check_type(Type, SeenVars, St);  check_type({remote_type, L, [{atom, _, Mod}, {atom, _, Name}, Args]}, -	   SeenVars, #lint{module=CurrentMod} = St) -> +	   SeenVars, St0) -> +    St = deprecated_type(L, Mod, Name, Args, St0), +    CurrentMod = St#lint.module,      case Mod =:= CurrentMod of  	true -> check_type({user_type, L, Name, Args}, SeenVars, St);  	false -> @@ -2712,7 +2717,7 @@ check_type({type, L, 'fun', [Dom, Range]}, SeenVars, St) ->  	    {type, _, any} -> St;  	    _ -> add_error(L, {type_syntax, 'fun'}, St)  	end, -    check_type({type, -1, product, [Dom, Range]}, SeenVars, St1); +    check_type({type, nowarn(), product, [Dom, Range]}, SeenVars, St1);  check_type({type, L, range, [From, To]}, SeenVars, St) ->      St1 =  	case {erl_eval:partial_eval(From), erl_eval:partial_eval(To)} of @@ -2729,7 +2734,7 @@ check_type({type, _L, map, Pairs}, SeenVars, St) ->  			check_type(Pair, AccSeenVars, AccSt)  		end, {SeenVars, St}, Pairs);  check_type({type, _L, map_field_assoc, [Dom, Range]}, SeenVars, St) -> -    check_type({type, -1, product, [Dom, Range]}, SeenVars, St); +    check_type({type, nowarn(), product, [Dom, Range]}, SeenVars, St);  check_type({type, _L, tuple, any}, SeenVars, St) -> {SeenVars, St};  check_type({type, _L, any}, SeenVars, St) -> {SeenVars, St};  check_type({type, L, binary, [Base, Unit]}, SeenVars, St) -> @@ -2772,7 +2777,7 @@ check_type({type, La, TypeName, Args}, SeenVars, St) ->                  end;              _ -> St          end, -    check_type({type, -1, product, Args}, SeenVars, St1); +    check_type({type, nowarn(), product, Args}, SeenVars, St1);  check_type({user_type, L, TypeName, Args}, SeenVars, St) ->      Arity = length(Args),      TypePair = {TypeName, Arity}, @@ -2919,11 +2924,16 @@ check_specs([FunType|Left], Arity, St0) ->  	      true -> St0;  	      false -> add_error(L, spec_wrong_arity, St0)  	  end, -    St2 = check_type({type, -1, product, [FunType1|CTypes]}, St1), +    St2 = check_type({type, nowarn(), product, [FunType1|CTypes]}, St1),      check_specs(Left, Arity, St2);  check_specs([], _Arity, St) ->      St. +nowarn() -> +    A0 = erl_anno:new(0), +    A1 = erl_anno:set_generated(true, A0), +    erl_anno:set_file("", A1). +  check_specs_without_function(#lint{module=Mod,defined=Funcs,specs=Specs}=St) ->      Fun = fun({M, F, A}, Line, AccSt) when M =:= Mod ->                    FA = {F, A}, @@ -3452,58 +3462,15 @@ vt_no_unused(Vt) -> [V || {_,{_,U,_L}}=V <- Vt, U =/= unused].  %% copy_expr(Expr, Line) -> Expr.  %%  Make a copy of Expr converting all line numbers to Line. -copy_expr(Expr, Line) -> -    modify_line(Expr, fun(_L) -> Line end). +copy_expr(Expr, Anno) -> +    erl_parse:map_anno(fun(_A) -> Anno end, Expr).  %% modify_line(Form, Fun) -> Form  %% modify_line(Expression, Fun) -> Expression  %%  Applies Fun to each line number occurrence.  modify_line(T, F0) -> -    modify_line1(T, F0). - -%% Forms. -modify_line1({function,F,A}, _Mf) -> {function,F,A}; -modify_line1({function,M,F,A}, Mf) -> -    {function,modify_line1(M, Mf),modify_line1(F, Mf),modify_line1(A, Mf)}; -modify_line1({attribute,L,record,{Name,Fields}}, Mf) -> -    {attribute,Mf(L),record,{Name,modify_line1(Fields, Mf)}}; -modify_line1({attribute,L,spec,{Fun,Types}}, Mf) -> -    {attribute,Mf(L),spec,{Fun,modify_line1(Types, Mf)}}; -modify_line1({attribute,L,callback,{Fun,Types}}, Mf) -> -    {attribute,Mf(L),callback,{Fun,modify_line1(Types, Mf)}}; -modify_line1({attribute,L,type,{TypeName,TypeDef,Args}}, Mf) -> -    {attribute,Mf(L),type,{TypeName,modify_line1(TypeDef, Mf), -			   modify_line1(Args, Mf)}}; -modify_line1({attribute,L,opaque,{TypeName,TypeDef,Args}}, Mf) -> -    {attribute,Mf(L),opaque,{TypeName,modify_line1(TypeDef, Mf), -                             modify_line1(Args, Mf)}}; -modify_line1({attribute,L,Attr,Val}, Mf) -> {attribute,Mf(L),Attr,Val}; -modify_line1({warning,W}, _Mf) -> {warning,W}; -modify_line1({error,W}, _Mf) -> {error,W}; -%% Expressions. -modify_line1({clauses,Cs}, Mf) -> {clauses,modify_line1(Cs, Mf)}; -modify_line1({typed_record_field,Field,Type}, Mf) -> -    {typed_record_field,modify_line1(Field, Mf),modify_line1(Type, Mf)}; -modify_line1({Tag,L}, Mf) -> {Tag,Mf(L)}; -modify_line1({Tag,L,E1}, Mf) -> -    {Tag,Mf(L),modify_line1(E1, Mf)}; -modify_line1({Tag,L,E1,E2}, Mf) -> -    {Tag,Mf(L),modify_line1(E1, Mf),modify_line1(E2, Mf)}; -modify_line1({bin_element,L,E1,E2,TSL}, Mf) -> -    {bin_element,Mf(L),modify_line1(E1, Mf),modify_line1(E2, Mf), TSL}; -modify_line1({Tag,L,E1,E2,E3}, Mf) -> -    {Tag,Mf(L),modify_line1(E1, Mf),modify_line1(E2, Mf),modify_line1(E3, Mf)}; -modify_line1({Tag,L,E1,E2,E3,E4}, Mf) -> -    {Tag,Mf(L), -     modify_line1(E1, Mf), -     modify_line1(E2, Mf), -     modify_line1(E3, Mf), -     modify_line1(E4, Mf)}; -modify_line1([H|T], Mf) -> -    [modify_line1(H, Mf)|modify_line1(T, Mf)]; -modify_line1([], _Mf) -> []; -modify_line1(E, _Mf) when not is_tuple(E), not is_list(E) -> E. +    erl_parse:map_anno(F0, T).  %% Check a record_info call. We have already checked that it is not  %% shadowed by an import. @@ -3573,6 +3540,20 @@ deprecated_function(Line, M, F, As, St) ->  	    St      end. +deprecated_type(L, M, N, As, St) -> +    NAs = length(As), +    case otp_internal:obsolete_type(M, N, NAs) of +        {deprecated, String} when is_list(String) -> +            case is_warn_enabled(deprecated_type, St) of +                true -> +                    add_warning(L, {deprecated_type, {M,N,NAs}, String}, St); +                false -> +                    St +            end; +        no -> +            St +    end. +  obsolete_guard({call,Line,{atom,Lr,F},As}, St0) ->      Arity = length(As),      case erl_internal:old_type_test(F, Arity) of diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl index 3502a50eaa..e328e065e3 100644 --- a/lib/stdlib/src/erl_parse.yrl +++ b/lib/stdlib/src/erl_parse.yrl @@ -2,7 +2,7 @@  %%  %% %CopyrightBegin%  %% -%% Copyright Ericsson AB 1996-2014. All Rights Reserved. +%% Copyright Ericsson AB 1996-2015. All Rights Reserved.  %%  %% The contents of this file are subject to the Erlang Public License,  %% Version 1.1, (the "License"); you may not use this file except in @@ -92,7 +92,7 @@ spec_fun -> atom ':' atom '/' integer '::' : {'$1', '$3', '$5'}.  typed_attr_val -> expr ',' typed_record_fields : {typed_record, '$1', '$3'}.  typed_attr_val -> expr '::' top_type           : {type_def, '$1', '$3'}. -typed_record_fields -> '{' typed_exprs '}' : {tuple, ?line('$1'), '$2'}. +typed_record_fields -> '{' typed_exprs '}' : {tuple, ?anno('$1'), '$2'}.  typed_exprs -> typed_expr                 : ['$1'].  typed_exprs -> typed_expr ',' typed_exprs : ['$1'|'$3']. @@ -105,26 +105,26 @@ type_sigs -> type_sig                     : ['$1'].  type_sigs -> type_sig ';' type_sigs       : ['$1'|'$3'].  type_sig -> fun_type                      : '$1'. -type_sig -> fun_type 'when' type_guards   : {type, ?line('$1'), bounded_fun, +type_sig -> fun_type 'when' type_guards   : {type, ?anno('$1'), bounded_fun,                                               ['$1','$3']}.  type_guards -> type_guard                 : ['$1'].  type_guards -> type_guard ',' type_guards : ['$1'|'$3']. -type_guard -> atom '(' top_types ')'      : {type, ?line('$1'), constraint, +type_guard -> atom '(' top_types ')'      : {type, ?anno('$1'), constraint,                                               ['$1', '$3']}.  type_guard -> var '::' top_type           : build_def('$1', '$3').  top_types -> top_type                     : ['$1'].  top_types -> top_type ',' top_types       : ['$1'|'$3']. -top_type -> var '::' top_type_100         : {ann_type, ?line('$1'), ['$1','$3']}. +top_type -> var '::' top_type_100         : {ann_type, ?anno('$1'), ['$1','$3']}.  top_type -> top_type_100                  : '$1'.  top_type_100 -> type_200                  : '$1'.  top_type_100 -> type_200 '|' top_type_100 : lift_unions('$1','$3'). -type_200 -> type_300 '..' type_300        : {type, ?line('$1'), range, +type_200 -> type_300 '..' type_300        : {type, ?anno('$1'), range,                                               [skip_paren('$1'),                                                skip_paren('$3')]}.  type_200 -> type_300                      : '$1'. @@ -140,61 +140,61 @@ type_400 -> type_500                      : '$1'.  type_500 -> prefix_op type                : ?mkop1('$1', skip_paren('$2')).  type_500 -> type                          : '$1'. -type -> '(' top_type ')'                  : {paren_type, ?line('$2'), ['$2']}. +type -> '(' top_type ')'                  : {paren_type, ?anno('$2'), ['$2']}.  type -> var                               : '$1'.  type -> atom                              : '$1'.  type -> atom '(' ')'                      : build_gen_type('$1').  type -> atom '(' top_types ')'            : build_type('$1', '$3'). -type -> atom ':' atom '(' ')'             : {remote_type, ?line('$1'), +type -> atom ':' atom '(' ')'             : {remote_type, ?anno('$1'),                                               ['$1', '$3', []]}. -type -> atom ':' atom '(' top_types ')'   : {remote_type, ?line('$1'), +type -> atom ':' atom '(' top_types ')'   : {remote_type, ?anno('$1'),                                               ['$1', '$3', '$5']}. -type -> '[' ']'                           : {type, ?line('$1'), nil, []}. -type -> '[' top_type ']'                  : {type, ?line('$1'), list, ['$2']}. -type -> '[' top_type ',' '...' ']'        : {type, ?line('$1'), +type -> '[' ']'                           : {type, ?anno('$1'), nil, []}. +type -> '[' top_type ']'                  : {type, ?anno('$1'), list, ['$2']}. +type -> '[' top_type ',' '...' ']'        : {type, ?anno('$1'),                                               nonempty_list, ['$2']}. -type -> '#' '{' '}'                       : {type, ?line('$1'), map, []}. -type -> '#' '{' map_pair_types '}'        : {type, ?line('$1'), map, '$3'}. -type -> '{' '}'                           : {type, ?line('$1'), tuple, []}. -type -> '{' top_types '}'                 : {type, ?line('$1'), tuple, '$2'}. -type -> '#' atom '{' '}'                  : {type, ?line('$1'), record, ['$2']}. -type -> '#' atom '{' field_types '}'      : {type, ?line('$1'), +type -> '#' '{' '}'                       : {type, ?anno('$1'), map, []}. +type -> '#' '{' map_pair_types '}'        : {type, ?anno('$1'), map, '$3'}. +type -> '{' '}'                           : {type, ?anno('$1'), tuple, []}. +type -> '{' top_types '}'                 : {type, ?anno('$1'), tuple, '$2'}. +type -> '#' atom '{' '}'                  : {type, ?anno('$1'), record, ['$2']}. +type -> '#' atom '{' field_types '}'      : {type, ?anno('$1'),                                               record, ['$2'|'$4']}.  type -> binary_type                       : '$1'.  type -> integer                           : '$1'. -type -> 'fun' '(' ')'                     : {type, ?line('$1'), 'fun', []}. +type -> 'fun' '(' ')'                     : {type, ?anno('$1'), 'fun', []}.  type -> 'fun' '(' fun_type_100 ')'        : '$3'.  fun_type_100 -> '(' '...' ')' '->' top_type -                                          : {type, ?line('$1'), 'fun', -                                             [{type, ?line('$1'), any}, '$5']}. +                                          : {type, ?anno('$1'), 'fun', +                                             [{type, ?anno('$1'), any}, '$5']}.  fun_type_100 -> fun_type                  : '$1'. -fun_type -> '(' ')' '->' top_type  : {type, ?line('$1'), 'fun', -                                      [{type, ?line('$1'), product, []}, '$4']}. +fun_type -> '(' ')' '->' top_type  : {type, ?anno('$1'), 'fun', +                                      [{type, ?anno('$1'), product, []}, '$4']}.  fun_type -> '(' top_types ')' '->' top_type -                                   : {type, ?line('$1'), 'fun', -                                      [{type, ?line('$1'), product, '$2'},'$5']}. +                                   : {type, ?anno('$1'), 'fun', +                                      [{type, ?anno('$1'), product, '$2'},'$5']}.  map_pair_types -> map_pair_type                    : ['$1'].  map_pair_types -> map_pair_type ',' map_pair_types : ['$1'|'$3']. -map_pair_type  -> top_type '=>' top_type           : {type, ?line('$2'), map_field_assoc,['$1','$3']}. +map_pair_type  -> top_type '=>' top_type           : {type, ?anno('$2'), map_field_assoc,['$1','$3']}.  field_types -> field_type                 : ['$1'].  field_types -> field_type ',' field_types : ['$1'|'$3']. -field_type -> atom '::' top_type          : {type, ?line('$1'), field_type, +field_type -> atom '::' top_type          : {type, ?anno('$1'), field_type,                                               ['$1', '$3']}. -binary_type -> '<<' '>>'                  : {type, ?line('$1'),binary, -					     [abstract(0, ?line('$1')), -					      abstract(0, ?line('$1'))]}. -binary_type -> '<<' bin_base_type '>>'    : {type, ?line('$1'),binary, -					     ['$2', abstract(0, ?line('$1'))]}. -binary_type -> '<<' bin_unit_type '>>'    : {type, ?line('$1'),binary, -                                             [abstract(0, ?line('$1')), '$2']}. +binary_type -> '<<' '>>'                  : {type, ?anno('$1'),binary, +					     [abstract2(0, ?anno('$1')), +					      abstract2(0, ?anno('$1'))]}. +binary_type -> '<<' bin_base_type '>>'    : {type, ?anno('$1'),binary, +					     ['$2', abstract2(0, ?anno('$1'))]}. +binary_type -> '<<' bin_unit_type '>>'    : {type, ?anno('$1'),binary, +                                             [abstract2(0, ?anno('$1')), '$2']}.  binary_type -> '<<' bin_base_type ',' bin_unit_type '>>' -                                    : {type, ?line('$1'), binary, ['$2', '$4']}. +                                    : {type, ?anno('$1'), binary, ['$2', '$4']}.  bin_base_type -> var ':' type          : build_bin_type(['$1'], '$3'). @@ -210,7 +210,7 @@ function_clauses -> function_clause : ['$1'].  function_clauses -> function_clause ';' function_clauses : ['$1'|'$3'].  function_clause -> atom clause_args clause_guard clause_body : -	{clause,?line('$1'),element(3, '$1'),'$2','$3','$4'}. +	{clause,?anno('$1'),element(3, '$1'),'$2','$3','$4'}.  clause_args -> argument_list : element(1, '$1'). @@ -221,10 +221,10 @@ clause_guard -> '$empty' : [].  clause_body -> '->' exprs: '$2'. -expr -> 'catch' expr : {'catch',?line('$1'),'$2'}. +expr -> 'catch' expr : {'catch',?anno('$1'),'$2'}.  expr -> expr_100 : '$1'. -expr_100 -> expr_150 '=' expr_100 : {match,?line('$2'),'$1','$3'}. +expr_100 -> expr_150 '=' expr_100 : {match,?anno('$2'),'$1','$3'}.  expr_100 -> expr_150 '!' expr_100 : ?mkop2('$1', '$2', '$3').  expr_100 -> expr_150 : '$1'. @@ -260,7 +260,7 @@ expr_700 -> record_expr : '$1'.  expr_700 -> expr_800 : '$1'.  expr_800 -> expr_max ':' expr_max : -	{remote,?line('$2'),'$1','$3'}. +	{remote,?anno('$2'),'$1','$3'}.  expr_800 -> expr_max : '$1'.  expr_max -> var : '$1'. @@ -272,7 +272,7 @@ expr_max -> binary_comprehension : '$1'.  expr_max -> tuple : '$1'.  %%expr_max -> struct : '$1'.  expr_max -> '(' expr ')' : '$2'. -expr_max -> 'begin' exprs 'end' : {block,?line('$1'),'$2'}. +expr_max -> 'begin' exprs 'end' : {block,?anno('$1'),'$2'}.  expr_max -> if_expr : '$1'.  expr_max -> case_expr : '$1'.  expr_max -> receive_expr : '$1'. @@ -280,22 +280,22 @@ expr_max -> fun_expr : '$1'.  expr_max -> try_expr : '$1'. -list -> '[' ']' : {nil,?line('$1')}. -list -> '[' expr tail : {cons,?line('$1'),'$2','$3'}. +list -> '[' ']' : {nil,?anno('$1')}. +list -> '[' expr tail : {cons,?anno('$1'),'$2','$3'}. -tail -> ']' : {nil,?line('$1')}. +tail -> ']' : {nil,?anno('$1')}.  tail -> '|' expr ']' : '$2'. -tail -> ',' expr tail : {cons,?line('$2'),'$2','$3'}. +tail -> ',' expr tail : {cons,?anno('$2'),'$2','$3'}. -binary -> '<<' '>>' : {bin,?line('$1'),[]}. -binary -> '<<' bin_elements '>>' : {bin,?line('$1'),'$2'}. +binary -> '<<' '>>' : {bin,?anno('$1'),[]}. +binary -> '<<' bin_elements '>>' : {bin,?anno('$1'),'$2'}.  bin_elements -> bin_element : ['$1'].  bin_elements -> bin_element ',' bin_elements : ['$1'|'$3'].  bin_element -> bit_expr opt_bit_size_expr opt_bit_type_list : -	{bin_element,?line('$1'),'$1','$2','$3'}. +	{bin_element,?anno('$1'),'$1','$2','$3'}.  bit_expr -> prefix_op expr_max : ?mkop1('$1', '$2').  bit_expr -> expr_max : '$1'. @@ -316,29 +316,29 @@ bit_size_expr -> expr_max : '$1'.  list_comprehension -> '[' expr '||' lc_exprs ']' : -	{lc,?line('$1'),'$2','$4'}. +	{lc,?anno('$1'),'$2','$4'}.  binary_comprehension -> '<<' binary '||' lc_exprs '>>' : -	{bc,?line('$1'),'$2','$4'}. +	{bc,?anno('$1'),'$2','$4'}.  lc_exprs -> lc_expr : ['$1'].  lc_exprs -> lc_expr ',' lc_exprs : ['$1'|'$3'].  lc_expr -> expr : '$1'. -lc_expr -> expr '<-' expr : {generate,?line('$2'),'$1','$3'}. -lc_expr -> binary '<=' expr : {b_generate,?line('$2'),'$1','$3'}. +lc_expr -> expr '<-' expr : {generate,?anno('$2'),'$1','$3'}. +lc_expr -> binary '<=' expr : {b_generate,?anno('$2'),'$1','$3'}. -tuple -> '{' '}' : {tuple,?line('$1'),[]}. -tuple -> '{' exprs '}' : {tuple,?line('$1'),'$2'}. +tuple -> '{' '}' : {tuple,?anno('$1'),[]}. +tuple -> '{' exprs '}' : {tuple,?anno('$1'),'$2'}.  %%struct -> atom tuple : -%%	{struct,?line('$1'),element(3, '$1'),element(3, '$2')}. +%%	{struct,?anno('$1'),element(3, '$1'),element(3, '$2')}.  map_expr -> '#' map_tuple : -	{map, ?line('$1'),'$2'}. +	{map, ?anno('$1'),'$2'}.  map_expr -> expr_max '#' map_tuple : -	{map, ?line('$2'),'$1','$3'}. +	{map, ?anno('$2'),'$1','$3'}.  map_expr -> map_expr '#' map_tuple : -	{map, ?line('$2'),'$1','$3'}. +	{map, ?anno('$2'),'$1','$3'}.  map_tuple -> '{' '}' : [].  map_tuple -> '{' map_fields '}' : '$2'. @@ -350,10 +350,10 @@ map_field -> map_field_assoc : '$1'.  map_field -> map_field_exact : '$1'.  map_field_assoc -> map_key '=>' expr : -	{map_field_assoc,?line('$1'),'$1','$3'}. +	{map_field_assoc,?anno('$1'),'$1','$3'}.  map_field_exact -> map_key ':=' expr : -	{map_field_exact,?line('$1'),'$1','$3'}. +	{map_field_exact,?anno('$1'),'$1','$3'}.  map_key -> expr : '$1'. @@ -363,17 +363,17 @@ map_key -> expr : '$1'.  %% always atoms for the moment, this might change in the future.  record_expr -> '#' atom '.' atom : -	{record_index,?line('$1'),element(3, '$2'),'$4'}. +	{record_index,?anno('$1'),element(3, '$2'),'$4'}.  record_expr -> '#' atom record_tuple : -	{record,?line('$1'),element(3, '$2'),'$3'}. +	{record,?anno('$1'),element(3, '$2'),'$3'}.  record_expr -> expr_max '#' atom '.' atom : -	{record_field,?line('$2'),'$1',element(3, '$3'),'$5'}. +	{record_field,?anno('$2'),'$1',element(3, '$3'),'$5'}.  record_expr -> expr_max '#' atom record_tuple : -	{record,?line('$2'),'$1',element(3, '$3'),'$4'}. +	{record,?anno('$2'),'$1',element(3, '$3'),'$4'}.  record_expr -> record_expr '#' atom '.' atom : -	{record_field,?line('$2'),'$1',element(3, '$3'),'$5'}. +	{record_field,?anno('$2'),'$1',element(3, '$3'),'$5'}.  record_expr -> record_expr '#' atom record_tuple : -	{record,?line('$2'),'$1',element(3, '$3'),'$4'}. +	{record,?anno('$2'),'$1',element(3, '$3'),'$4'}.  record_tuple -> '{' '}' : [].  record_tuple -> '{' record_fields '}' : '$2'. @@ -381,47 +381,47 @@ record_tuple -> '{' record_fields '}' : '$2'.  record_fields -> record_field : ['$1'].  record_fields -> record_field ',' record_fields : ['$1' | '$3']. -record_field -> var '=' expr : {record_field,?line('$1'),'$1','$3'}. -record_field -> atom '=' expr : {record_field,?line('$1'),'$1','$3'}. +record_field -> var '=' expr : {record_field,?anno('$1'),'$1','$3'}. +record_field -> atom '=' expr : {record_field,?anno('$1'),'$1','$3'}.  %% N.B. This is called from expr_700.  function_call -> expr_800 argument_list : -	{call,?line('$1'),'$1',element(1, '$2')}. +	{call,?anno('$1'),'$1',element(1, '$2')}. -if_expr -> 'if' if_clauses 'end' : {'if',?line('$1'),'$2'}. +if_expr -> 'if' if_clauses 'end' : {'if',?anno('$1'),'$2'}.  if_clauses -> if_clause : ['$1'].  if_clauses -> if_clause ';' if_clauses : ['$1' | '$3'].  if_clause -> guard clause_body : -	{clause,?line(hd(hd('$1'))),[],'$1','$2'}. +	{clause,?anno(hd(hd('$1'))),[],'$1','$2'}.  case_expr -> 'case' expr 'of' cr_clauses 'end' : -	{'case',?line('$1'),'$2','$4'}. +	{'case',?anno('$1'),'$2','$4'}.  cr_clauses -> cr_clause : ['$1'].  cr_clauses -> cr_clause ';' cr_clauses : ['$1' | '$3'].  cr_clause -> expr clause_guard clause_body : -	{clause,?line('$1'),['$1'],'$2','$3'}. +	{clause,?anno('$1'),['$1'],'$2','$3'}.  receive_expr -> 'receive' cr_clauses 'end' : -	{'receive',?line('$1'),'$2'}. +	{'receive',?anno('$1'),'$2'}.  receive_expr -> 'receive' 'after' expr clause_body 'end' : -	{'receive',?line('$1'),[],'$3','$4'}. +	{'receive',?anno('$1'),[],'$3','$4'}.  receive_expr -> 'receive' cr_clauses 'after' expr clause_body 'end' : -	{'receive',?line('$1'),'$2','$4','$5'}. +	{'receive',?anno('$1'),'$2','$4','$5'}.  fun_expr -> 'fun' atom '/' integer : -	{'fun',?line('$1'),{function,element(3, '$2'),element(3, '$4')}}. +	{'fun',?anno('$1'),{function,element(3, '$2'),element(3, '$4')}}.  fun_expr -> 'fun' atom_or_var ':' atom_or_var '/' integer_or_var : -	{'fun',?line('$1'),{function,'$2','$4','$6'}}. +	{'fun',?anno('$1'),{function,'$2','$4','$6'}}.  fun_expr -> 'fun' fun_clauses 'end' : -	build_fun(?line('$1'), '$2'). +	build_fun(?anno('$1'), '$2').  atom_or_var -> atom : '$1'.  atom_or_var -> var : '$1'. @@ -433,16 +433,16 @@ fun_clauses -> fun_clause : ['$1'].  fun_clauses -> fun_clause ';' fun_clauses : ['$1' | '$3'].  fun_clause -> argument_list clause_guard clause_body : -	{Args,Pos} = '$1', -	{clause,Pos,'fun',Args,'$2','$3'}. +	{Args,Anno} = '$1', +	{clause,Anno,'fun',Args,'$2','$3'}.  fun_clause -> var argument_list clause_guard clause_body :  	{clause,element(2, '$1'),element(3, '$1'),element(1, '$2'),'$3','$4'}.  try_expr -> 'try' exprs 'of' cr_clauses try_catch : -	build_try(?line('$1'),'$2','$4','$5'). +	build_try(?anno('$1'),'$2','$4','$5').  try_expr -> 'try' exprs try_catch : -	build_try(?line('$1'),'$2',[],'$3'). +	build_try(?anno('$1'),'$2',[],'$3').  try_catch -> 'catch' try_clauses 'end' :  	{'$2',[]}. @@ -455,18 +455,18 @@ try_clauses -> try_clause : ['$1'].  try_clauses -> try_clause ';' try_clauses : ['$1' | '$3'].  try_clause -> expr clause_guard clause_body : -	L = ?line('$1'), -	{clause,L,[{tuple,L,[{atom,L,throw},'$1',{var,L,'_'}]}],'$2','$3'}. +	A = ?anno('$1'), +	{clause,A,[{tuple,A,[{atom,A,throw},'$1',{var,A,'_'}]}],'$2','$3'}.  try_clause -> atom ':' expr clause_guard clause_body : -	L = ?line('$1'), -	{clause,L,[{tuple,L,['$1','$3',{var,L,'_'}]}],'$4','$5'}. +	A = ?anno('$1'), +	{clause,A,[{tuple,A,['$1','$3',{var,A,'_'}]}],'$4','$5'}.  try_clause -> var ':' expr clause_guard clause_body : -	L = ?line('$1'), -	{clause,L,[{tuple,L,['$1','$3',{var,L,'_'}]}],'$4','$5'}. +	A = ?anno('$1'), +	{clause,A,[{tuple,A,['$1','$3',{var,A,'_'}]}],'$4','$5'}. -argument_list -> '(' ')' : {[],?line('$1')}. -argument_list -> '(' exprs ')' : {'$2',?line('$1')}. +argument_list -> '(' ')' : {[],?anno('$1')}. +argument_list -> '(' exprs ')' : {'$2',?anno('$1')}.  exprs -> expr : ['$1']. @@ -483,7 +483,7 @@ atomic -> strings : '$1'.  strings -> string : '$1'.  strings -> string strings : -	{string,?line('$1'),element(3, '$1') ++ element(3, '$2')}. +	{string,?anno('$1'),element(3, '$1') ++ element(3, '$2')}.  prefix_op -> '+' : '$1'.  prefix_op -> '-' : '$1'. @@ -524,8 +524,14 @@ Erlang code.  -export([normalise/1,abstract/1,tokens/1,tokens/2]).  -export([abstract/2]).  -export([inop_prec/1,preop_prec/1,func_prec/0,max_prec/0]). +-export([map_anno/2, fold_anno/3, mapfold_anno/3, +         new_anno/1, anno_to_term/1, anno_from_term/1]).  -export([set_line/2,get_attribute/2,get_attributes/1]). +-deprecated([{set_line, 2, next_major_release}, +             {get_attribute, 2, next_major_release}, +             {get_attributes, 1, next_major_release}]). +  %% The following directive is needed for (significantly) faster compilation  %% of the generated .erl file by the HiPE compiler.  Please do not remove.  -compile([{hipe,[{regalloc,linear_scan}]}]). @@ -533,30 +539,31 @@ Erlang code.  -export_type([abstract_clause/0, abstract_expr/0, abstract_form/0,                error_info/0]). +%% XXX. To be refined.  -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_anno:line(), module(), error_description()}.  -type token() :: erl_scan:token(). -%% mkop(Op, Arg) -> {op,Line,Op,Arg}. -%% mkop(Left, Op, Right) -> {op,Line,Op,Left,Right}. +%% mkop(Op, Arg) -> {op,Anno,Op,Arg}. +%% mkop(Left, Op, Right) -> {op,Anno,Op,Left,Right}. --define(mkop2(L, OpPos, R), +-define(mkop2(L, OpAnno, R),          begin -            {Op,Pos} = OpPos, -            {op,Pos,Op,L,R} +            {Op,Anno} = OpAnno, +            {op,Anno,Op,L,R}          end). --define(mkop1(OpPos, A), +-define(mkop1(OpAnno, A),          begin -            {Op,Pos} = OpPos, -            {op,Pos,Op,A} +            {Op,Anno} = OpAnno, +            {op,Anno,Op,A}          end). -%% keep track of line info in tokens --define(line(Tup), element(2, Tup)). +%% keep track of annotation info in tokens +-define(anno(Tup), element(2, Tup)).  %% Entry points compatible to old erl_parse.  %% These really suck and are only here until Calle gets multiple @@ -566,10 +573,10 @@ Erlang code.        Tokens :: [token()],        AbsForm :: abstract_form(),        ErrorInfo :: error_info(). -parse_form([{'-',L1},{atom,L2,spec}|Tokens]) -> -    parse([{'-',L1},{'spec',L2}|Tokens]); -parse_form([{'-',L1},{atom,L2,callback}|Tokens]) -> -    parse([{'-',L1},{'callback',L2}|Tokens]); +parse_form([{'-',A1},{atom,A2,spec}|Tokens]) -> +    parse([{'-',A1},{'spec',A2}|Tokens]); +parse_form([{'-',A1},{atom,A2,callback}|Tokens]) -> +    parse([{'-',A1},{'callback',A2}|Tokens]);  parse_form(Tokens) ->      parse(Tokens). @@ -578,7 +585,8 @@ parse_form(Tokens) ->        ExprList :: [abstract_expr()],        ErrorInfo :: error_info().  parse_exprs(Tokens) -> -    case parse([{atom,0,f},{'(',0},{')',0},{'->',0}|Tokens]) of +    A = erl_anno:new(0), +    case parse([{atom,A,f},{'(',A},{')',A},{'->',A}|Tokens]) of  	{ok,{function,_Lf,f,0,[{clause,_Lc,[],[],Exprs}]}} ->  	    {ok,Exprs};  	{error,_} = Err -> Err @@ -589,42 +597,43 @@ parse_exprs(Tokens) ->        Term :: term(),        ErrorInfo :: error_info().  parse_term(Tokens) -> -    case parse([{atom,0,f},{'(',0},{')',0},{'->',0}|Tokens]) of -	{ok,{function,_Lf,f,0,[{clause,_Lc,[],[],[Expr]}]}} -> +    A = erl_anno:new(0), +    case parse([{atom,A,f},{'(',A},{')',A},{'->',A}|Tokens]) of +	{ok,{function,_Af,f,0,[{clause,_Ac,[],[],[Expr]}]}} ->  	    try normalise(Expr) of  		Term -> {ok,Term}  	    catch -		_:_R -> {error,{?line(Expr),?MODULE,"bad term"}} +		_:_R -> {error,{location(?anno(Expr)),?MODULE,"bad term"}}  	    end; -	{ok,{function,_Lf,f,0,[{clause,_Lc,[],[],[_E1,E2|_Es]}]}} -> -	    {error,{?line(E2),?MODULE,"bad term"}}; +	{ok,{function,_Af,f,A,[{clause,_Ac,[],[],[_E1,E2|_Es]}]}} -> +	    {error,{location(?anno(E2)),?MODULE,"bad term"}};  	{error,_} = Err -> Err      end.  -type attributes() :: 'export' | 'file' | 'import' | 'module'  		    | 'opaque' | 'record' | 'type'. -build_typed_attribute({atom,La,record}, -		      {typed_record, {atom,_Ln,RecordName}, RecTuple}) -> -    {attribute,La,record,{RecordName,record_tuple(RecTuple)}}; -build_typed_attribute({atom,La,Attr}, +build_typed_attribute({atom,Aa,record}, +		      {typed_record, {atom,_An,RecordName}, RecTuple}) -> +    {attribute,Aa,record,{RecordName,record_tuple(RecTuple)}}; +build_typed_attribute({atom,Aa,Attr},                        {type_def, {call,_,{atom,_,TypeName},Args}, Type})    when Attr =:= 'type' ; Attr =:= 'opaque' ->      case lists:all(fun({var, _, _}) -> true;                        (_)           -> false                     end, Args) of -        true -> {attribute,La,Attr,{TypeName,Type,Args}}; -        false -> error_bad_decl(La, Attr) +        true -> {attribute,Aa,Attr,{TypeName,Type,Args}}; +        false -> error_bad_decl(Aa, Attr)      end; -build_typed_attribute({atom,La,Attr},_) -> +build_typed_attribute({atom,Aa,Attr},_) ->      case Attr of -        record -> error_bad_decl(La, record); -        type   -> error_bad_decl(La, type); -	opaque -> error_bad_decl(La, opaque); -        _      -> ret_err(La, "bad attribute") +        record -> error_bad_decl(Aa, record); +        type   -> error_bad_decl(Aa, type); +	opaque -> error_bad_decl(Aa, opaque); +        _      -> ret_err(Aa, "bad attribute")      end. -build_type_spec({Kind,La}, {SpecFun, TypeSpecs}) +build_type_spec({Kind,Aa}, {SpecFun, TypeSpecs})    when (Kind =:= spec) or (Kind =:= callback) ->      NewSpecFun =  	case SpecFun of @@ -639,7 +648,7 @@ build_type_spec({Kind,La}, {SpecFun, TypeSpecs})  		%% Old style spec. Allow this for now.  		{Mod,Fun,Arity}  	    end, -    {attribute,La,Kind,{NewSpecFun, TypeSpecs}}. +    {attribute,Aa,Kind,{NewSpecFun, TypeSpecs}}.  find_arity_from_specs([Spec|_]) ->      %% Use the first spec to find the arity. If all are not the same, @@ -651,40 +660,40 @@ find_arity_from_specs([Spec|_]) ->      {type, _, 'fun', [{type, _, product, Args},_]} = Fun,      length(Args). -build_def({var, L, '_'}, _Types) -> -    ret_err(L, "bad type variable"); +build_def({var, A, '_'}, _Types) -> +    ret_err(A, "bad type variable");  build_def(LHS, Types) -> -    IsSubType = {atom, ?line(LHS), is_subtype}, -    {type, ?line(LHS), constraint, [IsSubType, [LHS, Types]]}. +    IsSubType = {atom, ?anno(LHS), is_subtype}, +    {type, ?anno(LHS), constraint, [IsSubType, [LHS, Types]]}. -lift_unions(T1, {type, _La, union, List}) -> -    {type, ?line(T1), union, [T1|List]}; +lift_unions(T1, {type, _Aa, union, List}) -> +    {type, ?anno(T1), union, [T1|List]};  lift_unions(T1, T2) -> -    {type, ?line(T1), union, [T1, T2]}. +    {type, ?anno(T1), union, [T1, T2]}. -skip_paren({paren_type,_L,[Type]}) -> +skip_paren({paren_type,_A,[Type]}) ->      skip_paren(Type);  skip_paren(Type) ->      Type. -build_gen_type({atom, La, tuple}) -> -    {type, La, tuple, any}; -build_gen_type({atom, La, map}) -> -    {type, La, map, any}; -build_gen_type({atom, La, Name}) -> +build_gen_type({atom, Aa, tuple}) -> +    {type, Aa, tuple, any}; +build_gen_type({atom, Aa, map}) -> +    {type, Aa, map, any}; +build_gen_type({atom, Aa, Name}) ->      Tag = type_tag(Name, 0), -    {Tag, La, Name, []}. +    {Tag, Aa, Name, []}.  build_bin_type([{var, _, '_'}|Left], Int) ->      build_bin_type(Left, Int);  build_bin_type([], Int) ->      skip_paren(Int); -build_bin_type([{var, La, _}|_], _) -> -    ret_err(La, "Bad binary type"). +build_bin_type([{var, Aa, _}|_], _) -> +    ret_err(Aa, "Bad binary type"). -build_type({atom, L, Name}, Types) -> +build_type({atom, A, Name}, Types) ->      Tag = type_tag(Name, length(Types)), -    {Tag, L, Name, Types}. +    {Tag, A, Name, Types}.  type_tag(TypeName, NumberOfTypeVariables) ->      case erl_internal:is_type(TypeName, NumberOfTypeVariables) of @@ -692,71 +701,75 @@ type_tag(TypeName, NumberOfTypeVariables) ->          false -> user_type      end. +abstract2(Term, Anno) -> +    Line = erl_anno:line(Anno), +    abstract(Term, Line). +  %% build_attribute(AttrName, AttrValue) -> -%%	{attribute,Line,module,Module} -%%	{attribute,Line,export,Exports} -%%	{attribute,Line,import,Imports} -%%	{attribute,Line,record,{Name,Inits}} -%%	{attribute,Line,file,{Name,Line}} -%%	{attribute,Line,Name,Val} - -build_attribute({atom,La,module}, Val) -> +%%	{attribute,Anno,module,Module} +%%	{attribute,Anno,export,Exports} +%%	{attribute,Anno,import,Imports} +%%	{attribute,Anno,record,{Name,Inits}} +%%	{attribute,Anno,file,{Name,Line}} +%%	{attribute,Anno,Name,Val} + +build_attribute({atom,Aa,module}, Val) ->      case Val of -	[{atom,_Lm,Module}] -> -	    {attribute,La,module,Module}; -	[{atom,_Lm,Module},ExpList] -> -	    {attribute,La,module,{Module,var_list(ExpList)}}; +	[{atom,_Am,Module}] -> +	    {attribute,Aa,module,Module}; +	[{atom,_Am,Module},ExpList] -> +	    {attribute,Aa,module,{Module,var_list(ExpList)}};  	_Other -> -	    error_bad_decl(La, module) +	    error_bad_decl(Aa, module)      end; -build_attribute({atom,La,export}, Val) -> +build_attribute({atom,Aa,export}, Val) ->      case Val of  	[ExpList] -> -	    {attribute,La,export,farity_list(ExpList)}; -	_Other -> error_bad_decl(La, export) +	    {attribute,Aa,export,farity_list(ExpList)}; +	_Other -> error_bad_decl(Aa, export)      end; -build_attribute({atom,La,import}, Val) -> +build_attribute({atom,Aa,import}, Val) ->      case Val of -	[{atom,_Lm,Mod},ImpList] -> -	    {attribute,La,import,{Mod,farity_list(ImpList)}}; -	_Other -> error_bad_decl(La, import) +	[{atom,_Am,Mod},ImpList] -> +	    {attribute,Aa,import,{Mod,farity_list(ImpList)}}; +	_Other -> error_bad_decl(Aa, import)      end; -build_attribute({atom,La,record}, Val) -> +build_attribute({atom,Aa,record}, Val) ->      case Val of -	[{atom,_Ln,Record},RecTuple] -> -	    {attribute,La,record,{Record,record_tuple(RecTuple)}}; -	_Other -> error_bad_decl(La, record) +	[{atom,_An,Record},RecTuple] -> +	    {attribute,Aa,record,{Record,record_tuple(RecTuple)}}; +	_Other -> error_bad_decl(Aa, record)      end; -build_attribute({atom,La,file}, Val) -> +build_attribute({atom,Aa,file}, Val) ->      case Val of -	[{string,_Ln,Name},{integer,_Ll,Line}] -> -	    {attribute,La,file,{Name,Line}}; -	_Other -> error_bad_decl(La, file) +	[{string,_An,Name},{integer,_Al,Line}] -> +	    {attribute,Aa,file,{Name,Line}}; +	_Other -> error_bad_decl(Aa, file)      end; -build_attribute({atom,La,Attr}, Val) -> +build_attribute({atom,Aa,Attr}, Val) ->      case Val of  	[Expr0] ->  	    Expr = attribute_farity(Expr0), -	    {attribute,La,Attr,term(Expr)}; -	_Other -> ret_err(La, "bad attribute") +	    {attribute,Aa,Attr,term(Expr)}; +	_Other -> ret_err(Aa, "bad attribute")      end. -var_list({cons,_Lc,{var,_,V},Tail}) -> +var_list({cons,_Ac,{var,_,V},Tail}) ->      [V|var_list(Tail)]; -var_list({nil,_Ln}) -> []; +var_list({nil,_An}) -> [];  var_list(Other) -> -    ret_err(?line(Other), "bad variable list"). +    ret_err(?anno(Other), "bad variable list"). -attribute_farity({cons,L,H,T}) -> -    {cons,L,attribute_farity(H),attribute_farity(T)}; -attribute_farity({tuple,L,Args0}) -> +attribute_farity({cons,A,H,T}) -> +    {cons,A,attribute_farity(H),attribute_farity(T)}; +attribute_farity({tuple,A,Args0}) ->      Args = attribute_farity_list(Args0), -    {tuple,L,Args}; -attribute_farity({map,L,Args0}) -> +    {tuple,A,Args}; +attribute_farity({map,A,Args0}) ->      Args = attribute_farity_map(Args0), -    {map,L,Args}; -attribute_farity({op,L,'/',{atom,_,_}=Name,{integer,_,_}=Arity}) -> -    {tuple,L,[Name,Arity]}; +    {map,A,Args}; +attribute_farity({op,A,'/',{atom,_,_}=Name,{integer,_,_}=Arity}) -> +    {tuple,A,[Name,Arity]};  attribute_farity(Other) -> Other.  attribute_farity_list(Args) -> @@ -764,45 +777,45 @@ attribute_farity_list(Args) ->  %% It is not meaningful to have farity keys.  attribute_farity_map(Args) -> -    [{Op,L,K,attribute_farity(V)} || {Op,L,K,V} <- Args]. +    [{Op,A,K,attribute_farity(V)} || {Op,A,K,V} <- Args]. --spec error_bad_decl(integer(), attributes()) -> no_return(). +-spec error_bad_decl(erl_anno:anno(), attributes()) -> no_return(). -error_bad_decl(L, S) -> -    ret_err(L, io_lib:format("bad ~w declaration", [S])). +error_bad_decl(Anno, S) -> +    ret_err(Anno, io_lib:format("bad ~w declaration", [S])). -farity_list({cons,_Lc,{op,_Lo,'/',{atom,_La,A},{integer,_Li,I}},Tail}) -> +farity_list({cons,_Ac,{op,_Ao,'/',{atom,_Aa,A},{integer,_Ai,I}},Tail}) ->      [{A,I}|farity_list(Tail)]; -farity_list({nil,_Ln}) -> []; +farity_list({nil,_An}) -> [];  farity_list(Other) -> -    ret_err(?line(Other), "bad function arity"). +    ret_err(?anno(Other), "bad function arity"). -record_tuple({tuple,_Lt,Fields}) -> +record_tuple({tuple,_At,Fields}) ->      record_fields(Fields);  record_tuple(Other) -> -    ret_err(?line(Other), "bad record declaration"). +    ret_err(?anno(Other), "bad record declaration"). -record_fields([{atom,La,A}|Fields]) -> -    [{record_field,La,{atom,La,A}}|record_fields(Fields)]; -record_fields([{match,_Lm,{atom,La,A},Expr}|Fields]) -> -    [{record_field,La,{atom,La,A},Expr}|record_fields(Fields)]; +record_fields([{atom,Aa,A}|Fields]) -> +    [{record_field,Aa,{atom,Aa,A}}|record_fields(Fields)]; +record_fields([{match,_Am,{atom,Aa,A},Expr}|Fields]) -> +    [{record_field,Aa,{atom,Aa,A},Expr}|record_fields(Fields)];  record_fields([{typed,Expr,TypeInfo}|Fields]) ->      [Field] = record_fields([Expr]),      TypeInfo1 =  	case Expr of  	    {match, _, _, _} -> TypeInfo; %% If we have an initializer. -	    {atom, La, _} -> +	    {atom, Aa, _} ->                  case has_undefined(TypeInfo) of                      false ->                          TypeInfo2 = maybe_add_paren(TypeInfo), -                        lift_unions(abstract(undefined, La), TypeInfo2); +                        lift_unions(abstract2(undefined, Aa), TypeInfo2);                      true ->                          TypeInfo                  end  	end,      [{typed_record_field,Field,TypeInfo1}|record_fields(Fields)];  record_fields([Other|_Fields]) -> -    ret_err(?line(Other), "bad record field"); +    ret_err(?anno(Other), "bad record field");  record_fields([]) -> [].  has_undefined({atom,_,undefined}) -> @@ -816,52 +829,53 @@ has_undefined({type,_,union,Ts}) ->  has_undefined(_) ->      false. -maybe_add_paren({ann_type,L,T}) -> -    {paren_type,L,[{ann_type,L,T}]}; +maybe_add_paren({ann_type,A,T}) -> +    {paren_type,A,[{ann_type,A,T}]};  maybe_add_paren(T) ->      T.  term(Expr) ->      try normalise(Expr) -    catch _:_R -> ret_err(?line(Expr), "bad attribute") +    catch _:_R -> ret_err(?anno(Expr), "bad attribute")      end. -%% build_function([Clause]) -> {function,Line,Name,Arity,[Clause]} +%% build_function([Clause]) -> {function,Anno,Name,Arity,[Clause]}  build_function(Cs) ->      Name = element(3, hd(Cs)),      Arity = length(element(4, hd(Cs))), -    {function,?line(hd(Cs)),Name,Arity,check_clauses(Cs, Name, Arity)}. +    {function,?anno(hd(Cs)),Name,Arity,check_clauses(Cs, Name, Arity)}. -%% build_fun(Line, [Clause]) -> {'fun',Line,{clauses,[Clause]}}. +%% build_fun(Anno, [Clause]) -> {'fun',Anno,{clauses,[Clause]}}. -build_fun(Line, Cs) -> +build_fun(Anno, Cs) ->      Name = element(3, hd(Cs)),      Arity = length(element(4, hd(Cs))),      CheckedCs = check_clauses(Cs, Name, Arity),      case Name of          'fun' -> -            {'fun',Line,{clauses,CheckedCs}}; +            {'fun',Anno,{clauses,CheckedCs}};          Name -> -            {named_fun,Line,Name,CheckedCs} +            {named_fun,Anno,Name,CheckedCs}      end.  check_clauses(Cs, Name, Arity) ->      [case C of -         {clause,L,N,As,G,B} when N =:= Name, length(As) =:= Arity -> -             {clause,L,As,G,B}; -         {clause,L,_N,_As,_G,_B} -> -             ret_err(L, "head mismatch") +         {clause,A,N,As,G,B} when N =:= Name, length(As) =:= Arity -> +             {clause,A,As,G,B}; +         {clause,A,_N,_As,_G,_B} -> +             ret_err(A, "head mismatch")       end || C <- Cs]. -build_try(L,Es,Scs,{Ccs,As}) -> -    {'try',L,Es,Scs,Ccs,As}. +build_try(A,Es,Scs,{Ccs,As}) -> +    {'try',A,Es,Scs,Ccs,As}.  -spec ret_err(_, _) -> no_return(). -ret_err(L, S) -> -    {location,Location} = get_attribute(L, location), -    return_error(Location, S). +ret_err(Anno, S) -> +    return_error(location(Anno), S). +location(Anno) -> +    erl_anno:location(Anno).  %%  Convert between the abstract form of a term and a term. @@ -909,7 +923,8 @@ normalise_list([]) ->        Data :: term(),        AbsTerm :: abstract_expr().  abstract(T) -> -    abstract(T, 0, enc_func(epp:default_encoding())). +    Anno = erl_anno:new(0), +    abstract(T, Anno, enc_func(epp:default_encoding())).  -type encoding_func() :: fun((non_neg_integer()) -> boolean()). @@ -919,16 +934,18 @@ abstract(T) ->        Options :: Line | [Option],        Option :: {line, Line} | {encoding, Encoding},        Encoding :: 'latin1' | 'unicode' | 'utf8' | 'none' | encoding_func(), -      Line :: erl_scan:line(), +      Line :: erl_anno:line(),        AbsTerm :: abstract_expr().  abstract(T, Line) when is_integer(Line) -> -    abstract(T, Line, enc_func(epp:default_encoding())); +    Anno = erl_anno:new(Line), +    abstract(T, Anno, enc_func(epp:default_encoding()));  abstract(T, Options) when is_list(Options) ->      Line = proplists:get_value(line, Options, 0),      Encoding = proplists:get_value(encoding, Options,epp:default_encoding()),      EncFunc = enc_func(Encoding), -    abstract(T, Line, EncFunc). +    Anno = erl_anno:new(Line), +    abstract(T, Anno, EncFunc).  -define(UNICODE(C),           (C < 16#D800 orelse @@ -942,53 +959,53 @@ enc_func(none) -> none;  enc_func(Fun) when is_function(Fun, 1) -> Fun;  enc_func(Term) -> erlang:error({badarg, Term}). -abstract(T, L, _E) when is_integer(T) -> {integer,L,T}; -abstract(T, L, _E) when is_float(T) -> {float,L,T}; -abstract(T, L, _E) when is_atom(T) -> {atom,L,T}; -abstract([], L, _E) -> {nil,L}; -abstract(B, L, _E) when is_bitstring(B) -> -    {bin, L, [abstract_byte(Byte, L) || Byte <- bitstring_to_list(B)]}; -abstract([H|T], L, none=E) -> -    {cons,L,abstract(H, L, E),abstract(T, L, E)}; -abstract(List, L, E) when is_list(List) -> -    abstract_list(List, [], L, E); -abstract(Tuple, L, E) when is_tuple(Tuple) -> -    {tuple,L,abstract_tuple_list(tuple_to_list(Tuple), L, E)}; -abstract(Map, L, E) when is_map(Map) -> -    {map,L,abstract_map_fields(maps:to_list(Map),L,E)}. - -abstract_list([H|T], String, L, E) -> +abstract(T, A, _E) when is_integer(T) -> {integer,A,T}; +abstract(T, A, _E) when is_float(T) -> {float,A,T}; +abstract(T, A, _E) when is_atom(T) -> {atom,A,T}; +abstract([], A, _E) -> {nil,A}; +abstract(B, A, _E) when is_bitstring(B) -> +    {bin, A, [abstract_byte(Byte, A) || Byte <- bitstring_to_list(B)]}; +abstract([H|T], A, none=E) -> +    {cons,A,abstract(H, A, E),abstract(T, A, E)}; +abstract(List, A, E) when is_list(List) -> +    abstract_list(List, [], A, E); +abstract(Tuple, A, E) when is_tuple(Tuple) -> +    {tuple,A,abstract_tuple_list(tuple_to_list(Tuple), A, E)}; +abstract(Map, A, E) when is_map(Map) -> +    {map,A,abstract_map_fields(maps:to_list(Map),A,E)}. + +abstract_list([H|T], String, A, E) ->      case is_integer(H) andalso H >= 0 andalso E(H) of          true -> -            abstract_list(T, [H|String], L, E); +            abstract_list(T, [H|String], A, E);          false -> -            AbstrList = {cons,L,abstract(H, L, E),abstract(T, L, E)}, -            not_string(String, AbstrList, L, E) +            AbstrList = {cons,A,abstract(H, A, E),abstract(T, A, E)}, +            not_string(String, AbstrList, A, E)      end; -abstract_list([], String, L, _E) -> -    {string, L, lists:reverse(String)}; -abstract_list(T, String, L, E) -> -    not_string(String, abstract(T, L, E), L, E). - -not_string([C|T], Result, L, E) -> -    not_string(T, {cons, L, {integer, L, C}, Result}, L, E); -not_string([], Result, _L, _E) -> +abstract_list([], String, A, _E) -> +    {string, A, lists:reverse(String)}; +abstract_list(T, String, A, E) -> +    not_string(String, abstract(T, A, E), A, E). + +not_string([C|T], Result, A, E) -> +    not_string(T, {cons, A, {integer, A, C}, Result}, A, E); +not_string([], Result, _A, _E) ->      Result. -abstract_tuple_list([H|T], L, E) -> -    [abstract(H, L, E)|abstract_tuple_list(T, L, E)]; -abstract_tuple_list([], _L, _E) -> +abstract_tuple_list([H|T], A, E) -> +    [abstract(H, A, E)|abstract_tuple_list(T, A, E)]; +abstract_tuple_list([], _A, _E) ->      []. -abstract_map_fields(Fs,L,E) -> -    [{map_field_assoc,L,abstract(K,L,E),abstract(V,L,E)}||{K,V}<-Fs]. +abstract_map_fields(Fs,A,E) -> +    [{map_field_assoc,A,abstract(K,A,E),abstract(V,A,E)}||{K,V}<-Fs]. -abstract_byte(Byte, L) when is_integer(Byte) -> -    {bin_element, L, {integer, L, Byte}, default, default}; -abstract_byte(Bits, L) -> +abstract_byte(Byte, A) when is_integer(Byte) -> +    {bin_element, A, {integer, A, Byte}, default, default}; +abstract_byte(Bits, A) ->      Sz = bit_size(Bits),      <<Val:Sz>> = Bits, -    {bin_element, L, {integer, L, Val}, {integer, L, Sz}, default}. +    {bin_element, A, {integer, A, Val}, {integer, A, Sz}, default}.  %%  Generate a list of tokens representing the abstract term. @@ -1002,32 +1019,32 @@ tokens(Abs) ->        AbsTerm :: abstract_expr(),        MoreTokens :: [token()],        Tokens :: [token()]. -tokens({char,L,C}, More) -> [{char,L,C}|More]; -tokens({integer,L,N}, More) -> [{integer,L,N}|More]; -tokens({float,L,F}, More) -> [{float,L,F}|More]; -tokens({atom,L,A}, More) -> [{atom,L,A}|More]; -tokens({var,L,V}, More) -> [{var,L,V}|More]; -tokens({string,L,S}, More) -> [{string,L,S}|More]; -tokens({nil,L}, More) -> [{'[',L},{']',L}|More]; -tokens({cons,L,Head,Tail}, More) -> -    [{'[',L}|tokens(Head, tokens_tail(Tail, More))]; -tokens({tuple,L,[]}, More) -> -    [{'{',L},{'}',L}|More]; -tokens({tuple,L,[E|Es]}, More) -> -    [{'{',L}|tokens(E, tokens_tuple(Es, ?line(E), More))]. - -tokens_tail({cons,L,Head,Tail}, More) -> -    [{',',L}|tokens(Head, tokens_tail(Tail, More))]; -tokens_tail({nil,L}, More) -> -    [{']',L}|More]; +tokens({char,A,C}, More) -> [{char,A,C}|More]; +tokens({integer,A,N}, More) -> [{integer,A,N}|More]; +tokens({float,A,F}, More) -> [{float,A,F}|More]; +tokens({atom,Aa,A}, More) -> [{atom,Aa,A}|More]; +tokens({var,A,V}, More) -> [{var,A,V}|More]; +tokens({string,A,S}, More) -> [{string,A,S}|More]; +tokens({nil,A}, More) -> [{'[',A},{']',A}|More]; +tokens({cons,A,Head,Tail}, More) -> +    [{'[',A}|tokens(Head, tokens_tail(Tail, More))]; +tokens({tuple,A,[]}, More) -> +    [{'{',A},{'}',A}|More]; +tokens({tuple,A,[E|Es]}, More) -> +    [{'{',A}|tokens(E, tokens_tuple(Es, ?anno(E), More))]. + +tokens_tail({cons,A,Head,Tail}, More) -> +    [{',',A}|tokens(Head, tokens_tail(Tail, More))]; +tokens_tail({nil,A}, More) -> +    [{']',A}|More];  tokens_tail(Other, More) -> -    L = ?line(Other), -    [{'|',L}|tokens(Other, [{']',L}|More])]. +    A = ?anno(Other), +    [{'|',A}|tokens(Other, [{']',A}|More])]. -tokens_tuple([E|Es], Line, More) -> -    [{',',Line}|tokens(E, tokens_tuple(Es, ?line(E), More))]; -tokens_tuple([], Line, More) -> -    [{'}',Line}|More]. +tokens_tuple([E|Es], Anno, More) -> +    [{',',Anno}|tokens(E, tokens_tuple(Es, ?anno(E), More))]; +tokens_tuple([], Anno, More) -> +    [{'}',Anno}|More].  %% Give the relative precedences of operators. @@ -1092,13 +1109,168 @@ max_prec() -> 900.  %%% longer apply. To get all present attributes as a property list  %%% get_attributes() should be used. +-compile({nowarn_deprecated_function,{erl_scan,set_attribute,3}}).  set_line(L, F) ->      erl_scan:set_attribute(line, L, F). +-compile({nowarn_deprecated_function,{erl_scan,attributes_info,2}}).  get_attribute(L, Name) ->      erl_scan:attributes_info(L, Name). +-compile({nowarn_deprecated_function,{erl_scan,attributes_info,1}}).  get_attributes(L) ->      erl_scan:attributes_info(L). +-spec map_anno(Fun, Abstr) -> NewAbstr when +      Fun :: fun((Anno) -> Anno), +      Anno :: erl_anno:anno(), +      Abstr :: abstract_form() | abstract_expr(), +      NewAbstr :: abstract_form() | abstract_expr(). + +map_anno(F0, Abstr) -> +    F = fun(A, Acc) -> {F0(A), Acc} end, +    {NewAbstr, []} = modify_anno1(Abstr, [], F), +    NewAbstr. + +-spec fold_anno(Fun, Acc0, Abstr) -> NewAbstr when +      Fun :: fun((Anno, AccIn) -> AccOut), +      Anno :: erl_anno:anno(), +      Acc0 :: term(), +      AccIn :: term(), +      AccOut :: term(), +      Abstr :: abstract_form() | abstract_expr(), +      NewAbstr :: abstract_form() | abstract_expr(). + +fold_anno(F0, Acc0, Abstr) -> +    F = fun(A, Acc) -> {A, F0(A, Acc)} end, +    {_, NewAcc} = modify_anno1(Abstr, Acc0, F), +    NewAcc. + +-spec mapfold_anno(Fun, Acc0, Abstr) -> {NewAbstr, Acc1} when +      Fun :: fun((Anno, AccIn) -> {Anno, AccOut}), +      Anno :: erl_anno:anno(), +      Acc0 :: term(), +      Acc1 :: term(), +      AccIn :: term(), +      AccOut :: term(), +      Abstr :: abstract_form() | abstract_expr(), +      NewAbstr :: abstract_form() | abstract_expr(). + +mapfold_anno(F, Acc0, Abstr) -> +    modify_anno1(Abstr, Acc0, F). + +-spec new_anno(Term) -> Abstr when +      Term :: term(), +      Abstr :: abstract_form() | abstract_expr(). + +new_anno(Term) -> +    map_anno(fun erl_anno:new/1, Term). + +-spec anno_to_term(Abstr) -> term() when +      Abstr :: abstract_form() | abstract_expr(). + +anno_to_term(Abstract) -> +    map_anno(fun erl_anno:to_term/1, Abstract). + +-spec anno_from_term(Term) -> abstract_form() | abstract_expr() when +      Term :: term(). + +anno_from_term(Term) -> +    map_anno(fun erl_anno:from_term/1, Term). + +%% Forms. +%% Recognize what sys_pre_expand does: +modify_anno1({'fun',A,F,{_,_,_}=Id}, Ac, Mf) -> +    {A1,Ac1} = Mf(A, Ac), +    {F1,Ac2} = modify_anno1(F, Ac1, Mf), +    {{'fun',A1,F1,Id},Ac2}; +modify_anno1({named_fun,A,N,F,{_,_,_}=Id}, Ac, Mf) -> +    {A1,Ac1} = Mf(A, Ac), +    {F1,Ac2} = modify_anno1(F, Ac1, Mf), +    {{named_fun,A1,N,F1,Id},Ac2}; +modify_anno1({attribute,A,N,[V]}, Ac, Mf) -> +    {{attribute,A1,N1,V1},Ac1} = modify_anno1({attribute,A,N,V}, Ac, Mf), +    {{attribute,A1,N1,[V1]},Ac1}; +%% End of sys_pre_expand special forms. +modify_anno1({function,F,A}, Ac, _Mf) -> +    {{function,F,A},Ac}; +modify_anno1({function,M,F,A}, Ac, Mf) -> +    {M1,Ac1} = modify_anno1(M, Ac, Mf), +    {F1,Ac2} = modify_anno1(F, Ac1, Mf), +    {A1,Ac3} = modify_anno1(A, Ac2, Mf), +    {{function,M1,F1,A1},Ac3}; +modify_anno1({attribute,A,record,{Name,Fields}}, Ac, Mf) -> +    {A1,Ac1} = Mf(A, Ac), +    {Fields1,Ac2} = modify_anno1(Fields, Ac1, Mf), +    {{attribute,A1,record,{Name,Fields1}},Ac2}; +modify_anno1({attribute,A,spec,{Fun,Types}}, Ac, Mf) -> +    {A1,Ac1} = Mf(A, Ac), +    {Types1,Ac2} = modify_anno1(Types, Ac1, Mf), +    {{attribute,A1,spec,{Fun,Types1}},Ac2}; +modify_anno1({attribute,A,callback,{Fun,Types}}, Ac, Mf) -> +    {A1,Ac1} = Mf(A, Ac), +    {Types1,Ac2} = modify_anno1(Types, Ac1, Mf), +    {{attribute,A1,callback,{Fun,Types1}},Ac2}; +modify_anno1({attribute,A,type,{TypeName,TypeDef,Args}}, Ac, Mf) -> +    {A1,Ac1} = Mf(A, Ac), +    {TypeDef1,Ac2} = modify_anno1(TypeDef, Ac1, Mf), +    {Args1,Ac3} = modify_anno1(Args, Ac2, Mf), +    {{attribute,A1,type,{TypeName,TypeDef1,Args1}},Ac3}; +modify_anno1({attribute,A,opaque,{TypeName,TypeDef,Args}}, Ac, Mf) -> +    {A1,Ac1} = Mf(A, Ac), +    {TypeDef1,Ac2} = modify_anno1(TypeDef, Ac1, Mf), +    {Args1,Ac3} = modify_anno1(Args, Ac2, Mf), +    {{attribute,A1,opaque,{TypeName,TypeDef1,Args1}},Ac3}; +modify_anno1({attribute,A,Attr,Val}, Ac, Mf) -> +    {A1,Ac1} = Mf(A, Ac), +    {{attribute,A1,Attr,Val},Ac1}; +modify_anno1({warning,W}, Ac, _Mf) -> +    {{warning,W},Ac}; +modify_anno1({error,W}, Ac, _Mf) -> +    {{error,W},Ac}; +%% Expressions. +modify_anno1({clauses,Cs}, Ac, Mf) -> +    {Cs1,Ac1} = modify_anno1(Cs, Ac, Mf), +    {{clauses,Cs1},Ac1}; +modify_anno1({typed_record_field,Field,Type}, Ac, Mf) -> +    {Field1,Ac1} = modify_anno1(Field, Ac, Mf), +    {Type1,Ac2} = modify_anno1(Type, Ac1, Mf), +    {{typed_record_field,Field1,Type1},Ac2}; +modify_anno1({Tag,A}, Ac, Mf) -> +    {A1,Ac1} = Mf(A, Ac), +    {{Tag,A1},Ac1}; +modify_anno1({Tag,A,E1}, Ac, Mf) -> +    {A1,Ac1} = Mf(A, Ac), +    {E11,Ac2} = modify_anno1(E1, Ac1, Mf), +    {{Tag,A1,E11},Ac2}; +modify_anno1({Tag,A,E1,E2}, Ac, Mf) -> +    {A1,Ac1} = Mf(A, Ac), +    {E11,Ac2} = modify_anno1(E1, Ac1, Mf), +    {E21,Ac3} = modify_anno1(E2, Ac2, Mf), +    {{Tag,A1,E11,E21},Ac3}; +modify_anno1({bin_element,A,E1,E2,TSL}, Ac, Mf) -> +    {A1,Ac1} = Mf(A, Ac), +    {E11,Ac2} = modify_anno1(E1, Ac1, Mf), +    {E21,Ac3} = modify_anno1(E2, Ac2, Mf), +    {{bin_element,A1,E11,E21, TSL},Ac3}; +modify_anno1({Tag,A,E1,E2,E3}, Ac, Mf) -> +    {A1,Ac1} = Mf(A, Ac), +    {E11,Ac2} = modify_anno1(E1, Ac1, Mf), +    {E21,Ac3} = modify_anno1(E2, Ac2, Mf), +    {E31,Ac4} = modify_anno1(E3, Ac3, Mf), +    {{Tag,A1,E11,E21,E31},Ac4}; +modify_anno1({Tag,A,E1,E2,E3,E4}, Ac, Mf) -> +    {A1,Ac1} = Mf(A, Ac), +    {E11,Ac2} = modify_anno1(E1, Ac1, Mf), +    {E21,Ac3} = modify_anno1(E2, Ac2, Mf), +    {E31,Ac4} = modify_anno1(E3, Ac3, Mf), +    {E41,Ac5} = modify_anno1(E4, Ac4, Mf), +    {{Tag,A1,E11,E21,E31,E41},Ac5}; +modify_anno1([H|T], Ac, Mf) -> +    {H1,Ac1} = modify_anno1(H, Ac, Mf), +    {T1,Ac2} = modify_anno1(T, Ac1, Mf), +    {[H1|T1],Ac2}; +modify_anno1([], Ac, _Mf) -> {[],Ac}; +modify_anno1(E, Ac, _Mf) when not is_tuple(E), not is_list(E) -> {E,Ac}. +  %% vim: ft=erlang diff --git a/lib/stdlib/src/erl_pp.erl b/lib/stdlib/src/erl_pp.erl index 469ce544c7..623a29f923 100644 --- a/lib/stdlib/src/erl_pp.erl +++ b/lib/stdlib/src/erl_pp.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %% -%% Copyright Ericsson AB 1996-2014. All Rights Reserved. +%% Copyright Ericsson AB 1996-2015. All Rights Reserved.  %%  %% The contents of this file are subject to the Erlang Public License,  %% Version 1.1, (the "License"); you may not use this file except in @@ -46,6 +46,23 @@  -record(options, {hook, encoding, opts}). +%-define(DEBUG, true). + +-ifdef(DEBUG). +-define(TEST(T), +        %% Assumes that erl_anno has been compiled with DEBUG=true. +        %% erl_pp does not use the annoations, but test it anyway. +        %% Note: hooks are not handled. +        _ = try +                erl_parse:map_anno(fun(A) when is_list(A) -> A end, T) +            catch +                _:_ -> +                    erlang:error(badarg, [T]) +            end). +-else. +-define(TEST(T), ok). +-endif. +  %%%  %%% Exported functions  %%% @@ -61,6 +78,7 @@ form(Thing) ->        Options :: options()).  form(Thing, Options) -> +    ?TEST(Thing),      State = state(Options),      frmt(lform(Thing, options(Options), State), State). @@ -75,6 +93,7 @@ attribute(Thing) ->        Options :: options()).  attribute(Thing, Options) -> +    ?TEST(Thing),      State = state(Options),      frmt(lattribute(Thing, options(Options), State), State). @@ -89,6 +108,7 @@ function(F) ->        Options :: options()).  function(F, Options) -> +    ?TEST(F),      frmt(lfunction(F, options(Options)), state(Options)).  -spec(guard(Guard) -> io_lib:chars() when @@ -102,6 +122,7 @@ guard(Gs) ->        Options :: options()).  guard(Gs, Options) -> +    ?TEST(Gs),      frmt(lguard(Gs, options(Options)), state(Options)).  -spec(exprs(Expressions) -> io_lib:chars() when @@ -123,12 +144,14 @@ exprs(Es, Options) ->        Options :: options()).  exprs(Es, I, Options) -> +    ?TEST(Es),      frmt({seq,[],[],[$,],lexprs(Es, options(Options))}, I, state(Options)).  -spec(expr(Expression) -> io_lib:chars() when        Expression :: erl_parse:abstract_expr()).  expr(E) -> +    ?TEST(E),      frmt(lexpr(E, 0, options(none)), state(none)).  -spec(expr(Expression, Options) -> io_lib:chars() when @@ -136,6 +159,7 @@ expr(E) ->        Options :: options()).  expr(E, Options) -> +    ?TEST(E),      frmt(lexpr(E, 0, options(Options)), state(Options)).  -spec(expr(Expression, Indent, Options) -> io_lib:chars() when @@ -144,6 +168,7 @@ expr(E, Options) ->        Options :: options()).  expr(E, I, Options) -> +    ?TEST(E),      frmt(lexpr(E, 0, options(Options)), I, state(Options)).  -spec(expr(Expression, Indent, Precedence, Options) -> io_lib:chars() when @@ -153,6 +178,7 @@ expr(E, I, Options) ->        Options :: options()).  expr(E, I, P, Options) -> +    ?TEST(E),      frmt(lexpr(E, P, options(Options)), I, state(Options)).  %%% @@ -213,24 +239,25 @@ lattribute({attribute,_Line,Name,Arg}, Opts, State) ->      [lattribute(Name, Arg, Opts, State),leaf(".\n")].  lattribute(module, {M,Vs}, _Opts, _State) -> -    attr("module",[{var,0,pname(M)}, -                   foldr(fun(V, C) -> {cons,0,{var,0,V},C} -                         end, {nil,0}, Vs)]); +    A = a0(), +    attr("module",[{var,A,pname(M)}, +                   foldr(fun(V, C) -> {cons,A,{var,A,V},C} +                         end, {nil,A}, Vs)]);  lattribute(module, M, _Opts, _State) -> -    attr("module", [{var,0,pname(M)}]); +    attr("module", [{var,a0(),pname(M)}]);  lattribute(export, Falist, _Opts, _State) -> -    call({var,0,"-export"}, [falist(Falist)], 0, options(none)); +    call({var,a0(),"-export"}, [falist(Falist)], 0, options(none));  lattribute(import, Name, _Opts, _State) when is_list(Name) -> -    attr("import", [{var,0,pname(Name)}]); +    attr("import", [{var,a0(),pname(Name)}]);  lattribute(import, {From,Falist}, _Opts, _State) -> -    attr("import",[{var,0,pname(From)},falist(Falist)]); +    attr("import",[{var,a0(),pname(From)},falist(Falist)]);  lattribute(optional_callbacks, Falist, Opts, _State) ->      ArgL = try falist(Falist)             catch _:_ -> abstract(Falist, Opts)             end, -    call({var,0,"-optional_callbacks"}, [ArgL], 0, options(none)); +    call({var,a0(),"-optional_callbacks"}, [ArgL], 0, options(none));  lattribute(file, {Name,Line}, _Opts, State) -> -    attr("file", [{var,0,(State#pp.string_fun)(Name)},{integer,0,Line}]); +    attr("file", [{var,a0(),(State#pp.string_fun)(Name)},{integer,a0(),Line}]);  lattribute(record, {Name,Is}, Opts, _State) ->      Nl = leaf(format("-record(~w,", [Name])),      [{first,Nl,record_fields(Is, Opts)},$)]; @@ -242,7 +269,7 @@ abstract(Arg, #options{encoding = Encoding}) ->  typeattr(Tag, {TypeName,Type,Args}, _Opts) ->      {first,leaf("-"++atom_to_list(Tag)++" "), -     typed(call({atom,0,TypeName}, Args, 0, options(none)), Type)}. +     typed(call({atom,a0(),TypeName}, Args, 0, options(none)), Type)}.  ltype({ann_type,_Line,[V,T]}) ->      typed(lexpr(V, options(none)), T); @@ -384,7 +411,7 @@ ltypes(Ts, F) ->      [F(T) || T <- Ts].  attr(Name, Args) -> -    call({var,0,format("-~s", [Name])}, Args, 0, options(none)). +    call({var,a0(),format("-~s", [Name])}, Args, 0, options(none)).  pname(['' | As]) ->      [$. | pname(As)]; @@ -396,9 +423,10 @@ pname(A) when is_atom(A) ->      write(A).  falist([]) -> -    {nil,0}; +    {nil,a0()};  falist([{Name,Arity}|Falist]) -> -    {cons,0,{var,0,format("~w/~w", [Name,Arity])},falist(Falist)}. +    A = a0(), +    {cons,A,{var,A,format("~w/~w", [Name,Arity])},falist(Falist)}.  lfunction({function,_Line,Name,_Arity,Cs}, Opts) ->      Cll = nl_clauses(fun (C, H) -> func_clause(Name, C, H) end, $;, Opts, Cs), @@ -1111,6 +1139,9 @@ write_char(C, PP) ->  %% Utilities  %% +a0() -> +    erl_anno:new(0). +  chars_size([C | Es]) when is_integer(C) ->      1 + chars_size(Es);  chars_size([E | Es]) -> diff --git a/lib/stdlib/src/erl_scan.erl b/lib/stdlib/src/erl_scan.erl index 4960a86760..5e7cc5f6d6 100644 --- a/lib/stdlib/src/erl_scan.erl +++ b/lib/stdlib/src/erl_scan.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %% -%% Copyright Ericsson AB 1996-2014. All Rights Reserved. +%% Copyright Ericsson AB 1996-2015. All Rights Reserved.  %%  %% The contents of this file are subject to the Erlang Public License,  %% Version 1.1, (the "License"); you may not use this file except in @@ -55,6 +55,15 @@           token_info/1,token_info/2,           attributes_info/1,attributes_info/2,set_attribute/3]). +-export([column/1,end_location/1,line/1,location/1,text/1, +         category/1,symbol/1]). + +-deprecated([{attributes_info, 1, next_major_release}, +             {attributes_info, 2, next_major_release}, +             {set_attribute, 3, next_major_release}, +             {token_info, 1, next_major_release}, +             {token_info, 2, next_major_release}]). +  %%% Private  -export([continuation_location/1]). @@ -78,9 +87,9 @@  -define(SETATTRFUN(F), is_function(F, 1)).  -type category() :: atom(). --type column() :: pos_integer(). --type line() :: integer(). --type location() :: line() | {line(),column()}. +-type column() :: pos_integer().                % Deprecated +-type line() :: integer().                      % Deprecated +-type location() :: line() | {line(),column()}. % Deprecated  -type resword_fun() :: fun((atom()) -> boolean()).  -type option() :: 'return' | 'return_white_spaces' | 'return_comments'                  | 'text' | {'reserved_word_fun', resword_fun()}. @@ -197,6 +206,56 @@ continuation_location({erl_scan_continuation,_,no_col,_,Line,_,_,_}) ->  continuation_location({erl_scan_continuation,_,Col,_,Line,_,_,_}) ->      {Line,Col}. +-spec column(Token) -> erl_anno:column() | 'undefined' when +      Token :: token(). + +column(Token) -> +    erl_anno:column(element(2, Token)). + +-spec end_location(Token) -> erl_anno:location() | 'undefined' when +      Token :: token(). + +end_location(Token) -> +    erl_anno:end_location(element(2, Token)). + +-spec line(Token) -> erl_anno:line() when +      Token :: token(). + +line(Token) -> +    erl_anno:line(element(2, Token)). + +-spec location(Token) -> erl_anno:location() when +      Token :: token(). + +location(Token) -> +    erl_anno:location(element(2, Token)). + +-spec text(Token) -> erl_anno:text() | 'undefined' when +      Token :: token(). + +text(Token) -> +    erl_anno:text(element(2, Token)). + +-spec category(Token) -> category() when +      Token :: token(). + +category({Category,_Anno}) -> +    Category; +category({Category,_Anno,_Symbol}) -> +    Category; +category(T) -> +    erlang:error(badarg, [T]). + +-spec symbol(Token) -> symbol() when +      Token :: token(). + +symbol({Category,_Anno}) -> +    Category; +symbol({_Category,_Anno,Symbol}) -> +    Symbol; +symbol(T) -> +    erlang:error(badarg, [T]). +  -type attribute_item() :: 'column' | 'length' | 'line'                          | 'location' | 'text'.  -type info_location() :: location() | term(). @@ -276,7 +335,17 @@ attributes_info({Line,Column}, column=Item) when ?ALINE(Line),  attributes_info(Line, column) when ?ALINE(Line) ->      undefined;  attributes_info(Attrs, column=Item) -> -    attr_info(Attrs, Item); +    case attr_info(Attrs, Item) of +        undefined -> +            case erl_anno:column(Attrs) of +                undefined -> +                    undefined; +                Column -> +                    {Item,Column} +            end; +        T -> +            T +    end;  attributes_info(Attrs, length=Item) ->      case attributes_info(Attrs, text) of          undefined -> @@ -290,14 +359,26 @@ attributes_info({Line,Column}, line=Item) when ?ALINE(Line),                                                 ?COLUMN(Column) ->      {Item,Line};  attributes_info(Attrs, line=Item) -> -    attr_info(Attrs, Item); +    case attr_info(Attrs, Item) of +        undefined -> +            case attr_info(Attrs, location) of +                {location,{Line,_Column}} -> +                    {Item,Line}; +                {location,Line} -> +                    {Item,Line}; +                undefined -> +                    undefined +            end; +        T -> +            T +    end;  attributes_info({Line,Column}=Location, location=Item) when ?ALINE(Line),                                                              ?COLUMN(Column) ->      {Item,Location};  attributes_info(Line, location=Item) when ?ALINE(Line) ->      {Item,Line};  attributes_info(Attrs, location=Item) -> -    {line,Line} = attributes_info(Attrs, line), % assume line is present +    {line,Line} = attributes_info(Attrs, line),      case attributes_info(Attrs, column) of          undefined ->              %% If set_attribute() has assigned a term such as {17,42} @@ -419,12 +500,28 @@ set_attr(line, {Line,Column}, Fun) when ?ALINE(Line), ?COLUMN(Column) ->              [{line,Ln},{column,Column}]      end;  set_attr(line=Tag, Attrs, Fun) when is_list(Attrs) -> -    {line,Line} = lists:keyfind(Tag, 1, Attrs), -    case lists:keyreplace(Tag, 1, Attrs, {line,Fun(Line)}) of -        [{line,Ln}] when ?ALINE(Ln) -> -            Ln; -        As -> -            As +    case lists:keyfind(Tag, 1, Attrs) of +        {line,Line} -> +            case lists:keyreplace(Tag, 1, Attrs, {line,Fun(Line)}) of +                [{line,Ln}] when ?ALINE(Ln) -> +                    Ln; +                As -> +                    As +            end; +        false -> +            {location, Location} = lists:keyfind(location, 1, Attrs), +            Ln = case Location of +                     {Line,Column} when ?ALINE(Line), ?COLUMN(Column) -> +                         {Fun(Line),Column}; +                     _ -> +                         Fun(Location) +                 end, +            case lists:keyreplace(location, 1, Attrs, {location,Ln}) of +                [{location,Ln}] when ?ALINE(Ln) -> +                    Ln; +                As -> +                    As +            end      end;  set_attr(T1, T2, T3) ->      erlang:error(badarg, [T1,T2,T3]). @@ -708,17 +805,17 @@ scan_name(Cs, Ncs) ->  -define(STR(St, S), if St#erl_scan.text -> S; true -> [] end).  scan_dot([$%|_]=Cs, St, Line, Col, Toks, Ncs) -> -    Attrs = attributes(Line, Col, St, Ncs), -    {ok,[{dot,Attrs}|Toks],Cs,Line,incr_column(Col, 1)}; +    Anno = anno(Line, Col, St, Ncs), +    {ok,[{dot,Anno}|Toks],Cs,Line,incr_column(Col, 1)};  scan_dot([$\n=C|Cs], St, Line, Col, Toks, Ncs) -> -    Attrs = attributes(Line, Col, St, ?STR(St, Ncs++[C])), -    {ok,[{dot,Attrs}|Toks],Cs,Line+1,new_column(Col, 1)}; +    Anno = anno(Line, Col, St, ?STR(St, Ncs++[C])), +    {ok,[{dot,Anno}|Toks],Cs,Line+1,new_column(Col, 1)};  scan_dot([C|Cs], St, Line, Col, Toks, Ncs) when ?WHITE_SPACE(C) -> -    Attrs = attributes(Line, Col, St, ?STR(St, Ncs++[C])), -    {ok,[{dot,Attrs}|Toks],Cs,Line,incr_column(Col, 2)}; +    Anno = anno(Line, Col, St, ?STR(St, Ncs++[C])), +    {ok,[{dot,Anno}|Toks],Cs,Line,incr_column(Col, 2)};  scan_dot(eof=Cs, St, Line, Col, Toks, Ncs) -> -    Attrs = attributes(Line, Col, St, Ncs), -    {ok,[{dot,Attrs}|Toks],Cs,Line,incr_column(Col, 1)}; +    Anno = anno(Line, Col, St, Ncs), +    {ok,[{dot,Anno}|Toks],Cs,Line,incr_column(Col, 1)};  scan_dot(Cs, St, Line, Col, Toks, Ncs) ->      tok2(Cs, St, Line, Col, Toks, Ncs, '.', 1). @@ -773,12 +870,12 @@ scan_nl_tabs(Cs, St, Line, Col, Toks, N) ->  %% stop anyway, nothing is gained by not collecting all white spaces.  scan_nl_white_space([$\n|Cs], #erl_scan{text = false}=St, Line, no_col=Col,                      Toks0, Ncs) -> -    Toks = [{white_space,Line,lists:reverse(Ncs)}|Toks0], +    Toks = [{white_space,anno(Line),lists:reverse(Ncs)}|Toks0],      scan_newline(Cs, St, Line+1, Col, Toks);  scan_nl_white_space([$\n|Cs], St, Line, Col, Toks, Ncs0) ->      Ncs = lists:reverse(Ncs0), -    Attrs = attributes(Line, Col, St, Ncs), -    Token = {white_space,Attrs,Ncs}, +    Anno = anno(Line, Col, St, Ncs), +    Token = {white_space,Anno,Ncs},      scan_newline(Cs, St, Line+1, new_column(Col, length(Ncs)), [Token|Toks]);  scan_nl_white_space([C|Cs], St, Line, Col, Toks, Ncs) when ?WHITE_SPACE(C) ->      scan_nl_white_space(Cs, St, Line, Col, Toks, [C|Ncs]); @@ -786,19 +883,20 @@ scan_nl_white_space([]=Cs, _St, Line, Col, Toks, Ncs) ->      {more,{Cs,Col,Toks,Line,Ncs,fun scan_nl_white_space/6}};  scan_nl_white_space(Cs, #erl_scan{text = false}=St, Line, no_col=Col,                      Toks, Ncs) -> -    scan1(Cs, St, Line+1, Col, [{white_space,Line,lists:reverse(Ncs)}|Toks]); +    Anno = anno(Line), +    scan1(Cs, St, Line+1, Col, [{white_space,Anno,lists:reverse(Ncs)}|Toks]);  scan_nl_white_space(Cs, St, Line, Col, Toks, Ncs0) ->      Ncs = lists:reverse(Ncs0), -    Attrs = attributes(Line, Col, St, Ncs), -    Token = {white_space,Attrs,Ncs}, +    Anno = anno(Line, Col, St, Ncs), +    Token = {white_space,Anno,Ncs},      scan1(Cs, St, Line+1, new_column(Col, length(Ncs)), [Token|Toks]).  newline_end(Cs, #erl_scan{text = false}=St, Line, no_col=Col,              Toks, _N, Ncs) -> -    scan1(Cs, St, Line+1, Col, [{white_space,Line,Ncs}|Toks]); +    scan1(Cs, St, Line+1, Col, [{white_space,anno(Line),Ncs}|Toks]);  newline_end(Cs, St, Line, Col, Toks, N, Ncs) -> -    Attrs = attributes(Line, Col, St, Ncs), -    scan1(Cs, St, Line+1, new_column(Col, N), [{white_space,Attrs,Ncs}|Toks]). +    Anno = anno(Line, Col, St, Ncs), +    scan1(Cs, St, Line+1, new_column(Col, N), [{white_space,Anno,Ncs}|Toks]).  scan_spcs([$\s|Cs], St, Line, Col, Toks, N) when N < 16 ->      scan_spcs(Cs, St, Line, Col, Toks, N+1); @@ -847,20 +945,20 @@ scan_char([$\\|Cs]=Cs0, St, Line, Col, Toks) ->          {eof,Ncol} ->              scan_error(char, Line, Col, Line, Ncol, eof);          {nl,Val,Str,Ncs,Ncol} -> -            Attrs = attributes(Line, Col, St, ?STR(St, "$\\"++Str)), %" -            Ntoks = [{char,Attrs,Val}|Toks], +            Anno = anno(Line, Col, St, ?STR(St, "$\\"++Str)), %" +            Ntoks = [{char,Anno,Val}|Toks],              scan1(Ncs, St, Line+1, Ncol, Ntoks);          {Val,Str,Ncs,Ncol} -> -            Attrs = attributes(Line, Col, St, ?STR(St, "$\\"++Str)), %" -            Ntoks = [{char,Attrs,Val}|Toks], +            Anno = anno(Line, Col, St, ?STR(St, "$\\"++Str)), %" +            Ntoks = [{char,Anno,Val}|Toks],              scan1(Ncs, St, Line, Ncol, Ntoks)      end;  scan_char([$\n=C|Cs], St, Line, Col, Toks) -> -    Attrs = attributes(Line, Col, St, ?STR(St, [$$,C])), -    scan1(Cs, St, Line+1, new_column(Col, 1), [{char,Attrs,C}|Toks]); +    Anno = anno(Line, Col, St, ?STR(St, [$$,C])), +    scan1(Cs, St, Line+1, new_column(Col, 1), [{char,Anno,C}|Toks]);  scan_char([C|Cs], St, Line, Col, Toks) when ?UNICODE(C) -> -    Attrs = attributes(Line, Col, St, ?STR(St, [$$,C])), -    scan1(Cs, St, Line, incr_column(Col, 2), [{char,Attrs,C}|Toks]); +    Anno = anno(Line, Col, St, ?STR(St, [$$,C])), +    scan1(Cs, St, Line, incr_column(Col, 2), [{char,Anno,C}|Toks]);  scan_char([C|_Cs], _St, Line, Col, _Toks) when ?CHAR(C) ->      scan_error({illegal,character}, Line, Col, Line, incr_column(Col, 1), eof);  scan_char([], _St, Line, Col, Toks) -> @@ -879,8 +977,8 @@ scan_string(Cs, St, Line, Col, Toks, {Wcs,Str,Line0,Col0}) ->              Estr = string:substr(Nwcs, 1, 16), % Expanded escape chars.              scan_error({string,$\",Estr}, Line0, Col0, Nline, Ncol, Ncs); %"          {Ncs,Nline,Ncol,Nstr,Nwcs} -> -            Attrs = attributes(Line0, Col0, St, Nstr), -            scan1(Ncs, St, Nline, Ncol, [{string,Attrs,Nwcs}|Toks]) +            Anno = anno(Line0, Col0, St, Nstr), +            scan1(Ncs, St, Nline, Ncol, [{string,Anno,Nwcs}|Toks])      end.  scan_qatom(Cs, St, Line, Col, Toks, {Wcs,Str,Line0,Col0}) -> @@ -896,8 +994,8 @@ scan_qatom(Cs, St, Line, Col, Toks, {Wcs,Str,Line0,Col0}) ->          {Ncs,Nline,Ncol,Nstr,Nwcs} ->              case catch list_to_atom(Nwcs) of                  A when is_atom(A) -> -                    Attrs = attributes(Line0, Col0, St, Nstr), -                    scan1(Ncs, St, Nline, Ncol, [{atom,Attrs,A}|Toks]); +                    Anno = anno(Line0, Col0, St, Nstr), +                    scan1(Ncs, St, Nline, Ncol, [{atom,Anno,A}|Toks]);                  _ ->                      scan_error({illegal,atom}, Line0, Col0, Nline, Ncol, Ncs)              end @@ -1173,28 +1271,28 @@ scan_comment(Cs, St, Line, Col, Toks, Ncs0) ->      tok3(Cs, St, Line, Col, Toks, comment, Ncs, Ncs).  tok2(Cs, #erl_scan{text = false}=St, Line, no_col=Col, Toks, _Wcs, P) -> -    scan1(Cs, St, Line, Col, [{P,Line}|Toks]); +    scan1(Cs, St, Line, Col, [{P,anno(Line)}|Toks]);  tok2(Cs, St, Line, Col, Toks, Wcs, P) -> -    Attrs = attributes(Line, Col, St, Wcs), -    scan1(Cs, St, Line, incr_column(Col, length(Wcs)), [{P,Attrs}|Toks]). +    Anno = anno(Line, Col, St, Wcs), +    scan1(Cs, St, Line, incr_column(Col, length(Wcs)), [{P,Anno}|Toks]).  tok2(Cs, #erl_scan{text = false}=St, Line, no_col=Col, Toks, _Wcs, P, _N) -> -    scan1(Cs, St, Line, Col, [{P,Line}|Toks]); +    scan1(Cs, St, Line, Col, [{P,anno(Line)}|Toks]);  tok2(Cs, St, Line, Col, Toks, Wcs, P, N) -> -    Attrs = attributes(Line, Col, St, Wcs), -    scan1(Cs, St, Line, incr_column(Col, N), [{P,Attrs}|Toks]). +    Anno = anno(Line, Col, St, Wcs), +    scan1(Cs, St, Line, incr_column(Col, N), [{P,Anno}|Toks]).  tok3(Cs, #erl_scan{text = false}=St, Line, no_col=Col, Toks, Item, _S, Sym) -> -    scan1(Cs, St, Line, Col, [{Item,Line,Sym}|Toks]); +    scan1(Cs, St, Line, Col, [{Item,anno(Line),Sym}|Toks]);  tok3(Cs, St, Line, Col, Toks, Item, String, Sym) -> -    Token = {Item,attributes(Line, Col, St, String),Sym}, +    Token = {Item,anno(Line, Col, St, String),Sym},      scan1(Cs, St, Line, incr_column(Col, length(String)), [Token|Toks]).  tok3(Cs, #erl_scan{text = false}=St, Line, no_col=Col, Toks, Item,       _String, Sym, _Length) -> -    scan1(Cs, St, Line, Col, [{Item,Line,Sym}|Toks]); +    scan1(Cs, St, Line, Col, [{Item,anno(Line),Sym}|Toks]);  tok3(Cs, St, Line, Col, Toks, Item, String, Sym, Length) -> -    Token = {Item,attributes(Line, Col, St, String),Sym}, +    Token = {Item,anno(Line, Col, St, String),Sym},      scan1(Cs, St, Line, incr_column(Col, Length), [Token|Toks]).  scan_error(Error, Line, Col, EndLine, EndCol, Rest) -> @@ -1205,23 +1303,28 @@ scan_error(Error, Line, Col, EndLine, EndCol, Rest) ->  scan_error(Error, ErrorLoc, EndLoc, Rest) ->      {{error,{ErrorLoc,?MODULE,Error},EndLoc},Rest}. --compile({inline,[attributes/4]}). +-compile({inline,[anno/4]}). -attributes(Line, no_col, #erl_scan{text = false}, _String) -> -    Line; -attributes(Line, no_col, #erl_scan{text = true}, String) -> -    [{line,Line},{text,String}]; -attributes(Line, Col, #erl_scan{text = false}, _String) -> -    {Line,Col}; -attributes(Line, Col, #erl_scan{text = true}, String) -> -    [{line,Line},{column,Col},{text,String}]. +anno(Line, no_col, #erl_scan{text = false}, _String) -> +    anno(Line); +anno(Line, no_col, #erl_scan{text = true}, String) -> +    Anno = anno(Line), +    erl_anno:set_text(String, Anno); +anno(Line, Col, #erl_scan{text = false}, _String) -> +    anno({Line, Col}); +anno(Line, Col, #erl_scan{text = true}, String) -> +    Anno = anno({Line, Col}), +    erl_anno:set_text(String, Anno).  location(Line, no_col) ->      Line;  location(Line, Col) when is_integer(Col) ->      {Line,Col}. --compile({inline,[incr_column/2,new_column/2]}). +-compile({inline,[anno/1,incr_column/2,new_column/2]}). + +anno(Location) -> +    erl_anno:new(Location).  incr_column(no_col=Col, _N) ->      Col; diff --git a/lib/stdlib/src/escript.erl b/lib/stdlib/src/escript.erl index 90e1f3a8d6..f0827009a5 100644 --- a/lib/stdlib/src/escript.erl +++ b/lib/stdlib/src/escript.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %% -%% Copyright Ericsson AB 2007-2014. All Rights Reserved. +%% Copyright Ericsson AB 2007-2015. All Rights Reserved.  %%  %% The contents of this file are subject to the Erlang Public License,  %% Version 1.1, (the "License"); you may not use this file except in @@ -620,12 +620,13 @@ parse_source(S, File, Fd, StartLine, HeaderSz, CheckOnly) ->                      {ok, {attribute,_, module, M} = Form} ->                          epp_parse_file(Epp, S2#state{module = M}, [Form, FileForm]);                      {ok, _} -> -                        ModForm = {attribute,1,module, Module}, +                        ModForm = {attribute,a1(),module, Module},                          epp_parse_file2(Epp, S2, [ModForm, FileForm], OptModRes);                      {error, _} ->                          epp_parse_file2(Epp, S2, [FileForm], OptModRes); -                    {eof, _LastLine} = Eof -> -                        S#state{forms_or_bin = [FileForm, Eof]} +                    {eof, LastLine} -> +                        Anno = anno(LastLine), +                        S#state{forms_or_bin = [FileForm, {eof, Anno}]}                  end,              ok = epp:close(Epp),              ok = file:close(Fd), @@ -644,7 +645,7 @@ check_source(S, CheckOnly) ->  	    %% Optionally add export of main/1  	    Forms2 =  		case ExpMain of -		    false -> [{attribute,0,export, [{main,1}]} | Forms]; +		    false -> [{attribute, a0(), export, [{main,1}]} | Forms];  		    true  -> Forms  		end,  	    Forms3 = [FileForm2, ModForm2 | Forms2], @@ -722,8 +723,9 @@ epp_parse_file2(Epp, S, Forms, Parsed) ->              io:format("~ts:~w: ~ts\n",                        [S#state.file,Ln,Mod:format_error(Args)]),              epp_parse_file(Epp, S#state{n_errors = S#state.n_errors + 1}, [Form | Forms]); -        {eof, _LastLine} = Eof -> -            S#state{forms_or_bin = lists:reverse([Eof | Forms])} +        {eof, LastLine} -> +            Anno = anno(LastLine), +            S#state{forms_or_bin = lists:reverse([{eof, Anno} | Forms])}      end.  %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% @@ -778,7 +780,8 @@ interpret(Forms, HasRecs,  File, Args) ->  	end,      Dict = parse_to_dict(Forms2),      ArgsA = erl_parse:abstract(Args, 0), -    Call = {call,0,{atom,0,main},[ArgsA]}, +    Anno = a0(), +    Call = {call,Anno,{atom,Anno,main},[ArgsA]},      try          _ = erl_eval:expr(Call,                            erl_eval:new_bindings(), @@ -890,6 +893,15 @@ enc() ->          Enc -> [Enc]      end. +a0() -> +    anno(0). + +a1() -> +    anno(1). + +anno(L) -> +    erl_anno:new(L). +  fatal(Str) ->      throw(Str). diff --git a/lib/stdlib/src/gb_sets.erl b/lib/stdlib/src/gb_sets.erl index 0a26d0182d..393fb07229 100644 --- a/lib/stdlib/src/gb_sets.erl +++ b/lib/stdlib/src/gb_sets.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %%  -%% Copyright Ericsson AB 2001-2014. All Rights Reserved. +%% Copyright Ericsson AB 2001-2015. All Rights Reserved.  %%   %% The contents of this file are subject to the Erlang Public License,  %% Version 1.1, (the "License"); you may not use this file except in @@ -207,21 +207,19 @@  %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -%%% gb_sets:set() in OTP 17 only. -  -spec empty() -> Set when -      Set :: gb_sets:set(). +      Set :: set().  empty() ->      {0, nil}.  -spec new() -> Set when -      Set :: gb_sets:set(). +      Set :: set().  new() -> empty().  -spec is_empty(Set) -> boolean() when -      Set :: gb_sets:set(). +      Set :: set().  is_empty({0, nil}) ->      true; @@ -229,7 +227,7 @@ is_empty(_) ->      false.  -spec size(Set) -> non_neg_integer() when -      Set :: gb_sets:set(). +      Set :: set().  size({Size, _}) ->      Size. diff --git a/lib/stdlib/src/io.erl b/lib/stdlib/src/io.erl index b9ace2f442..0b59546dc4 100644 --- a/lib/stdlib/src/io.erl +++ b/lib/stdlib/src/io.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %% -%% Copyright Ericsson AB 1996-2014. All Rights Reserved. +%% Copyright Ericsson AB 1996-2015. All Rights Reserved.  %%  %% The contents of this file are subject to the Erlang Public License,  %% Version 1.1, (the "License"); you may not use this file except in @@ -45,7 +45,7 @@  %% ErrorDescription is whatever the I/O-server sends.  -type server_no_data() :: {'error', ErrorDescription :: term()} | 'eof'. --type location() :: erl_scan:location(). +-type location() :: erl_anno:location().  %%------------------------------------------------------------------------- diff --git a/lib/stdlib/src/ms_transform.erl b/lib/stdlib/src/ms_transform.erl index 7b6f4e5b50..6e3723bb98 100644 --- a/lib/stdlib/src/ms_transform.erl +++ b/lib/stdlib/src/ms_transform.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %%  -%% Copyright Ericsson AB 2002-2013. All Rights Reserved. +%% Copyright Ericsson AB 2002-2015. All Rights Reserved.  %%   %% The contents of this file are subject to the Erlang Public License,  %% Version 1.1, (the "License"); you may not use this file except in @@ -822,9 +822,10 @@ th(T,B,OB) when is_tuple(T) ->  th(Nonstruct,B,_OB) ->      {Nonstruct,B}. -warn_var_clash(Line,Name,OuterBound) -> +warn_var_clash(Anno,Name,OuterBound) ->      case gb_sets:is_member(Name,OuterBound) of  	true -> +            Line = erl_anno:line(Anno),  	    add_warning(Line,{?WARN_SHADOW_VAR,Name});  	_ ->  	    ok diff --git a/lib/stdlib/src/orddict.erl b/lib/stdlib/src/orddict.erl index c98d78b34d..af5d917840 100644 --- a/lib/stdlib/src/orddict.erl +++ b/lib/stdlib/src/orddict.erl @@ -115,8 +115,8 @@ erase(_, []) -> [].        Orddict1 :: orddict(),        Orddict2 :: orddict(). -store(Key, New, [{K,_}=E|Dict]) when Key < K -> -    [{Key,New},E|Dict]; +store(Key, New, [{K,_}|_]=Dict) when Key < K -> +    [{Key,New}|Dict];  store(Key, New, [{K,_}=E|Dict]) when Key > K ->      [E|store(Key, New, Dict)];  store(Key, New, [{_K,_Old}|Dict]) ->		%Key == K @@ -129,8 +129,8 @@ store(Key, New, []) -> [{Key,New}].        Orddict1 :: orddict(),        Orddict2 :: orddict(). -append(Key, New, [{K,_}=E|Dict]) when Key < K -> -    [{Key,[New]},E|Dict]; +append(Key, New, [{K,_}|_]=Dict) when Key < K -> +    [{Key,[New]}|Dict];  append(Key, New, [{K,_}=E|Dict]) when Key > K ->      [E|append(Key, New, Dict)];  append(Key, New, [{_K,Old}|Dict]) ->		%Key == K @@ -143,8 +143,8 @@ append(Key, New, []) -> [{Key,[New]}].        Orddict1 :: orddict(),        Orddict2 :: orddict(). -append_list(Key, NewList, [{K,_}=E|Dict]) when Key < K -> -    [{Key,NewList},E|Dict]; +append_list(Key, NewList, [{K,_}|_]=Dict) when Key < K -> +    [{Key,NewList}|Dict];  append_list(Key, NewList, [{K,_}=E|Dict]) when Key > K ->      [E|append_list(Key, NewList, Dict)];  append_list(Key, NewList, [{_K,Old}|Dict]) ->		%Key == K @@ -170,8 +170,8 @@ update(Key, Fun, [{K,Val}|Dict]) when Key == K ->        Orddict1 :: orddict(),        Orddict2 :: orddict(). -update(Key, _, Init, [{K,_}=E|Dict]) when Key < K -> -    [{Key,Init},E|Dict]; +update(Key, _, Init, [{K,_}|_]=Dict) when Key < K -> +    [{Key,Init}|Dict];  update(Key, Fun, Init, [{K,_}=E|Dict]) when Key > K ->      [E|update(Key, Fun, Init, Dict)];  update(Key, Fun, _Init, [{_K,Val}|Dict]) ->		%Key == K @@ -184,8 +184,8 @@ update(Key, _, Init, []) -> [{Key,Init}].        Orddict1 :: orddict(),        Orddict2 :: orddict(). -update_counter(Key, Incr, [{K,_}=E|Dict]) when Key < K -> -    [{Key,Incr},E|Dict]; +update_counter(Key, Incr, [{K,_}|_]=Dict) when Key < K -> +    [{Key,Incr}|Dict];  update_counter(Key, Incr, [{K,_}=E|Dict]) when Key > K ->      [E|update_counter(Key, Incr, Dict)];  update_counter(Key, Incr, [{_K,Val}|Dict]) ->		%Key == K diff --git a/lib/stdlib/src/otp_internal.erl b/lib/stdlib/src/otp_internal.erl index 540c1cac9c..24721da187 100644 --- a/lib/stdlib/src/otp_internal.erl +++ b/lib/stdlib/src/otp_internal.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %% -%% Copyright Ericsson AB 1999-2014. All Rights Reserved. +%% Copyright Ericsson AB 1999-2015. All Rights Reserved.  %%  %% The contents of this file are subject to the Erlang Public License,  %% Version 1.1, (the "License"); you may not use this file except in @@ -18,7 +18,7 @@  %%  -module(otp_internal). --export([obsolete/3]). +-export([obsolete/3, obsolete_type/3]).  %%---------------------------------------------------------------------- @@ -26,7 +26,7 @@  -type mfas()    :: mfa() | {atom(), atom(), [byte()]}.  -type release() :: string(). --spec obsolete(atom(), atom(), byte()) -> +-spec obsolete(module(), atom(), arity()) ->  	'no' | {tag(), string()} | {tag(), mfas(), release()}.  obsolete(Module, Name, Arity) -> @@ -595,8 +595,41 @@ obsolete_1(core_lib, is_literal_list, 1) ->       " instead"};  obsolete_1(core_lib, literal_value, 1) ->      {deprecated,{core_lib,concrete,1}}; +obsolete_1(erl_scan, set_attribute, 3) -> +    {deprecated, +     "deprecated (will be removed in OTP 19); use erl_anno:set_line/2 instead"}; +obsolete_1(erl_scan, attributes_info, 1) -> +    {deprecated, +     "deprecated (will be removed in OTP 19); use " +     "erl_anno:{column,line,location,text}/1 instead"}; +obsolete_1(erl_scan, attributes_info, 2) -> +    {deprecated, +     "deprecated (will be removed in OTP 19); use " +     "erl_anno:{column,line,location,text}/1 instead"}; +obsolete_1(erl_scan, token_info, 1) -> +    {deprecated, +     "deprecated (will be removed in OTP 19); use " +     "erl_scan:{category,column,line,location,symbol,text}/1 instead"}; +obsolete_1(erl_scan, token_info, 2) -> +    {deprecated, +     "deprecated (will be removed in OTP 19); use " +     "erl_scan:{category,column,line,location,symbol,text}/1 instead"}; +obsolete_1(erl_parse, set_line, 2) -> +    {deprecated, +     "deprecated (will be removed in OTP 19); use erl_anno:set_line/2 instead"}; +obsolete_1(erl_parse, get_attributes, 1) -> +    {deprecated, +     "deprecated (will be removed in OTP 19); use " +     "erl_anno:{column,line,location,text}/1 instead"}; +obsolete_1(erl_parse, get_attribute, 2) -> +    {deprecated, +     "deprecated (will be removed in OTP 19); use " +     "erl_anno:{column,line,location,text}/1 instead"}; +obsolete_1(erl_lint, modify_line, 2) -> +    {deprecated, +     "deprecated (will be removed in OTP 19); use erl_parse:map_anno/2 instead"};  obsolete_1(ssl, negotiated_next_protocol, 1) -> -    {deprecated,{ssl,negotiated_protocol}}; +    {deprecated,{ssl,negotiated_protocol,1}};  obsolete_1(_, _, _) ->      no. @@ -644,3 +677,30 @@ is_snmp_agent_function(add_agent_caps,        2) -> true;  is_snmp_agent_function(del_agent_caps,        1) -> true;  is_snmp_agent_function(get_agent_caps,        0) -> true;  is_snmp_agent_function(_,		      _) -> false. + +-spec obsolete_type(module(), atom(), arity()) -> +	'no' | {tag(), string()} | {tag(), mfas(), release()}. + +obsolete_type(Module, Name, NumberOfVariables) -> +    case obsolete_type_1(Module, Name, NumberOfVariables) of +%% 	{deprecated=Tag,{_,_,_}=Replacement} -> +%% 	    {Tag,Replacement,"in a future release"}; +	{_,String}=Ret when is_list(String) -> +	    Ret; +%% 	{_,_,_}=Ret -> +%% 	    Ret; +	no -> +	    no +    end. + +obsolete_type_1(erl_scan,column,0) -> +    {deprecated, +     "deprecated (will be removed in OTP 19); use erl_anno:column() instead"}; +obsolete_type_1(erl_scan,line,0) -> +    {deprecated, +     "deprecated (will be removed in OTP 19); use erl_anno:line() instead"}; +obsolete_type_1(erl_scan,location,0) -> +    {deprecated, +     "deprecated (will be removed in OTP 19); use erl_anno:location() instead"}; +obsolete_type_1(_,_,_) -> +    no. diff --git a/lib/stdlib/src/qlc.erl b/lib/stdlib/src/qlc.erl index 5b19ee6190..ad8aafbb1a 100644 --- a/lib/stdlib/src/qlc.erl +++ b/lib/stdlib/src/qlc.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %% -%% Copyright Ericsson AB 2004-2013. All Rights Reserved. +%% Copyright Ericsson AB 2004-2015. All Rights Reserved.  %%  %% The contents of this file are subject to the Erlang Public License,  %% Version 1.1, (the "License"); you may not use this file except in @@ -1006,7 +1006,7 @@ listify(T) ->  -record(simple_qlc,          {p,         % atom(), pattern variable           le, -         line, +         line :: erl_anno:anno(),           init_value,           optz       % #optz           }). @@ -1148,15 +1148,18 @@ abstract(Info, true=_Flat, NElements, Depth) ->          [{match,_,Expr,Q}] ->              Q;          [{match,_,Expr,Q} | Body] -> -            {block, 0, lists:reverse(Body, [Q])}; +            {block, anno0(), lists:reverse(Body, [Q])};          _ -> -            {block, 0, lists:reverse(Body0, [Expr])} +            {block, anno0(), lists:reverse(Body0, [Expr])}      end. -abstract({qlc, E0, Qs0, Opt}, NElements, Depth) -> +abstract(Info, NElements, Depth) -> +    abstract1(Info, NElements, Depth, anno1()). + +abstract1({qlc, E0, Qs0, Opt}, NElements, Depth, A) ->      Qs = lists:map(fun({generate, P, LE}) -> -                           {generate, 1, binary_to_term(P),  -                            abstract(LE, NElements, Depth)}; +                           {generate, A, binary_to_term(P), +                            abstract1(LE, NElements, Depth, A)};                        (F) ->                              binary_to_term(F)                     end, Qs0), @@ -1165,12 +1168,12 @@ abstract({qlc, E0, Qs0, Opt}, NElements, Depth) ->               [] -> [];               _ -> [abstract_term(Opt, 1)]           end, -    ?QLC_Q(1, 1, 1, 1, {lc,1,E,Qs}, Os); -abstract({table, {M, F, As0}}, _NElements, _Depth)  +    ?QLC_Q(A, A, A, A, {lc,A,E,Qs}, Os); +abstract1({table, {M, F, As0}}, _NElements, _Depth, Anno)                            when is_atom(M), is_atom(F), is_list(As0) ->      As = [abstract_term(A, 1) || A <- As0], -    {call, 1, {remote, 1, {atom, 1, M}, {atom, 1, F}}, As}; -abstract({table, TableDesc}, _NElements, _Depth) -> +    {call, Anno, {remote, Anno, {atom, Anno, M}, {atom, Anno, F}}, As}; +abstract1({table, TableDesc}, _NElements, _Depth, _A) ->      case io_lib:deep_char_list(TableDesc) of          true ->              {ok, Tokens, _} = erl_scan:string(lists:flatten(TableDesc++".")), @@ -1179,27 +1182,28 @@ abstract({table, TableDesc}, _NElements, _Depth) ->          false -> % abstract expression              TableDesc      end; -abstract({append, Infos}, NElements, Depth) -> +abstract1({append, Infos}, NElements, Depth, A) ->      As = lists:foldr(fun(Info, As0) ->  -                             {cons,1,abstract(Info, NElements, Depth),As0} -                     end, {nil, 1}, Infos), -    {call, 1, {remote, 1, {atom, 1, ?MODULE}, {atom, 1, append}}, [As]}; -abstract({sort, Info, SortOptions}, NElements, Depth) ->     -    {call, 1, {remote, 1, {atom, 1, ?MODULE}, {atom, 1, sort}}, -     [abstract(Info, NElements, Depth), abstract_term(SortOptions, 1)]}; -abstract({keysort, Info, Kp, SortOptions}, NElements, Depth) -> -    {call, 1, {remote, 1, {atom, 1, ?MODULE}, {atom, 1, keysort}}, -     [abstract_term(Kp, 1), abstract(Info, NElements, Depth),  +                             {cons,A,abstract1(Info, NElements, Depth, A), +                              As0} +                     end, {nil, A}, Infos), +    {call, A, {remote, A, {atom, A, ?MODULE}, {atom, A, append}}, [As]}; +abstract1({sort, Info, SortOptions}, NElements, Depth, A) -> +    {call, A, {remote, A, {atom, A, ?MODULE}, {atom, A, sort}}, +     [abstract1(Info, NElements, Depth, A), abstract_term(SortOptions, 1)]}; +abstract1({keysort, Info, Kp, SortOptions}, NElements, Depth, A) -> +    {call, A, {remote, A, {atom, A, ?MODULE}, {atom, A, keysort}}, +     [abstract_term(Kp, 1), abstract1(Info, NElements, Depth, A),        abstract_term(SortOptions, 1)]}; -abstract({list,L,MS}, NElements, Depth) -> -    {call, 1, {remote, 1, {atom, 1, ets}, {atom, 1, match_spec_run}}, -     [abstract(L, NElements, Depth), -      {call, 1, {remote, 1, {atom, 1, ets}, {atom, 1, match_spec_compile}}, +abstract1({list,L,MS}, NElements, Depth, A) -> +    {call, A, {remote, A, {atom, A, ets}, {atom, A, match_spec_run}}, +     [abstract1(L, NElements, Depth, A), +      {call, A, {remote, A, {atom, A, ets}, {atom, A, match_spec_compile}},         [abstract_term(depth(MS, Depth), 1)]}]}; -abstract({list, L}, NElements, Depth) when NElements =:= infinity;  -                                           NElements >= length(L) -> +abstract1({list, L}, NElements, Depth, _A) when NElements =:= infinity; +                                                NElements >= length(L) ->      abstract_term(depth(L, Depth), 1); -abstract({list, L}, NElements, Depth) -> +abstract1({list, L}, NElements, Depth, _A) ->      abstract_term(depth(lists:sublist(L, NElements), Depth) ++ '...', 1).  depth(List, infinity) -> @@ -1251,14 +1255,14 @@ abstract_term(Term) ->      abstract_term(Term, 0).  abstract_term(Term, Line) -> -    abstr_term(Term, Line). +    abstr_term(Term, anno(Line)).  abstr_term(Tuple, Line) when is_tuple(Tuple) ->      {tuple,Line,[abstr_term(E, Line) || E <- tuple_to_list(Tuple)]};  abstr_term([_ | _]=L, Line) ->      case io_lib:char_list(L) of          true -> -            erl_parse:abstract(L, Line); +            erl_parse:abstract(L, erl_anno:line(Line));          false ->              abstr_list(L, Line)      end; @@ -1285,7 +1289,7 @@ abstr_term(Fun, Line) when is_function(Fun) ->  abstr_term(PPR, Line) when is_pid(PPR); is_port(PPR); is_reference(PPR) ->      {special, Line, lists:flatten(io_lib:write(PPR))};      abstr_term(Simple, Line) -> -    erl_parse:abstract(Simple, Line). +    erl_parse:abstract(Simple, erl_anno:line(Line)).  abstr_list([H | T], Line) ->      {cons, Line, abstr_term(H, Line), abstr_list(T, Line)}; @@ -1519,7 +1523,7 @@ join_info(Join, QInfo, Qdata, Code) ->                           %% Only compared constants (==).                           [Cs1_0, Cs2_0]                   end, -    L = 0, +    L = anno0(),      G1_0 = {var,L,'G1'}, G2_0 = {var,L,'G2'},      JP = element(JQNum + 1, Code),      %% Create code for wh1 and wh2 in #join{}: @@ -1571,7 +1575,7 @@ join_merge_info(QNum, QInfo, Code, G, ExtraConstants) ->                          {P, P};                      _ ->                           {PV, _} = aux_name1('P', 0, abstract_vars(P)), -                        L = 0, +                        L = erl_anno:new(0),                          V = {var, L, PV},                          {V, {match, L, V, P}}                   end, @@ -1579,19 +1583,20 @@ join_merge_info(QNum, QInfo, Code, G, ExtraConstants) ->              LEI = {generate, term_to_binary(M), LEInfo},              TP = term_to_binary(G),              CFs = [begin -                       Call = {call,0,{atom,0,element},[{integer,0,Col},EPV]}, -                       F = list2op([{op,0,Op,abstract_term(Con),Call} -                                      || {Con,Op} <- ConstOps], 'or'), +                       A = anno0(), +                       Call = {call,A,{atom,A,element},[{integer,A,Col},EPV]}, +                       F = list2op([{op,A,Op,abstract_term(Con),Call} +                                      || {Con,Op} <- ConstOps], 'or', A),                         term_to_binary(F)                     end ||                        {Col,ConstOps} <- ExtraConstants],              {{I,G}, [{generate, TP, {qlc, DQP, [LEI | CFs], []}}]}      end. -list2op([E], _Op) -> +list2op([E], _Op, _Anno) ->      E; -list2op([E | Es], Op) -> -    {op,0,Op,E,list2op(Es, Op)}. +list2op([E | Es], Op, Anno) -> +    {op,Anno,Op,E,list2op(Es, Op, Anno)}.  join_lookup_info(QNum, QInfo, G) ->      {generate, _, LEInfo}=I = lists:nth(QNum, QInfo), @@ -1704,7 +1709,7 @@ eval_le(LE_fun, GOpt) ->  prep_qlc_lc({simple_v1, PVar, LE_fun, L}, Opt, GOpt, _H) ->      check_lookup_option(Opt, false), -    prep_simple_qlc(PVar, L, eval_le(LE_fun, GOpt), Opt); +    prep_simple_qlc(PVar, anno(L), eval_le(LE_fun, GOpt), Opt);  prep_qlc_lc({qlc_v1, QFun, CodeF, Qdata0, QOpt}, Opt, GOpt, _H) ->      F = fun(?qual_data(_QNum, _GoI, _SI, fil)=QualData, ModGens) ->                   {QualData, ModGens}; @@ -1821,7 +1826,7 @@ may_create_simple(#qlc_opt{unique = Unique, cache = Cache} = Opt,      if           Unique and not IsUnique;           (Cache =/= false) and not IsCached -> -            prep_simple_qlc(?SIMPLE_QVAR, 1, Prep, Opt); +            prep_simple_qlc(?SIMPLE_QVAR, anno(1), Prep, Opt);          true ->              Prep      end. @@ -3772,6 +3777,15 @@ grd(Fun, Arg) ->              false      end. +anno0() -> +    anno(0). + +anno1() -> +    anno(1). + +anno(L) -> +    erl_anno:new(L). +  family(L) ->      sofs:to_external(sofs:relation_to_family(sofs:relation(L))). diff --git a/lib/stdlib/src/qlc_pt.erl b/lib/stdlib/src/qlc_pt.erl index b6bb758dfb..a4d2157b35 100644 --- a/lib/stdlib/src/qlc_pt.erl +++ b/lib/stdlib/src/qlc_pt.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %% -%% Copyright Ericsson AB 2004-2014. All Rights Reserved. +%% Copyright Ericsson AB 2004-2015. All Rights Reserved.  %%  %% The contents of this file are subject to the Erlang Public License,  %% Version 1.1, (the "License"); you may not use this file except in @@ -39,7 +39,12 @@           opt        % #qlc_opt          }). --record(state, {imp, maxargs, records, xwarnings = []}). +-record(state, {imp, +                maxargs, +                records, +                xwarnings = [], +                intro_vars, +                node_info}).  %-define(debug, true). @@ -66,37 +71,49 @@        Options :: [Option],        Option :: type_checker | compile:option()). -parse_transform(Forms, Options) -> +parse_transform(Forms0, Options) ->      ?DEBUG("qlc Parse Transform~n", []), -    State = #state{imp = is_qlc_q_imported(Forms), -                   maxargs = ?COMPILE_MAX_NUM_OF_ARGS, -                   records = record_attributes(Forms)}, -    case called_from_type_checker(Options) of -        true -> -            %% The returned value should conform to the types, but -            %% need not evaluate to anything meaningful. -            L = 0, -            {tuple,_,Fs0} = abstr(#qlc_lc{}, L), -            F = fun(_Id, LC, A) -> -                        Init = simple(L, 'V', LC, L), -                        {{tuple,L,set_field(#qlc_lc.lc, Fs0, Init)}, A} -                end, -            {Forms1,ok} = qlc_mapfold(F, ok, Forms, State), -            Forms1; -        false -> -            FormsNoShadows = no_shadows(Forms, State), -            case compile_messages(Forms, FormsNoShadows, Options, State) of -                {[],[],Warnings} -> -                    {NewForms, State1} = transform(FormsNoShadows, State), -                    ExtraWs = State1#state.xwarnings, -                    {[],WForms} = no_duplicates(NewForms, [], Warnings,  -                                                ExtraWs, Options), -                    WForms ++ NewForms; -                {E0,Errors,Warnings} -> -                    {EForms,WForms} = no_duplicates(Forms, E0++Errors,  -                                                    Warnings, [], Options), -                    EForms ++ WForms ++ Forms -            end +    Imported = is_qlc_q_imported(Forms0), +    {Forms, FormsNoShadows, State} = initiate(Forms0, Imported), +    NodeInfo = State#state.node_info, +    try +        case called_from_type_checker(Options) of +            true -> +                %% The returned value should conform to the types, but +                %% need not evaluate to anything meaningful. +                L = anno0(), +                {tuple,_,Fs0} = abstr(#qlc_lc{}, L), +                F = fun(_Id, LC, A) -> +                            Init = simple(L, 'V', LC, L), +                            {{tuple,L,set_field(#qlc_lc.lc, Fs0, Init)}, A} +                    end, +                {Forms1,ok} = qlc_mapfold(F, ok, Forms, State), +                Forms1; +            false -> +                case +                    compile_messages(Forms, FormsNoShadows, Options, State) +                of +                    {[],Warnings} -> +                        ?DEBUG("node info1 ~p~n", +                               [lists:sort(ets:tab2list(NodeInfo))]), +                        {NewForms, State1} = +                            transform(FormsNoShadows, State), +                        ExtraWs = State1#state.xwarnings, +                        {[],WForms} = no_duplicates(NewForms, [], Warnings, +                                                    ExtraWs, Options), +                        (restore_locations(WForms, State) ++ +                         restore_anno(NewForms, NodeInfo)); +                    {Errors,Warnings} -> +                        ?DEBUG("node info2 ~p~n", +                               [lists:sort(ets:tab2list(NodeInfo))]), +                        {EForms,WForms} = no_duplicates(FormsNoShadows, Errors, +                                                        Warnings, [], +                                                        Options), +                        restore_locations(EForms ++ WForms, State) ++ Forms0 +                end +        end +    after +        true = ets:delete(NodeInfo)      end.  -spec(transform_from_evaluator(LC, Bs) -> Expr when @@ -124,30 +141,78 @@ called_from_type_checker(Options) ->      lists:member(type_checker, Options).  transform_expression(LC, Bs0, WithLintErrors) -> -    L = 1, +    L = anno1(),      As = [{var,L,V} || {V,_Val} <- Bs0],      Ar = length(As),      F = {function,L,bar,Ar,[{clause,L,As,[],[?QLC_Q(L, L, L, L, LC, [])]}]}, -    Forms = [{attribute,L,file,{"foo",L}}, -             {attribute,L,module,foo}, F], -    State = #state{imp = false, -                   maxargs = ?EVAL_MAX_NUM_OF_ARGS, -                   records = record_attributes(Forms)}, +    Forms0 = [{attribute,L,file,{"foo",L}}, +              {attribute,L,module,foo}, F], +    {Forms, FormsNoShadows, State} = initiate(Forms0, false), +    NodeInfo = State#state.node_info,      Options = [], -    FormsNoShadows = no_shadows(Forms, State), -    case compile_messages(Forms, FormsNoShadows, Options, State) of -        {[],[],_Warnings} -> -            {NewForms,_State1} = transform(FormsNoShadows, State), -            {function,L,bar,Ar,[{clause,L,As,[],[NF]}]} =  -                lists:last(NewForms), -            {ok,NF}; -        {E0,Errors,_Warnings} when WithLintErrors -> -            {not_ok,mforms(error, E0 ++ Errors)}; -        {E0,Errors0,_Warnings} -> -            [{error,Reason} | _] = mforms(error, E0++Errors0), -            {not_ok, {error, ?APIMOD, Reason}} +    try compile_messages(Forms, FormsNoShadows, Options, State) of +        {Errors0,_Warnings} -> +            case restore_locations(Errors0, State) of +                [] -> +                    {NewForms,_State1} = transform(FormsNoShadows, State), +                    NewForms1 = restore_anno(NewForms, NodeInfo), +                    {function,L,bar,Ar,[{clause,L,As,[],[NF]}]} = +                        lists:last(NewForms1), +                    {ok,NF}; +                Errors when WithLintErrors -> +                    {not_ok,mforms(error, Errors)}; +                Errors -> +                    [{error,Reason} | _] = mforms(error, Errors), +                    {not_ok, {error, ?APIMOD, Reason}} +            end +    after +        true = ets:delete(NodeInfo)      end. +-ifdef(DEBUG). +-define(ILIM, 0). +-else. +-define(ILIM, 255). +-endif. + +initiate(Forms0, Imported) -> +    NodeInfo = ets:new(?APIMOD, []), +    true = ets:insert(NodeInfo, {var_n, ?ILIM}), +    exclude_integers_from_unique_line_numbers(Forms0, NodeInfo), +    ?DEBUG("node info0 ~p~n", +           [lists:sort(ets:tab2list(NodeInfo))]), +    State0 = #state{imp = Imported, +                    maxargs = ?EVAL_MAX_NUM_OF_ARGS, +                    records = record_attributes(Forms0), +                    node_info = NodeInfo}, +    Forms = save_anno(Forms0, NodeInfo), +    FormsNoShadows = no_shadows(Forms, State0), +    IntroVars = intro_variables(FormsNoShadows, State0), +    State = State0#state{intro_vars = IntroVars}, +    {Forms, FormsNoShadows, State}. + +%% Make sure restore_locations() does not confuse integers with (the +%% unique) line numbers. +exclude_integers_from_unique_line_numbers(Forms, NodeInfo) -> +    Integers = find_integers(Forms), +    lists:foreach(fun(I) -> ets:insert(NodeInfo, {I}) end, Integers). + +find_integers(Forms) -> +    F = fun(A) -> +                Fs1 = erl_parse:map_anno(fun(_) -> A end, Forms), +                ordsets:from_list(integers(Fs1, [])) +        end, +    ordsets:to_list(ordsets:intersection(F(anno0()), F(anno1()))). + +integers([E | Es], L) -> +    integers(Es, integers(E, L)); +integers(T, L) when is_tuple(T) -> +    integers(tuple_to_list(T), L); +integers(I, L) when is_integer(I), I > ?ILIM -> +    [I | L]; +integers(_, L) -> +    L. +  -define(I(I), {integer, L, I}).  -define(A(A), {atom, L, A}).  -define(V(V), {var, L, V}). @@ -164,9 +229,15 @@ mforms(Tag, L) ->  %% Avoid duplicated lint warnings and lint errors. Care has been taken  %% not to introduce unused variables in the transformed code.  %% -no_duplicates(Forms, Errors, Warnings0, ExtraWarnings, Options) -> +no_duplicates(Forms, Errors, Warnings0, ExtraWarnings0, Options) ->      %% Some mistakes such as "{X} =:= {}" are found by strong      %% validation as well as by qlc. Prefer the warnings from qlc: +    %%  The Compiler and qlc do not agree on the location of errors. +    %%  For now, qlc's messages about failing patterns and filters +    %%  are ignored. +    ExtraWarnings = [W || W={_File,[{_,qlc,Tag}]} <- +                              ExtraWarnings0, +                    not lists:member(Tag, [nomatch_pattern,nomatch_filter])],      Warnings1 = mforms(Warnings0) --          ([{File,[{L,v3_core,nomatch}]} ||               {File,[{L,qlc,M}]} <- mforms(ExtraWarnings), @@ -185,13 +256,22 @@ mforms(L) ->      lists:sort([{File,[M]} || {File,Ms} <- L, M <- Ms]).  mforms2(Tag, L) -> -    Line = 0, +    Line = anno0(),      ML = lists:flatmap(fun({File,Ms}) -> -                               [[{attribute,Line,file,{File,Line}}, {Tag,M}] || +                               [[{attribute,Line,file,{File,0}}, {Tag,M}] ||                                     M <- Ms]                         end, lists:sort(L)),      lists:flatten(lists:sort(ML)). +restore_locations([T | Ts], State) -> +    [restore_locations(T, State) | restore_locations(Ts, State)]; +restore_locations(T, State) when is_tuple(T) -> +    list_to_tuple(restore_locations(tuple_to_list(T), State)); +restore_locations(I, State) when I > ?ILIM -> +    restore_loc(I, State); +restore_locations(T, _State) -> +    T. +  is_qlc_q_imported(Forms) ->      [[] || {attribute,_,import,{?APIMOD,FAs}} <- Forms, {?Q,1} <- FAs] =/= []. @@ -212,13 +292,20 @@ compile_messages(Forms, FormsNoShadows, Options, State) ->                 (_QId, Q, GA, A) ->                      {Q,GA,A}              end, -    {_,BGens} = qual_fold(BGenF, [], [], FormsNoShadows, State), +    {_,BGens} = qual_fold(BGenF, [], [], Forms, State),      GenForm = used_genvar_check(FormsNoShadows, State),      ?DEBUG("GenForm = ~ts~n", [catch erl_pp:form(GenForm)]), -    WarnFun = fun(Id, LC, A) -> {tag_lines(LC, get_lcid_no(Id)), A} end, +    {GEs,_} = compile_forms([GenForm], Options), +    UsedGenVarMsgs = used_genvar_messages(GEs, State), +    NodeInfo = State#state.node_info, +    WarnFun = fun(_Id, LC, A) -> {lc_nodes(LC, NodeInfo), A} end,      {WForms,ok} = qlc_mapfold(WarnFun, ok, Forms, State), -    {Es,Ws} = compile_forms(WForms ++ [GenForm], Options), -    {badarg(Forms, State),tagged_messages(Es)++BGens,tagged_messages(Ws)}. +    {Es,Ws} = compile_forms(WForms, Options), +    LcEs = lc_messages(Es, NodeInfo), +    LcWs = lc_messages(Ws, NodeInfo), +    Errors = badarg(Forms, State) ++ UsedGenVarMsgs++LcEs++BGens, +    Warnings = LcWs, +    {Errors,Warnings}.  badarg(Forms, State) ->      F = fun(_Id, {lc,_L,_E,_Qs}=LC, Es) ->  @@ -230,54 +317,39 @@ badarg(Forms, State) ->      {_,E0} = qlc_mapfold(F, [], Forms, State),      E0. -tag_lines(E, No) -> -    map_lines(fun(Id) ->  -                      case is_lcid(Id) of -                          true -> Id; -                          false -> make_lcid(Id, No) -                      end -              end, E). - -map_lines(F, E) -> -    erl_lint:modify_line(E, F). - -tagged_messages(MsL) -> -    [{File, -      [{Loc,Mod,untag(T)} || {Loc0,Mod,T} <- Ms, -                             {true,Loc} <- [tloc(Loc0)]]} -     || {File,Ms} <- MsL] -    ++ +lc_nodes(E, NodeInfo) -> +    erl_parse:map_anno(fun(Anno) -> +                               N = erl_anno:line(Anno), +                               [{N, Data}] = ets:lookup(NodeInfo, N), +                               NData = Data#{inside_lc => true}, +                               true = ets:insert(NodeInfo, {N, NData}), +                               Anno +                       end, E). + +used_genvar_messages(MsL, S) ->      [{File,[{Loc,?APIMOD,{used_generator_variable,V}}]} -       || {_, Ms} <- MsL,  +       || {_, Ms} <- MsL,             {XLoc,erl_lint,{unbound_var,_}} <- Ms, -           {Loc,File,V} <- [extra(XLoc)]]. - -tloc({Id,Column}) -> -    {IsLcid,T} = tloc(Id), -    {IsLcid,{T,Column}}; -tloc(Id) -> -    IsLcid = is_lcid(Id), -    {IsLcid,case IsLcid of -                true -> get_lcid_line(Id); -                false -> any -            end}. - -extra({extra,Line,File,V}) -> -    {Line,File,V}; -extra({Line,Column}) -> -    case extra(Line) of -        {L,File,V} -> {{L,Column},File,V}; -        Else -> Else -    end; -extra(Else) -> -    Else. - -untag([E | Es]) -> [untag(E) | untag(Es)]; -untag(T) when is_tuple(T) -> list_to_tuple(untag(tuple_to_list(T))); -untag(E) -> -    case is_lcid(E) of -        true -> get_lcid_line(E); -        false -> E +           {Loc,File,V} <- [genvar_pos(XLoc, S)]]. + +lc_messages(MsL, NodeInfo) -> +    [{File,[{Loc,Mod,T} || {Loc,Mod,T} <- Ms, lc_loc(Loc, NodeInfo)]} || +        {File,Ms} <- MsL]. + +lc_loc(N, NodeInfo) -> +    case ets:lookup(NodeInfo, N) of +        [{N, #{inside_lc := true}}] -> +            true; +        [{N, _}] -> +            false +    end. + +genvar_pos(Location, S) -> +    case ets:lookup(S#state.node_info, Location) of +        [{Location, #{genvar_pos := Pos}}] -> +            Pos; +        [] -> +            Location      end.  %% -> [{Qid,[variable()]}]. @@ -293,6 +365,7 @@ untag(E) ->  %% variables (unless they are unsafe).  %%  intro_variables(FormsNoShadows, State) -> +    NodeInfo = State#state.node_info,      Fun = fun(QId, {T,_L,P0,_E0}=Q, {GVs,QIds}, Foo) when T =:= b_generate;                                                            T =:= generate ->                    PVs = qlc:var_ufold(fun({var,_,V}) -> {QId,V} end, P0), @@ -302,10 +375,11 @@ intro_variables(FormsNoShadows, State) ->                    %% where E is an LC expression consisting of a                    %% template mentioning all variables occurring in F.                    Vs = ordsets:to_list(qlc:vars(Filter0)), -                  Id = QId#qid.lcid, -                  LC1 = embed_vars(intro_set_line({QId,f1}, Vs), Id), -                  LC2 = embed_vars(intro_set_line({QId,f2}, Vs), Id), -                  AnyLine = -1, +                  AnyLine = anno0(), +                  Vars = [{var,AnyLine,V} || V <- Vs], +                  LC = embed_vars(Vars, AnyLine), +                  LC1 = intro_anno(LC, before, QId, NodeInfo), +                  LC2 = intro_anno(LC, 'after', QId, NodeInfo),                    Filter = {block,AnyLine,[LC1,Filter0,LC2]},                    {Filter,{GVs,[{QId,[]} | QIds]},Foo}            end, @@ -317,9 +391,15 @@ intro_variables(FormsNoShadows, State) ->      Es0 = compile_errors(FForms),      %% A variable is bound inside the filter if it is not bound before      %% the filter, but it is bound after the filter (obviously). -    Before = [{QId,V} || {{QId,f1},erl_lint,{unbound_var,V}} <- Es0], -    After = [{QId,V} || {{QId,f2},erl_lint,{unbound_var,V}} <- Es0], -    Unsafe = [{QId,V} || {{QId,f2},erl_lint,{unsafe_var,V,_Where}} <- Es0], +    Before = [{QId,V} || +                 {L,erl_lint,{unbound_var,V}} <- Es0, +                 {_L,{QId,before}} <- ets:lookup(NodeInfo, L)], +    After = [{QId,V} || +                {L,erl_lint,{unbound_var,V}} <- Es0, +                {_L,{QId,'after'}} <- ets:lookup(NodeInfo, L)], +    Unsafe = [{QId,V} || +                 {L,erl_lint,{unsafe_var,V,_Where}} <- Es0, +                 {_L,{QId,'after'}} <- ets:lookup(NodeInfo, L)],      ?DEBUG("Before = ~p~n", [Before]),      ?DEBUG("After = ~p~n", [After]),      ?DEBUG("Unsafe = ~p~n", [Unsafe]), @@ -328,9 +408,14 @@ intro_variables(FormsNoShadows, State) ->      I1 = family(IV ++ GenVars),      sofs:to_external(sofs:family_union(sofs:family(QIds), I1)). -intro_set_line(Tag, Vars) -> -    L = erl_parse:set_line(1, fun(_) -> Tag end), -    [{var,L,V} || V <- Vars]. +intro_anno(LC, Where, QId, NodeInfo) -> +    Data = {QId,Where}, +    Fun = fun(Anno) -> +                  Location = erl_anno:location(Anno), +                  true = ets:insert(NodeInfo, {Location,Data}), +                  Anno +          end, +    erl_parse:map_anno(Fun, save_anno(LC, NodeInfo)).  compile_errors(FormsNoShadows) ->      case compile_forms(FormsNoShadows, []) of @@ -341,11 +426,8 @@ compile_errors(FormsNoShadows) ->              lists:flatmap(fun({_File,Es}) -> Es end, Errors)      end. --define(MAX_NUM_OF_LINES, 23). % assume max 1^23 lines (> 8 millions) -  compile_forms(Forms0, Options) -> -    Forms = [F || F <- Forms0, element(1, F) =/= eof] ++  -            [{eof,1 bsl ?MAX_NUM_OF_LINES}], +    Forms = [F || F <- Forms0, element(1, F) =/= eof] ++  [{eof,anno0()}],      try           case compile:noenv_forms(Forms, compile_options(Options)) of              {ok, _ModName, Ws0} -> @@ -384,20 +466,23 @@ bitstr_options() ->  %% for each ListExpr. The expression mentions all introduced variables  %% occurring in ListExpr. Running the function through the compiler  %% yields error messages for erroneous use of introduced variables. -%% The messages have the form -%% {{extra,LineNo,File,Var},Module,{unbound_var,V}}, where Var is the -%% original variable name and V is the name invented by no_shadows/2.  %%  used_genvar_check(FormsNoShadows, State) -> -    F = fun(QId, {T, Ln, _P, LE}=Q, {QsIVs0, Exprs0}, IVsSoFar0)  +    NodeInfo = State#state.node_info, +    F = fun(QId, {T, Ln, _P, LE}=Q, {QsIVs0, Exprs0}, IVsSoFar0)                                     when T =:= b_generate; T =:= generate -> -                F = fun({var, _, V}=Var) ->  -                            {var, L, OrigVar} = undo_no_shadows(Var), -                            AF = fun(Line) ->  -                                         {extra, Line, get(?QLC_FILE), OrigVar} -                                 end, -                            L2 = erl_parse:set_line(L, AF), -                            {var, L2, V}  +                F = fun(Var) -> +                            {var, Anno0, OrigVar} = +                                undo_no_shadows(Var, State), +                            {var, Anno, _} = NewVar = save_anno(Var, NodeInfo), +                            Location0 = erl_anno:location(Anno0), +                            Location = erl_anno:location(Anno), +                            [{Location, Data}] = +                                ets:lookup(NodeInfo, Location), +                            Pos = {Location0,get(?QLC_FILE),OrigVar}, +                            NData = Data#{genvar_pos => Pos}, +                            true = ets:insert(NodeInfo, {Location, NData}), +                            NewVar                      end,                  Vs = [Var || {var, _, V}=Var <- qlc:var_fold(F, [], LE),                               lists:member(V, IVsSoFar0)], @@ -411,12 +496,12 @@ used_genvar_check(FormsNoShadows, State) ->                  {QsIVs, IVsSoFar} = q_intro_vars(QId, QsIVs0, IVsSoFar0),                  {Filter, {QsIVs, Exprs}, IVsSoFar}          end, -    IntroVars = intro_variables(FormsNoShadows, State), -    Acc0 = {IntroVars, [{atom, 0, true}]}, +    Acc0 = {State#state.intro_vars, [{atom, anno0(), true}]},      {_, {[], Exprs}} = qual_fold(F, Acc0, [], FormsNoShadows, State),      FunctionNames = [Name || {function, _, Name, _, _} <- FormsNoShadows],      UniqueFName = qlc:aux_name(used_genvar, 1, sets:from_list(FunctionNames)), -    {function,0,UniqueFName,0,[{clause,0,[],[],lists:reverse(Exprs)}]}. +    A = anno0(), +    {function,A,UniqueFName,0,[{clause,A,[],[],lists:reverse(Exprs)}]}.  q_intro_vars(QId, [{QId, IVs} | QsIVs], IVsSoFar) -> {QsIVs, IVs ++ IVsSoFar}. @@ -514,7 +599,8 @@ q_intro_vars(QId, [{QId, IVs} | QsIVs], IVsSoFar) -> {QsIVs, IVs ++ IVsSoFar}.  %%   (calling LEf returns the objects generated by LE).  transform(FormsNoShadows, State) -> -    IntroVars = intro_variables(FormsNoShadows, State), +    _ = erlang:system_flag(backtrace_depth, 500), +    IntroVars = State#state.intro_vars,      AllVars = sets:from_list(ordsets:to_list(qlc:vars(FormsNoShadows))),      ?DEBUG("AllVars = ~p~n", [sets:to_list(AllVars)]),      F1 = fun(QId, {generate,_,P,LE}, Foo, {GoI,SI}) -> @@ -588,8 +674,8 @@ transform(FormsNoShadows, State) ->                                              [{match,L,{var,L,Fun},FunC},                                               {call,L,{var,L,Fun},As0}]}]}},                   {ok, OrigE0} = dict:find(Id, Source), -                 OrigE = undo_no_shadows(OrigE0), -                 QCode = qcode(OrigE, XQCs, Source, L), +                 OrigE = undo_no_shadows(OrigE0, State), +                 QCode = qcode(OrigE, XQCs, Source, L, State),                   Qdata = qdata(XQCs, L),                   TemplateInfo =                        template_columns(Qs, E, AllIVs, Dependencies, State), @@ -598,7 +684,7 @@ transform(FormsNoShadows, State) ->                   Opt = opt_info(TemplateInfo, SizeInfo, JoinInfo, MSQs, L,                                  EqColumnConstants, EqualColumnConstants),                   LCTuple =  -                     case qlc_kind(OrigE, Qs) of +                     case qlc_kind(OrigE, Qs, State) of                           qlc ->                               {tuple,L,[?A(qlc_v1),FunW,QCode,Qdata,Opt]};                           {simple, PL, LE, V} -> @@ -612,7 +698,7 @@ transform(FormsNoShadows, State) ->           end,      {NForms,{[],XW}} = qlc_mapfold(F2, {IntroVars,[]}, ModifiedForms1, State),      display_forms(NForms), -    {restore_line_numbers(NForms), State#state{xwarnings = XW}}. +    {NForms, State#state{xwarnings = XW}}.  join_kind(Qs, LcL, AllIVs, Dependencies, State) ->      {EqualCols2, EqualColsN} = equal_columns(Qs, AllIVs, Dependencies, State), @@ -623,20 +709,21 @@ join_kind(Qs, LcL, AllIVs, Dependencies, State) ->      if           EqualColsN =/= []; MatchColsN =/= [] ->               {[],  -             [{get(?QLC_FILE),[{abs(LcL),?APIMOD,too_complex_join}]}]}; +             [{get(?QLC_FILE),[{LcL,?APIMOD,too_complex_join}]}]};          EqualCols2 =:= [], MatchCols2 =:= [] ->              {[], []};          length(Tables) > 2 ->               {[],  -             [{get(?QLC_FILE),[{abs(LcL),?APIMOD,too_many_joins}]}]}; +             [{get(?QLC_FILE),[{LcL,?APIMOD,too_many_joins}]}]};          EqualCols2 =:= MatchCols2 ->              {EqualCols2, []};          true ->               {{EqualCols2, MatchCols2}, []}      end. -qlc_kind(OrigE, Qs) -> -    {OrigFilterData, OrigGeneratorData} = qual_data(undo_no_shadows(Qs)), +qlc_kind(OrigE, Qs, State) -> +    {OrigFilterData, OrigGeneratorData} = +        qual_data(undo_no_shadows(Qs, State)),      OrigAllFilters = filters_as_one(OrigFilterData),      {_FilterData, GeneratorData} = qual_data(Qs),      case {OrigE, OrigAllFilters, OrigGeneratorData} of @@ -663,12 +750,12 @@ warn_failing_qualifiers(Qualifiers, AllIVs, Dependencies, State) ->          lists:foldl(fun({_QId,{fil,_Filter}}, {[]=Frames,Warnings}) ->                              {Frames,Warnings};                         ({_QId,{fil,Filter}}, {Frames,Warnings}) -> -                        case filter(set_line(Filter, 0), Frames, BindFun,  +                        case filter(reset_anno(Filter), Frames, BindFun,                                      State, Imported) of                              [] ->                                  {[],                                   [{get(?QLC_FILE), -                                   [{abs_loc(element(2, Filter)),?APIMOD, +                                   [{loc(element(2, Filter)),?APIMOD,                                       nomatch_filter}]} | Warnings]};                              Frames1 ->                                   {Frames1,Warnings} @@ -678,7 +765,7 @@ warn_failing_qualifiers(Qualifiers, AllIVs, Dependencies, State) ->                              {failed, _, _} ->                                   {Frames,                                   [{get(?QLC_FILE), -                                   [{abs_loc(element(2, Pattern)),?APIMOD, +                                   [{loc(element(2, Pattern)),?APIMOD,                                       nomatch_pattern}]} | Warnings]};                              _ ->                                  {Frames,Warnings} @@ -751,8 +838,8 @@ opt_constants(L, ColumnConstants) ->       || IdNo <- Ns]       ++ [{clause,L,[?V('_')],[],[?A(no_column_fun)]}]. -abstr(Term, Line) -> -    erl_parse:abstract(Term, Line). +abstr(Term, Anno) -> +    erl_parse:abstract(Term, loc(Anno)).  %% Extra generators are introduced for join.  join_quals(JoinInfo, QCs, L, LcNo, ExtraConstants, AllVars) -> @@ -837,9 +924,10 @@ join_handle(AP, L, [F, H, O, C], Constants) ->          {{var, _, _}, []} ->              {'fun',L,{clauses,[{clause,L,[H],[],[H]}]}};          _ -> +            A = anno0(),              G0 = [begin -                      Call = {call,0,{atom,0,element},[{integer,0,Col},O]}, -                      list2op([{op,0,Op,Con,Call} || {Con,Op} <- Cs], 'or') +                      Call = {call,A,{atom,A,element},[{integer,A,Col},O]}, +                      list2op([{op,A,Op,Con,Call} || {Con,Op} <- Cs], 'or')                    end || {Col,Cs} <- Constants],              G = if G0 =:= [] -> G0; true -> [G0] end,              CC1 = {clause,L,[AP],G,[{cons,L,O,closure({call,L,F,[F,C]},L)}]}, @@ -876,14 +964,15 @@ join_handle_constants(QId, ExtraConstants) ->  %% order the traverse fun would return them.  column_fun(Columns, QualifierNumber, LcL) -> +    A = anno0(),      ColCls0 =           [begin               true = Vs0 =/= [], % at least one value to look up               Vs1 = list2cons(Vs0), -             Fils1 = {tuple,0,[{atom,0,FTag}, +             Fils1 = {tuple,A,[{atom,A,FTag},                                 lists:foldr -                                   (fun(F, A) -> {cons,0,{integer,0,F},A}  -                                    end, {nil,0}, Fils)]}, +                                   (fun(F, Ac) -> {cons,A,{integer,A,F},Ac} +                                    end, {nil,A}, Fils)]},               Tag = case ordsets:to_list(qlc:vars(Vs1)) of                         Imp when length(Imp) > 0, % imported vars                                  length(Vs0) > 1 -> @@ -891,13 +980,13 @@ column_fun(Columns, QualifierNumber, LcL) ->                         _ ->                             values                     end, -             Vs = {tuple,0,[{atom,0,Tag},Vs1,Fils1]}, -             {clause,0,[erl_parse:abstract(Col)],[],[Vs]} +             Vs = {tuple,A,[{atom,A,Tag},Vs1,Fils1]}, +             {clause,A,[erl_parse:abstract(Col)],[],[Vs]}           end ||              {{CIdNo,Col}, Vs0, {FTag,Fils}} <- Columns,              CIdNo =:= QualifierNumber] -        ++ [{clause,0,[{var,0,'_'}],[],[{atom,0,false}]}], -    ColCls = set_line(ColCls0, LcL), +        ++ [{clause,A,[{var,A,'_'}],[],[{atom,A,false}]}], +    ColCls = set_anno(ColCls0, LcL),      {'fun', LcL, {clauses, ColCls}}.  %% Tries to find columns of the template that (1) are equal to (or @@ -920,7 +1009,7 @@ template_columns(Qs0, E0, AllIVs, Dependencies, State) ->      MatchColumns = eq_columns2(Qs, AllIVs, Dependencies, State),      Equal = template_cols(EqualColumns),       Match = template_cols(MatchColumns), -    L = 0, +    L = anno0(),      if           Match =:= Equal ->               [{?V('_'), Match}]; @@ -947,7 +1036,7 @@ template_cols(ColumnClasses) ->  template_as_pattern(E) ->      P = simple_template(E), -    {?TID,foo,foo,{gen,P,{nil,0}}}. +    {?TID,foo,foo,{gen,P,{nil,anno0()}}}.  simple_template({call,L,{remote,_,{atom,_,erlang},{atom,_,element}}=Call,                   [{integer,_,I}=A1,A2]}) when I > 0 -> @@ -1004,10 +1093,10 @@ match_spec_quals(Template, Dependencies, Qualifiers, State) ->                       GQId =:= QId2,                       {FQId,{fil,F}}=Filter <- Filters, % guard filters only                       FQId =:= QId]  -               ++ [{GId#qid.no,Pattern,[],{atom,0,true}} ||  +               ++ [{GId#qid.no,Pattern,[],{atom,anno0(),true}} ||                        {GId,{gen,Pattern,_}} <- GeneratorData,                        lists:member(GId, NoFilterGIds)], -    E = {nil, 0}, +    E = {nil, anno0()},      GF = [{{GNum,Pattern},Filter} ||                {GNum,Pattern,Filter,F} <- Candidates,               no =/= try_ms(E, Pattern, F, State)], @@ -1024,7 +1113,7 @@ match_spec_quals(Template, Dependencies, Qualifiers, State) ->          %% expressione can be replaced by a match specification.          [{GNum, AbstrMS, all}]      catch _:_ -> -        {TemplVar, _} = anon_var({var,0,'_'}, 0), +        {TemplVar, _} = anon_var({var,anno0(),'_'}, 0),          [one_gen_match_spec(GNum, Pattern, GFilterData, State, TemplVar) ||              {{GNum,Pattern},GFilterData} <- GFFL]      end. @@ -1038,7 +1127,7 @@ gen_ms(E, Pattern, GFilterData, State) ->      {ok, MS, AMS} = try_ms(E, Pattern, filters_as_one(GFilterData), State),      case MS of          [{'$1',[true],['$1']}] -> -            {atom, 0, no_match_spec}; +            {atom, anno0(), no_match_spec};          _ ->              AMS      end. @@ -1060,7 +1149,7 @@ pattern_as_template({match,_,_E,{var,_,_}=V}=P, _TemplVar) ->  pattern_as_template({match,_,{var,_,_}=V,_E}=P, _TemplVar) ->      {V, P};  pattern_as_template(E, TemplVar) -> -    L = 0, +    L = anno0(),      {TemplVar, {match, L, E, TemplVar}}.  %% Tries to find columns which are compared or matched against @@ -1203,7 +1292,7 @@ lu_skip(ColConstants, FilterData, PatternFrame, PatternVars,      ColFil = [{Column, FId#qid.no} ||                   {FId,{fil,Fil}} <-                        filter_list(FilterData, Dependencies, State), -                 [] =/= (SFs = safe_filter(set_line(Fil, 0), PatternFrames, +                 [] =/= (SFs = safe_filter(reset_anno(Fil), PatternFrames,                                             BindFun, State, Imported)),                   {GId,PV} <- PatternVars,                   [] =/=  @@ -1392,7 +1481,7 @@ join_skip(JoinClasses, FilterData, PatternFrame, PatternVars, Dependencies,                       JF = unify(JoinOp, V1, V2, JF2, BindFun, Imported),                       %% "Run" the filter: -                     SFs = safe_filter(set_line(Fil, 0), PatternFrames, +                     SFs = safe_filter(reset_anno(Fil), PatternFrames,                                         BindFun, State, Imported),                       JImp = qlc:vars([SFs, JF]), % kludge                       lists:all(fun(Frame) ->  @@ -1403,7 +1492,7 @@ join_skip(JoinClasses, FilterData, PatternFrame, PatternVars, Dependencies,  filter_info(FilterData, AllIVs, Dependencies, State) ->      FilterList = filter_list(FilterData, Dependencies, State), -    Filter0 = set_line(filters_as_one(FilterList), 0), +    Filter0 = reset_anno(filters_as_one(FilterList)),      Anon0 = 0,      {Filter, Anon1} = anon_var(Filter0, Anon0),      Imported = ordsets:subtract(qlc:vars(Filter), % anonymous too @@ -1510,7 +1599,7 @@ pattern(P0, AnonI, Frame0, BindFun, State) ->           catch _:_ -> P0 % template, records already expanded           end,      %% Makes test for equality simple: -    P2 = set_line(P1, 0), +    P2 = reset_anno(P1),      {P3, AnonN} = anon_var(P2, AnonI),      {P4, F1} = match_in_pattern(tuple2cons(P3), Frame0, BindFun),      {P, F2} = element_calls(P4, F1, BindFun, _Imp=[]), % kludge for templates @@ -1550,8 +1639,11 @@ anon_var(E, AnonI) ->                     (Var, N) -> {Var, N}                  end, AnonI, E). -set_line(T, L) -> -    map_lines(fun(_L) -> L end, T). +reset_anno(T) -> +    set_anno(T, anno0()). + +set_anno(T, A) -> +    erl_parse:map_anno(fun(_L) -> A end, T).  -record(fstate, {state, bind_fun, imported}). @@ -1673,7 +1765,7 @@ frames_to_columns(Fs, PatternVars, DerefFun, SelectorFun, Imp, CompOp) ->      %% same variables have to be the representatives in every frame.)      SizesVarsL =          [begin  -             PatVar = {var,0,PV}, +             PatVar = {var,anno0(),PV},               PatternSizes = [pattern_size([F], PatVar, false) ||                                   F <- Fs],               MaxPZ = lists:max([0 | PatternSizes -- [undefined]]), @@ -1692,8 +1784,8 @@ frames_to_columns(Fs, PatternVars, DerefFun, SelectorFun, Imp, CompOp) ->  frames2cols(Fs, PatN, PatSizes, Vars, DerefFun, SelectorFun, CompOp) ->      Rs = [ begin                 RL = [{{PatN,Col},cons2tuple(element(2, Const))} || -                        {V, Col} <- lists:zip(sublist(Vars, PatSz), -                                              seq(1, PatSz)), +                        {V, Col} <- lists:zip(lists:sublist(Vars, PatSz), +                                              lists:seq(1, PatSz)),                          %% Do not handle the case where several                          %% values compare equal, e.g. "X =:= 1                          %% andalso X == 1.0". Looking up both @@ -1722,11 +1814,11 @@ frames2cols(Fs, PatN, PatSizes, Vars, DerefFun, SelectorFun, CompOp) ->      [C || {_,Vs}=C <- sofs:to_external(Cs), not col_ignore(Vs, CompOp)].  pat_vars(N) -> -    [unique_var() || _ <- seq(1, N)]. +    [unique_var() || _ <- lists:seq(1, N)].  pat_tuple(Sz, Vars) when is_integer(Sz), Sz > 0 ->      TupleTail = unique_var(), -    {cons_tuple, list2cons(sublist(Vars, Sz) ++ TupleTail)}; +    {cons_tuple, list2cons(lists:sublist(Vars, Sz) ++ TupleTail)};  pat_tuple(_, _Vars) ->      unique_var(). @@ -1740,7 +1832,7 @@ col_ignore(Vs, '==') ->  pattern_sizes(PatternVars, Fs) ->      [{QId#qid.no, Size} ||           {QId,PV} <- PatternVars, -        undefined =/= (Size = pattern_size(Fs, {var,0,PV}, true))]. +        undefined =/= (Size = pattern_size(Fs, {var,anno0(),PV}, true))].  pattern_size(Fs, PatternVar, Exact) ->      Fun = fun(F) -> (deref_pattern(_Imported = []))(PatternVar, F) end, @@ -1768,7 +1860,8 @@ prep_expr(E, F, S, BF, Imported) ->      element_calls(tuple2cons(expand_expr_records(E, S)), F, BF, Imported).  unify_column(Frame, Var, Col, BindFun, Imported) -> -    Call = {call,0,{atom,0,element},[{integer,0,Col}, {var,0,Var}]}, +    A = anno0(), +    Call = {call,A,{atom,A,element},[{integer,A,Col}, {var,A,Var}]},      element_calls(Call, Frame, BindFun, Imported).  %% cons_tuple is used for representing {V1, ..., Vi | TupleTail}. @@ -1800,19 +1893,21 @@ element_calls(E, F, _BF, _Imported) ->      {E, F}.  unique_var() -> -    {var, 0, make_ref()}. +    {var, anno0(), make_ref()}.  is_unique_var({var, _L, V}) ->      is_reference(V).  expand_pattern_records(P, State) -> -    E = {'case',0,{atom,0,true},[{clause,0,[P],[],[{atom,0,true}]}]}, -    {'case',_,_,[{clause,0,[NP],_,_}]} = expand_expr_records(E, State), +    A = anno0(), +    E = {'case',A,{atom,A,true},[{clause,A,[P],[],[{atom,A,true}]}]}, +    {'case',_,_,[{clause,A,[NP],_,_}]} = expand_expr_records(E, State),      NP.  expand_expr_records(E, State) ->      RecordDefs = State#state.records, -    Forms = RecordDefs ++ [{function,1,foo,0,[{clause,1,[],[],[pe(E)]}]}], +    A = anno1(), +    Forms = RecordDefs ++ [{function,A,foo,0,[{clause,A,[],[],[pe(E)]}]}],      [{function,_,foo,0,[{clause,_,[],[],[NE]}]}] =           erl_expand_records:module(Forms, [no_strict_record_tests]),      NE. @@ -2126,15 +2221,15 @@ tuple2cons(E) ->      E.  list2cons([E | Es]) -> -    {cons, 0, E, list2cons(Es)}; +    {cons, anno0(), E, list2cons(Es)};  list2cons([]) -> -    {nil, 0}; +    {nil, anno0()};  list2cons(E) ->      E.  %% Returns {..., Variable} if Variable is a tuple tail.  cons2tuple({cons_tuple, Es}) -> -    {tuple, 0, cons2list(Es)}; +    {tuple, anno0(), cons2list(Es)};  cons2tuple(T) when is_tuple(T) ->      list_to_tuple(cons2tuple(tuple_to_list(T)));  cons2tuple([E | Es]) -> @@ -2173,11 +2268,10 @@ bindings_subset(F1, F2, Imp) ->  %% not to have guard semantics, affected filters will have to be  %% recognized and excluded here as well.  try_ms(E, P, Fltr, State) -> -    L = 1, +    L = anno1(),      Fun =  {'fun',L,{clauses,[{clause,L,[P],[[Fltr]],[E]}]}},      Expr = {call,L,{remote,L,{atom,L,ets},{atom,L,fun2ms}},[Fun]}, -    Form0 = {function,L,foo,0,[{clause,L,[],[],[Expr]}]}, -    Form = restore_line_numbers(Form0), +    Form = {function,L,foo,0,[{clause,L,[],[],[Expr]}]},      X = ms_transform:parse_transform(State#state.records ++ [Form], []),      case catch           begin @@ -2194,11 +2288,11 @@ try_ms(E, P, Fltr, State) ->      end.  filters_as_one([]) -> -    {atom, 0, true}; +    {atom, anno0(), true};  filters_as_one(FilterData) ->      [{_,{fil,Filter1}} | Filters] = lists:reverse(FilterData),      lists:foldr(fun({_QId,{fil,Filter}}, AbstF) -> -                        {op,0,'andalso',Filter,AbstF} +                        {op,anno0(),'andalso',Filter,AbstF}                  end, Filter1, Filters).  qual_data(Qualifiers) -> @@ -2233,38 +2327,40 @@ qdata([], L) ->      {nil,L}.  qcon(Cs) -> -    list2cons([{tuple,0,[{integer,0,Col},list2cons(qcon1(ConstOps))]} ||  +    A = anno0(), +    list2cons([{tuple,A,[{integer,A,Col},list2cons(qcon1(ConstOps))]} ||                    {Col,ConstOps} <- Cs]).  qcon1(ConstOps) -> -    [{tuple,0,[Const,abstr(Op, 0)]} || {Const,Op} <- ConstOps]. +    A = anno0(), +    [{tuple,A,[Const,abstr(Op, A)]} || {Const,Op} <- ConstOps].  %% The original code (in Source) is used for filters and the template  %% since the translated code can have QLCs and we don't want them to  %% be visible. -qcode(E, QCs, Source, L) -> +qcode(E, QCs, Source, L, State) ->      CL = [begin                Bin = term_to_binary(C, [compressed]),                {bin, L, [{bin_element, L,                            {string, L, binary_to_list(Bin)},                           default, default}]}            end || {_,C} <- lists:keysort(1, [{qlc:template_state(),E} |  -                                            qcode(QCs, Source)])], +                                            qcode(QCs, Source, State)])],      {'fun', L, {clauses, [{clause, L, [], [], [{tuple, L, CL}]}]}}. -qcode([{_QId, {_QIvs, {{gen,P,_LE,_GV}, GoI, _SI}}} | QCs], Source) -> -    [{GoI,undo_no_shadows(P)} | qcode(QCs, Source)]; -qcode([{QId, {_QIVs, {{fil,_F}, GoI, _SI}}} | QCs], Source) -> +qcode([{_QId, {_QIvs, {{gen,P,_LE,_GV}, GoI, _SI}}} | QCs], Source, State) -> +    [{GoI,undo_no_shadows(P, State)} | qcode(QCs, Source, State)]; +qcode([{QId, {_QIVs, {{fil,_F}, GoI, _SI}}} | QCs], Source, State) ->      {ok,OrigF} = dict:find(QId, Source), -    [{GoI,undo_no_shadows(OrigF)} | qcode(QCs, Source)]; -qcode([], _Source) -> +    [{GoI,undo_no_shadows(OrigF, State)} | qcode(QCs, Source, State)]; +qcode([], _Source, _State) ->      [].  closure(Code, L) ->      {'fun',L,{clauses,[{clause,L,[],[],[Code]}]}}. -simple(L, Var, Init, Line) -> -    {tuple,L,[?A(simple_v1),?A(Var),Init,?I(Line)]}. +simple(L, Var, Init, Anno) -> +    {tuple,L,[?A(simple_v1),?A(Var),Init,abstr(loc(Anno), Anno)]}.  clauses([{QId,{QIVs,{QualData,GoI,S}}} | QCs], RL, Fun, Go, NGV, E, IVs,St) ->      ?DEBUG("QIVs = ~p~n", [QIVs]), @@ -2426,19 +2522,22 @@ aux_var(Name, LcN, QN, N, AllVars) ->      qlc:aux_name(lists:concat([Name, LcN, '_', QN, '_']), N, AllVars).  no_compiler_warning(L) -> -    erl_parse:set_line(L, fun(Line) -> -abs(Line) end). +    Anno = erl_anno:new(L), +    erl_anno:set_generated(true, Anno). -abs_loc(L) -> -    loc(erl_parse:set_line(L, fun(Line) -> abs(Line) end)). - -loc(L) -> -    {location,Location} = erl_parse:get_attribute(L, location), -    Location. +loc(A) -> +    erl_anno:location(A).  list2op([E], _Op) ->      E;  list2op([E | Es], Op) -> -    {op,0,Op,E,list2op(Es, Op)}. +    {op,anno0(),Op,E,list2op(Es, Op)}. + +anno0() -> +    erl_anno:new(0). + +anno1() -> +    erl_anno:new(1).  %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% @@ -2491,13 +2590,61 @@ qlcmf(T, _F, _Imp, A, No) ->  occ_vars(E) ->      qlc:var_fold(fun({var,_L,V}) -> V end, [], E). +%% Every Anno is replaced by a unique number. The number is used in a +%% table that holds data about the abstract node where Anno resides. +%% In particular, the original location is kept there, so that the +%% original abstract code can be re-created. +save_anno(Abstr, NodeInfo) -> +    F = fun(Anno) -> +                N = next_slot(NodeInfo), +                Location = erl_anno:location(Anno), +                Data = {N, #{location => Location}}, +                true = ets:insert(NodeInfo, Data), +                erl_anno:new(N) +        end, +    erl_parse:map_anno(F, Abstr). + +next_slot(T) -> +    I = ets:update_counter(T, var_n, 1), +    case ets:lookup(T, I) of +        [] -> +            I; +        _ -> +            next_slot(T) +    end. + +restore_anno(Abstr, NodeInfo) -> +    F = fun(Anno) -> +                Location = erl_anno:location(Anno), +                case ets:lookup(NodeInfo, Location) of +                    [{Location, Data}] -> +                        OrigLocation = maps:get(location, Data), +                        erl_anno:set_location(OrigLocation, Anno); +                    [{Location}] -> % generated code +                        Anno; +                    [] -> +                        Anno +                end +        end, +    erl_parse:map_anno(F, Abstr). + +restore_loc(Location, #state{node_info = NodeInfo}) -> +  case ets:lookup(NodeInfo, Location) of +      [{Location, #{location := OrigLocation}}] -> +          OrigLocation; +      [{Location}] -> +          Location; +      [] -> +          Location +  end. +  no_shadows(Forms0, State) ->      %% Variables that may shadow other variables are introduced in      %% LCs and Funs. Such variables (call them SV, Shadowing      %% Variables) are now renamed. Each (new) occurrence in a pattern      %% is assigned an index (integer), unique in the file.       %% -    %% The state {LastIndex,ActiveVars,UsedVars,AllVars,Singletons} +    %% The state {LastIndex,ActiveVars,UsedVars,AllVars,Singletons,State}      %% holds the last index used for each SV (LastIndex), the SVs in      %% the current scope (ActiveVars), used SVs (UsedVars, the indexed      %% name is the key), all variables occurring in the file @@ -2507,16 +2654,15 @@ no_shadows(Forms0, State) ->      %% the indexed name of an SV occurs in the file, next index is      %% tried (to avoid mixing up introduced names with existing ones).      %% -    %% The original names of variables are kept in the line number -    %% position of the abstract code: {var, {nos, OriginalName, L}, -    %% NewName}. undo_no_shadows/1 re-creates the original code. +    %% The original names of variables are kept in a table in State. +    %% undo_no_shadows/2 re-creates the original code.      AllVars = sets:from_list(ordsets:to_list(qlc:vars(Forms0))),      ?DEBUG("nos AllVars = ~p~n", [sets:to_list(AllVars)]),      VFun = fun(_Id, LC, Vs) -> nos(LC, Vs) end,      LI = ets:new(?APIMOD,[]),      UV = ets:new(?APIMOD,[]),      D0 = dict:new(), -    S1 = {LI, D0, UV, AllVars, []}, +    S1 = {LI, D0, UV, AllVars, [], State},      _ = qlc_mapfold(VFun, S1, Forms0, State),      ?DEBUG("UsedIntroVars = ~p~n", [ets:match_object(UV, '_')]),      Singletons = ets:select(UV, ets:fun2ms(fun({K,0}) -> K  end)), @@ -2524,7 +2670,7 @@ no_shadows(Forms0, State) ->      true = ets:delete_all_objects(LI),      true = ets:delete_all_objects(UV),      %% Do it again, this time we know which variables are singletons. -    S2 = {LI, D0, UV, AllVars, Singletons}, +    S2 = {LI, D0, UV, AllVars, Singletons, State},      {Forms,_} = qlc_mapfold(VFun, S2, Forms0, State),      true = ets:delete(LI),      true = ets:delete(UV), @@ -2568,11 +2714,11 @@ nos({lc,L,E0,Qs0}, S) ->      {Qs, S1} = lists:mapfoldl(F, S, Qs0),      {E, _} = nos(E0, S1),      {{lc,L,E,Qs}, S}; -nos({var,L,V}=Var, {_LI,Vs,UV,_A,_Sg}=S) when V =/= '_' -> +nos({var,L,V}=Var, {_LI,Vs,UV,_A,_Sg,State}=S) when V =/= '_' ->      case used_var(V, Vs, UV) of          {true, VN} -> -            NL = nos_var(L, V), -            {{var,NL,VN}, S}; +            nos_var(L, V, State), +            {{var,L,VN}, S};          false ->              {Var, S}      end; @@ -2590,7 +2736,7 @@ nos_pattern([P0 | Ps0], S0, PVs0) ->      {P, S1, PVs1} = nos_pattern(P0, S0, PVs0),      {Ps, S, PVs} = nos_pattern(Ps0, S1, PVs1),      {[P | Ps], S, PVs}; -nos_pattern({var,L,V}, {LI,Vs0,UV,A,Sg}, PVs0) when V =/= '_' -> +nos_pattern({var,L,V}, {LI,Vs0,UV,A,Sg,State}, PVs0) when V =/= '_' ->      {Name, Vs, PVs} =           case lists:keyfind(V, 1, PVs0) of              {V, VN} -> @@ -2604,16 +2750,25 @@ nos_pattern({var,L,V}, {LI,Vs0,UV,A,Sg}, PVs0) when V =/= '_' ->                      end,                  {N, Vs1, [{V,VN} | PVs0]}          end, -    NL = nos_var(L, V), -    {{var,NL,Name}, {LI,Vs,UV,A,Sg}, PVs}; +    nos_var(L, V, State), +    {{var,L,Name}, {LI,Vs,UV,A,Sg,State}, PVs};  nos_pattern(T, S0, PVs0) when is_tuple(T) ->      {TL, S, PVs} = nos_pattern(tuple_to_list(T), S0, PVs0),      {list_to_tuple(TL), S, PVs};  nos_pattern(T, S, PVs) ->      {T, S, PVs}. -nos_var(L, Name) -> -    erl_parse:set_line(L, fun(Line) -> {nos,Name,Line} end). +nos_var(Anno, Name, State) -> +    NodeInfo = State#state.node_info, +    Location = erl_anno:location(Anno), +    case ets:lookup(NodeInfo, Location) of +        [{Location, #{name := _}}] -> +            true; +        [{Location, Data}] -> +            true = ets:insert(NodeInfo, {Location, Data#{name => Name}}); +        [] -> % cannot happen +            true +    end.  used_var(V, Vs, UV) ->      case dict:find(V, Vs) of @@ -2638,69 +2793,30 @@ next_var(V, Vs, AllVars, LI, UV) ->                   {VN, NVs}      end. -undo_no_shadows(E) -> -    var_map(fun undo_no_shadows1/1, E). - -undo_no_shadows1({var, L, _}=Var) -> -    case erl_parse:get_attribute(L, line) of -        {line,{nos,V,_VL}} -> -            NL = erl_parse:set_line(L, fun({nos,_V,VL}) -> VL end), -            undo_no_shadows1({var, NL, V}); -        _Else -> -            Var -    end. - -restore_line_numbers(E) -> -    var_map(fun restore_line_numbers1/1, E). +undo_no_shadows(E, State) -> +    var_map(fun(Anno) -> undo_no_shadows1(Anno, State) end, E). -restore_line_numbers1({var, L, V}=Var) -> -    case erl_parse:get_attribute(L, line) of -        {line,{nos,_,_}} -> -            NL = erl_parse:set_line(L, fun({nos,_V,VL}) -> VL end), -            restore_line_numbers1({var, NL, V}); -        _Else -> +undo_no_shadows1({var, Anno, _}=Var, State) -> +    Location = erl_anno:location(Anno), +    NodeInfo = State#state.node_info, +    case ets:lookup(NodeInfo, Location) of +        [{Location, #{name := Name}}] -> +            {var, Anno, Name}; +        _ ->              Var      end.  %% QLC identifier.   %% The first one encountered in the file has No=1. -make_lcid(Attrs, No) when is_integer(No), No > 0 -> -    F = fun(Line) when is_integer(Line), Line < (1 bsl ?MAX_NUM_OF_LINES) -> -                sgn(Line) * ((No bsl ?MAX_NUM_OF_LINES) + sgn(Line) * Line) -        end, -    erl_parse:set_line(Attrs, F). - -is_lcid(Attrs) -> -    try  -        {line,Id} = erl_parse:get_attribute(Attrs, line), -        is_integer(Id) andalso (abs(Id) > (1 bsl ?MAX_NUM_OF_LINES)) -    catch _:_ -> -        false -    end. - -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)). +make_lcid(Anno, No) when is_integer(No), No > 0 -> +    {No, erl_anno:line(Anno)}. -sgn(X) when X >= 0 -> -    1; -sgn(X) when X < 0 -> -    -1. +get_lcid_no({No, _Line}) -> +    No. -seq(S, E) when S - E =:= 1 -> -    []; -seq(S, E) ->  -    lists:seq(S, E). - -sublist(_, 0) -> -    []; -sublist(L, N) -> -    lists:sublist(L, N). +get_lcid_line({_No, Line}) -> +    Line.  qid(LCId, No) ->      #qid{no = No, lcid = LCId}. diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl index 679c13f0cf..c6ba574ff4 100644 --- a/lib/stdlib/src/shell.erl +++ b/lib/stdlib/src/shell.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %% -%% Copyright Ericsson AB 1996-2013. All Rights Reserved. +%% Copyright Ericsson AB 1996-2015. All Rights Reserved.  %%  %% The contents of this file are subject to the Erlang Public License,  %% Version 1.1, (the "License"); you may not use this file except in @@ -314,7 +314,8 @@ prompt(N, Eval0, Bs0, RT, Ds0) ->      case get_prompt_func() of          {M,F} ->              L = [{history,N}], -            C = {call,1,{remote,1,{atom,1,M},{atom,1,F}},[{value,1,L}]}, +            A = erl_anno:new(1), +            C = {call,A,{remote,A,{atom,A,M},{atom,A,F}},[{value,A,L}]},              {V,Eval,Bs,Ds} = shell_cmd([C], Eval0, Bs0, RT, Ds0, pmt),              {Eval,Bs,Ds,case V of                              {pmt,Val} -> @@ -416,7 +417,7 @@ expand_expr({call,_L,{atom,_,v},[N]}, C) ->          {_,undefined,_} ->  	    no_command(N);  	{Ces,V,CommandN} when is_list(Ces) -> -            {value,CommandN,V} +            {value,erl_anno:new(CommandN),V}      end;  expand_expr({call,L,F,Args}, C) ->      {call,L,expand_expr(F, C),expand_exprs(Args, C)}; @@ -901,7 +902,7 @@ prep_check({call,Line,{atom,_,f},[{var,_,_Name}]}) ->      {atom,Line,ok};  prep_check({value,_CommandN,_Val}) ->      %% erl_lint cannot handle the history expansion {value,_,_}. -    {atom,0,ok}; +    {atom,a0(),ok};  prep_check(T) when is_tuple(T) ->      list_to_tuple(prep_check(tuple_to_list(T)));  prep_check([E | Es]) -> @@ -913,7 +914,7 @@ expand_records([], E0) ->      E0;  expand_records(UsedRecords, E0) ->      RecordDefs = [Def || {_Name,Def} <- UsedRecords], -    L = 1, +    L = erl_anno:new(1),      E = prep_rec(E0),      Forms = RecordDefs ++ [{function,L,foo,0,[{clause,L,[],[],[E]}]}],      [{function,L,foo,0,[{clause,L,[],[],[NE]}]}] =  @@ -1320,13 +1321,15 @@ list_bindings([{Name,Val}|Bs], RT) ->      case erl_eval:fun_data(Val) of          {fun_data,_FBs,FCs0} ->              FCs = expand_value(FCs0), % looks nicer -            F = {'fun',0,{clauses,FCs}}, -            M = {match,0,{var,0,Name},F}, +            A = a0(), +            F = {'fun',A,{clauses,FCs}}, +            M = {match,A,{var,A,Name},F},              io:fwrite(<<"~ts\n">>, [erl_pp:expr(M, enc())]);          {named_fun_data,_FBs,FName,FCs0} ->              FCs = expand_value(FCs0), % looks nicer -            F = {named_fun,0,FName,FCs}, -            M = {match,0,{var,0,Name},F}, +            A = a0(), +            F = {named_fun,A,FName,FCs}, +            M = {match,A,{var,A,Name},F},              io:fwrite(<<"~ts\n">>, [erl_pp:expr(M, enc())]);          false ->              Namel = io_lib:fwrite(<<"~s = ">>, [Name]), @@ -1356,13 +1359,18 @@ expand_value(E) ->  %% There is no abstract representation of funs.  try_abstract(V, CommandN) ->      try erl_parse:abstract(V) -    catch _:_ -> {call,0,{atom,0,v},[{integer,0,CommandN}]} +    catch +        _:_ -> +            A = a0(), +            {call,A,{atom,A,v},[{integer,A,CommandN}]}      end.  %% Rather than listing possibly huge results the calls to v/1 are shown.  prep_list_commands(E) -> -    substitute_v1(fun({value,CommandN,_V}) ->  -                          {call,0,{atom,0,v},[{integer,0,CommandN}]} +    A = a0(), +    substitute_v1(fun({value,Anno,_V}) -> +                          CommandN = erl_anno:line(Anno), +                          {call,A,{atom,A,v},[{integer,A,CommandN}]}                    end, E).  substitute_v1(F, {value,_,_}=Value) -> @@ -1374,6 +1382,9 @@ substitute_v1(F, [E | Es]) ->  substitute_v1(_F, E) ->       E. +a0() -> +    erl_anno:new(0). +  check_and_get_history_and_results() ->      check_env(shell_history_length),      check_env(shell_saved_results), diff --git a/lib/stdlib/src/slave.erl b/lib/stdlib/src/slave.erl index 1898dc8aba..28da45621a 100644 --- a/lib/stdlib/src/slave.erl +++ b/lib/stdlib/src/slave.erl @@ -128,7 +128,7 @@ relay1(Pid) ->  %%	    {error, {already_running, Name@Host}}  -spec start(Host) -> {ok, Node} | {error, Reason} when -      Host :: atom(), +      Host :: inet:hostname(),        Node :: node(),        Reason :: timeout | no_rsh | {already_running, Node}. @@ -138,8 +138,8 @@ start(Host) ->      start(Host, Name, [], no_link).  -spec start(Host, Name) -> {ok, Node} | {error, Reason} when -      Host :: atom(), -      Name :: atom(), +      Host :: inet:hostname(), +      Name :: atom() | string(),        Node :: node(),        Reason :: timeout | no_rsh | {already_running, Node}. @@ -147,8 +147,8 @@ start(Host, Name) ->      start(Host, Name, []).  -spec start(Host, Name, Args) -> {ok, Node} | {error, Reason} when -      Host :: atom(), -      Name :: atom(), +      Host :: inet:hostname(), +      Name :: atom() | string(),        Args :: string(),        Node :: node(),        Reason :: timeout | no_rsh | {already_running, Node}. @@ -157,7 +157,7 @@ start(Host, Name, Args) ->      start(Host, Name, Args, no_link).  -spec start_link(Host) -> {ok, Node} | {error, Reason} when -      Host :: atom(), +      Host :: inet:hostname(),        Node :: node(),        Reason :: timeout | no_rsh | {already_running, Node}. @@ -167,8 +167,8 @@ start_link(Host) ->      start(Host, Name, [], self()).  -spec start_link(Host, Name) -> {ok, Node} | {error, Reason} when -      Host :: atom(), -      Name :: atom(), +      Host :: inet:hostname(), +      Name :: atom() | string(),        Node :: node(),        Reason :: timeout | no_rsh | {already_running, Node}. @@ -176,8 +176,8 @@ start_link(Host, Name) ->      start_link(Host, Name, []).  -spec start_link(Host, Name, Args) -> {ok, Node} | {error, Reason} when -      Host :: atom(), -      Name :: atom(), +      Host :: inet:hostname(), +      Name :: atom() | string(),        Args :: string(),        Node :: node(),        Reason :: timeout | no_rsh | {already_running, Node}. @@ -210,7 +210,6 @@ start(Host0, Name, Args, LinkTo, Prog) ->        Node :: node().  stop(Node) -> -%    io:format("stop(~p)~n", [Node]),      rpc:call(Node, erlang, halt, []),      ok. @@ -229,7 +228,6 @@ wait_for_slave(Parent, Host, Name, Node, Args, LinkTo, Prog) ->      Waiter = register_unique_name(0),      case mk_cmd(Host, Name, Args, Waiter, Prog) of  	{ok, Cmd} -> -%%	    io:format("Command: ~ts~n", [Cmd]),  	    open_port({spawn, Cmd}, [stream]),  	    receive  		{SlavePid, slave_started} -> diff --git a/lib/stdlib/src/stdlib.app.src b/lib/stdlib/src/stdlib.app.src index 68c7ec07e3..a27a35dca2 100644 --- a/lib/stdlib/src/stdlib.app.src +++ b/lib/stdlib/src/stdlib.app.src @@ -2,7 +2,7 @@  %%   %% %CopyrightBegin%  %% -%% Copyright Ericsson AB 1996-2011. All Rights Reserved. +%% Copyright Ericsson AB 1996-2015. All Rights Reserved.  %%  %% The contents of this file are subject to the Erlang Public License,  %% Version 1.1, (the "License"); you may not use this file except in @@ -39,6 +39,7 @@  	     edlin_expand,  	     epp,  	     eval_bits, +             erl_anno,  	     erl_bits,  	     erl_compile,  	     erl_eval, diff --git a/lib/stdlib/src/supervisor.erl b/lib/stdlib/src/supervisor.erl index 7c0cd8b26a..67655b1145 100644 --- a/lib/stdlib/src/supervisor.erl +++ b/lib/stdlib/src/supervisor.erl @@ -1403,13 +1403,8 @@ add_restart([R|Restarts], Now, Period) ->  add_restart([], _, _) ->      []. -inPeriod(Time, Now, Period) -> -    case Time - Now of -	T when T > Period -> -	    false; -	_ -> -	    true -    end. +inPeriod(Then, Now, Period) -> +    Now =< Then + Period.  %%% ------------------------------------------------------  %%% Error and progress reporting. diff --git a/lib/stdlib/src/timer.erl b/lib/stdlib/src/timer.erl index 19d803345e..c266177b4d 100644 --- a/lib/stdlib/src/timer.erl +++ b/lib/stdlib/src/timer.erl @@ -161,10 +161,11 @@ sleep(T) ->        Time :: integer(),        Value :: term().  tc(F) -> -    Before = os:timestamp(), +    T1 = erlang:monotonic_time(),      Val = F(), -    After = os:timestamp(), -    {now_diff(After, Before), Val}. +    T2 = erlang:monotonic_time(), +    Time = erlang:convert_time_unit(T2 - T1, native, micro_seconds), +    {Time, Val}.  %%  %% Measure the execution time (in microseconds) for Fun(Args). @@ -175,10 +176,11 @@ tc(F) ->        Time :: integer(),        Value :: term().  tc(F, A) -> -    Before = os:timestamp(), +    T1 = erlang:monotonic_time(),      Val = apply(F, A), -    After = os:timestamp(), -    {now_diff(After, Before), Val}. +    T2 = erlang:monotonic_time(), +    Time = erlang:convert_time_unit(T2 - T1, native, micro_seconds), +    {Time, Val}.  %%  %% Measure the execution time (in microseconds) for an MFA. @@ -190,10 +192,11 @@ tc(F, A) ->        Time :: integer(),        Value :: term().  tc(M, F, A) -> -    Before = os:timestamp(), +    T1 = erlang:monotonic_time(),      Val = apply(M, F, A), -    After = os:timestamp(), -    {now_diff(After, Before), Val}. +    T2 = erlang:monotonic_time(), +    Time = erlang:convert_time_unit(T2 - T1, native, micro_seconds), +    {Time, Val}.  %%  %% Calculate the time difference (in microseconds) of two diff --git a/lib/stdlib/src/zip.erl b/lib/stdlib/src/zip.erl index 44e75ff15b..3c67bd67c6 100644 --- a/lib/stdlib/src/zip.erl +++ b/lib/stdlib/src/zip.erl @@ -1150,7 +1150,7 @@ server_loop(Parent, OpenZip) ->  	    From ! {self(), OpenZip},  	    server_loop(Parent, OpenZip);          {'EXIT', Parent, Reason} -> -            openzip_close(OpenZip), +            _ = openzip_close(OpenZip),              exit({parent_died, Reason});  	_ ->  	    {error, bad_msg} | 
