File 0442-v3_core-Don-t-make-the-compiler-crash-on-invalid-map.patch of Package erlang
From e4fe93ac25a95ca24de132ad365c2954d6118b26 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Sat, 29 Feb 2020 08:10:52 +0100
Subject: [PATCH 22/30] v3_core: Don't make the compiler crash on invalid map
updates
Consider this code that does a map update on the integer 42:
42 #{part => V = false},
V
Since 42 is not a map, v3_core would rewrite the code like this:
erlang:error(badmap),
V
In this particular example, since `V` is clearly unreachable,
sys_core_fold will remove the use of `V` and the compiler will not
crash. However, the Core Linter will complain if it is enabled.
The compiler will crash when given some more complicated examples:
foobar() ->
case 42 of
V ->
[];
power ->
[]#{key =>
receive
V -> false
end}
end,
V.
To avoid this problem, stop rewriting failing map updates to
a call to `error/1`.
---
lib/compiler/src/v3_core.erl | 61 +++++++++++++++++++-----------------
lib/compiler/test/map_SUITE.erl | 18 +++++++++++
lib/compiler/test/warnings_SUITE.erl | 4 +--
3 files changed, 52 insertions(+), 31 deletions(-)
diff --git a/lib/compiler/src/v3_core.erl b/lib/compiler/src/v3_core.erl
index c7e61b315a..2ecf9f02ec 100644
--- a/lib/compiler/src/v3_core.erl
+++ b/lib/compiler/src/v3_core.erl
@@ -860,32 +860,41 @@ make_bool_switch(L, E, V, T, F) ->
[Error]}]}]}.
expr_map(M0, Es0, L, St0) ->
- {M1,Eps0,St1} = safe(M0, St0),
+ {M1,Eps0,St1} = safe_map(M0, St0),
Badmap = badmap_term(M1, St1),
A = lineno_anno(L, St1),
Fc = fail_clause([], [{eval_failure,badmap}|A], Badmap),
- case is_valid_map_src(M1) of
- true ->
- {M2,Eps1,St2} = map_build_pairs(M1, Es0, full_anno(L, St1), St1),
- M3 = case Es0 of
- [] -> M1;
- [_|_] -> M2
- end,
- Cs = [#iclause{
- anno=#a{anno=[compiler_generated|A]},
- pats=[],
- guard=[#icall{anno=#a{anno=A},
- module=#c_literal{anno=A,val=erlang},
- name=#c_literal{anno=A,val=is_map},
- args=[M1]}],
- body=[M3]}],
- Eps = Eps0 ++ Eps1,
- {#icase{anno=#a{anno=A},args=[],clauses=Cs,fc=Fc},Eps,St2};
- false ->
- %% Not a map source. The update will always fail.
- St2 = add_warning(L, badmap, St1),
- #iclause{body=[Fail]} = Fc,
- {Fail,Eps0,St2}
+ {M2,Eps1,St2} = map_build_pairs(M1, Es0, full_anno(L, St1), St1),
+ M3 = case Es0 of
+ [] -> M1;
+ [_|_] -> M2
+ end,
+ Cs = [#iclause{
+ anno=#a{anno=[compiler_generated|A]},
+ pats=[],
+ guard=[#icall{anno=#a{anno=A},
+ module=#c_literal{anno=A,val=erlang},
+ name=#c_literal{anno=A,val=is_map},
+ args=[M1]}],
+ body=[M3]}],
+ Eps = Eps0 ++ Eps1,
+ {#icase{anno=#a{anno=A},args=[],clauses=Cs,fc=Fc},Eps,St2}.
+
+safe_map(M0, St0) ->
+ case safe(M0, St0) of
+ {#c_var{},_,_}=Res ->
+ Res;
+ {#c_literal{val=Map},_,_}=Res when is_map(Map) ->
+ Res;
+ {NotMap,Eps0,St1} ->
+ %% Not a map. There will be a syntax error if we try to
+ %% pretty-print the Core Erlang code and then try to parse
+ %% it. To avoid the syntax error, force the term into a
+ %% variable.
+ {V,St2} = new_var(St1),
+ Anno = cerl:get_ann(NotMap),
+ Eps1 = [#iset{anno=#a{anno=Anno},var=V,arg=NotMap}],
+ {V,Eps0++Eps1,St2}
end.
badmap_term(_Map, #core{in_guard=true}) ->
@@ -928,10 +937,6 @@ maybe_warn_repeated_keys(Ck,Line,Used,St) ->
map_op(map_field_assoc) -> #c_literal{val=assoc};
map_op(map_field_exact) -> #c_literal{val=exact}.
-is_valid_map_src(#c_literal{val = M}) when is_map(M) -> true;
-is_valid_map_src(#c_var{}=Var) -> not cerl:is_c_fname(Var);
-is_valid_map_src(_) -> false.
-
%% try_exception([ExcpClause], St) -> {[ExcpVar],Handler,St}.
try_exception(Ecs0, St0) ->
@@ -3471,8 +3476,6 @@ format_error(nomatch) ->
"pattern cannot possibly match";
format_error(bad_binary) ->
"binary construction will fail because of a type mismatch";
-format_error(badmap) ->
- "map construction will fail because of a type mismatch";
format_error({map_key_repeated,Key}) when is_atom(Key) ->
io_lib:format("key '~w' will be overridden in expression", [Key]);
format_error({map_key_repeated,Key}) ->
diff --git a/lib/compiler/test/map_SUITE.erl b/lib/compiler/test/map_SUITE.erl
index 46c1acef4c..3c5c6214bc 100644
--- a/lib/compiler/test/map_SUITE.erl
+++ b/lib/compiler/test/map_SUITE.erl
@@ -979,6 +979,24 @@ t_update_assoc(Config) when is_list(Config) ->
BadMap = id(badmap),
{'EXIT',{{badmap,BadMap},_}} = (catch BadMap#{nonexisting=>val}),
{'EXIT',{{badmap,<<>>},_}} = (catch <<>>#{nonexisting=>val}),
+ F1 = fun() ->
+ 0 #{part => V = false},
+ V
+ end,
+ {'EXIT',{{badmap,0},_}} = (catch F1()),
+ F2 = fun() ->
+ case 42 of
+ V ->
+ [];
+ power ->
+ []#{key =>
+ receive
+ V -> false
+ end}
+ end,
+ V
+ end,
+ 42 = F2(),
%% Evaluation order.
{'EXIT',{blurf,_}} =
diff --git a/lib/compiler/test/warnings_SUITE.erl b/lib/compiler/test/warnings_SUITE.erl
index a91d8399ff..2abae7e9c7 100644
--- a/lib/compiler/test/warnings_SUITE.erl
+++ b/lib/compiler/test/warnings_SUITE.erl
@@ -621,8 +621,8 @@ maps(Config) when is_list(Config) ->
ok.
">>,
[],
- {warnings,[{3,v3_core,badmap}]}},
- {ok_map_literal_key,
+ {warnings,[{3,sys_core_fold,{eval_failure,badmap}}]}},
+ {ok_map_literal_key,
<<"
t() ->
V = id(1),
--
2.16.4