Skip to content

Commit

Permalink
Introduce {ENTER,LEAVE}_FUNCTION macros.
Browse files Browse the repository at this point in the history
This deduplicates code a bit and helps comparing logic against amd64.
And this slightly improves CFI annotation correctness.
  • Loading branch information
dustanddreams committed Mar 15, 2024
1 parent 18c4510 commit 55ab2f3
Show file tree
Hide file tree
Showing 4 changed files with 118 additions and 173 deletions.
67 changes: 29 additions & 38 deletions runtime/arm64.S
Original file line number Diff line number Diff line change
Expand Up @@ -185,6 +185,21 @@ G(name):
.size G(name), .-G(name)
#endif

/* Function prologue and epilogue */

.macro ENTER_FUNCTION
CFI_OFFSET(29, -16)
CFI_OFFSET(30, -8)
stp x29, x30, [sp, -16]!
CFI_ADJUST(16)
add x29, sp, #0
.endm

.macro LEAVE_FUNCTION
ldp x29, x30, [sp], 16
CFI_ADJUST(-16)
.endm

/* Stack switching operations */

/* struct stack_info */
Expand Down Expand Up @@ -451,11 +466,7 @@ G(caml_system__code_begin):
FUNCTION(caml_call_realloc_stack)
CFI_STARTPROC
/* Save return address and frame pointer */
CFI_OFFSET(29, -16)
CFI_OFFSET(30, -8)
stp x29, x30, [sp, -16]!
CFI_ADJUST(16)
add x29, sp, #0
ENTER_FUNCTION
/* Save all registers (including ALLOC_PTR & TRAP_PTR) */
SAVE_ALL_REGS
ldr C_ARG_1, [sp, 16] /* argument */
Expand All @@ -465,11 +476,11 @@ FUNCTION(caml_call_realloc_stack)
cbz x0, 1f
RESTORE_ALL_REGS
/* Free stack space and return to caller */
ldp x29, x30, [sp], 16
LEAVE_FUNCTION
ret
1: RESTORE_ALL_REGS
/* Raise the Stack_overflow exception */
ldp x29, x30, [sp], 16
LEAVE_FUNCTION
add sp, sp, 16 /* pop argument */
ADDRGLOBAL(x0, caml_exn_Stack_overflow)
b G(caml_raise_exn)
Expand All @@ -480,11 +491,7 @@ FUNCTION(caml_call_gc)
CFI_STARTPROC
L(caml_call_gc):
/* Save return address and frame pointer */
CFI_OFFSET(29, -16)
CFI_OFFSET(30, -8)
stp x29, x30, [sp, -16]!
CFI_ADJUST(16)
add x29, sp, #0
ENTER_FUNCTION
/* Store all registers (including ALLOC_PTR & TRAP_PTR) */
SAVE_ALL_REGS
SWITCH_OCAML_TO_C
Expand All @@ -493,7 +500,7 @@ L(caml_call_gc):
SWITCH_C_TO_OCAML
RESTORE_ALL_REGS
/* Free stack space and return to caller */
ldp x29, x30, [sp], 16
LEAVE_FUNCTION
ret
CFI_ENDPROC
END_FUNCTION(caml_call_gc)
Expand Down Expand Up @@ -552,11 +559,7 @@ FUNCTION(caml_allocN)

