Skip to content

Commit

Permalink
Revert bad commit.
Browse files Browse the repository at this point in the history
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@13268 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
  • Loading branch information
alainfrisch committed Jan 23, 2013
1 parent 20a4b99 commit ba00d09
Show file tree
Hide file tree
Showing 7 changed files with 3 additions and 44 deletions.
10 changes: 2 additions & 8 deletions asmrun/backtrace.c
Original file line number Diff line number Diff line change
Expand Up @@ -23,16 +23,10 @@

int caml_backtrace_active = 0;
int caml_backtrace_pos = 0;
int caml_backtrace_extract = 0;
code_t * caml_backtrace_buffer = NULL;
value caml_backtrace_last_exn = Val_unit;
#define BACKTRACE_BUFFER_SIZE 1024

CAMLprim value caml_set_backtrace_extract(value vflag){
caml_backtrace_extract = Int_val(vflag);
return Val_unit;
}

/* Start or stop the backtrace machinery */

CAMLprim value caml_record_backtrace(value vflag)
Expand Down Expand Up @@ -110,9 +104,9 @@ void caml_stash_backtrace(value exn, uintnat pc, char * sp, char * trapsp)
}
/* Stop when we reach the current exception handler */
#ifndef Stack_grows_upwards
if (sp > trapsp && !caml_backtrace_extract) return;
if (sp > trapsp) return;
#else
if (sp < trapsp && !caml_backtrace_extract) return;
if (sp < trapsp) return;
#endif
}
}
Expand Down
Binary file modified boot/ocamlc
Binary file not shown.
Binary file modified boot/ocamldep
Binary file not shown.
Binary file modified boot/ocamllex
Binary file not shown.
9 changes: 1 addition & 8 deletions byterun/backtrace.c
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,6 @@

CAMLexport int caml_backtrace_active = 0;
CAMLexport int caml_backtrace_pos = 0;
CAMLexport int caml_backtrace_extract = 0;
CAMLexport code_t * caml_backtrace_buffer = NULL;
CAMLexport value caml_backtrace_last_exn = Val_unit;
CAMLexport char * caml_cds_file = NULL;
Expand All @@ -60,10 +59,6 @@ enum {
POS_CNUM = 3
};

CAMLprim value caml_set_backtrace_extract(value vflag){
caml_backtrace_extract = Int_val(vflag);
return Val_unit;
}
/* Start or stop the backtrace machinery */

CAMLprim value caml_record_backtrace(value vflag)
Expand Down Expand Up @@ -97,7 +92,6 @@ CAMLprim value caml_backtrace_status(value vunit)

void caml_stash_backtrace(value exn, code_t pc, value * sp)
{
value * limit;
code_t end_code = (code_t) ((char *) caml_start_code + caml_code_size);
if (pc != NULL) pc = pc - 1;
if (exn != caml_backtrace_last_exn) {
Expand All @@ -112,8 +106,7 @@ void caml_stash_backtrace(value exn, code_t pc, value * sp)
if (pc >= caml_start_code && pc < end_code){
caml_backtrace_buffer[caml_backtrace_pos++] = pc;
}
limit = (caml_backtrace_extract ? caml_stack_high : caml_trapsp);
for (/*nothing*/; sp < limit; sp++) {
for (/*nothing*/; sp < caml_trapsp; sp++) {
code_t p = (code_t) *sp;
if (p >= caml_start_code && p < end_code) {
if (caml_backtrace_pos >= BACKTRACE_BUFFER_SIZE) break;
Expand Down
23 changes: 0 additions & 23 deletions stdlib/printexc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -137,28 +137,5 @@ let get_backtrace () =
external record_backtrace: bool -> unit = "caml_record_backtrace"
external backtrace_status: unit -> bool = "caml_backtrace_status"

external set_backtrace_extract: bool -> unit = "caml_set_backtrace_extract"

let current_call_stack () =
let rb = backtrace_status () in
record_backtrace true;
set_backtrace_extract true;
(try raise Exit with _ -> ());
let bt = get_exception_backtrace () in
set_backtrace_extract false;
record_backtrace rb;
match bt with
| None -> []
| Some a ->
let res = ref [] in
for i = Array.length a - 1 downto 0 do
match a.(i) with
| Known_location (_, fn, lineno, ch1, ch2) when fn <> "printexc.ml" ->
res := (fn, lineno, ch1, ch2) :: !res
| _ -> ()
done;
!res


let register_printer fn =
printers := fn :: !printers
5 changes: 0 additions & 5 deletions stdlib/printexc.mli
Original file line number Diff line number Diff line change
Expand Up @@ -82,8 +82,3 @@ val register_printer: (exn -> string option) -> unit
the backtrace if it has itself raised an exception before.
@since 3.11.2
*)

val current_call_stack: unit -> (string * int * int * int) list
(** [Printexc.current_call_stack ()] returns a suffix of the current
call stack (whose length is not specified). Each item is a tuple
(file name, line number, first character, last character). *)

0 comments on commit ba00d09

Please sign in to comment.