]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml/contrib/parsing/parse.ml
Update
[l4.git] / l4 / pkg / ocaml / ocaml / contrib / parsing / parse.ml
1 (***********************************************************************)
2 (*                                                                     *)
3 (*                           Objective Caml                            *)
4 (*                                                                     *)
5 (*            Xavier Leroy, projet Cristal, INRIA Rocquencourt         *)
6 (*                                                                     *)
7 (*  Copyright 1996 Institut National de Recherche en Informatique et   *)
8 (*  en Automatique.  All rights reserved.  This file is distributed    *)
9 (*  under the terms of the Q Public License version 1.0.               *)
10 (*                                                                     *)
11 (***********************************************************************)
12
13 (* $Id: parse.ml 5224 2002-11-01 17:06:47Z doligez $ *)
14
15 (* Entry points in the parser *)
16
17 open Location
18
19 (* Skip tokens to the end of the phrase *)
20
21 let rec skip_phrase lexbuf =
22   try
23     match Lexer.token lexbuf with
24       Parser.SEMISEMI | Parser.EOF -> ()
25     | _ -> skip_phrase lexbuf
26   with
27     | Lexer.Error (Lexer.Unterminated_comment, _) -> ()
28     | Lexer.Error (Lexer.Unterminated_string, _) -> ()
29     | Lexer.Error (Lexer.Unterminated_string_in_comment, _) -> ()
30     | Lexer.Error (Lexer.Illegal_character _, _) -> skip_phrase lexbuf
31 ;;
32
33 let maybe_skip_phrase lexbuf =
34   if Parsing.is_current_lookahead Parser.SEMISEMI
35   || Parsing.is_current_lookahead Parser.EOF
36   then ()
37   else skip_phrase lexbuf
38
39 let wrap parsing_fun lexbuf =
40   try
41     let ast = parsing_fun Lexer.token lexbuf in
42     Parsing.clear_parser();
43     ast
44   with
45   | Lexer.Error(Lexer.Unterminated_comment, _) as err -> raise err
46   | Lexer.Error(Lexer.Unterminated_string, _) as err -> raise err
47   | Lexer.Error(Lexer.Unterminated_string_in_comment, _) as err -> raise err
48   | Lexer.Error(Lexer.Illegal_character _, _) as err ->
49       if !Location.input_name = "" then skip_phrase lexbuf;
50       raise err
51   | Syntaxerr.Error _ as err ->
52       if !Location.input_name = "" then maybe_skip_phrase lexbuf;
53       raise err
54   | Parsing.Parse_error | Syntaxerr.Escape_error ->
55       let loc = Location.curr lexbuf in
56       if !Location.input_name = "" 
57       then maybe_skip_phrase lexbuf;
58       raise(Syntaxerr.Error(Syntaxerr.Other loc))
59 ;;
60
61 let implementation = wrap Parser.implementation
62 and interface = wrap Parser.interface
63 and toplevel_phrase = wrap Parser.toplevel_phrase
64 and use_file = wrap Parser.use_file