Skip to content

Commit

Permalink
Merge pull request #8435 from jhogberg/john/jit/fix-invalid-reg-cache/G…
Browse files Browse the repository at this point in the history
…H-8433

arm: Add missing clobber of register cache when SUPER_TMP is used
  • Loading branch information
jhogberg committed May 2, 2024
2 parents 943c40d + 277892b commit 5881f2f
Show file tree
Hide file tree
Showing 3 changed files with 96 additions and 2 deletions.
2 changes: 2 additions & 0 deletions erts/emulator/beam/jit/arm/beam_asm.hpp
Original file line number Diff line number Diff line change
Expand Up @@ -978,6 +978,8 @@ class BeamModuleAssembler : public BeamAssembler,
void reg_cache_put(arm::Mem mem, a64::Gp src) {
if (src != SUPER_TMP) {
reg_cache.put(mem, src);
} else {
reg_cache.invalidate(mem);
}
}

Expand Down
26 changes: 24 additions & 2 deletions erts/emulator/test/beam_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,8 @@
packed_registers/1, apply_last/1, apply_last_bif/1,
heap_sizes/1, big_lists/1, fconv/1,
select_val/1, select_tuple_arity/1,
swap_temp_apply/1, beam_init_yregs/1]).
swap_temp_apply/1, beam_init_yregs/1,
beam_register_cache/1]).

-export([applied/2,swap_temp_applied/1]).

Expand All @@ -38,7 +39,8 @@ all() ->
[packed_registers, apply_last, apply_last_bif,
heap_sizes, big_lists, fconv,
select_val, select_tuple_arity,
swap_temp_apply, beam_init_yregs].
swap_temp_apply, beam_init_yregs,
beam_register_cache].

groups() ->
[].
Expand Down Expand Up @@ -505,6 +507,26 @@ beam_init_yregs(Config) ->

ok.

%% GH-8433: The register cache wasn't properly maintained for certain helper
%% functions in the ARM JIT.
beam_register_cache(Config) ->
DataDir = proplists:get_value(data_dir, Config),
Mod = ?FUNCTION_NAME,

File = filename:join(DataDir, Mod),
{ok,Mod,Code} = compile:file(File, [from_asm,no_postopt,binary]),
{module,Mod} = code:load_binary(Mod, Mod, Code),

try
ok = Mod:Mod()
after
%% Clean up.
true = code:delete(Mod),
false = code:purge(Mod)
end,

ok.

%%% Common utilities.
spawn_exec(F) ->
{Pid,Ref} = spawn_monitor(fun() ->
Expand Down
70 changes: 70 additions & 0 deletions erts/emulator/test/beam_SUITE_data/beam_register_cache.S
Original file line number Diff line number Diff line change
@@ -0,0 +1,70 @@
{module, beam_register_cache}. %% version = 0

{exports, [{beam_register_cache,0},
{module_info,0},
{module_info,1}]}.

{attributes, []}.

{labels, 17}.


{function, beam_register_cache, 0, 2}.
{label,1}.
{line,[{location,"beam_register_cache.erl",4}]}.
{func_info,{atom,beam_register_cache},{atom,beam_register_cache},0}.
{label,2}.
{allocate,0,0}.
{move,{literal,{a,b,c,d,e}},{x,0}}.
{call,1,{f,5}}. % test/1
{test,is_eq_exact,{f,3},[{x,0},{atom,d}]}. %% 'b' on error
{move,{atom,ok},{x,0}}.
{deallocate,0}.
return.
{label,3}.
{badmatch,{x,0}}.


{function, test, 1, 5}.
{label,4}.
{line,[{location,"beam_register_cache.erl",8}]}.
{func_info,{atom,beam_register_cache},{atom,test},1}.
{label,5}.
{test,is_tuple,{f,4},[{x,0}]}.
{test,test_arity,{f,4},[{x,0},5]}.
{allocate,5,1}.
{get_tuple_element,{x,0},0,{y,4}}.
{get_tuple_element,{x,0},1,{y,3}}.
{get_tuple_element,{x,0},2,{y,2}}.
{get_tuple_element,{x,0},3,{y,1}}.
{get_tuple_element,{x,0},4,{y,0}}.
{test,is_eq_exact,{f,6},[{y,3},{atom,b}]}.
{move,{y,1},{y,3}}. %% i_move_trim blew up the register cache here...
{trim,2,3}. %%
{move,{y,1},{x,0}}. %% ... mixing up {y,1} from {y,3} loaded in is_eq_exact
{deallocate,3}.
return.
{label,6}.
{test_heap,2,0}.
{put_list,{y,4},nil,{x,0}}.
{deallocate,5}.
return.


{function, module_info, 0, 14}.
{label,13}.
{line,[]}.
{func_info,{atom,beam_register_cache},{atom,module_info},0}.
{label,14}.
{move,{atom,beam_register_cache},{x,0}}.
{call_ext_only,1,{extfunc,erlang,get_module_info,1}}.


{function, module_info, 1, 16}.
{label,15}.
{line,[]}.
{func_info,{atom,beam_register_cache},{atom,module_info},1}.
{label,16}.
{move,{x,0},{x,1}}.
{move,{atom,beam_register_cache},{x,0}}.
{call_ext_only,2,{extfunc,erlang,get_module_info,2}}.

0 comments on commit 5881f2f

Please sign in to comment.