summaryrefslogtreecommitdiff
path: root/debugger/time_travel.ml
blob: b05d05767b7cf8819d30962bf40627ef0e7f3084 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
563
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
603
604
605
606
607
608
609
610
611
612
613
614
615
616
617
618
619
620
621
622
623
624
625
626
627
628
629
630
631
632
633
634
635
636
637
638
639
640
641
642
643
644
645
646
647
648
649
650
651
652
653
654
655
656
657
658
659
660
661
662
663
664
665
666
667
668
669
670
671
672
673
674
675
676
677
678
679
680
681
682
683
(**************************************************************************)
(*                                                                        *)
(*                                 OCaml                                  *)
(*                                                                        *)
(*           Jerome Vouillon, projet Cristal, INRIA Rocquencourt          *)
(*           OCaml port by John Malecki and Xavier Leroy                  *)
(*                                                                        *)
(*   Copyright 1996 Institut National de Recherche en Informatique et     *)
(*     en Automatique.                                                    *)
(*                                                                        *)
(*   All rights reserved.  This file is distributed under the terms of    *)
(*   the GNU Lesser General Public License version 2.1, with the          *)
(*   special exception on linking described in the file LICENSE.          *)
(*                                                                        *)
(**************************************************************************)

(**************************** Time travel ******************************)

open Int64ops
open Instruct
open Events
open Debugcom
open Primitives
open Checkpoints
open Breakpoints
open Trap_barrier
open Input_handling
open Debugger_config
open Program_loading
open Question

exception Current_checkpoint_lost
exception Current_checkpoint_lost_start_at of int64 * int64

let remove_1st key list =
  let rec remove =
    function
      []   -> []
    | a::l -> if a == key then l else a::(remove l)
  in
    remove list

(*** Debugging. ***)

let debug_time_travel = ref false

(*** Internal utilities. ***)

(* Insert a checkpoint in the checkpoint list.
 * Raise `Exit' if there is already a checkpoint at the same time.
 *)
let insert_checkpoint ({c_time = time} as checkpoint) =
  let rec traverse =
    function
      [] -> [checkpoint]
    | (({c_time = t} as a)::l) as l' ->
        if t > time then
          a::(traverse l)
        else if t = time then
          raise Exit
        else
          checkpoint::l'
  in
    checkpoints := traverse !checkpoints

(* Remove a checkpoint from the checkpoint list.
 * --- No error if not found.
 *)
let remove_checkpoint checkpoint =
  checkpoints := remove_1st checkpoint !checkpoints

(* Wait for the process used by `checkpoint' to connect.
 * --- Usually not called (the process is already connected).
 *)
let wait_for_connection checkpoint =
  try
    Exec.unprotect
      (function () ->
         let old_controller = Input_handling.current_controller !connection in
           execute_with_other_controller
             (function
                fd ->
                  old_controller fd;
                  if checkpoint.c_valid = true then
                    exit_main_loop ())
             !connection
             main_loop)
  with
    Sys.Break ->
      checkpoint.c_parent <- root;
      remove_checkpoint checkpoint;
      checkpoint.c_pid <- -1;
      raise Sys.Break

(* Select a checkpoint as current. *)
let set_current_checkpoint checkpoint =
  if !debug_time_travel then
    prerr_endline ("Select: " ^ (Int.to_string checkpoint.c_pid));
  if not checkpoint.c_valid then
    wait_for_connection checkpoint;
  current_checkpoint := checkpoint;
  let dead_frags = List.filter (fun frag ->
      not (List.mem frag checkpoint.c_code_fragments))
    (Symbols.code_fragments ())
  in
  List.iter Symbols.erase_symbols dead_frags;
  set_current_connection checkpoint.c_fd

