summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--parsing/parse.ml20
1 files changed, 9 insertions, 11 deletions
diff --git a/parsing/parse.ml b/parsing/parse.ml
index ab84b13d4..2f4926ff8 100644
--- a/parsing/parse.ml
+++ b/parsing/parse.ml
@@ -20,9 +20,9 @@ let rec skip_phrase lexbuf =
Parser.SEMISEMI | Parser.EOF -> ()
| _ -> skip_phrase lexbuf
with
- | Lexer.Error (Lexer.Unterminated_comment _, _) -> ()
- | Lexer.Error (Lexer.Unterminated_string, _) -> ()
- | Lexer.Error (Lexer.Unterminated_string_in_comment _, _) -> ()
+ | Lexer.Error (Lexer.Unterminated_comment _, _)
+ | Lexer.Error (Lexer.Unterminated_string, _)
+ | Lexer.Error (Lexer.Unterminated_string_in_comment _, _)
| Lexer.Error (Lexer.Illegal_character _, _) -> skip_phrase lexbuf
;;
@@ -39,21 +39,19 @@ let wrap parsing_fun lexbuf =
Parsing.clear_parser();
ast
with
- | Lexer.Error(Lexer.Unterminated_comment _, _) as err -> raise err
- | Lexer.Error(Lexer.Unterminated_string, _) as err -> raise err
- | Lexer.Error(Lexer.Unterminated_string_in_comment _, _) as err -> raise err
- | Lexer.Error(Lexer.Illegal_character _, _) as err ->
- if !Location.input_name = "//toplevel//" then skip_phrase lexbuf;
+ | Lexer.Error(Lexer.Illegal_character _, _) as err
+ when !Location.input_name = "//toplevel//"->
+ skip_phrase lexbuf;
raise err
- | Syntaxerr.Error _ as err ->
- if !Location.input_name = "//toplevel//" then maybe_skip_phrase lexbuf;
+ | Syntaxerr.Error _ as err
+ when !Location.input_name = "//toplevel//" ->
+ maybe_skip_phrase lexbuf;
raise err
| Parsing.Parse_error | Syntaxerr.Escape_error ->
let loc = Location.curr lexbuf in
if !Location.input_name = "//toplevel//"
then maybe_skip_phrase lexbuf;
raise(Syntaxerr.Error(Syntaxerr.Other loc))
-;;
let implementation = wrap Parser.implementation
and interface = wrap Parser.interface