aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src/maps.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src/maps.erl')
-rw-r--r--lib/stdlib/src/maps.erl157
1 files changed, 62 insertions, 95 deletions
diff --git a/lib/stdlib/src/maps.erl b/lib/stdlib/src/maps.erl
index 60463feec2..51965ddb57 100644
--- a/lib/stdlib/src/maps.erl
+++ b/lib/stdlib/src/maps.erl
@@ -21,7 +21,7 @@
-module(maps).
-export([get/3, filter/2,fold/3,
- map/2, size/1,
+ map/2, size/1, new/0,
update_with/3, update_with/4,
without/2, with/2,
iterator/1, next/1]).
@@ -29,13 +29,15 @@
%% BIFs
-export([get/2, find/2, from_list/1,
is_key/2, keys/1, merge/2,
- new/0, put/3, remove/2, take/2,
+ put/3, remove/2, take/2,
to_list/1, update/3, values/1]).
--opaque iterator() :: {term(), term(), iterator()}
- | none | nonempty_improper_list(integer(),map()).
+-opaque iterator(Key, Value) :: {Key, Value, iterator(Key, Value)} | none
+ | nonempty_improper_list(integer(), #{Key => Value}).
--export_type([iterator/0]).
+-type iterator() :: iterator(term(), term()).
+
+-export_type([iterator/2, iterator/0]).
-dialyzer({no_improper_lists, iterator/1}).
@@ -50,9 +52,7 @@
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).
@@ -75,9 +75,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).
@@ -91,13 +90,6 @@ keys(_) -> erlang:nif_error(undef).
merge(_,_) -> erlang:nif_error(undef).
-
--spec new() -> Map when
- Map :: map().
-
-new() -> erlang:nif_error(undef).
-
-
%% Shadowed by erl_bif_types: maps:put/3
-spec put(Key,Value,Map1) -> Map2 when
Key :: term(),
@@ -116,17 +108,13 @@ 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).
-spec to_list(Map) -> [{Key,Value}] when
- Map :: map(),
- Key :: term(),
- Value :: term().
+ Map :: #{Key => Value}.
to_list(Map) when is_map(Map) ->
to_list_internal(erts_internal:map_next(0, Map, []));
@@ -140,79 +128,69 @@ to_list_internal(Acc) ->
%% 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 new() -> Map when
+ Map :: #{}.
+
+new() -> #{}.
+
-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) ->
- try maps:get(Key,Map) of
- Val -> maps:update(Key,Fun(Val),Map)
- catch
- error:{badkey,_} ->
- erlang:error({badkey,Key},[Key,Fun,Map])
+ case Map of
+ #{Key := Value} -> Map#{Key := Fun(Value)};
+ #{} -> erlang:error({badkey,Key},[Key,Fun,Map])
end;
update_with(Key,Fun,Map) ->
erlang:error(error_type(Map),[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 maps:find(Key,Map) of
- {ok,Val} -> maps:update(Key,Fun(Val),Map);
- error -> maps:put(Key,Init,Map)
+ case Map of
+ #{Key := Value} -> Map#{Key := Fun(Value)};
+ #{} -> Map#{Key => Init}
end;
update_with(Key,Fun,Init,Map) ->
erlang:error(error_type(Map),[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 maps:find(Key, Map) of
- {ok, Value} ->
- Value;
- error ->
- Default
+ case Map of
+ #{Key := Value} -> Value;
+ #{} -> Default
end;
get(Key,Map,Default) ->
erlang:error({badmap,Map},[Key,Map,Default]).
--spec filter(Pred,MapOrIter) -> Map when
+-spec filter(Pred, MapOrIter) -> Map when
Pred :: fun((Key, Value) -> boolean()),
- Key :: term(),
- Value :: term(),
- MapOrIter :: map() | iterator(),
- Map :: map().
+ MapOrIter :: #{Key => Value} | iterator(Key, Value),
+ Map :: #{Key => Value}.
filter(Pred,Map) when is_function(Pred,2), is_map(Map) ->
maps:from_list(filter_1(Pred, iterator(Map)));
@@ -235,14 +213,11 @@ filter_1(Pred, Iter) ->
end.
-spec fold(Fun,Init,MapOrIter) -> Acc when
- Fun :: fun((K, V, AccIn) -> AccOut),
+ Fun :: fun((Key, Value, AccIn) -> AccOut),
Init :: term(),
- Acc :: term(),
- AccIn :: term(),
- AccOut :: term(),
- MapOrIter :: map() | iterator(),
- K :: term(),
- V :: term().
+ Acc :: AccOut,
+ AccIn :: Init | AccOut,
+ MapOrIter :: #{Key => Value} | iterator(Key, Value).
fold(Fun,Init,Map) when is_function(Fun,3), is_map(Map) ->
fold_1(Fun,Init,iterator(Map));
@@ -260,12 +235,9 @@ fold_1(Fun, Acc, Iter) ->
end.
-spec map(Fun,MapOrIter) -> Map when
- Fun :: fun((K, V1) -> V2),
- MapOrIter :: map() | iterator(),
- Map :: map(),
- K :: term(),
- V1 :: term(),
- V2 :: term().
+ Fun :: fun((Key, Value1) -> Value2),
+ MapOrIter :: #{Key => Value1} | iterator(Key, Value1),
+ Map :: #{Key => Value2}.
map(Fun,Map) when is_function(Fun, 2), is_map(Map) ->
maps:from_list(map_1(Fun, iterator(Map)));
@@ -291,17 +263,15 @@ size(Val) ->
erlang:error({badmap,Val},[Val]).
-spec iterator(Map) -> Iterator when
- Map :: map(),
- Iterator :: iterator().
+ Map :: #{Key => Value},
+ Iterator :: iterator(Key, Value).
iterator(M) when is_map(M) -> [0 | M];
iterator(M) -> erlang:error({badmap, M}, [M]).
-spec next(Iterator) -> {Key, Value, NextIterator} | 'none' when
- Iterator :: iterator(),
- Key :: term(),
- Value :: term(),
- NextIterator :: iterator().
+ Iterator :: iterator(Key, Value),
+ NextIterator :: iterator(Key, Value).
next({K, V, I}) ->
{K, V, I};
next([Path | Map]) when is_integer(Path), is_map(Map) ->
@@ -318,29 +288,26 @@ next(Iter) ->
K :: term().
without(Ks,M) when is_list(Ks), is_map(M) ->
- lists:foldl(fun(K, M1) -> maps:remove(K, M1) end, M, Ks);
+ lists:foldl(fun maps:remove/2, M, Ks);
without(Ks,M) ->
erlang:error(error_type(M),[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) ->
- Fun = fun(K, List) ->
- case maps:find(K, Map1) of
- {ok, V} ->
- [{K, V} | List];
- error ->
- List
- end
- end,
- maps:from_list(lists:foldl(Fun, [], Ks));
+ maps:from_list(with_1(Ks, Map1));
with(Ks,M) ->
erlang:error(error_type(M),[Ks,M]).
+with_1([K|Ks], Map) ->
+ case Map of
+ #{K := V} -> [{K,V}|with_1(Ks, Map)];
+ #{} -> with_1(Ks, Map)
+ end;
+with_1([], _Map) -> [].
error_type(M) when is_map(M) -> badarg;
error_type(V) -> {badmap, V}.