]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/debugger/show_source.ml
update
[l4.git] / l4 / pkg / ocaml / contrib / debugger / show_source.ml
1 (***********************************************************************)
2 (*                                                                     *)
3 (*                           Objective Caml                            *)
4 (*                                                                     *)
5 (*          Jerome Vouillon, projet Cristal, INRIA Rocquencourt        *)
6 (*          Objective Caml port by John Malecki and Xavier Leroy       *)
7 (*                                                                     *)
8 (*  Copyright 1996 Institut National de Recherche en Informatique et   *)
9 (*  en Automatique.  All rights reserved.  This file is distributed    *)
10 (*  under the terms of the Q Public License version 1.0.               *)
11 (*                                                                     *)
12 (***********************************************************************)
13
14 (* $Id: show_source.ml 9299 2009-06-17 08:15:39Z xclerc $ *)
15
16 open Debugger_config
17 open Instruct
18 open Parameters
19 open Primitives
20 open Printf
21 open Source
22
23 (* Print a line; return the beginning of the next line *)
24 let print_line buffer line_number start point before =
25   let next = next_linefeed buffer start
26   and content = buffer_content buffer
27   in
28     printf "%i " line_number;
29     if point <= next && point >= start then
30       (print_string (String.sub content start (point - start));
31        print_string (if before then event_mark_before else event_mark_after);
32        print_string (String.sub content point (next - point)))
33     else
34       print_string (String.sub content start (next - start));
35     print_newline ();
36     next
37
38 (* Tell Emacs we are nowhere in the source. *)
39 let show_no_point () =
40   if !emacs then printf "\026\026H\n"
41
42 (* Print the line containing the point *)
43 let show_point ev selected =
44   let mdle = ev.ev_module in
45   let before = (ev.ev_kind = Event_before) in
46   if !emacs && selected then
47     begin try
48       let buffer = get_buffer (Events.get_pos ev) mdle in
49       let source = source_of_module ev.ev_loc.Location.loc_start mdle in
50       printf "\026\026M%s:%i:%i" source
51         (snd (start_and_cnum buffer ev.ev_loc.Location.loc_start))
52         (snd (start_and_cnum buffer ev.ev_loc.Location.loc_end));
53       printf "%s\n" (if before then ":before" else ":after")
54     with
55       Out_of_range -> (* point_of_coord *)
56         prerr_endline "Position out of range."
57     | Not_found    -> (* Events.get_pos || get_buffer *)
58         prerr_endline ("No source file for " ^ mdle ^ ".");
59         show_no_point ()
60     end
61   else
62     begin try
63       let pos = Events.get_pos ev in
64       let buffer = get_buffer pos mdle in
65       let start, point = start_and_cnum buffer pos in
66       ignore(print_line buffer pos.Lexing.pos_lnum start point before)
67     with
68       Out_of_range -> (* point_of_coord *)
69         prerr_endline "Position out of range."
70     | Not_found    -> (* Events.get_pos || get_buffer *)
71         prerr_endline ("No source file for " ^ mdle ^ ".")
72     end
73
74 (* Display part of the source. *)
75 let show_listing pos mdle start stop point before =
76   try
77     let buffer = get_buffer pos mdle in
78       let rec aff (line_start, line_number) =
79         if line_number <= stop then
80           aff (print_line buffer line_number line_start point before + 1, line_number + 1)
81       in
82         aff (pos_of_line buffer start)
83   with
84     Out_of_range -> (* pos_of_line *)
85       prerr_endline "Position out of range."
86   | Not_found    -> (* get_buffer *)
87       prerr_endline ("No source file for " ^ mdle ^ ".")