1(**************************************************************************)
2(*                                                                        *)
3(*                                 OCaml                                  *)
4(*                                                                        *)
5(*           Jerome Vouillon, projet Cristal, INRIA Rocquencourt          *)
6(*           OCaml port by John Malecki and Xavier Leroy                  *)
7(*                                                                        *)
8(*   Copyright 1996 Institut National de Recherche en Informatique et     *)
9(*     en Automatique.                                                    *)
10(*                                                                        *)
11(*   All rights reserved.  This file is distributed under the terms of    *)
12(*   the GNU Lesser General Public License version 2.1, with the          *)
13(*   special exception on linking described in the file LICENSE.          *)
14(*                                                                        *)
15(**************************************************************************)
16
17(***************************** Checkpoints *****************************)
18
19open Primitives
20open Debugcom
21
22(*** A type for checkpoints. ***)
23
24type checkpoint_state =
25    C_stopped
26  | C_running of int64
27
28(* `c_valid' is true if and only if the corresponding
29 * process is connected to the debugger.
30 * `c_parent' is the checkpoint whose process is parent
31 * of the checkpoint one (`root' if no parent).
32 * c_pid =  2 for root pseudo-checkpoint.
33 * c_pid =  0 for ghost checkpoints.
34 * c_pid = -1 for kill checkpoints.
35 *)
36type checkpoint =
37  {mutable c_time : int64;
38   mutable c_pid : int;
39   mutable c_fd : io_channel;
40   mutable c_valid : bool;
41   mutable c_report : report option;
42   mutable c_state : checkpoint_state;
43   mutable c_parent : checkpoint;
44   mutable c_breakpoint_version : int;
45   mutable c_breakpoints : (int * int ref) list;
46   mutable c_trap_barrier : int}
47
48(*** Pseudo-checkpoint `root'. ***)
49(* --- Parents of all checkpoints which have no parent. *)
50val root : checkpoint
51
52(*** Current state ***)
53val checkpoints : checkpoint list ref
54val current_checkpoint : checkpoint ref
55
56val current_time : unit -> int64
57val current_report : unit -> report option
58val current_pc : unit -> int option
59val current_pc_sp : unit -> (int * int) option
60