(* Kill `checkpoint'. *)
let kill_checkpoint checkpoint =
  if !debug_time_travel then
    prerr_endline ("Kill: " ^ (Int.to_string checkpoint.c_pid));
  if checkpoint.c_pid > 0 then          (* Ghosts don't have to be killed ! *)
    (if not checkpoint.c_valid then
       wait_for_connection checkpoint;
     stop checkpoint.c_fd;
     if checkpoint.c_parent.c_pid > 0 then
       wait_child checkpoint.c_parent.c_fd;
     checkpoint.c_parent <- root;
     close_io checkpoint.c_fd;
     remove_file checkpoint.c_fd;
     remove_checkpoint checkpoint);
  checkpoint.c_pid <- -1                (* Don't exist anymore *)

(*** Cleaning the checkpoint list. ***)

(* Separate checkpoints before (<=) and after (>) `t'. *)
(* ### t checkpoints -> (after, before) *)
let cut t =
  let rec cut_t =
    function
      [] -> ([], [])
    | ({c_time = t'} as a::l) as l' ->
        if t' <= t then
          ([], l')
        else
          let (b, e) = cut_t l in
            (a::b, e)
  in
    cut_t

(* Partition the checkpoints list. *)
let cut2 t0 t l =
  let rec cut2_t0 t =
    function
      [] -> []
    | l ->
       let (after, before) = cut (t0 -- t -- _1) l in
         let l = cut2_t0 (t ++ t) before in
           after::l
  in
    let (after, before) = cut (t0 -- _1) l in
      after::(cut2_t0 t before)

(* Separate first elements and last element of a list of checkpoints. *)
let chk_merge2 cont =
  let rec chk_merge2_cont =
    function
      [] -> cont
    | [a] ->
        let (accepted, rejected) = cont in
          (a::accepted, rejected)
    | a::l ->
        let (accepted, rejected) = chk_merge2_cont l in
          (accepted, a::rejected)
  in chk_merge2_cont

(* Separate the checkpoint list. *)
(* ### list -> accepted * rejected *)
let rec chk_merge =
  function
    [] -> ([], [])
  | l::tail ->
       chk_merge2 (chk_merge tail) l

let new_checkpoint_list checkpoint_count accepted rejected =
  if List.length accepted >= checkpoint_count then
    let (k, l) = list_truncate2 checkpoint_count accepted in
      (k, l @ rejected)
  else
    let (k, l) =
      list_truncate2 (checkpoint_count - List.length accepted) rejected
    in
      (List.merge (fun t1 t2 -> compare t2.c_time t1.c_time) accepted k,
       l)

(* Clean the checkpoint list. *)
(* Reference time is `time'. *)
let clean_checkpoints time checkpoint_count =
  let (after, before) = cut time !checkpoints in
    let (accepted, rejected) =
      chk_merge (cut2 time !checkpoint_small_step before)
    in
      let (kept, lost) =
        new_checkpoint_list checkpoint_count accepted after
      in
        List.iter kill_checkpoint (lost @ rejected);
        checkpoints := kept

(*** Internal functions for moving. ***)

(* Find the first checkpoint before (or at) `time'.
 * Ask for reloading the program if necessary.
 *)
let find_checkpoint_before time =
  let rec find =
    function
      [] ->
        print_string "Can't go that far in the past !"; print_newline ();
        if yes_or_no "Reload program" then begin
          load_program ();
          find !checkpoints
          end
        else
          raise Toplevel
    | { c_time = t } as a::l ->
        if t > time then
          find l
        else
          a
  in find !checkpoints

(* Make a copy of the current checkpoint and clean the checkpoint list. *)
(* --- The new checkpoint is not put in the list. *)
let duplicate_current_checkpoint () =
  let checkpoint = !current_checkpoint in
    if not checkpoint.c_valid then
      wait_for_connection checkpoint;
    let new_checkpoint =                        (* Ghost *)
      {c_time = checkpoint.c_time;
       c_pid = 0;
       c_fd = checkpoint.c_fd;
       c_valid = false;
       c_report = checkpoint.c_report;
       c_state = C_stopped;
       c_parent = checkpoint;
       c_breakpoint_version = checkpoint.c_breakpoint_version;
       c_breakpoints = checkpoint.c_breakpoints;
       c_trap_barrier = checkpoint.c_trap_barrier;
       c_code_fragments = checkpoint.c_code_fragments}
    in
      checkpoints := list_replace checkpoint new_checkpoint !checkpoints;
      set_current_checkpoint checkpoint;
      clean_checkpoints (checkpoint.c_time ++ _1) (!checkpoint_max_count - 1);
      if new_checkpoint.c_pid = 0 then  (* The ghost has not been killed *)
        (match do_checkpoint () with    (* Duplicate checkpoint *)
           Checkpoint_done pid ->
             (new_checkpoint.c_pid <- pid;
              if !debug_time_travel then
                prerr_endline ("Waiting for connection: " ^ Int.to_string pid))
         | Checkpoint_failed ->
             prerr_endline
               "A fork failed. Reducing maximum number of checkpoints.";
             checkpoint_max_count := List.length !checkpoints - 1;
             remove_checkpoint new_checkpoint)

(* Was the movement interrupted ? *)
(* --- An exception could have been used instead, *)
(* --- but it is not clear where it should be caught. *)
(* --- For instance, it should not be caught in `step' *)
(* --- (as `step' is used in `next_1'). *)
(* --- On the other side, other modules does not need to know *)
(* --- about this exception. *)
let interrupted = ref false

(* Information about last breakpoint encountered *)
let last_breakpoint = ref None

(* Last debug info loaded *)
let last_debug_info = ref None

let rec do_go_dynlink steps =
  match do_go steps with
  | { rep_type = Code_loaded frag; rep_event_count = steps } as report ->
    begin match !last_debug_info with
    | Some di ->
      Symbols.add_symbols frag di;
      Symbols.set_all_events frag;
      last_debug_info := None
    | None -> assert false
    end;
    if !break_on_load then report
    else do_go_dynlink steps
  | { rep_type = Code_unloaded frag; rep_event_count = steps } ->
    Symbols.erase_symbols frag;
    do_go_dynlink steps
  | { rep_type = Debug_info di; rep_event_count = steps } ->
    last_debug_info := Some (Array.to_list di);
    do_go_dynlink steps
  | report -> report

(* Ensure we stop on an event. *)
let rec stop_on_event report =
  match report with
    {rep_type = Breakpoint; rep_program_pointer = pc;
     rep_stack_pointer = sp} ->
      last_breakpoint := Some (pc, sp);
      Symbols.update_current_event ();
      begin match !current_event with
        None   -> find_event ()
      | Some _ -> ()
      end
  | {rep_type = Trap_barrier} ->
      (* No event at current position. *)
      find_event ()
  | _ ->
      ()

and find_event () =
  if !debug_time_travel then begin
    print_string "Searching next event...";
    print_newline ()
  end;
  let report = do_go_dynlink _1 in
  !current_checkpoint.c_report <- Some report;
  stop_on_event report

(* Internal function for running debugged program.
 * Requires `duration > 0'.
 *)
let internal_step duration =
  match current_report () with
    Some {rep_type = Exited | Uncaught_exc} -> ()
  | _ ->
      Exec.protect
        (function () ->
           if !make_checkpoints then
             duplicate_current_checkpoint ()
           else
             remove_checkpoint !current_checkpoint;
           update_breakpoints ();
           update_trap_barrier ();
           !current_checkpoint.c_state <- C_running duration;
           let report = do_go_dynlink duration in
             !current_checkpoint.c_report <- Some report;
             !current_checkpoint.c_state <- C_stopped;
             !current_checkpoint.c_code_fragments <- Symbols.code_fragments ();
             if report.rep_type = Event then begin
               !current_checkpoint.c_time <-
                 !current_checkpoint.c_time ++ duration;
               interrupted := false;
               last_breakpoint := None
               end
             else begin
               !current_checkpoint.c_time <-
                  !current_checkpoint.c_time ++ duration
                  -- report.rep_event_count ++ _1;
               interrupted := true;
               last_breakpoint := None;
               stop_on_event report
               end;
             (try
                insert_checkpoint !current_checkpoint
              with
                Exit ->
                  kill_checkpoint !current_checkpoint;
                  set_current_checkpoint
                    (find_checkpoint_before (current_time ()))));
        if !debug_time_travel then begin
          print_string "Checkpoints: pid(time)"; print_newline ();
          List.iter
            (function {c_time = time; c_pid = pid; c_valid = valid} ->
              Printf.printf "%d(%Ld)%s " pid time
                            (if valid then "" else "(invalid)"))
            !checkpoints;
          print_newline ()
        end

(*** Miscellaneous functions (exported). ***)

(* Create a checkpoint at time 0 (new program). *)
let new_checkpoint pid fd =
  let new_checkpoint =
    {c_time = _0;
     c_pid = pid;
     c_fd = fd;
     c_valid = true;
     c_report = None;
     c_state = C_stopped;
     c_parent = root;
     c_breakpoint_version = 0;
     c_breakpoints = [];
     c_trap_barrier = Sp.null;
     c_code_fragments = [main_frag]}
  in
    insert_checkpoint new_checkpoint

(* Set the file descriptor of a checkpoint *)
(* (a new process has connected with the debugger). *)
(* --- Return `true' on success (close the connection otherwise). *)
let set_file_descriptor pid fd =
  let rec find =
    function
      [] ->
        prerr_endline "Unexpected connection";
        close_io fd;
        false
    | ({c_pid = pid'} as checkpoint)::l ->
        if pid <> pid' then
          find l
        else
          (checkpoint.c_fd <- fd;
           checkpoint.c_valid <- true;
           true)
  in
    if !debug_time_travel then
      prerr_endline ("New connection: " ^(Int.to_string pid));
    find (!current_checkpoint::!checkpoints)

(* Kill all the checkpoints. *)
let kill_all_checkpoints () =
  List.iter kill_checkpoint (!current_checkpoint::!checkpoints)

(* Kill a checkpoint without killing the process. *)
(* (used when connection with the process is lost). *)
(* --- Assume that the checkpoint is valid. *)
let forget_process fd pid =
  let checkpoint =
    List.find (function c -> c.c_pid = pid) (!current_checkpoint::!checkpoints)
  in
  if pid > 0 then begin
    Printf.eprintf "Lost connection with process %d" pid;
    let kont =
      if checkpoint == !current_checkpoint then begin
        Printf.eprintf " (active process)\n";
        match !current_checkpoint.c_state with
          C_stopped ->
            Printf.eprintf "at time %Ld" !current_checkpoint.c_time;
            fun () -> raise Current_checkpoint_lost
        | C_running duration ->
            Printf.eprintf "between time %Ld and time %Ld"
                          !current_checkpoint.c_time
                          (!current_checkpoint.c_time ++ duration);
            fun () -> raise (Current_checkpoint_lost_start_at
                              (!current_checkpoint.c_time, duration))
        end
      else ignore in
    Printf.eprintf "\n"; flush stderr;
    Input_handling.remove_file fd;
    close_io checkpoint.c_fd;
    remove_file checkpoint.c_fd;
    remove_checkpoint checkpoint;
    checkpoint.c_pid <- -1;             (* Don't exist anymore *)
    if checkpoint.c_parent.c_pid > 0 then
      wait_child checkpoint.c_parent.c_fd;
    kont ()
  end

(* Try to recover when the current checkpoint is lost. *)
let recover () =
  set_current_checkpoint
    (find_checkpoint_before (current_time ()))

(*** Simple movements. ***)

(* Forward stepping.  Requires `duration >= 0'. *)
let rec step_forward duration =
  if duration > !checkpoint_small_step then begin
    let first_step =
      if duration > !checkpoint_big_step then
        !checkpoint_big_step
      else
        !checkpoint_small_step
    in
      internal_step first_step;
      if not !interrupted then
        step_forward (duration -- first_step)
    end
  else if duration != _0 then
    internal_step duration

(* Go to time `time' from current checkpoint (internal). *)
let internal_go_to time =
  let duration = time -- (current_time ()) in
    if duration > _0 then
      execute_without_breakpoints (function () -> step_forward duration)

(* Move to a given time. *)
let go_to time =
  let checkpoint = find_checkpoint_before time in
    set_current_checkpoint checkpoint;
    internal_go_to time

(* Return the time of the last breakpoint *)
(* between current time and `max_time'. *)
let find_last_breakpoint max_time =
  let rec find break =
    let time = current_time () in
    step_forward (max_time -- time);
    match !last_breakpoint, !temporary_breakpoint_position with
      (Some _, _) when current_time () < max_time ->
        find !last_breakpoint
    | (Some (pc, _), Some pc') when pc = pc' ->
        (max_time, !last_breakpoint)
    | _ ->
        (time, break)
  in
    find
      (match current_pc_sp () with
         (Some (pc, _)) as state when breakpoint_at_pc pc -> state
       | _                                                -> None)

(* Run from `time_max' back to `time'. *)
(* --- Assume 0 <= time < time_max *)
let rec back_to time time_max =
  let
    {c_time = t} = find_checkpoint_before (pre64 time_max)
  in
    go_to (Int64.max time t);
    let (new_time, break) = find_last_breakpoint time_max in
    if break <> None || (new_time <= time) then begin
      go_to new_time;
      interrupted := break <> None;
      last_breakpoint := break
    end else
      back_to time new_time

(* Backward stepping. *)
(* --- Assume duration > 1 *)
let step_backward duration =
  let time = current_time () in
    if time > _0 then
      back_to (Int64.max _0 (time -- duration)) time

(* Run the program from current time. *)
(* Stop at the first breakpoint, or at the end of the program. *)
let rec run () =
  internal_step !checkpoint_big_step;
  if not !interrupted then
    run ()

(* Run the program backward from current time. *)
(* Stop at the first breakpoint, or at the beginning of the program. *)
let back_run () =
  if current_time () > _0 then
    back_to _0 (current_time ())

(* Step in any direction. *)
(* Stop at the first breakpoint, or after `duration' steps. *)
let step duration =
  if duration >= _0 then
    step_forward duration
  else
    step_backward (_0 -- duration)

(*** Next, finish. ***)

(* Finish current function. *)
let finish () =
  Symbols.update_current_event ();
  match !current_event with
    None ->
      prerr_endline "`finish' not meaningful in outermost frame.";
      raise Toplevel
  | Some {ev_ev={ev_stacksize}} ->
      set_initial_frame();
      let (frame, pc) = up_frame ev_stacksize in
      if frame = Sp.null then begin
        prerr_endline "`finish' not meaningful in outermost frame.";
        raise Toplevel
      end;
      begin
        try ignore(Symbols.any_event_at_pc pc)
        with Not_found ->
               prerr_endline "Calling function has no debugging information.";
               raise Toplevel
      end;
      exec_with_trap_barrier
        frame
        (fun () ->
           exec_with_temporary_breakpoint
             pc
             (fun () ->
                while
                  run ();
                  match !last_breakpoint with
                    Some (pc', frame') when pc = pc' ->
                      interrupted := false;
                      frame <> frame'
                  | _ ->
                      false
                do
                  ()
                done))

let next_1 () =
  Symbols.update_current_event ();
  match !current_event with
    None ->                             (* Beginning of the program. *)
      step _1
  | Some {ev_ev={ev_stacksize=ev_stacksize1}} ->
      let (frame1, _pc1) = initial_frame() in
      step _1;
      if not !interrupted then begin
        Symbols.update_current_event ();
        match !current_event with
          None -> ()
        | Some {ev_ev={ev_stacksize=ev_stacksize2}} ->
            let (frame2, _pc2) = initial_frame() in
            (* Call `finish' if we've entered a function. *)
            if frame1 <> Sp.null && frame2 <> Sp.null &&
               Sp.(compare (base frame2 ev_stacksize2)
                     (base frame1 ev_stacksize1)) > 0
            then finish()
      end

(* Same as `step' (forward) but skip over function calls. *)
let rec next =
  function
    0 -> ()
  | n ->
      next_1 ();
      if not !interrupted then
        next (n - 1)

(* Run backward until just before current function. *)
let start () =
  Symbols.update_current_event ();
  match !current_event with
    None ->
      prerr_endline "`start not meaningful in outermost frame.";
      raise Toplevel
  | Some {ev_ev={ev_stacksize}} ->
      let (frame, _) = initial_frame() in
      let (frame', pc) = up_frame ev_stacksize in
      if frame' = Sp.null then begin
        prerr_endline "`start not meaningful in outermost frame.";
        raise Toplevel
      end;
      let nargs =
        match
          try Symbols.any_event_at_pc pc with Not_found ->
            prerr_endline "Calling function has no debugging information.";
            raise Toplevel
        with
          {ev_ev = {ev_info = Event_return nargs}} -> nargs
        | _ ->  Misc.fatal_error "Time_travel.start"
      in
      let offset = if nargs < 4 then 1 else 2 in
      let pc = { pc with pos = pc.pos - 4 * offset } in
      while
        exec_with_temporary_breakpoint pc back_run;
        match !last_breakpoint with
          Some (pc', frame') when pc = pc' ->
            step _minus1;
            (not !interrupted)
              &&
            Sp.(compare (base frame' nargs) (base frame ev_stacksize)) > 0
        | _ ->
            false
      do
        ()
      done

let previous_1 () =
  Symbols.update_current_event ();
  match !current_event with
    None ->                             (* End of the program. *)
      step _minus1
  | Some {ev_ev={ev_stacksize=ev_stacksize1}} ->
      let (frame1, _pc1) = initial_frame() in
      step _minus1;
      if not !interrupted then begin
        Symbols.update_current_event ();
        match !current_event with
          None -> ()
        | Some {ev_ev={ev_stacksize=ev_stacksize2}} ->
            let (frame2, _pc2) = initial_frame() in
            (* Call `start' if we've entered a function. *)
            if frame1 <> Sp.null && frame2 <> Sp.null &&
              Sp.(compare (base frame2 ev_stacksize2)
                    (base frame1 ev_stacksize1)) > 0
            then start()
      end

(* Same as `step' (backward) but skip over function calls. *)
let rec previous =
  function
    0 -> ()
  | n ->
      previous_1 ();
      if not !interrupted then
        previous (n - 1)