Skip to content

Commit

Permalink
fixup! Optimize bsr for small operands
Browse files Browse the repository at this point in the history
  • Loading branch information
bjorng committed Aug 14, 2023
1 parent b78544f commit 36c0ff3
Show file tree
Hide file tree
Showing 2 changed files with 24 additions and 9 deletions.
18 changes: 13 additions & 5 deletions erts/emulator/beam/jit/arm/instr_arith.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -1519,11 +1519,19 @@ void BeamModuleAssembler::emit_i_bsr(const ArgLabel &Fail,

/* Ensure that both operands are small and that the shift
* count is positive. */
a.and_(TMP1, lhs.reg, rhs.reg);
a.mvn(TMP1, TMP1);
a.tst(TMP1, imm(_TAG_IMMED1_MASK));
a.ccmp(rhs.reg, imm(0), imm(NZCV::kSigned), arm::CondCode::kEQ);
a.b_lt(generic);
if (std::get<0>(getClampedRange(RHS)) >= 0) {
ERTS_CT_ASSERT(_TAG_IMMED1_SMALL == _TAG_IMMED1_MASK);
a.and_(TMP1, lhs.reg, rhs.reg);
a.and_(TMP1, TMP1, imm(_TAG_IMMED1_MASK));
a.cmp(TMP1, imm(_TAG_IMMED1_SMALL));
a.b_ne(generic);
} else {
a.and_(TMP1, lhs.reg, rhs.reg);
a.mvn(TMP1, TMP1);
a.tst(TMP1, imm(_TAG_IMMED1_MASK));
a.ccmp(rhs.reg, imm(0), imm(NZCV::kSigned), arm::CondCode::kEQ);
a.b_lt(generic);
}

a.asr(TMP1, rhs.reg, imm(_TAG_IMMED1_SIZE));
mov_imm(TMP2, 63);
Expand Down
15 changes: 11 additions & 4 deletions erts/emulator/test/small_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1069,7 +1069,8 @@ test_bsr(_Config) ->
Fs0 = gen_func_names(Pairs, 0),
Fs = [gen_bsr_function(F) || F <- Fs0],
Tree = ?Q(["-module('@Mod@').",
"-compile([export_all,nowarn_export_all])."]) ++ Fs,
"-compile([export_all,nowarn_export_all]).",
"id(I) -> I."]) ++ Fs,
%% merl:print(Tree),
{ok,_Bin} = merl:compile_and_load(Tree, []),
test_bsr(Fs0, Mod),
Expand Down Expand Up @@ -1107,12 +1108,18 @@ gen_bsr_function({Name,{N,S}}) ->
Res
end;
'@Name@'(N0, S, More) ->
Res = N0 bsr S,
Res = id(N0 bsr S),
if
More ->
N = N0 band _@Mask@,
Res = N0 bsr S,
Res = N bsr S;
Res = id(N0 bsr S),
Res = id(N bsr S),
if
S >= 0 ->
Res = id(N bsr S);
true ->
Res
end;
true ->
Res
end. ").
Expand Down

0 comments on commit 36c0ff3

Please sign in to comment.