aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r--lib/stdlib/src/dets.erl2
-rw-r--r--lib/stdlib/src/erl_expand_records.erl95
-rw-r--r--lib/stdlib/src/erl_internal.erl118
-rw-r--r--lib/stdlib/src/erl_lint.erl165
-rw-r--r--lib/stdlib/src/erl_parse.yrl13
-rw-r--r--lib/stdlib/src/eval_bits.erl14
-rw-r--r--lib/stdlib/src/math.erl19
-rw-r--r--lib/stdlib/src/otp_internal.erl2
-rw-r--r--lib/stdlib/src/proc_lib.erl19
-rw-r--r--lib/stdlib/src/qlc_pt.erl55
-rw-r--r--lib/stdlib/src/rand.erl140
-rw-r--r--lib/stdlib/src/sets.erl66
-rw-r--r--lib/stdlib/src/stdlib.app.src2
-rw-r--r--lib/stdlib/src/stdlib.appup.src6
-rw-r--r--lib/stdlib/src/timer.erl6
15 files changed, 507 insertions, 215 deletions
diff --git a/lib/stdlib/src/dets.erl b/lib/stdlib/src/dets.erl
index bf22949870..8ce29f23d3 100644
--- a/lib/stdlib/src/dets.erl
+++ b/lib/stdlib/src/dets.erl
@@ -3305,7 +3305,7 @@ time_now() ->
make_timestamp(MonTime, TimeOffset) ->
ErlangSystemTime = erlang:convert_time_unit(MonTime+TimeOffset,
native,
- micro_seconds),
+ microsecond),
MegaSecs = ErlangSystemTime div 1000000000000,
Secs = ErlangSystemTime div 1000000 - MegaSecs*1000000,
MicroSecs = ErlangSystemTime rem 1000000,
diff --git a/lib/stdlib/src/erl_expand_records.erl b/lib/stdlib/src/erl_expand_records.erl
index ebcbc54ab1..2280464bff 100644
--- a/lib/stdlib/src/erl_expand_records.erl
+++ b/lib/stdlib/src/erl_expand_records.erl
@@ -17,7 +17,8 @@
%%
%% %CopyrightEnd%
%%
-%% Purpose : Expand records into tuples.
+%% Purpose: Expand records into tuples. Also add explicit module
+%% names to calls to imported functions and BIFs.
%% N.B. Although structs (tagged tuples) are not yet allowed in the
%% language there is code included in pattern/2 and expr/3 (commented out)
@@ -31,7 +32,7 @@
-record(exprec, {compile=[], % Compile flags
vcount=0, % Variable counter
- imports=[], % Imports
+ calltype=#{}, % Call types
records=dict:new(), % Record definitions
strict_ra=[], % strict record accesses
checked_ra=[] % successfully accessed records
@@ -46,22 +47,34 @@
%% erl_lint without errors.
module(Fs0, Opts0) ->
Opts = compiler_options(Fs0) ++ Opts0,
- St0 = #exprec{compile = Opts},
+ Calltype = init_calltype(Fs0),
+ St0 = #exprec{compile = Opts, calltype = Calltype},
{Fs,_St} = forms(Fs0, St0),
Fs.
compiler_options(Forms) ->
lists:flatten([C || {attribute,_,compile,C} <- Forms]).
+init_calltype(Forms) ->
+ Locals = [{{Name,Arity},local} || {function,_,Name,Arity,_} <- Forms],
+ Ctype = maps:from_list(Locals),
+ init_calltype_imports(Forms, Ctype).
+
+init_calltype_imports([{attribute,_,import,{Mod,Fs}}|T], Ctype0) ->
+ true = is_atom(Mod),
+ Ctype = foldl(fun(FA, Acc) ->
+ Acc#{FA=>{imported,Mod}}
+ end, Ctype0, Fs),
+ init_calltype_imports(T, Ctype);
+init_calltype_imports([_|T], Ctype) ->
+ init_calltype_imports(T, Ctype);
+init_calltype_imports([], Ctype) -> Ctype.
+
forms([{attribute,_,record,{Name,Defs}}=Attr | Fs], St0) ->
NDefs = normalise_fields(Defs),
St = St0#exprec{records=dict:store(Name, NDefs, St0#exprec.records)},
{Fs1, St1} = forms(Fs, St),
{[Attr | Fs1], St1};
-forms([{attribute,L,import,Is} | Fs0], St0) ->
- St1 = import(Is, St0),
- {Fs,St2} = forms(Fs0, St1),
- {[{attribute,L,import,Is} | Fs], St2};
forms([{function,L,N,A,Cs0} | Fs0], St0) ->
{Cs,St1} = clauses(Cs0, St0),
{Fs,St2} = forms(Fs0, St1),
@@ -334,8 +347,16 @@ expr({'receive',Line,Cs0,To0,ToEs0}, St0) ->
{ToEs,St2} = exprs(ToEs0, St1),
{Cs,St3} = clauses(Cs0, St2),
{{'receive',Line,Cs,To,ToEs},St3};
-expr({'fun',_,{function,_F,_A}}=Fun, St) ->
- {Fun,St};
+expr({'fun',Lf,{function,F,A}}=Fun0, St0) ->
+ case erl_internal:bif(F, A) of
+ true ->
+ {As,St1} = new_vars(A, Lf, St0),
+ Cs = [{clause,Lf,As,[],[{call,Lf,{atom,Lf,F},As}]}],
+ Fun = {'fun',Lf,{clauses,Cs}},
+ expr(Fun, St1);
+ false ->
+ {Fun0,St0}
+ end;
expr({'fun',_,{function,_M,_F,_A}}=Fun, St) ->
{Fun,St};
expr({'fun',Line,{clauses,Cs0}}, St0) ->
@@ -352,14 +373,30 @@ expr({call,Line,{remote,_,{atom,_,erlang},{atom,_,is_record}},
expr({call,Line,{tuple,_,[{atom,_,erlang},{atom,_,is_record}]},
[A,{atom,_,Name}]}, St) ->
record_test(Line, A, Name, St);
+expr({call,Line,{atom,_La,record_info},[_,_]=As0}, St0) ->
+ {As,St1} = expr_list(As0, St0),
+ record_info_call(Line, As, St1);
expr({call,Line,{atom,_La,N}=Atom,As0}, St0) ->
{As,St1} = expr_list(As0, St0),
Ar = length(As),
- case {N,Ar} =:= {record_info,2} andalso not imported(N, Ar, St1) of
- true ->
- record_info_call(Line, As, St1);
- false ->
- {{call,Line,Atom,As},St1}
+ NA = {N,Ar},
+ case St0#exprec.calltype of
+ #{NA := local} ->
+ {{call,Line,Atom,As},St1};
+ #{NA := {imported,Module}} ->
+ ModAtom = {atom,Line,Module},
+ {{call,Line,{remote,Line,ModAtom,Atom},As},St1};
+ _ ->
+ case erl_internal:bif(N, Ar) of
+ true ->
+ ModAtom = {atom,Line,erlang},
+ {{call,Line,{remote,Line,ModAtom,Atom},As},St1};
+ false ->
+ %% Call to a module_info/0,1 or one of the
+ %% pseudo-functions in the shell. Leave it as
+ %% a local call.
+ {{call,Line,Atom,As},St1}
+ end
end;
expr({call,Line,{remote,Lr,M,F},As0}, St0) ->
{[M1,F1 | As1],St1} = expr_list([M,F | As0], St0),
@@ -470,9 +507,16 @@ lc_tq(Line, [{b_generate,Lg,P0,G0} | Qs0], St0) ->
{P1,St2} = pattern(P0, St1),
{Qs1,St3} = lc_tq(Line, Qs0, St2),
{[{b_generate,Lg,P1,G1} | Qs1],St3};
-lc_tq(Line, [F0 | Qs0], St0) ->
+lc_tq(Line, [F0 | Qs0], #exprec{calltype=Calltype}=St0) ->
%% Allow record/2 and expand out as guard test.
- case erl_lint:is_guard_test(F0) of
+ IsOverriden = fun(FA) ->
+ case Calltype of
+ #{FA := local} -> true;
+ #{FA := {imported,_}} -> true;
+ _ -> false
+ end
+ end,
+ case erl_lint:is_guard_test(F0, [], IsOverriden) of
true ->
{F1,St1} = guard_test(F0, St0),
{Qs1,St2} = lc_tq(Line, Qs0, St1),
@@ -769,6 +813,13 @@ bin_element({bin_element,Line,Expr,Size,Type}, {Es,St0}) ->
end,
{[{bin_element,Line,Expr1,Size1,Type} | Es],St2}.
+new_vars(N, L, St) -> new_vars(N, L, St, []).
+
+new_vars(N, L, St0, Vs) when N > 0 ->
+ {V,St1} = new_var(L, St0),
+ new_vars(N-1, L, St1, [V|Vs]);
+new_vars(0, _L, St, Vs) -> {Vs,St}.
+
new_var(L, St0) ->
{New,St1} = new_var_name(St0),
{{var,L,New},St1}.
@@ -783,18 +834,6 @@ make_list(Ts, Line) ->
call_error(L, R) ->
{call,L,{remote,L,{atom,L,erlang},{atom,L,error}},[R]}.
-import({Mod,Fs}, St) ->
- St#exprec{imports=add_imports(Mod, Fs, St#exprec.imports)};
-import(_Mod0, St) ->
- St.
-
-add_imports(Mod, [F | Fs], Is) ->
- add_imports(Mod, Fs, orddict:store(F, Mod, Is));
-add_imports(_, [], Is) -> Is.
-
-imported(F, A, St) ->
- orddict:is_key({F,A}, St#exprec.imports).
-
%%%
%%% Replace is_record/3 in guards with matching if possible.
%%%
diff --git a/lib/stdlib/src/erl_internal.erl b/lib/stdlib/src/erl_internal.erl
index c08328b4b7..006e7946af 100644
--- a/lib/stdlib/src/erl_internal.erl
+++ b/lib/stdlib/src/erl_internal.erl
@@ -54,6 +54,8 @@
-export([is_type/2]).
+-export([add_predefined_functions/1]).
+
%%---------------------------------------------------------------------------
%% Erlang builtin functions allowed in guards.
@@ -61,42 +63,28 @@
Name :: atom(),
Arity :: arity().
+%% Please keep the alphabetical order.
guard_bif(abs, 1) -> true;
-guard_bif(float, 1) -> true;
-guard_bif(trunc, 1) -> true;
-guard_bif(round, 1) -> true;
-guard_bif(length, 1) -> true;
-guard_bif(hd, 1) -> true;
-guard_bif(tl, 1) -> true;
-guard_bif(size, 1) -> true;
+guard_bif(binary_part, 2) -> true;
+guard_bif(binary_part, 3) -> true;
guard_bif(bit_size, 1) -> true;
guard_bif(byte_size, 1) -> true;
+guard_bif(ceil, 1) -> true;
guard_bif(element, 2) -> true;
-guard_bif(self, 0) -> true;
+guard_bif(float, 1) -> true;
+guard_bif(floor, 1) -> true;
+guard_bif(hd, 1) -> true;
+guard_bif(length, 1) -> true;
guard_bif(map_size, 1) -> true;
guard_bif(node, 0) -> true;
guard_bif(node, 1) -> true;
+guard_bif(round, 1) -> true;
+guard_bif(self, 0) -> true;
+guard_bif(size, 1) -> true;
+guard_bif(tl, 1) -> true;
+guard_bif(trunc, 1) -> true;
guard_bif(tuple_size, 1) -> true;
-guard_bif(is_atom, 1) -> true;
-guard_bif(is_binary, 1) -> true;
-guard_bif(is_bitstring, 1) -> true;
-guard_bif(is_boolean, 1) -> true;
-guard_bif(is_float, 1) -> true;
-guard_bif(is_function, 1) -> true;
-guard_bif(is_function, 2) -> true;
-guard_bif(is_integer, 1) -> true;
-guard_bif(is_list, 1) -> true;
-guard_bif(is_map, 1) -> true;
-guard_bif(is_number, 1) -> true;
-guard_bif(is_pid, 1) -> true;
-guard_bif(is_port, 1) -> true;
-guard_bif(is_reference, 1) -> true;
-guard_bif(is_tuple, 1) -> true;
-guard_bif(is_record, 2) -> true;
-guard_bif(is_record, 3) -> true;
-guard_bif(binary_part, 2) -> true;
-guard_bif(binary_part, 3) -> true;
-guard_bif(Name, A) when is_atom(Name), is_integer(A) -> false.
+guard_bif(Name, A) -> new_type_test(Name, A).
%% Erlang type tests.
-spec type_test(Name, Arity) -> boolean() when
@@ -109,10 +97,11 @@ type_test(Name, Arity) ->
%% Erlang new-style type tests.
-spec new_type_test(Name::atom(), Arity::arity()) -> boolean().
+%% Please keep the alphabetical order.
new_type_test(is_atom, 1) -> true;
-new_type_test(is_boolean, 1) -> true;
new_type_test(is_binary, 1) -> true;
new_type_test(is_bitstring, 1) -> true;
+new_type_test(is_boolean, 1) -> true;
new_type_test(is_float, 1) -> true;
new_type_test(is_function, 1) -> true;
new_type_test(is_function, 2) -> true;
@@ -122,10 +111,10 @@ new_type_test(is_map, 1) -> true;
new_type_test(is_number, 1) -> true;
new_type_test(is_pid, 1) -> true;
new_type_test(is_port, 1) -> true;
-new_type_test(is_reference, 1) -> true;
-new_type_test(is_tuple, 1) -> true;
new_type_test(is_record, 2) -> true;
new_type_test(is_record, 3) -> true;
+new_type_test(is_reference, 1) -> true;
+new_type_test(is_tuple, 1) -> true;
new_type_test(Name, A) when is_atom(Name), is_integer(A) -> false.
%% Erlang old-style type tests.
@@ -271,6 +260,7 @@ bif(bitsize, 1) -> true;
bif(bit_size, 1) -> true;
bif(bitstring_to_list, 1) -> true;
bif(byte_size, 1) -> true;
+bif(ceil, 1) -> true;
bif(check_old_code, 1) -> true;
bif(check_process_code, 2) -> true;
bif(check_process_code, 3) -> true;
@@ -291,6 +281,7 @@ bif(float_to_list, 1) -> true;
bif(float_to_list, 2) -> true;
bif(float_to_binary, 1) -> true;
bif(float_to_binary, 2) -> true;
+bif(floor, 1) -> true;
bif(garbage_collect, 0) -> true;
bif(garbage_collect, 1) -> true;
bif(garbage_collect, 2) -> true;
@@ -584,3 +575,68 @@ is_type(term, 0) -> true;
is_type(timeout, 0) -> true;
is_type(tuple, 0) -> true;
is_type(_, _) -> false.
+
+%%%
+%%% Add and export the pre-defined functions:
+%%%
+%%% module_info/0
+%%% module_info/1
+%%% behaviour_info/1 (optional)
+%%%
+
+-spec add_predefined_functions(Forms) -> UpdatedForms when
+ Forms :: [erl_parse:abstract_form() | erl_parse:form_info()],
+ UpdatedForms :: [erl_parse:abstract_form() | erl_parse:form_info()].
+
+add_predefined_functions(Forms) ->
+ Forms ++ predefined_functions(Forms).
+
+predefined_functions(Forms) ->
+ Attrs = [{Name,Val} || {attribute,_,Name,Val} <- Forms],
+ {module,Mod} = lists:keyfind(module, 1, Attrs),
+ Callbacks = [Callback || {callback,Callback} <- Attrs],
+ OptionalCallbacks = get_optional_callbacks(Attrs),
+ Mpf1 = module_predef_func_beh_info(Callbacks, OptionalCallbacks),
+ Mpf2 = module_predef_funcs_mod_info(Mod),
+ Mpf = [erl_parse:new_anno(F) || F <- Mpf1++Mpf2],
+ Exp = [{F,A} || {function,_,F,A,_} <- Mpf],
+ [{attribute,0,export,Exp}|Mpf].
+
+get_optional_callbacks(Attrs) ->
+ L = [O || {optional_callbacks,O} <- Attrs, is_fa_list(O)],
+ lists:append(L).
+
+is_fa_list([{FuncName, Arity}|L])
+ when is_atom(FuncName), is_integer(Arity), Arity >= 0 ->
+ is_fa_list(L);
+is_fa_list([]) -> true;
+is_fa_list(_) -> false.
+
+module_predef_func_beh_info([], _) ->
+ [];
+module_predef_func_beh_info(Callbacks0, OptionalCallbacks) ->
+ Callbacks = [FA || {{_,_}=FA,_} <- Callbacks0],
+ List = make_list(Callbacks),
+ OptionalList = make_list(OptionalCallbacks),
+ [{function,0,behaviour_info,1,
+ [{clause,0,[{atom,0,callbacks}],[],[List]},
+ {clause,0,[{atom,0,optional_callbacks}],[],[OptionalList]}]}].
+
+make_list([]) -> {nil,0};
+make_list([{Name,Arity}|Rest]) ->
+ {cons,0,
+ {tuple,0,
+ [{atom,0,Name},
+ {integer,0,Arity}]},
+ make_list(Rest)}.
+
+module_predef_funcs_mod_info(Mod) ->
+ ModAtom = {atom,0,Mod},
+ [{function,0,module_info,0,
+ [{clause,0,[],[],
+ [{call,0,{remote,0,{atom,0,erlang},{atom,0,get_module_info}},
+ [ModAtom]}]}]},
+ {function,0,module_info,1,
+ [{clause,0,[{var,0,'X'}],[],
+ [{call,0,{remote,0,{atom,0,erlang},{atom,0,get_module_info}},
+ [ModAtom,{var,0,'X'}]}]}]}].
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index e9332ce069..49b65069b7 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -27,7 +27,7 @@
-export([module/1,module/2,module/3,format_error/1]).
-export([exprs/2,exprs_opt/3,used_vars/2]). % Used from erl_eval.erl.
--export([is_pattern_expr/1,is_guard_test/1,is_guard_test/2]).
+-export([is_pattern_expr/1,is_guard_test/1,is_guard_test/2,is_guard_test/3]).
-export([is_guard_expr/1]).
-export([bool_option/4,value_option/3,value_option/7]).
@@ -238,7 +238,11 @@ format_error({removed_type, MNA, ReplacementMNA, Rel}) ->
io_lib:format("the type ~s was removed in ~s; use ~s instead",
[format_mna(MNA), Rel, format_mna(ReplacementMNA)]);
format_error({obsolete_guard, {F, A}}) ->
- io_lib:format("~p/~p obsolete", [F, A]);
+ io_lib:format("~p/~p obsolete (use is_~p/~p)", [F, A, F, A]);
+format_error({obsolete_guard_overridden,Test}) ->
+ io_lib:format("obsolete ~s/1 (meaning is_~s/1) is illegal when "
+ "there is a local/imported function named is_~p/1 ",
+ [Test,Test,Test]);
format_error({too_many_arguments,Arity}) ->
io_lib:format("too many arguments (~w) - "
"maximum allowed is ~w", [Arity,?MAX_ARGUMENTS]);
@@ -1765,7 +1769,8 @@ bit_size({atom,_Line,all}, _Vt, St, _Check) -> {all,[],St};
bit_size(Size, Vt, St, Check) ->
%% Try to safely evaluate Size if constant to get size,
%% otherwise just treat it as an expression.
- case is_gexpr(Size, St#lint.records) of
+ Info = is_guard_test2_info(St),
+ case is_gexpr(Size, Info) of
true ->
case erl_eval:partial_eval(Size) of
{integer,_ILn,I} -> {I,[],St};
@@ -2000,77 +2005,104 @@ gexpr_list(Es, Vt, St) ->
%% is_guard_test(Expression) -> boolean().
%% Test if a general expression is a guard test.
+%%
+%% Note: Only use this function in contexts where there can be
+%% no definition of a local function that may override a guard BIF
+%% (for example, in the shell).
-spec is_guard_test(Expr) -> boolean() when
Expr :: erl_parse:abstract_expr().
is_guard_test(E) ->
- is_guard_test2(E, dict:new()).
+ is_guard_test2(E, {dict:new(),fun(_) -> false end}).
%% is_guard_test(Expression, Forms) -> boolean().
is_guard_test(Expression, Forms) ->
+ is_guard_test(Expression, Forms, fun(_) -> false end).
+
+
+%% is_guard_test(Expression, Forms, IsOverridden) -> boolean().
+%% Test if a general expression is a guard test.
+%%
+%% IsOverridden({Name,Arity}) should return 'true' if Name/Arity is
+%% a local or imported function in the module. If the abstract code has
+%% passed through erl_expand_records, any call without an explicit
+%% module is to a local function, so IsOverridden can be defined as:
+%%
+%% fun(_) -> true end
+%%
+-spec is_guard_test(Expr, Forms, IsOverridden) -> boolean() when
+ Expr :: erl_parse:abstract_expr(),
+ Forms :: [erl_parse:abstract_form() | erl_parse:form_info()],
+ IsOverridden :: fun((fa()) -> boolean()).
+
+is_guard_test(Expression, Forms, IsOverridden) ->
RecordAttributes = [A || A = {attribute, _, record, _D} <- Forms],
St0 = foldl(fun(Attr0, St1) ->
Attr = set_file(Attr0, "none"),
attribute_state(Attr, St1)
end, start(), RecordAttributes),
- is_guard_test2(set_file(Expression, "nofile"), St0#lint.records).
+ is_guard_test2(set_file(Expression, "nofile"),
+ {St0#lint.records,IsOverridden}).
%% is_guard_test2(Expression, RecordDefs :: dict:dict()) -> boolean().
-is_guard_test2({call,Line,{atom,Lr,record},[E,A]}, RDs) ->
- is_gexpr({call,Line,{atom,Lr,is_record},[E,A]}, RDs);
-is_guard_test2({call,_Line,{atom,_La,Test},As}=Call, RDs) ->
- case erl_internal:type_test(Test, length(As)) of
- true -> is_gexpr_list(As, RDs);
- false -> is_gexpr(Call, RDs)
- end;
-is_guard_test2(G, RDs) ->
+is_guard_test2({call,Line,{atom,Lr,record},[E,A]}, Info) ->
+ is_gexpr({call,Line,{atom,Lr,is_record},[E,A]}, Info);
+is_guard_test2({call,_Line,{atom,_La,Test},As}=Call, {_,IsOverridden}=Info) ->
+ A = length(As),
+ not IsOverridden({Test,A}) andalso
+ case erl_internal:type_test(Test, A) of
+ true -> is_gexpr_list(As, Info);
+ false -> is_gexpr(Call, Info)
+ end;
+is_guard_test2(G, Info) ->
%%Everything else is a guard expression.
- is_gexpr(G, RDs).
+ is_gexpr(G, Info).
%% is_guard_expr(Expression) -> boolean().
%% Test if an expression is a guard expression.
is_guard_expr(E) -> is_gexpr(E, []).
-is_gexpr({var,_L,_V}, _RDs) -> true;
-is_gexpr({char,_L,_C}, _RDs) -> true;
-is_gexpr({integer,_L,_I}, _RDs) -> true;
-is_gexpr({float,_L,_F}, _RDs) -> true;
-is_gexpr({atom,_L,_A}, _RDs) -> true;
-is_gexpr({string,_L,_S}, _RDs) -> true;
-is_gexpr({nil,_L}, _RDs) -> true;
-is_gexpr({cons,_L,H,T}, RDs) -> is_gexpr_list([H,T], RDs);
-is_gexpr({tuple,_L,Es}, RDs) -> is_gexpr_list(Es, RDs);
-%%is_gexpr({struct,_L,_Tag,Es}, RDs) ->
-%% is_gexpr_list(Es, RDs);
-is_gexpr({record_index,_L,_Name,Field}, RDs) ->
- is_gexpr(Field, RDs);
-is_gexpr({record_field,_L,Rec,_Name,Field}, RDs) ->
- is_gexpr_list([Rec,Field], RDs);
-is_gexpr({record,L,Name,Inits}, RDs) ->
- is_gexpr_fields(Inits, L, Name, RDs);
-is_gexpr({bin,_L,Fs}, RDs) ->
+is_gexpr({var,_L,_V}, _Info) -> true;
+is_gexpr({char,_L,_C}, _Info) -> true;
+is_gexpr({integer,_L,_I}, _Info) -> true;
+is_gexpr({float,_L,_F}, _Info) -> true;
+is_gexpr({atom,_L,_A}, _Info) -> true;
+is_gexpr({string,_L,_S}, _Info) -> true;
+is_gexpr({nil,_L}, _Info) -> true;
+is_gexpr({cons,_L,H,T}, Info) -> is_gexpr_list([H,T], Info);
+is_gexpr({tuple,_L,Es}, Info) -> is_gexpr_list(Es, Info);
+%%is_gexpr({struct,_L,_Tag,Es}, Info) ->
+%% is_gexpr_list(Es, Info);
+is_gexpr({record_index,_L,_Name,Field}, Info) ->
+ is_gexpr(Field, Info);
+is_gexpr({record_field,_L,Rec,_Name,Field}, Info) ->
+ is_gexpr_list([Rec,Field], Info);
+is_gexpr({record,L,Name,Inits}, Info) ->
+ is_gexpr_fields(Inits, L, Name, Info);
+is_gexpr({bin,_L,Fs}, Info) ->
all(fun ({bin_element,_Line,E,Sz,_Ts}) ->
- is_gexpr(E, RDs) and (Sz =:= default orelse is_gexpr(Sz, RDs))
+ is_gexpr(E, Info) and (Sz =:= default orelse is_gexpr(Sz, Info))
end, Fs);
-is_gexpr({call,_L,{atom,_Lf,F},As}, RDs) ->
+is_gexpr({call,_L,{atom,_Lf,F},As}, {_,IsOverridden}=Info) ->
A = length(As),
- erl_internal:guard_bif(F, A) andalso is_gexpr_list(As, RDs);
-is_gexpr({call,_L,{remote,_Lr,{atom,_Lm,erlang},{atom,_Lf,F}},As}, RDs) ->
+ not IsOverridden({F,A}) andalso erl_internal:guard_bif(F, A)
+ andalso is_gexpr_list(As, Info);
+is_gexpr({call,_L,{remote,_Lr,{atom,_Lm,erlang},{atom,_Lf,F}},As}, Info) ->
A = length(As),
(erl_internal:guard_bif(F, A) orelse is_gexpr_op(F, A))
- andalso is_gexpr_list(As, RDs);
-is_gexpr({call,L,{tuple,Lt,[{atom,Lm,erlang},{atom,Lf,F}]},As}, RDs) ->
- is_gexpr({call,L,{remote,Lt,{atom,Lm,erlang},{atom,Lf,F}},As}, RDs);
-is_gexpr({op,_L,Op,A}, RDs) ->
- is_gexpr_op(Op, 1) andalso is_gexpr(A, RDs);
-is_gexpr({op,_L,'andalso',A1,A2}, RDs) ->
- is_gexpr_list([A1,A2], RDs);
-is_gexpr({op,_L,'orelse',A1,A2}, RDs) ->
- is_gexpr_list([A1,A2], RDs);
-is_gexpr({op,_L,Op,A1,A2}, RDs) ->
- is_gexpr_op(Op, 2) andalso is_gexpr_list([A1,A2], RDs);
-is_gexpr(_Other, _RDs) -> false.
+ andalso is_gexpr_list(As, Info);
+is_gexpr({call,L,{tuple,Lt,[{atom,Lm,erlang},{atom,Lf,F}]},As}, Info) ->
+ is_gexpr({call,L,{remote,Lt,{atom,Lm,erlang},{atom,Lf,F}},As}, Info);
+is_gexpr({op,_L,Op,A}, Info) ->
+ is_gexpr_op(Op, 1) andalso is_gexpr(A, Info);
+is_gexpr({op,_L,'andalso',A1,A2}, Info) ->
+ is_gexpr_list([A1,A2], Info);
+is_gexpr({op,_L,'orelse',A1,A2}, Info) ->
+ is_gexpr_list([A1,A2], Info);
+is_gexpr({op,_L,Op,A1,A2}, Info) ->
+ is_gexpr_op(Op, 2) andalso is_gexpr_list([A1,A2], Info);
+is_gexpr(_Other, _Info) -> false.
is_gexpr_op(Op, A) ->
try erl_internal:op_type(Op, A) of
@@ -2082,14 +2114,14 @@ is_gexpr_op(Op, A) ->
catch _:_ -> false
end.
-is_gexpr_list(Es, RDs) -> all(fun (E) -> is_gexpr(E, RDs) end, Es).
+is_gexpr_list(Es, Info) -> all(fun (E) -> is_gexpr(E, Info) end, Es).
-is_gexpr_fields(Fs, L, Name, RDs) ->
+is_gexpr_fields(Fs, L, Name, {RDs,_}=Info) ->
IFs = case dict:find(Name, RDs) of
{ok,{_Line,Fields}} -> Fs ++ init_fields(Fs, L, Fields);
error -> Fs
end,
- all(fun ({record_field,_Lf,_Name,V}) -> is_gexpr(V, RDs);
+ all(fun ({record_field,_Lf,_Name,V}) -> is_gexpr(V, Info);
(_Other) -> false end, IFs).
%% exprs(Sequence, VarTable, State) ->
@@ -3193,7 +3225,8 @@ lc_quals([{b_generate,_Line,P,E} | Qs], Vt0, Uvt0, St0) ->
{Vt,Uvt,St} = handle_generator(P,E,Vt0,Uvt0,St1),
lc_quals(Qs, Vt, Uvt, St);
lc_quals([F|Qs], Vt, Uvt, St0) ->
- {Fvt,St1} = case is_guard_test2(F, St0#lint.records) of
+ Info = is_guard_test2_info(St0),
+ {Fvt,St1} = case is_guard_test2(F, Info) of
true -> guard_test(F, Vt, St0);
false -> expr(F, Vt, St0)
end,
@@ -3201,6 +3234,12 @@ lc_quals([F|Qs], Vt, Uvt, St0) ->
lc_quals([], Vt, Uvt, St) ->
{Vt, Uvt, St}.
+is_guard_test2_info(#lint{records=RDs,locals=Locals,imports=Imports}) ->
+ {RDs,fun(FA) ->
+ is_local_function(Locals, FA) orelse
+ is_imported_function(Imports, FA)
+ end}.
+
handle_generator(P,E,Vt,Uvt,St0) ->
{Evt,St1} = expr(E, Vt, St0),
%% Forget variables local to E immediately.
@@ -3618,16 +3657,26 @@ obsolete_guard({call,Line,{atom,Lr,F},As}, St0) ->
false ->
deprecated_function(Line, erlang, F, As, St0);
true ->
- case is_warn_enabled(obsolete_guard, St0) of
- true ->
- add_warning(Lr,{obsolete_guard, {F, Arity}}, St0);
- false ->
- St0
- end
+ St = case is_warn_enabled(obsolete_guard, St0) of
+ true ->
+ add_warning(Lr, {obsolete_guard, {F, Arity}}, St0);
+ false ->
+ St0
+ end,
+ test_overriden_by_local(Lr, F, Arity, St)
end;
obsolete_guard(_G, St) ->
St.
+test_overriden_by_local(Line, OldTest, Arity, St) ->
+ ModernTest = list_to_atom("is_"++atom_to_list(OldTest)),
+ case is_local_function(St#lint.locals, {ModernTest, Arity}) of
+ true ->
+ add_error(Line, {obsolete_guard_overridden,OldTest}, St);
+ false ->
+ St
+ end.
+
%% keyword_warning(Line, Atom, State) -> State.
%% Add warning for atoms that will be reserved keywords in the future.
%% (Currently, no such keywords to warn for.)
diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl
index 85b2816451..549179da68 100644
--- a/lib/stdlib/src/erl_parse.yrl
+++ b/lib/stdlib/src/erl_parse.yrl
@@ -1567,19 +1567,6 @@ anno_from_term(Term) ->
map_anno(fun erl_anno:from_term/1, Term).
%% Forms.
-%% Recognize what sys_pre_expand does:
-modify_anno1({'fun',A,F,{_,_,_}=Id}, Ac, Mf) ->
- {A1,Ac1} = Mf(A, Ac),
- {F1,Ac2} = modify_anno1(F, Ac1, Mf),
- {{'fun',A1,F1,Id},Ac2};
-modify_anno1({named_fun,A,N,F,{_,_,_}=Id}, Ac, Mf) ->
- {A1,Ac1} = Mf(A, Ac),
- {F1,Ac2} = modify_anno1(F, Ac1, Mf),
- {{named_fun,A1,N,F1,Id},Ac2};
-modify_anno1({attribute,A,N,[V]}, Ac, Mf) ->
- {{attribute,A1,N1,V1},Ac1} = modify_anno1({attribute,A,N,V}, Ac, Mf),
- {{attribute,A1,N1,[V1]},Ac1};
-%% End of sys_pre_expand special forms.
modify_anno1({function,F,A}, Ac, _Mf) ->
{{function,F,A},Ac};
modify_anno1({function,M,F,A}, Ac, Mf) ->
diff --git a/lib/stdlib/src/eval_bits.erl b/lib/stdlib/src/eval_bits.erl
index 80667023fb..631faa3be5 100644
--- a/lib/stdlib/src/eval_bits.erl
+++ b/lib/stdlib/src/eval_bits.erl
@@ -67,16 +67,20 @@ expr_grp([Field | FS], Bs0, Lf, Acc) ->
expr_grp([], Bs0, _Lf, Acc) ->
{value,Acc,Bs0}.
+eval_field({bin_element, _, {string, _, S}, {integer,_,8}, [integer,{unit,1},unsigned,big]}, Bs0, _Fun) ->
+ Latin1 = [C band 16#FF || C <- S],
+ {list_to_binary(Latin1),Bs0};
eval_field({bin_element, _, {string, _, S}, default, default}, Bs0, _Fun) ->
Latin1 = [C band 16#FF || C <- S],
{list_to_binary(Latin1),Bs0};
-eval_field({bin_element, Line, {string, _, S}, Size0, Options0}, Bs, _Fun) ->
- {_Size,[Type,_Unit,_Sign,Endian]} =
+eval_field({bin_element, Line, {string, _, S}, Size0, Options0}, Bs0, Fun) ->
+ {Size1,[Type,{unit,Unit},Sign,Endian]} =
make_bit_type(Line, Size0, Options0),
- Res = << <<(eval_exp_field1(C, no_size, no_unit,
- Type, Endian, no_sign))/binary>> ||
+ {value,Size,Bs1} = Fun(Size1, Bs0),
+ Res = << <<(eval_exp_field1(C, Size, Unit,
+ Type, Endian, Sign))/binary>> ||
C <- S >>,
- {Res,Bs};
+ {Res,Bs1};
eval_field({bin_element,Line,E,Size0,Options0}, Bs0, Fun) ->
{value,V,Bs1} = Fun(E, Bs0),
{Size1,[Type,{unit,Unit},Sign,Endian]} =
diff --git a/lib/stdlib/src/math.erl b/lib/stdlib/src/math.erl
index 97c965e27a..3a3b384d8f 100644
--- a/lib/stdlib/src/math.erl
+++ b/lib/stdlib/src/math.erl
@@ -25,7 +25,9 @@
-export([sin/1, cos/1, tan/1, asin/1, acos/1, atan/1, atan2/2, sinh/1,
cosh/1, tanh/1, asinh/1, acosh/1, atanh/1, exp/1, log/1,
- log2/1, log10/1, pow/2, sqrt/1, erf/1, erfc/1]).
+ log2/1, log10/1, pow/2, sqrt/1, erf/1, erfc/1,
+ ceil/1, floor/1,
+ fmod/2]).
-spec acos(X) -> float() when
X :: number().
@@ -63,6 +65,11 @@ atan2(_, _) ->
atanh(_) ->
erlang:nif_error(undef).
+-spec ceil(X) -> float() when
+ X :: number().
+ceil(_) ->
+ erlang:nif_error(undef).
+
-spec cos(X) -> float() when
X :: number().
cos(_) ->
@@ -88,6 +95,16 @@ erfc(_) ->
exp(_) ->
erlang:nif_error(undef).
+-spec floor(X) -> float() when
+ X :: number().
+floor(_) ->
+ erlang:nif_error(undef).
+
+-spec fmod(X, Y) -> float() when
+ X :: number(), Y :: number().
+fmod(_, _) ->
+ erlang:nif_error(undef).
+
-spec log(X) -> float() when
X :: number().
log(_) ->
diff --git a/lib/stdlib/src/otp_internal.erl b/lib/stdlib/src/otp_internal.erl
index 3bd338071b..4161ced9ab 100644
--- a/lib/stdlib/src/otp_internal.erl
+++ b/lib/stdlib/src/otp_internal.erl
@@ -416,7 +416,7 @@ obsolete_1(inviso, _, _) ->
%% Added in R15B01.
obsolete_1(gs, _, _) ->
- {deprecated,"the gs application has been deprecated and will be removed in OTP 18; use the wx application instead"};
+ {removed,"the gs application has been removed; use the wx application instead"};
obsolete_1(ssh, sign_data, 2) ->
{deprecated,"deprecated (will be removed in R16A); use public_key:pem_decode/1, public_key:pem_entry_decode/1 "
"and public_key:sign/3 instead"};
diff --git a/lib/stdlib/src/proc_lib.erl b/lib/stdlib/src/proc_lib.erl
index 3dc1848550..363705b0f4 100644
--- a/lib/stdlib/src/proc_lib.erl
+++ b/lib/stdlib/src/proc_lib.erl
@@ -232,7 +232,7 @@ init_p(Parent, Ancestors, Fun) when is_function(Fun) ->
Fun()
catch
Class:Reason ->
- exit_p(Class, Reason)
+ exit_p(Class, Reason, erlang:get_stacktrace())
end.
-spec init_p(pid(), [pid()], atom(), atom(), [term()]) -> term().
@@ -247,7 +247,7 @@ init_p_do_apply(M, F, A) ->
apply(M, F, A)
catch
Class:Reason ->
- exit_p(Class, Reason)
+ exit_p(Class, Reason, erlang:get_stacktrace())
end.
-spec wake_up(atom(), atom(), [term()]) -> term().
@@ -257,22 +257,29 @@ wake_up(M, F, A) when is_atom(M), is_atom(F), is_list(A) ->
apply(M, F, A)
catch
Class:Reason ->
- exit_p(Class, Reason)
+ exit_p(Class, Reason, erlang:get_stacktrace())
end.
-exit_p(Class, Reason) ->
+exit_p(Class, Reason, Stacktrace) ->
case get('$initial_call') of
{M,F,A} when is_atom(M), is_atom(F), is_integer(A) ->
MFA = {M,F,make_dummy_args(A, [])},
crash_report(Class, Reason, MFA),
- exit(Reason);
+ erlang:raise(exit, exit_reason(Class, Reason, Stacktrace), Stacktrace);
_ ->
%% The process dictionary has been cleared or
%% possibly modified.
crash_report(Class, Reason, []),
- exit(Reason)
+ erlang:raise(exit, exit_reason(Class, Reason, Stacktrace), Stacktrace)
end.
+exit_reason(error, Reason, Stacktrace) ->
+ {Reason, Stacktrace};
+exit_reason(exit, Reason, _Stacktrace) ->
+ Reason;
+exit_reason(throw, Reason, Stacktrace) ->
+ {{nocatch, Reason}, Stacktrace}.
+
-spec start(Module, Function, Args) -> Ret when
Module :: module(),
Function :: atom(),
diff --git a/lib/stdlib/src/qlc_pt.erl b/lib/stdlib/src/qlc_pt.erl
index 0db63b81f4..28221ea75f 100644
--- a/lib/stdlib/src/qlc_pt.erl
+++ b/lib/stdlib/src/qlc_pt.erl
@@ -41,6 +41,7 @@
}).
-record(state, {imp,
+ overridden,
maxargs,
records,
xwarnings = [],
@@ -184,7 +185,9 @@ initiate(Forms0, Imported) ->
exclude_integers_from_unique_line_numbers(Forms0, NodeInfo),
?DEBUG("node info0 ~p~n",
[lists:sort(ets:tab2list(NodeInfo))]),
+ IsOverridden = set_up_overridden(Forms0),
State0 = #state{imp = Imported,
+ overridden = IsOverridden,
maxargs = ?EVAL_MAX_NUM_OF_ARGS,
records = record_attributes(Forms0),
node_info = NodeInfo},
@@ -1519,36 +1522,35 @@ filter_info(FilterData, AllIVs, Dependencies, State) ->
%% to be placed after further generators (the docs states otherwise, but
%% this seems to be common practice).
filter_list(FilterData, Dependencies, State) ->
- RDs = State#state.records,
- sel_gf(FilterData, 1, Dependencies, RDs, [], []).
+ sel_gf(FilterData, 1, Dependencies, State, [], []).
sel_gf([], _N, _Deps, _RDs, _Gens, _Gens1) ->
[];
-sel_gf([{#qid{no = N}=Id,{fil,F}}=Fil | FData], N, Deps, RDs, Gens, Gens1) ->
- case erl_lint:is_guard_test(F, RDs) of
+sel_gf([{#qid{no = N}=Id,{fil,F}}=Fil | FData], N, Deps, State, Gens, Gens1) ->
+ case is_guard_test(F, State) of
true ->
{Id,GIds} = lists:keyfind(Id, 1, Deps),
case length(GIds) =< 1 of
true ->
case generators_in_scope(GIds, Gens1) of
true ->
- [Fil|sel_gf(FData, N+1, Deps, RDs, Gens, Gens1)];
+ [Fil|sel_gf(FData, N+1, Deps, State, Gens, Gens1)];
false ->
- sel_gf(FData, N + 1, Deps, RDs, [], [])
+ sel_gf(FData, N + 1, Deps, State, [], [])
end;
false ->
case generators_in_scope(GIds, Gens) of
true ->
- [Fil | sel_gf(FData, N + 1, Deps, RDs, Gens, [])];
+ [Fil | sel_gf(FData, N + 1, Deps, State, Gens, [])];
false ->
- sel_gf(FData, N + 1, Deps, RDs, [], [])
+ sel_gf(FData, N + 1, Deps, State, [], [])
end
end;
false ->
- sel_gf(FData, N + 1, Deps, RDs, [], [])
+ sel_gf(FData, N + 1, Deps, State, [], [])
end;
-sel_gf(FData, N, Deps, RDs, Gens, Gens1) ->
- sel_gf(FData, N + 1, Deps, RDs, [N | Gens], [N | Gens1]).
+sel_gf(FData, N, Deps, State, Gens, Gens1) ->
+ sel_gf(FData, N + 1, Deps, State, [N | Gens], [N | Gens1]).
generators_in_scope(GenIds, GenNumbers) ->
lists:all(fun(#qid{no=N}) -> lists:member(N, GenNumbers) end, GenIds).
@@ -1870,7 +1872,8 @@ prep_expr(E, F, S, BF, Imported) ->
unify_column(Frame, Var, Col, BindFun, Imported) ->
A = anno0(),
- Call = {call,A,{atom,A,element},[{integer,A,Col}, {var,A,Var}]},
+ Call = {call,A,{remote,A,{atom,A,erlang},{atom,A,element}},
+ [{integer,A,Col}, {var,A,Var}]},
element_calls(Call, Frame, BindFun, Imported).
%% cons_tuple is used for representing {V1, ..., Vi | TupleTail}.
@@ -1880,6 +1883,8 @@ unify_column(Frame, Var, Col, BindFun, Imported) ->
%% about the size of the tuple is known.
element_calls({call,_,{remote,_,{atom,_,erlang},{atom,_,element}},
[{integer,_,I},Term0]}, F0, BF, Imported) when I > 0 ->
+ %% Note: erl_expand_records ensures that all calls to element/2
+ %% have an explicit "erlang:" prefix.
TupleTail = unique_var(),
VarsL = [unique_var() || _ <- lists:seq(1, I)],
Vars = VarsL ++ TupleTail,
@@ -1887,10 +1892,6 @@ element_calls({call,_,{remote,_,{atom,_,erlang},{atom,_,element}},
VarI = lists:nth(I, VarsL),
{Term, F} = element_calls(Term0, F0, BF, Imported),
{VarI, unify('=:=', Tuple, Term, F, BF, Imported)};
-element_calls({call,L1,{atom,_,element}=E,As}, F0, BF, Imported) ->
- %% erl_expand_records should add "erlang:"...
- element_calls({call,L1,{remote,L1,{atom,L1,erlang},E}, As}, F0, BF,
- Imported);
element_calls(T, F0, BF, Imported) when is_tuple(T) ->
{L, F} = element_calls(tuple_to_list(T), F0, BF, Imported),
{list_to_tuple(L), F};
@@ -2484,7 +2485,7 @@ filter(E, L, QIVs, S, RL, Fun, Go, GoI, IVs, State) ->
%% This is the "guard semantics" used in ordinary list
%% comprehension: if a filter looks like a guard test, it returns
%% 'false' rather than fails.
- Body = case erl_lint:is_guard_test(E, State#state.records) of
+ Body = case is_guard_test(E, State) of
true ->
CT = {clause,L,[],[[E]],[{call,L,?V(Fun),NAsT}]},
CF = {clause,L,[],[[?A(true)]],[{call,L,?V(Fun),NAsF}]},
@@ -2888,6 +2889,26 @@ family_list(L) ->
family(L) ->
sofs:relation_to_family(sofs:relation(L)).
+is_guard_test(E, #state{records = RDs, overridden = IsOverridden}) ->
+ erl_lint:is_guard_test(E, RDs, IsOverridden).
+
+%% In code that has been run through erl_expand_records, a guard
+%% test will never contain calls without an explicit module
+%% prefix. Unfortunately, this module runs *some* of the code
+%% through erl_expand_records, but not all of it.
+%%
+%% Therefore, we must set up our own list of local and imported functions
+%% that will override a BIF with the same name.
+
+set_up_overridden(Forms) ->
+ Locals = [{Name,Arity} || {function,_,Name,Arity,_} <- Forms],
+ Imports0 = [Fs || {attribute,_,import,Fs} <- Forms],
+ Imports1 = lists:flatten(Imports0),
+ Imports2 = [Fs || {_,Fs} <- Imports1],
+ Imports = lists:flatten(Imports2),
+ Overridden = gb_sets:from_list(Imports ++ Locals),
+ fun(FA) -> gb_sets:is_element(FA, Overridden) end.
+
-ifdef(debug).
display_forms(Forms) ->
io:format("Forms ***~n"),
diff --git a/lib/stdlib/src/rand.erl b/lib/stdlib/src/rand.erl
index 93409d95df..1f457b9e0e 100644
--- a/lib/stdlib/src/rand.erl
+++ b/lib/stdlib/src/rand.erl
@@ -19,7 +19,7 @@
%%
%% =====================================================================
%% Multiple PRNG module for Erlang/OTP
-%% Copyright (c) 2015 Kenji Rikitake
+%% Copyright (c) 2015-2016 Kenji Rikitake
%% =====================================================================
-module(rand).
@@ -27,11 +27,14 @@
-export([seed_s/1, seed_s/2, seed/1, seed/2,
export_seed/0, export_seed_s/1,
uniform/0, uniform/1, uniform_s/1, uniform_s/2,
+ jump/0, jump/1,
normal/0, normal_s/1
]).
-compile({inline, [exs64_next/1, exsplus_next/1,
+ exsplus_jump/1,
exs1024_next/1, exs1024_calc/2,
+ exs1024_jump/1,
get_52/1, normal_kiwi/1]}).
-define(DEFAULT_ALG_HANDLER, exsplus).
@@ -48,7 +51,8 @@
max := integer(),
next := fun(),
uniform := fun(),
- uniform_n := fun()}.
+ uniform_n := fun(),
+ jump := fun()}.
%% Internal state
-opaque state() :: {alg_handler(), alg_seed()}.
@@ -79,9 +83,7 @@ export_seed_s({#{type:=Alg}, Seed}) -> {Alg, Seed}.
-spec seed(AlgOrExpState::alg() | export_state()) -> state().
seed(Alg) ->
- R = seed_s(Alg),
- _ = seed_put(R),
- R.
+ seed_put(seed_s(Alg)).
-spec seed_s(AlgOrExpState::alg() | export_state()) -> state().
seed_s(Alg) when is_atom(Alg) ->
@@ -97,9 +99,7 @@ seed_s({Alg0, Seed}) ->
-spec seed(Alg :: alg(), {integer(), integer(), integer()}) -> state().
seed(Alg0, S0) ->
- State = seed_s(Alg0, S0),
- _ = seed_put(State),
- State.
+ seed_put(seed_s(Alg0, S0)).
-spec seed_s(Alg :: alg(), {integer(), integer(), integer()}) -> state().
seed_s(Alg0, S0 = {_, _, _}) ->
@@ -150,6 +150,25 @@ uniform_s(N, State0 = {#{uniform:=Uniform}, _})
{F, State} = Uniform(State0),
{trunc(F * N) + 1, State}.
+%% jump/1: given a state, jump/1
+%% returns a new state which is equivalent to that
+%% after a large number of call defined for each algorithm.
+%% The large number is algorithm dependent.
+
+-spec jump(state()) -> NewS :: state().
+jump(State = {#{jump:=Jump}, _}) ->
+ Jump(State).
+
+%% jump/0: read the internal state and
+%% apply the jump function for the state as in jump/1
+%% and write back the new value to the internal state,
+%% then returns the new value.
+
+-spec jump() -> NewS :: state().
+
+jump() ->
+ seed_put(jump(seed_get())).
+
%% normal/0: returns a random float with standard normal distribution
%% updating the state in the process dictionary.
@@ -192,9 +211,10 @@ normal_s(State0) ->
-type uint64() :: 0..16#ffffffffffffffff.
-type uint58() :: 0..16#03ffffffffffffff.
--spec seed_put(state()) -> undefined | state().
+-spec seed_put(state()) -> state().
seed_put(Seed) ->
- put(?SEED_DICT, Seed).
+ put(?SEED_DICT, Seed),
+ Seed.
seed_get() ->
case get(?SEED_DICT) of
@@ -205,15 +225,18 @@ seed_get() ->
%% Setup alg record
mk_alg(exs64) ->
{#{type=>exs64, max=>?UINT64MASK, next=>fun exs64_next/1,
- uniform=>fun exs64_uniform/1, uniform_n=>fun exs64_uniform/2},
+ uniform=>fun exs64_uniform/1, uniform_n=>fun exs64_uniform/2,
+ jump=>fun exs64_jump/1},
fun exs64_seed/1};
mk_alg(exsplus) ->
{#{type=>exsplus, max=>?UINT58MASK, next=>fun exsplus_next/1,
- uniform=>fun exsplus_uniform/1, uniform_n=>fun exsplus_uniform/2},
+ uniform=>fun exsplus_uniform/1, uniform_n=>fun exsplus_uniform/2,
+ jump=>fun exsplus_jump/1},
fun exsplus_seed/1};
mk_alg(exs1024) ->
{#{type=>exs1024, max=>?UINT64MASK, next=>fun exs1024_next/1,
- uniform=>fun exs1024_uniform/1, uniform_n=>fun exs1024_uniform/2},
+ uniform=>fun exs1024_uniform/1, uniform_n=>fun exs1024_uniform/2,
+ jump=>fun exs1024_jump/1},
fun exs1024_seed/1}.
%% =====================================================================
@@ -246,6 +269,9 @@ exs64_uniform(Max, {Alg, R}) ->
{V, R1} = exs64_next(R),
{(V rem Max) + 1, {Alg, R1}}.
+exs64_jump(_) ->
+ erlang:error(not_implemented).
+
%% =====================================================================
%% exsplus PRNG: Xorshift116+
%% Algorithm by Sebastiano Vigna
@@ -283,6 +309,40 @@ exsplus_uniform(Max, {Alg, R}) ->
{V, R1} = exsplus_next(R),
{(V rem Max) + 1, {Alg, R1}}.
+%% This is the jump function for the exsplus generator, 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.
+
+%% -define(JUMPCONST, 16#000d174a83e17de2302f8ea6bc32c797).
+%% split into 58-bit chunks
+%% and two iterative executions
+
+-define(JUMPCONST1, 16#02f8ea6bc32c797).
+-define(JUMPCONST2, 16#345d2a0f85f788c).
+-define(JUMPELEMLEN, 58).
+
+-dialyzer({no_improper_lists, exsplus_jump/1}).
+-spec exsplus_jump(state()) -> state().
+exsplus_jump({Alg, S}) ->
+ {S1, AS1} = exsplus_jump(S, [0|0], ?JUMPCONST1, ?JUMPELEMLEN),
+ {_, AS2} = exsplus_jump(S1, AS1, ?JUMPCONST2, ?JUMPELEMLEN),
+ {Alg, AS2}.
+
+-dialyzer({no_improper_lists, exsplus_jump/4}).
+exsplus_jump(S, AS, _, 0) ->
+ {S, AS};
+exsplus_jump(S, [AS0|AS1], J, N) ->
+ {_, NS} = exsplus_next(S),
+ case (J band 1) of
+ 1 ->
+ [S0|S1] = S,
+ exsplus_jump(NS, [(AS0 bxor S0)|(AS1 bxor S1)], J bsr 1, N-1);
+ 0 ->
+ exsplus_jump(NS, [AS0|AS1], J bsr 1, N-1)
+ end.
+
%% =====================================================================
%% exs1024 PRNG: Xorshift1024*
%% Algorithm by Sebastiano Vigna
@@ -340,6 +400,60 @@ exs1024_uniform(Max, {Alg, R}) ->
{V, R1} = exs1024_next(R),
{(V rem Max) + 1, {Alg, R1}}.
+%% This is the jump function for the exs1024 generator, equivalent
+%% to 2^512 calls to next(); it can be used to generate 2^512
+%% non-overlapping subsequences for parallel computations.
+%% Note: the jump function takes ~2000 times of the execution time of
+%% next/1.
+
+%% Jump constant here split into 58 bits for speed
+-define(JUMPCONSTHEAD, 16#00242f96eca9c41d).
+-define(JUMPCONSTTAIL,
+ [16#0196e1ddbe5a1561,
+ 16#0239f070b5837a3c,
+ 16#03f393cc68796cd2,
+ 16#0248316f404489af,
+ 16#039a30088bffbac2,
+ 16#02fea70dc2d9891f,
+ 16#032ae0d9644caec4,
+ 16#0313aac17d8efa43,
+ 16#02f132e055642626,
+ 16#01ee975283d71c93,
+ 16#00552321b06f5501,
+ 16#00c41d10a1e6a569,
+ 16#019158ecf8aa1e44,
+ 16#004e9fc949d0b5fc,
+ 16#0363da172811fdda,
+ 16#030e38c3b99181f2,
+ 16#0000000a118038fc]).
+-define(JUMPTOTALLEN, 1024).
+-define(RINGLEN, 16).
+
+-spec exs1024_jump(state()) -> state().
+
+exs1024_jump({Alg, {L, RL}}) ->
+ P = length(RL),
+ AS = exs1024_jump({L, RL},
+ [0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0],
+ ?JUMPCONSTTAIL, ?JUMPCONSTHEAD, ?JUMPELEMLEN, ?JUMPTOTALLEN),
+ {ASL, ASR} = lists:split(?RINGLEN - P, AS),
+ {Alg, {ASL, lists:reverse(ASR)}}.
+
+exs1024_jump(_, AS, _, _, _, 0) ->
+ AS;
+exs1024_jump(S, AS, [H|T], _, 0, TN) ->
+ exs1024_jump(S, AS, T, H, ?JUMPELEMLEN, TN);
+exs1024_jump({L, RL}, AS, JL, J, N, TN) ->
+ {_, NS} = exs1024_next({L, RL}),
+ case (J band 1) of
+ 1 ->
+ AS2 = lists:zipwith(fun(X, Y) -> X bxor Y end,
+ AS, L ++ lists:reverse(RL)),
+ exs1024_jump(NS, AS2, JL, J bsr 1, N-1, TN-1);
+ 0 ->
+ exs1024_jump(NS, AS, JL, J bsr 1, N-1, TN-1)
+ end.
+
%% =====================================================================
%% Ziggurat cont
%% =====================================================================
diff --git a/lib/stdlib/src/sets.erl b/lib/stdlib/src/sets.erl
index 3e70450320..c65a13b22e 100644
--- a/lib/stdlib/src/sets.erl
+++ b/lib/stdlib/src/sets.erl
@@ -128,14 +128,14 @@ is_element(E, S) ->
Set2 :: set(Element).
add_element(E, S0) ->
Slot = get_slot(S0, E),
- {S1,Ic} = on_bucket(fun (B0) -> add_bkt_el(E, B0, B0) end, S0, Slot),
- maybe_expand(S1, Ic).
-
--spec add_bkt_el(T, [T], [T]) -> {[T], 0 | 1}.
-add_bkt_el(E, [E|_], Bkt) -> {Bkt,0};
-add_bkt_el(E, [_|B], Bkt) ->
- add_bkt_el(E, B, Bkt);
-add_bkt_el(E, [], Bkt) -> {[E|Bkt],1}.
+ Bkt = get_bucket(S0, Slot),
+ case lists:member(E, Bkt) of
+ true ->
+ S0;
+ false ->
+ S1 = update_bucket(S0, Slot, [E | Bkt]),
+ maybe_expand(S1)
+ end.
%% del_element(Element, Set) -> Set.
%% Return Set but with Element removed.
@@ -144,15 +144,28 @@ add_bkt_el(E, [], Bkt) -> {[E|Bkt],1}.
Set2 :: set(Element).
del_element(E, S0) ->
Slot = get_slot(S0, E),
- {S1,Dc} = on_bucket(fun (B0) -> del_bkt_el(E, B0) end, S0, Slot),
- maybe_contract(S1, Dc).
+ Bkt = get_bucket(S0, Slot),
+ case lists:member(E, Bkt) of
+ false ->
+ S0;
+ true ->
+ S1 = update_bucket(S0, Slot, lists:delete(E, Bkt)),
+ maybe_contract(S1, 1)
+ end.
--spec del_bkt_el(T, [T]) -> {[T], 0 | 1}.
-del_bkt_el(E, [E|Bkt]) -> {Bkt,1};
-del_bkt_el(E, [Other|Bkt0]) ->
- {Bkt1,Dc} = del_bkt_el(E, Bkt0),
- {[Other|Bkt1],Dc};
-del_bkt_el(_, []) -> {[],0}.
+%% update_bucket(Set, Slot, NewBucket) -> UpdatedSet.
+%% Replace bucket in Slot by NewBucket
+-spec update_bucket(Set1, Slot, Bkt) -> Set2 when
+ Set1 :: set(Element),
+ Set2 :: set(Element),
+ Slot :: non_neg_integer(),
+ Bkt :: [Element].
+update_bucket(Set, Slot, NewBucket) ->
+ SegI = ((Slot-1) div ?seg_size) + 1,
+ BktI = ((Slot-1) rem ?seg_size) + 1,
+ Segs = Set#set.segs,
+ Seg = element(SegI, Segs),
+ Set#set{segs = setelement(SegI, Segs, setelement(BktI, Seg, NewBucket))}.
%% union(Set1, Set2) -> Set
%% Return the union of Set1 and Set2.
@@ -272,19 +285,6 @@ get_slot(T, Key) ->
-spec get_bucket(set(), non_neg_integer()) -> term().
get_bucket(T, Slot) -> get_bucket_s(T#set.segs, Slot).
-%% on_bucket(Fun, Hashdb, Slot) -> {NewHashDb,Result}.
-%% Apply Fun to the bucket in Slot and replace the returned bucket.
--spec on_bucket(fun((_) -> {[_], 0 | 1}), set(E), non_neg_integer()) ->
- {set(E), 0 | 1}.
-on_bucket(F, T, Slot) ->
- SegI = ((Slot-1) div ?seg_size) + 1,
- BktI = ((Slot-1) rem ?seg_size) + 1,
- Segs = T#set.segs,
- Seg = element(SegI, Segs),
- B0 = element(BktI, Seg),
- {B1, Res} = F(B0), %Op on the bucket.
- {T#set{segs = setelement(SegI, Segs, setelement(BktI, Seg, B1))},Res}.
-
%% fold_set(Fun, Acc, Dictionary) -> Dictionary.
%% filter_set(Fun, Dictionary) -> Dictionary.
@@ -349,8 +349,8 @@ put_bucket_s(Segs, Slot, Bkt) ->
Seg = setelement(BktI, element(SegI, Segs), Bkt),
setelement(SegI, Segs, Seg).
--spec maybe_expand(set(E), 0 | 1) -> set(E).
-maybe_expand(T0, Ic) when T0#set.size + Ic > T0#set.exp_size ->
+-spec maybe_expand(set(E)) -> set(E).
+maybe_expand(T0) when T0#set.size + 1 > T0#set.exp_size ->
T = maybe_expand_segs(T0), %Do we need more segments.
N = T#set.n + 1, %Next slot to expand into
Segs0 = T#set.segs,
@@ -360,12 +360,12 @@ maybe_expand(T0, Ic) when T0#set.size + Ic > T0#set.exp_size ->
{B1,B2} = rehash(B, Slot1, Slot2, T#set.maxn),
Segs1 = put_bucket_s(Segs0, Slot1, B1),
Segs2 = put_bucket_s(Segs1, Slot2, B2),
- T#set{size = T#set.size + Ic,
+ T#set{size = T#set.size + 1,
n = N,
exp_size = N * ?expand_load,
con_size = N * ?contract_load,
segs = Segs2};
-maybe_expand(T, Ic) -> T#set{size = T#set.size + Ic}.
+maybe_expand(T) -> T#set{size = T#set.size + 1}.
-spec maybe_expand_segs(set(E)) -> set(E).
maybe_expand_segs(T) when T#set.n =:= T#set.maxn ->
diff --git a/lib/stdlib/src/stdlib.app.src b/lib/stdlib/src/stdlib.app.src
index 09176d2ca0..8cf46482dd 100644
--- a/lib/stdlib/src/stdlib.app.src
+++ b/lib/stdlib/src/stdlib.app.src
@@ -106,7 +106,7 @@
dets]},
{applications, [kernel]},
{env, []},
- {runtime_dependencies, ["sasl-3.0","kernel-5.0","erts-8.0","crypto-3.3",
+ {runtime_dependencies, ["sasl-3.0","kernel-5.0","erts-9.0","crypto-3.3",
"compiler-5.0"]}
]}.
diff --git a/lib/stdlib/src/stdlib.appup.src b/lib/stdlib/src/stdlib.appup.src
index e917b7ea1f..979161fef7 100644
--- a/lib/stdlib/src/stdlib.appup.src
+++ b/lib/stdlib/src/stdlib.appup.src
@@ -18,9 +18,7 @@
%% %CopyrightEnd%
{"%VSN%",
%% Up from - max one major revision back
- [{<<"3\\.[0-1](\\.[0-9]+)*">>,[restart_new_emulator]}, % OTP-19.*
- {<<"2\\.[5-8](\\.[0-9]+)*">>,[restart_new_emulator]}], % OTP-18.*
+ [{<<"3\\.[0-1](\\.[0-9]+)*">>,[restart_new_emulator]}], % OTP-19.*
%% Down to - max one major revision back
- [{<<"3\\.[0-1](\\.[0-9]+)*">>,[restart_new_emulator]}, % OTP-19.*
- {<<"2\\.[5-8](\\.[0-9]+)*">>,[restart_new_emulator]}] % OTP-18.*
+ [{<<"3\\.[0-1](\\.[0-9]+)*">>,[restart_new_emulator]}] % OTP-19.*
}.
diff --git a/lib/stdlib/src/timer.erl b/lib/stdlib/src/timer.erl
index ca868627a9..df10790ea0 100644
--- a/lib/stdlib/src/timer.erl
+++ b/lib/stdlib/src/timer.erl
@@ -165,7 +165,7 @@ tc(F) ->
T1 = erlang:monotonic_time(),
Val = F(),
T2 = erlang:monotonic_time(),
- Time = erlang:convert_time_unit(T2 - T1, native, micro_seconds),
+ Time = erlang:convert_time_unit(T2 - T1, native, microsecond),
{Time, Val}.
%%
@@ -180,7 +180,7 @@ tc(F, A) ->
T1 = erlang:monotonic_time(),
Val = apply(F, A),
T2 = erlang:monotonic_time(),
- Time = erlang:convert_time_unit(T2 - T1, native, micro_seconds),
+ Time = erlang:convert_time_unit(T2 - T1, native, microsecond),
{Time, Val}.
%%
@@ -196,7 +196,7 @@ tc(M, F, A) ->
T1 = erlang:monotonic_time(),
Val = apply(M, F, A),
T2 = erlang:monotonic_time(),
- Time = erlang:convert_time_unit(T2 - T1, native, micro_seconds),
+ Time = erlang:convert_time_unit(T2 - T1, native, microsecond),
{Time, Val}.
%%