File 2584-Refine-types-of-functions-in-maps-module.patch of Package erlang
From 7cae8734155671908264dc5ad057879125125ffe Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Micha=C5=82=20Muska=C5=82a?= <michal@muskala.eu>
Date: Thu, 19 Jul 2018 19:37:07 +0200
Subject: [PATCH 2/2] Refine types of functions in maps module
This only touches functions that are not further manually enhanced in
erl_bif_types. The hope is that this will allow dialyzer to discover
more issues in code using maps.
---
.../test/small_SUITE_data/results/maps_sum | 2 +-
lib/stdlib/doc/src/maps.xml | 34 +++---
lib/stdlib/src/maps.erl | 101 +++++++-----------
3 files changed, 59 insertions(+), 78 deletions(-)
diff --git a/lib/stdlib/doc/src/maps.xml b/lib/stdlib/doc/src/maps.xml
index a225dea3b5..4c5199ca2b 100644
--- a/lib/stdlib/doc/src/maps.xml
+++ b/lib/stdlib/doc/src/maps.xml
@@ -75,8 +75,8 @@
<name name="fold" arity="3"/>
<fsummary></fsummary>
<desc>
- <p>Calls <c>F(K, V, AccIn)</c> for every <c><anno>K</anno></c> to value
- <c><anno>V</anno></c> association in <c><anno>Map</anno></c> in
+ <p>Calls <c>F(Key, Value, AccIn)</c> for every <c><anno>Key</anno></c> to value
+ <c><anno>Value</anno></c> association in <c><anno>Map</anno></c> in
any order. Function <c>fun F/3</c> must return a new
accumulator, which is passed to the next successive call.
This function returns the final value of the accumulator. The initial
@@ -189,10 +189,10 @@ false</code>
<fsummary></fsummary>
<desc>
<p>Produces a new map <c><anno>Map2</anno></c> by calling function
- <c>fun F(K, V1)</c> for every <c><anno>K</anno></c> to value
- <c><anno>V1</anno></c> association in <c><anno>Map1</anno></c> in
+ <c>fun F(Key, Value1)</c> for every <c><anno>Key</anno></c> to value
+ <c><anno>Value1</anno></c> association in <c><anno>Map1</anno></c> in
any order. Function <c>fun F/2</c> must return value
- <c><anno>V2</anno></c> to be associated with key <c><anno>K</anno></c>
+ <c><anno>Value2</anno></c> to be associated with key <c><anno>Key</anno></c>
for the new map <c><anno>Map2</anno></c>.</p>
<p><em>Example:</em></p>
<code type="none">
diff --git a/lib/stdlib/src/maps.erl b/lib/stdlib/src/maps.erl
index 12302ce839..da0f92e412 100644
--- a/lib/stdlib/src/maps.erl
+++ b/lib/stdlib/src/maps.erl
@@ -39,11 +39,8 @@
get(_,_) -> erlang:nif_error(undef).
-
-spec find(Key,Map) -> {ok, Value} | error when
- Key :: term(),
- Map :: map(),
- Value :: term().
+ Map :: #{Key => Value, _ => _}.
find(_,_) -> erlang:nif_error(undef).
@@ -66,9 +63,8 @@ is_key(_,_) -> erlang:nif_error(undef).
-spec keys(Map) -> Keys when
- Map :: map(),
- Keys :: [Key],
- Key :: term().
+ Map :: #{Key => _},
+ Keys :: [Key].
keys(_) -> erlang:nif_error(undef).
@@ -107,46 +103,38 @@ put(_,_,_) -> erlang:nif_error(undef).
remove(_,_) -> erlang:nif_error(undef).
-spec take(Key,Map1) -> {Value,Map2} | error when
- Key :: term(),
- Map1 :: map(),
- Value :: term(),
- Map2 :: map().
+ Map1 :: #{Key => Value, _ => _},
+ Map2 :: #{_ => _}.
take(_,_) -> erlang:nif_error(undef).
%% Shadowed by erl_bif_types: maps:to_list/1
-spec to_list(Map) -> [{Key,Value}] when
- Map :: map(),
- Key :: term(),
- Value :: term().
+ Map :: #{Key => Value}.
to_list(_) -> erlang:nif_error(undef).
%% Shadowed by erl_bif_types: maps:update/3
-spec update(Key,Value,Map1) -> Map2 when
- Key :: term(),
- Value :: term(),
- Map1 :: map(),
- Map2 :: map().
+ Map1 :: #{Key := _, _ => _},
+ Map2 :: #{Key := Value, _ => _}.
update(_,_,_) -> erlang:nif_error(undef).
-spec values(Map) -> Values when
- Map :: map(),
- Values :: [Value],
- Value :: term().
+ Map :: #{_ => Value},
+ Values :: [Value].
values(_) -> erlang:nif_error(undef).
%% End of BIFs
-spec update_with(Key,Fun,Map1) -> Map2 when
- Key :: term(),
- Map1 :: map(),
- Map2 :: map(),
- Fun :: fun((Value1 :: term()) -> Value2 :: term()).
+ Map1 :: #{Key := Value1, _ => _},
+ Map2 :: #{Key := Value2, _ => _},
+ Fun :: fun((Value1) -> Value2).
update_with(Key,Fun,Map) when is_function(Fun,1), is_map(Map) ->
case Map of
@@ -158,11 +146,9 @@ update_with(Key,Fun,Map) ->
-spec update_with(Key,Fun,Init,Map1) -> Map2 when
- Key :: term(),
- Map1 :: Map1,
- Map2 :: Map2,
- Fun :: fun((Value1 :: term()) -> Value2 :: term()),
- Init :: term().
+ Map1 :: #{Key => Value1, _ => _},
+ Map2 :: #{Key := Value2 | Init, _ => _},
+ Fun :: fun((Value1) -> Value2).
update_with(Key,Fun,Init,Map) when is_function(Fun,1), is_map(Map) ->
case Map of
@@ -174,10 +160,7 @@ update_with(Key,Fun,Init,Map) ->
-spec get(Key, Map, Default) -> Value | Default when
- Key :: term(),
- Map :: map(),
- Value :: term(),
- Default :: term().
+ Map :: #{Key => Value, _ => _}.
get(Key,Map,Default) when is_map(Map) ->
case Map of
@@ -188,12 +171,10 @@ get(Key,Map,Default) ->
erlang:error({badmap,Map},[Key,Map,Default]).
--spec filter(Pred,Map1) -> Map2 when
+-spec filter(Pred, Map1) -> Map2 when
Pred :: fun((Key, Value) -> boolean()),
- Key :: term(),
- Value :: term(),
- Map1 :: map(),
- Map2 :: map().
+ Map1 :: #{Key => Value},
+ Map2 :: #{Key => Value}.
filter(Pred,Map) when is_function(Pred,2), is_map(Map) ->
maps:from_list([{K,V}||{K,V}<-maps:to_list(Map),Pred(K,V)]);
@@ -202,14 +183,11 @@ filter(Pred,Map) ->
-spec fold(Fun,Init,Map) -> Acc when
- Fun :: fun((K, V, AccIn) -> AccOut),
+ Fun :: fun((Key, Value, AccIn) -> AccOut),
Init :: term(),
- Acc :: term(),
- AccIn :: term(),
- AccOut :: term(),
- Map :: map(),
- K :: term(),
- V :: term().
+ Acc :: AccOut,
+ AccIn :: Init | AccOut,
+ Map :: #{Key => Value}.
fold(Fun,Init,Map) when is_function(Fun,3), is_map(Map) ->
lists:foldl(fun({K,V},A) -> Fun(K,V,A) end,Init,maps:to_list(Map));
@@ -217,12 +195,9 @@ fold(Fun,Init,Map) ->
erlang:error(error_type(Map),[Fun,Init,Map]).
-spec map(Fun,Map1) -> Map2 when
- Fun :: fun((K, V1) -> V2),
- Map1 :: map(),
- Map2 :: map(),
- K :: term(),
- V1 :: term(),
- V2 :: term().
+ Fun :: fun((Key, Value1) -> Value2),
+ Map1 :: #{Key => Value1},
+ Map2 :: #{Key => Value2}.
map(Fun,Map) when is_function(Fun, 2), is_map(Map) ->
maps:from_list([{K,Fun(K,V)}||{K,V}<-maps:to_list(Map)]);
@@ -253,9 +228,8 @@ without(Ks,M) ->
-spec with(Ks, Map1) -> Map2 when
Ks :: [K],
- Map1 :: map(),
- Map2 :: map(),
- K :: term().
+ Map1 :: #{K => V, _ => _},
+ Map2 :: #{K => V}.
with(Ks,Map1) when is_list(Ks), is_map(Map1) ->
?MODULE:from_list(with_1(Ks, Map1));
--
2.18.0