diff options
author | Xavier Leroy <xavier.leroy@inria.fr> | 1995-07-12 14:28:51 +0000 |
---|---|---|
committer | Xavier Leroy <xavier.leroy@inria.fr> | 1995-07-12 14:28:51 +0000 |
commit | a2ef5d87140f9284035c4bf12c924dcb5799caec (patch) | |
tree | 70ef9067a47e1fc92133945828ffc46ad23e02d3 /stdlib/parsing.mli | |
parent | 2241e743e252f9c9e94b2c7926b16e4fb317f5b6 (diff) |
Modif des actions des parsers produits par camlyacc: elles prennent
l'env en premier argument et le repassent a peek_val (plus efficace
pour le compilateur natif).
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@91 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/parsing.mli')
-rw-r--r-- | stdlib/parsing.mli | 6 |
1 files changed, 4 insertions, 2 deletions
diff --git a/stdlib/parsing.mli b/stdlib/parsing.mli index e2c17d40c..99e891ce1 100644 --- a/stdlib/parsing.mli +++ b/stdlib/parsing.mli @@ -29,8 +29,10 @@ exception Parse_error (* The following definitions are used by the generated parsers only. They are not intended to be used by user programs. *) +type parser_env + type parse_tables = - { actions : (unit -> Obj.t) array; + { actions : (parser_env -> Obj.t) array; transl_const : int array; transl_block : int array; lhs : string; @@ -48,5 +50,5 @@ exception YYexit of Obj.t val yyparse : parse_tables -> int -> (Lexing.lexbuf -> 'a) -> Lexing.lexbuf -> 'b -val peek_val : int -> 'a +val peek_val : parser_env -> int -> 'a val is_current_lookahead: 'a -> bool |