File 2535-stdlib-Fix-handling-of-locations-and-annotations.patch of Package erlang

From de736de7b0eee391e3411ecd515d7bdae1bdc16c Mon Sep 17 00:00:00 2001
From: Hans Bolinder <hasse@erlang.org>
Date: Mon, 13 Feb 2017 10:38:23 +0100
Subject: [PATCH 05/15] stdlib: Fix handling of locations and annotations

---
 lib/stdlib/src/c.erl               |  4 ++--
 lib/stdlib/src/epp.erl             |  2 +-
 lib/stdlib/src/erl_compile.erl     |  4 ++--
 lib/stdlib/src/erl_lint.erl        |  9 +++++++--
 lib/stdlib/src/escript.erl         |  8 +++-----
 lib/stdlib/src/qlc_pt.erl          |  4 ++--
 lib/stdlib/test/erl_lint_SUITE.erl | 10 +++++++---
 lib/stdlib/test/erl_pp_SUITE.erl   | 11 ++++++-----
 lib/stdlib/test/erl_scan_SUITE.erl |  6 +++---
 9 files changed, 33 insertions(+), 25 deletions(-)

diff --git a/lib/stdlib/src/c.erl b/lib/stdlib/src/c.erl
index 52df2319d..bb7b48549 100644
--- a/lib/stdlib/src/c.erl
+++ b/lib/stdlib/src/c.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 1996-2016. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2017. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -400,7 +400,7 @@ split_def([], Res) -> {d, list_to_atom(reverse(Res))}.
 make_term(Str) ->
     case erl_scan:string(Str) of
 	{ok, Tokens, _} ->
-	    case erl_parse:parse_term(Tokens ++ [{dot, 1}]) of
+	    case erl_parse:parse_term(Tokens ++ [{dot, erl_anno:new(1)}]) of
 		{ok, Term} -> Term;
 		{error, {_,_,Reason}} ->
 		    io:format("~ts: ~ts~n", [Reason, Str]),
diff --git a/lib/stdlib/src/epp.erl b/lib/stdlib/src/epp.erl
index 40eba4ad6..61d755ba5 100644
--- a/lib/stdlib/src/epp.erl
+++ b/lib/stdlib/src/epp.erl
@@ -286,7 +286,7 @@ parse_file(Epp) ->
 	{warning,W} ->
 	    [{warning,W}|parse_file(Epp)];
 	{eof,Location} ->
-	    [{eof,erl_anno:new(Location)}]
+	    [{eof,Location}]
     end.
 
 -spec default_encoding() -> source_encoding().
diff --git a/lib/stdlib/src/erl_compile.erl b/lib/stdlib/src/erl_compile.erl
index a6ae398d0..76db2eeac 100644
--- a/lib/stdlib/src/erl_compile.erl
+++ b/lib/stdlib/src/erl_compile.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 1997-2016. All Rights Reserved.
+%% Copyright Ericsson AB 1997-2017. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -337,7 +337,7 @@ file_or_directory(Name) ->
 make_term(Str) -> 
     case erl_scan:string(Str) of
 	{ok, Tokens, _} ->		  
-	    case erl_parse:parse_term(Tokens ++ [{dot, 1}]) of
+	    case erl_parse:parse_term(Tokens ++ [{dot, erl_anno:new(1)}]) of
 		{ok, Term} -> Term;
 		{error, {_,_,Reason}} ->
 		    io:format(?STDERR, "~ts: ~ts~n", [Reason, Str]),
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index 1b84234fa..0ffca0886 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -2,7 +2,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 1996-2016. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2017. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -737,7 +737,12 @@ start_state({attribute,_,module,M}, St0) ->
     St1 = St0#lint{module=M},
     St1#lint{state=attribute};
 start_state(Form, St) ->
