File 2209-epp-Add-the-error-and-warning-directives.patch of Package erlang

From 14d72f02146b1d0aa3293eef9a823cbf0f4a4e99 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Thu, 1 Oct 2015 15:41:01 +0200
Subject: [PATCH 2/3] epp: Add the -error and -warning directives

If one of several alternatives configurations are required for
an Erlang module to compile, but none are available, it would
be useful to give a nice error message. For example:

  -ifdef(CONFIG_A).
     %% Some code if A is true.
  -else.
  -ifdef(CONFIG_B).
    %% Some code if B is true.
  -else.
    -error("Neither CONFIG_A nor CONFIG_B are available").
  -endif.
  -endif.

If neither CONFIG_A nor CONFIG_B are defined, the error message
will be:

  module.erl:10: -error("Neither CONFIG_A nor CONFIG_B are available").

That is basically the same behavior as for the #error directive in
GCC.

For symmetry with the -error directive, add the -warning
directive to generate a compiler warning. For example:

  -ifdef(HAVE_COOL_FEATURE).
     %% Code if we have Cool Feature.
  -else.
     %% Inefficient fallback code.
     -warning("Using inefficient fallback").
  -endif.

If HAVE_COOL_FEATURE is not defined, the warning message will
be:

  module.erl:8: Warning: -warning("Using inefficient fallback").

That is basically the same behavior as for the #warning directive
in GCC.

Conflicts:
	lib/stdlib/src/epp.erl
	lib/stdlib/test/epp_SUITE.erl
---
 lib/stdlib/src/epp.erl        | 42 ++++++++++++++++++++++++++---
 lib/stdlib/test/epp_SUITE.erl | 63 +++++++++++++++++++++++++++++++++++++++++--
 2 files changed, 99 insertions(+), 6 deletions(-)

diff --git a/lib/stdlib/src/epp.erl b/lib/stdlib/src/epp.erl
index 71c465d..73934e0 100644
--- a/lib/stdlib/src/epp.erl
+++ b/lib/stdlib/src/epp.erl
@@ -53,6 +53,8 @@
 			    | {atom(),non_neg_integer()}
 			    | tokens().
 
+-type warning_info() :: {erl_anno:location(), module(), term()}.
+
 -define(DEFAULT_ENCODING, utf8).
 
 %% Epp state record.
@@ -158,11 +160,13 @@ scan_erl_form(Epp) ->
     epp_request(Epp, scan_erl_form).
 
 -spec parse_erl_form(Epp) ->
-        {'ok', AbsForm} | {'eof', Line} | {error, ErrorInfo} when
+    {'ok', AbsForm} | {error, ErrorInfo} |
+    {'warning',WarningInfo} | {'eof',Line} when
       Epp :: epp_handle(),
       AbsForm :: erl_parse:abstract_form(),
       Line :: erl_anno:line(),
-      ErrorInfo :: erl_scan:error_info() | erl_parse:error_info().
+      ErrorInfo :: erl_scan:error_info() | erl_parse:error_info(),
+      WarningInfo :: warning_info().
 
 parse_erl_form(Epp) ->
     case epp_request(Epp, scan_erl_form) of
@@ -219,6 +223,10 @@ format_error({illegal_function_usage,Macro}) ->
     io_lib:format("?~s must not begin a form", [Macro]);
 format_error({'NYI',What}) ->
     io_lib:format("not yet implemented '~s'", [What]);
+format_error({error,Term}) ->
+    io_lib:format("-error(~p).", [Term]);
+format_error({warning,Term}) ->
+    io_lib:format("-warning(~p).", [Term]);
 format_error(E) -> file:format_error(E).
 
 -spec parse_file(FileName, IncludePath, PredefMacros) ->
@@ -263,9 +271,11 @@ parse_file(Ifile, Options) ->
 
 -spec parse_file(Epp) -> [Form] when
       Epp :: epp_handle(),
-      Form :: erl_parse:abstract_form() | {'error', ErrorInfo} | {'eof',Line},
+      Form :: erl_parse:abstract_form() | {'error', ErrorInfo} |
+	      {'warning',WarningInfo} | {'eof',Line},
       Line :: erl_anno:line(),
-      ErrorInfo :: erl_scan:error_info() | erl_parse:error_info().
+      ErrorInfo :: erl_scan:error_info() | erl_parse:error_info(),
+      WarningInfo :: warning_info().
 
 parse_file(Epp) ->
     case parse_erl_form(Epp) of
@@ -273,6 +283,8 @@ parse_file(Epp) ->
 	    end;
 	{error,E} ->
 	    [{error,E}|parse_file(Epp)];
+	{warning,W} ->
+	    [{warning,W}|parse_file(Epp)];
 	{eof,Location} ->
 	    [{eof,erl_anno:new(Location)}]
     end.
@@ -752,6 +764,10 @@ scan_toks([{'-',_Lh},{atom,_Ld,define}=Define|Toks], From, St) ->
     scan_define(Toks, Define, From, St);
 scan_toks([{'-',_Lh},{atom,_Ld,undef}=Undef|Toks], From, St) ->
     scan_undef(Toks, Undef, From, St);
+scan_toks([{'-',_Lh},{atom,_Ld,error}=Error|Toks], From, St) ->
+    scan_err_warn(Toks, Error, From, St);
+scan_toks([{'-',_Lh},{atom,_Ld,warning}=Warn|Toks], From, St) ->
+    scan_err_warn(Toks, Warn, From, St);
 scan_toks([{'-',_Lh},{atom,_Li,include}=Inc|Toks], From, St) ->
     scan_include(Toks, Inc, From, St);
 scan_toks([{'-',_Lh},{atom,_Li,include_lib}=IncLib|Toks], From, St) ->
