Skip to content

Commit

Permalink
Friendlier error messages
Browse files Browse the repository at this point in the history
Friendlier to machines that is. ``File "foo.ml", line 42, characters 7-15'' is
replaced by ``foo.ml:42:7-15''.
  • Loading branch information
raphael-proust committed Mar 8, 2013
1 parent a81a5b0 commit a5cb141
Show file tree
Hide file tree
Showing 6 changed files with 9 additions and 12 deletions.
2 changes: 1 addition & 1 deletion camlp4/Camlp4/Struct/Loc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -263,7 +263,7 @@ value strictly_before x y =

value to_string x = do {
let (a, b) = (x.start, x.stop) in
let res = sprintf "File \"%s\", line %d, characters %d-%d"
let res = sprintf "%s:%d:%d-%d"
x.file_name a.line (a.off - a.bol) (b.off - a.bol) in
if x.start.line <> x.stop.line then
sprintf "%s (end at line %d, character %d)"
Expand Down
2 changes: 1 addition & 1 deletion camlp4/boot/Camlp4.ml
Original file line number Diff line number Diff line change
Expand Up @@ -3273,7 +3273,7 @@ module Struct =
let to_string x =
let (a, b) = ((x.start), (x.stop)) in
let res =
sprintf "File \"%s\", line %d, characters %d-%d" x.file_name
sprintf "%s:%d:%d-%d" x.file_name
a.line (a.off - a.bol) (b.off - a.bol)
in
if x.start.line <> x.stop.line
Expand Down
2 changes: 1 addition & 1 deletion debugger/pos.ml
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ open Source;;

let get_desc ev =
let loc = ev.ev_loc in
Printf.sprintf "file %s, line %d, characters %d-%d"
Printf.sprintf "%s:%d:%d-%d"
loc.loc_start.pos_fname loc.loc_start.pos_lnum
(loc.loc_start.pos_cnum - loc.loc_start.pos_bol + 1)
(loc.loc_end.pos_cnum - loc.loc_start.pos_bol + 1)
Expand Down
9 changes: 3 additions & 6 deletions parsing/location.ml
Original file line number Diff line number Diff line change
Expand Up @@ -221,9 +221,6 @@ let print_filename ppf file =
let reset () =
num_loc_lines := 0

let (msg_file, msg_line, msg_chars, msg_to, msg_colon) =
("File \"", "\", line ", ", characters ", "-", ":")

(* return file, line, char from the given position *)
let get_pos_info pos =
(pos.pos_fname, pos.pos_lnum, pos.pos_cnum - pos.pos_bol)
Expand All @@ -237,16 +234,16 @@ let print_loc ppf loc =
fprintf ppf "Characters %i-%i"
loc.loc_start.pos_cnum loc.loc_end.pos_cnum
end else begin
fprintf ppf "%s%a%s%i" msg_file print_filename file msg_line line;
fprintf ppf "%a:%i" print_filename file line;
if startchar >= 0 then
fprintf ppf "%s%i%s%i" msg_chars startchar msg_to endchar
fprintf ppf ":%i-%i" startchar endchar
end
;;

let print ppf loc =
if loc.loc_start.pos_fname = "//toplevel//"
&& highlight_locations ppf loc none then ()
else fprintf ppf "%a%s@." print_loc loc msg_colon
else fprintf ppf "%a@." print_loc loc
;;

let print_error ppf loc =
Expand Down
4 changes: 2 additions & 2 deletions stdlib/printexc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ open Printf;;

let printers = ref []

let locfmt = format_of_string "File \"%s\", line %d, characters %d-%d: %s";;
let locfmt = format_of_string "%s:%d:%d-%d %s";;

let field x i =
let f = Obj.field x i in
Expand Down Expand Up @@ -105,7 +105,7 @@ let format_loc_info pos li =
in
match li with
| Known_location(is_raise, filename, lineno, startchar, endchar) ->
sprintf "%s file \"%s\", line %d, characters %d-%d"
sprintf "%s %s:%d:%d-%d"
info filename lineno startchar endchar
| Unknown_location(is_raise) ->
sprintf "%s unknown location"
Expand Down
2 changes: 1 addition & 1 deletion tools/dumpobj.ml
Original file line number Diff line number Diff line change
Expand Up @@ -400,7 +400,7 @@ let print_event ev =
if !print_locations then
let ls = ev.ev_loc.loc_start in
let le = ev.ev_loc.loc_end in
printf "File \"%s\", line %d, characters %d-%d:\n" ls.Lexing.pos_fname
printf "%s:%d:%d-%d\n" ls.Lexing.pos_fname
ls.Lexing.pos_lnum (ls.Lexing.pos_cnum - ls.Lexing.pos_bol)
(le.Lexing.pos_cnum - ls.Lexing.pos_bol)

Expand Down

0 comments on commit a5cb141

Please sign in to comment.