Skip to content

Commit

Permalink
Revert "Merge pull request #378 from bobot/feature/reraise_raw_backtr…
Browse files Browse the repository at this point in the history
…ace_primitive"

This reverts commit 5adf895, reversing
changes made to 38c3db4.

The reason for the revert is a continuous integration failure on 32bit
arm machines. I don't have the time (or capabilities) to investigate
it right now, and we need functional continuous testing for other
upcoming merges, so the safest choice is to revert -- and hopefully
merge back after the issue is fixed.
  • Loading branch information
gasche committed Jul 27, 2016
1 parent a904c97 commit f1b63d4
Show file tree
Hide file tree
Showing 16 changed files with 85 additions and 366 deletions.
4 changes: 0 additions & 4 deletions Changes
Expand Up @@ -152,10 +152,6 @@ OCaml 4.04.0:
array of floats
(Thomas Braibant)

- GPR#378: Add [Printexc.raise_with_backtrace] raise an exception using
an explicit backtrace
(François Bobot, review by Gabriel Scherer, Xavier Leroy, Damien Doligez,
Frédéric Bour)

### Manual and documentation:

Expand Down
17 changes: 6 additions & 11 deletions asmrun/backtrace_prim.c
Expand Up @@ -69,14 +69,6 @@ frame_descr * caml_next_frame_descriptor(uintnat * pc, char ** sp)
}
}

int caml_alloc_backtrace_buffer(void){
Assert(caml_backtrace_pos == 0);
caml_backtrace_buffer = malloc(BACKTRACE_BUFFER_SIZE
* sizeof(backtrace_slot));
if (caml_backtrace_buffer == NULL) return -1;
return 0;
}

/* Stores the return addresses contained in the given stack fragment
into the backtrace array ; this version is performance-sensitive as
it is called at each [raise] in a program compiled with [-g], so we
Expand All @@ -89,9 +81,12 @@ void caml_stash_backtrace(value exn, uintnat pc, char * sp, char * trapsp)
caml_backtrace_pos = 0;
caml_backtrace_last_exn = exn;
}

if (caml_backtrace_buffer == NULL && caml_alloc_backtrace_buffer() == -1)
return;
if (caml_backtrace_buffer == NULL) {
Assert(caml_backtrace_pos == 0);
caml_backtrace_buffer = malloc(BACKTRACE_BUFFER_SIZE
* sizeof(backtrace_slot));
if (caml_backtrace_buffer == NULL) return;
}

/* iterate on each frame */
while (1) {
Expand Down
23 changes: 0 additions & 23 deletions bytecomp/translcore.ml
Expand Up @@ -338,9 +338,6 @@ let primitives_table = create_hashtable 57 [
let find_primitive prim_name =
Hashtbl.find primitives_table prim_name

let prim_restore_raw_backtrace =
Primitive.simple ~name:"caml_restore_raw_backtrace" ~arity:2 ~alloc:false

let specialize_comparison table env ty =
let (gencomp, intcomp, floatcomp, stringcomp,
nativeintcomp, int32comp, int64comp, _) = table in
Expand Down Expand Up @@ -774,26 +771,6 @@ and transl_exp0 e =
match argl with [obj; meth; cache; pos] ->
wrap (Lsend(Cached, meth, obj, [cache; pos], e.exp_loc))
| _ -> assert false
else if p.prim_name = "%raise_with_backtrace" then begin
let texn1 = List.hd args (* Should not fail by typing *) in
let texn2,bt = match argl with
| [a;b] -> a,b
| _ -> assert false (* idem *)
in
let vexn = Ident.create "exn" in
Llet(Strict, Pgenval, vexn, texn2,
event_before e begin
Lsequence(
wrap (Lprim (Pccall prim_restore_raw_backtrace,
[Lvar vexn;bt],
e.exp_loc)),
wrap0 (Lprim(Praise Raise_reraise,
[event_after texn1 (Lvar vexn)],
e.exp_loc))
)
end
)
end
else begin
let prim = transl_primitive_application
e.exp_loc p e.exp_env prim_type (Some path) args in
Expand Down
43 changes: 3 additions & 40 deletions byterun/backtrace.c
Expand Up @@ -49,11 +49,9 @@ CAMLprim value caml_record_backtrace(value vflag)
caml_backtrace_active = flag;
caml_backtrace_pos = 0;
caml_backtrace_last_exn = Val_unit;
/* Note: We do lazy initialization of caml_backtrace_buffer when
needed in order to simplify the interface with the thread
library (thread creation doesn't need to allocate
caml_backtrace_buffer). So we don't have to allocate it here.
*/
/* Note: lazy initialization of caml_backtrace_buffer in
caml_stash_backtrace to simplify the interface with the thread
libraries */
}
return Val_unit;
}
Expand Down Expand Up @@ -169,41 +167,6 @@ CAMLprim value caml_get_exception_raw_backtrace(value unit)
CAMLreturn(res);
}

