summaryrefslogtreecommitdiffstats
path: root/parsing/syntaxerr.ml
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>1997-08-22 08:55:41 +0000
committerXavier Leroy <xavier.leroy@inria.fr>1997-08-22 08:55:41 +0000
commit579e1523e94f7fef3d11346207161beea667b9dc (patch)
treec41dd7d0041ef03ce58e40772b3a3ac612c9e7f7 /parsing/syntaxerr.ml
parent23686e53207f43ee1b913095acc964063a36281f (diff)
Meilleures erreurs de syntaxe pour les parentheses mal fermees, etc
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@1689 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'parsing/syntaxerr.ml')
-rw-r--r--parsing/syntaxerr.ml47
1 files changed, 47 insertions, 0 deletions
diff --git a/parsing/syntaxerr.ml b/parsing/syntaxerr.ml
new file mode 100644
index 000000000..6b87819b0
--- /dev/null
+++ b/parsing/syntaxerr.ml
@@ -0,0 +1,47 @@
+(***********************************************************************)
+(* *)
+(* Objective Caml *)
+(* *)
+(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
+(* *)
+(* Copyright 1997 Institut National de Recherche en Informatique et *)
+(* Automatique. Distributed only by permission. *)
+(* *)
+(***********************************************************************)
+
+(* $Id$ *)
+
+(* Auxiliary type for reporting syntax errors *)
+
+open Format
+
+type error =
+ Unclosed of Location.t * string * Location.t * string
+ | Other of Location.t
+
+exception Error of error
+
+let report_error = function
+ Unclosed(opening_loc, opening, closing_loc, closing) ->
+ if String.length !Location.input_name > 0 then begin
+ Location.print closing_loc;
+ print_string "Syntax error: missing '";
+ print_string closing;
+ print_string "'"; force_newline();
+ Location.print opening_loc;
+ print_string "This is the location of the unmatched '";
+ print_string opening;
+ print_string "'"
+ end else begin
+ Location.print opening_loc;
+ print_string "Syntax error: this '";
+ print_string opening;
+ print_string "' has no matching '";
+ print_string closing;
+ print_string "'"
+ end
+ | Other loc ->
+ Location.print loc;
+ print_string "Syntax error"
+
+