FUNCTION(caml_c_call)
CFI_STARTPROC
CFI_OFFSET(29, -16)
CFI_OFFSET(30, -8)
stp x29, x30, [sp, -16]!
CFI_ADJUST(16)
add x29, sp, #0
ENTER_FUNCTION
TSAN_SAVE_CALLER_REGS
TSAN_ENTER_FUNCTION
TSAN_RESTORE_CALLER_REGS
Expand Down Expand Up @@ -587,7 +590,7 @@ FUNCTION(caml_c_call)
CFI_ADJUST(-16)
#endif
/* Return */
ldp x29, x30, [sp], 16
LEAVE_FUNCTION
RET_FROM_C_CALL
CFI_ENDPROC
END_FUNCTION(caml_c_call)
Expand All @@ -599,11 +602,7 @@ FUNCTION(caml_c_call_stack_args)
C function : ADDITIONAL_ARG
C stack args : begin=STACK_ARG_BEGIN
end=STACK_ARG_END */
CFI_OFFSET(29, -16)
CFI_OFFSET(30, -8)
stp x29, x30, [sp, -16]!
CFI_ADJUST(16)
add x29, sp, #0
ENTER_FUNCTION
/* Switch from OCaml to C */
SWITCH_OCAML_TO_C
/* Make the exception handler alloc ptr available to the C code */
Expand All @@ -628,7 +627,7 @@ FUNCTION(caml_c_call_stack_args)
/* Switch from C to OCaml */
SWITCH_C_TO_OCAML
/* Return */
ldp x29, x30, [sp], 16
LEAVE_FUNCTION
RET_FROM_C_CALL
CFI_ENDPROC
END_FUNCTION(caml_c_call_stack_args)
Expand Down Expand Up @@ -878,7 +877,7 @@ FUNCTION(caml_raise_exception)
CFI_ADJUST(-16)
#endif
/* Restore frame and link on return to OCaml */
ldp x29, x30, [sp], 16
LEAVE_FUNCTION
b G(caml_raise_exn)
CFI_ENDPROC
END_FUNCTION(caml_raise_exception)
Expand Down Expand Up @@ -969,9 +968,7 @@ FUNCTION(caml_callback3_asm)
Preserves old_stack and new_stack registers */
.macro SWITCH_OCAML_STACKS old_stack, new_stack
/* Save frame pointer and return address for old_stack */
stp x29, x30, [sp, -16]!
CFI_ADJUST(16)
add x29, sp, #0
ENTER_FUNCTION
/* Save OCaml SP and exn_handler in the stack info */
mov TMP, sp
str TMP, Stack_sp(\old_stack)
Expand All @@ -983,8 +980,7 @@ FUNCTION(caml_callback3_asm)
/* restore exn_handler for new stack */
ldr TRAP_PTR, Stack_exception(\new_stack)
/* Restore frame pointer and return address for new_stack */
ldp x29, x30, [sp], 16
CFI_ADJUST(-16)
LEAVE_FUNCTION
.endm


Expand Down Expand Up @@ -1154,11 +1150,7 @@ CFI_STARTPROC
/* x0: fiber
x1: fun
x2: arg */
CFI_OFFSET(29, -16)
CFI_OFFSET(30, -8)
stp x29, x30, [sp, -16]!
CFI_ADJUST(16)
add x29, sp, #0
ENTER_FUNCTION
sub x0, x0, 1 /* x0 := Ptr_val(x0) */
ldr x3, [x1] /* code pointer */
/* save old stack pointer and exception handler */
Expand Down Expand Up @@ -1226,8 +1218,7 @@ L(frame_runstack):
mov x1, x19
ldr TMP, [x19] /* code pointer */
/* Invoke handle_value (or handle_exn) */
ldp x29, x30, [sp], 16
CFI_ADJUST(-16)
LEAVE_FUNCTION
br TMP
L(fiber_exn_handler):
add x8, sp, 16 /* x8 := stack_handler */
Expand Down
51 changes: 25 additions & 26 deletions runtime/power.S
Original file line number Diff line number Diff line change
Expand Up @@ -99,6 +99,20 @@ caml_hot.code_end:
.size \name, . - \name
.endm

/* Function prologue and epilogue */

.macro ENTER_FUNCTION
/* Save return address in caller's frame. */
mflr 0
std 0, LR_SAVE(SP)
.endm

.macro LEAVE_FUNCTION
/* Restore return address. */
ld 0, LR_SAVE(SP)
mtlr 0
.endm

/* Accessing global variables. */

#define LSYMB(glob) .L##glob
Expand Down Expand Up @@ -260,9 +274,7 @@ caml_hot.code_end:
#if defined(WITH_THREAD_SANITIZER) /* { */

.macro TSAN_SETUP_C_CALL size
/* Save return address in caller's frame. */
mflr 0
std 0, LR_SAVE(SP)
ENTER_FUNCTION
/* Setup new frame for a function call and possibly some register saves. */
addi SP, SP, -(RESERVED_STACK + \size)
std 2, TOC_SAVE(SP)
Expand All @@ -271,9 +283,7 @@ caml_hot.code_end:
.macro TSAN_CLEANUP_AFTER_C_CALL size
/* Undo call frame. */
addi SP, SP, (RESERVED_STACK + \size)
/* Restore return address. */
ld 0, LR_SAVE(SP)
mtlr 0
LEAVE_FUNCTION
.endm