@@ -807,6 +823,24 @@ scan_extends([{atom,Ln,A}=ModAtom,{')',_Lr}|_Ts], Ms0) ->
     Ms#{'BASE_MODULE_STRING':={none,[{string,Ln,ModString}]}};
 scan_extends(_Ts, Ms) -> Ms.
 
+scan_err_warn([{'(',_}|_]=Toks0, {atom,_,Tag}=Token, From, St) ->
+    try expand_macros(Toks0, St) of
+	Toks when is_list(Toks) ->
+	    case erl_parse:parse_term(Toks) of
+		{ok,Term} ->
+		    epp_reply(From, {Tag,{loc(Token),epp,{Tag,Term}}});
+		{error,_} ->
+		    epp_reply(From, {error,{loc(Token),epp,{bad,Tag}}})
+	    end
+    catch
+	_:_ ->
+	    epp_reply(From, {error,{loc(Token),epp,{bad,Tag}}})
+    end,
+    wait_req_scan(St);
+scan_err_warn(_Toks, {atom,_,Tag}=Token, From, St) ->
+    epp_reply(From, {error,{loc(Token),epp,{bad,Tag}}}),
+    wait_req_scan(St).
+
 %% scan_define(Tokens, DefineToken, From, EppState)
 
 scan_define([{'(',_Lp},{Type,_Lm,_}=Mac|Toks], Def, From, St)
diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl
index ef2c912..4078513 100644
--- a/lib/stdlib/test/epp_SUITE.erl
+++ b/lib/stdlib/test/epp_SUITE.erl
@@ -27,7 +27,8 @@
          pmod/1, not_circular/1, skip_header/1, otp_6277/1, otp_7702/1,
          otp_8130/1, overload_mac/1, otp_8388/1, otp_8470/1, otp_8503/1,
          otp_8562/1, otp_8665/1, otp_8911/1, otp_10302/1, otp_10820/1,
-         otp_11728/1, encoding/1, function_macro/1]).
+         otp_11728/1, encoding/1, function_macro/1,
+	 test_error/1, test_warning/1]).
 
 -export([epp_parse_erl_form/2]).
 
@@ -67,7 +68,7 @@ all() ->
      not_circular, skip_header, otp_6277, otp_7702, otp_8130,
      overload_mac, otp_8388, otp_8470, otp_8503, otp_8562,
      otp_8665, otp_8911, otp_10302, otp_10820, otp_11728,
-     encoding, function_macro].
+     encoding, function_macro, test_error, test_warning].
 
 groups() -> 
     [{upcase_mac, [], [upcase_mac_1, upcase_mac_2]},
@@ -1055,7 +1056,65 @@ ifdef(Config) ->
            ],
     ?line [] = run(Config, Ts).
 
+%% OTP-12847: Test the -error directive.
+test_error(Config) ->
+    Cs = [{error_c1,
+           <<"-error(\"string and macro: \" ?MODULE_STRING).\n"
+	     "-ifdef(NOT_DEFINED).\n"
+	     " -error(\"this one will be skipped\").\n"
+	     "-endif.\n">>,
+           {errors,[{1,epp,{error,"string and macro: epp_test"}}],[]}},
+
+	  {error_c2,
+	   <<"-ifdef(CONFIG_A).\n"
+	     " t() -> a.\n"
+	     "-else.\n"
+	     "-ifdef(CONFIG_B).\n"
+	     " t() -> b.\n"
+	     "-else.\n"
+	     "-error(\"Neither CONFIG_A nor CONFIG_B are available\").\n"
+	     "-endif.\n"
+	     "-endif.\n">>,
+	   {errors,[{7,epp,{error,"Neither CONFIG_A nor CONFIG_B are available"}}],[]}},
+
+	  {error_c3,
+	   <<"-error(a b c).\n">>,
+	   {errors,[{1,epp,{bad,error}}],[]}}
 
+	 ],
+
+    [] = compile(Config, Cs),
+    ok.
+
+%% OTP-12847: Test the -warning directive.
+test_warning(Config) ->
+    Cs = [{warn_c1,
+           <<"-warning({a,term,?MODULE}).\n"
+	     "-ifdef(NOT_DEFINED).\n"
+	     "-warning(\"this one will be skipped\").\n"
+	     "-endif.\n">>,
+           {warnings,[{1,epp,{warning,{a,term,epp_test}}}]}},
+
+	  {warn_c2,
+	   <<"-ifdef(CONFIG_A).\n"
+	     " t() -> a.\n"
+	     "-else.\n"
+	     "-ifdef(CONFIG_B).\n"
+	     " t() -> b.\n"
+	     "-else.\n"
+	     " t() -> c.\n"
+	     "-warning(\"Using fallback\").\n"
+	     "-endif.\n"
+	     "-endif.\n">>,
+	   {warnings,[{8,epp,{warning,"Using fallback"}}]}},
+
+	  {warn_c3,
+	   <<"-warning(a b c).\n">>,
+	   {errors,[{1,epp,{bad,warning}}],[]}}
+	 ],
+
+    [] = compile(Config, Cs),
+    ok.
 
 overload_mac(doc) ->
     ["Advanced test on overloading macros."];
-- 
2.1.4

openSUSE Build Service is sponsored by