summaryrefslogtreecommitdiffstats
path: root/camlp4/boot/Camlp4.ml
diff options
context:
space:
mode:
authorNicolas Pouillard <np@nicolaspouillard.fr>2009-03-05 16:11:37 +0000
committerNicolas Pouillard <np@nicolaspouillard.fr>2009-03-05 16:11:37 +0000
commitc487f4e95742172fe17f6e69dab7d1770f0630b4 (patch)
tree7497b91582666fec74ce02211e35c8850f2b9813 /camlp4/boot/Camlp4.ml
parent436a615911f879f594025e4334e45af1e7903550 (diff)
camlp4: bootstrap
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@9180 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'camlp4/boot/Camlp4.ml')
-rw-r--r--camlp4/boot/Camlp4.ml46
1 files changed, 33 insertions, 13 deletions
diff --git a/camlp4/boot/Camlp4.ml b/camlp4/boot/Camlp4.ml
index 3a2f2828b..ee2172984 100644
--- a/camlp4/boot/Camlp4.ml
+++ b/camlp4/boot/Camlp4.ml
@@ -372,7 +372,6 @@ module Sig =
* - Daniel de Rauglaudre: initial version
* - Nicolas Pouillard: refactoring
*)
-
(** Camlp4 signature repository *)
(** {6 Basic signatures} *)
(** Signature with just a type. *)
@@ -1954,12 +1953,17 @@ module Sig =
val register_str_item_filter : Ast.str_item filter -> unit
+ val register_topphrase_filter : Ast.str_item filter -> unit
+
val fold_interf_filters :
('a -> Ast.sig_item filter -> 'a) -> 'a -> 'a
val fold_implem_filters :
('a -> Ast.str_item filter -> 'a) -> 'a -> 'a
+ val fold_topphrase_filters :
+ ('a -> Ast.str_item filter -> 'a) -> 'a -> 'a
+
end
module type DynAst =
@@ -13301,10 +13305,16 @@ module Struct =
let fold_implem_filters f i = Queue.fold f i implem_filters
+ let topphrase_filters = Queue.create ()
+
+ let fold_topphrase_filters f i = Queue.fold f i topphrase_filters
+
let register_sig_item_filter f = Queue.add f interf_filters
let register_str_item_filter f = Queue.add f implem_filters
+ let register_topphrase_filter f = Queue.add f topphrase_filters
+
end
end
@@ -17555,9 +17565,12 @@ module Printers =
end =
struct
module Id =
- struct let name = "Camlp4.Printers.Null"
- let version = Sys.ocaml_version
- end
+ struct
+ let name = "Camlp4.Printers.Null"
+
+ let version = Sys.ocaml_version
+
+ end
module Make (Syntax : Sig.Syntax) =
struct
@@ -17820,9 +17833,12 @@ module Printers =
open Format
module Id =
- struct let name = "Camlp4.Printers.OCaml"
- let version = Sys.ocaml_version
- end
+ struct
+ let name = "Camlp4.Printers.OCaml"
+
+ let version = Sys.ocaml_version
+
+ end
module Make (Syntax : Sig.Camlp4Syntax) =
struct
@@ -19254,9 +19270,12 @@ module Printers =
open Format
module Id =
- struct let name = "Camlp4.Printers.OCamlr"
- let version = Sys.ocaml_version
- end
+ struct
+ let name = "Camlp4.Printers.OCamlr"
+
+ let version = Sys.ocaml_version
+
+ end
module Make (Syntax : Sig.Camlp4Syntax) =
struct
@@ -20203,9 +20222,10 @@ module PreCast :
end =
struct
- module Id = struct let name = "Camlp4.PreCast"
- let version = Sys.ocaml_version
- end
+ module Id =
+ struct let name = "Camlp4.PreCast"
+ let version = Sys.ocaml_version
+ end
type camlp4_token =
Sig.camlp4_token =