summaryrefslogtreecommitdiffstats
path: root/testlabl
diff options
context:
space:
mode:
authorJacques Garrigue <garrigue at math.nagoya-u.ac.jp>2006-11-01 08:59:13 +0000
committerJacques Garrigue <garrigue at math.nagoya-u.ac.jp>2006-11-01 08:59:13 +0000
commit60b57896b33224dcd12fb568089c269eca4157d8 (patch)
tree2652d0ab88a20e18b97e06b2dcd6a600f59ea5c5 /testlabl
parent6ef4e22e548362a1bf893edb645dfba1d27e5ea2 (diff)
loosing abbreviation
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@7710 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'testlabl')
-rw-r--r--testlabl/bugs/privrows-abate.ml53
1 files changed, 53 insertions, 0 deletions
diff --git a/testlabl/bugs/privrows-abate.ml b/testlabl/bugs/privrows-abate.ml
new file mode 100644
index 000000000..4e31243bc
--- /dev/null
+++ b/testlabl/bugs/privrows-abate.ml
@@ -0,0 +1,53 @@
+type 'a termpc =
+ [`And of 'a * 'a
+ |`Or of 'a * 'a
+ |`Not of 'a
+ |`Atom of string
+ ]
+
+type 'a termk =
+ [`Dia of 'a
+ |`Box of 'a
+ |'a termpc
+ ]
+
+module type T = sig
+ type term
+ val map : (term -> term) -> term -> term
+ val nnf : term -> term
+ val nnf_not : term -> term
+end
+
+module Fpc(X : T with type term = private [> 'a termpc] as 'a) =
+ struct
+ type term = X.term termpc
+ let nnf = function
+ |`Not(`Atom _) as x -> x
+ |`Not x -> X.nnf_not x
+ | x -> X.map X.nnf x
+ let map f : term -> X.term = function
+ |`Not x -> `Not (f x)
+ |`And(x,y) -> `And (f x, f y)
+ |`Or (x,y) -> `Or (f x, f y)
+ |`Atom _ as x -> x
+ let nnf_not : term -> _ = function
+ |`Not x -> X.nnf x
+ |`And(x,y) -> `Or (X.nnf_not x, X.nnf_not y)
+ |`Or (x,y) -> `And (X.nnf_not x, X.nnf_not y)
+ |`Atom _ as x -> `Not x
+ end
+
+module Fk(X : T with type term = private [> 'a termk] as 'a) =
+ struct
+ type term = X.term termk
+ module Pc = Fpc(X)
+ let map f : term -> _ = function
+ |`Dia x -> `Dia (f x)
+ |`Box x -> `Box (f x)
+ |#termpc as x -> Pc.map f x
+ let nnf = Pc.nnf
+ let nnf_not : term -> _ = function
+ |`Dia x -> `Box (X.nnf_not x)
+ |`Box x -> `Dia (X.nnf_not x)
+ |#termpc as x -> Pc.nnf_not x
+ end