Skip to content

Commit

Permalink
Fixes for SEGV errors in frame_pointer tests.
Browse files Browse the repository at this point in the history
  • Loading branch information
tmcgilchrist committed Sep 12, 2024
1 parent 104ff0e commit d787ca7
Show file tree
Hide file tree
Showing 2 changed files with 35 additions and 46 deletions.
3 changes: 1 addition & 2 deletions asmcomp/amd64/emit.mlp
Original file line number Diff line number Diff line change
Expand Up @@ -467,8 +467,7 @@ let emit_instr env fallthrough i =
I.mov rsp rbp;
end;
if env.f.fun_frame_required then begin
let n = (frame_size env) - 8 (* return address *)
- (if fp then 8 else 0) (* frame pointer *) in
let n = (frame_size env) - 8 - (if fp then 8 else 0) in
if n <> 0
then begin
I.sub (int n) rsp;
Expand Down
78 changes: 34 additions & 44 deletions runtime/arm64.S
Original file line number Diff line number Diff line change
Expand Up @@ -159,22 +159,12 @@ G(name):
.macro ENTER_FUNCTION
CFI_OFFSET(29, -16)
CFI_OFFSET(30, -8)
/*
sub sp, sp, #16
str x29, [sp]
str x30, [sp, #8]
*/
stp x29, x30, [sp, -16]!
CFI_ADJUST(16)
add x29, sp, #0
.endm

.macro LEAVE_FUNCTION
/*
ldr x29, [sp]
ldr x30, [sp, #8]
add sp, sp, #16
*/
ldp x29, x30, [sp], 16
CFI_ADJUST(-16)
.endm
Expand Down Expand Up @@ -313,6 +303,32 @@ G(name):
ldr TRAP_PTR, Caml_state(exn_handler)
.endm

/* Updates the oldest saved frame pointer in the target fiber.
A fiber stack may need to grow, causing the reallocation of the entire fiber,
including stack_info and stack_handler structures.
caml_try_realloc_stack will not be able to update the linked list of
frame-pointers if it has been split (ie, in a continuation).
caml_resume and caml_reperform use this macro to update the oldest saved rbp
(highest one in the stack) in case the fiber was reallocated to reattach the
frame-pointer linked list.
REG: Stack_handler(target_fiber)
The frame pointer will be pushed into the stack immediately after these
instructions. The offset of the oldest saved x29 in a fiber from the stack
handler is 48 = 4 words (caml_runstack) + 2 words (x30 and x29).
*/
#ifdef WITH_FRAME_POINTERS
.macro UPDATE_BASE_POINTER reg
ldr TMP2, [sp, -16]
str TMP2, [\reg, -48]
.endm
#else
.macro UPDATE_BASE_POINTER reg
.endm
#endif

#if defined(WITH_THREAD_SANITIZER) /* { */

/* Push the current value of the link register to the stack. */
Expand Down Expand Up @@ -653,8 +669,8 @@ L(jump_to_caml):
/* Set up stack frame and save callee-save registers */
CFI_OFFSET(29, -160)
CFI_OFFSET(30, -152)
stp x29, x30, [sp, -160]! ; sp = 0x000000016fdff010 => 0x000000016fdfef70
CFI_ADJUST(160) ; sub sp, sp, 160; stp x29, x30, [sp]
stp x29, x30, [sp, -160]!
CFI_ADJUST(160)
mov x29, sp
stp x19, x20, [sp, 16]
stp x21, x22, [sp, 32]
Expand Down Expand Up @@ -975,31 +991,6 @@ END_FUNCTION(caml_callback3_asm)
LEAVE_FUNCTION
.endm

/* Updates the oldest saved frame pointer in the target fiber.
A fiber stack may need to grow, causing the reallocation of the entire fiber,
including stack_info and stack_handler structures.
caml_try_realloc_stack will not be able to update the linked list of
frame-pointers if it has been split (ie, in a continuation).
caml_resume and caml_reperform use this macro to update the oldest saved fp (x29)
(highest one in the stack) in case the fiber was reallocated to reattach the
frame-pointer linked list.
REG: Stack_handler(target_fiber)
The frame pointer will be pushed into the stack immediately after these
instructions. The offset of the oldest saved fp in a fiber from the stack
handler is 48 = 4 words (caml_runstack) + 2 words (lr (x30) and fp (x29)).
*/
#ifdef WITH_FRAME_POINTERS
#define UPDATE_BASE_POINTER(REG) \
;; ldr TMP, [sp, -8]; \
;; str TMP, [REG, -48]
#else
#define UPDATE_BASE_POINTER(REG)
#endif


/*
* A continuation is a one word object that points to a fiber. A fiber [f] will
* point to its parent at Handler_parent(Stack_handler(f)). In the following,
Expand Down Expand Up @@ -1064,6 +1055,7 @@ L(do_perform):
ldr x9, Caml_state(current_stack)
SWITCH_OCAML_STACKS x9, x10
/* No parent stack. Raise Effect.Unhandled. */
ENTER_FUNCTION
#if defined(WITH_THREAD_SANITIZER)
/* We must let the TSan runtime know that we switched back to the
original performer stack. For that, we perform the necessary calls
Expand All @@ -1085,7 +1077,7 @@ END_FUNCTION(caml_perform)

FUNCTION(caml_reperform)
CFI_STARTPROC
/* x0: effect to perform
/* x0: effect to reperform
x1: continuation
x2: last_fiber */
ldr TMP, Stack_handler_from_cont(x2)
Expand All @@ -1094,7 +1086,7 @@ FUNCTION(caml_reperform)
add x3, x2, 1 /* x3 (last_fiber) := Val_ptr(old stack) */
/* Need to update the oldest saved frame pointer here as the execution of
the handler may have caused the current fiber stack to reallocate. */
/* TODO call UPDATE_BASE_POINTERS (x2) */
UPDATE_BASE_POINTER TMP
b L(do_perform)
CFI_ENDPROC
END_FUNCTION(caml_reperform)
Expand Down Expand Up @@ -1145,14 +1137,12 @@ FUNCTION(caml_resume)
/* Need to update the oldest saved frame pointer here as the current fiber
stack may have been reallocated or we may be resuming a computation
that was not originally run here. */
/* TODO UPDATE_BASE_POINTER(x8)
When we switch stacks to x9, then we loose the placeholder for
where we were resumed from?
*/
UPDATE_BASE_POINTER x8
SWITCH_OCAML_STACKS x9, x0
mov x0, x2
br x4
1: ADDRGLOBAL(ADDITIONAL_ARG, caml_raise_continuation_already_resumed)
1: ENTER_FUNCTION
ADDRGLOBAL(ADDITIONAL_ARG, caml_raise_continuation_already_resumed)
b G(caml_c_call)
CFI_ENDPROC
END_FUNCTION(caml_resume)
Expand Down

0 comments on commit d787ca7

Please sign in to comment.