summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorNicolas Pouillard <np@nicolaspouillard.fr>2008-09-19 12:54:10 +0000
committerNicolas Pouillard <np@nicolaspouillard.fr>2008-09-19 12:54:10 +0000
commitf0de463f2879ce16db1f8957e8c17249a32ed5a6 (patch)
tree5a11e781be0fb25bebb42a38eaeac30b5f8e0f34
parentd385cf85912bfd6dc148557e846f4defdf4c5552 (diff)
camlp4: more test fixtures
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@9033 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--camlp4/test/fixtures/assert.ml3
-rw-r--r--camlp4/test/fixtures/curry-constr.ml3
-rw-r--r--camlp4/test/fixtures/exception-with-eqn-bug.ml1
-rw-r--r--camlp4/test/fixtures/loc-bug.ml3
-rw-r--r--camlp4/test/fixtures/macrotest.mli25
-rw-r--r--camlp4/test/fixtures/method_private_virtual.ml9
-rw-r--r--camlp4/test/fixtures/stream-parser-bug.ml6
-rw-r--r--camlp4/test/fixtures/superfluous.ml12
8 files changed, 62 insertions, 0 deletions
diff --git a/camlp4/test/fixtures/assert.ml b/camlp4/test/fixtures/assert.ml
new file mode 100644
index 000000000..8d9ea4998
--- /dev/null
+++ b/camlp4/test/fixtures/assert.ml
@@ -0,0 +1,3 @@
+module MySet = Set.Make(String);;
+let set = MySet.empty;;
+assert (MySet.is_empty set);;
diff --git a/camlp4/test/fixtures/curry-constr.ml b/camlp4/test/fixtures/curry-constr.ml
new file mode 100644
index 000000000..4443ece49
--- /dev/null
+++ b/camlp4/test/fixtures/curry-constr.ml
@@ -0,0 +1,3 @@
+type t = A of int
+type u = B of t
+let f = function B A x -> x
diff --git a/camlp4/test/fixtures/exception-with-eqn-bug.ml b/camlp4/test/fixtures/exception-with-eqn-bug.ml
new file mode 100644
index 000000000..b93c20241
--- /dev/null
+++ b/camlp4/test/fixtures/exception-with-eqn-bug.ml
@@ -0,0 +1 @@
+exception Foo of string = Bar
diff --git a/camlp4/test/fixtures/loc-bug.ml b/camlp4/test/fixtures/loc-bug.ml
new file mode 100644
index 000000000..2901e6f85
--- /dev/null
+++ b/camlp4/test/fixtures/loc-bug.ml
@@ -0,0 +1,3 @@
+#default_quotation "expr";;
+Lwt.return
+ << 3 + >>
diff --git a/camlp4/test/fixtures/macrotest.mli b/camlp4/test/fixtures/macrotest.mli
new file mode 100644
index 000000000..4912fd34c
--- /dev/null
+++ b/camlp4/test/fixtures/macrotest.mli
@@ -0,0 +1,25 @@
+DEFINE A;
+DEFINE B;
+
+IFDEF A THEN
+ value a_should_be_present : int;
+ENDIF;
+
+IFNDEF C THEN
+ value b_should_be_present : int;
+ENDIF;
+
+IFNDEF C THEN
+ value c_should_be_present : int;
+ELSE
+ value a_should_NOT_be_present : int;
+END;
+
+IFDEF C THEN
+ value b_should_NOT_be_present : int;
+ELSE
+ value d_should_be_present : int;
+ value e_should_be_present : int;
+ENDIF;
+
+value f_should_be_present : int;
diff --git a/camlp4/test/fixtures/method_private_virtual.ml b/camlp4/test/fixtures/method_private_virtual.ml
new file mode 100644
index 000000000..6c0b94a62
--- /dev/null
+++ b/camlp4/test/fixtures/method_private_virtual.ml
@@ -0,0 +1,9 @@
+class virtual c1 = object method virtual private f : unit end;;
+class virtual c2 = object method private virtual f : unit end;;
+
+<:str_item< class virtual c1 = object method virtual private f : unit; end >>;;
+<:str_item< class virtual c2 = object method private virtual f : unit; end >>;;
+<:str_item< class virtual c2 = object method $private:p$ virtual f : unit; end >>;;
+<:str_item< class virtual c2 = object method virtual $private:p$ f : unit; end >>;;
+<:str_item< class $virtual:v$ c2 [$t1$] =
+ object ($pat:self$) method virtual $private:p$ $lid:f$ : $t2$; end >>;;
diff --git a/camlp4/test/fixtures/stream-parser-bug.ml b/camlp4/test/fixtures/stream-parser-bug.ml
new file mode 100644
index 000000000..6c17793ce
--- /dev/null
+++ b/camlp4/test/fixtures/stream-parser-bug.ml
@@ -0,0 +1,6 @@
+let foo = parser
+ | [< '42; ps >] ->
+ let ps = ps + 42 in
+ type_phrases ps
+ | [< >] -> [< >]
+
diff --git a/camlp4/test/fixtures/superfluous.ml b/camlp4/test/fixtures/superfluous.ml
new file mode 100644
index 000000000..79b086b90
--- /dev/null
+++ b/camlp4/test/fixtures/superfluous.ml
@@ -0,0 +1,12 @@
+open Camlp4.PreCast;;
+open Syntax;;
+
+let _loc = Loc.ghost;;
+let st = <:str_item< >>;;
+let e = <:expr< 1 >>
+let bi = <:binding< x = 0 >>;;
+
+(* none of these holds due to superfluous StSem and StNil *)
+assert (Ast.StSem (_loc, st, st) = <:str_item< $st$ $st$ >>);;
+assert (Ast.StExp (_loc, e) = <:str_item< $exp:e$ >>);;
+assert (Ast.StVal (_loc, bi) = <:str_item< let $bi$ >>);;