Skip to content

Commit

Permalink
Inline safe calls to maps:put/3
Browse files Browse the repository at this point in the history
Using the map syntax instead of `maps:put/3` is slightly more
efficient in itself, but also reduces register shuffling and can open
up for combining multiple adjacent map update operations into a single
update operation.
  • Loading branch information
bjorng committed Jun 3, 2024
1 parent 9c3096a commit 39756eb
Show file tree
Hide file tree
Showing 2 changed files with 57 additions and 3 deletions.
12 changes: 12 additions & 0 deletions lib/compiler/src/beam_ssa_type.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1497,6 +1497,8 @@ will_succeed_1(#b_set{op=has_map_field}, _Src, _Ts) ->
yes;
will_succeed_1(#b_set{op=get_tuple_element}, _Src, _Ts) ->
yes;
will_succeed_1(#b_set{op=put_map,args=[#b_literal{val=assoc}|_]}, _Src, _Ts) ->
yes;
will_succeed_1(#b_set{op=put_tuple}, _Src, _Ts) ->
yes;
will_succeed_1(#b_set{op=update_tuple,args=[Tuple | Updates]}, _Src, Ts) ->
Expand Down Expand Up @@ -1671,6 +1673,16 @@ simplify_remote_call(erlang, throw, [Term], Ts, I) ->
beam_ssa:add_anno(thrown_type, Type, I);
simplify_remote_call(erlang, '++', [#b_literal{val=[]},Tl], _Ts, _I) ->
Tl;
simplify_remote_call(maps=Mod, put=Name, [Key,Val,Map], Ts, I) ->
case concrete_type(Map, Ts) of
#t_map{} ->
%% This call to maps:put/3 cannot fail. Replace with the
%% slightly more efficient `put_map` instruction.
Args = [#b_literal{val=assoc},Map,Key,Val],
I#b_set{op=put_map,args=Args};
_ ->
simplify_pure_call(Mod, Name, [Key,Val,Map], I)
end;
simplify_remote_call(Mod, Name, Args, _Ts, I) ->
case erl_bifs:is_pure(Mod, Name, length(Args)) of
true ->
Expand Down
48 changes: 45 additions & 3 deletions system/doc/efficiency_guide/maps.md
Original file line number Diff line number Diff line change
Expand Up @@ -459,9 +459,51 @@ constructing an empty map.
If the key is known to already exist in the map, `maps:update/3` is slightly
more efficient than `maps:put/3`.

If the keys are constants known at compile-time, using the map update syntax
with the `=>` operator is more efficient than multiple calls to `maps:put/3`,
especially for small maps.
If the compiler can determine that the third argument is always a map, it
will rewrite the call to `maps:put/3` to use the map syntax for updating the map.

For example, consider the following function:

```erlang
add_to_known_map(Map0, A, B, C) when is_map(Map0) ->
Map1 = maps:put(a, A, Map0),
Map2 = maps:put(b, B, Map1),
maps:put(c, C, Map2).
```

The compiler first rewrites each call to `maps:put/3` to use the map
syntax, and subsequently combines the three update operations to a
single update operation:

```erlang
add_to_known_map(Map0, A, B, C) when is_map(Map0) ->
Map0#{a => A, b => B, c => C}.
```

If the compiler cannot determine that the third argument is always a
map, it retains the `maps:put/3` call. For example, given this
function:

```erlang
add_to_map(Map0, A, B, C) ->
Map1 = maps:put(a, A, Map0),
Map2 = maps:put(b, B, Map1),
maps:put(c, C, Map2).
```

the compiler keeps the first call to `maps:put/3`, but rewrites
and combines the other two calls:

```erlang
add_to_map(Map0, A, B, C) ->
Map1 = maps:put(a, A, Map0),
Map1#{b => B, c => C}.
```

> #### Change {: .info }
>
> The rewriting of `maps:put/3` to the map syntax was introduced in
> Erlang/OTP 28.
### maps:remove/2

Expand Down

0 comments on commit 39756eb

Please sign in to comment.