diff options
author | Sverker Eriksson <[email protected]> | 2016-10-26 17:37:35 +0200 |
---|---|---|
committer | Sverker Eriksson <[email protected]> | 2016-10-26 17:37:35 +0200 |
commit | 42b9881d075344344a8c78026e282b40fa707a0c (patch) | |
tree | d9755627cee82a99eff6755c8f092ed45dd7a71e /lib/stdlib/src | |
parent | 6408400fc1ca9609169f6a0450f1c4671aced91c (diff) | |
parent | 1302b09c4aa0f944bdc0e3beeebb2cf84cc06c89 (diff) | |
download | otp-42b9881d075344344a8c78026e282b40fa707a0c.tar.gz otp-42b9881d075344344a8c78026e282b40fa707a0c.tar.bz2 otp-42b9881d075344344a8c78026e282b40fa707a0c.zip |
Merge branch 'master' into sverker/hipe-fun-purge
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r-- | lib/stdlib/src/dets.erl | 2 | ||||
-rw-r--r-- | lib/stdlib/src/edlin_expand.erl | 2 | ||||
-rw-r--r-- | lib/stdlib/src/erl_expand_records.erl | 95 | ||||
-rw-r--r-- | lib/stdlib/src/erl_internal.erl | 118 | ||||
-rw-r--r-- | lib/stdlib/src/erl_lint.erl | 165 | ||||
-rw-r--r-- | lib/stdlib/src/erl_parse.yrl | 13 | ||||
-rw-r--r-- | lib/stdlib/src/eval_bits.erl | 14 | ||||
-rw-r--r-- | lib/stdlib/src/gen_statem.erl | 1051 | ||||
-rw-r--r-- | lib/stdlib/src/math.erl | 13 | ||||
-rw-r--r-- | lib/stdlib/src/ms_transform.erl | 2 | ||||
-rw-r--r-- | lib/stdlib/src/otp_internal.erl | 2 | ||||
-rw-r--r-- | lib/stdlib/src/qlc_pt.erl | 55 | ||||
-rw-r--r-- | lib/stdlib/src/stdlib.app.src | 2 | ||||
-rw-r--r-- | lib/stdlib/src/stdlib.appup.src | 4 | ||||
-rw-r--r-- | lib/stdlib/src/supervisor.erl | 4 | ||||
-rw-r--r-- | lib/stdlib/src/timer.erl | 6 |
16 files changed, 994 insertions, 554 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/edlin_expand.erl b/lib/stdlib/src/edlin_expand.erl index ec64470461..5f821caef0 100644 --- a/lib/stdlib/src/edlin_expand.erl +++ b/lib/stdlib/src/edlin_expand.erl @@ -118,7 +118,7 @@ format_col([A|T], Width, Len, Acc0) -> {H1, _} -> H1; H2 -> H2 end, - Acc = [io_lib:format("~-*s", [Width,H]) | Acc0], + Acc = [io_lib:format("~-*ts", [Width,H]) | Acc0], format_col(T, Width, Len+Width, Acc); format_col([], _, _, Acc) -> lists:reverse(Acc, "\n"). 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/gen_statem.erl b/lib/stdlib/src/gen_statem.erl index 3b3477b282..17d1ebecec 100644 --- a/lib/stdlib/src/gen_statem.erl +++ b/lib/stdlib/src/gen_statem.erl @@ -44,15 +44,20 @@ -export( [wakeup_from_hibernate/3]). -%% Type exports for templates +%% Type exports for templates and callback modules -export_type( [event_type/0, - callback_mode/0, + init_result/0, + callback_mode_result/0, state_function_result/0, handle_event_result/0, + state_enter_result/1, + event_handler_result/1, + reply_action/0, + enter_action/0, action/0]). -%% Fix problem for doc build +%% Type that is exported just to be documented -export_type([transition_option/0]). %%%========================================================================== @@ -63,7 +68,7 @@ {To :: pid(), Tag :: term()}. % Reply-to specifier for call -type state() :: - state_name() | % For StateName/3 callback functios + state_name() | % For StateName/3 callback functions term(). % For handle_event/4 callback function -type state_name() :: atom(). @@ -72,9 +77,12 @@ -type event_type() :: {'call',From :: from()} | 'cast' | - 'info' | 'timeout' | 'internal'. + 'info' | 'timeout' | 'state_timeout' | 'internal'. +-type callback_mode_result() :: + callback_mode() | [callback_mode() | state_enter()]. -type callback_mode() :: 'state_functions' | 'handle_event_function'. +-type state_enter() :: 'state_enter'. -type transition_option() :: postpone() | hibernate() | event_timeout(). @@ -89,6 +97,10 @@ %% Generate a ('timeout', EventContent, ...) event after Time %% unless some other event is delivered Time :: timeout(). +-type state_timeout() :: + %% Generate a ('state_timeout', EventContent, ...) event after Time + %% unless the state is changed + Time :: timeout(). -type action() :: %% During a state change: @@ -108,44 +120,67 @@ 'postpone' | % Set the postpone option {'postpone', Postpone :: postpone()} | %% + %% All 'next_event' events are kept in a list and then + %% inserted at state changes so the first in the + %% action() list is the first to be delivered. + {'next_event', % Insert event as the next to handle + EventType :: event_type(), + EventContent :: term()} | + enter_action(). +-type enter_action() :: 'hibernate' | % Set the hibernate option {'hibernate', Hibernate :: hibernate()} | %% (Timeout :: event_timeout()) | % {timeout,Timeout} - {'timeout', % Set the event timeout option + {'timeout', % Set the event_timeout option Time :: event_timeout(), EventContent :: term()} | + {'state_timeout', % Set the state_timeout option + Time :: state_timeout(), EventContent :: term()} | %% - reply_action() | - %% - %% All 'next_event' events are kept in a list and then - %% inserted at state changes so the first in the - %% action() list is the first to be delivered. - {'next_event', % Insert event as the next to handle - EventType :: event_type(), - EventContent :: term()}. + reply_action(). -type reply_action() :: {'reply', % Reply to a caller From :: from(), Reply :: term()}. +-type init_result() :: + {ok, state(), data()} | + {ok, state(), data(), [action()] | action()} | + 'ignore' | + {'stop', Reason :: term()}. + +%% Old, not advertised -type state_function_result() :: - {'next_state', % {next_state,NextStateName,NewData,[]} - NextStateName :: state_name(), + event_handler_result(state_name()). +-type handle_event_result() :: + event_handler_result(state()). +%% +-type state_enter_result(StateType) :: + {'next_state', % {next_state,NextState,NewData,[]} + State :: StateType, NewData :: data()} | {'next_state', % State transition, maybe to the same state - NextStateName :: state_name(), + State :: StateType, NewData :: data(), - Actions :: [action()] | action()} | - common_state_callback_result(). --type handle_event_result() :: + Actions :: [enter_action()] | enter_action()} | + state_callback_result(enter_action()). +-type event_handler_result(StateType) :: {'next_state', % {next_state,NextState,NewData,[]} - NextState :: state(), + NextState :: StateType, NewData :: data()} | {'next_state', % State transition, maybe to the same state - NextState :: state(), + NextState :: StateType, NewData :: data(), Actions :: [action()] | action()} | - common_state_callback_result(). --type common_state_callback_result() :: + state_callback_result(action()). +-type state_callback_result(ActionType) :: + {'keep_state', % {keep_state,NewData,[]} + NewData :: data()} | + {'keep_state', % Keep state, change data + NewData :: data(), + Actions :: [ActionType] | ActionType} | + 'keep_state_and_data' | % {keep_state_and_data,[]} + {'keep_state_and_data', % Keep state and data -> only actions + Actions :: [ActionType] | ActionType} | 'stop' | % {stop,normal} {'stop', % Stop the server Reason :: term()} | @@ -158,32 +193,20 @@ {'stop_and_reply', % Reply then stop the server Reason :: term(), Replies :: [reply_action()] | reply_action(), - NewData :: data()} | - {'keep_state', % {keep_state,NewData,[]} - NewData :: data()} | - {'keep_state', % Keep state, change data - NewData :: data(), - Actions :: [action()] | action()} | - 'keep_state_and_data' | % {keep_state_and_data,[]} - {'keep_state_and_data', % Keep state and data -> only actions - Actions :: [action()] | action()}. + NewData :: data()}. %% The state machine init function. It is called only once and %% the server is not running until this function has returned %% an {ok, ...} tuple. Thereafter the state callbacks are called %% for all events to this server. --callback init(Args :: term()) -> - {ok, state(), data()} | - {ok, state(), data(), [action()] | action()} | - 'ignore' | - {'stop', Reason :: term()}. +-callback init(Args :: term()) -> init_result(). %% This callback shall return the callback mode of the callback module. %% %% It is called once after init/0 and code_change/4 but before %% the first state callback StateName/3 or handle_event/4. --callback callback_mode() -> callback_mode(). +-callback callback_mode() -> callback_mode_result(). %% Example state callback for StateName = 'state_name' %% when callback_mode() =:= state_functions. @@ -194,19 +217,28 @@ %% StateName/3 callbacks and terminate/3, so the state name %% 'terminate' is unusable in this mode. -callback state_name( - event_type(), + 'enter', + OldStateName :: state_name(), + Data :: data()) -> + state_enter_result('state_name'); + (event_type(), EventContent :: term(), Data :: data()) -> - state_function_result(). + event_handler_result(state_name()). %% %% State callback for all states %% when callback_mode() =:= handle_event_function. -callback handle_event( - event_type(), + 'enter', + OldState :: state(), + State :: state(), % Current state + Data :: data()) -> + state_enter_result(state()); + (event_type(), EventContent :: term(), State :: state(), % Current state Data :: data()) -> - handle_event_result(). + event_handler_result(state()). %% Clean up before the server terminates. -callback terminate( @@ -385,53 +417,79 @@ call(ServerRef, Request) -> -spec call( ServerRef :: server_ref(), Request :: term(), - Timeout :: timeout()) -> + Timeout :: + timeout() | + {'clean_timeout',T :: timeout()} | + {'dirty_timeout',T :: timeout()}) -> Reply :: term(). -call(ServerRef, Request, infinity) -> - try gen:call(ServerRef, '$gen_call', Request, infinity) of - {ok,Reply} -> - Reply - catch - Class:Reason -> - erlang:raise( - Class, - {Reason,{?MODULE,call,[ServerRef,Request,infinity]}}, - erlang:get_stacktrace()) - end; call(ServerRef, Request, Timeout) -> - %% Call server through proxy process to dodge any late reply - Ref = make_ref(), - Self = self(), - Pid = spawn( - fun () -> - Self ! - try gen:call( - ServerRef, '$gen_call', Request, Timeout) of - Result -> - {Ref,Result} - catch Class:Reason -> - {Ref,Class,Reason,erlang:get_stacktrace()} - end - end), - Mref = monitor(process, Pid), - receive - {Ref,Result} -> - demonitor(Mref, [flush]), - case Result of + case parse_timeout(Timeout) of + {dirty_timeout,T} -> + try gen:call(ServerRef, '$gen_call', Request, T) of {ok,Reply} -> Reply + catch + Class:Reason -> + erlang:raise( + Class, + {Reason,{?MODULE,call,[ServerRef,Request,Timeout]}}, + erlang:get_stacktrace()) + end; + {clean_timeout,T} -> + %% Call server through proxy process to dodge any late reply + Ref = make_ref(), + Self = self(), + Pid = spawn( + fun () -> + Self ! + try gen:call( + ServerRef, '$gen_call', Request, T) of + Result -> + {Ref,Result} + catch Class:Reason -> + {Ref,Class,Reason, + erlang:get_stacktrace()} + end + end), + Mref = monitor(process, Pid), + receive + {Ref,Result} -> + demonitor(Mref, [flush]), + case Result of + {ok,Reply} -> + Reply + end; + {Ref,Class,Reason,Stacktrace} -> + demonitor(Mref, [flush]), + erlang:raise( + Class, + {Reason,{?MODULE,call,[ServerRef,Request,Timeout]}}, + Stacktrace); + {'DOWN',Mref,_,_,Reason} -> + %% There is a theoretical possibility that the + %% proxy process gets killed between try--of and ! + %% so this clause is in case of that + exit(Reason) end; - {Ref,Class,Reason,Stacktrace} -> - demonitor(Mref, [flush]), - erlang:raise( - Class, - {Reason,{?MODULE,call,[ServerRef,Request,Timeout]}}, - Stacktrace); - {'DOWN',Mref,_,_,Reason} -> - %% There is a theoretical possibility that the - %% proxy process gets killed between try--of and ! - %% so this clause is in case of that - exit(Reason) + Error when is_atom(Error) -> + erlang:error(Error, [ServerRef,Request,Timeout]) + end. + +parse_timeout(Timeout) -> + case Timeout of + {clean_timeout,infinity} -> + {dirty_timeout,infinity}; + {clean_timeout,_} -> + Timeout; + {dirty_timeout,_} -> + Timeout; + {_,_} -> + %% Be nice and throw a badarg for speling errors + badarg; + infinity -> + {dirty_timeout,infinity}; + T -> + {clean_timeout,T} end. %% Reply from a state machine callback to whom awaits in call/2 @@ -517,8 +575,9 @@ enter(Module, Opts, State, Data, Server, Actions, Parent) -> %% The values should already have been type checked Name = gen:get_proc_name(Server), Debug = gen:debug_options(Name, Opts), - P = Events = [], - Event = {internal,initial_state}, + Events = [], + P = [], + Event = {internal,init_state}, %% We enforce {postpone,false} to ensure that %% our fake Event gets discarded, thought it might get logged NewActions = @@ -530,19 +589,31 @@ enter(Module, Opts, State, Data, Server, Actions, Parent) -> end, S = #{ callback_mode => undefined, + state_enter => false, module => Module, name => Name, - %% All fields below will be replaced according to the arguments to - %% loop_event_actions/10 when it finally loops back to loop/3 state => State, data => Data, postponed => P, - hibernate => false, - timer => undefined}, + %% The rest of the fields are set from to the arguments to + %% loop_event_actions/9 when it finally loops back to loop/3 + %% in loop_events_done/9 + %% + %% Marker for initial state, cleared immediately when used + init_state => true + }, NewDebug = sys_debug(Debug, S, State, {enter,Event,State}), - loop_event_actions( - Parent, NewDebug, S, Events, - State, Data, P, Event, State, NewActions). + case call_callback_mode(S) of + {ok,NewS} -> + StateTimer = undefined, + loop_event_actions( + Parent, NewDebug, NewS, StateTimer, + Events, Event, State, Data, NewActions); + {Class,Reason,Stacktrace} -> + terminate( + Class, Reason, Stacktrace, + NewDebug, S, [Event|Events]) + end. %%%========================================================================== %%% gen callbacks @@ -563,7 +634,9 @@ init_it(Starter, Parent, ServerRef, Module, Args, Opts) -> proc_lib:init_ack(Starter, {error,Reason}), error_info( Class, Reason, Stacktrace, - #{name => Name, callback_mode => undefined}, + #{name => Name, + callback_mode => undefined, + state_enter => false}, [], [], undefined), erlang:raise(Class, Reason, Stacktrace) end. @@ -594,7 +667,9 @@ init_result(Starter, Parent, ServerRef, Module, Result, Opts) -> proc_lib:init_ack(Starter, {error,Error}), error_info( error, Error, ?STACKTRACE(), - #{name => Name, callback_mode => undefined}, + #{name => Name, + callback_mode => undefined, + state_enter => false}, [], [], undefined), exit(Error) end. @@ -605,12 +680,10 @@ init_result(Starter, Parent, ServerRef, Module, Result, Opts) -> system_continue(Parent, Debug, S) -> loop(Parent, Debug, S). -system_terminate( - Reason, _Parent, Debug, - #{state := State, data := Data, postponed := P} = S) -> +system_terminate(Reason, _Parent, Debug, S) -> terminate( exit, Reason, ?STACKTRACE(), - Debug, S, [], State, Data, P). + Debug, S, []). system_code_change( #{module := Module, @@ -647,7 +720,7 @@ system_replace_state( format_status( Opt, [PDict,SysState,Parent,Debug, - #{name := Name, postponed := P, state := State, data := Data} = S]) -> + #{name := Name, postponed := P} = S]) -> Header = gen:format_status_header("Status for state machine", Name), Log = sys:get_debug(log, Debug, []), [{header,Header}, @@ -656,7 +729,7 @@ format_status( {"Parent",Parent}, {"Logged Events",Log}, {"Postponed",P}]} | - case format_status(Opt, PDict, S, State, Data) of + case format_status(Opt, PDict, S) of L when is_list(L) -> L; T -> [T] end]. @@ -732,7 +805,8 @@ loop(Parent, Debug, #{hibernate := Hibernate} = S) -> end. %% Entry point for wakeup_from_hibernate/3 -loop_receive(Parent, Debug, #{timer := Timer} = S) -> +loop_receive( + Parent, Debug, #{timer := Timer, state_timer := StateTimer} = S) -> receive Msg -> case Msg of @@ -743,34 +817,23 @@ loop_receive(Parent, Debug, #{timer := Timer} = S) -> sys:handle_system_msg( Req, Pid, Parent, ?MODULE, Debug, S, Hibernate); {'EXIT',Parent,Reason} = EXIT -> - #{state := State, data := Data, postponed := P} = S, %% EXIT is not a 2-tuple and therefore %% not an event and has no event_type(), %% but this will stand out in the crash report... terminate( - exit, Reason, ?STACKTRACE(), - Debug, S, [EXIT], State, Data, P); - {timeout,Timer,Content} when Timer =/= undefined -> + exit, Reason, ?STACKTRACE(), Debug, S, [EXIT]); + {timeout,Timer,Content} + when Timer =/= undefined -> loop_receive_result( - Parent, Debug, S, {timeout,Content}); + Parent, Debug, S, StateTimer, + {timeout,Content}); + {timeout,StateTimer,Content} + when StateTimer =/= undefined -> + loop_receive_result( + Parent, Debug, S, undefined, + {state_timeout,Content}); _ -> - %% Cancel Timer if running - case Timer of - undefined -> - ok; - _ -> - case erlang:cancel_timer(Timer) of - TimeLeft when is_integer(TimeLeft) -> - ok; - false -> - receive - {timeout,Timer,_} -> - ok - after 0 -> - ok - end - end - end, + cancel_timer(Timer), Event = case Msg of {'$gen_call',From,Request} -> @@ -780,112 +843,185 @@ loop_receive(Parent, Debug, #{timer := Timer} = S) -> _ -> {info,Msg} end, - loop_receive_result(Parent, Debug, S, Event) + loop_receive_result( + Parent, Debug, S, StateTimer, Event) end end. -loop_receive_result( - Parent, Debug, - #{state := State, - data := Data, - postponed := P} = S, - Event) -> - %% The engine state map S is now dismantled - %% and will not be restored until we return to loop/3. - %% - %% The fields 'callback_mode', 'module', and 'name' are still valid. - %% The fields 'state', 'data', and 'postponed' are held in arguments. - %% The fields 'timer' and 'hibernate' will be recalculated. +loop_receive_result(Parent, Debug, #{state := State} = S, StateTimer, Event) -> + %% The fields 'timer', 'state_timer' and 'hibernate' + %% are now invalid in state map S - they will be recalculated + %% and restored when we return to loop/3 %% NewDebug = sys_debug(Debug, S, State, {in,Event}), %% Here the queue of not yet handled events is created Events = [], Hibernate = false, - loop_event( - Parent, NewDebug, S, Events, State, Data, P, Event, Hibernate). + loop_event(Parent, NewDebug, S, StateTimer, Events, Event, Hibernate). %% Process the event queue, or if it is empty %% loop back to loop/3 to receive a new event loop_events( - Parent, Debug, S, [Event|Events], - State, Data, P, Hibernate, _Timeout) -> + Parent, Debug, S, StateTimeout, + [Event|Events], _Timeout, State, Data, P, Hibernate) -> %% - %% If there was a state timer requested we just ignore that + %% If there was an event timer requested we just ignore that %% since we have events to handle which cancels the timer loop_event( - Parent, Debug, S, Events, State, Data, P, Event, Hibernate); + Parent, Debug, S, StateTimeout, + Events, Event, State, Data, P, Hibernate); loop_events( - Parent, Debug, S, [], - State, Data, P, Hibernate, Timeout) -> + Parent, Debug, S, {state_timeout,Time,EventContent}, + [] = Events, Timeout, State, Data, P, Hibernate) -> + if + Time =:= 0 -> + %% Simulate an immediate timeout + %% so we do not get the timeout message + %% after any received event + %% + %% This faked event will cancel + %& any not yet started event timer + Event = {state_timeout,EventContent}, + StateTimer = undefined, + loop_event( + Parent, Debug, S, StateTimer, + Events, Event, State, Data, P, Hibernate); + true -> + StateTimer = erlang:start_timer(Time, self(), EventContent), + loop_events( + Parent, Debug, S, StateTimer, + Events, Timeout, State, Data, P, Hibernate) + end; +loop_events( + Parent, Debug, S, StateTimer, + [] = Events, Timeout, State, Data, P, Hibernate) -> case Timeout of {timeout,0,EventContent} -> - %% Immediate timeout - simulate it + %% Simulate an immediate timeout %% so we do not get the timeout message %% after any received event + %% + Event = {timeout,EventContent}, loop_event( - Parent, Debug, S, [], - State, Data, P, {timeout,EventContent}, Hibernate); + Parent, Debug, S, StateTimer, + Events, Event, State, Data, P, Hibernate); {timeout,Time,EventContent} -> - %% Actually start a timer Timer = erlang:start_timer(Time, self(), EventContent), loop_events_done( - Parent, Debug, S, Timer, State, Data, P, Hibernate); + Parent, Debug, S, StateTimer, + State, Data, P, Hibernate, Timer); undefined -> - %% No state timeout has been requested + %% No event timeout has been requested Timer = undefined, loop_events_done( - Parent, Debug, S, Timer, State, Data, P, Hibernate) + Parent, Debug, S, StateTimer, + State, Data, P, Hibernate, Timer) end. -%% -loop_events_done(Parent, Debug, S, Timer, State, Data, P, Hibernate) -> + +%% Back to the top +loop_events_done( + Parent, Debug, S, StateTimer, + State, Data, P, Hibernate, Timer) -> NewS = S#{ state := State, data := Data, postponed := P, - hibernate := Hibernate, - timer := Timer}, + hibernate => Hibernate, + timer => Timer, + state_timer => StateTimer}, loop(Parent, Debug, NewS). -loop_event( - Parent, Debug, + + +call_callback_mode(#{module := Module} = S) -> + try Module:callback_mode() of + CallbackMode -> + callback_mode_result(S, CallbackMode) + catch + CallbackMode -> + callback_mode_result(S, CallbackMode); + error:undef -> + %% Process undef to check for the simple mistake + %% of calling a nonexistent state function + %% to make the undef more precise + case erlang:get_stacktrace() of + [{Module,callback_mode,[]=Args,_} + |Stacktrace] -> + {error, + {undef_callback,{Module,callback_mode,Args}}, + Stacktrace}; + Stacktrace -> + {error,undef,Stacktrace} + end; + Class:Reason -> + {Class,Reason,erlang:get_stacktrace()} + end. + +callback_mode_result(S, CallbackMode) -> + case + parse_callback_mode( + if + is_atom(CallbackMode) -> + [CallbackMode]; + true -> + CallbackMode + end, undefined, false) + of + {undefined,_} -> + {error, + {bad_return_from_callback_mode,CallbackMode}, + ?STACKTRACE()}; + {CBMode,StateEnter} -> + {ok, + S#{ + callback_mode := CBMode, + state_enter := StateEnter}} + end. + +parse_callback_mode([], CBMode, StateEnter) -> + {CBMode,StateEnter}; +parse_callback_mode([H|T], CBMode, StateEnter) -> + case callback_mode(H) of + true -> + parse_callback_mode(T, H, StateEnter); + false -> + case H of + state_enter -> + parse_callback_mode(T, CBMode, true); + _ -> + {undefined,StateEnter} + end + end; +parse_callback_mode(_, _CBMode, StateEnter) -> + {undefined,StateEnter}. + +call_state_function( + #{callback_mode := undefined} = S, + Type, Content, State, Data) -> + case call_callback_mode(S) of + {ok,NewS} -> + call_state_function(NewS, Type, Content, State, Data); + Error -> + Error + end; +call_state_function( #{callback_mode := CallbackMode, module := Module} = S, - Events, - State, Data, P, {Type,Content} = Event, Hibernate) -> - %% - %% If Hibernate is true here it can only be - %% because it was set from an event action - %% and we did not go into hibernation since there - %% were events in queue, so we do what the user - %% might depend on i.e collect garbage which - %% would have happened if we actually hibernated - %% and immediately was awakened - Hibernate andalso garbage_collect(), - %% + Type, Content, State, Data) -> try case CallbackMode of - undefined -> - Module:callback_mode(); state_functions -> erlang:apply(Module, State, [Type,Content,Data]); handle_event_function -> Module:handle_event(Type, Content, State, Data) end of - Result when CallbackMode =:= undefined -> - loop_event_callback_mode( - Parent, Debug, S, Events, State, Data, P, Event, Result); Result -> - loop_event_result( - Parent, Debug, S, Events, State, Data, P, Event, Result) + {ok,Result,S} catch - Result when CallbackMode =:= undefined -> - loop_event_callback_mode( - Parent, Debug, S, Events, State, Data, P, Event, Result); Result -> - loop_event_result( - Parent, Debug, S, Events, State, Data, P, Event, Result); + {ok,Result,S}; error:badarg -> case erlang:get_stacktrace() of [{erlang,apply, @@ -895,329 +1031,425 @@ loop_event( when CallbackMode =:= state_functions -> %% We get here e.g if apply fails %% due to State not being an atom - terminate( - error, - {undef_state_function,{Module,State,Args}}, - Stacktrace, - Debug, S, [Event|Events], State, Data, P); + {error, + {undef_state_function,{Module,State,Args}}, + Stacktrace}; Stacktrace -> - terminate( - error, badarg, Stacktrace, - Debug, S, [Event|Events], State, Data, P) + {error,badarg,Stacktrace} end; error:undef -> %% Process undef to check for the simple mistake %% of calling a nonexistent state function %% to make the undef more precise case erlang:get_stacktrace() of - [{Module,callback_mode,[]=Args,_} - |Stacktrace] - when CallbackMode =:= undefined -> - terminate( - error, - {undef_callback,{Module,callback_mode,Args}}, - Stacktrace, - Debug, S, [Event|Events], State, Data, P); [{Module,State,[Type,Content,Data]=Args,_} |Stacktrace] when CallbackMode =:= state_functions -> - terminate( - error, - {undef_state_function,{Module,State,Args}}, - Stacktrace, - Debug, S, [Event|Events], State, Data, P); + {error, + {undef_state_function,{Module,State,Args}}, + Stacktrace}; [{Module,handle_event,[Type,Content,State,Data]=Args,_} |Stacktrace] when CallbackMode =:= handle_event_function -> - terminate( - error, - {undef_state_function,{Module,handle_event,Args}}, - Stacktrace, - Debug, S, [Event|Events], State, Data, P); + {error, + {undef_state_function,{Module,handle_event,Args}}, + Stacktrace}; Stacktrace -> - terminate( - error, undef, Stacktrace, - Debug, S, [Event|Events], State, Data, P) + {error,undef,Stacktrace} end; Class:Reason -> - Stacktrace = erlang:get_stacktrace(), - terminate( - Class, Reason, Stacktrace, - Debug, S, [Event|Events], State, Data, P) + {Class,Reason,erlang:get_stacktrace()} end. -%% Interpret callback_mode() result -loop_event_callback_mode( - Parent, Debug, S, Events, State, Data, P, Event, CallbackMode) -> - case callback_mode(CallbackMode) of - true -> - Hibernate = false, % We have already GC:ed recently - loop_event( - Parent, Debug, - S#{callback_mode := CallbackMode}, - Events, - State, Data, P, Event, Hibernate); - false -> +%% Update S and continue +loop_event( + Parent, Debug, S, StateTimer, + Events, Event, State, Data, P, Hibernate) -> + NewS = + S#{ + state := State, + data := Data, + postponed := P}, + loop_event(Parent, Debug, NewS, StateTimer, Events, Event, Hibernate). + +loop_event( + Parent, Debug, #{state := State, data := Data} = S, StateTimer, + Events, {Type,Content} = Event, Hibernate) -> + %% + %% If Hibernate is true here it can only be + %% because it was set from an event action + %% and we did not go into hibernation since there + %% were events in queue, so we do what the user + %% might rely on i.e collect garbage which + %% would have happened if we actually hibernated + %% and immediately was awakened + Hibernate andalso garbage_collect(), + case call_state_function(S, Type, Content, State, Data) of + {ok,Result,NewS} -> + {NewData,NextState,Actions} = + parse_event_result( + true, Debug, NewS, Result, + Events, Event, State, Data), + loop_event_actions( + Parent, Debug, S, StateTimer, + Events, Event, NextState, NewData, Actions); + {Class,Reason,Stacktrace} -> terminate( - error, - {bad_return_from_callback_mode,CallbackMode}, - ?STACKTRACE(), - Debug, S, [Event|Events], State, Data, P) + Class, Reason, Stacktrace, Debug, S, [Event|Events]) end. %% Interpret all callback return variants -loop_event_result( - Parent, Debug, S, Events, State, Data, P, Event, Result) -> +parse_event_result( + AllowStateChange, Debug, S, Result, Events, Event, State, Data) -> case Result of stop -> terminate( - exit, normal, ?STACKTRACE(), - Debug, S, [Event|Events], State, Data, P); + exit, normal, ?STACKTRACE(), Debug, S, [Event|Events]); {stop,Reason} -> terminate( - exit, Reason, ?STACKTRACE(), - Debug, S, [Event|Events], State, Data, P); + exit, Reason, ?STACKTRACE(), Debug, S, [Event|Events]); {stop,Reason,NewData} -> terminate( exit, Reason, ?STACKTRACE(), - Debug, S, [Event|Events], State, NewData, P); + Debug, S#{data := NewData}, [Event|Events]); {stop_and_reply,Reason,Replies} -> Q = [Event|Events], reply_then_terminate( exit, Reason, ?STACKTRACE(), - Debug, S, Q, State, Data, P, Replies); + Debug, S, Q, Replies); {stop_and_reply,Reason,Replies,NewData} -> Q = [Event|Events], reply_then_terminate( exit, Reason, ?STACKTRACE(), - Debug, S, Q, State, NewData, P, Replies); - {next_state,NextState,NewData} -> - loop_event_actions( - Parent, Debug, S, Events, - State, NewData, P, Event, NextState, []); - {next_state,NextState,NewData,Actions} -> - loop_event_actions( - Parent, Debug, S, Events, - State, NewData, P, Event, NextState, Actions); + Debug, S#{data := NewData}, Q, Replies); + {next_state,State,NewData} -> + {NewData,State,[]}; + {next_state,NextState,NewData} when AllowStateChange -> + {NewData,NextState,[]}; + {next_state,State,NewData,Actions} -> + {NewData,State,Actions}; + {next_state,NextState,NewData,Actions} when AllowStateChange -> + {NewData,NextState,Actions}; {keep_state,NewData} -> - loop_event_actions( - Parent, Debug, S, Events, - State, NewData, P, Event, State, []); + {NewData,State,[]}; {keep_state,NewData,Actions} -> - loop_event_actions( - Parent, Debug, S, Events, - State, NewData, P, Event, State, Actions); + {NewData,State,Actions}; keep_state_and_data -> - loop_event_actions( - Parent, Debug, S, Events, - State, Data, P, Event, State, []); + {Data,State,[]}; {keep_state_and_data,Actions} -> - loop_event_actions( - Parent, Debug, S, Events, - State, Data, P, Event, State, Actions); + {Data,State,Actions}; _ -> terminate( error, {bad_return_from_state_function,Result}, ?STACKTRACE(), - Debug, S, [Event|Events], State, Data, P) + Debug, S, [Event|Events]) end. -loop_event_actions( - Parent, Debug, S, Events, State, NewData, P, Event, NextState, Actions) -> - Postpone = false, % Shall we postpone this event; boolean() +parse_enter_actions( + Debug, S, State, Actions, + Hibernate, Timeout, StateTimeout) -> + Postpone = forbidden, + NextEvents = forbidden, + parse_actions( + Debug, S, State, listify(Actions), + Hibernate, Timeout, StateTimeout, Postpone, NextEvents). + +parse_actions(Debug, S, State, Actions) -> Hibernate = false, Timeout = undefined, + StateTimeout = undefined, + Postpone = false, NextEvents = [], - loop_event_actions( - Parent, Debug, S, Events, State, NewData, P, Event, NextState, - if - is_list(Actions) -> - Actions; - true -> - [Actions] - end, - Postpone, Hibernate, Timeout, NextEvents). + parse_actions( + Debug, S, State, listify(Actions), + Hibernate, Timeout, StateTimeout, Postpone, NextEvents). %% -%% Process all actions -loop_event_actions( - Parent, Debug, S, Events, - State, NewData, P, Event, NextState, [Action|Actions], - Postpone, Hibernate, Timeout, NextEvents) -> +parse_actions( + Debug, _S, _State, [], + Hibernate, Timeout, StateTimeout, Postpone, NextEvents) -> + {ok,Debug,Hibernate,Timeout,StateTimeout,Postpone,NextEvents}; +parse_actions( + Debug, S, State, [Action|Actions], + Hibernate, Timeout, StateTimeout, Postpone, NextEvents) -> case Action of %% Actual actions {reply,From,Reply} -> case from(From) of true -> NewDebug = do_reply(Debug, S, State, From, Reply), - loop_event_actions( - Parent, NewDebug, S, Events, - State, NewData, P, Event, NextState, Actions, - Postpone, Hibernate, Timeout, NextEvents); + parse_actions( + NewDebug, S, State, Actions, + Hibernate, Timeout, StateTimeout, + Postpone, NextEvents); false -> - terminate( - error, - {bad_action_from_state_function,Action}, - ?STACKTRACE(), - Debug, S, [Event|Events], State, NewData, P) - end; - {next_event,Type,Content} -> - case event_type(Type) of - true -> - NewDebug = - sys_debug(Debug, S, State, {in,{Type,Content}}), - loop_event_actions( - Parent, NewDebug, S, Events, - State, NewData, P, Event, NextState, Actions, - Postpone, Hibernate, Timeout, - [{Type,Content}|NextEvents]); - false -> - terminate( - error, - {bad_action_from_state_function,Action}, - ?STACKTRACE(), - Debug, S, [Event|Events], State, NewData, P) + {error, + {bad_action_from_state_function,Action}, + ?STACKTRACE()} end; %% Actions that set options - {postpone,NewPostpone} when is_boolean(NewPostpone) -> - loop_event_actions( - Parent, Debug, S, Events, - State, NewData, P, Event, NextState, Actions, - NewPostpone, Hibernate, Timeout, NextEvents); - {postpone,_} -> - terminate( - error, - {bad_action_from_state_function,Action}, - ?STACKTRACE(), - Debug, S, [Event|Events], State, NewData, P); - postpone -> - loop_event_actions( - Parent, Debug, S, Events, - State, NewData, P, Event, NextState, Actions, - true, Hibernate, Timeout, NextEvents); {hibernate,NewHibernate} when is_boolean(NewHibernate) -> - loop_event_actions( - Parent, Debug, S, Events, - State, NewData, P, Event, NextState, Actions, - Postpone, NewHibernate, Timeout, NextEvents); + parse_actions( + Debug, S, State, Actions, + NewHibernate, Timeout, StateTimeout, Postpone, NextEvents); {hibernate,_} -> - terminate( - error, - {bad_action_from_state_function,Action}, - ?STACKTRACE(), - Debug, S, [Event|Events], State, NewData, P); + {error, + {bad_action_from_state_function,Action}, + ?STACKTRACE()}; hibernate -> - loop_event_actions( - Parent, Debug, S, Events, - State, NewData, P, Event, NextState, Actions, - Postpone, true, Timeout, NextEvents); + parse_actions( + Debug, S, State, Actions, + true, Timeout, StateTimeout, Postpone, NextEvents); + {state_timeout,Time,_} = NewStateTimeout + when is_integer(Time), Time >= 0; + Time =:= infinity -> + parse_actions( + Debug, S, State, Actions, + Hibernate, Timeout, NewStateTimeout, Postpone, NextEvents); + {state_timeout,_,_} -> + {error, + {bad_action_from_state_function,Action}, + ?STACKTRACE()}; {timeout,infinity,_} -> % Clear timer - it will never trigger - loop_event_actions( - Parent, Debug, S, Events, - State, NewData, P, Event, NextState, Actions, - Postpone, Hibernate, undefined, NextEvents); + parse_actions( + Debug, S, State, Actions, + Hibernate, undefined, StateTimeout, Postpone, NextEvents); {timeout,Time,_} = NewTimeout when is_integer(Time), Time >= 0 -> - loop_event_actions( - Parent, Debug, S, Events, - State, NewData, P, Event, NextState, Actions, - Postpone, Hibernate, NewTimeout, NextEvents); + parse_actions( + Debug, S, State, Actions, + Hibernate, NewTimeout, StateTimeout, Postpone, NextEvents); {timeout,_,_} -> - terminate( - error, - {bad_action_from_state_function,Action}, - ?STACKTRACE(), - Debug, S, [Event|Events], State, NewData, P); + {error, + {bad_action_from_state_function,Action}, + ?STACKTRACE()}; infinity -> % Clear timer - it will never trigger - loop_event_actions( - Parent, Debug, S, Events, - State, NewData, P, Event, NextState, Actions, - Postpone, Hibernate, undefined, NextEvents); + parse_actions( + Debug, S, State, Actions, + Hibernate, undefined, StateTimeout, Postpone, NextEvents); Time when is_integer(Time), Time >= 0 -> NewTimeout = {timeout,Time,Time}, - loop_event_actions( - Parent, Debug, S, Events, - State, NewData, P, Event, NextState, Actions, - Postpone, Hibernate, NewTimeout, NextEvents); + parse_actions( + Debug, S, State, Actions, + Hibernate, NewTimeout, StateTimeout, Postpone, NextEvents); + {postpone,NewPostpone} + when is_boolean(NewPostpone), Postpone =/= forbidden -> + parse_actions( + Debug, S, State, Actions, + Hibernate, Timeout, StateTimeout, NewPostpone, NextEvents); + {postpone,_} -> + {error, + {bad_action_from_state_function,Action}, + ?STACKTRACE()}; + postpone when Postpone =/= forbidden -> + parse_actions( + Debug, S, State, Actions, + Hibernate, Timeout, StateTimeout, true, NextEvents); + {next_event,Type,Content} -> + case event_type(Type) of + true when NextEvents =/= forbidden -> + NewDebug = + sys_debug(Debug, S, State, {in,{Type,Content}}), + parse_actions( + NewDebug, S, State, Actions, + Hibernate, Timeout, StateTimeout, + Postpone, [{Type,Content}|NextEvents]); + _ -> + {error, + {bad_action_from_state_function,Action}, + ?STACKTRACE()} + end; _ -> - terminate( - error, - {bad_action_from_state_function,Action}, - ?STACKTRACE(), - Debug, S, [Event|Events], State, NewData, P) - end; -%% -%% End of actions list + {error, + {bad_action_from_state_function,Action}, + ?STACKTRACE()} + end. + loop_event_actions( - Parent, Debug, S, Events, - State, NewData, P0, Event, NextState, [], - Postpone, Hibernate, Timeout, NextEvents) -> + Parent, Debug, + #{state := State, state_enter := StateEnter} = S, StateTimer, + Events, Event, NextState, NewData, Actions) -> + case parse_actions(Debug, S, State, Actions) of + {ok,NewDebug,Hibernate,Timeout,StateTimeout,Postpone,NextEvents} -> + if + StateEnter, NextState =/= State -> + loop_event_enter( + Parent, NewDebug, S, StateTimer, + Events, Event, NextState, NewData, + Hibernate, Timeout, StateTimeout, Postpone, NextEvents); + StateEnter -> + case maps:is_key(init_state, S) of + true -> + %% Avoid infinite loop in initial state + %% with state entry events + NewS = maps:remove(init_state, S), + loop_event_enter( + Parent, NewDebug, NewS, StateTimer, + Events, Event, NextState, NewData, + Hibernate, Timeout, StateTimeout, + Postpone, NextEvents); + false -> + loop_event_result( + Parent, NewDebug, S, StateTimer, + Events, Event, NextState, NewData, + Hibernate, Timeout, StateTimeout, + Postpone, NextEvents) + end; + true -> + loop_event_result( + Parent, NewDebug, S, StateTimer, + Events, Event, NextState, NewData, + Hibernate, Timeout, StateTimeout, Postpone, NextEvents) + end; + {Class,Reason,Stacktrace} -> + terminate( + Class, Reason, Stacktrace, + Debug, S#{data := NewData}, [Event|Events]) + end. + +loop_event_enter( + Parent, Debug, #{state := State} = S, StateTimer, + Events, Event, NextState, NewData, + Hibernate, Timeout, StateTimeout, Postpone, NextEvents) -> + case call_state_function(S, enter, State, NextState, NewData) of + {ok,Result,NewS} -> + {NewerData,_,Actions} = + parse_event_result( + false, Debug, NewS, Result, + Events, Event, NextState, NewData), + loop_event_enter_actions( + Parent, Debug, NewS, StateTimer, + Events, Event, NextState, NewerData, + Hibernate, Timeout, StateTimeout, Postpone, NextEvents, Actions); + {Class,Reason,Stacktrace} -> + terminate( + Class, Reason, Stacktrace, + Debug, S#{state := NextState, data := NewData}, + [Event|Events]) + end. + +loop_event_enter_actions( + Parent, Debug, S, StateTimer, + Events, Event, NextState, NewData, + Hibernate, Timeout, StateTimeout, Postpone, NextEvents, Actions) -> + case + parse_enter_actions( + Debug, S, NextState, Actions, + Hibernate, Timeout, StateTimeout) + of + {ok,NewDebug,NewHibernate,NewTimeout,NewStateTimeout,_,_} -> + loop_event_result( + Parent, NewDebug, S, StateTimer, + Events, Event, NextState, NewData, + NewHibernate, NewTimeout, NewStateTimeout, Postpone, NextEvents); + {Class,Reason,Stacktrace} -> + terminate( + Class, Reason, Stacktrace, + Debug, S#{state := NextState, data := NewData}, + [Event|Events]) + end. + +loop_event_result( + Parent, Debug, + #{state := State, postponed := P_0} = S, StateTimer, + Events, Event, NextState, NewData, + Hibernate, Timeout, StateTimeout, Postpone, NextEvents) -> %% %% All options have been collected and next_events are buffered. %% Do the actual state transition. %% - P1 = % Move current event to postponed if Postpone + NewStateTimeout = + case StateTimeout of + {state_timeout,Time,_} -> + %% New timeout -> cancel timer + case StateTimer of + {state_timeout,_,_} -> + ok; + _ -> + cancel_timer(StateTimer) + end, + case Time of + infinity -> + undefined; + _ -> + StateTimeout + end; + undefined when NextState =/= State -> + %% State change -> cancel timer + case StateTimer of + {state_timeout,_,_} -> + ok; + _ -> + cancel_timer(StateTimer) + end, + undefined; + undefined -> + StateTimer + end, + %% + P_1 = % Move current event to postponed if Postpone case Postpone of true -> - [Event|P0]; + [Event|P_0]; false -> - P0 + P_0 end, - {Q2,P} = % Move all postponed events to queue if state change + {Events_1,NewP} = % Move all postponed events to queue if state change if NextState =:= State -> - {Events,P1}; + {Events,P_1}; true -> - {lists:reverse(P1, Events),[]} + {lists:reverse(P_1, Events),[]} end, %% Place next events first in queue - Q = lists:reverse(NextEvents, Q2), + NewEvents = lists:reverse(NextEvents, Events_1), %% NewDebug = sys_debug( Debug, S, State, case Postpone of true -> - {postpone,Event,NextState}; + {postpone,Event,State}; false -> - {consume,Event,NextState} + {consume,Event,State} end), + %% loop_events( - Parent, NewDebug, S, Q, NextState, NewData, P, Hibernate, Timeout). + Parent, NewDebug, S, NewStateTimeout, + NewEvents, Timeout, NextState, NewData, NewP, Hibernate). %%--------------------------------------------------------------------------- %% Server helpers reply_then_terminate( Class, Reason, Stacktrace, - Debug, S, Q, State, Data, P, Replies) -> + Debug, #{state := State} = S, Q, Replies) -> if is_list(Replies) -> do_reply_then_terminate( Class, Reason, Stacktrace, - Debug, S, Q, State, Data, P, Replies); + Debug, S, Q, Replies, State); true -> do_reply_then_terminate( Class, Reason, Stacktrace, - Debug, S, Q, State, Data, P, [Replies]) + Debug, S, Q, [Replies], State) end. %% do_reply_then_terminate( - Class, Reason, Stacktrace, Debug, S, Q, State, Data, P, []) -> - terminate(Class, Reason, Stacktrace, Debug, S, Q, State, Data, P); + Class, Reason, Stacktrace, Debug, S, Q, [], _State) -> + terminate(Class, Reason, Stacktrace, Debug, S, Q); do_reply_then_terminate( - Class, Reason, Stacktrace, Debug, S, Q, State, Data, P, [R|Rs]) -> + Class, Reason, Stacktrace, Debug, S, Q, [R|Rs], State) -> case R of {reply,{_To,_Tag}=From,Reply} -> NewDebug = do_reply(Debug, S, State, From, Reply), do_reply_then_terminate( - Class, Reason, Stacktrace, - NewDebug, S, Q, State, Data, P, Rs); + Class, Reason, Stacktrace, NewDebug, S, Q, Rs, State); _ -> terminate( error, {bad_reply_action_from_state_function,R}, ?STACKTRACE(), - Debug, S, Q, State, Data, P) + Debug, S, Q) end. do_reply(Debug, S, State, From, Reply) -> @@ -1227,7 +1459,9 @@ do_reply(Debug, S, State, From, Reply) -> terminate( Class, Reason, Stacktrace, - Debug, #{module := Module} = S, Q, State, Data, P) -> + Debug, + #{module := Module, state := State, data := Data, postponed := P} = S, + Q) -> try Module:terminate(Reason, State, Data) of _ -> ok catch @@ -1236,7 +1470,7 @@ terminate( ST = erlang:get_stacktrace(), error_info( C, R, ST, S, Q, P, - format_status(terminate, get(), S, State, Data)), + format_status(terminate, get(), S)), sys:print_log(Debug), erlang:raise(C, R, ST) end, @@ -1247,7 +1481,7 @@ terminate( _ -> error_info( Class, Reason, Stacktrace, S, Q, P, - format_status(terminate, get(), S, State, Data)), + format_status(terminate, get(), S)), sys:print_log(Debug) end, case Stacktrace of @@ -1259,7 +1493,9 @@ terminate( error_info( Class, Reason, Stacktrace, - #{name := Name, callback_mode := CallbackMode}, + #{name := Name, + callback_mode := CallbackMode, + state_enter := StateEnter}, Q, P, FmtData) -> {FixedReason,FixedStacktrace} = case Stacktrace of @@ -1286,6 +1522,13 @@ error_info( end; _ -> {Reason,Stacktrace} end, + CBMode = + case StateEnter of + true -> + [CallbackMode,state_enter]; + false -> + CallbackMode + end, error_logger:format( "** State machine ~p terminating~n" ++ case Q of @@ -1312,8 +1555,9 @@ error_info( [] -> []; [Event|_] -> [Event] end] ++ - [FmtData,Class,FixedReason, - CallbackMode] ++ + [FmtData, + Class,FixedReason, + CBMode] ++ case Q of [_|[_|_] = Events] -> [Events]; _ -> [] @@ -1329,7 +1573,9 @@ error_info( %% Call Module:format_status/2 or return a default value -format_status(Opt, PDict, #{module := Module}, State, Data) -> +format_status( + Opt, PDict, + #{module := Module, state := State, data := Data}) -> case erlang:function_exported(Module, format_status, 2) of true -> try Module:format_status(Opt, [PDict,State,Data]) @@ -1353,3 +1599,24 @@ format_status_default(Opt, State, Data) -> _ -> [{data,[{"State",StateData}]}] end. + +listify(Item) when is_list(Item) -> + Item; +listify(Item) -> + [Item]. + +cancel_timer(undefined) -> + ok; +cancel_timer(TRef) -> + case erlang:cancel_timer(TRef) of + false -> + %% We have to assume that TRef is the ref of a running timer + %% and if so the timer has expired + %% hence we must wait for the timeout message + receive + {timeout,TRef,_} -> + ok + end; + _TimeLeft -> + ok + end. 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/ms_transform.erl b/lib/stdlib/src/ms_transform.erl index c0eea652e7..98745b13f3 100644 --- a/lib/stdlib/src/ms_transform.erl +++ b/lib/stdlib/src/ms_transform.erl @@ -451,6 +451,8 @@ check_type(_,[{record,_,_,_}],ets) -> ok; check_type(_,[{cons,_,_,_}],dbg) -> ok; +check_type(_,[{nil,_}],dbg) -> + ok; check_type(Line0,[{match,_,{var,_,_},X}],Any) -> check_type(Line0,[X],Any); check_type(Line0,[{match,_,X,{var,_,_}}],Any) -> 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/stdlib.appup.src b/lib/stdlib/src/stdlib.appup.src index 9877662743..e917b7ea1f 100644 --- a/lib/stdlib/src/stdlib.appup.src +++ b/lib/stdlib/src/stdlib.appup.src @@ -18,9 +18,9 @@ %% %CopyrightEnd% {"%VSN%", %% Up from - max one major revision back - [{<<"3\\.0(\\.[0-9]+)*">>,[restart_new_emulator]}, % OTP-19.* + [{<<"3\\.[0-1](\\.[0-9]+)*">>,[restart_new_emulator]}, % OTP-19.* {<<"2\\.[5-8](\\.[0-9]+)*">>,[restart_new_emulator]}], % OTP-18.* %% Down to - max one major revision back - [{<<"3\\.0(\\.[0-9]+)*">>,[restart_new_emulator]}, % OTP-19.* + [{<<"3\\.[0-1](\\.[0-9]+)*">>,[restart_new_emulator]}, % OTP-19.* {<<"2\\.[5-8](\\.[0-9]+)*">>,[restart_new_emulator]}] % OTP-18.* }. diff --git a/lib/stdlib/src/supervisor.erl b/lib/stdlib/src/supervisor.erl index c81e72689c..1cd65fbf18 100644 --- a/lib/stdlib/src/supervisor.erl +++ b/lib/stdlib/src/supervisor.erl @@ -1087,6 +1087,10 @@ wait_dynamic_children(#child{restart_type=RType} = Child, Pids, Sz, wait_dynamic_children(Child, ?SETS:del_element(Pid, Pids), Sz-1, TRef, EStack); + {'DOWN', _MRef, process, Pid, {shutdown, _}} -> + wait_dynamic_children(Child, ?SETS:del_element(Pid, Pids), Sz-1, + TRef, EStack); + {'DOWN', _MRef, process, Pid, normal} when RType =/= permanent -> wait_dynamic_children(Child, ?SETS:del_element(Pid, Pids), Sz-1, TRef, EStack); 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}. %% |