diff options
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r-- | lib/stdlib/src/erl_posix_msg.erl | 4 | ||||
-rw-r--r-- | lib/stdlib/src/maps.erl | 157 | ||||
-rw-r--r-- | lib/stdlib/src/rand.erl | 2 | ||||
-rw-r--r-- | lib/stdlib/src/uri_string.erl | 23 |
4 files changed, 79 insertions, 107 deletions
diff --git a/lib/stdlib/src/erl_posix_msg.erl b/lib/stdlib/src/erl_posix_msg.erl index 8959fea498..b9ed4a3a9d 100644 --- a/lib/stdlib/src/erl_posix_msg.erl +++ b/lib/stdlib/src/erl_posix_msg.erl @@ -81,9 +81,9 @@ message_1(el2hlt) -> <<"level 2 halted">>; message_1(el2nsync) -> <<"level 2 not synchronized">>; message_1(el3hlt) -> <<"level 3 halted">>; message_1(el3rst) -> <<"level 3 reset">>; -message_1(elibacc) -> <<"can not access a needed shared library">>; +message_1(elibacc) -> <<"cannot access a needed shared library">>; message_1(elibbad) -> <<"accessing a corrupted shared library">>; -message_1(elibexec) -> <<"can not exec a shared library directly">>; +message_1(elibexec) -> <<"cannot exec a shared library directly">>; message_1(elibmax) -> <<"attempting to link in more shared libraries than system limit">>; message_1(elibscn) -> <<".lib section in a.out corrupted">>; 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}. diff --git a/lib/stdlib/src/rand.erl b/lib/stdlib/src/rand.erl index 362e98006e..4951dc727b 100644 --- a/lib/stdlib/src/rand.erl +++ b/lib/stdlib/src/rand.erl @@ -486,7 +486,7 @@ uniform_real_s(Alg, Next, M0, BitNo, R1, V1, Bits) -> {M1 * math:pow(2.0, BitNo - 56), {Alg, R1}}; BitNo =:= -1008 -> %% Endgame - %% For the last round we can not have 14 zeros or more + %% For the last round we cannot have 14 zeros or more %% at the top of M1 because then we will underflow, %% so we need at least 43 bits if diff --git a/lib/stdlib/src/uri_string.erl b/lib/stdlib/src/uri_string.erl index f07307c039..d33dc89af8 100644 --- a/lib/stdlib/src/uri_string.erl +++ b/lib/stdlib/src/uri_string.erl @@ -415,7 +415,7 @@ transcode(URIString, Options) when is_list(URIString) -> %% (application/x-www-form-urlencoded encoding algorithm) %%------------------------------------------------------------------------- -spec compose_query(QueryList) -> QueryString when - QueryList :: [{unicode:chardata(), unicode:chardata()}], + QueryList :: [{unicode:chardata(), unicode:chardata() | true}], QueryString :: uri_string() | error(). compose_query(List) -> @@ -423,7 +423,7 @@ compose_query(List) -> -spec compose_query(QueryList, Options) -> QueryString when - QueryList :: [{unicode:chardata(), unicode:chardata()}], + QueryList :: [{unicode:chardata(), unicode:chardata() | true}], Options :: [{encoding, atom()}], QueryString :: uri_string() | error(). @@ -435,6 +435,11 @@ compose_query(List, Options) -> throw:{error, Atom, RestData} -> {error, Atom, RestData} end. %% +compose_query([{Key,true}|Rest], Options, IsList, Acc) -> + Separator = get_separator(Rest), + K = form_urlencode(Key, Options), + IsListNew = IsList orelse is_list(Key), + compose_query(Rest, Options, IsListNew, <<Acc/binary,K/binary,Separator/binary>>); compose_query([{Key,Value}|Rest], Options, IsList, Acc) -> Separator = get_separator(Rest), K = form_urlencode(Key, Options), @@ -454,7 +459,7 @@ compose_query([], _Options, IsList, Acc) -> %%------------------------------------------------------------------------- -spec dissect_query(QueryString) -> QueryList when QueryString :: uri_string(), - QueryList :: [{unicode:chardata(), unicode:chardata()}] + QueryList :: [{unicode:chardata(), unicode:chardata() | true}] | error(). dissect_query(<<>>) -> []; @@ -1889,13 +1894,12 @@ dissect_query_key(<<$=,T/binary>>, IsList, Acc, Key, Value) -> dissect_query_value(T, IsList, Acc, Key, Value); dissect_query_key(<<"&#",T/binary>>, IsList, Acc, Key, Value) -> dissect_query_key(T, IsList, Acc, <<Key/binary,"&#">>, Value); -dissect_query_key(<<$&,_T/binary>>, _IsList, _Acc, _Key, _Value) -> - throw({error, missing_value, "&"}); +dissect_query_key(T = <<$&,_/binary>>, IsList, Acc, Key, <<>>) -> + dissect_query_value(T, IsList, Acc, Key, true); dissect_query_key(<<H,T/binary>>, IsList, Acc, Key, Value) -> dissect_query_key(T, IsList, Acc, <<Key/binary,H>>, Value); -dissect_query_key(B, _, _, _, _) -> - throw({error, missing_value, B}). - +dissect_query_key(T = <<>>, IsList, Acc, Key, <<>>) -> + dissect_query_value(T, IsList, Acc, Key, true). dissect_query_value(<<$&,T/binary>>, IsList, Acc, Key, Value) -> K = form_urldecode(IsList, Key), @@ -1908,9 +1912,10 @@ dissect_query_value(<<>>, IsList, Acc, Key, Value) -> V = form_urldecode(IsList, Value), lists:reverse([{K,V}|Acc]). - %% HTML 5.2 - 4.10.21.6 URL-encoded form data - WHATWG URL (10 Jan 2018) - UTF-8 %% HTML 5.0 - 4.10.22.6 URL-encoded form data - decoding (non UTF-8) +form_urldecode(_, true) -> + true; form_urldecode(true, B) -> Result = base10_decode(form_urldecode(B, <<>>)), convert_to_list(Result, utf8); |