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/gen_statem.erl | 261 | ||||
-rw-r--r-- | lib/stdlib/src/maps.erl | 157 | ||||
-rw-r--r-- | lib/stdlib/src/otp_internal.erl | 6 | ||||
-rw-r--r-- | lib/stdlib/src/rand.erl | 563 | ||||
-rw-r--r-- | lib/stdlib/src/stdlib.app.src | 2 | ||||
-rw-r--r-- | lib/stdlib/src/uri_string.erl | 23 |
7 files changed, 744 insertions, 272 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/gen_statem.erl b/lib/stdlib/src/gen_statem.erl index faa43fbc1e..24b268cd38 100644 --- a/lib/stdlib/src/gen_statem.erl +++ b/lib/stdlib/src/gen_statem.erl @@ -330,6 +330,7 @@ %% Type validation functions +%% - return true if the value is of the type, false otherwise -compile( {inline, [callback_mode/1, state_enter/1, @@ -1277,7 +1278,7 @@ parse_actions(StateCall, Debug, S, [Action|Actions], TransOpts) -> end. parse_actions_reply( - StateCall, ?not_sys_debug, S, Actions, TransOpts, + StateCall, ?not_sys_debug = Debug, S, Actions, TransOpts, From, Reply) -> %% case from(From) of @@ -1287,8 +1288,7 @@ parse_actions_reply( false -> [error, {bad_action_from_state_function,{reply,From,Reply}}, - ?STACKTRACE(), - ?not_sys_debug] + ?STACKTRACE(), Debug] end; parse_actions_reply( StateCall, Debug, #state{name = Name, state = State} = S, @@ -1302,12 +1302,11 @@ parse_actions_reply( false -> [error, {bad_action_from_state_function,{reply,From,Reply}}, - ?STACKTRACE(), - Debug] + ?STACKTRACE(), Debug] end. parse_actions_next_event( - StateCall, ?not_sys_debug, S, + StateCall, ?not_sys_debug = Debug, S, Actions, TransOpts, Type, Content) -> case event_type(Type) of true when StateCall -> @@ -1320,8 +1319,7 @@ parse_actions_next_event( [error, {bad_state_enter_action_from_state_function, {next_event,Type,Content}}, - ?STACKTRACE(), - ?not_sys_debug] + ?STACKTRACE(), Debug] end; parse_actions_next_event( StateCall, Debug, #state{name = Name, state = State} = S, @@ -1403,13 +1401,13 @@ parse_actions_timeout_add( loop_event_done( Parent, ?not_sys_debug, #state{postponed = P} = S, +%% #state{postponed = will_not_happen = P} = S, Events, Event, NextState, NewData, #trans_opts{ postpone = Postpone, hibernate = Hibernate, - timeouts_r = [], next_events_r = []}) -> + timeouts_r = [], next_events_r = NextEventsR}) -> %% - %% Optimize the simple cases - %% i.e no timer changes, no inserted events and no debug, + %% Optimize the simple cases i.e no debug and no timer changes, %% by duplicate stripped down code %% %% Fast path @@ -1417,14 +1415,12 @@ loop_event_done( case Postpone of true -> loop_event_done_fast( - Parent, Hibernate, - S, - Events, [Event|P], NextState, NewData); + Parent, Hibernate, S, + Events, [Event|P], NextState, NewData, NextEventsR); false -> loop_event_done_fast( - Parent, Hibernate, - S, - Events, P, NextState, NewData) + Parent, Hibernate, S, + Events, P, NextState, NewData, NextEventsR) end; loop_event_done( Parent, Debug_0, @@ -1456,26 +1452,23 @@ loop_event_done( {S#state.name,State}, {consume,Event_0,NextState})|P_0] end, - {Events_2,P_2,Timers_2} = - %% Move all postponed events to queue, - %% cancel the event timer, - %% and cancel the state timeout if the state changes - if - NextState =:= State -> - {Events_0,P_1, + {Events_2,P_2, + Timers_2} = + %% Cancel the event timeout + if + NextState =:= State -> + {Events_0,P_1, cancel_timer_by_type( timeout, {TimerTypes_0,CancelTimers_0})}; - true -> - {lists:reverse(P_1, Events_0), - [], - cancel_timer_by_type( - state_timeout, + true -> + %% Move all postponed events to queue + %% and cancel the state timeout + {lists:reverse(P_1, Events_0),[], + cancel_timer_by_type( + state_timeout, cancel_timer_by_type( timeout, {TimerTypes_0,CancelTimers_0}))} - %% The state timer is removed from TimerTypes - %% but remains in TimerRefs until we get - %% the cancel_timer msg - end, + end, {TimerRefs_3,{TimerTypes_3,CancelTimers_3},TimeoutEvents} = %% Stop and start timers parse_timers(TimerRefs_0, Timers_2, TimeoutsR), @@ -1495,114 +1488,144 @@ loop_event_done( hibernate = Hibernate}, lists:reverse(Events_4R)). +loop_event_done(Parent, Debug, S, Q) -> +%% io:format( +%% "loop_event_done:~n" +%% " state = ~p, data = ~p, postponed = ~p~n " +%% " timer_refs = ~p, timer_types = ~p, cancel_timers = ~p.~n" +%% " Q = ~p.~n", +%% [S#state.state,S#state.data,S#state.postponed, +%% S#state.timer_refs,S#state.timer_types,S#state.cancel_timers, +%% Q]), + case Q of + [] -> + %% Get a new event + loop(Parent, Debug, S); + [{Type,Content}|Events] -> + %% Loop until out of enqueued events + loop_event(Parent, Debug, S, Events, Type, Content) + end. + + %% Fast path %% +%% Cancel event timer and state timer only if running loop_event_done_fast( Parent, Hibernate, #state{ state = NextState, - timer_types = #{timeout := _} = TimerTypes, + timer_types = TimerTypes, cancel_timers = CancelTimers} = S, - Events, P, NextState, NewData) -> - %% - %% Same state, event timeout active - %% - loop_event_done_fast( - Parent, Hibernate, S, - Events, P, NextState, NewData, - cancel_timer_by_type( - timeout, {TimerTypes,CancelTimers})); -loop_event_done_fast( - Parent, Hibernate, - #state{state = NextState} = S, - Events, P, NextState, NewData) -> - %% + Events, P, NextState, NewData, NextEventsR) -> %% Same state - %% - loop_event_done( - Parent, ?not_sys_debug, - S#state{ - data = NewData, - postponed = P, - hibernate = Hibernate}, - Events); -loop_event_done_fast( - Parent, Hibernate, - #state{ - timer_types = #{timeout := _} = TimerTypes, - cancel_timers = CancelTimers} = S, - Events, P, NextState, NewData) -> - %% - %% State change, event timeout active - %% - loop_event_done_fast( - Parent, Hibernate, S, - lists:reverse(P, Events), [], NextState, NewData, - cancel_timer_by_type( - state_timeout, - cancel_timer_by_type( - timeout, {TimerTypes,CancelTimers}))); + case TimerTypes of + #{timeout := _} -> + %% Event timeout active + loop_event_done_fast_2( + Parent, Hibernate, S, + Events, P, NextState, NewData, NextEventsR, + cancel_timer_by_type( + timeout, {TimerTypes,CancelTimers})); + _ -> + %% No event timeout active + loop_event_done_fast_2( + Parent, Hibernate, S, + Events, P, NextState, NewData, NextEventsR, + {TimerTypes,CancelTimers}) + end; loop_event_done_fast( Parent, Hibernate, #state{ - timer_types = #{state_timeout := _} = TimerTypes, + timer_types = TimerTypes, cancel_timers = CancelTimers} = S, - Events, P, NextState, NewData) -> - %% - %% State change, state timeout active - %% - loop_event_done_fast( - Parent, Hibernate, S, - lists:reverse(P, Events), [], NextState, NewData, - cancel_timer_by_type( - state_timeout, - cancel_timer_by_type( - timeout, {TimerTypes,CancelTimers}))); + Events, P, NextState, NewData, NextEventsR) -> + %% State change + case TimerTypes of + #{timeout := _} -> + %% Event timeout active + %% - cancel state_timeout too since it is faster than inspecting + loop_event_done_fast( + Parent, Hibernate, S, + Events, P, NextState, NewData, NextEventsR, + cancel_timer_by_type( + state_timeout, + cancel_timer_by_type( + timeout, {TimerTypes,CancelTimers}))); + #{state_timeout := _} -> + %% State_timeout active but not event timeout + loop_event_done_fast( + Parent, Hibernate, S, + Events, P, NextState, NewData, NextEventsR, + cancel_timer_by_type( + state_timeout, {TimerTypes,CancelTimers})); + _ -> + %% No event nor state_timeout active + loop_event_done_fast( + Parent, Hibernate, S, + Events, P, NextState, NewData, NextEventsR, + {TimerTypes,CancelTimers}) + end. +%% +%% Retry postponed events loop_event_done_fast( - Parent, Hibernate, - #state{} = S, - Events, P, NextState, NewData) -> - %% - %% State change, no timeout to automatically cancel - %% - loop_event_done( - Parent, ?not_sys_debug, - S#state{ - state = NextState, - data = NewData, - postponed = [], - hibernate = Hibernate}, - lists:reverse(P, Events)). + Parent, Hibernate, S, + Events, P, NextState, NewData, NextEventsR, TimerTypes_CancelTimers) -> + case P of + %% Handle 0..2 postponed events without list reversal since + %% that will move out all live registers and back again + [] -> + loop_event_done_fast_2( + Parent, Hibernate, S, + Events, [], NextState, NewData, NextEventsR, + TimerTypes_CancelTimers); + [E] -> + loop_event_done_fast_2( + Parent, Hibernate, S, + [E|Events], [], NextState, NewData, NextEventsR, + TimerTypes_CancelTimers); + [E1,E2] -> + loop_event_done_fast_2( + Parent, Hibernate, S, + [E2,E1|Events], [], NextState, NewData, NextEventsR, + TimerTypes_CancelTimers); + _ -> + %% A bit slower path + loop_event_done_fast_2( + Parent, Hibernate, S, + lists:reverse(P, Events), [], NextState, NewData, NextEventsR, + TimerTypes_CancelTimers) + end. %% %% Fast path %% -loop_event_done_fast( +loop_event_done_fast_2( Parent, Hibernate, S, - Events, P, NextState, NewData, + Events, P, NextState, NewData, NextEventsR, {TimerTypes,CancelTimers}) -> %% - loop_event_done( - Parent, ?not_sys_debug, - S#state{ - state = NextState, - data = NewData, - postponed = P, - timer_types = TimerTypes, - cancel_timers = CancelTimers, - hibernate = Hibernate}, - Events). - -loop_event_done(Parent, Debug, S, Q) -> - case Q of + NewS = + S#state{ + state = NextState, + data = NewData, + postponed = P, + timer_types = TimerTypes, + cancel_timers = CancelTimers, + hibernate = Hibernate}, + case NextEventsR of + %% Handle 0..2 next events without list reversal since + %% that will move out all live registers and back again [] -> - %% Get a new event - loop(Parent, Debug, S); - [{Type,Content}|Events] -> - %% Loop until out of enqueued events - loop_event(Parent, Debug, S, Events, Type, Content) + loop_event_done(Parent, ?not_sys_debug, NewS, Events); + [E] -> + loop_event_done(Parent, ?not_sys_debug, NewS, [E|Events]); + [E2,E1] -> + loop_event_done(Parent, ?not_sys_debug, NewS, [E1,E2|Events]); + _ -> + %% A bit slower path + loop_event_done( + Parent, ?not_sys_debug, NewS, lists:reverse(NextEventsR, Events)) end. - %%--------------------------------------------------------------------------- %% Server loop helpers 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/otp_internal.erl b/lib/stdlib/src/otp_internal.erl index aaed13ba3a..2cfc702b53 100644 --- a/lib/stdlib/src/otp_internal.erl +++ b/lib/stdlib/src/otp_internal.erl @@ -398,10 +398,8 @@ obsolete_1(megaco, format_versions, 1) -> %% *** OS-MON-MIB *** -obsolete_1(os_mon_mib, init, 1) -> - {deprecated, {os_mon_mib, load, 1}}; -obsolete_1(os_mon_mib, stop, 1) -> - {deprecated, {os_mon_mib, unload, 1}}; +obsolete_1(os_mon_mib, _, _) -> + {removed, "was removed in 22.0"}; obsolete_1(auth, is_auth, 1) -> {deprecated, {net_adm, ping, 1}}; diff --git a/lib/stdlib/src/rand.erl b/lib/stdlib/src/rand.erl index 362e98006e..3a9a1e007b 100644 --- a/lib/stdlib/src/rand.erl +++ b/lib/stdlib/src/rand.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2015-2017. All Rights Reserved. +%% Copyright Ericsson AB 2015-2018. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -32,18 +32,24 @@ uniform/0, uniform/1, uniform_s/1, uniform_s/2, uniform_real/0, uniform_real_s/1, jump/0, jump/1, - normal/0, normal/2, normal_s/1, normal_s/3 + normal/0, normal/2, normal_s/1, normal_s/3 ]). +%% Test, dev and internal +-export([exro928_jump_2pow512/1, exro928_jump_2pow20/1, + exro928_seed/1, exro928_next/1, exro928_next_state/1, + format_jumpconst58/1, seed58/2]). + %% Debug -export([make_float/3, float2str/1, bc64/1]). --compile({inline, [exs64_next/1, exsplus_next/1, +-compile({inline, [exs64_next/1, exsplus_next/1, exsss_next/1, exs1024_next/1, exs1024_calc/2, + exro928_next_state/4, exrop_next/1, exrop_next_s/2, get_52/1, normal_kiwi/1]}). --define(DEFAULT_ALG_HANDLER, exrop). +-define(DEFAULT_ALG_HANDLER, exsss). -define(SEED_DICT, rand_seed). %% ===================================================================== @@ -80,8 +86,8 @@ %% This depends on the algorithm handler function -type alg_state() :: - exs64_state() | exsplus_state() | exs1024_state() | - exrop_state() | term(). + exsplus_state() | exro928_state() | exrop_state() | exs1024_state() | + exs64_state() | term(). %% This is the algorithm handling definition within this module, %% and the type to use for plugins. @@ -124,14 +130,17 @@ %% Algorithm state -type state() :: {alg_handler(), alg_state()}. --type builtin_alg() :: exs64 | exsplus | exsp | exs1024 | exs1024s | exrop. +-type builtin_alg() :: + exsss | exro928ss | exrop | exs1024s | exsp | exs64 | exsplus | exs1024. -type alg() :: builtin_alg() | atom(). -type export_state() :: {alg(), alg_state()}. +-type seed() :: [integer()] | integer() | {integer(), integer(), integer()}. -export_type( [builtin_alg/0, alg/0, alg_handler/0, alg_state/0, - state/0, export_state/0]). + state/0, export_state/0, seed/0]). -export_type( - [exs64_state/0, exsplus_state/0, exs1024_state/0, exrop_state/0]). + [exsplus_state/0, exro928_state/0, exrop_state/0, exs1024_state/0, + exs64_state/0]). %% ===================================================================== %% Range macro and helper @@ -229,12 +238,12 @@ export_seed() -> end. -spec export_seed_s(State :: state()) -> export_state(). -export_seed_s({#{type:=Alg}, Seed}) -> {Alg, Seed}. +export_seed_s({#{type:=Alg}, AlgState}) -> {Alg, AlgState}. %% seed(Alg) seeds RNG with runtime dependent values %% and return the NEW state -%% seed({Alg,Seed}) setup RNG with a previously exported seed +%% seed({Alg,AlgState}) setup RNG with a previously exported seed %% and return the NEW state -spec seed( @@ -246,11 +255,11 @@ seed(Alg) -> -spec seed_s( AlgOrStateOrExpState :: builtin_alg() | state() | export_state()) -> state(). -seed_s({AlgHandler, _Seed} = State) when is_map(AlgHandler) -> +seed_s({AlgHandler, _AlgState} = State) when is_map(AlgHandler) -> State; -seed_s({Alg0, Seed}) -> - {Alg,_SeedFun} = mk_alg(Alg0), - {Alg, Seed}; +seed_s({Alg, AlgState}) when is_atom(Alg) -> + {AlgHandler,_SeedFun} = mk_alg(Alg), + {AlgHandler,AlgState}; seed_s(Alg) -> seed_s(Alg, {erlang:phash2([{node(),self()}]), erlang:system_time(), @@ -259,19 +268,15 @@ seed_s(Alg) -> %% seed/2: seeds RNG with the algorithm and given values %% and returns the NEW state. --spec seed( - Alg :: builtin_alg(), Seed :: {integer(), integer(), integer()}) -> - state(). -seed(Alg0, S0) -> - seed_put(seed_s(Alg0, S0)). +-spec seed(Alg :: builtin_alg(), Seed :: seed()) -> state(). +seed(Alg, Seed) -> + seed_put(seed_s(Alg, Seed)). --spec seed_s( - Alg :: builtin_alg(), Seed :: {integer(), integer(), integer()}) -> - state(). -seed_s(Alg0, S0 = {_, _, _}) -> - {Alg, Seed} = mk_alg(Alg0), - AS = Seed(S0), - {Alg, AS}. +-spec seed_s(Alg :: builtin_alg(), Seed :: seed()) -> state(). +seed_s(Alg, Seed) -> + {AlgHandler,SeedFun} = mk_alg(Alg), + AlgState = SeedFun(Seed), + {AlgHandler,AlgState}. %%% uniform/0, uniform/1, uniform_s/1, uniform_s/2 are all %%% uniformly distributed random numbers. @@ -281,8 +286,8 @@ seed_s(Alg0, S0 = {_, _, _}) -> -spec uniform() -> X :: float(). uniform() -> - {X, Seed} = uniform_s(seed_get()), - _ = seed_put(Seed), + {X, State} = uniform_s(seed_get()), + _ = seed_put(State), X. %% uniform/1: given an integer N >= 1, @@ -291,8 +296,8 @@ uniform() -> -spec uniform(N :: pos_integer()) -> X :: pos_integer(). uniform(N) -> - {X, Seed} = uniform_s(N, seed_get()), - _ = seed_put(Seed), + {X, State} = uniform_s(N, seed_get()), + _ = seed_put(State), X. %% uniform_s/1: given a state, uniform_s/1 @@ -486,7 +491,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 @@ -613,6 +618,11 @@ mk_alg(exsp) -> uniform=>fun exsp_uniform/1, uniform_n=>fun exsp_uniform/2, jump=>fun exsplus_jump/1}, fun exsplus_seed/1}; +mk_alg(exsss) -> + {#{type=>exsss, bits=>58, next=>fun exsss_next/1, + uniform=>fun exsss_uniform/1, uniform_n=>fun exsss_uniform/2, + jump=>fun exsplus_jump/1}, + fun exsss_seed/1}; mk_alg(exs1024) -> {#{type=>exs1024, max=>?MASK(64), next=>fun exs1024_next/1, jump=>fun exs1024_jump/1}, @@ -625,7 +635,13 @@ mk_alg(exrop) -> {#{type=>exrop, bits=>58, weak_low_bits=>1, next=>fun exrop_next/1, uniform=>fun exrop_uniform/1, uniform_n=>fun exrop_uniform/2, jump=>fun exrop_jump/1}, - fun exrop_seed/1}. + fun exrop_seed/1}; +mk_alg(exro928ss) -> + {#{type=>exro928ss, bits=>58, next=>fun exro928ss_next/1, + uniform=>fun exro928ss_uniform/1, + uniform_n=>fun exro928ss_uniform/2, + jump=>fun exro928_jump/1}, + fun exro928_seed/1}. %% ===================================================================== %% exs64 PRNG: Xorshift64* @@ -635,6 +651,14 @@ mk_alg(exrop) -> -opaque exs64_state() :: uint64(). +exs64_seed(L) when is_list(L) -> + [R] = seed64_nz(1, L), + R; +exs64_seed(A) when is_integer(A) -> + [R] = seed64(1, ?MASK(64, A)), + R; +%% +%% Traditional integer triplet seed exs64_seed({A1, A2, A3}) -> {V1, _} = exs64_next((?MASK(32, A1) * 4294967197 + 1)), {V2, _} = exs64_next((?MASK(32, A2) * 4294967231 + 1)), @@ -656,11 +680,49 @@ exs64_next(R) -> %% 58 bits fits into an immediate on 64bits erlang and is thus much faster. %% Modification of the original Xorshift128+ algorithm to 116 %% by Sebastiano Vigna, a lot of thanks for his help and work. +%% +%% Reference C code for Xorshift116+ and Xorshift116** +%% +%% #include <stdint.h> +%% +%% #define MASK(b, v) (((UINT64_C(1) << (b)) - 1) & (v)) +%% #define BSL(b, v, n) (MASK((b)-(n), (v)) << (n)) +%% #define ROTL(b, v, n) (BSL((b), (v), (n)) | ((v) >> ((b)-(n)))) +%% +%% uint64_t s[2]; +%% +%% uint64_t next(void) { +%% uint64_t s1 = s[0]; +%% const uint64_t s0 = s[1]; +%% +%% s1 ^= BSL(58, s1, 24); // a +%% s1 ^= s0 ^ (s1 >> 11) ^ (s0 >> 41); // b, c +%% s[0] = s0; +%% s[1] = s1; +%% +%% const uint64_t result_plus = MASK(58, s0 + s1); +%% uint64_t result_starstar = s0; +%% result_starstar = MASK(58, result_starstar * 5); +%% result_starstar = ROTL(58, result_starstar, 7); +%% result_starstar = MASK(58, result_starstar * 9); +%% +%% return result_plus; +%% return result_starstar; +%% } +%% %% ===================================================================== -opaque exsplus_state() :: nonempty_improper_list(uint58(), uint58()). -dialyzer({no_improper_lists, exsplus_seed/1}). +exsplus_seed(L) when is_list(L) -> + [S0,S1] = seed58_nz(2, L), + [S0|S1]; +exsplus_seed(X) when is_integer(X) -> + [S0,S1] = seed58(2, ?MASK(64, X)), + [S0|S1]; +%% +%% Traditional integer triplet seed exsplus_seed({A1, A2, A3}) -> {_, R1} = exsplus_next( [?MASK(58, (A1 * 4294967197) + 1)| @@ -670,16 +732,62 @@ exsplus_seed({A1, A2, A3}) -> tl(R1)]), R2. +-dialyzer({no_improper_lists, exsss_seed/1}). + +exsss_seed(L) when is_list(L) -> + [S0,S1] = seed58_nz(2, L), + [S0|S1]; +exsss_seed(X) when is_integer(X) -> + [S0,S1] = seed58(2, ?MASK(64, X)), + [S0|S1]; +%% +%% Seed from traditional integer triple - mix into splitmix +exsss_seed({A1, A2, A3}) -> + {_, X0} = seed58(?MASK(64, A1)), + {S0, X1} = seed58(?MASK(64, A2) bxor X0), + {S1, _} = seed58(?MASK(64, A3) bxor X1), + [S0|S1]. + +%% Advance Xorshift116 state one step +-define( + exs_next(S0, S1, S1_b), + begin + S1_b = S1 bxor ?BSL(58, S1, 24), + S1_b bxor S0 bxor (S1_b bsr 11) bxor (S0 bsr 41) + end). + +-define( + scramble_starstar(S, V_a, V_b), + begin + %% The multiply by add shifted trick avoids creating bignums + %% which improves performance significantly + %% + V_a = ?MASK(58, S + ?BSL(58, S, 2)), % V_a = S * 5 + V_b = ?ROTL(58, V_a, 7), + ?MASK(58, V_b + ?BSL(58, V_b, 3)) % V_b * 9 + end). + -dialyzer({no_improper_lists, exsplus_next/1}). -%% Advance xorshift116+ state for one step and generate 58bit unsigned integer +%% Advance state and generate 58bit unsigned integer -spec exsplus_next(exsplus_state()) -> {uint58(), exsplus_state()}. exsplus_next([S1|S0]) -> %% Note: members s0 and s1 are swapped here - S11 = S1 bxor ?BSL(58, S1, 24), - S12 = S11 bxor S0 bxor (S11 bsr 11) bxor (S0 bsr 41), - {?MASK(58, S0 + S12), [S0|S12]}. + NewS1 = ?exs_next(S0, S1, S1_1), + {?MASK(58, S0 + NewS1), [S0|NewS1]}. +%% %% Note: members s0 and s1 are swapped here +%% S11 = S1 bxor ?BSL(58, S1, 24), +%% S12 = S11 bxor S0 bxor (S11 bsr 11) bxor (S0 bsr 41), +%% {?MASK(58, S0 + S12), [S0|S12]}. + +-dialyzer({no_improper_lists, exsss_next/1}). +-spec exsss_next(exsplus_state()) -> {uint58(), exsplus_state()}. +exsss_next([S1|S0]) -> + %% Note: members s0 and s1 are swapped here + NewS1 = ?exs_next(S0, S1, S1_1), + {?scramble_starstar(S0, V_0, V_1), [S0|NewS1]}. +%% {?MASK(58, S0 + NewS1), [S0|NewS1]}. exsp_uniform({Alg, R0}) -> {I, R1} = exsplus_next(R0), @@ -687,18 +795,48 @@ exsp_uniform({Alg, R0}) -> %% randomness quality than the others {(I bsr (58-53)) * ?TWO_POW_MINUS53, {Alg, R1}}. +exsss_uniform({Alg, R0}) -> + {I, R1} = exsss_next(R0), + {(I bsr (58-53)) * ?TWO_POW_MINUS53, {Alg, R1}}. + exsp_uniform(Range, {Alg, R}) -> {V, R1} = exsplus_next(R), MaxMinusRange = ?BIT(58) - Range, ?uniform_range(Range, Alg, R1, V, MaxMinusRange, I). +exsss_uniform(Range, {Alg, R}) -> + {V, R1} = exsss_next(R), + MaxMinusRange = ?BIT(58) - Range, + ?uniform_range(Range, Alg, R1, V, MaxMinusRange, I). -%% This is the jump function for the exsplus generator, equivalent + +%% This is the jump function for the exs* generators, +%% i.e the Xorshift116 generators, equivalent %% to 2^64 calls to next/1; it can be used to generate 2^52 %% non-overlapping subsequences for parallel computations. %% Note: the jump function takes 116 times of the execution time of %% next/1. - +%% +%% #include <stdint.h> +%% +%% void jump(void) { +%% static const uint64_t JUMP[] = { 0x02f8ea6bc32c797, +%% 0x345d2a0f85f788c }; +%% int i, b; +%% uint64_t s0 = 0; +%% uint64_t s1 = 0; +%% for(i = 0; i < sizeof JUMP / sizeof *JUMP; i++) +%% for(b = 0; b < 58; b++) { +%% if (JUMP[i] & 1ULL << b) { +%% s0 ^= s[0]; +%% s1 ^= s[1]; +%% } +%% next(); +%% } +%% s[0] = s0; +%% s[1] = s1; +%% } +%% %% -define(JUMPCONST, 16#000d174a83e17de2302f8ea6bc32c797). %% split into 58-bit chunks %% and two iterative executions @@ -708,7 +846,8 @@ exsp_uniform(Range, {Alg, R}) -> -define(JUMPELEMLEN, 58). -dialyzer({no_improper_lists, exsplus_jump/1}). --spec exsplus_jump(state()) -> state(). +-spec exsplus_jump({alg_handler(), exsplus_state()}) -> + {alg_handler(), exsplus_state()}. exsplus_jump({Alg, S}) -> {S1, AS1} = exsplus_jump(S, [0|0], ?JUMPCONST1, ?JUMPELEMLEN), {_, AS2} = exsplus_jump(S1, AS1, ?JUMPCONST2, ?JUMPELEMLEN), @@ -735,6 +874,12 @@ exsplus_jump(S, [AS0|AS1], J, N) -> -opaque exs1024_state() :: {list(uint64()), list(uint64())}. +exs1024_seed(L) when is_list(L) -> + {seed64_nz(16, L), []}; +exs1024_seed(X) when is_integer(X) -> + {seed64(16, ?MASK(64, X)), []}; +%% +%% Seed from traditional triple, remain backwards compatible exs1024_seed({A1, A2, A3}) -> B1 = ?MASK(21, (?MASK(21, A1) + 1) * 2097131), B2 = ?MASK(21, (?MASK(21, A2) + 1) * 2097133), @@ -806,8 +951,8 @@ exs1024_next({[H], RL}) -> -define(JUMPTOTALLEN, 1024). -define(RINGLEN, 16). --spec exs1024_jump(state()) -> state(). - +-spec exs1024_jump({alg_handler(), exs1024_state()}) -> + {alg_handler(), exs1024_state()}. exs1024_jump({Alg, {L, RL}}) -> P = length(RL), AS = exs1024_jump({L, RL}, @@ -832,6 +977,195 @@ exs1024_jump({L, RL}, AS, JL, J, N, TN) -> end. %% ===================================================================== +%% exro928ss PRNG: Xoroshiro928** +%% +%% Reference URL: http://vigna.di.unimi.it/ftp/papers/ScrambledLinear.pdf +%% i.e the Xoroshiro1024 generator with ** scrambler +%% with {S, R, T} = {5, 7, 9} as recommended in the paper. +%% +%% {A, B, C} were tried out and selected as {44, 9, 45} +%% and the jump coefficients calculated. +%% +%% Standard jump function pseudocode: +%% +%% Jump constant j = 0xb10773cb...44085302f77130ca +%% Generator state: s +%% New generator state: t = 0 +%% foreach bit in j, low to high: +%% if the bit is one: +%% t ^= s +%% next s +%% s = t +%% +%% Generator used for reference value calculation: +%% +%% #include <stdint.h> +%% #include <stdio.h> +%% +%% int p = 0; +%% uint64_t s[16]; +%% +%% #define MASK(x) ((x) & ((UINT64_C(1) << 58) - 1)) +%% static __inline uint64_t rotl(uint64_t x, int n) { +%% return MASK(x << n) | (x >> (58 - n)); +%% } +%% +%% uint64_t next() { +%% const int q = p; +%% const uint64_t s0 = s[p = (p + 1) & 15]; +%% uint64_t s15 = s[q]; +%% +%% const uint64_t result_starstar = MASK(rotl(MASK(s0 * 5), 7) * 9); +%% +%% s15 ^= s0; +%% s[q] = rotl(s0, 44) ^ s15 ^ MASK(s15 << 9); +%% s[p] = rotl(s15, 45); +%% +%% return result_starstar; +%% } +%% +%% static const uint64_t jump_2pow512[15] = +%% { 0x44085302f77130ca, 0xba05381fdfd14902, 0x10a1de1d7d6813d2, +%% 0xb83fe51a1eb3be19, 0xa81b0090567fd9f0, 0x5ac26d5d20f9b49f, +%% 0x4ddd98ee4be41e01, 0x0657e19f00d4b358, 0xf02f778573cf0f0a, +%% 0xb45a3a8a3cef3cc0, 0x6e62a33cc2323831, 0xbcb3b7c4cc049c53, +%% 0x83f240c6007e76ce, 0xe19f5fc1a1504acd, 0x00000000b10773cb }; +%% +%% static const uint64_t jump_2pow20[15] = +%% { 0xbdb966a3daf905e6, 0x644807a56270cf78, 0xda90f4a806c17e9e, +%% 0x4a426866bfad3c77, 0xaf699c306d8e7566, 0x8ebc73c700b8b091, +%% 0xc081a7bf148531fb, 0xdc4d3af15f8a4dfd, 0x90627c014098f4b6, +%% 0x06df2eb1feaf0fb6, 0x5bdeb1a5a90f2e6b, 0xa480c5878c3549bd, +%% 0xff45ef33c82f3d48, 0xa30bebc15fefcc78, 0x00000000cb3d181c }; +%% +%% void jump(const uint64_t *jump) { +%% uint64_t j, t[16] = {0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0}; +%% int m, n, k; +%% for (m = 0; m < 15; m++, jump++) { +%% for (n = 0, j = *jump; n < 64; n++, j >>= 1) { +%% if ((j & 1) != 0) { +%% for (k = 0; k < 16; k++) { +%% t[k] ^= s[(p + k) & 15]; +%% } +%% } +%% next(); +%% } +%% } +%% for (k = 0; k < 16; k++) { +%% s[(p + k) & 15] = t[k]; +%% } +%% } +%% +%% ===================================================================== + +-opaque exro928_state() :: {list(uint58()), list(uint58())}. + +-spec exro928_seed( + list(uint58()) | integer() | {integer(), integer(), integer()}) -> + exro928_state(). +exro928_seed(L) when is_list(L) -> + {seed58_nz(16, L), []}; +exro928_seed(X) when is_integer(X) -> + {seed58(16, ?MASK(64, X)), []}; +%% +%% Seed from traditional integer triple - mix into splitmix +exro928_seed({A1, A2, A3}) -> + {S0, X0} = seed58(?MASK(64, A1)), + {S1, X1} = seed58(?MASK(64, A2) bxor X0), + {S2, X2} = seed58(?MASK(64, A3) bxor X1), + {[S0,S1,S2|seed58(13, X2)], []}. + + +%% Update the state and calculate output word +-spec exro928ss_next(exro928_state()) -> {uint58(), exro928_state()}. +exro928ss_next({[S15,S0|Ss], Rs}) -> + SR = exro928_next_state(Ss, Rs, S15, S0), + %% + %% {S, R, T} = {5, 7, 9} + %% const uint64_t result_starstar = rotl(s0 * S, R) * T; + %% + {?scramble_starstar(S0, V_0, V_1), SR}; +%% %% The multiply by add shifted trick avoids creating bignums +%% %% which improves performance significantly +%% %% +%% V0 = ?MASK(58, S0 + ?BSL(58, S0, 2)), % V0 = S0 * 5 +%% V1 = ?ROTL(58, V0, 7), +%% V = ?MASK(58, V1 + ?BSL(58, V1, 3)), % V = V1 * 9 +%% {V, SR}; +exro928ss_next({[S15], Rs}) -> + exro928ss_next({[S15|lists:reverse(Rs)], []}). + +-spec exro928_next(exro928_state()) -> {{uint58(),uint58()}, exro928_state()}. +exro928_next({[S15,S0|Ss], Rs}) -> + SR = exro928_next_state(Ss, Rs, S15, S0), + {{S15,S0}, SR}; +exro928_next({[S15], Rs}) -> + exro928_next({[S15|lists:reverse(Rs)], []}). + +%% Just update the state +-spec exro928_next_state(exro928_state()) -> exro928_state(). +exro928_next_state({[S15,S0|Ss], Rs}) -> + exro928_next_state(Ss, Rs, S15, S0); +exro928_next_state({[S15], Rs}) -> + [S0|Ss] = lists:reverse(Rs), + exro928_next_state(Ss, [], S15, S0). + +exro928_next_state(Ss, Rs, S15, S0) -> + %% {A, B, C} = {44, 9, 45}, + %% s15 ^= s0; + %% NewS15: s[q] = rotl(s0, A) ^ s15 ^ (s15 << B); + %% NewS0: s[p] = rotl(s15, C); + %% + Q = S15 bxor S0, + NewS15 = ?ROTL(58, S0, 44) bxor Q bxor ?BSL(58, Q, 9), + NewS0 = ?ROTL(58, Q, 45), + {[NewS0|Ss], [NewS15|Rs]}. + + +exro928ss_uniform({Alg, SR}) -> + {V, NewSR} = exro928ss_next(SR), + {(V bsr (58-53)) * ?TWO_POW_MINUS53, {Alg, NewSR}}. + +exro928ss_uniform(Range, {Alg, SR}) -> + {V, NewSR} = exro928ss_next(SR), + MaxMinusRange = ?BIT(58) - Range, + ?uniform_range(Range, Alg, NewSR, V, MaxMinusRange, I). + + +-spec exro928_jump({alg_handler(), exro928_state()}) -> + {alg_handler(), exro928_state()}. +exro928_jump({Alg, SR}) -> + {Alg,exro928_jump_2pow512(SR)}. + +-spec exro928_jump_2pow512(exro928_state()) -> exro928_state(). +exro928_jump_2pow512(SR) -> + polyjump( + SR, fun exro928_next_state/1, + %% 2^512 + [16#4085302F77130CA, 16#54E07F7F4524091, + 16#5E1D7D6813D2BA0, 16#4687ACEF8644287, + 16#4567FD9F0B83FE5, 16#43E6D27EA06C024, + 16#641E015AC26D5D2, 16#6CD61377663B92F, + 16#70A0657E19F00D4, 16#43C0BDDE15CF3C3, + 16#745A3A8A3CEF3CC, 16#58A8CF308C8E0C6, + 16#7B7C4CC049C536E, 16#431801F9DB3AF2C, + 16#41A1504ACD83F24, 16#6C41DCF2F867D7F]). + +-spec exro928_jump_2pow20(exro928_state()) -> exro928_state(). +exro928_jump_2pow20(SR) -> + polyjump( + SR, fun exro928_next_state/1, + %% 2^20 + [16#5B966A3DAF905E6, 16#601E9589C33DE2F, + 16#74A806C17E9E644, 16#59AFEB4F1DF6A43, + 16#46D8E75664A4268, 16#42E2C246BDA670C, + 16#4531FB8EBC73C70, 16#537F702069EFC52, + 16#4B6DC4D3AF15F8A, 16#5A4189F0050263D, + 16#46DF2EB1FEAF0FB, 16#77AC696A43CB9AC, + 16#4C5878C3549BD5B, 16#7CCF20BCF522920, + 16#415FEFCC78FF45E, 16#72CF460728C2FAF]). + +%% ===================================================================== %% exrop PRNG: Xoroshiro116+ %% %% Reference URL: http://xorshift.di.unimi.it/ @@ -899,6 +1233,15 @@ exs1024_jump({L, RL}, AS, JL, J, N, TN) -> -opaque exrop_state() :: nonempty_improper_list(uint58(), uint58()). -dialyzer({no_improper_lists, exrop_seed/1}). + +exrop_seed(L) when is_list(L) -> + [S0,S1] = seed58_nz(2, L), + [S0|S1]; +exrop_seed(X) when is_integer(X) -> + [S0,S1] = seed58(2, ?MASK(64, X)), + [S0|S1]; +%% +%% Traditional integer triplet seed exrop_seed({A1, A2, A3}) -> [_|S1] = exrop_next_s( @@ -962,6 +1305,142 @@ exrop_jump([S__0|S__1] = _S, S0, S1, J, Js) -> end. %% ===================================================================== +%% Mask and fill state list, ensure not all zeros +%% ===================================================================== + +seed58_nz(N, Ss) -> + seed_nz(N, Ss, 58, false). + +seed64_nz(N, Ss) -> + seed_nz(N, Ss, 64, false). + +seed_nz(_N, [], _M, false) -> + erlang:error(zero_seed); +seed_nz(0, [_|_], _M, _NZ) -> + erlang:error(too_many_seed_integers); +seed_nz(0, [], _M, _NZ) -> + []; +seed_nz(N, [], M, true) -> + [0|seed_nz(N - 1, [], M, true)]; +seed_nz(N, [S|Ss], M, NZ) -> + if + is_integer(S) -> + R = ?MASK(M, S), + [R|seed_nz(N - 1, Ss, M, NZ orelse R =/= 0)]; + true -> + erlang:error(non_integer_seed) + end. + +%% ===================================================================== +%% Splitmix seeders, lowest bits of SplitMix64, zeros skipped +%% ===================================================================== + +-spec seed58(non_neg_integer(), uint64()) -> list(uint58()). +seed58(0, _X) -> + []; +seed58(N, X) -> + {Z,NewX} = seed58(X), + [Z|seed58(N - 1, NewX)]. +%% +seed58(X_0) -> + {Z0,X} = splitmix64_next(X_0), + case ?MASK(58, Z0) of + 0 -> + seed58(X); + Z -> + {Z,X} + end. + +-spec seed64(non_neg_integer(), uint64()) -> list(uint64()). +seed64(0, _X) -> + []; +seed64(N, X) -> + {Z,NewX} = seed64(X), + [Z|seed64(N - 1, NewX)]. +%% +seed64(X_0) -> + {Z,X} = ZX = splitmix64_next(X_0), + if + Z =:= 0 -> + seed64(X); + true -> + ZX + end. + +%% The SplitMix64 generator: +%% +%% uint64_t splitmix64_next() { +%% uint64_t z = (x += 0x9e3779b97f4a7c15); +%% z = (z ^ (z >> 30)) * 0xbf58476d1ce4e5b9; +%% z = (z ^ (z >> 27)) * 0x94d049bb133111eb; +%% return z ^ (z >> 31); +%% } +%% +splitmix64_next(X_0) -> + X = ?MASK(64, X_0 + 16#9e3779b97f4a7c15), + Z_0 = ?MASK(64, (X bxor (X bsr 30)) * 16#bf58476d1ce4e5b9), + Z_1 = ?MASK(64, (Z_0 bxor (Z_0 bsr 27)) * 16#94d049bb133111eb), + {?MASK(64, Z_1 bxor (Z_1 bsr 31)),X}. + +%% ===================================================================== +%% Polynomial jump with a jump constant word list, +%% high bit in each word marking top of word, +%% SR is a {Forward, Reverse} queue tuple with Forward never empty +%% ===================================================================== + +polyjump({Ss, Rs} = SR, NextState, JumpConst) -> + %% Create new state accumulator T + Ts = lists:duplicate(length(Ss) + length(Rs), 0), + polyjump(SR, NextState, JumpConst, Ts). +%% +%% Foreach jump word +polyjump(_SR, _NextState, [], Ts) -> + %% Return new calculated state + {Ts, []}; +polyjump(SR, NextState, [J|Js], Ts) -> + polyjump(SR, NextState, Js, Ts, J). +%% +%% Foreach bit in jump word until top bit +polyjump(SR, NextState, Js, Ts, 1) -> + polyjump(SR, NextState, Js, Ts); +polyjump({Ss, Rs} = SR, NextState, Js, Ts, J) when J =/= 0 -> + NewSR = NextState(SR), + NewJ = J bsr 1, + case ?MASK(1, J) of + 0 -> + polyjump(NewSR, NextState, Js, Ts, NewJ); + 1 -> + %% Xor this state onto T + polyjump(NewSR, NextState, Js, xorzip_sr(Ts, Ss, Rs), NewJ) + end. + +xorzip_sr([], [], undefined) -> + []; +xorzip_sr(Ts, [], Rs) -> + xorzip_sr(Ts, lists:reverse(Rs), undefined); +xorzip_sr([T|Ts], [S|Ss], Rs) -> + [T bxor S|xorzip_sr(Ts, Ss, Rs)]. + +%% ===================================================================== + +format_jumpconst58(String) -> + ReOpts = [{newline,any},{capture,all_but_first,binary},global], + {match,Matches} = re:run(String, "0x([a-zA-Z0-9]+)", ReOpts), + format_jumcons58_matches(lists:reverse(Matches), 0). + +format_jumcons58_matches([], J) -> + format_jumpconst58_value(J); +format_jumcons58_matches([[Bin]|Matches], J) -> + NewJ = (J bsl 64) bor binary_to_integer(Bin, 16), + format_jumcons58_matches(Matches, NewJ). + +format_jumpconst58_value(0) -> + ok; +format_jumpconst58_value(J) -> + io:format("16#~s,~n", [integer_to_list(?MASK(58, J) bor ?BIT(58), 16)]), + format_jumpconst58_value(J bsr 58). + +%% ===================================================================== %% Ziggurat cont %% ===================================================================== -define(NOR_R, 3.6541528853610087963519472518). diff --git a/lib/stdlib/src/stdlib.app.src b/lib/stdlib/src/stdlib.app.src index cd09872b87..9cd425db9a 100644 --- a/lib/stdlib/src/stdlib.app.src +++ b/lib/stdlib/src/stdlib.app.src @@ -108,7 +108,7 @@ dets]}, {applications, [kernel]}, {env, []}, - {runtime_dependencies, ["sasl-3.0","kernel-6.0","erts-10.0","crypto-3.3", + {runtime_dependencies, ["sasl-3.0","kernel-6.0","erts-@OTP-15128@","crypto-3.3", "compiler-5.0"]} ]}. 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); |