summaryrefslogtreecommitdiffstats
path: root/parsing/syntaxerr.ml
diff options
context:
space:
mode:
Diffstat (limited to 'parsing/syntaxerr.ml')
-rw-r--r--parsing/syntaxerr.ml60
1 files changed, 31 insertions, 29 deletions
diff --git a/parsing/syntaxerr.ml b/parsing/syntaxerr.ml
index b19a382d4..13212eecd 100644
--- a/parsing/syntaxerr.ml
+++ b/parsing/syntaxerr.ml
@@ -12,8 +12,6 @@
(* Auxiliary type for reporting syntax errors *)
-open Format
-
type error =
Unclosed of Location.t * string * Location.t * string
| Expecting of Location.t * string
@@ -22,44 +20,48 @@ type error =
| Variable_in_scope of Location.t * string
| Other of Location.t
-
-
exception Error of error
exception Escape_error
-let report_error ppf = function
+let prepare_error = function
| Unclosed(opening_loc, opening, closing_loc, closing) ->
- if !Location.input_name = "//toplevel//"
- && Location.highlight_locations ppf opening_loc closing_loc
- then fprintf ppf "Syntax error: '%s' expected, \
- the highlighted '%s' might be unmatched" closing opening
- else begin
- fprintf ppf "%aSyntax error: '%s' expected@."
- Location.print_error closing_loc closing;
- fprintf ppf "%aThis '%s' might be unmatched"
- Location.print_error opening_loc opening
- end
+ Location.errorf ~loc:closing_loc
+ ~sub:[
+ Location.error ~loc:opening_loc
+ (Printf.sprintf "Error: This '%s' might be unmatched" opening)
+ ]
+ ~if_highlight:
+ (Printf.sprintf "Syntax error: '%s' expected, \
+ the highlighted '%s' might be unmatched"
+ closing opening)
+ "Error: Syntax error: '%s' expected" closing
+
| Expecting (loc, nonterm) ->
- fprintf ppf
- "%a@[Syntax error: %s expected.@]"
- Location.print_error loc nonterm
+ Location.errorf ~loc "Error: Syntax error: %s expected." nonterm
| Not_expecting (loc, nonterm) ->
- fprintf ppf
- "%a@[Syntax error: %s not expected.@]"
- Location.print_error loc nonterm
+ Location.errorf ~loc "Error: Syntax error: %s not expected." nonterm
| Applicative_path loc ->
- fprintf ppf
- "%aSyntax error: applicative paths of the form F(X).t \
+ Location.errorf ~loc
+ "Error: Syntax error: applicative paths of the form F(X).t \
are not supported when the option -no-app-func is set."
- Location.print_error loc
| Variable_in_scope (loc, var) ->
- fprintf ppf
- "%a@[In this scoped type, variable '%s@ \
- is reserved for the local type %s.@]"
- Location.print_error loc var var
+ Location.errorf ~loc
+ "Error: In this scoped type, variable '%s@ \
+ is reserved for the local type %s."
+ var var
| Other loc ->
- fprintf ppf "%aSyntax error" Location.print_error loc
+ Location.error ~loc "Error: Syntax error"
+
+let () =
+ Location.register_error_of_exn
+ (function
+ | Error err -> Some (prepare_error err)
+ | _ -> None
+ )
+
+let report_error ppf err =
+ Location.report_error ppf (prepare_error err)
let location_of_error = function
| Unclosed(l,_,_,_)