Skip to content

Commit

Permalink
Merge branch 'bjorn/erts/improve-beam-ops'
Browse files Browse the repository at this point in the history
* bjorn/erts/improve-beam-ops:
  arith_instrs.tab: Clean up bsl/bsr
  beam_makeops: Stop using the Arg() macro
  Eliminate the beam_instrs.h file
  Add the 'S' type for a register source
  Introduce more packable types
  Pack cold instructions too
  Pack instructions using 'q', 'c', and 's'
  beam_makeops: Rewrite the packer, fixing several bugs
  Make map update instruction functions indepedent of instruction format
  beam_makeops: Introduce the new type 'W' (machine word)
  Use the wait_timeout_{un}locked_int instructions
  beam_makeops: Remove the unused aliases 'N' and 'U'
  beam_makeops: Add an additional sanity check
  beam_makeops: Prevent truncation when packing 'I' values
  Improve performance for bsl/bsr
  arith_instrs.tab: Eliminate warning for uninitialized value
  beam_emu: Remove unused macros
  beam_makeops: Remove unused subroutine save_c_code
  Add missing -no_next for badarg instruction
  • Loading branch information
bjorng committed Aug 24, 2017
2 parents 6c4b60d + 7b64965 commit fbf740d
Show file tree
Hide file tree
Showing 10 changed files with 447 additions and 352 deletions.
1 change: 0 additions & 1 deletion erts/emulator/Makefile.in
Original file line number Diff line number Diff line change
Expand Up @@ -546,7 +546,6 @@ endif

$(TTF_DIR)/beam_cold.h \
$(TTF_DIR)/beam_hot.h \
$(TTF_DIR)/beam_instrs.h \
$(TTF_DIR)/beam_opcodes.c \
$(TTF_DIR)/beam_opcodes.h \
$(TTF_DIR)/beam_pred_funcs.h \
Expand Down
80 changes: 43 additions & 37 deletions erts/emulator/beam/arith_instrs.tab
Original file line number Diff line number Diff line change
Expand Up @@ -226,16 +226,12 @@ i_bsr := shift.setup_bsr.execute;
shift.head() {
Eterm Op1, Op2;
Sint shift_left_count;
Sint ires;
Eterm* bigp;
Eterm tmp_big[2];
Uint BIF;
}