/* Copy back a backtrace and exception to the global state.
This function should be used only with Printexc.raw_backtrace */
/* noalloc (caml value): so no CAMLparam* CAMLreturn* */
CAMLprim value caml_restore_raw_backtrace(value exn, value backtrace)
{
intnat i;
mlsize_t bt_size;

caml_backtrace_last_exn = exn;

bt_size = Wosize_val(backtrace);
if(bt_size > BACKTRACE_BUFFER_SIZE){
bt_size = BACKTRACE_BUFFER_SIZE;
}

/* We don't allocate if the backtrace is empty (no -g or backtrace
not activated) */
if(bt_size == 0){
caml_backtrace_pos = 0;
return Val_unit;
}

/* Allocate if needed and copy the backtrace buffer */
if (caml_backtrace_buffer == NULL && caml_alloc_backtrace_buffer() == -1){
return Val_unit;
}

caml_backtrace_pos = bt_size;
for(i=0; i < caml_backtrace_pos; i++){
caml_backtrace_buffer[i] = Backtrace_slot_val(Field(backtrace, i));
}

return Val_unit;
}

#define Val_debuginfo(bslot) (Val_long((uintnat)(bslot)>>1))
#define Debuginfo_val(vslot) ((debuginfo)(Long_val(vslot) << 1))

Expand Down
14 changes: 5 additions & 9 deletions byterun/backtrace_prim.c
Expand Up @@ -217,13 +217,6 @@ CAMLprim value caml_remove_debug_info(code_t start)
CAMLreturn(Val_unit);
}

int caml_alloc_backtrace_buffer(void){
Assert(caml_backtrace_pos == 0);
caml_backtrace_buffer = malloc(BACKTRACE_BUFFER_SIZE * sizeof(code_t));
if (caml_backtrace_buffer == NULL) return -1;
return 0;
}

/* Store the return addresses contained in the given stack fragment
into the backtrace array */

Expand All @@ -235,8 +228,11 @@ void caml_stash_backtrace(value exn, code_t pc, value * sp, int reraise)
caml_backtrace_last_exn = exn;
}

if (caml_backtrace_buffer == NULL && caml_alloc_backtrace_buffer() == -1)
return;
if (caml_backtrace_buffer == NULL) {
Assert(caml_backtrace_pos == 0);
caml_backtrace_buffer = malloc(BACKTRACE_BUFFER_SIZE * sizeof(code_t));
if (caml_backtrace_buffer == NULL) return;
}

if (caml_backtrace_pos >= BACKTRACE_BUFFER_SIZE) return;
/* testing the code region is needed: PR#1554 */
Expand Down
3 changes: 0 additions & 3 deletions byterun/caml/backtrace_prim.h
Expand Up @@ -70,9 +70,6 @@ void caml_debuginfo_location(debuginfo dbg, /*out*/ struct caml_loc_info * li);
#define Val_backtrace_slot(bslot) (Val_long(((uintnat)(bslot))>>1))
#define Backtrace_slot_val(vslot) ((backtrace_slot)(Long_val(vslot) << 1))

