]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/camlp4/Camlp4/Struct/Grammar/Parser.mli
update
[l4.git] / l4 / pkg / ocaml / contrib / camlp4 / Camlp4 / Struct / Grammar / Parser.mli
1 (* camlp4r *)
2 (****************************************************************************)
3 (*                                                                          *)
4 (*                              Objective Caml                              *)
5 (*                                                                          *)
6 (*                            INRIA Rocquencourt                            *)
7 (*                                                                          *)
8 (*  Copyright  2007   Institut National de Recherche  en  Informatique et   *)
9 (*  en Automatique.  All rights reserved.  This file is distributed under   *)
10 (*  the terms of the GNU Library General Public License, with the special   *)
11 (*  exception on linking described in LICENSE at the top of the Objective   *)
12 (*  Caml source tree.                                                       *)
13 (*                                                                          *)
14 (****************************************************************************)
15
16
17
18 (* Authors:
19  * - Daniel de Rauglaudre: initial version
20  * - Nicolas Pouillard: refactoring
21  *)
22
23 module Make (Structure : Structure.S) : sig
24   open Structure;
25   open Context;
26   value add_loc :
27     Context.t -> Loc.t -> (Context.t -> 'a -> 'b) -> 'a -> ('b * Loc.t);
28   value level_number : internal_entry -> string -> int;
29   value strict_parsing : ref bool;
30   value strict_parsing_warning : ref bool;
31   value top_symb :
32     internal_entry -> symbol -> symbol;
33   value top_tree :
34     internal_entry -> tree -> tree;
35   value entry_of_symb :
36     internal_entry -> symbol -> internal_entry;
37   value continue :
38     internal_entry -> Loc.t -> Action.t -> symbol -> Context.t -> tree ->
39     (Stream.t (Token.t * Loc.t) -> Action.t) -> Stream.t (Token.t * Loc.t) -> Action.t;
40   value do_recover :
41     (internal_entry -> 'a -> 'b -> tree -> Context.t -> Stream.t (Token.t * Loc.t) -> Action.t) -> internal_entry ->
42     'a -> 'b -> Loc.t -> Action.t -> symbol -> Context.t -> tree -> Stream.t (Token.t * Loc.t) -> Action.t;
43   value recover :
44     (internal_entry -> 'a -> 'b -> tree -> Context.t -> Stream.t (Token.t * Loc.t) -> Action.t) -> internal_entry ->
45     'a -> 'b -> Loc.t -> Action.t -> symbol -> Context.t -> tree -> Stream.t (Token.t * Loc.t) -> Action.t;
46   value parser_of_tree :
47     internal_entry -> int -> int -> tree -> Context.t -> Stream.t (Token.t * Loc.t) -> Action.t;
48   value parser_cont :
49     (Context.t -> Stream.t (Token.t * Loc.t) -> Action.t) -> internal_entry -> int -> int -> symbol -> tree ->
50     Context.t -> Loc.t -> Action.t -> Stream.t (Token.t * Loc.t) -> Action.t;
51   value parser_of_token_list :
52     (Context.t -> Loc.t -> Action.t -> Stream.t (Token.t * Loc.t) -> Action.t) -> list symbol -> Context.t -> Stream.t (Token.t * Loc.t) -> Action.t;
53   value parser_of_symbol :
54     internal_entry -> int -> symbol -> Context.t -> Stream.t (Token.t * Loc.t) -> Action.t;
55   value parse_top_symb' :
56     internal_entry -> symbol -> Context.t -> Stream.t (Token.t * Loc.t) -> Action.t;
57   value parse_top_symb :
58     internal_entry -> symbol -> Stream.t (Token.t * Loc.t) -> Action.t;
59   value start_parser_of_levels :
60     internal_entry -> int -> list level -> int -> Context.t -> Stream.t (Token.t * Loc.t) -> Action.t;
61   value start_parser_of_entry :
62     internal_entry -> int -> Context.t -> Stream.t (Token.t * Loc.t) -> Action.t;
63   value continue_parser_of_levels :
64     internal_entry -> int -> list level -> Context.t -> int -> Loc.t -> 'a -> Stream.t (Token.t * Loc.t) -> Action.t;
65   value continue_parser_of_entry :
66     internal_entry -> int -> Loc.t -> Action.t -> Context.t -> Stream.t (Token.t * Loc.t) -> Action.t;
67 end;
68