-    St1 = add_error(element(2, Form), undefined_module, St),
+    Anno = case Form of
+               {eof, L} -> erl_anno:new(L);
+               %% {warning, Warning} and {error, Error} not possible here.
+               _ -> element(2, Form)
+           end,
+    St1 = add_error(Anno, undefined_module, St),
     attribute_state(Form, St1#lint{state=attribute}).
 
 %% attribute_state(Form, State) ->
diff --git a/lib/stdlib/src/escript.erl b/lib/stdlib/src/escript.erl
index c42ae981e..6e8f780f7 100644
--- a/lib/stdlib/src/escript.erl
+++ b/lib/stdlib/src/escript.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 2007-2016. All Rights Reserved.
+%% Copyright Ericsson AB 2007-2017. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -629,8 +629,7 @@ parse_source(S, File, Fd, StartLine, HeaderSz, CheckOnly) ->
                     {error, _} ->
                         epp_parse_file2(Epp, S2, [FileForm], OptModRes);
                     {eof, LastLine} ->
-                        Anno = anno(LastLine),
-                        S#state{forms_or_bin = [FileForm, {eof, Anno}]}
+                        S#state{forms_or_bin = [FileForm, {eof, LastLine}]}
                 end,
             ok = epp:close(Epp),
             ok = file:close(Fd),
@@ -728,8 +727,7 @@ epp_parse_file2(Epp, S, Forms, Parsed) ->
                       [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} ->
-            Anno = anno(LastLine),
-            S#state{forms_or_bin = lists:reverse([{eof, Anno} | Forms])}
+            S#state{forms_or_bin = lists:reverse([{eof, LastLine} | Forms])}
     end.
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
diff --git a/lib/stdlib/src/qlc_pt.erl b/lib/stdlib/src/qlc_pt.erl
index 28221ea75..4a39f8ae9 100644
--- a/lib/stdlib/src/qlc_pt.erl
+++ b/lib/stdlib/src/qlc_pt.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 2004-2016. All Rights Reserved.
+%% Copyright Ericsson AB 2004-2017. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -439,7 +439,7 @@ compile_forms(Forms0, Options) ->
                  (_) -> false
               end,
     Forms = ([F || F <- Forms0, not Exclude(element(1, F))]
-             ++ [{eof,anno0()}]),
+             ++ [{eof,0}]),
     try 
         case compile:noenv_forms(Forms, compile_options(Options)) of
             {ok, _ModName, Ws0} ->
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index c7dcd9ae1..df38edf39 100644
--- a/lib/stdlib/test/erl_lint_SUITE.erl
+++ b/lib/stdlib/test/erl_lint_SUITE.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 1999-2016. All Rights Reserved.
+%% Copyright Ericsson AB 1999-2017. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -2549,7 +2549,7 @@ otp_5878(Config) when is_list(Config) ->
                    {function,9,t,0,[{clause,9,[],[],[{record,10,r,[]}]}]},
                    {eof,11}],
     {error,[{"rec.erl",[{7,erl_lint,old_abstract_code}]}],[]} =
-        compile:forms(OldAbstract, [return, report]),
+        compile_forms(OldAbstract, [return, report]),
 
     ok.
 
@@ -3848,9 +3848,13 @@ otp_11879(_Config) ->
              [{1,erl_lint,{spec_fun_undefined,{f,1}}},
               {2,erl_lint,spec_wrong_arity},
               {22,erl_lint,callback_wrong_arity}]}],
-     []} = compile:forms(Fs, [return,report]),
+     []} = compile_forms(Fs, [return,report]),
     ok.
 
+compile_forms(Terms, Opts) ->
+    Forms = [erl_parse:anno_from_term(Term) || Term <- Terms],
+    compile:forms(Forms, Opts).
+
 %% OTP-13230: -deprecated without -module.
 otp_13230(Config) when is_list(Config) ->
     Abstr = <<"-deprecated([{frutt,0,next_version}]).">>,
diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl
index 31ea3210a..1a028204b 100644
--- a/lib/stdlib/test/erl_pp_SUITE.erl
+++ b/lib/stdlib/test/erl_pp_SUITE.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 2006-2016. All Rights Reserved.
+%% Copyright Ericsson AB 2006-2017. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -1068,10 +1068,10 @@ otp_11100(Config) when is_list(Config) ->
     %% There are a few places where the added code ("options(none)")
     %% doesn't make a difference (pp:bit_elem_type/1 is an example).
 
+    A1 = erl_anno:new(1),
     %% Cannot trigger the use of the hook function with export/import.
     "-export([{fy,a}/b]).\n" =
-        pf({attribute,1,export,[{{fy,a},b}]}),
-    A1 = erl_anno:new(1),
+        pf({attribute,A1,export,[{{fy,a},b}]}),
     "-type foo() :: integer(INVALID-FORM:{foo,bar}:).\n" =
         pf({attribute,A1,type,{foo,{type,A1,integer,[{foo,bar}]},[]}}),
     pf({attribute,A1,type,
@@ -1100,10 +1100,11 @@ otp_11100(Config) when is_list(Config) ->
 
 %% OTP-11861. behaviour_info() and -callback.
 otp_11861(Config) when is_list(Config) ->
+    A3 = erl_anno:new(3),
     "-optional_callbacks([bar/0]).\n" =
-        pf({attribute,3,optional_callbacks,[{bar,0}]}),
+        pf({attribute,A3,optional_callbacks,[{bar,0}]}),
     "-optional_callbacks([{bar,1,bad}]).\n" =
-        pf({attribute,4,optional_callbacks,[{bar,1,bad}]}),
+        pf({attribute,A3,optional_callbacks,[{bar,1,bad}]}),
     ok.
 
 pf(Form) ->
-- 
2.12.0

openSUSE Build Service is sponsored by