Skip to content

Commit

Permalink
[WIP] Add a test for ocaml#11031
Browse files Browse the repository at this point in the history
  • Loading branch information
fabbing committed Feb 23, 2022
1 parent a6369a2 commit 24cba9f
Show file tree
Hide file tree
Showing 2 changed files with 164 additions and 0 deletions.
68 changes: 68 additions & 0 deletions testsuite/tests/frame-pointers/exception_handler.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,68 @@
(* TEST
modules = "fp_backtrace.c"
* hassysthreads
include systhreads
** no-flambda
*** native
*** bytecode
*)

(* https://github.com/ocaml/ocaml/pull/11031 *)
external fp_backtrace : unit -> unit = "fp_backtrace" [@@noalloc]

exception Exn1
exception Exn2

(* We want to be sure to use some stack space so that rbp is shifted,
* preventing inlining seems enough *)
let[@inline never] raiser i =
match i with
| 1 -> raise Exn1
| 2 -> raise Exn2
| _ -> 42 (* shouldn't happen *)

let[@inline never][@local never] f x = x

(* This give us a chance to overwrite the memory address pointed by rbp if it
* is still within 'raiser' stack frame.
* Technically we don't need to overwrite it but by doing so we avoid some
* infinite loop while walking the stack. *)
let[@inline never] handler () =
(* Force spilling of x0, x1, x2 *)
let x0 = Sys.opaque_identity 0x6f56df77 (* 0xdeadbeef *) in
let x1 = Sys.opaque_identity 0x6f56df77 (* 0xdeadbeef *) in
let x2 = Sys.opaque_identity 0x6f56df77 (* 0xdeadbeef *) in
let _ = f x0 in
let _ = f x1 in
let _ = f x2 in
let _ = Sys.opaque_identity x0 in
let _ = Sys.opaque_identity x1 in
let _ = Sys.opaque_identity x2 in
fp_backtrace ()

let[@inline never] nested i =
begin
try
try ignore (raiser i) with Exn1 -> handler ()
with
| Exn2 -> handler ()
end;
i

(* Check that we haven't broken anything by raising directly from this
* function, it doesn't require rbp to be adjusted *)
let[@inline never] bare i =
begin
try
try (if i == 1 then raise Exn1 else raise Exn2) with
| Exn1 -> handler ()
with
| Exn2 -> handler ()
end;
i

let () =
ignore (bare 1);
ignore (bare 2);
ignore (nested 1);
ignore (nested 2)
96 changes: 96 additions & 0 deletions testsuite/tests/frame-pointers/fp_backtrace.c
Original file line number Diff line number Diff line change
@@ -0,0 +1,96 @@
#include <execinfo.h>
#include <unistd.h>
#include <setjmp.h>
#include <signal.h>
#include <stdio.h>

#define ARRSIZE(a) (sizeof(a) / sizeof(*(a)))

typedef struct frame_info
{
struct frame_info* prev; /* rbp */
void* retaddr; /* rip */
} frame_info;

/* Signals to ignore while attempting to read frame_info members */
const int signals[] = { SIGSEGV, SIGBUS };
/* Store original signal handers */
struct sigaction handlers[ARRSIZE(signals)] = { 0 };
jmp_buf resume_buf;


static void signal_handler(int /* signum */)
{
/* Should be safe to be called from a signal handler.
* See 21.2.1 "Performing a nonlocal goto from a signal hanlder" from
* The Linux Programming Interface, Michael Kerrisk */
siglongjmp(resume_buf, 1);
}

static int install_signal_handlers(void)
{
for (int i = 0; i < (int)ARRSIZE(signals); i++) {
struct sigaction action = { 0 };
action.sa_handler = signal_handler;
sigemptyset(&action.sa_mask);
action.sa_flags = 0;

if (sigaction(signals[i], &action, &handlers[i]) != 0) {
perror("sigaction");
return -1;
}
}
return 0;
}

static int restore_signal_handlers(void)
{
for (int i = 0; i < (int)ARRSIZE(signals); i++) {
if (sigaction(signals[i], &handlers[i], NULL) != 0) {
perror("sigaction");
return -1;
}
}
return 0;
}

void fp_backtrace(void)
{
frame_info *fi;
void* rip;

/* Print our current function */
asm ("leaq 0(%%rip), %%rax\n"
"movq %%rax, %[rip]\n"
: [rip] "=rm" (rip) : /* no input */ : "rax");
/* This requires the binary to be linked with '-rdynamic' */
backtrace_symbols_fd(&rip, 1, STDOUT_FILENO);

/* Initialize [fi] from rbp register */
asm ("movq %%rbp, %[fi]\n" : [fi] "=rm" (fi));

while (!sigsetjmp(resume_buf, 1) && fi) {
if (install_signal_handlers() != 0)
return;

struct frame_info* prev = fi->prev;
void* retaddr = fi->retaddr;

if (restore_signal_handlers() != 0)
return;

/* This requires the binary to be linked with '-rdynamic' */
backtrace_symbols_fd(&retaddr, 1, STDOUT_FILENO);

/* Detect the simplest kind of infinite loop */
if (fi == prev) {
printf("fp_backtrace: loop detected\n");
return;
}
fi = prev;
}

/* A signal was caught, restore signal handlers to previous one */
if (fi)
restore_signal_handlers();
}

0 comments on commit 24cba9f

Please sign in to comment.