summaryrefslogtreecommitdiff
path: root/lib/stdlib/src
diff options
context:
space:
mode:
authorPéter Gömöri <gomoripeti@gmail.com>2021-05-29 12:55:58 +0200
committerPéter Gömöri <gomoripeti@gmail.com>2022-03-09 14:18:30 +0100
commitcc043f8a7d52ad48b41bb9dd89e199d811d09164 (patch)
tree792f23845a1510902d8902fe679a2e738723a3fc /lib/stdlib/src
parent9f6d99f8d285f76c2782aeadd33f547c1ab6024c (diff)
downloaderlang-cc043f8a7d52ad48b41bb9dd89e199d811d09164.tar.gz
Fully support maps in ms_transform
Before this change only map patterns worked and only in the shell via a hack in `normalise/1` (It converted a map pattern AST to map, but it did not convert a map expressions AST). Now the transformation takes care of map patterns in MS head and map expressions in MS guards/body and `normalise/1` only does what `erl_parse:normalise/1`. Checking restrictions on map keys and values is left to the PAM machine.
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r--lib/stdlib/src/ms_transform.erl21
1 files changed, 14 insertions, 7 deletions
diff --git a/lib/stdlib/src/ms_transform.erl b/lib/stdlib/src/ms_transform.erl
index f38b0eb905..dde8e572a3 100644
--- a/lib/stdlib/src/ms_transform.erl
+++ b/lib/stdlib/src/ms_transform.erl
@@ -756,7 +756,12 @@ tg({bin_element,Anno,X,Y,Z},B) ->
tg({bin,Anno,List},B) ->
{bin,Anno,[tg(X,B) || X <- List]};
-
+
+tg({map_field_assoc, Anno, Field, Value}, B) ->
+ {map_field_assoc, Anno, tg(Field, B), tg(Value, B)};
+tg({map, Anno, List}, B) ->
+ {map, Anno, [tg(X, B) || X <- List]};
+
tg(T,B) when is_tuple(T), tuple_size(T) >= 2 ->
Element = element(1,T),
Anno = element(2,T),
@@ -858,6 +863,9 @@ th({var,Anno,Name},B,OB) ->
Trans ->
{{atom,Anno,Trans},B}
end;
+th({map_field_exact,Anno,Field,Value},B,OB) ->
+ {[NField, NValue], NB} = th([Field, Value], B, OB),
+ {{map_field_assoc,Anno,NField,NValue}, NB};
th([H|T],B,OB) ->
{NH,NB} = th(H,B,OB),
{NT,NNB} = th(T,NB,OB),
@@ -1134,12 +1142,11 @@ normalise({op,_,'++',A,B}) ->
normalise(A) ++ normalise(B);
normalise({tuple,_,Args}) ->
list_to_tuple(normalise_list(Args));
-normalise({map,_,Pairs0}) ->
- Pairs1 = lists:map(fun ({map_field_exact,_,K,V}) ->
- {normalise(K),normalise(V)}
- end,
- Pairs0),
- maps:from_list(Pairs1);
+normalise({map,_,Pairs}) ->
+ maps:from_list(lists:map(fun
+ %% only allow '=>'
+ ({map_field_assoc,_,K,V}) -> {normalise(K),normalise(V)}
+ end, Pairs));
%% Special case for unary +/-.
normalise({op,_,'+',{char,_,I}}) -> I;
normalise({op,_,'+',{integer,_,I}}) -> I;