Skip to content

Commit

Permalink
Merge pull request ocaml#13635 from stedolan/update-frame-pointers
Browse files Browse the repository at this point in the history
Avoid traversing C parts of frame pointer chain when reallocating stack
  • Loading branch information
dra27 authored Dec 6, 2024
2 parents c7b188b + d32da79 commit d90601c
Show file tree
Hide file tree
Showing 9 changed files with 260 additions and 108 deletions.
5 changes: 5 additions & 0 deletions Changes
Original file line number Diff line number Diff line change
Expand Up @@ -62,6 +62,11 @@ Working version
Out_of_memory exceptions that the runtime could not handle.
(Guillaume Munch-Maccagnoni, review by Stephen Dolan)

- #13575, #13635: Maintain OCaml frame pointers correctly even when using
C libraries that do not support them.
(Stephen Dolan and David Allsopp, report by Thomas Leonard, review by Tim
McGilchrist and Fabrice Buoro)

### Code generation and optimizations:

- #13565: less tagging in switches compiled to affine transformations
Expand Down
62 changes: 39 additions & 23 deletions runtime/amd64.S
Original file line number Diff line number Diff line change
Expand Up @@ -160,7 +160,7 @@ G(name):
Version 1.0
https://github.com/hjl-tools/x86-psABI/wiki/x86-64-psABI-1.0.pdf */

#define DW_REG_rbx 3
#define DW_REG_rbp 6
#define DW_REG_rsp 7
#define DW_REG_r13 13

Expand Down Expand Up @@ -193,7 +193,12 @@ G(name):
/* Stack switching operations */
/******************************************************************************/

/* Switch from OCaml to C stack. Clobbers %r10, %r11. */
/* Switch from OCaml to C stack. Clobbers %r10, %r11.
If a C function is called which might call back into OCaml,
then nothing may be pushed to the C stack between SWITCH_OCAML_TO_C
and the next C call. (This is to ensure frame pointers are correctly
maintained if the stack is reallocated) */
#ifdef ASM_CFI_SUPPORTED
#define SWITCH_OCAML_TO_C_CFI \
CFI_REMEMBER_STATE; \
Expand Down Expand Up @@ -737,43 +742,54 @@ CFI_STARTPROC
C stack args : begin=%r13 end=%r12 */
/* Switch from OCaml to C */
SWITCH_OCAML_TO_C
/* we use %rbx (otherwise unused) to enable backtraces */
movq %rsp, %rbx
#ifdef ASM_CFI_SUPPORTED
.cfi_escape DW_CFA_def_cfa_expression, 5, \
/* %rbp points to the c_stack_link structure */ \
DW_OP_breg + DW_REG_rbx, Cstack_sp, DW_OP_deref, \
DW_OP_plus_uconst, RETADDR_ENTRY_SIZE
#endif
/* Make the alloc ptr available to the C code */
movq %r15, Caml_state(young_ptr)
/* Copy the arguments and call */
C_call (GCALL(caml_c_call_copy_stack_args))
/* Prepare for return to OCaml */
movq Caml_state(young_ptr), %r15
/* Load ocaml stack and restore global variables */
SWITCH_C_TO_OCAML
/* Return to OCaml caller */
LEAVE_FUNCTION
RET_FROM_C_CALL
CFI_ENDPROC
END_FUNCTION(caml_c_call_stack_args)

/* To correctly maintain frame pointers during stack reallocation,
the runtime assumes that the caml_c_call stub does not push
anything to the stack before the first frame pointer on the C stack.
To guarantee this when stack arguments are used, the actual pushing
of arguments is done by this separate function */
FUNCTION(caml_c_call_copy_stack_args)
CFI_STARTPROC
/* Set up a frame pointer even without WITH_FRAME_POINTERS,
which we use to pop an unknown number of arguments later */
pushq %rbp; CFI_ADJUST(8)
movq %rsp, %rbp
CFI_DEF_CFA_REGISTER(DW_REG_rbp)
/* Copy arguments from OCaml to C stack */
#if defined(SYS_mingw64) || defined (SYS_cygwin)
addq $32, %rsp
#endif
LBL(105):
subq $8, %r12
cmpq %r13,%r12
jb LBL(106)
push (%r12); CFI_ADJUST(8)
push (%r12)
jmp LBL(105)
LBL(106):
#if defined(SYS_mingw64) || defined (SYS_cygwin)
/* Allocate the shadow store on Windows (the c_stack_link store was used
in calling caml_c_call_copy_stack_args) */
subq $32, %rsp
#endif
/* Call the function (address in %rax) */
C_call (*%rax)
/* Pop arguments back off the stack */
movq Caml_state(c_stack), %rsp
/* Prepare for return to OCaml */
movq Caml_state(young_ptr), %r15
/* Load ocaml stack and restore global variables */
SWITCH_C_TO_OCAML
/* Return to OCaml caller */
LEAVE_FUNCTION
RET_FROM_C_CALL
movq %rbp, %rsp
CFI_DEF_CFA_REGISTER(DW_REG_rsp)
popq %rbp; CFI_ADJUST(-8)
ret
CFI_ENDPROC
END_FUNCTION(caml_c_call_stack_args)
END_FUNCTION(caml_c_call_copy_stack_args)

