Xavier Clerc's remarks.

master
Jacques-Henri Jourdan 2019-07-16 13:42:04 +02:00
parent 593f94055a
commit 78de99ecc2
7 changed files with 15 additions and 11 deletions

View File

@ -122,7 +122,9 @@ let update_breakpoints () =
let execute_without_breakpoints f =
Misc.protect_refs [Misc.R (Debugger_config.break_on_load, false);
Misc.R (current_version, 0);
Misc.R (positions, [])]
Misc.R (positions, []);
Misc.R (breakpoints, []);
Misc.R (breakpoint_number, 0)]
f
(* Add a position in the position list. *)

View File

@ -31,7 +31,7 @@ val breakpoints : (breakpoint_id * Events.code_event) list ref
val breakpoint_at_pc : Debugcom.pc -> bool
(* List of breakpoints at `pc'. *)
val breakpoints_at_pc : Debugcom.pc -> int list
val breakpoints_at_pc : Debugcom.pc -> breakpoint_id list
(*** Set and remove breakpoints ***)
@ -46,7 +46,7 @@ val execute_without_breakpoints : (unit -> unit) -> unit
val new_breakpoint : Events.code_event -> unit
(* Remove a breakpoint from lists. *)
val remove_breakpoint : int -> unit
val remove_breakpoint : breakpoint_id -> unit
val remove_all_breakpoints : unit -> unit

View File

@ -29,8 +29,6 @@ let modules =
let program_source_dirs =
ref ([] : string list)
let events =
ref ([] : debug_event list)
let events_by_pc =
(Hashtbl.create 257 : (pc, debug_event) Hashtbl.t)
let events_by_module =
@ -96,7 +94,7 @@ let read_symbols' bytecode_file =
!eventlists, !dirs
let clear_symbols () =
modules := []; events := [];
modules := [];
program_source_dirs := [];
Hashtbl.clear events_by_pc; Hashtbl.clear events_by_module;
Hashtbl.clear all_events_by_module
@ -106,7 +104,6 @@ let add_symbols frag all_events =
(fun evl ->
List.iter
(fun ev ->
events := ev :: !events;
Hashtbl.add events_by_pc {frag; pos = ev.ev_pos} ev)
evl)
all_events;

View File

@ -538,7 +538,7 @@ external module is not yet loaded, it is impossible to set a
breakpoint in its code. In order to facilitate setting breakpoints in
dynamically loaded code, the debugger stops the program each time new
modules are loaded. This behavior can be disabled using the
"break_on_load" variable:
\var{break_on_load} variable:
\begin{options}
\item["set break_on_load" \var{on/off}]

View File

@ -444,7 +444,6 @@ extern void caml_instr_atexit (void);
#endif
/* A table of all code fragments (main program and dynlinked modules) */
struct code_fragment {
char *code_start;
char *code_end;
@ -454,7 +453,7 @@ struct code_fragment {
extern struct ext_table caml_code_fragments_table;
int caml_find_code_fragment(char* pc, int *index, struct code_fragment **cf);
int caml_find_code_fragment(char *pc, int *index, struct code_fragment **cf);
#endif /* CAML_INTERNALS */

View File

@ -386,20 +386,26 @@ void caml_debugger(enum event_kind event, value param)
/* Report the event to the debugger */
switch(event) {
case PROGRAM_START: /* Nothing to report */
CAMLassert (param == Val_unit);
goto command_loop;
case EVENT_COUNT:
CAMLassert (param == Val_unit);
caml_putch(dbg_out, REP_EVENT);
break;
case BREAKPOINT:
CAMLassert (param == Val_unit);
caml_putch(dbg_out, REP_BREAKPOINT);
break;
case PROGRAM_EXIT:
CAMLassert (param == Val_unit);
caml_putch(dbg_out, REP_EXITED);
break;
case TRAP_BARRIER:
CAMLassert (param == Val_unit);
caml_putch(dbg_out, REP_TRAP);
break;
case UNCAUGHT_EXC:
CAMLassert (param == Val_unit);
caml_putch(dbg_out, REP_UNCAUGHT_EXC);
break;
case DEBUG_INFO_ADDED:

View File

@ -282,7 +282,7 @@ void caml_instr_atexit (void)
}
#endif /* CAML_INSTR */
int caml_find_code_fragment(char* pc, int *index, struct code_fragment **cf)
int caml_find_code_fragment(char *pc, int *index, struct code_fragment **cf)
{
struct code_fragment *cfi;
int i;