]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/camlp4/Camlp4/Struct/FreeVars.mli
update
[l4.git] / l4 / pkg / ocaml / contrib / camlp4 / Camlp4 / Struct / FreeVars.mli
1 (* camlp4r *)
2 (****************************************************************************)
3 (*                                                                          *)
4 (*                              Objective Caml                              *)
5 (*                                                                          *)
6 (*                            INRIA Rocquencourt                            *)
7 (*                                                                          *)
8 (*  Copyright   2006    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 (* Authors:
17  * - Nicolas Pouillard: initial version
18  *)
19
20 module Make (Ast : Sig.Camlp4Ast) : sig
21   module S : Set.S with type elt = string;
22
23   value fold_binding_vars : (string -> 'accu -> 'accu) -> Ast.binding -> 'accu -> 'accu;
24
25   class c_fold_pattern_vars ['accu] : [string -> 'accu -> 'accu] -> ['accu] ->
26     object
27       inherit Ast.fold;
28       value acc : 'accu;
29       method acc : 'accu;
30     end;
31
32   value fold_pattern_vars : (string -> 'accu -> 'accu) -> Ast.patt -> 'accu -> 'accu;
33
34   class fold_free_vars ['accu] : [string -> 'accu -> 'accu] -> [?env_init:S.t] -> ['accu] ->
35     object ('self_type)
36       inherit Ast.fold;
37       value free : 'accu;
38       value env : S.t;
39       method free : 'accu;
40       method set_env : S.t -> 'self_type;
41       method add_atom : string -> 'self_type;
42       method add_patt : Ast.patt -> 'self_type;
43       method add_binding : Ast.binding -> 'self_type;
44     end;
45
46   value free_vars : S.t -> Ast.expr -> S.t;
47
48 end;