1996-11-29 08:55:09 -08:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
2011-07-27 07:17:02 -07:00
|
|
|
(* OCaml *)
|
1996-11-29 08:55:09 -08:00
|
|
|
(* *)
|
|
|
|
(* Jerome Vouillon, projet Cristal, INRIA Rocquencourt *)
|
2011-07-27 07:17:02 -07:00
|
|
|
(* OCaml port by John Malecki and Xavier Leroy *)
|
1996-11-29 08:55:09 -08:00
|
|
|
(* *)
|
|
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
1999-11-17 10:59:06 -08:00
|
|
|
(* en Automatique. All rights reserved. This file is distributed *)
|
|
|
|
(* under the terms of the Q Public License version 1.0. *)
|
1996-11-29 08:55:09 -08:00
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(******************************* Breakpoints ***************************)
|
|
|
|
|
2003-11-21 08:10:57 -08:00
|
|
|
open Checkpoints
|
|
|
|
open Debugcom
|
1996-11-29 08:55:09 -08:00
|
|
|
open Instruct
|
|
|
|
open Primitives
|
2003-11-21 08:10:57 -08:00
|
|
|
open Printf
|
1996-11-29 08:55:09 -08:00
|
|
|
|
|
|
|
(*** Debugging. ***)
|
1997-03-21 05:31:13 -08:00
|
|
|
let debug_breakpoints = ref false
|
1996-11-29 08:55:09 -08:00
|
|
|
|
|
|
|
(*** Data. ***)
|
|
|
|
|
|
|
|
(* Number of the last added breakpoint. *)
|
|
|
|
let breakpoint_number = ref 0
|
|
|
|
|
|
|
|
(* Breakpoint number -> event. *)
|
|
|
|
let breakpoints = ref ([] : (int * debug_event) list)
|
|
|
|
|
|
|
|
(* Program counter -> breakpoint count. *)
|
|
|
|
let positions = ref ([] : (int * int ref) list)
|
|
|
|
|
|
|
|
(* Versions of the breakpoint list. *)
|
|
|
|
let current_version = ref 0
|
|
|
|
let max_version = ref 0
|
|
|
|
|
|
|
|
(*** Miscellaneous. ***)
|
|
|
|
|
|
|
|
(* Mark breakpoints as installed in current checkpoint. *)
|
|
|
|
let copy_breakpoints () =
|
|
|
|
!current_checkpoint.c_breakpoints <- !positions;
|
|
|
|
!current_checkpoint.c_breakpoint_version <- !current_version
|
|
|
|
|
|
|
|
(* Announce a new version of the breakpoint list. *)
|
|
|
|
let new_version () =
|
|
|
|
incr max_version;
|
1997-03-27 13:08:13 -08:00
|
|
|
current_version := !max_version
|
1996-11-29 08:55:09 -08:00
|
|
|
|
|
|
|
(*** Information about breakpoints. ***)
|
|
|
|
|
|
|
|
let breakpoints_count () =
|
|
|
|
List.length !breakpoints
|
|
|
|
|
|
|
|
(* List of breakpoints at `pc'. *)
|
1997-03-27 13:08:13 -08:00
|
|
|
let rec breakpoints_at_pc pc =
|
|
|
|
begin try
|
|
|
|
let ev = Symbols.event_at_pc pc in
|
|
|
|
match ev.ev_repr with
|
|
|
|
Event_child {contents = pc'} -> breakpoints_at_pc pc'
|
|
|
|
| _ -> []
|
|
|
|
with Not_found ->
|
|
|
|
[]
|
|
|
|
end
|
|
|
|
@
|
2009-05-20 04:52:42 -07:00
|
|
|
List.map fst (List.filter (function (_, {ev_pos = pos}) -> pos = pc) !breakpoints)
|
1996-11-29 08:55:09 -08:00
|
|
|
|
1997-03-27 13:08:13 -08:00
|
|
|
(* Is there a breakpoint at `pc' ? *)
|
|
|
|
let breakpoint_at_pc pc =
|
|
|
|
breakpoints_at_pc pc <> []
|
|
|
|
|
1996-11-29 08:55:09 -08:00
|
|
|
(*** Set and remove breakpoints ***)
|
|
|
|
|
|
|
|
(* Remove all breakpoints. *)
|
|
|
|
let remove_breakpoints pos =
|
|
|
|
if !debug_breakpoints then
|
|
|
|
(print_string "Removing breakpoints..."; print_newline ());
|
|
|
|
List.iter
|
|
|
|
(function (pos, _) ->
|
|
|
|
if !debug_breakpoints then begin
|
|
|
|
print_int pos;
|
|
|
|
print_newline()
|
|
|
|
end;
|
1997-03-21 05:31:13 -08:00
|
|
|
reset_instr pos;
|
1998-11-12 06:51:27 -08:00
|
|
|
Symbols.set_event_at_pc pos)
|
1996-11-29 08:55:09 -08:00
|
|
|
pos
|
|
|
|
|
|
|
|
(* Set all breakpoints. *)
|
|
|
|
let set_breakpoints pos =
|
|
|
|
if !debug_breakpoints then
|
|
|
|
(print_string "Setting breakpoints..."; print_newline ());
|
|
|
|
List.iter
|
|
|
|
(function (pos, _) ->
|
|
|
|
if !debug_breakpoints then begin
|
|
|
|
print_int pos;
|
1997-05-19 08:42:21 -07:00
|
|
|
print_newline()
|
1996-11-29 08:55:09 -08:00
|
|
|
end;
|
|
|
|
set_breakpoint pos)
|
|
|
|
pos
|
|
|
|
|
|
|
|
(* Ensure the current version in installed in current checkpoint. *)
|
|
|
|
let update_breakpoints () =
|
1997-03-27 13:08:13 -08:00
|
|
|
if !debug_breakpoints then begin
|
|
|
|
prerr_string "Updating breakpoints... ";
|
|
|
|
prerr_int !current_checkpoint.c_breakpoint_version;
|
|
|
|
prerr_string " ";
|
|
|
|
prerr_int !current_version;
|
|
|
|
prerr_endline ""
|
|
|
|
end;
|
1996-11-29 08:55:09 -08:00
|
|
|
if !current_checkpoint.c_breakpoint_version <> !current_version then
|
1997-11-13 01:04:16 -08:00
|
|
|
Exec.protect
|
1996-11-29 08:55:09 -08:00
|
|
|
(function () ->
|
|
|
|
remove_breakpoints !current_checkpoint.c_breakpoints;
|
|
|
|
set_breakpoints !positions;
|
|
|
|
copy_breakpoints ())
|
|
|
|
|
|
|
|
let change_version version pos =
|
1997-11-13 01:04:16 -08:00
|
|
|
Exec.protect
|
1996-11-29 08:55:09 -08:00
|
|
|
(function () ->
|
|
|
|
current_version := version;
|
|
|
|
positions := pos)
|
2010-01-22 04:48:24 -08:00
|
|
|
|
1996-11-29 08:55:09 -08:00
|
|
|
(* Execute given function with no breakpoint in current checkpoint. *)
|
|
|
|
(* --- `goto' runs faster this way (does not stop on each breakpoint). *)
|
|
|
|
let execute_without_breakpoints f =
|
|
|
|
let version = !current_version
|
|
|
|
and pos = !positions
|
|
|
|
in
|
|
|
|
change_version 0 [];
|
|
|
|
try
|
|
|
|
f ();
|
|
|
|
change_version version pos
|
|
|
|
with
|
|
|
|
x ->
|
|
|
|
change_version version pos
|
|
|
|
|
|
|
|
(* Add a position in the position list. *)
|
|
|
|
(* Change version if necessary. *)
|
|
|
|
let insert_position pos =
|
|
|
|
try
|
|
|
|
incr (List.assoc pos !positions)
|
|
|
|
with
|
|
|
|
Not_found ->
|
|
|
|
positions := (pos, ref 1) :: !positions;
|
|
|
|
new_version ()
|
|
|
|
|
|
|
|
(* Remove a position in the position list. *)
|
|
|
|
(* Change version if necessary. *)
|
|
|
|
let remove_position pos =
|
|
|
|
let count = List.assoc pos !positions in
|
|
|
|
decr count;
|
|
|
|
if !count = 0 then begin
|
2009-05-20 04:52:42 -07:00
|
|
|
positions := List.remove_assoc pos !positions;
|
1997-03-27 13:08:13 -08:00
|
|
|
new_version ()
|
1996-11-29 08:55:09 -08:00
|
|
|
end
|
|
|
|
|
|
|
|
(* Insert a new breakpoint in lists. *)
|
1997-03-30 11:42:12 -08:00
|
|
|
let rec new_breakpoint =
|
|
|
|
function
|
|
|
|
{ev_repr = Event_child pc} ->
|
|
|
|
new_breakpoint (Symbols.any_event_at_pc !pc)
|
|
|
|
| event ->
|
1997-11-13 01:04:16 -08:00
|
|
|
Exec.protect
|
1997-03-30 11:42:12 -08:00
|
|
|
(function () ->
|
|
|
|
incr breakpoint_number;
|
|
|
|
insert_position event.ev_pos;
|
|
|
|
breakpoints := (!breakpoint_number, event) :: !breakpoints);
|
2012-10-17 05:26:42 -07:00
|
|
|
printf "Breakpoint %d at %d: %s" !breakpoint_number event.ev_pos
|
2003-11-21 08:10:57 -08:00
|
|
|
(Pos.get_desc event);
|
1997-03-30 11:42:12 -08:00
|
|
|
print_newline ()
|
1996-11-29 08:55:09 -08:00
|
|
|
|
|
|
|
(* Remove a breakpoint from lists. *)
|
|
|
|
let remove_breakpoint number =
|
|
|
|
try
|
2005-08-23 13:16:43 -07:00
|
|
|
let ev = List.assoc number !breakpoints in
|
|
|
|
let pos = ev.ev_pos in
|
1997-11-13 01:04:16 -08:00
|
|
|
Exec.protect
|
1997-05-19 08:42:21 -07:00
|
|
|
(function () ->
|
2009-05-20 04:52:42 -07:00
|
|
|
breakpoints := List.remove_assoc number !breakpoints;
|
2005-08-23 13:16:43 -07:00
|
|
|
remove_position pos;
|
2012-10-17 05:26:42 -07:00
|
|
|
printf "Removed breakpoint %d at %d: %s" number ev.ev_pos
|
2005-08-23 13:16:43 -07:00
|
|
|
(Pos.get_desc ev);
|
|
|
|
print_newline ()
|
|
|
|
)
|
1996-11-29 08:55:09 -08:00
|
|
|
with
|
|
|
|
Not_found ->
|
|
|
|
prerr_endline ("No breakpoint number " ^ (string_of_int number) ^ ".");
|
|
|
|
raise Not_found
|
|
|
|
|
|
|
|
let remove_all_breakpoints () =
|
|
|
|
List.iter (function (number, _) -> remove_breakpoint number) !breakpoints
|
|
|
|
|
|
|
|
(*** Temporary breakpoints. ***)
|
|
|
|
|
|
|
|
(* Temporary breakpoint position. *)
|
|
|
|
let temporary_breakpoint_position = ref (None : int option)
|
|
|
|
|
|
|
|
(* Execute `funct' with a breakpoint added at `pc'. *)
|
|
|
|
(* --- Used by `finish'. *)
|
|
|
|
let exec_with_temporary_breakpoint pc funct =
|
|
|
|
let previous_version = !current_version in
|
|
|
|
let remove () =
|
|
|
|
temporary_breakpoint_position := None;
|
|
|
|
current_version := previous_version;
|
|
|
|
let count = List.assoc pc !positions in
|
|
|
|
decr count;
|
|
|
|
if !count = 0 then begin
|
2009-05-20 04:52:42 -07:00
|
|
|
positions := List.remove_assoc pc !positions;
|
1996-11-29 08:55:09 -08:00
|
|
|
reset_instr pc;
|
1998-11-12 06:51:27 -08:00
|
|
|
Symbols.set_event_at_pc pc
|
1997-05-19 08:42:21 -07:00
|
|
|
end
|
1996-11-29 08:55:09 -08:00
|
|
|
|
|
|
|
in
|
1997-11-13 01:04:16 -08:00
|
|
|
Exec.protect (function () -> insert_position pc);
|
1996-11-29 08:55:09 -08:00
|
|
|
temporary_breakpoint_position := Some pc;
|
|
|
|
try
|
|
|
|
funct ();
|
1997-11-13 01:04:16 -08:00
|
|
|
Exec.protect remove
|
1996-11-29 08:55:09 -08:00
|
|
|
with
|
|
|
|
x ->
|
1997-11-13 01:04:16 -08:00
|
|
|
Exec.protect remove;
|
1996-11-29 08:55:09 -08:00
|
|
|
raise x
|