Skip to content

Commit

Permalink
use a map file to hide the module aliases
Browse files Browse the repository at this point in the history
  • Loading branch information
gasche committed May 31, 2020
1 parent 647b416 commit fddb0f9
Show file tree
Hide file tree
Showing 19 changed files with 128 additions and 66 deletions.
132 changes: 115 additions & 17 deletions debugger/.depend

Large diffs are not rendered by default.

19 changes: 13 additions & 6 deletions debugger/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@ LINKFLAGS=-linkall -I $(UNIXDIR) -I $(DYNLINKDIR)
YACCFLAGS=
CAMLLEX=$(BEST_OCAMLLEX)
CAMLDEP=$(BEST_OCAMLDEP)
DEPFLAGS=-slash
DEPFLAGS=-slash -map ocamldebug_map.mli
DEPINCLUDES=$(INCLUDES)

DIRECTORIES=$(UNIXDIR) $(DYNLINKDIR) $(addprefix $(ROOTDIR)/,\
Expand Down Expand Up @@ -74,14 +74,21 @@ clean::
.SUFFIXES:
.SUFFIXES: .ml .cmo .mli .cmi

.ml.cmo:
$(CAMLC) -c $(COMPFLAGS) $<
ocamldebug_map.cmi: ocamldebug_map.mli
$(CAMLC) -c -no-alias-deps $<

.mli.cmi:
$(CAMLC) -c $(COMPFLAGS) $<
.ml.cmo: ocamldebug_map.cmi
$(CAMLC) -c $(COMPFLAGS) -open Ocamldebug_map $<

.mli.cmi: ocamldebug_map.cmi
$(CAMLC) -c $(COMPFLAGS) -open Ocamldebug_map $<

depend: beforedepend
$(CAMLDEP) $(DEPFLAGS) $(DEPINCLUDES) *.mli *.ml \
# we need -as-map in the camldep invokation because ocamldebug_map.mli
# is one of the *.mli files; if we don't use -as-map here, it gets
# listed and depends on all other .cmi, which create cyclic
# dependencies.
$(CAMLDEP) $(DEPFLAGS) $(DEPINCLUDES) -open Ocamldebug_map -as-map *.mli *.ml \
| sed -e 's,$(UNIXDIR)/,$$(UNIXDIR)/,' > .depend

ocamldebug_lexer.ml: ocamldebug_lexer.mll
Expand Down
4 changes: 0 additions & 4 deletions debugger/ocamldebug_breakpoints.ml
Original file line number Diff line number Diff line change
Expand Up @@ -22,10 +22,6 @@ open Instruct
open Ocamldebug_events
open Printf

module Exec = Ocamldebug_exec
module Parameters = Ocamldebug_parameters
module Pos = Ocamldebug_pos
module Symbols = Ocamldebug_symbols

(*** Debugging. ***)
let debug_breakpoints = ref false
Expand Down
7 changes: 0 additions & 7 deletions debugger/ocamldebug_command_line.ml
Original file line number Diff line number Diff line change
Expand Up @@ -45,13 +45,6 @@ open Ocamldebug_checkpoints
open Ocamldebug_frames
open Ocamldebug_printval

module Eval = Ocamldebug_eval
module Events = Ocamldebug_events
module History = Ocamldebug_history
module Lexer = Ocamldebug_lexer
module Loadprinter = Ocamldebug_loadprinter
module Pos = Ocamldebug_pos
module Unix_tools = Ocamldebug_unix_tools

(** Instructions, variables and infos lists. **)
type dbg_instruction =
Expand Down
1 change: 0 additions & 1 deletion debugger/ocamldebug_debugcom.ml
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,6 @@
open Ocamldebug_int64ops
open Ocamldebug_primitives

module Input_handling = Ocamldebug_input_handling

(* The current connection with the debuggee *)

Expand Down
3 changes: 0 additions & 3 deletions debugger/ocamldebug_eval.ml
Original file line number Diff line number Diff line change
Expand Up @@ -21,9 +21,6 @@ open Types
open Ocamldebug_parser_aux
open Ocamldebug_events

module Debugcom = Ocamldebug_debugcom
module Frames = Ocamldebug_frames
module Printval = Ocamldebug_printval

type error =
Unbound_identifier of Ident.t
Expand Down
1 change: 0 additions & 1 deletion debugger/ocamldebug_frames.ml
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,6 @@ open Ocamldebug_debugcom
open Ocamldebug_events
open Ocamldebug_symbols

module Events = Ocamldebug_events

(* Current frame number *)
let current_frame = ref 0
Expand Down
1 change: 0 additions & 1 deletion debugger/ocamldebug_input_handling.ml
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,6 @@
open Unix
open Ocamldebug_primitives

module Parameters = Ocamldebug_parameters

(*** Actives files. ***)

Expand Down
2 changes: 0 additions & 2 deletions debugger/ocamldebug_loadprinter.ml
Original file line number Diff line number Diff line change
Expand Up @@ -19,8 +19,6 @@ open Misc
open Longident
open Types

module Parameters = Ocamldebug_parameters
module Printval = Ocamldebug_printval

(* Error report *)

Expand Down
4 changes: 0 additions & 4 deletions debugger/ocamldebug_main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -27,10 +27,6 @@ open Ocamldebug_show_information
open Format
open Ocamldebug_primitives

module Exec = Ocamldebug_exec
module Loadprinter = Ocamldebug_loadprinter
module Parameters = Ocamldebug_parameters
module Unix_tools = Ocamldebug_unix_tools

let line_buffer = Lexing.from_function read_user_input

Expand Down
1 change: 0 additions & 1 deletion debugger/ocamldebug_printval.ml
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,6 @@ open Format
open Ocamldebug_parser_aux
open Types

module Debugcom = Ocamldebug_debugcom

(* To name printed and ellipsed values *)

Expand Down
2 changes: 0 additions & 2 deletions debugger/ocamldebug_program_loading.ml
Original file line number Diff line number Diff line change
Expand Up @@ -21,8 +21,6 @@ open Ocamldebug_config
open Ocamldebug_parameters
open Ocamldebug_input_handling

module Primitives = Ocamldebug_primitives
module Unix_tools = Ocamldebug_unix_tools

(*** Debugging. ***)

Expand Down
4 changes: 0 additions & 4 deletions debugger/ocamldebug_program_management.ml
Original file line number Diff line number Diff line change
Expand Up @@ -27,10 +27,6 @@ open Ocamldebug_question
open Ocamldebug_program_loading
open Ocamldebug_time_travel

module Breakpoints = Ocamldebug_breakpoints
module History = Ocamldebug_history
module Input_handling = Ocamldebug_input_handling
module Symbols = Ocamldebug_symbols

(*** Connection opening and control. ***)

Expand Down
1 change: 0 additions & 1 deletion debugger/ocamldebug_question.ml
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,6 @@

open Ocamldebug_input_handling
open Ocamldebug_primitives
module Lexer = Ocamldebug_lexer

(* Ask user a yes or no question. *)
let yes_or_no message =
Expand Down
5 changes: 0 additions & 5 deletions debugger/ocamldebug_show_information.ml
Original file line number Diff line number Diff line change
Expand Up @@ -26,11 +26,6 @@ open Ocamldebug_show_source
open Ocamldebug_breakpoints
open Ocamldebug_parameters

module Debugcom = Ocamldebug_debugcom
module Events = Ocamldebug_events
module Parameters = Ocamldebug_parameters
module Printval = Ocamldebug_printval
module Symbols = Ocamldebug_symbols

(* Display information about the current event. *)
let show_current_event ppf =
Expand Down
1 change: 0 additions & 1 deletion debugger/ocamldebug_show_source.ml
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,6 @@ open Ocamldebug_primitives
open Printf
open Ocamldebug_source

module Events = Ocamldebug_events

(* Print a line; return the beginning of the next line *)
let print_line buffer line_number start point before =
Expand Down
2 changes: 0 additions & 2 deletions debugger/ocamldebug_symbols.ml
Original file line number Diff line number Diff line change
Expand Up @@ -23,8 +23,6 @@ open Ocamldebug_debugcom
open Ocamldebug_events
module String = Misc.Stdlib.String

module Checkpoints = Ocamldebug_checkpoints
module Events = Ocamldebug_events

let modules =
ref ([] : string list)
Expand Down
3 changes: 0 additions & 3 deletions debugger/ocamldebug_time_travel.ml
Original file line number Diff line number Diff line change
Expand Up @@ -29,9 +29,6 @@ open Ocamldebug_config
open Ocamldebug_program_loading
open Ocamldebug_question

module Exec = Ocamldebug_exec
module Input_handling = Ocamldebug_input_handling
module Symbols = Ocamldebug_symbols

exception Current_checkpoint_lost
exception Current_checkpoint_lost_start_at of int64 * int64
Expand Down
1 change: 0 additions & 1 deletion debugger/ocamldebug_trap_barrier.ml
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,6 @@
open Ocamldebug_debugcom
open Ocamldebug_checkpoints

module Exec = Ocamldebug_exec

let current_trap_barrier = ref 0

Expand Down

0 comments on commit fddb0f9

Please sign in to comment.