Update HACKING file with new build instructions
[SXSI/xpathcomp.git] / src / formula.ml
1 INCLUDE "utils.ml"
2 open Format
3
4
5 type 'hcons expr =
6   | False | True
7   | Or of 'hcons * 'hcons
8   | And of 'hcons * 'hcons
9   | Atom of ([ `Left | `Right ] * bool * State.t)
10   | Pred of Tree.Predicate.t
11
12 type 'hcons node = {
13   pos : 'hcons expr;
14   mutable neg : 'hcons;
15   st : (StateSet.t*StateSet.t*StateSet.t)*(StateSet.t*StateSet.t*StateSet.t);
16   size: int; (* Todo check if this is needed *)
17 }
18
19 external hash_const_variant : [> ] -> int = "%identity"
20
21 module rec Node : Hcons.S
22   with type data = Data.t = Hcons.Make (Data)
23   and Data : Hashtbl.HashedType  with type t = Node.t node =
24   struct
25     type t =  Node.t node
26     let equal x y = x.size == y.size &&
27       match x.pos, y.pos with
28         | a,b when a == b -> true
29         | Or(xf1, xf2), Or(yf1, yf2)
30         | And(xf1, xf2), And(yf1,yf2)  -> (xf1 == yf1) && (xf2 == yf2)
31         | Atom(d1, p1, s1), Atom(d2 ,p2 ,s2) -> d1 == d2 && p1 == p2 && s1 == s2
32         | Pred(p1), Pred(p2) -> p1 == p2
33         | _ -> false
34
35     let hash f =
36       match f.pos with
37         | False -> 0
38         | True -> 1
39         | Or (f1, f2) -> HASHINT3(PRIME2, Uid.to_int f1.Node.id, Uid.to_int f2.Node.id)
40         | And (f1, f2) -> HASHINT3(PRIME3, Uid.to_int f1.Node.id, Uid.to_int f2.Node.id)
41         | Atom(d, p, s) -> HASHINT4(PRIME4, hash_const_variant d,vb p,s)
42         | Pred(p) -> HASHINT2(PRIME5, Uid.to_int p.Tree.Predicate.id)
43   end
44
45 type t = Node.t
46 let hash x = x.Node.key
47 let uid x = x.Node.id
48 let equal = Node.equal
49 let expr f = f.Node.node.pos
50 let st f = f.Node.node.st
51 let size f = f.Node.node.size
52 let compare f1 f2 = compare f1.Node.id  f2.Node.id
53 let prio f =
54   match expr f with
55     | True | False -> 10
56     | Pred _ -> 9
57     | Atom _ -> 8
58     | And _ -> 6
59     | Or _ -> 1
60
61 let rec print ?(parent=false) ppf f =
62   if parent then fprintf ppf "(";
63   let _ = match expr f with
64     | True -> fprintf ppf "%s" Pretty.top
65     | False -> fprintf ppf "%s" Pretty.bottom
66     | And(f1,f2) ->
67         print ~parent:(prio f > prio f1) ppf f1;
68         fprintf ppf " %s "  Pretty.wedge;
69         print ~parent:(prio f > prio f2) ppf f2;
70     | Or(f1,f2) ->
71         (print ppf f1);
72         fprintf ppf " %s " Pretty.vee;
73         (print ppf f2);
74     | Atom(dir, b, s) ->
75         let _ = flush_str_formatter() in
76         let fmt = str_formatter in
77         let a_str, d_str =
78           match  dir with
79             | `Left ->  Pretty.down_arrow, Pretty.subscript 1
80             | `Right -> Pretty.down_arrow, Pretty.subscript 2
81         in
82           fprintf fmt "%s%s" a_str d_str;
83           State.print fmt s;
84           let str = flush_str_formatter() in
85             if b then fprintf ppf "%s" str
86             else Pretty.pp_overline ppf str
87     | Pred p -> fprintf ppf "P%s" (Pretty.subscript (Uid.to_int p.Tree.Predicate.id))
88   in
89     if parent then fprintf ppf ")"
90
91 let print ppf f =  print ~parent:false ppf f
92
93 let is_true f = (expr f) == True
94 let is_false f = (expr f) == False
95
96
97 let cons pos neg s1 s2 size1 size2 =
98   let nnode = Node.make { pos = neg; neg = (Obj.magic 0); st = s2; size = size2 } in
99   let pnode = Node.make { pos = pos; neg = nnode ; st = s1; size = size1 } in
100     (Node.node nnode).neg <- pnode; (* works because the neg field isn't taken into
101                                       account for hashing ! *)
102     pnode,nnode
103
104 let empty_triple = StateSet.empty,StateSet.empty,StateSet.empty
105 let empty_hex = empty_triple,empty_triple
106 let true_,false_ = cons True False empty_hex empty_hex 0 0
107 let atom_ d p s =
108   let si = StateSet.singleton s in
109   let ss = match d with
110     | `Left -> (si,StateSet.empty,si),empty_triple
111     | `Right -> empty_triple,(si,StateSet.empty,si)
112   in fst (cons (Atom(d,p,s)) (Atom(d,not p,s)) ss ss 1 1)
113
114 let pred_ p =
115   let fneg = !(p.Tree.Predicate.node) in
116   let pneg = Tree.Predicate.make (ref (fun t n -> not (fneg t n))) in
117   fst (cons (Pred p) (Pred pneg) empty_hex empty_hex 1 1)
118
119 let not_ f = f.Node.node.neg
120 let union_hex  ((l1,ll1,lll1),(r1,rr1,rrr1))  ((l2,ll2,lll2),(r2,rr2,rrr2)) =
121   (StateSet.mem_union l1 l2 ,StateSet.mem_union ll1 ll2,StateSet.mem_union lll1 lll2),
122   (StateSet.mem_union r1 r2 ,StateSet.mem_union rr1 rr2,StateSet.mem_union rrr1 rrr2)
123
124 let merge_states f1 f2 =
125   let sp =
126     union_hex (st f1) (st f2)
127   and sn =
128     union_hex (st (not_ f1)) (st (not_ f2))
129   in
130     sp,sn
131
132 let order f1 f2 = if uid f1  < uid f2 then f2,f1 else f1,f2
133
134 let or_ f1 f2 =
135   (* Tautologies: x|x, x|not(x) *)
136
137   if equal f1 f2 then f1
138   else if equal f1 (not_ f2) then true_
139
140       (* simplification *)
141   else if is_true f1 || is_true f2 then true_
142   else if is_false f1 && is_false f2 then false_
143   else if is_false f1 then f2
144   else if is_false f2 then f1 
145
146               (* commutativity of | *)
147   else
148     let f1, f2 = order f1 f2 in
149     let psize = (size f1) + (size f2) in
150     let nsize = (size (not_ f1)) + (size (not_ f2)) in
151     let sp, sn = merge_states f1 f2 in
152       fst (cons (Or(f1,f2)) (And(not_ f1, not_ f2)) sp sn psize nsize)
153
154
155 let and_ f1 f2 =
156   not_ (or_ (not_ f1) (not_ f2))
157
158
159 let of_bool = function true -> true_ | false -> false_
160
161 let or_pred f1 f2 =
162   match expr f1, expr f2 with
163     | Pred p1, Pred p2 ->
164         let fp1 = !(p1.Tree.Predicate.node)
165         and fp2 = !(p2.Tree.Predicate.node) in
166         pred_ (Tree.Predicate.make (ref (fun t n -> (fp1 t n) || (fp2 t n))))
167     | _ -> or_ f1 f2
168
169 let and_pred f1 f2 =
170   match expr f1, expr f2 with
171       Pred p1, Pred p2 ->
172         let fp1 = !(p1.Tree.Predicate.node)
173         and fp2 = !(p2.Tree.Predicate.node) in
174         pred_ (Tree.Predicate.make (ref (fun t n -> (fp1 t n) && (fp2 t n))))
175     | _ -> and_ f1 f2
176
177
178 module Infix = struct
179   let ( +| ) f1 f2 = or_ f1 f2
180
181   let ( *& ) f1 f2 = and_ f1 f2
182
183   let ( *+ ) d s = atom_ d true s
184   let ( *- ) d s = atom_ d false s
185 end