Do not keep file name in exception, after all.

git-svn-id: http://caml.inria.fr/svn/ocaml/branches/exception_registration@14110 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Alain Frisch 2013-09-12 13:41:01 +00:00
parent 290fe0c0b2
commit 6950d6f780
6 changed files with 17 additions and 15 deletions

View File

@ -218,7 +218,7 @@ let main () =
with
Toplevel ->
exit 2
| Env.Error (e, _) ->
| Env.Error e ->
eprintf "Debugger [version %s] environment error:@ @[@;" Config.version;
Env.report_error err_formatter e;
eprintf "@]@.";

View File

@ -16,7 +16,7 @@ type error =
| CannotRun of string
| WrongMagic of string
exception Error of error * string
exception Error of error
(* Optionally preprocess a source file *)
@ -30,7 +30,7 @@ let preprocess sourcefile =
in
if Ccomp.command comm <> 0 then begin
Misc.remove_file tmpfile;
raise (Error (CannotRun comm, !Location.input_name));
raise (Error (CannotRun comm));
end;
tmpfile
@ -57,10 +57,10 @@ let apply_rewriter magic fn_in ppx =
Misc.remove_file fn_in;
if not ok then begin
Misc.remove_file fn_out;
raise (Error (CannotRun comm, !Location.input_name));
raise (Error (CannotRun comm));
end;
if not (Sys.file_exists fn_out) then
raise (Error (WrongMagic comm, !Location.input_name));
raise (Error (WrongMagic comm));
(* check magic before passing to the next ppx *)
let ic = open_in_bin fn_out in
let buffer =
@ -68,7 +68,7 @@ let apply_rewriter magic fn_in ppx =
close_in ic;
if buffer <> magic then begin
Misc.remove_file fn_out;
raise (Error (WrongMagic comm, !Location.input_name));
raise (Error (WrongMagic comm));
end;
fn_out
@ -147,9 +147,10 @@ let report_error ppf = function
let () =
Location.register_error_of_exn
(function
| Error (err, file) ->
| Error err ->
Some
(Location.error_of_printer (Location.in_file file) report_error err)
(Location.error_of_printer
(Location.in_file !Location.input_name) report_error err)
| _ ->
None
)

View File

@ -16,7 +16,7 @@ type error =
| CannotRun of string
| WrongMagic of string
exception Error of error * string (* source file *)
exception Error of error
val preprocess : string -> string
val remove_preprocessed : string -> unit

View File

@ -44,7 +44,7 @@ let initial_env () =
let preprocess sourcefile =
try
Pparse.preprocess sourcefile
with Pparse.Error (err, _file) ->
with Pparse.Error err ->
Format.eprintf "Preprocessing error@.%a@."
Pparse.report_error err;
exit 2

View File

@ -58,9 +58,9 @@ type error =
| Inconsistent_import of string * string * string
| Need_recursive_types of string * string
exception Error of error * string
exception Error of error
let error err = raise (Error (err, !Location.input_name))
let error err = raise (Error err)
module EnvLazy : sig
type ('a,'b) t
@ -1609,9 +1609,10 @@ let report_error ppf = function
let () =
Location.register_error_of_exn
(function
| Error (err, file) ->
| Error err ->
Some
(Location.error_of_printer (Location.in_file file) report_error err)
(Location.error_of_printer
(Location.in_file !Location.input_name) report_error err)
| _ ->
None
)

View File

@ -174,7 +174,7 @@ type error =
| Inconsistent_import of string * string * string
| Need_recursive_types of string * string
exception Error of error * string (* file name *)
exception Error of error
open Format