shift.setup_bsr(Src1, Src2) {
Op1 = $Src1;
Op2 = $Src2;
BIF = BIF_bsr_2;
shift_left_count = 0;
if (is_small(Op2)) {
shift_left_count = -signed_val(Op2);
} else if (is_big(Op2)) {
Expand All @@ -245,15 +241,13 @@ shift.setup_bsr(Src1, Src2) {
*/
shift_left_count = make_small(bignum_header_is_neg(*big_val(Op2)) ?
MAX_SMALL : MIN_SMALL);
} else {
shift_left_count = 0;
}
}

shift.setup_bsl(Src1, Src2) {
Op1 = $Src1;
Op2 = $Src2;
BIF = BIF_bsl_2;
shift_left_count = 0;
if (is_small(Op2)) {
shift_left_count = signed_val(Op2);
} else if (is_big(Op2)) {
Expand All @@ -271,82 +265,80 @@ shift.setup_bsl(Src1, Src2) {
*/
shift_left_count = MAX_SMALL;
}
} else {
shift_left_count = 0;
}
}

shift.execute(Fail, Live, Dst) {
Uint big_words_needed;

if (is_small(Op1)) {
ires = signed_val(Op1);
if (shift_left_count == 0 || ires == 0) {
Sint int_res = signed_val(Op1);
if (shift_left_count == 0 || int_res == 0) {
if (is_not_integer(Op2)) {
c_p->freason = BADARITH;
$BIF_ERROR_ARITY_2($Fail, BIF, Op1, Op2);
goto shift_error;
}
if (ires == 0) {
if (int_res == 0) {
$Dst = Op1;
$NEXT0();
}
} else if (shift_left_count < 0) { /* Right shift */
Eterm bsr_res;
shift_left_count = -shift_left_count;
if (shift_left_count >= SMALL_BITS-1) {
$Dst = (ires < 0) ? SMALL_MINUS_ONE : SMALL_ZERO;
bsr_res = (int_res < 0) ? SMALL_MINUS_ONE : SMALL_ZERO;
} else {
$Dst = make_small(ires >> shift_left_count);
bsr_res = make_small(int_res >> shift_left_count);
}
$Dst = bsr_res;
$NEXT0();
} else if (shift_left_count < SMALL_BITS-1) { /* Left shift */
if ((ires > 0 &&
((~(Uint)0 << ((SMALL_BITS-1)-shift_left_count)) &
ires) == 0) ||
((~(Uint)0 << ((SMALL_BITS-1)-shift_left_count)) &
~ires) == 0) {
$Dst = make_small(ires << shift_left_count);
if ((int_res > 0 &&
((~(Uint)0 << ((SMALL_BITS-1)-shift_left_count)) & int_res) == 0) ||
((~(Uint)0 << ((SMALL_BITS-1)-shift_left_count)) & ~int_res) == 0) {
$Dst = make_small(int_res << shift_left_count);
$NEXT0();
}
}
ires = 1; /* big_size(small_to_big(Op1)) */
big_words_needed = 1; /* big_size(small_to_big(Op1)) */
goto big_shift;
} else if (is_big(Op1)) {
if (shift_left_count == 0) {
if (is_not_integer(Op2)) {
c_p->freason = BADARITH;
$BIF_ERROR_ARITY_2($Fail, BIF, Op1, Op2);
goto shift_error;
}
$Dst = Op1;
$NEXT0();
}
ires = big_size(Op1);
big_words_needed = big_size(Op1);

big_shift:
if (shift_left_count > 0) { /* Left shift. */
ires += (shift_left_count / D_EXP);
big_words_needed += (shift_left_count / D_EXP);
} else { /* Right shift. */
if (ires <= (-shift_left_count / D_EXP)) {
ires = 3; /* ??? */
if (big_words_needed <= (-shift_left_count / D_EXP)) {
big_words_needed = 3; /* ??? */
} else {
ires -= (-shift_left_count / D_EXP);
big_words_needed -= (-shift_left_count / D_EXP);
}
}
{
ires = BIG_NEED_SIZE(ires+1);
Eterm tmp_big[2];
Sint big_need_size = BIG_NEED_SIZE(big_words_needed+1);

/*
* Slightly conservative check the size to avoid
* allocating huge amounts of memory for bignums that
* clearly would overflow the arity in the header
* word.
*/
if (ires-8 > BIG_ARITY_MAX) {
if (big_need_size-8 > BIG_ARITY_MAX) {
$SYSTEM_LIMIT($Fail);
}
$GC_TEST_PRESERVE(ires+1, $Live, Op1);
$GC_TEST_PRESERVE(big_need_size+1, $Live, Op1);
if (is_small(Op1)) {
Op1 = small_to_big(signed_val(Op1), tmp_big);
}
bigp = HTOP;
Op1 = big_lshift(Op1, shift_left_count, bigp);
Op1 = big_lshift(Op1, shift_left_count, HTOP);
if (is_big(Op1)) {
HTOP += bignum_header_arity(*HTOP) + 1;
}
Expand All @@ -369,8 +361,22 @@ shift.execute(Fail, Live, Dst) {
/*
* One or more non-integer arguments.
*/
shift_error:
c_p->freason = BADARITH;
$BIF_ERROR_ARITY_2($Fail, BIF, Op1, Op2);
if ($Fail) {
$FAIL($Fail);
} else {
reg[0] = Op1;
reg[1] = Op2;
SWAPOUT;
if (I[0] == (BeamInstr) OpCode(i_bsl_ssjtd)) {
I = handle_error(c_p, I, reg, &bif_export[BIF_bsl_2]->info.mfa);
} else {
ASSERT(I[0] == (BeamInstr) OpCode(i_bsr_ssjtd));
I = handle_error(c_p, I, reg, &bif_export[BIF_bsr_2]->info.mfa);
}
goto post_error_handling;
}
}

i_int_bnot(Fail, Src, Live, Dst) {
Expand Down
23 changes: 12 additions & 11 deletions erts/emulator/beam/beam_debug.c
Original file line number Diff line number Diff line change
Expand Up @@ -522,12 +522,13 @@ print_op(fmtfn_t to, void *to_arg, int op, int size, BeamInstr* addr)
}
ap++;
break;
case 'I': /* Untagged integer. */
case 't':
case 't': /* Untagged integers */
case 'I':
case 'W':
switch (op) {
case op_i_gc_bif1_jIsId:
case op_i_gc_bif2_jIIssd:
case op_i_gc_bif3_jIIssd:
case op_i_gc_bif1_jWstd:
case op_i_gc_bif2_jWtssd:
case op_i_gc_bif3_jWtssd:
{
const ErtsGcBif* p;
BifFunction gcf = (BifFunction) *ap;
Expand Down Expand Up @@ -672,8 +673,8 @@ print_op(fmtfn_t to, void *to_arg, int op, int size, BeamInstr* addr)
}
}
break;
case op_i_jump_on_val_xfII:
case op_i_jump_on_val_yfII:
case op_i_jump_on_val_xfIW:
case op_i_jump_on_val_yfIW:
{
int n;
for (n = ap[-2]; n > 0; n--) {
Expand All @@ -696,9 +697,9 @@ print_op(fmtfn_t to, void *to_arg, int op, int size, BeamInstr* addr)
break;
case op_i_put_tuple_xI:
case op_i_put_tuple_yI:
case op_new_map_dII:
case op_update_map_assoc_sdII:
case op_update_map_exact_jsdII:
case op_new_map_dtI:
case op_update_map_assoc_sdtI:
case op_update_map_exact_jsdtI:
{
int n = unpacked[-1];

Expand All @@ -718,7 +719,7 @@ print_op(fmtfn_t to, void *to_arg, int op, int size, BeamInstr* addr)
}
}
break;
case op_i_new_small_map_lit_dIq:
case op_i_new_small_map_lit_dtq:
{
Eterm *tp = tuple_val(unpacked[-1]);
int n = arityval(*tp);
Expand Down

0 comments on commit fbf740d

Please sign in to comment.