Skip to content

Commit 6f0e673

Browse files
committed
More warnings for debugger/.
1 parent b8e418e commit 6f0e673

19 files changed

+48
-61
lines changed

debugger/Makefile.shared

+1-1
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,7 @@ CAMLRUN ?= ../boot/ocamlrun
1818
CAMLYACC ?= ../boot/ocamlyacc
1919

2020
CAMLC=$(CAMLRUN) ../ocamlc -nostdlib -I ../stdlib
21-
COMPFLAGS=-warn-error A -safe-string $(INCLUDES)
21+
COMPFLAGS=$(INCLUDES) -absname -w +a-4-9-41-42-44-45-48 -warn-error A -safe-string -strict-sequence -strict-formats
2222
LINKFLAGS=-linkall -I $(UNIXDIR)
2323
YACCFLAGS=
2424
CAMLLEX=$(CAMLRUN) ../boot/ocamllex

debugger/breakpoints.ml

+1-2
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,6 @@
1919
open Checkpoints
2020
open Debugcom
2121
open Instruct
22-
open Primitives
2322
open Printf
2423

2524
(*** Debugging. ***)
@@ -137,7 +136,7 @@ let execute_without_breakpoints f =
137136
f ();
138137
change_version version pos
139138
with
140-
x ->
139+
_ ->
141140
change_version version pos
142141

143142
(* Add a position in the position list. *)

debugger/breakpoints.mli

-1
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,6 @@
1616

1717
(******************************* Breakpoints ***************************)
1818

19-
open Primitives
2019
open Instruct
2120

2221
(*** Debugging. ***)

debugger/command_line.ml

+17-17
Original file line numberDiff line numberDiff line change
@@ -179,7 +179,7 @@ let interprete_line ppf line =
179179
i.instr_action ppf lexbuf;
180180
resume_user_input ();
181181
i.instr_repeat
182-
| l ->
182+
| _ ->
183183
error "Ambiguous command."
184184
end
185185
| None ->
@@ -216,7 +216,7 @@ let line_loop ppf line_buffer =
216216
error ("System error: " ^ s) *)
217217

218218
(** Instructions. **)
219-
let instr_cd ppf lexbuf =
219+
let instr_cd _ppf lexbuf =
220220
let dir = argument_eol argument lexbuf in
221221
if ask_kill_program () then
222222
try
@@ -225,15 +225,15 @@ let instr_cd ppf lexbuf =
225225
| Sys_error s ->
226226
error s
227227

228-
let instr_shell ppf lexbuf =
228+
let instr_shell _ppf lexbuf =
229229
let cmdarg = argument_list_eol argument lexbuf in
230230
let cmd = String.concat " " cmdarg in
231231
(* perhaps we should use $SHELL -c ? *)
232232
let err = Sys.command cmd in
233233
if (err != 0) then
234234
eprintf "Shell command %S failed with exit code %d\n%!" cmd err
235235

236-
let instr_env ppf lexbuf =
236+
let instr_env _ppf lexbuf =
237237
let cmdarg = argument_list_eol argument lexbuf in
238238
let cmdarg = string_trim (String.concat " " cmdarg) in
239239
if cmdarg <> "" then
@@ -286,7 +286,7 @@ let instr_dir ppf lexbuf =
286286
dirs)
287287
Debugger_config.load_path_for
288288

289-
let instr_kill ppf lexbuf =
289+
let instr_kill _ppf lexbuf =
290290
eol lexbuf;
291291
if not !loaded then error "The program is not being run.";
292292
if (yes_or_no "Kill the program being debugged") then begin
@@ -393,7 +393,7 @@ let print_info_list ppf =
393393
let pr_infos ppf = List.iter (fun i -> fprintf ppf "%s@ " i.info_name) in
394394
fprintf ppf "List of info commands: %a@." pr_infos !info_list
395395