.macro TSAN_ENTER_FUNCTION
Expand Down Expand Up @@ -381,9 +391,7 @@ caml_system__code_begin:
/* Desired size is passed in register TMP2. */

FUNCTION caml_call_realloc_stack
/* Save return address in caller's frame. */
mflr 0
std 0, LR_SAVE(SP)
ENTER_FUNCTION
/* Save all registers, as well as ALLOC_PTR and TRAP_PTR */
SAVE_ALL_REGS /* TMP2 is preserved */
/* Recover desired size, to be passed in r3 */
Expand All @@ -395,8 +403,7 @@ FUNCTION caml_call_realloc_stack
cmpdi 3, 0
/* Restore all registers, and also return address */
RESTORE_ALL_REGS
ld 0, LR_SAVE(SP)
mtlr 0
LEAVE_FUNCTION
/* Check status */
beq 1f
/* Reallocation successful: return to caller */
Expand All @@ -409,9 +416,7 @@ ENDFUNCTION caml_call_realloc_stack
/* Invoke the garbage collector. */

FUNCTION caml_call_gc
/* Save return address in caller's frame */
mflr 0
std 0, LR_SAVE(SP)
ENTER_FUNCTION
/* Save all registers, as well as ALLOC_PTR and TRAP_PTR */
SAVE_ALL_REGS
/* Switch stacks and call caml_garbage_collection */
Expand All @@ -420,8 +425,7 @@ FUNCTION caml_call_gc
SWITCH_C_TO_OCAML
/* Restore registers and return to caller */
RESTORE_ALL_REGS
ld 0, LR_SAVE(SP)
mtlr 0
LEAVE_FUNCTION
ld 2, TOC_SAVE(SP)
blr
ENDFUNCTION caml_call_gc
Expand Down Expand Up @@ -597,8 +601,7 @@ FUNCTION caml_raise_exception
ld TMP, Caml_state(current_stack)
ld SP, Stack_sp(TMP)
/* Reload return address from caller's frame (for the backtrace) */
ld 0, LR_SAVE(SP)
mtlr 0
LEAVE_FUNCTION
#if defined(WITH_THREAD_SANITIZER)
/* Call __tsan_func_exit for every OCaml stack frame exited due to the
exception */
Expand Down Expand Up @@ -886,8 +889,7 @@ ENDFUNCTION caml_callback3_asm
Preserves old_stack and new_stack registers */
.macro SWITCH_OCAML_STACKS old_stack, new_stack
/* Save return address for old_stack */
mflr 0
std 0, LR_SAVE(SP)
ENTER_FUNCTION
/* Save OCaml SP and exn_handler in the stack info */
std SP, Stack_sp(\old_stack)
std TRAP_PTR, Stack_exception(\old_stack)
Expand All @@ -897,8 +899,7 @@ ENDFUNCTION caml_callback3_asm
/* restore exn_handler for new stack */
ld TRAP_PTR, Stack_exception(\new_stack)
/* Restore return address for new_stack */
ld 0, LR_SAVE(SP)
mtlr 0
LEAVE_FUNCTION
.endm

/*
Expand Down Expand Up @@ -1082,8 +1083,7 @@ FUNCTION caml_runstack
r4: fun
r5: arg */
/* save return address and TOC on old stack */
mflr 0
std 0, LR_SAVE(SP)
ENTER_FUNCTION
std 2, TOC_SAVE_PARENT(SP)
addi 3, 3, -1 /* r3 := Ptr_val(r3) */
ld 12, 0(4) /* r12 := code pointer */
Expand Down Expand Up @@ -1150,8 +1150,7 @@ FUNCTION caml_runstack
ld 12, 0(4) /* code pointer */
mtctr 12 /* code pointer */
/* Invoke handle_value (or handle_exn) */
ld 0, LR_SAVE(SP)
mtlr 0
LEAVE_FUNCTION
bctr
.Lfiber_exn_handler:
addi 8, SP, (RESERVED_STACK + 16) /* r8 := stack_handler */
Expand Down

0 comments on commit 55ab2f3

Please sign in to comment.