/* Allocate the caml_backtrace_buffer. Returns 0 on success, -1 otherwise */
int caml_alloc_backtrace_buffer(void);

#define BACKTRACE_BUFFER_SIZE 1024

/* Besides decoding backtrace info, [backtrace_prim] has two other
Expand Down
6 changes: 2 additions & 4 deletions stdlib/printexc.ml
Expand Up @@ -89,9 +89,6 @@ type raw_backtrace
external get_raw_backtrace:
unit -> raw_backtrace = "caml_get_exception_raw_backtrace"

external raise_with_backtrace: exn -> raw_backtrace -> 'a
= "%raise_with_backtrace"

type backtrace_slot =
| Known_location of {
is_raise : bool;
Expand Down Expand Up @@ -239,7 +236,8 @@ external get_raw_backtrace_next_slot :

(* confusingly named:
returns the *string* corresponding to the global current backtrace *)
let get_backtrace () = raw_backtrace_to_string (get_raw_backtrace ())
let get_backtrace () =
backtrace_to_string (convert_raw_backtrace (get_raw_backtrace ()))

external record_backtrace: bool -> unit = "caml_record_backtrace"
external backtrace_status: unit -> bool = "caml_backtrace_status"
Expand Down
19 changes: 2 additions & 17 deletions stdlib/printexc.mli
Expand Up @@ -42,20 +42,13 @@ val print_backtrace: out_channel -> unit
on the output channel [oc]. The backtrace lists the program
locations where the most-recently raised exception was raised
and where it was propagated through function calls.
If the call is not inside an exception handler, the returned
backtrace is unspecified. If the call is after some
exception-catching code (before in the handler, or in a when-guard
during the matching of the exception handler), the backtrace may
correspond to a later exception than the handled one.
@since 3.11.0
*)

val get_backtrace: unit -> string
(** [Printexc.get_backtrace ()] returns a string containing the
same exception backtrace that [Printexc.print_backtrace] would
print. Same restriction usage than {!print_backtrace}.
print.
@since 3.11.0
*)

Expand Down Expand Up @@ -113,7 +106,7 @@ type raw_backtrace
val get_raw_backtrace: unit -> raw_backtrace
(** [Printexc.get_raw_backtrace ()] returns the same exception
backtrace that [Printexc.print_backtrace] would print, but in
a raw format. Same restriction usage than {!print_backtrace}.
a raw format.
@since 4.01.0
*)
Expand All @@ -132,14 +125,6 @@ val raw_backtrace_to_string: raw_backtrace -> string
@since 4.01.0
*)

external raise_with_backtrace: exn -> raw_backtrace -> 'a
= "%raise_with_backtrace"
(** Reraise the exception using the given raw_backtrace for the
origin of the exception
@since 4.03.0
*)

(** {6 Current call stack} *)

val get_callstack: int -> raw_backtrace
Expand Down
71 changes: 20 additions & 51 deletions testsuite/tests/backtrace/backtrace2.byte.reference
Expand Up @@ -2,57 +2,26 @@ a
No exception
b
Uncaught exception Backtrace2.Error("b")
Raised at file "backtrace2.ml", line 8, characters 23-34
Called from file "backtrace2.ml", line 8, characters 44-55
Called from file "backtrace2.ml", line 8, characters 44-55
Called from file "backtrace2.ml", line 8, characters 44-55
Called from file "backtrace2.ml", line 8, characters 44-55
Called from file "backtrace2.ml", line 8, characters 44-55
Called from file "backtrace2.ml", line 13, characters 4-11
Re-raised at file "backtrace2.ml", line 15, characters 68-71
Called from file "backtrace2.ml", line 58, characters 11-23
Raised at file "backtrace2.ml", line 7, characters 21-32
Called from file "backtrace2.ml", line 7, characters 42-53
Called from file "backtrace2.ml", line 7, characters 42-53
Called from file "backtrace2.ml", line 7, characters 42-53
Called from file "backtrace2.ml", line 7, characters 42-53
Called from file "backtrace2.ml", line 7, characters 42-53
Called from file "backtrace2.ml", line 11, characters 4-11
Re-raised at file "backtrace2.ml", line 13, characters 68-71
Called from file "backtrace2.ml", line 18, characters 11-23
Uncaught exception Backtrace2.Error("c")
Raised at file "backtrace2.ml", line 16, characters 26-37
Called from file "backtrace2.ml", line 58, characters 11-23
Raised at file "backtrace2.ml", line 14, characters 26-37
Called from file "backtrace2.ml", line 18, characters 11-23
Uncaught exception Backtrace2.Error("d")
Raised at file "backtrace2.ml", line 8, characters 23-34
Called from file "backtrace2.ml", line 8, characters 44-55
Called from file "backtrace2.ml", line 8, characters 44-55
Called from file "backtrace2.ml", line 8, characters 44-55
Called from file "backtrace2.ml", line 8, characters 44-55
Called from file "backtrace2.ml", line 8, characters 44-55
Called from file "backtrace2.ml", line 13, characters 4-11
Called from file "backtrace2.ml", line 58, characters 11-23
e
Uncaught exception Backtrace2.Error("e")
Raised at file "backtrace2.ml", line 22, characters 56-59
Called from file "backtrace2.ml", line 58, characters 11-23
f
Uncaught exception Backtrace2.Error("f")
Raised at file "backtrace2.ml", line 28, characters 68-71
Called from file "backtrace2.ml", line 58, characters 11-23
Raised at file "backtrace2.ml", line 7, characters 21-32
Called from file "backtrace2.ml", line 7, characters 42-53
Called from file "backtrace2.ml", line 7, characters 42-53
Called from file "backtrace2.ml", line 7, characters 42-53
Called from file "backtrace2.ml", line 7, characters 42-53
Called from file "backtrace2.ml", line 7, characters 42-53
Called from file "backtrace2.ml", line 11, characters 4-11
Called from file "backtrace2.ml", line 18, characters 11-23
Uncaught exception Invalid_argument("index out of bounds")
Raised by primitive operation at file "backtrace2.ml", line 58, characters 14-22
test_Not_found
Uncaught exception Not_found
Raised at file "hashtbl.ml", line 192, characters 19-28
Called from file "backtrace2.ml", line 39, characters 9-42
Re-raised at file "backtrace2.ml", line 39, characters 67-70
Called from file "backtrace2.ml", line 58, characters 11-23
Uncaught exception Not_found
Raised at file "backtrace2.ml", line 43, characters 24-33
Called from file "backtrace2.ml", line 43, characters 43-52
Called from file "backtrace2.ml", line 43, characters 43-52
Called from file "backtrace2.ml", line 43, characters 43-52
Called from file "backtrace2.ml", line 43, characters 43-52
Called from file "backtrace2.ml", line 43, characters 43-52
Called from file "camlinternalLazy.ml", line 27, characters 17-27
Re-raised at file "camlinternalLazy.ml", line 34, characters 10-11
Called from file "backtrace2.ml", line 58, characters 11-23
Uncaught exception Not_found
Raised at file "hashtbl.ml", line 192, characters 19-28
Called from file "backtrace2.ml", line 46, characters 8-41
Re-raised at file "camlinternalLazy.ml", line 33, characters 62-63
Called from file "camlinternalLazy.ml", line 27, characters 17-27
Re-raised at file "camlinternalLazy.ml", line 34, characters 10-11
Called from file "backtrace2.ml", line 58, characters 11-23
Raised by primitive operation at file "backtrace2.ml", line 18, characters 14-22

0 comments on commit f1b63d4

Please sign in to comment.