summaryrefslogtreecommitdiffstats
path: root/camlp4
diff options
context:
space:
mode:
authorNicolas Pouillard <np@nicolaspouillard.fr>2008-10-03 15:28:05 +0000
committerNicolas Pouillard <np@nicolaspouillard.fr>2008-10-03 15:28:05 +0000
commitdb5e084aa2603597eb4e200080c4b2399f093c04 (patch)
tree99d7d6bd6e1271246f092c45ff2d5affa091b0e2 /camlp4
parentcdd086080461ed15994f8367c806b2eb6f811168 (diff)
camlp4: little cleanup in Grammar.Static
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@9054 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'camlp4')
-rw-r--r--camlp4/Camlp4/Struct/Grammar/Static.ml11
1 files changed, 5 insertions, 6 deletions
diff --git a/camlp4/Camlp4/Struct/Grammar/Static.ml b/camlp4/Camlp4/Struct/Grammar/Static.ml
index b20eed779..7d7b51eff 100644
--- a/camlp4/Camlp4/Struct/Grammar/Static.ml
+++ b/camlp4/Camlp4/Struct/Grammar/Static.ml
@@ -16,6 +16,10 @@
* - Daniel de Rauglaudre: initial version
* - Nicolas Pouillard: refactoring
*)
+
+value uncurry f (x,y) = f x y;
+value flip f x y = f y x;
+
module Make (Lexer : Sig.Lexer)
: Sig.Grammar.Static with module Loc = Lexer.Loc
and module Token = Lexer.Token
@@ -68,12 +72,7 @@ module Make (Lexer : Sig.Lexer)
value delete_rule = Delete.delete_rule;
value srules e rl =
- let t =
- List.fold_left
- (fun tree (symbols, action) -> Insert.insert_tree e symbols action tree)
- DeadEnd rl
- in
- Stree t;
+ Stree (List.fold_left (flip (uncurry (Insert.insert_tree e))) DeadEnd rl);
value sfold0 = Fold.sfold0;
value sfold1 = Fold.sfold1;
value sfold0sep = Fold.sfold0sep;