diff options
author | Alain Frisch <alain@frisch.fr> | 2013-09-12 11:59:45 +0000 |
---|---|---|
committer | Alain Frisch <alain@frisch.fr> | 2013-09-12 11:59:45 +0000 |
commit | 71efb4666b1df8cc841fe3d7b0ffe43fcd8d2958 (patch) | |
tree | 9898a7a09c2a1781811766baee22e6cb8a37ade4 | |
parent | 6ad98b3d0927ab206eec09aeaa3d7f776e1d2c0e (diff) |
Switch Lexer.Error to the new system.
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/exception_registration@14107 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r-- | driver/errors.ml | 3 | ||||
-rw-r--r-- | driver/opterrors.ml | 3 | ||||
-rw-r--r-- | ocamldoc/odoc_analyse.ml | 3 | ||||
-rw-r--r-- | parsing/lexer.mli | 1 | ||||
-rw-r--r-- | parsing/lexer.mll | 10 | ||||
-rw-r--r-- | parsing/syntaxerr.mli | 1 | ||||
-rw-r--r-- | tools/ocamldep.ml | 3 | ||||
-rw-r--r-- | tools/ocamlprof.ml | 3 |
8 files changed, 11 insertions, 16 deletions
diff --git a/driver/errors.ml b/driver/errors.ml index f7864ccd0..29447fccb 100644 --- a/driver/errors.ml +++ b/driver/errors.ml @@ -21,9 +21,6 @@ open Format let report_error ppf exn = let report ppf = function - | Lexer.Error(err, loc) -> - Location.print_error ppf loc; - Lexer.report_error ppf err | Pparse.Error err -> Pparse.report_error ppf err | Env.Error err -> diff --git a/driver/opterrors.ml b/driver/opterrors.ml index 7a519b79b..feb07a98f 100644 --- a/driver/opterrors.ml +++ b/driver/opterrors.ml @@ -20,9 +20,6 @@ open Format let report_error ppf exn = let report ppf = function - | Lexer.Error(err, l) -> - Location.print_error ppf l; - Lexer.report_error ppf err | Pparse.Error err -> Pparse.report_error ppf err | Env.Error err -> diff --git a/ocamldoc/odoc_analyse.ml b/ocamldoc/odoc_analyse.ml index 4b2af7f97..a29e4baaf 100644 --- a/ocamldoc/odoc_analyse.ml +++ b/ocamldoc/odoc_analyse.ml @@ -108,9 +108,6 @@ module Sig_analyser = Odoc_sig.Analyser (Odoc_comments.Basic_info_retriever) differences only concern code generation (i believe).*) let process_error exn = let report ppf = function - | Lexer.Error(err, loc) -> - Location.print_error ppf loc; - Lexer.report_error ppf err | Env.Error err -> Location.print_error_cur_file ppf; Env.report_error ppf err diff --git a/parsing/lexer.mli b/parsing/lexer.mli index 0c98ffc34..b067b2aa3 100644 --- a/parsing/lexer.mli +++ b/parsing/lexer.mli @@ -31,6 +31,7 @@ exception Error of error * Location.t open Format val report_error: formatter -> error -> unit + (* Deprecated. Use Location.{error_of_exn, report_error}. *) val in_comment : unit -> bool;; val in_string : unit -> bool;; diff --git a/parsing/lexer.mll b/parsing/lexer.mll index 8b34b2483..8aed03b2f 100644 --- a/parsing/lexer.mll +++ b/parsing/lexer.mll @@ -242,7 +242,15 @@ let report_error ppf = function | Literal_overflow ty -> fprintf ppf "Integer literal exceeds the range of representable \ integers of type %s" ty -;; + +let () = + Location.register_error_of_exn + (function + | Error (err, loc) -> + Some (Location.error_of_printer loc report_error err) + | _ -> + None + ) } diff --git a/parsing/syntaxerr.mli b/parsing/syntaxerr.mli index 0bacb0f95..1aec26ed5 100644 --- a/parsing/syntaxerr.mli +++ b/parsing/syntaxerr.mli @@ -26,5 +26,6 @@ exception Error of error exception Escape_error val report_error: formatter -> error -> unit + (* Deprecated. Use Location.{error_of_exn, report_error}. *) val location_of_error: error -> Location.t diff --git a/tools/ocamldep.ml b/tools/ocamldep.ml index 233dba34d..baf212c60 100644 --- a/tools/ocamldep.ml +++ b/tools/ocamldep.ml @@ -208,9 +208,6 @@ let print_raw_dependencies source_file deps = let report_err source_file exn = error_occurred := true; match exn with - | Lexer.Error(err, range) -> - Format.fprintf Format.err_formatter "@[%a%a@]@." - Location.print_error range Lexer.report_error err | Sys_error msg -> Format.fprintf Format.err_formatter "@[I/O error:@ %s@]@." msg | Pparse.Error err -> diff --git a/tools/ocamlprof.ml b/tools/ocamlprof.ml index acd99f200..bb6d5086d 100644 --- a/tools/ocamlprof.ml +++ b/tools/ocamlprof.ml @@ -501,9 +501,6 @@ let main () = exit 0 with x -> let report_error ppf = function - | Lexer.Error(err, range) -> - fprintf ppf "@[%a%a@]@." - Location.print_error range Lexer.report_error err | Profiler msg -> fprintf ppf "@[%s@]@." msg | Sys_error msg -> |