396-
let instr_complete ppf lexbuf =
396+
let instr_complete _ppf lexbuf =
397397
let ppf = Format.err_formatter in
398398
let rec print_list l =
399399
try
@@ -465,7 +465,7 @@ let instr_help ppf lexbuf =
465465
find_variable
466466
(fun v _ _ ->
467467
print_help ("show " ^ v.var_name) ("show " ^ v.var_help))
468-
(fun v ->
468+
(fun _v ->
469469
print_help "show" "display debugger variable.";
470470
print_variable_list ppf)
471471
ppf
@@ -585,8 +585,8 @@ let instr_source ppf lexbuf =
585585

586586
let instr_set =
587587
find_variable
588-
(fun {var_action = (funct, _)} ppf lexbuf -> funct lexbuf)
589-
(function ppf -> error "Argument required.")
588+
(fun {var_action = (funct, _)} _ppf lexbuf -> funct lexbuf)
589+
(function _ppf -> error "Argument required.")
590590

591591
let instr_show =
592592
find_variable
@@ -600,8 +600,8 @@ let instr_show =
600600

601601
let instr_info =
602602
find_info
603-
(fun i ppf lexbuf -> i.info_action lexbuf)
604-
(function ppf ->
603+
(fun i _ppf lexbuf -> i.info_action lexbuf)
604+
(function _ppf ->
605605
error "\"info\" must be followed by the name of an info command.")
606606

607607
let instr_break ppf lexbuf =
@@ -673,7 +673,7 @@ let instr_break ppf lexbuf =
673673
| Not_found ->
674674
eprintf "Can\'t find any event there.@."
675675

676-
let instr_delete ppf lexbuf =
676+
let instr_delete _ppf lexbuf =
677677
match integer_list_eol Lexer.lexeme lexbuf with
678678
| [] ->
679679
if breakpoints_count () <> 0 && yes_or_no "Delete all breakpoints"
@@ -771,7 +771,7 @@ let instr_last ppf lexbuf =
771771
go_to (History.previous_time count);
772772
show_current_event ppf
773773

774-
let instr_list ppf lexbuf =
774+
let instr_list _ppf lexbuf =
775775
let (mo, beg, e) = list_arguments_eol Lexer.lexeme lexbuf in
776776
let (curr_mod, line, column) =
777777
try
@@ -866,9 +866,9 @@ let loading_mode_variable ppf =
866866
(find_ident
867867
"loading mode"
868868
(matching_elements (ref loading_modes) fst)
869-
(fun (_, mode) ppf lexbuf ->
869+
(fun (_, mode) _ppf lexbuf ->
870870
eol lexbuf; set_launching_function mode)
871-
(function ppf -> error "Syntax error.")
871+
(function _ppf -> error "Syntax error.")
872872
ppf),
873873
function ppf ->
874874
let rec find = function
@@ -946,7 +946,7 @@ let info_breakpoints ppf lexbuf =
946946
end
947947
;;
948948

949-
let info_events ppf lexbuf =
949+
let info_events _ppf lexbuf =
950950
ensure_loaded ();
951951
let mdle =
952952
convert_module (module_of_longident (opt_longident_eol Lexer.lexeme lexbuf))
@@ -1210,7 +1210,7 @@ It can be either:\n\
12101210
var_action = follow_fork_variable;
12111211
var_help =
12121212
"process to follow after forking.\n\
1213-
It can be either :
1213+
It can be either :\n\
12141214
child: the newly created process.\n\
12151215
parent: the process that called fork.\n" }];
12161216

debugger/debugcom.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -282,7 +282,7 @@ module Remote_value =
282282
Remote(input_remote_value !conn.io_in)
283283

284284
let closure_code = function
285-
| Local obj -> assert false
285+
| Local _ -> assert false
286286
| Remote v ->
287287
output_char !conn.io_out 'C';
288288
output_remote_value !conn.io_out v;

debugger/eval.ml

+4-4
Original file line numberDiff line numberDiff line change
@@ -61,12 +61,12 @@ let rec path event = function
6161
| None ->
6262
raise(Error(Unbound_identifier id))
6363
end
64-
| Pdot(root, fieldname, pos) ->
64+
| Pdot(root, _fieldname, pos) ->
6565
let v = path event root in
6666
if not (Debugcom.Remote_value.is_block v) then
6767
raise(Error(Not_initialized_yet root));
6868
Debugcom.Remote_value.field v pos
69-
| Papply(p1, p2) ->
69+
| Papply _ ->
7070
fatal_error "Eval.path: Papply"
7171

7272
let rec expression event env = function
@@ -135,10 +135,10 @@ let rec expression event env = function
135135
| E_field(arg, lbl) ->
136136
let (v, ty) = expression event env arg in
137137
begin match (Ctype.repr(Ctype.expand_head_opt env ty)).desc with
138-
Tconstr(path, args, _) ->
138+
Tconstr(path, _, _) ->
139139
let tydesc = Env.find_type path env in
140140
begin match tydesc.type_kind with
141-
Type_record(lbl_list, repr) ->
141+
Type_record(lbl_list, _repr) ->
142142
let (pos, ty_res) =
143143
find_label lbl env ty path tydesc 0 lbl_list in
144144
(Debugcom.Remote_value.field v pos, ty_res)

debugger/exec.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ let interrupted = ref false
2020

2121
let is_protected = ref false
2222

23-
let break signum =
23+
let break _signum =
2424
if !is_protected
2525
then interrupted := true
2626
else raise Sys.Break

debugger/frames.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -125,6 +125,6 @@ let do_backtrace action =
125125

126126
let stack_depth () =
127127
let num_frames = ref 0 in
128-
do_backtrace (function Some ev -> incr num_frames; true
128+
do_backtrace (function Some _ev -> incr num_frames; true
129129
| None -> num_frames := -1; false);
130130
!num_frames

debugger/frames.mli

-1
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,6 @@
1717
(****************************** Frames *********************************)
1818

1919
open Instruct
20-
open Primitives
2120

2221
(* Current frame number *)
2322
val current_frame : int ref

debugger/loadprinter.ml

+4-4
Original file line numberDiff line numberDiff line change
@@ -94,8 +94,8 @@ let loadfile ppf name =
9494

9595
let rec eval_path = function
9696
Pident id -> Symtable.get_global_value id
97-
| Pdot(p, s, pos) -> Obj.field (eval_path p) pos
98-
| Papply(p1, p2) -> fatal_error "Loadprinter.eval_path"
97+
| Pdot(p, _, pos) -> Obj.field (eval_path p) pos
98+
| Papply _ -> fatal_error "Loadprinter.eval_path"
9999

100100
(* Install, remove a printer (as in toplevel/topdirs) *)
101101

@@ -146,13 +146,13 @@ let install_printer ppf lid =
146146
raise(Error(Unavailable_module(s, lid))) in
147147
let print_function =
148148
if is_old_style then
149-
(fun formatter repr -> Obj.obj v (Obj.obj repr))
149+
(fun _formatter repr -> Obj.obj v (Obj.obj repr))
150150
else
151151
(fun formatter repr -> Obj.obj v formatter (Obj.obj repr)) in
152152
Printval.install_printer path ty_arg ppf print_function
153153

154154
let remove_printer lid =
155-
let (ty_arg, path, is_old_style) = find_printer_type lid in
155+
let (_ty_arg, path, _is_old_style) = find_printer_type lid in
156156
try
157157
Printval.remove_printer path
158158
with Not_found ->

debugger/main.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,7 @@ open Primitives
2929

3030
let line_buffer = Lexing.from_function read_user_input
3131

32-
let rec loop ppf = line_loop ppf line_buffer
32+
let loop ppf = line_loop ppf line_buffer
3333

3434
let current_duration = ref (-1L)
3535

debugger/parameters.ml

-1
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,6 @@ open Primitives
2020
open Config
2121
open Debugger_config
2222

23-
let program_loaded = ref false
2423
let program_name = ref ""
2524
let socket_name = ref ""
2625
let arguments = ref ""

debugger/parser_aux.mli

-4
Original file line numberDiff line numberDiff line change
@@ -14,10 +14,6 @@
1414
(* *)
1515
(**************************************************************************)
1616

17-
(*open Globals*)
18-
19-
open Primitives
20-
2117
type expression =
2218
E_ident of Longident.t (* x or Mod.x *)
2319
| E_name of int (* $xxx *)

debugger/pos.ml

-2
Original file line numberDiff line numberDiff line change
@@ -16,8 +16,6 @@
1616
open Instruct;;
1717
open Lexing;;
1818
open Location;;
19-
open Primitives;;
20-
open Source;;
2119

2220
let get_desc ev =
2321
let loc = ev.ev_loc in

debugger/printval.ml

+5-5
Original file line numberDiff line numberDiff line change
@@ -40,7 +40,7 @@ let name_value v ty =
4040
let find_named_value name =
4141
Hashtbl.find named_values name
4242

43-
let check_depth ppf depth obj ty =
43+
let check_depth depth obj ty =
4444
if depth <= 0 then begin
4545
let n = name_value obj ty in
4646
Some (Outcometree.Oval_stuff ("$" ^ string_of_int n))
@@ -57,19 +57,19 @@ module EvalPath =
5757
with Symtable.Error _ ->
5858
raise Error
5959
end
60-
| Pdot(root, fieldname, pos) ->
60+
| Pdot(root, _fieldname, pos) ->
6161
let v = eval_path env root in
6262
if not (Debugcom.Remote_value.is_block v)
6363
then raise Error
6464
else Debugcom.Remote_value.field v pos
65-
| Papply(p1, p2) ->
65+
| Papply _ ->
6666
raise Error
6767
let same_value = Debugcom.Remote_value.same
6868
end
6969

7070
module Printer = Genprintval.Make(Debugcom.Remote_value)(EvalPath)
7171

72-
let install_printer path ty ppf fn =
72+
let install_printer path ty _ppf fn =
7373
Printer.install_printer path ty
7474
(fun ppf remote_val ->
7575
try
@@ -90,7 +90,7 @@ let print_exception ppf obj =
9090
let print_value max_depth env obj (ppf : Format.formatter) ty =
9191
let t =
9292
Printer.outval_of_value !max_printer_steps max_depth
93-
(check_depth ppf) env obj ty in
93+
check_depth env obj ty in
9494
!Oprint.out_value ppf t
9595

9696
let print_named_value max_depth exp env obj ppf ty =

debugger/source.ml

+4-6
Original file line numberDiff line numberDiff line change
@@ -67,8 +67,6 @@ type buffer = string * (int * int) list ref
6767

6868
let buffer_max_count = ref 10
6969

70-
let cache_size = 30
71-
7270
let buffer_list =
7371
ref ([] : (string * buffer) list)
7472

@@ -101,7 +99,7 @@ let insert_pos buffer ((position, line) as pair) =
10199
function
102100
[] ->
103101
[(position, line)]
104-
| ((pos, lin) as a::l) as l' ->
102+
| ((_pos, lin) as a::l) as l' ->
105103
if lin < line then
106104
pair::l'
107105
else if lin = line then
@@ -141,13 +139,13 @@ let line_of_pos buffer position =
141139
raise Out_of_range
142140
else
143141
(0, 1)
144-
| ((pos, line) as pair)::l ->
142+
| ((pos, _line) as pair)::l ->
145143
if pos > position then
146144
find l
147145
else
148146
pair
149147
and find_line previous =
150-
let (pos, line) as next = next_line buffer previous in
148+
let (pos, _line) as next = next_line buffer previous in
151149
if pos <= position then
152150
find_line next
153151
else
@@ -166,7 +164,7 @@ let pos_of_line buffer line =
166164
raise Out_of_range
167165
else
168166
(0, 1)
169-
| ((pos, lin) as pair)::l ->
167+
| ((_pos, lin) as pair)::l ->
170168
if lin > line then
171169
find l
172170
else

debugger/symbols.ml

+2-2
Original file line numberDiff line numberDiff line change
@@ -62,7 +62,7 @@ let read_symbols' bytecode_file =
6262
let num_eventlists = input_binary_int ic in
6363
let dirs = ref StringSet.empty in
6464
let eventlists = ref [] in
65-
for i = 1 to num_eventlists do
65+
for _i = 1 to num_eventlists do
6666
let orig = input_binary_int ic in
6767
let evl = (input_value ic : debug_event list) in
6868
(* Relocate events in event list *)
@@ -182,7 +182,7 @@ let event_near_pos md char =
182182
(* Flip "event" bit on all instructions *)
183183
let set_all_events () =
184184
Hashtbl.iter
185-
(fun pc ev ->
185+
(fun _pc ev ->
186186
match ev.ev_kind with
187187
Event_pseudo -> ()
188188
| _ -> Debugcom.set_event ev.ev_pos)

0 commit comments

Comments
 (0)