Skip to content

Commit

Permalink
Merge branch 'raimo/stdlib/gen_statem-log-callback_mode/GH-8605/OTP-1…
Browse files Browse the repository at this point in the history
…9164' into maint

* raimo/stdlib/gen_statem-log-callback_mode/GH-8605/OTP-19164:
  Use the pre cached callback_mode value for logger
  • Loading branch information
RaimoNiskanen committed Jul 11, 2024
2 parents 17880bd + 26fb239 commit 6af5114
Show file tree
Hide file tree
Showing 2 changed files with 25 additions and 8 deletions.
13 changes: 11 additions & 2 deletions lib/stdlib/src/gen_statem.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1526,14 +1526,23 @@ format_status(Status) ->


%% Helper function for #params.callback_mode, that caches callback_mode()
-compile({inline, [params_callback_mode/2]}).
-compile({inline, [params_callback_mode/2, params_callback_mode/1]}).
params_callback_mode(CallbackMode, Modules) ->
case CallbackMode of
state_functions -> CallbackMode;
handle_event_function ->
Module = hd(Modules),
fun Module:handle_event/4
end.
%%
%% Inverse of the above - return the callback_mode() value before caching
params_callback_mode(CallbackMode) ->
case CallbackMode of
state_functions ->
CallbackMode;
HandleEventFun when is_function(HandleEventFun, 4) ->
handle_event_function
end.

%% Type validation functions
%% - return true if the value is of the type, false otherwise
Expand Down Expand Up @@ -4355,7 +4364,7 @@ error_info(
queue=>maps:get(queue,Status),
postponed=>maps:get(postponed,Status),
modules=>Modules,
callback_mode=>CallbackMode,
callback_mode=>params_callback_mode(CallbackMode),
state_enter=>StateEnter,
state=>NewState,
timeouts=>{NumTimers,maps:get(timeouts,Status)},
Expand Down
20 changes: 14 additions & 6 deletions lib/stdlib/test/gen_statem_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1405,16 +1405,21 @@ terminate_crash_format(Config) ->
error_logger_forwarder:register(),
OldFl = process_flag(trap_exit, true),
try
terminate_crash_format(Config,?MODULE,{formatted,idle,crash_terminate}),
terminate_crash_format(Config,format_status_statem,
{{formatted,idle},{formatted,crash_terminate}})
terminate_crash_format(
Config, ?MODULE, {formatted,idle,crash_terminate}, state_functions),
terminate_crash_format(
Config, format_status_statem,
{{formatted,idle},{formatted,crash_terminate}}, state_functions),
terminate_crash_format(
[{callback_mode,handle_event_function} | Config], ?MODULE,
{formatted,idle,crash_terminate}, handle_event_function)
after
dbg:stop(),
process_flag(trap_exit, OldFl),
error_logger_forwarder:unregister()
end.

terminate_crash_format(Config, Module, Match) ->
terminate_crash_format(Config, Module, State, CallbackMode) ->
Data = crash_terminate,
{ok,Pid} =
gen_statem:start(
Expand All @@ -1424,10 +1429,13 @@ terminate_crash_format(Config, Module, Match) ->
receive
{error,_GroupLeader,
{Pid,
"** State machine"++_,
"** State machine "++_,
[Pid,
{{call,{Self,_}},stop},
Match,exit,{crash,terminate}|_]}} ->
State,
exit, {crash,terminate},
[Module],
CallbackMode | _]}} ->
ok;
Other when is_tuple(Other), element(1, Other) =:= error ->
ct:fail({unexpected,Other})
Expand Down

0 comments on commit 6af5114

Please sign in to comment.