summaryrefslogtreecommitdiffstats
path: root/camlp4/examples/lambda_parser.ml
diff options
context:
space:
mode:
authorNicolas Pouillard <np@nicolaspouillard.fr>2008-09-19 12:50:41 +0000
committerNicolas Pouillard <np@nicolaspouillard.fr>2008-09-19 12:50:41 +0000
commitd385cf85912bfd6dc148557e846f4defdf4c5552 (patch)
treea586797404b4d4fbe2341e5e91278c9d40db0543 /camlp4/examples/lambda_parser.ml
parent7d912ae76a00ad7bbfa2ed1bda0dc9e93d754ce2 (diff)
camlp4: more examples and tests
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@9032 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'camlp4/examples/lambda_parser.ml')
-rw-r--r--camlp4/examples/lambda_parser.ml34
1 files changed, 34 insertions, 0 deletions
diff --git a/camlp4/examples/lambda_parser.ml b/camlp4/examples/lambda_parser.ml
new file mode 100644
index 000000000..9c7097679
--- /dev/null
+++ b/camlp4/examples/lambda_parser.ml
@@ -0,0 +1,34 @@
+(* Please keep me in sync with brion.inria.fr/gallium/index.php/Lambda_calculus_quotations *)
+
+type term =
+ | Lam of var * term
+ | App of term * term
+ | Int of int
+ | Var of var
+and var = string
+
+module LambdaGram = Camlp4.PreCast.MakeGram(Camlp4.PreCast.Lexer);;
+module Loc = Camlp4.PreCast.Loc;; (* should not be necessary when camlp4 will be fixed *)
+open Camlp4.Sig;; (* from tokens *)
+let term = LambdaGram.Entry.mk "term";;
+let term_eoi = LambdaGram.Entry.mk "lambda term quotation";;
+
+EXTEND LambdaGram
+ GLOBAL: term term_eoi;
+ term:
+ [ "top"
+ [ "fun"; v = var; "->"; t = term -> Lam(v, t) ]
+ | "app"
+ [ t1 = SELF; t2 = SELF -> App(t1, t2) ]
+ | "simple"
+ [ v = var -> Var(v)
+ | `INT(i, _) -> Int(i)
+ | "("; t = term; ")" -> t ]
+ ];
+ var:
+ [[ `LIDENT v -> v ]];
+ term_eoi:
+ [[ t = term; `EOI -> t ]];
+END;;
+
+let lambda_parser = LambdaGram.parse_string term_eoi;;