File 0133-Preprocessor-Fail-compilation-for-unknown-functions.patch of Package erlang
From cd2a596d5d9bf2846b1f0c3f58ef7aa68c4b9b0b Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Tue, 3 Oct 2023 10:32:03 +0200
Subject: [PATCH] Preprocessor: Fail compilation for unknown functions
EEP 44 suggested extensions to the preprocessor.
In OTP 19, the `-error` and `-warning` directives were implemented.
In OTP 21, the `-if` and `-elif` directives were implemented. These
directive evaluate a condition that syntactically looks like a guard
expression. Semantically, however, there were a few differences
compared to standard guard expressions.
One difference was that there were more built-in functions available,
such as `defined(Name)` to test whether `Name` is a defined macro.
Ultimately, of the suggested built-in functions, only `defined(Name)`
was actually implemented (but it was not documented).
Another difference was that calls to unknown functions would not cause
a compilation error, but would merely fail the condition and cause the
code following the `-if` directive to be skipped. The rationale was
that one could test for new guard BIFs directly by calling them in an
`-if` condition. Thus, one could test for the presence of maps like
so:
-if(not is_map(a)).
%% Code using maps.
-else.
%% Fallback code that don't use maps.
-endif.
The idea is that in a release with maps, `not is_map(a)` would return
`true`, and in a release without maps, the call to the unknown
function `is_map/1` would fail and the code following the `-if` would
be skipped. This is, of course, a purely hypothetical example, because
maps were introduced in OTP 17 well before `-if` could handle guard
expressions.
In practice, new guard BIFs are not introduced very often. If I
haven't missed any, the only guard BIFs introduced after OTP 21 are
`min/2` and `max/2` in OTP 26. We could attempt test whether `max/2`
works in a guard like so:
-if(max(0, 0) =:= 0).
check(X) when max(X, 0) =:= 0 -> negative;
check(_) -> positive.
-else.
check(X) ->
case max(X, 0) of
0 -> negative;
_ -> positive
end.
-endif.
Unsurprisingly, this code compiles and works in OTP 26.
Perhaps somewhat surprisingly, this code does not compile in OTP 25:
t.erl:5:2: badly formed 'if'
% 5| -if(max(0, 0) =:= 0).
% | ^
The reason is that calls to known non-guard BIF functions result in a
compilation error (as described in the EEP). Of course, `min/2` and
`max/2` has existed as non-guard BIFs for a long time.
Given that the current behavior has not proven itself useful, but
instead can hide typos, this commit makes calls that are not to known
guard BIFs into compilation errors.
Fixes #7706
---
lib/stdlib/src/epp.erl | 44 ++++------------
lib/stdlib/test/epp_SUITE.erl | 17 +++---
system/doc/reference_manual/macros.xml | 71 ++++++++++++++++++--------
3 files changed, 68 insertions(+), 64 deletions(-)
diff --git a/lib/stdlib/src/epp.erl b/lib/stdlib/src/epp.erl
index 1f7f614b00..2b531c8869 100644
--- a/lib/stdlib/src/epp.erl
+++ b/lib/stdlib/src/epp.erl
@@ -1366,7 +1366,7 @@ eval_if(Toks0, St) ->
{ok,Es0} -> Es0;
{error,E} -> throw(E)
end,
- Es = rewrite_expr(Es1, St),
+ Es = evaluate_builtins(Es1, St),
assert_guard_expr(Es),
Bs = erl_eval:new_bindings(),
LocalFun = fun(_Name, _Args) ->
@@ -1380,8 +1380,7 @@ eval_if(Toks0, St) ->
false
end.
-assert_guard_expr([E0]) ->
- E = rewrite_expr(E0, none),
+assert_guard_expr([E]) ->
case erl_lint:is_guard_expr(E) of
false ->
throw({bad,'if'});
@@ -1391,13 +1390,9 @@ assert_guard_expr([E0]) ->
assert_guard_expr(_) ->
throw({bad,'if'}).
-%% Dual-purpose rewriting function. When the second argument is
-%% an #epp{} record, calls to defined(Symbol) will be evaluated.
-%% When the second argument is 'none', legal calls to our built-in
-%% functions are eliminated in order to turn the expression into
-%% a legal guard expression.
-
-rewrite_expr({call,_,{atom,_,defined},[N0]}, #epp{macs=Macs}) ->
+%% evaluate_builtins(AbstractForm0, #epp{}) -> AbstractForm.
+%% Evaluate call to special functions for the preprocessor.
+evaluate_builtins({call,_,{atom,_,defined},[N0]}, #epp{macs=Macs}) ->
%% Evaluate defined(Symbol).
N = case N0 of
{var,_,N1} -> N1;
@@ -1405,32 +1400,13 @@ rewrite_expr({call,_,{atom,_,defined},[N0]}, #epp{macs=Macs}) ->
_ -> throw({bad,'if'})
end,
{atom,erl_anno:new(0),maps:is_key(N, Macs)};
-rewrite_expr({call,_,{atom,_,Name},As0}, none) ->
- As = rewrite_expr(As0, none),
- Arity = length(As),
- case erl_internal:bif(Name, Arity) andalso
- not erl_internal:guard_bif(Name, Arity) of
- false ->
- %% A guard BIF, an -if built-in, or an unknown function.
- %% Eliminate the call so that erl_lint will not complain.
- %% The call might fail later at evaluation time.
- to_conses(As);
- true ->
- %% An auto-imported BIF (not guard BIF). Not allowed.
- throw({bad,'if'})
- end;
-rewrite_expr([H|T], St) ->
- [rewrite_expr(H, St)|rewrite_expr(T, St)];
-rewrite_expr(Tuple, St) when is_tuple(Tuple) ->
- list_to_tuple(rewrite_expr(tuple_to_list(Tuple), St));
-rewrite_expr(Other, _) ->
+evaluate_builtins([H|T], St) ->
+ [evaluate_builtins(H, St)|evaluate_builtins(T, St)];
+evaluate_builtins(Tuple, St) when is_tuple(Tuple) ->
+ list_to_tuple(evaluate_builtins(tuple_to_list(Tuple), St));
+evaluate_builtins(Other, _) ->
Other.
-to_conses([H|T]) ->
- {cons,erl_anno:new(0),H,to_conses(T)};
-to_conses([]) ->
- {nil,erl_anno:new(0)}.
-
%% scan_elif(Tokens, EndifToken, From, EppState)
%% Handle the conditional parsing of a file.
%% Report a badly formed if test and then treat as false macro.
diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl
index c62f6fa3c1..90b1712d14 100644
--- a/lib/stdlib/test/epp_SUITE.erl
+++ b/lib/stdlib/test/epp_SUITE.erl
@@ -1254,8 +1254,15 @@ test_if(Config) ->
{if_8c,
<<"-if(?foo).\n" %Undefined symbol.
"-endif.\n">>,
- {errors,[{{1,25},epp,{undefined,foo,none}}],[]}}
+ {errors,[{{1,25},epp,{undefined,foo,none}}],[]}},
+ {if_9c,
+ <<"-if(not_builtin()).\n"
+ "a bug.\n"
+ "-else.\n"
+ "t() -> ok.\n"
+ "-endif.\n">>,
+ {errors,[{{1,21},epp,{bad,'if'}}],[]}}
],
[] = compile(Config, Cs),
@@ -1321,14 +1328,6 @@ test_if(Config) ->
ok},
{if_7,
- <<"-if(not_builtin()).\n"
- "a bug.\n"
- "-else.\n"
- "t() -> ok.\n"
- "-endif.\n">>,
- ok},
-
- {if_8,
<<"-if(42).\n" %Not boolean.
"a bug.\n"
"-else.\n"
diff --git a/system/doc/reference_manual/macros.xml b/system/doc/reference_manual/macros.xml
index ab503f740e..d865b055fc 100644
--- a/system/doc/reference_manual/macros.xml
+++ b/system/doc/reference_manual/macros.xml
@@ -206,11 +206,16 @@ f() ->
</section>
<section>
- <title>Flow Control in Macros</title>
- <p>The following macro directives are supplied:</p>
+ <title>Removing a macro definition</title>
+ <p>A definition of macro can be removed as follows:</p>
+ <code type="none">
+-undef(Macro).</code>
+ </section>
+
+ <section>
+ <title>Conditional Compilation</title>
+ <p>The following macro directives support conditional compilation:</p>
<taglist>
- <tag><c>-undef(Macro).</c></tag>
- <item>Causes the macro to behave as if it had never been defined.</item>
<tag><c>-ifdef(Macro).</c></tag>
<item>Evaluate the following lines only if <c>Macro</c> is
defined.</item>
@@ -218,24 +223,38 @@ f() ->
<item>Evaluate the following lines only if <c>Macro</c> is not
defined.</item>
<tag><c>-else.</c></tag>
- <item>Only allowed after an <c>ifdef</c> or <c>ifndef</c>
- directive. If that condition is false, the lines following
- <c>else</c> are evaluated instead.</item>
- <tag><c>-endif.</c></tag>
- <item>Specifies the end of an <c>ifdef</c>, an <c>ifndef</c>
- directive, or the end of an <c>if</c> or <c>elif</c> directive.</item>
+ <item>Only allowed after the <c>ifdef</c>, <c>ifndef</c>, <c>if</c>,
+ and <c>elif</c> directives. The lines following <c>else</c> are
+ evaluated if the preceding directive evaluated to false.</item>
<tag><c>-if(Condition).</c></tag>
<item>Evaluates the following lines only if <c>Condition</c>
evaluates to true.</item>
<tag><c>-elif(Condition).</c></tag>
<item>Only allowed after an <c>if</c> or another <c>elif</c> directive.
- If the preceding <c>if</c> or <c>elif</c> directives do not
+ If the preceding <c>if</c> or <c>elif</c> directive does not
evaluate to true, and the <c>Condition</c> evaluates to true,
the lines following the <c>elif</c> are evaluated instead.</item>
+ <tag><c>-endif.</c></tag>
+ <item>Specifies the end of a series of control flow directives.</item>
</taglist>
<note>
- <p>The macro directives cannot be used inside functions.</p>
+ <p>Macro directives cannot be used inside functions.</p>
</note>
+
+ <p>Syntactically, the <c>Condition</c> in <c>if</c> and
+ <c>elif</c> must be a <seeguide
+ marker="expressions#guard-expressions">guard
+ expression</seeguide>. Other constructs (such as a <c>case</c>
+ expression) result in a compilation error.</p>
+
+ <p>As opposed to the standard guard expressions, an expression in
+ an <c>if</c> and <c>elif</c> also supports calling the
+ psuedo-function <c>defined(Name)</c>, which tests whether the
+ <c>Name</c> argument is the name of a previously defined macro.
+ <c>defined(Name)</c> evaluates to <c>true</c> if the macro is
+ defined and <c>false</c> otherwise. An attempt to call other
+ functions results in a compilation error.</p>
+
<p><em>Example:</em></p>
<code type="none">
-module(m).
@@ -264,19 +283,29 @@ or
<code type="none">
-module(m)
...
--ifdef(OTP_RELEASE).
- %% OTP 21 or higher
- -if(?OTP_RELEASE >= 22).
- %% Code that will work in OTP 22 or higher
- -elif(?OTP_RELEASE >= 21).
- %% Code that will work in OTP 21 or higher
- -endif.
+-if(?OTP_RELEASE >= 25).
+%% Code that will work in OTP 25 or higher
+-elif(?OTP_RELEASE >= 26).
+%% Code that will work in OTP 26 or higher
-else.
- %% OTP 20 or lower.
+%% Code that will work in OTP 24 or lower.
-endif.
...</code>
- <p>The code uses the <c>OTP_RELEASE</c> macro to conditionally
+ <p>This code uses the <c>OTP_RELEASE</c> macro to conditionally
select code depending on release.</p>
+
+ <p><em>Example:</em></p>
+ <code type="none">
+-module(m)
+...
+-if(?OTP_RELEASE >= 26 andalso defined(debug)).
+%% Debugging code that requires OTP 26 or later.
+-else.
+%% Non-debug code that works in any release.
+-endif.
+...</code>
+ <p>This code uses the <c>OTP_RELEASE</c> macro and <c>defined(debug)</c>
+ to compile debug code only for OTP 26 or later.</p>
</section>
<section>
--
2.35.3