/******************************************************************************/
/* Start the OCaml program */
Expand Down
36 changes: 26 additions & 10 deletions runtime/amd64nt.asm
Original file line number Diff line number Diff line change
Expand Up @@ -339,30 +339,46 @@ caml_c_call_stack_args:
; C stack args : begin=r13 end=r12
; Switch from OCaml to C
SWITCH_OCAML_TO_C
; we use rbx (otherwise unused) to enable backtraces
mov rbx, rsp
; Make the alloc ptr available to the C code
mov Caml_state(young_ptr), r15
; Copy the arguments and call
call caml_c_call_copy_stack_args
; Prepare for return to OCaml
mov r15, Caml_state(young_ptr)
; Load ocaml stack and restore global variables
SWITCH_C_TO_OCAML
; Return to OCaml caller
RET_FROM_C_CALL

; To correctly maintain frame pointers during stack reallocation,
; the runtime assumes that the caml_c_call stub does not push
; anything to the stack before the first frame pointer on the C stack.
; To guarantee this when stack arguments are used, the actual pushing
; of arguments is done by this separate function
PUBLIC caml_c_call_copy_stack_args
ALIGN 4
caml_c_call_copy_stack_args:
; Set up a frame pointer even without WITH_FRAME_POINTERS,
; which we use to pop an unknown number of arguments later
push rbp
mov rbp, rsp
; Copy arguments from OCaml to C stack
add rsp, 32
L105:
sub r12, 8
cmp r12,r13
jb L210
push qword ptr [r12]
jmp L105
L210:
; Allocate the shadow store on Windows (the c_stack_link store was used
; in calling caml_c_call_copy_stack_args)
sub rsp, 32
; Call the function (address in %rax)
call rax
; Pop arguments back off the stack
mov rsp, Caml_state(c_stack)
; Prepare for return to OCaml
mov r15, Caml_state(young_ptr)
; Load ocaml stack and restore global variables
SWITCH_C_TO_OCAML
; Return to OCaml caller
RET_FROM_C_CALL
mov rsp, rbp
pop rbp
ret

; Start the OCaml program

Expand Down
48 changes: 35 additions & 13 deletions runtime/arm64.S
Original file line number Diff line number Diff line change
Expand Up @@ -47,6 +47,7 @@
*/

#define DW_REG_x21 21
#define DW_REG_x29 29
#define DW_REG_sp 31


Expand Down Expand Up @@ -191,7 +192,12 @@ G(name):
#define Handler_parent(reg) [reg, #24]
#define Handler_parent_offset 24

/* Switch from OCaml to C stack. */
/* Switch from OCaml to C stack.
If a C function is called which might call back into OCaml,
then nothing may be pushed to the C stack between SWITCH_OCAML_TO_C
and the next C call. (This is to ensure frame pointers are correctly
maintained if the stack is reallocated) */
.macro SWITCH_OCAML_TO_C
/* Fill in Caml_state->current_stack->sp */
ldr TMP, Caml_state(current_stack)
Expand Down Expand Up @@ -612,30 +618,46 @@ FUNCTION(caml_c_call_stack_args)
/* Make the exception handler alloc ptr available to the C code */
str ALLOC_PTR, Caml_state(young_ptr)
str TRAP_PTR, Caml_state(exn_handler)
/* Store sp to restore after call */
mov x19, sp
/* Copy the arguments and call */
bl G(caml_c_call_copy_stack_args)
/* Reload new allocation pointer & exn handler */
ldr ALLOC_PTR, Caml_state(young_ptr)
ldr TRAP_PTR, Caml_state(exn_handler)
/* Switch from C to OCaml */
SWITCH_C_TO_OCAML
/* Return */
LEAVE_FUNCTION
RET_FROM_C_CALL
CFI_ENDPROC
END_FUNCTION(caml_c_call_stack_args)

/* To correctly maintain frame pointers during stack reallocation,
the runtime assumes that the caml_c_call stub does not push
anything to the stack before the first frame pointer on the C stack.
To guarantee this when stack arguments are used, the actual pushing
of arguments is done by this separate function */
FUNCTION(caml_c_call_copy_stack_args)
CFI_STARTPROC
ENTER_FUNCTION
CFI_DEF_CFA_REGISTER(DW_REG_x29)
/* Copy arguments from OCaml to C stack
NB: STACK_ARG_{BEGIN,END} are 16-byte aligned */
1: sub STACK_ARG_END, STACK_ARG_END, 16
cmp STACK_ARG_END, STACK_ARG_BEGIN
b.lo 2f
ldp TMP, TMP2, [STACK_ARG_END]
stp TMP, TMP2, [sp, -16]!; CFI_ADJUST(16)
stp TMP, TMP2, [sp, -16]!
b 1b
2: /* Call the function */
blr ADDITIONAL_ARG
/* Restore stack */
mov sp, x19
/* Reload new allocation pointer & exn handler */
ldr ALLOC_PTR, Caml_state(young_ptr)
ldr TRAP_PTR, Caml_state(exn_handler)
/* Switch from C to OCaml */
SWITCH_C_TO_OCAML
/* Return */
mov sp, x29
CFI_DEF_CFA_REGISTER(DW_REG_sp)
LEAVE_FUNCTION
RET_FROM_C_CALL
ret
CFI_ENDPROC
END_FUNCTION(caml_c_call_stack_args)
END_FUNCTION(caml_c_call_copy_stack_args)


