aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib')
-rw-r--r--lib/stdlib/doc/src/erl_expand_records.xml6
-rw-r--r--lib/stdlib/doc/src/erl_internal.xml10
-rw-r--r--lib/stdlib/doc/src/math.xml2
-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.erl13
-rw-r--r--lib/stdlib/src/otp_internal.erl2
-rw-r--r--lib/stdlib/src/qlc_pt.erl55
-rw-r--r--lib/stdlib/src/stdlib.app.src2
-rw-r--r--lib/stdlib/src/timer.erl6
-rw-r--r--lib/stdlib/test/Makefile1
-rw-r--r--lib/stdlib/test/erl_lint_SUITE.erl10
-rw-r--r--lib/stdlib/test/erl_pp_SUITE.erl20
-rw-r--r--lib/stdlib/test/ets_SUITE.erl113
-rw-r--r--lib/stdlib/test/io_proto_SUITE.erl2
-rw-r--r--lib/stdlib/test/math_SUITE.erl92
-rw-r--r--lib/stdlib/test/qlc_SUITE.erl21
-rw-r--r--lib/stdlib/test/shell_SUITE.erl7
-rw-r--r--lib/stdlib/test/timer_SUITE.erl2
-rw-r--r--lib/stdlib/test/timer_simple_SUITE.erl2
24 files changed, 545 insertions, 228 deletions
diff --git a/lib/stdlib/doc/src/erl_expand_records.xml b/lib/stdlib/doc/src/erl_expand_records.xml
index 7e4aa2db37..b6aa75ed03 100644
--- a/lib/stdlib/doc/src/erl_expand_records.xml
+++ b/lib/stdlib/doc/src/erl_expand_records.xml
@@ -45,8 +45,10 @@
<name name="module" arity="2"/>
<fsummary>Expand all records in a module.</fsummary>
<desc>
- <p>Expands all records in a module. The returned module has no
- references to records, attributes, or code.</p>
+ <p>Expands all records in a module to use explicit tuple
+ operations and adds explicit module names to calls to BIFs and
+ imported functions. The returned module has no references to
+ records, attributes, or code.</p>
</desc>
</func>
</funcs>
diff --git a/lib/stdlib/doc/src/erl_internal.xml b/lib/stdlib/doc/src/erl_internal.xml
index cf49df0972..17cd0fb240 100644
--- a/lib/stdlib/doc/src/erl_internal.xml
+++ b/lib/stdlib/doc/src/erl_internal.xml
@@ -44,6 +44,16 @@
<funcs>
<func>
+ <name name="add_predefined_functions" arity="1"/>
+ <fsummary>Add code for pre-defined functions.</fsummary>
+ <desc>
+ <p>Adds to <c><anno>Forms</anno></c> the code for the standard
+ pre-defined functions (such as <c>module_info/0</c>) that are
+ to be included in every module.</p>
+ </desc>
+ </func>
+
+ <func>
<name name="arith_op" arity="2"/>
<fsummary>Test for an arithmetic operator.</fsummary>
<desc>
diff --git a/lib/stdlib/doc/src/math.xml b/lib/stdlib/doc/src/math.xml
index 1358ce5cbf..70ca6ae78e 100644
--- a/lib/stdlib/doc/src/math.xml
+++ b/lib/stdlib/doc/src/math.xml
@@ -57,9 +57,11 @@
<name name="atan" arity="1"/>
<name name="atan2" arity="2"/>
<name name="atanh" arity="1"/>
+ <name name="ceil" arity="1"/>
<name name="cos" arity="1"/>
<name name="cosh" arity="1"/>
<name name="exp" arity="1"/>
+ <name name="floor" arity="1"/>
<name name="log" arity="1"/>
<name name="log10" arity="1"/>
<name name="log2" arity="1"/>
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..1db48cd0a2 100644
--- a/lib/stdlib/src/math.erl
+++ b/lib/stdlib/src/math.erl
@@ -25,7 +25,8 @@
-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]).
-spec acos(X) -> float() when
X :: number().
@@ -63,6 +64,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 +94,11 @@ erfc(_) ->
exp(_) ->
erlang:nif_error(undef).
+-spec floor(X) -> float() when
+ X :: number().
+floor(_) ->
+ 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/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/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/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}.
%%
diff --git a/lib/stdlib/test/Makefile b/lib/stdlib/test/Makefile
index 28c35aed55..deac04aa66 100644
--- a/lib/stdlib/test/Makefile
+++ b/lib/stdlib/test/Makefile
@@ -52,6 +52,7 @@ MODULES= \
io_proto_SUITE \
lists_SUITE \
log_mf_h_SUITE \
+ math_SUITE \
ms_transform_SUITE \
proc_lib_SUITE \
qlc_SUITE \
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index d916eb3eef..4ee3950882 100644
--- a/lib/stdlib/test/erl_lint_SUITE.erl
+++ b/lib/stdlib/test/erl_lint_SUITE.erl
@@ -1554,7 +1554,15 @@ guard(Config) when is_list(Config) ->
[],
{errors,[{1,erl_lint,illegal_guard_expr},
{2,erl_lint,illegal_guard_expr}],
- []}}
+ []}},
+ {guard10,
+ <<"is_port(_) -> false.
+ t(P) when port(P) -> ok.
+ ">>,
+ [],
+ {error,
+ [{2,erl_lint,{obsolete_guard_overridden,port}}],
+ [{2,erl_lint,{obsolete_guard,{port,1}}}]}}
],
[] = run(Config, Ts1),
ok.
diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl
index a103f6dc53..13c5662741 100644
--- a/lib/stdlib/test/erl_pp_SUITE.erl
+++ b/lib/stdlib/test/erl_pp_SUITE.erl
@@ -1166,19 +1166,21 @@ compile(Config, Tests) ->
lists:foldl(F, [], Tests).
compile_file(Config, Test0) ->
- case compile_file(Config, Test0, ['E']) of
+ Test = ["-module(erl_pp_test).\n",
+ "-compile(export_all).\n",
+ Test0],
+ case compile_file(Config, Test, ['E']) of
{ok, RootFile} ->
File = RootFile ++ ".E",
{ok, Bin0} = file:read_file(File),
- Bin = strip_module_info(Bin0),
%% A very simple check: just try to compile the output.
- case compile_file(Config, Bin, []) of
+ case compile_file(Config, Bin0, []) of
{ok, RootFile2} ->
File2 = RootFile2 ++ ".E",
{ok, Bin1} = file:read_file(File2),
case Bin0 =:= Bin1 of
true ->
- test_max_line(binary_to_list(Bin));
+ test_max_line(binary_to_list(Bin0));
false ->
{error, file_contents_modified, {Bin0, Bin1}}
end;
@@ -1189,11 +1191,8 @@ compile_file(Config, Test0) ->
Error
end.
-compile_file(Config, Test0, Opts0) ->
+compile_file(Config, Test, Opts0) ->
FileName = filename('erl_pp_test.erl', Config),
- Test = list_to_binary(["-module(erl_pp_test). "
- "-compile(export_all). ",
- Test0]),
Opts = [export_all,return,nowarn_unused_record,{outdir,?privdir} | Opts0],
ok = file:write_file(FileName, Test),
case compile:file(FileName, Opts) of
@@ -1202,11 +1201,6 @@ compile_file(Config, Test0, Opts0) ->
Error -> Error
end.
-strip_module_info(Bin) ->
- {match, [{Start,_Len}|_]} = re:run(Bin, "module_info"),
- <<R:Start/binary,_/binary>> = Bin,
- R.
-
flat_expr1(Expr0) ->
Expr = erl_parse:new_anno(Expr0),
lists:flatten(erl_pp:expr(Expr)).
diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl
index b02d17bdb6..9a14c7014c 100644
--- a/lib/stdlib/test/ets_SUITE.erl
+++ b/lib/stdlib/test/ets_SUITE.erl
@@ -218,7 +218,7 @@ memory_check_summary(_Config) ->
receive {get_failed_memchecks, FailedMemchecks} -> ok end,
io:format("Failed memchecks: ~p\n",[FailedMemchecks]),
NoFailedMemchecks = length(FailedMemchecks),
- if NoFailedMemchecks > 3 ->
+ if NoFailedMemchecks > 1 ->
ct:fail("Too many failed (~p) memchecks", [NoFailedMemchecks]);
true ->
ok
@@ -591,12 +591,6 @@ select_fail_do(Opts) ->
-define(S(T),ets:info(T,memory)).
--define(TAB_STRUCT_SZ, erts_debug:get_internal_state('DbTable_words')).
-%%-define(NORMAL_TAB_STRUCT_SZ, 26). %% SunOS5.8, 32-bit, non smp, private heap
-%%
-%% The hardcoded expected memory sizes (in words) are the ones we expect on:
-%% SunOS5.8, 32-bit, non smp, private heap
-%%
%% Whitebox test of ets:info(X, memory).
memory(Config) when is_list(Config) ->
@@ -607,11 +601,11 @@ memory(Config) when is_list(Config) ->
memory_do(Opts) ->
L = [T1,T2,T3,T4] = fill_sets_int(1000,Opts),
XR1 = case mem_mode(T1) of
- {normal,_} -> {13836,13046,13046,13052}; %{13862,13072,13072,13078};
- {compressed,4} -> {11041,10251,10251,10252}; %{11067,10277,10277,10278};
- {compressed,8} -> {10050,9260,9260,9260} %{10076,9286,9286,9286}
+ {normal,_} -> {13836, 15346, 15346, 15346+6};
+ {compressed,4} -> {11041, 12551, 12551, 12551+1};
+ {compressed,8} -> {10050, 11560, 11560, 11560}
end,
- XRes1 = adjust_xmem(L, XR1),
+ XRes1 = adjust_xmem(L, XR1, 1),
Res1 = {?S(T1),?S(T2),?S(T3),?S(T4)},
lists:foreach(fun(T) ->
Before = ets:info(T,size),
@@ -623,11 +617,11 @@ memory_do(Opts) ->
end,
L),
XR2 = case mem_mode(T1) of
- {normal,_} -> {13826,13037,13028,13034}; %{13852,13063,13054,13060};
- {compressed,4} -> {11031,10242,10233,10234}; %{11057,10268,10259,10260};
- {compressed,8} -> {10040,9251,9242,9242} %10066,9277,9268,9268}
+ {normal,_} -> {13826, 15337, 15337-9, 15337-3};
+ {compressed,4} -> {11031, 12542, 12542-9, 12542-8};
+ {compressed,8} -> {10040, 11551, 11551-9, 11551-9}
end,
- XRes2 = adjust_xmem(L, XR2),
+ XRes2 = adjust_xmem(L, XR2, 1),
Res2 = {?S(T1),?S(T2),?S(T3),?S(T4)},
lists:foreach(fun(T) ->
Before = ets:info(T,size),
@@ -639,17 +633,17 @@ memory_do(Opts) ->
end,
L),
XR3 = case mem_mode(T1) of
- {normal,_} -> {13816,13028,13010,13016}; %{13842,13054,13036,13042};
- {compressed,4} -> {11021,10233,10215,10216}; %{11047,10259,10241,10242};
- {compressed,8} -> {10030,9242,9224,9224} %{10056,9268,9250,9250}
+ {normal,_} -> {13816, 15328, 15328-18, 15328-12};
+ {compressed,4} -> {11021, 12533, 12533-18, 12533-17};
+ {compressed,8} -> {10030, 11542, 11542-18, 11542-18}
end,
- XRes3 = adjust_xmem(L, XR3),
+ XRes3 = adjust_xmem(L, XR3, 1),
Res3 = {?S(T1),?S(T2),?S(T3),?S(T4)},
lists:foreach(fun(T) ->
ets:delete_all_objects(T)
end,
L),
- XRes4 = adjust_xmem(L, {50,260,260,260}), %{76,286,286,286}),
+ XRes4 = adjust_xmem(L, {50, 256, 256, 256}, 0),
Res4 = {?S(T1),?S(T2),?S(T3),?S(T4)},
lists:foreach(fun(T) ->
ets:delete(T)
@@ -660,7 +654,7 @@ memory_do(Opts) ->
ets:select_delete(T,[{'_',[],[true]}])
end,
L2),
- XRes5 = adjust_xmem(L2, {50,260,260,260}), %{76,286,286,286}),
+ XRes5 = adjust_xmem(L2, {50, 256, 256, 256}, 0),
Res5 = {?S(T11),?S(T12),?S(T13),?S(T14)},
io:format("XRes1 = ~p~n"
" Res1 = ~p~n~n"
@@ -698,15 +692,15 @@ chk_normal_tab_struct_size() ->
erlang:system_info(smp_support),
erlang:system_info(heap_type)},
io:format("System = ~p~n", [System]),
- io:format("?TAB_STRUCT_SZ=~p~n", [?TAB_STRUCT_SZ]),
ok.
-adjust_xmem([_T1,_T2,_T3,_T4], {A0,B0,C0,D0} = _Mem0) ->
+adjust_xmem([_T1,_T2,_T3,_T4], {A0,B0,C0,D0} = _Mem0, EstCnt) ->
%% Adjust for 64-bit, smp, and os:
%% Table struct size may differ.
- TabDiff = ?TAB_STRUCT_SZ,
- {A0+TabDiff, B0+TabDiff, C0+TabDiff, D0+TabDiff}.
+ {TabSz, EstSz} = erts_debug:get_internal_state('DbTable_words'),
+ HTabSz = TabSz + EstCnt*EstSz,
+ {A0+TabSz, B0+HTabSz, C0+HTabSz, D0+HTabSz}.
%% Misc. whitebox tests
t_whitebox(Config) when is_list(Config) ->
@@ -1908,7 +1902,7 @@ evil_counter(I,Opts) ->
end,
Start = Start0 + rand:uniform(100000),
ets:insert(T, {dracula,Start}),
- Iter = 40000,
+ Iter = 40000 div syrup_factor(),
End = Start + Iter,
End = evil_counter_1(Iter, T),
ets:delete(T).
@@ -3302,7 +3296,8 @@ evil_delete_owner(Name, Flags, Data, Fix) ->
exit_large_table_owner(Config) when is_list(Config) ->
%%Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 500000)],
- FEData = fun(Do) -> repeat_while(fun(500000) -> {false,ok};
+ Laps = 500000 div syrup_factor(),
+ FEData = fun(Do) -> repeat_while(fun(I) when I =:= Laps -> {false,ok};
(I) -> Do({erlang:phash2(I, 16#ffffff),I}),
{true, I+1}
end, 1)
@@ -3318,7 +3313,8 @@ exit_large_table_owner_do(Opts,{FEData,Config}) ->
exit_many_large_table_owner(Config) when is_list(Config) ->
ct:timetrap({minutes,30}), %% valgrind needs a lot
%%Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 500000)],
- FEData = fun(Do) -> repeat_while(fun(500000) -> {false,ok};
+ Laps = 500000 div syrup_factor(),
+ FEData = fun(Do) -> repeat_while(fun(I) when I =:= Laps -> {false,ok};
(I) -> Do({erlang:phash2(I, 16#ffffff),I}),
{true, I+1}
end, 1)
@@ -4271,7 +4267,8 @@ heavy_lookup_element_do(Opts) ->
Tab = ets_new(foobar_table, [set, protected, {keypos, 2} | Opts]),
ok = fill_tab2(Tab, 0, 7000),
%% lookup ALL elements 50 times
- _ = [do_lookup_element(Tab, 6999, 1) || _ <- lists:seq(1, 50)],
+ Laps = 50 div syrup_factor(),
+ _ = [do_lookup_element(Tab, 6999, 1) || _ <- lists:seq(1, Laps)],
true = ets:delete(Tab),
verify_etsmem(EtsMem).
@@ -4295,6 +4292,7 @@ heavy_concurrent(Config) when is_list(Config) ->
do_heavy_concurrent(Opts) ->
Size = 10000,
+ Laps = 10000 div syrup_factor(),
EtsMem = etsmem(),
Tab = ets_new(blupp, [set, public, {keypos, 2} | Opts]),
ok = fill_tab2(Tab, 0, Size),
@@ -4302,7 +4300,7 @@ do_heavy_concurrent(Opts) ->
fun (N) ->
my_spawn_link(
fun () ->
- do_heavy_concurrent_proc(Tab, Size, N)
+ do_heavy_concurrent_proc(Tab, Laps, N)
end)
end,
lists:seq(1, 500)),
@@ -4448,15 +4446,15 @@ build_table2(L1,L2,Num) ->
T.
time_match_object(Tab,Match, Res) ->
- T1 = erlang:monotonic_time(micro_seconds),
+ T1 = erlang:monotonic_time(microsecond),
Res = ets:match_object(Tab,Match),
- T2 = erlang:monotonic_time(micro_seconds),
+ T2 = erlang:monotonic_time(microsecond),
T2 - T1.
time_match(Tab,Match) ->
- T1 = erlang:monotonic_time(micro_seconds),
+ T1 = erlang:monotonic_time(microsecond),
ets:match(Tab,Match),
- T2 = erlang:monotonic_time(micro_seconds),
+ T2 = erlang:monotonic_time(microsecond),
T2 - T1.
seventyfive_percent_success(_,S,Fa,0) ->
@@ -5363,12 +5361,12 @@ verify_table_load(T) ->
Stats = ets:info(T,stats),
{Buckets,AvgLen,StdDev,ExpSD,_MinLen,_MaxLen,_} = Stats,
ok = if
- AvgLen > 7 ->
+ AvgLen > 1.2 ->
io:format("Table overloaded: Stats=~p\n~p\n",
[Stats, ets:info(T)]),
false;
- Buckets>256, AvgLen < 6 ->
+ Buckets>256, AvgLen < 0.47 ->
io:format("Table underloaded: Stats=~p\n~p\n",
[Stats, ets:info(T)]),
false;
@@ -5442,7 +5440,8 @@ smp_select_delete(Config) when is_list(Config) ->
Eq+1
end,
0, TotCnts),
- verify_table_load(T),
+ %% May fail as select_delete does not shrink table (enough)
+ %%verify_table_load(T),
LeftInTab = ets:select_delete(T, [{{'$1','$1'}, [], [true]}]),
0 = ets:info(T,size),
false = ets:info(T,fixed),
@@ -5718,27 +5717,45 @@ etsmem() ->
{Bl0+Bl,BlSz0+BlSz}
end, {0,0}, CS)
end},
- {Mem,AllTabs}.
+ {Mem,AllTabs, erts_debug:get_internal_state('DbTable_meta')}.
-verify_etsmem({MemInfo,AllTabs}) ->
+verify_etsmem(EtsMem) ->
wait_for_test_procs(),
+ verify_etsmem(EtsMem, false).
+
+verify_etsmem({MemInfo,AllTabs,MetaState}=EtsMem, Adjusted) ->
case etsmem() of
- {MemInfo,_} ->
+ {MemInfo,_,_} ->
io:format("Ets mem info: ~p", [MemInfo]),
case MemInfo of
{ErlMem,EtsAlloc} when ErlMem == notsup; EtsAlloc == undefined ->
%% Use 'erl +Mea max' to do more complete memory leak testing.
{comment,"Incomplete or no mem leak testing"};
_ ->
- ok
+ case Adjusted of
+ true ->
+ {comment, "Meta state adjusted"};
+ false ->
+ ok
+ end
end;
- {MemInfo2, AllTabs2} ->
+
+ {MemInfo2, AllTabs2, MetaState2} ->
io:format("Expected: ~p", [MemInfo]),
io:format("Actual: ~p", [MemInfo2]),
io:format("Changed tables before: ~p\n",[AllTabs -- AllTabs2]),
io:format("Changed tables after: ~p\n", [AllTabs2 -- AllTabs]),
- ets_test_spawn_logger ! {failed_memcheck, get('__ETS_TEST_CASE__')},
- {comment, "Failed memory check"}
+ io:format("Meta state before: ~p\n", [MetaState]),
+ io:format("Meta state after: ~p\n", [MetaState2]),
+ case {MetaState =:= MetaState2, Adjusted} of
+ {false, false} ->
+ io:format("Adjust meta state and retry...\n\n",[]),
+ {ok,ok} = erts_debug:set_internal_state('DbTable_meta', MetaState),
+ verify_etsmem(EtsMem, true);
+ _ ->
+ ets_test_spawn_logger ! {failed_memcheck, get('__ETS_TEST_CASE__')},
+ {comment, "Failed memory check"}
+ end
end.
@@ -6259,5 +6276,11 @@ do_tc(Do, Report) ->
T1 = erlang:monotonic_time(),
Do(),
T2 = erlang:monotonic_time(),
- Elapsed = erlang:convert_time_unit(T2 - T1, native, milli_seconds),
+ Elapsed = erlang:convert_time_unit(T2 - T1, native, millisecond),
Report(Elapsed).
+
+syrup_factor() ->
+ case erlang:system_info(build_type) of
+ valgrind -> 20;
+ _ -> 1
+ end.
diff --git a/lib/stdlib/test/io_proto_SUITE.erl b/lib/stdlib/test/io_proto_SUITE.erl
index 1e286a9306..db321d7490 100644
--- a/lib/stdlib/test/io_proto_SUITE.erl
+++ b/lib/stdlib/test/io_proto_SUITE.erl
@@ -1715,7 +1715,7 @@ toerl_loop(Port,Acc) ->
end.
millistamp() ->
- erlang:monotonic_time(milli_seconds).
+ erlang:monotonic_time(millisecond).
get_data_within(Port, X, Acc) when X =< 0 ->
?dbg({get_data_within, X, Acc, ?LINE}),
diff --git a/lib/stdlib/test/math_SUITE.erl b/lib/stdlib/test/math_SUITE.erl
new file mode 100644
index 0000000000..2b29e44228
--- /dev/null
+++ b/lib/stdlib/test/math_SUITE.erl
@@ -0,0 +1,92 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2007-2016. 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.
+%% You may obtain a copy of the License at
+%%
+%% http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+
+-module(math_SUITE).
+
+-include_lib("common_test/include/ct.hrl").
+
+%% Test server specific exports
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2,
+ init_per_testcase/2, end_per_testcase/2]).
+
+%% Test cases
+-export([floor_ceil/1]).
+
+
+suite() ->
+ [{ct_hooks,[ts_install_cth]},
+ {timetrap,{minutes,1}}].
+
+all() ->
+ [floor_ceil].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
+
+init_per_testcase(_Case, Config) ->
+ Config.
+
+end_per_testcase(_Case, _Config) ->
+ ok.
+
+floor_ceil(_Config) ->
+ MinusZero = 0.0/(-1.0),
+ -43.0 = do_floor_ceil(-42.1),
+ -43.0 = do_floor_ceil(-42.7),
+ 0.0 = do_floor_ceil(MinusZero),
+ 10.0 = do_floor_ceil(10.1),
+ 10.0 = do_floor_ceil(10.9),
+
+ -533.0 = do_floor_ceil(-533.0),
+ 453555.0 = do_floor_ceil(453555.0),
+
+ -58.0 = do_floor_ceil(-58),
+ 777.0 = do_floor_ceil(777),
+
+ ok.
+
+do_floor_ceil(Val) ->
+ Floor = math:floor(Val),
+ Ceil = math:ceil(Val),
+
+ true = is_float(Floor),
+ true = is_float(Ceil),
+
+ if
+ Floor =:= Ceil ->
+ Floor;
+ true ->
+ 1.0 = Ceil - Floor,
+ Floor
+ end.
diff --git a/lib/stdlib/test/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl
index 2bd940020c..8c7d5a5fcf 100644
--- a/lib/stdlib/test/qlc_SUITE.erl
+++ b/lib/stdlib/test/qlc_SUITE.erl
@@ -58,7 +58,7 @@
-export([
badarg/1, nested_qlc/1, unused_var/1, lc/1, fun_clauses/1,
filter_var/1, single/1, exported_var/1, generator_vars/1,
- nomatch/1, errors/1, pattern/1,
+ nomatch/1, errors/1, pattern/1, overridden_bif/1,
eval/1, cursor/1, fold/1, eval_unique/1, eval_cache/1, append/1,
evaluator/1, string_to_handle/1, table/1, process_dies/1,
@@ -126,7 +126,7 @@ groups() ->
[{parse_transform, [],
[badarg, nested_qlc, unused_var, lc, fun_clauses,
filter_var, single, exported_var, generator_vars,
- nomatch, errors, pattern]},
+ nomatch, errors, pattern, overridden_bif]},
{evaluation, [],
[eval, cursor, fold, eval_unique, eval_cache, append,
evaluator, string_to_handle, table, process_dies, sort,
@@ -468,6 +468,23 @@ pattern(Config) when is_list(Config) ->
-record(k, {t,v}).\n">>, Ts),
ok.
+%% Override a guard BIF with an imported or local function.
+overridden_bif(Config) ->
+ Ts = [
+ <<"[2] = qlc:e(qlc:q([P || P <- [1,2,3], port(P)])),
+ [10] = qlc:e(qlc:q([P || P <- [0,9,10,11,12],
+ (is_reference(P) andalso P > 5)])),
+ Empty = gb_sets:empty(), Single = gb_sets:singleton(42),
+ GbSets = [Empty,Single],
+ [Single] = qlc:e(qlc:q([S || S <- GbSets, size(S) =/= 0]))
+ ">>
+ ],
+ run(Config, "-import(gb_sets, [size/1]).
+ -compile({no_auto_import, [size/1, is_reference/1]}).
+ port(N) -> N rem 2 =:= 0.
+ is_reference(N) -> N rem 10 =:= 0.\n", Ts),
+ ok.
+
%% eval/2
eval(Config) when is_list(Config) ->
diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl
index c409a6949b..07eb6772db 100644
--- a/lib/stdlib/test/shell_SUITE.erl
+++ b/lib/stdlib/test/shell_SUITE.erl
@@ -573,7 +573,7 @@ otp_5327(Config) when is_list(Config) ->
(catch evaluate(<<"<<32/unit:8>>.">>, [])),
ok.
-%% OTP-5435. sys_pre_expand not in the path.
+%% OTP-5435. compiler application not in the path.
otp_5435(Config) when is_list(Config) ->
true = <<103133:64/float>> =:=
evaluate(<<"<<103133:64/float>> = <<103133:64/float>>.">>, []),
@@ -591,8 +591,9 @@ start_node(Name) ->
otp_5435_2() ->
true = code:del_path(compiler),
- %% sys_pre_expand can no longer be found
- %% OTP-5876. But erl_expand_records can!
+ %% Make sure record evaluation is not dependent on the compiler
+ %% application being in the path.
+ %% OTP-5876.
[{attribute,_,record,{bar,_}},ok] =
scan(<<"rd(foo,{bar}),
rd(bar,{foo = (#foo{})#foo.bar}),
diff --git a/lib/stdlib/test/timer_SUITE.erl b/lib/stdlib/test/timer_SUITE.erl
index 5fc95b16a6..9062cbae80 100644
--- a/lib/stdlib/test/timer_SUITE.erl
+++ b/lib/stdlib/test/timer_SUITE.erl
@@ -353,7 +353,7 @@ res_combine({error,Es}, [{error,E}|T]) ->
system_time() ->
- erlang:monotonic_time(milli_seconds).
+ erlang:monotonic_time(millisecond).
%% ------------------------------------------------------- %%
diff --git a/lib/stdlib/test/timer_simple_SUITE.erl b/lib/stdlib/test/timer_simple_SUITE.erl
index ff5116b8b6..1a582ae95a 100644
--- a/lib/stdlib/test/timer_simple_SUITE.erl
+++ b/lib/stdlib/test/timer_simple_SUITE.erl
@@ -457,7 +457,7 @@ append([],X) ->
X.
system_time() ->
- erlang:monotonic_time(micro_seconds).
+ erlang:monotonic_time(microsecond).
%% ------------------------------------------------------- %%