summaryrefslogtreecommitdiffstats
path: root/debugger/show_source.ml
diff options
context:
space:
mode:
Diffstat (limited to 'debugger/show_source.ml')
-rw-r--r--debugger/show_source.ml80
1 files changed, 80 insertions, 0 deletions
diff --git a/debugger/show_source.ml b/debugger/show_source.ml
new file mode 100644
index 000000000..86e26ac47
--- /dev/null
+++ b/debugger/show_source.ml
@@ -0,0 +1,80 @@
+(***********************************************************************)
+(* *)
+(* Objective Caml *)
+(* *)
+(* Jerome Vouillon, projet Cristal, INRIA Rocquencourt *)
+(* Objective Caml port by John Malecki and Xavier Leroy *)
+(* *)
+(* Copyright 1996 Institut National de Recherche en Informatique et *)
+(* Automatique. Distributed only by permission. *)
+(* *)
+(***********************************************************************)
+
+(* $Id$ *)
+
+open Debugger_config
+open Parameters
+open Misc
+open Primitives
+open Source
+
+(* Print a line; return the beginning of the next line *)
+let print_line buffer line_number start point before =
+ let next = next_linefeed buffer start
+ and content = buffer_content buffer
+ in
+ print_int line_number;
+ print_string " ";
+ if (point <= next) & (point >= start) then
+ (print_string (String.sub content start (point - start));
+ print_string (if before then event_mark_before else event_mark_after);
+ print_string (String.sub content point (next - point)))
+ else
+ print_string (String.sub content start (next - start));
+ print_newline ();
+ next
+
+(* Tell Emacs we are nowhere in the source. *)
+let show_no_point () =
+ if !emacs then begin
+ print_string "\026\026H";
+ print_newline ()
+ end
+
+(* Print the line containing the point *)
+let show_point mdle point before selected =
+ if !emacs & selected then begin
+ let source = source_of_module mdle in
+ print_string "\026\026M";
+ print_string source;
+ print_string ":";
+ print_int point;
+ print_string (if before then ":before" else ":after");
+ print_newline ()
+ end
+ else begin
+ try
+ let buffer = get_buffer mdle in
+ let (start, line_number) = line_of_pos buffer point in
+ print_line buffer line_number start point before; ()
+ with
+ Out_of_range ->
+ prerr_endline "Position out of range."
+ | Not_found ->
+ prerr_endline ("Cannot find " ^ mdle ^ ".")
+ end
+
+(* Display part of the source. *)
+let show_listing mdle start stop point before =
+ let buffer = get_buffer mdle in
+ try
+ let rec aff (line_start, line_number) =
+ if line_number <= stop then
+ aff (print_line buffer line_number line_start point before + 1, line_number + 1)
+ in
+ aff (pos_of_line buffer start)
+ with
+ Out_of_range ->
+ prerr_endline "Position out of range."
+ | Not_found ->
+ prerr_endline ("Cannot find " ^ mdle ^ ".")