summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--ocamlbuild/lexers.mli2
-rw-r--r--ocamlbuild/lexers.mll5
-rw-r--r--ocamlbuild/main.ml5
-rw-r--r--ocamlbuild/testsuite/internal.ml12
4 files changed, 12 insertions, 12 deletions
diff --git a/ocamlbuild/lexers.mli b/ocamlbuild/lexers.mli
index aa7dd5ada..a59d7589b 100644
--- a/ocamlbuild/lexers.mli
+++ b/ocamlbuild/lexers.mli
@@ -12,7 +12,7 @@
(* Original author: Nicolas Pouillard *)
-exception Error of (string * Lexing.position)
+exception Error of (string * Loc.location)
type conf_values =
{ plus_tags : (string * Loc.location) list;
diff --git a/ocamlbuild/lexers.mll b/ocamlbuild/lexers.mll
index 35af2c34a..797337d85 100644
--- a/ocamlbuild/lexers.mll
+++ b/ocamlbuild/lexers.mll
@@ -13,9 +13,10 @@
(* Original author: Nicolas Pouillard *)
{
-exception Error of (string * Lexing.position)
+exception Error of (string * Loc.location)
-let error lexbuf fmt = Printf.ksprintf (fun s -> raise (Error (s,Lexing.lexeme_start_p lexbuf))) fmt
+let error lexbuf fmt =
+ Printf.ksprintf (fun s -> raise (Error (s, Loc.of_lexbuf lexbuf))) fmt
open Glob_ast
diff --git a/ocamlbuild/main.ml b/ocamlbuild/main.ml
index de7a4a94a..5f86f7932 100644
--- a/ocamlbuild/main.ml
+++ b/ocamlbuild/main.ml
@@ -301,9 +301,8 @@ let main () =
| Ocaml_utils.Ocamldep_error msg ->
Log.eprintf "Ocamldep error: %s" msg;
exit rc_ocamldep_error
- | Lexers.Error (msg,pos) ->
- let module L = Lexing in
- Log.eprintf "%s, line %d, column %d: Lexing error: %s." pos.L.pos_fname pos.L.pos_lnum (pos.L.pos_cnum - pos.L.pos_bol) msg;
+ | Lexers.Error (msg,loc) ->
+ Log.eprintf "%aLexing error: %s." Loc.print_loc loc msg;
exit rc_lexing_error
| Arg.Bad msg ->
Log.eprintf "%s" msg;
diff --git a/ocamlbuild/testsuite/internal.ml b/ocamlbuild/testsuite/internal.ml
index 38f4aecba..b25594f88 100644
--- a/ocamlbuild/testsuite/internal.ml
+++ b/ocamlbuild/testsuite/internal.ml
@@ -51,14 +51,14 @@ let () = test "BuildDir"
~targets:("dummy.byte",[]) ();;
let tag_pat_msgs =
- ["*:a", "File \"_tags\", line 1, column 0: \
- Lexing error: Invalid globbing pattern \"*\".";
+ ["*:a", "File \"_tags\", line 1, characters 0-2:\n\
+ Lexing error: Invalid globbing pattern \"*\".";
- "\n<*{>:a", "File \"_tags\", line 2, column 0: \
- Lexing error: Invalid globbing pattern \"<*{>\".";
+ "\n<*{>:a", "File \"_tags\", line 2, characters 0-5:\n\
+ Lexing error: Invalid globbing pattern \"<*{>\".";
- "<*>: ~@a,# ~a", "File \"_tags\", line 1, column 10: \
- Lexing error: Only ',' separated tags are alllowed."];;
+ "<*>: ~@a,# ~a", "File \"_tags\", line 1, characters 10-11:\n\
+ Lexing error: Only ',' separated tags are alllowed."];;
List.iteri (fun i (content,failing_msg) ->
let () = test (Printf.sprintf "TagsErrorMessage_%d" (i+1))