/* Start the OCaml program */

Expand Down
84 changes: 22 additions & 62 deletions runtime/fiber.c
Original file line number Diff line number Diff line change
Expand Up @@ -445,63 +445,6 @@ void caml_rewrite_exception_stack(struct stack_info *old_stack,
fiber_debug_log ("exn_ptr is null");
}
}

#ifdef WITH_FRAME_POINTERS
/* Update absolute base pointers for new stack */
static void rewrite_frame_pointers(struct stack_info *old_stack,
struct stack_info *new_stack)
{
struct frame_walker {
struct frame_walker *base_addr;
uintnat return_addr;
};
ptrdiff_t delta;

delta = (char*)Stack_high(new_stack) - (char*)Stack_high(old_stack);

/* Walk the frame-pointers linked list */
for (struct frame_walker *frame = __builtin_frame_address(0), *next;
frame;
frame = next) {
void *top, **p;

top = (char*)&frame->return_addr
+ 1 * sizeof(value) /* return address */
+ 2 * sizeof(value) /* trap frame */
+ 2 * sizeof(value); /* DWARF pointer & gc_regs */

/* Detect top of the fiber and bail out */
/* It also avoid to dereference invalid base pointer at main */
if (top == Stack_high(old_stack))
break;

/* Save the base address since it may be adjusted */
next = frame->base_addr;

if (!(Stack_base(old_stack) <= (value*)frame->base_addr
&& (value*)frame->base_addr < Stack_high(old_stack))) {
/* No need to adjust base pointers that don't point into the reallocated
* fiber */
continue;
}

if (Stack_base(old_stack) <= (value*)&frame->base_addr
&& (value*)&frame->base_addr < Stack_high(old_stack)) {
/* The base pointer itself is located inside the reallocated fiber
* and needs to be adjusted on the new fiber */
p = (void**)((char*)Stack_high(new_stack) - (char*)Stack_high(old_stack)
+ (char*)&frame->base_addr);
CAMLassert(*p == frame->base_addr);
*p += delta;
}
else {
/* Base pointers on other stacks are adjusted in place */
frame->base_addr = (struct frame_walker*)((char*)frame->base_addr
+ delta);
}
}
}
#endif
#endif

int caml_try_realloc_stack(asize_t required_space)
Expand Down Expand Up @@ -545,9 +488,6 @@ int caml_try_realloc_stack(asize_t required_space)
#ifdef NATIVE_CODE
caml_rewrite_exception_stack(old_stack, (value**)&Caml_state->exn_handler,
new_stack);
#ifdef WITH_FRAME_POINTERS
rewrite_frame_pointers(old_stack, new_stack);
#endif
#endif

/* Update stack pointers in Caml_state->c_stack. It is possible to have
Expand All @@ -558,9 +498,29 @@ int caml_try_realloc_stack(asize_t required_space)
link != NULL;
link = link->prev) {
if (link->stack == old_stack) {
ptrdiff_t delta =
(char*)Stack_high(new_stack) - (char*)Stack_high(old_stack);
#ifdef WITH_FRAME_POINTERS
struct stack_frame {
struct stack_frame* prev;
void* retaddr;
};

/* Frame pointer is pushed just below the c_stack_link.
This is somewhat tricky to guarantee when there are stack
arguments to C calls: see caml_c_call_copy_stack_args */
struct stack_frame* fp = ((struct stack_frame*)link) - 1;
CAMLassert(fp->prev == link->sp);

/* Rewrite OCaml frame pointers above this C frame */
while (Stack_base(old_stack) <= (value*)fp->prev &&
(value*)fp->prev < Stack_high(old_stack)) {
fp->prev = (struct stack_frame*)((char*)fp->prev + delta);
fp = fp->prev;
}
#endif
link->stack = new_stack;
link->sp = (void*)((char*)Stack_high(new_stack) -
((char*)Stack_high(old_stack) - (char*)link->sp));
link->sp = (char*)link->sp + delta;
}
}
}
Expand Down
1 change: 1 addition & 0 deletions testsuite/tests/frame-pointers/c_call.reference
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
fp_backtrace_many_args
caml_c_call_copy_stack_args
caml_c_call_stack_args
camlC_call$f
camlC_call$entry
Expand Down
Loading

0 comments on commit d90601c

Please sign in to comment.