Skip to content

Commit

Permalink
Merge pull request #9353 from bjorng/bjorn/compile/try_catch
Browse files Browse the repository at this point in the history
Improve register allocation for try ... catch constructs
  • Loading branch information
bjorng authored Jan 29, 2025
2 parents fa9b471 + 8b814a7 commit 0411d8a
Showing 1 changed file with 62 additions and 3 deletions.
65 changes: 62 additions & 3 deletions lib/compiler/src/beam_ssa_pre_codegen.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2007,6 +2007,11 @@ copy_retval_is([#b_set{op=call,dst=#b_var{}=Dst}=I0|Is], RC, Yregs,
false ->
copy_retval_is(Is, RC, Yregs, none, Count1, [I1|Acc])
end;
copy_retval_is([#b_set{op=landingpad,args=[#b_literal{val='try'}|_]=Args0}=I0|Is],
_RC, Yregs, Copy, Count, Acc0) ->
I = I0#b_set{args=copy_sub_args(Args0, Copy)},
Acc = [I|acc_copy(Acc0, Copy)],
copy_landingpad(Is, Yregs, Count, Acc, []);
copy_retval_is([#b_set{args=Args0}=I0|Is], RC, Yregs, Copy, Count, Acc) ->
I = I0#b_set{args=copy_sub_args(Args0, Copy)},
case beam_ssa:clobbers_xregs(I) of
Expand All @@ -2025,6 +2030,53 @@ copy_retval_is([], RC, _, Copy, Count, Acc) ->
{reverse(Acc, [Copy]),Count}
end.

%% Consider this function:
%%
%% do_try(F) ->
%% try F()
%% catch
%% C:R:Stk ->
%% {'EXIT',C,R,Stk}
%% end.
%%
%% That would result in the following SSA code for the `catch` clause:
%%
%% z0/_16 = landingpad `'try'`, y2/_14
%% y1/_4 = extract z0/_16, `0`
%% y0/_3 = extract z0/_16, `1`
%% x0/_2 = extract z0/_16, `2`
%% z0/_17 = kill_try_tag y2/_14
%% x0/Stk = build_stacktrace x0/_2
%%
%% Note that three Y registers are required. That can be reduced to
%% two Y registers if we rewrite the code like so:
%%
%% x0/_37 = extract z0/_16, `0`
%% x1/_38 = extract z0/_16, `1`
%% x2/_2 = extract z0/_16, `2`
%% z0/_17 = kill_try_tag y1/_14
%% y1/_3 = copy x1/_38
%% y0/_4 = copy x0/_37
%%

copy_landingpad([I0|Is], Yregs, Count0, Acc0, Copies0) ->
case I0 of
#b_set{dst=Dst,op=extract} ->
case sets:is_element(Dst, Yregs) of
true ->
{NewDst,Count} = new_var(Count0),
Copies = [#b_set{op=copy,dst=Dst,args=[NewDst]}|Copies0],
I = I0#b_set{dst=NewDst},
Acc = [I|Acc0],
copy_landingpad(Is, Yregs, Count, Acc, Copies);
false ->
Acc = [I0|Acc0],
copy_landingpad(Is, Yregs, Count0, Acc, Copies0)
end;
#b_set{op=kill_try_tag} ->
{reverse(Acc0, [I0|Copies0 ++ Is]),Count0}
end.

%%
%% Consider this code:
%%
Expand Down Expand Up @@ -2788,15 +2840,22 @@ reserve_xregs_is([gc|Is], Res, Xs0, Used) ->
Xs = res_xregs_prune(Xs0, Used, Res),
reserve_xregs_is(Is, Res, Xs, Used);
reserve_xregs_is([#b_set{op=Op,dst=Dst,args=Args}=I|Is], Res0, Xs0, Used0) ->
Res = reserve_xreg(Dst, Xs0, Res0),
Res1 = reserve_xreg(Dst, Xs0, Res0),
Used1 = ordsets:union(Used0, beam_ssa:used(I)),
Used = ordsets:del_element(Dst, Used1),
case Op of
call ->
Xs = reserve_call_args(tl(Args)),
reserve_xregs_is(Is, Res, Xs, Used);
reserve_xregs_is(Is, Res1, Xs, Used);
extract ->
%% Avoid potential register shuffling by pinning the
%% destination variable to the X register where the
%% runtime system will place it.
[_,#b_literal{val=Reg}] = Args,
Res = Res1#{Dst => {x,Reg}},
reserve_xregs_is(Is, Res, Xs0, Used);
_ ->
reserve_xregs_is(Is, Res, Xs0, Used)
reserve_xregs_is(Is, Res1, Xs0, Used)
end;
reserve_xregs_is([], Res, Xs, _Used) ->
{Res,Xs}.
Expand Down

0 comments on commit 0411d8a

Please sign in to comment.