Sanitize header files and add a timestamp mark in each source file.
[tatoo.git] / src / ptset.ml
1 (* Original file: *)
2 (***********************************************************************)
3 (*                                                                     *)
4 (*  Copyright (C) Jean-Christophe Filliatre                            *)
5 (*                                                                     *)
6 (*  This software is free software; you can redistribute it and/or     *)
7 (*  modify it under the terms of the GNU Library General Public        *)
8 (*  License version 2.1, with the special exception on linking         *)
9 (*  described in file http://www.lri.fr/~filliatr/ftp/ocaml/ds/LICENSE *)
10 (*                                                                     *)
11 (*  This software is distributed in the hope that it will be useful,   *)
12 (*  but WITHOUT ANY WARRANTY; without even the implied warranty of     *)
13 (*  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.               *)
14 (*                                                                     *)
15 (***********************************************************************)
16
17 (*
18   Time-stamp: <Last modified on 2013-01-30 19:07:53 CET by Kim Nguyen>
19 *)
20
21 (* Modified by Kim Nguyen *)
22 (* The Patricia trees are themselves deeply hash-consed. The module
23    provides a Make (and Weak) functor to build hash-consed patricia
24    trees whose elements are Abstract hash-consed values.
25 *)
26
27 INCLUDE "utils.ml"
28
29 include Sigs.PTSET
30
31 module type HConsBuilder =
32   functor (H : Sigs.AUX.HashedType) -> Hcons.S with type data = H.t
33
34 module Builder (HCB : HConsBuilder) (H : Hcons.Abstract) :
35   S with type elt = H.t =
36 struct
37   type elt = H.t
38
39   type 'a set =
40     | Empty
41     | Leaf of elt
42     | Branch of int * int * 'a * 'a
43
44   module rec Node : Hcons.S with type data = Data.t = HCB(Data)
45                             and Data : Sigs.AUX.HashedType with type t = Node.t set =
46   struct
47     type t =  Node.t set
48     let equal x y =
49       match x,y with
50       | Empty,Empty -> true
51       | Leaf k1, Leaf k2 ->  k1 == k2
52       | Branch(b1,i1,l1,r1), Branch(b2,i2,l2,r2) ->
53           b1 == b2 && i1 == i2 && (Node.equal l1 l2) && (Node.equal r1 r2)
54
55       | _ -> false
56
57     let hash = function
58     | Empty -> 0
59     | Leaf i -> HASHINT2 (PRIME1, Uid.to_int (H.uid i))
60     | Branch (b,i,l,r) ->
61         HASHINT4(b, i, Uid.to_int l.Node.id, Uid.to_int r.Node.id)
62   end
63
64   include Node
65
66   let empty = Node.make Empty
67
68   let is_empty s = (Node.node s) == Empty
69
70   let branch p m l r = Node.make (Branch(p,m,l,r))
71
72   let leaf k = Node.make (Leaf k)
73
74                             (* To enforce the invariant that a branch contains two non empty
75                                sub-trees *)
76   let branch_ne p m t0 t1 =
77     if (is_empty t0) then t1
78     else if is_empty t1 then t0 else branch p m t0 t1
79
80                             (******** from here on, only use the smart constructors ************)
81
82   let zero_bit k m = (k land m) == 0
83
84   let singleton k = leaf k
85
86   let is_singleton n =
87     match Node.node n with Leaf _ -> true
88     | _ -> false
89
90   let mem (k:elt) n =
91     let kid = Uid.to_int (H.uid k) in
92     let rec loop n = match Node.node n with
93     | Empty -> false
94     | Leaf j ->  k == j
95     | Branch (p, _, l, r) -> if kid <= p then loop l else loop r
96     in loop n
97
98   let rec min_elt n = match Node.node n with
99   | Empty -> raise Not_found
100   | Leaf k -> k
101   | Branch (_,_,s,_) -> min_elt s
102
103   let rec max_elt n = match Node.node n with
104   | Empty -> raise Not_found
105   | Leaf k -> k
106   | Branch (_,_,_,t) -> max_elt t
107
108   let elements s =
109     let rec elements_aux acc n = match Node.node n with
110     | Empty -> acc
111     | Leaf k -> k :: acc
112     | Branch (_,_,l,r) -> elements_aux (elements_aux acc r) l
113     in
114     elements_aux [] s
115
116   let mask k m  = (k lor (m-1)) land (lnot m)
117
118   let naive_highest_bit x =
119     assert (x < 256);
120     let rec loop i =
121       if i = 0 then 1 else if x lsr i = 1 then 1 lsl i else loop (i-1)
122     in
123     loop 7
124
125   let hbit = Array.init 256 naive_highest_bit
126   (*
127     external clz : int -> int = "caml_clz" "noalloc"
128     external leading_bit : int -> int = "caml_leading_bit" "noalloc"
129   *)
130   let highest_bit x =
131     try
132       let n = (x) lsr 24 in
133       if n != 0 then  hbit.(n) lsl 24
134       else let n = (x) lsr 16 in if n != 0 then hbit.(n) lsl 16
135         else let n = (x) lsr 8 in if n != 0 then hbit.(n) lsl 8
136           else hbit.(x)
137     with
138       _ -> raise (Invalid_argument ("highest_bit " ^ (string_of_int x)))
139
140   let highest_bit64 x =
141     let n = x lsr 32 in if n != 0 then highest_bit n lsl 32
142       else highest_bit x
143
144   let branching_bit p0 p1 = highest_bit64 (p0 lxor p1)
145
146   let join p0 t0 p1 t1 =
147     let m = branching_bit p0 p1  in
148     let msk = mask p0 m in
149     if zero_bit p0 m then
150     branch_ne msk m t0 t1
151     else
152     branch_ne msk m t1 t0
153
154   let match_prefix k p m = (mask k m) == p
155
156   let add k t =
157     let kid = Uid.to_int (H.uid k) in
158     assert (kid >=0);
159     let rec ins n = match Node.node n with
160     | Empty -> leaf k
161     | Leaf j ->  if j == k then n else join kid (leaf k) (Uid.to_int (H.uid j)) n
162     | Branch (p,m,t0,t1)  ->
163         if match_prefix kid p m then
164         if zero_bit kid m then
165         branch_ne p m (ins t0) t1
166         else
167         branch_ne p m t0 (ins t1)
168         else
169         join kid (leaf k)  p n
170     in
171     ins t
172
173   let remove k t =
174     let kid = Uid.to_int(H.uid k) in
175     let rec rmv n = match Node.node n with
176     | Empty -> empty
177     | Leaf j  -> if  k == j then empty else n
178     | Branch (p,m,t0,t1) ->
179         if match_prefix kid p m then
180         if zero_bit kid m then
181         branch_ne p m (rmv t0) t1
182         else
183         branch_ne p m t0 (rmv t1)
184         else
185         n
186     in
187     rmv t
188
189   (* should run in O(1) thanks to hash consing *)
190
191   let equal a b = Node.equal a b
192
193   let compare a b = (Uid.to_int (Node.uid a)) - (Uid.to_int (Node.uid b))
194
195   let rec merge s t =
196     if equal s t (* This is cheap thanks to hash-consing *)
197     then s
198     else
199     match Node.node s, Node.node t with
200     | Empty, _  -> t
201     | _, Empty  -> s
202     | Leaf k, _ -> add k t
203     | _, Leaf k -> add k s
204     | Branch (p,m,s0,s1), Branch (q,n,t0,t1) ->
205         if m == n && match_prefix q p m then
206         branch p  m  (merge s0 t0) (merge s1 t1)
207         else if m > n && match_prefix q p m then
208         if zero_bit q m then
209         branch_ne p m (merge s0 t) s1
210         else
211         branch_ne p m s0 (merge s1 t)
212         else if m < n && match_prefix p q n then
213         if zero_bit p n then
214         branch_ne q n (merge s t0) t1
215         else
216         branch_ne q n t0 (merge s t1)
217         else
218                                   (* The prefixes disagree. *)
219         join p s q t
220
221
222
223
224   let rec subset s1 s2 = (equal s1 s2) ||
225     match (Node.node s1,Node.node s2) with
226     | Empty, _ -> true
227     | _, Empty -> false
228     | Leaf k1, _ -> mem k1 s2
229     | Branch _, Leaf _ -> false
230     | Branch (p1,m1,l1,r1), Branch (p2,m2,l2,r2) ->
231         if m1 == m2 && p1 == p2 then
232         subset l1 l2 && subset r1 r2
233         else if m1 < m2 && match_prefix p1 p2 m2 then
234         if zero_bit p1 m2 then
235         subset l1 l2 && subset r1 l2
236         else
237         subset l1 r2 && subset r1 r2
238         else
239         false
240
241
242   let union s1 s2 = merge s1 s2
243                             (* Todo replace with e Memo Module *)
244
245   let rec inter s1 s2 =
246     if equal s1 s2
247     then s1
248     else
249     match (Node.node s1,Node.node s2) with
250     | Empty, _ -> empty
251     | _, Empty -> empty
252     | Leaf k1, _ -> if mem k1 s2 then s1 else empty
253     | _, Leaf k2 -> if mem k2 s1 then s2 else empty
254     | Branch (p1,m1,l1,r1), Branch (p2,m2,l2,r2) ->
255         if m1 == m2 && p1 == p2 then
256         merge (inter l1 l2)  (inter r1 r2)
257         else if m1 > m2 && match_prefix p2 p1 m1 then
258         inter (if zero_bit p2 m1 then l1 else r1) s2
259         else if m1 < m2 && match_prefix p1 p2 m2 then
260         inter s1 (if zero_bit p1 m2 then l2 else r2)
261         else
262         empty
263
264   let rec diff s1 s2 =
265     if equal s1 s2
266     then empty
267     else
268     match (Node.node s1,Node.node s2) with
269     | Empty, _ -> empty
270     | _, Empty -> s1
271     | Leaf k1, _ -> if mem k1 s2 then empty else s1
272     | _, Leaf k2 -> remove k2 s1
273     | Branch (p1,m1,l1,r1), Branch (p2,m2,l2,r2) ->
274         if m1 == m2 && p1 == p2 then
275         merge (diff l1 l2) (diff r1 r2)
276         else if m1 > m2 && match_prefix p2 p1 m1 then
277         if zero_bit p2 m1 then
278         merge (diff l1 s2) r1
279         else
280         merge l1 (diff r1 s2)
281         else if m1 < m2 && match_prefix p1 p2 m2 then
282         if zero_bit p1 m2 then diff s1 l2 else diff s1 r2
283         else
284         s1
285
286
287   (*s All the following operations ([cardinal], [iter], [fold], [for_all],
288     [exists], [filter], [partition], [choose], [elements]) are
289     implemented as for any other kind of binary trees. *)
290
291   let rec cardinal n = match Node.node n with
292   | Empty -> 0
293   | Leaf _ -> 1
294   | Branch (_,_,t0,t1) -> cardinal t0 + cardinal t1
295
296   let rec iter f n = match Node.node n with
297   | Empty -> ()
298   | Leaf k -> f k
299   | Branch (_,_,t0,t1) -> iter f t0; iter f t1
300
301   let rec fold f s accu = match Node.node s with
302   | Empty -> accu
303   | Leaf k -> f k accu
304   | Branch (_,_,t0,t1) -> fold f t0 (fold f t1 accu)
305
306
307   let rec for_all p n = match Node.node n with
308   | Empty -> true
309   | Leaf k -> p k
310   | Branch (_,_,t0,t1) -> for_all p t0 && for_all p t1
311
312   let rec exists p n = match Node.node n with
313   | Empty -> false
314   | Leaf k -> p k
315   | Branch (_,_,t0,t1) -> exists p t0 || exists p t1
316
317   let rec filter pr n = match Node.node n with
318   | Empty -> empty
319   | Leaf k -> if pr k then n else empty
320   | Branch (p,m,t0,t1) -> branch_ne p m (filter pr t0) (filter pr t1)
321
322   let partition p s =
323     let rec part (t,f as acc) n = match Node.node n with
324     | Empty -> acc
325     | Leaf k -> if p k then (add k t, f) else (t, add k f)
326     | Branch (_,_,t0,t1) -> part (part acc t0) t1
327     in
328     part (empty, empty) s
329
330   let rec choose n = match Node.node n with
331   | Empty -> raise Not_found
332   | Leaf k -> k
333   | Branch (_, _,t0,_) -> choose t0   (* we know that [t0] is non-empty *)
334
335
336   let split x s =
337     let coll k (l, b, r) =
338       if k < x then add k l, b, r
339       else if k > x then l, b, add k r
340       else l, true, r
341     in
342     fold coll s (empty, false, empty)
343
344   (*s Additional functions w.r.t to [Set.S]. *)
345
346   let rec intersect s1 s2 = (equal s1 s2) ||
347     match (Node.node s1,Node.node s2) with
348     | Empty, _ -> false
349     | _, Empty -> false
350     | Leaf k1, _ -> mem k1 s2
351     | _, Leaf k2 -> mem k2 s1
352     | Branch (p1,m1,l1,r1), Branch (p2,m2,l2,r2) ->
353         if m1 == m2 && p1 == p2 then
354         intersect l1 l2 || intersect r1 r2
355         else if m1 < m2 && match_prefix p2 p1 m1 then
356         intersect (if zero_bit p2 m1 then l1 else r1) s2
357         else if m1 > m2 && match_prefix p1 p2 m2 then
358         intersect s1 (if zero_bit p1 m2 then l2 else r2)
359         else
360         false
361
362
363   let from_list l = List.fold_left (fun acc e -> add e acc) empty l
364
365
366 end
367
368 module Make = Builder(Hcons.Make)
369 module Weak = Builder(Hcons.Weak)
370
371 module PosInt
372   =
373 struct
374   include Make(Hcons.PosInt)
375   let print ppf s =
376     Format.pp_print_string ppf "{ ";
377     iter (fun i -> Format.fprintf ppf "%i " i) s;
378     Format.pp_print_string ppf "}";
379     Format.pp_print_flush ppf ()
380 end