53872b3fb3a3c49788be7f24706fc1b0cd802598
[SXSI/xpathcomp.git] / tree.ml
1 (******************************************************************************)
2 (*  SXSI : XPath evaluator                                                    *)
3 (*  Kim Nguyen (Kim.Nguyen@nicta.com.au)                                      *)
4 (*  Copyright NICTA 2008                                                      *)
5 (*  Distributed under the terms of the LGPL (see LICENCE)                     *)
6 (******************************************************************************)
7 module type BINARY =
8 sig
9   type node_content
10   type string_content
11   type descr = Nil | Node of node_content  |String of string_content 
12   type t
13   val parse_xml_uri : string -> t
14   val parse_xml_string : string -> t
15   val string : t -> string
16   val descr : t -> descr
17   val left : t -> t
18   val right : t -> t
19   val id : t -> int
20   val tag : t -> Tag.t
21   val print_xml_fast : out_channel -> t -> unit
22   val compare : t -> t -> int
23   val equal : t -> t -> bool
24 end
25
26 module OldBinary = 
27 struct
28
29   type string_content = string
30   type descr = Nil | Node of node_content  | String of string_content
31   and node_content = int*Tag.t * descr * descr * (descr ref)
32   type t = descr
33       
34   let descr t = t
35
36   let string = function String s -> s | _ -> failwith "string"
37     
38  
39   external parse_xml_uri : string -> t = "caml_call_shredder_uri"
40   external parse_xml_string : string -> t = "caml_call_shredder_string"
41        
42   let parse_xml_uri s = Node(0,Tag.tag "",parse_xml_uri s,Nil,ref Nil)
43   let parse_xml_string s = Node(0,Tag.tag "",parse_xml_string s,Nil,ref Nil)
44   let tstring = function Nil -> "Nil"
45     | Node (_,_,_,_,_) -> "Node"
46     | String _ -> "String"
47         
48
49 let print_xml fmt t =
50   let pp_str = Format.pp_print_string fmt in
51   let rec loop = function Nil -> ()
52     | String (s) -> pp_str s
53     | Node (_,t,l,r,_) when Tag.equal t Tag.pcdata -> loop l;loop r
54     | Node (_,t,l,r,_) -> 
55         pp_str ("<" ^ (Tag.to_string t));
56         ( match l with
57               Nil -> pp_str "/>"
58             | Node(_,t',atts,children,_) when Tag.equal t' Tag.attribute -> 
59                 (loop_attributes atts;
60                  match children with
61                    | Nil -> pp_str "/>"
62                    | _ -> 
63                        pp_str ">"; 
64                        loop children;
65                        pp_str ("</"^ (Tag.to_string t)^">" )
66                 )
67             | _ -> pp_str ">"; loop l;          
68                 pp_str ("</"^ (Tag.to_string t)^">" );
69         );loop r
70   and loop_attributes = function 
71     | Node(_,t,Node(_,_,String(s),_,_),r,_) ->
72         pp_str (" "^(Tag.to_string t)^"=\""^ s ^"\"") ;
73         loop_attributes r
74     | _ -> ()
75
76   in
77     loop t
78
79 let print_xml fmt = 
80   function Node(i,t,l,_,_) -> print_xml fmt (Node(i,t,l,Nil,ref Nil))
81   | t -> print_xml fmt t
82
83
84 (* a bit ugly but inlining like this makes serialization faster *)
85
86 let print_xml_fast outc t =
87   let rec loop = function Nil -> ()
88     | String (s) -> output_string outc  s
89     | Node (_,t,l,r,_) when Tag.equal t Tag.pcdata -> loop l;loop r
90     | Node (_,t,l,r,_) -> let t = Tag.to_string t in
91         output_char outc  '<';
92         output_string outc  t;
93         ( match l with
94               Nil -> output_string outc  "/>"
95             | Node(_,t',atts,children,_) when Tag.equal t' Tag.attribute -> 
96                 (loop_attributes atts;
97                  match children with
98                    | Nil -> output_string outc  "/>"
99                    | _ -> 
100                        output_char outc  '>'; 
101                        loop children;
102                        output_string outc  "</";
103                        output_string outc  t;
104                        output_char outc '>' )
105             | _ ->
106                 output_char outc  '>'; 
107                 loop l;         
108                 output_string outc  "</";
109                 output_string outc t;
110                 output_char outc '>'
111         );loop r
112   and loop_attributes = function 
113     | Node(_,t,Node(_,_,String(s),_,_),r,_) -> 
114         output_char outc ' ';
115         output_string outc (Tag.to_string t);
116         output_string outc "=\"";
117         output_string outc s;
118         output_char outc '"';
119         loop_attributes r
120     | _ -> ()
121
122   in
123     loop t
124
125 let print_xml_fast outc = 
126   function Node(i,t,l,_,_) -> print_xml_fast outc (Node(i,t,l,Nil,ref Nil))
127   | t -> print_xml_fast outc t
128
129
130
131 let tabs = ref 0
132
133 let prtabs fmt = 
134   for i = 0 to !tabs 
135   do
136     Format.fprintf fmt " "
137   done
138
139     
140 let rec dump fmt t = 
141   incr tabs;
142   let _ = match t with
143     | Nil ->  prtabs fmt; Format.fprintf fmt "#" 
144     | String s -> prtabs fmt; Format.fprintf fmt "(String %s)" s
145     | Node(id,t,l,r,_) -> 
146         prtabs fmt;
147         Format.fprintf fmt " (tag='";
148         Tag.print fmt t;
149         Format.fprintf fmt "', id='%i')\n" id;
150         prtabs fmt;
151         dump fmt l;
152         Format.fprintf fmt "\n";
153         prtabs fmt;
154         dump fmt r;
155         Format.fprintf fmt "\n";
156         prtabs fmt;prtabs fmt;
157         Format.fprintf fmt "(id='%i'end )\n" id
158   in decr tabs
159         
160           
161 let dump fmt t = 
162   tabs:=0;
163   dump fmt t;
164   tabs:=0
165
166 let id = function Node(i,_,_,_,_) -> i
167   | _ -> failwith "id"
168
169 let tag = function Node(_,t,_,_,_) -> t
170   | _ -> failwith "tag"
171
172 let left = function Node(_,_,l,_,_) -> l
173   | _ -> failwith "left"
174
175 let right = function Node(_,_,_,r,_) -> r
176   | _ -> failwith "right"
177
178 let first_child = left
179 let next_sibling = right
180
181 let is_root = function Node (_,_,_,_,{contents=Nil}) -> true | _ -> false
182 let is_left n = match n with
183   | Node (_,_,_,_,{contents=p}) when not(is_root n) && (left p) == n -> true 
184   | _ -> false
185
186 let is_right n = match n with
187   | Node (_,_,_,_,{contents=p}) when not(is_root n) && (right p) == n -> true 
188   | _ -> false
189
190
191 let compare t1 t2 = match t1,t2 with
192   | Nil,Nil -> 0
193   | String s1, String s2 -> String.compare s1 s2
194   | Nil, String _ -> -1
195   | String _, Nil -> 1
196   | Node(i1,_,_,_,_), Node(i2,_,_,_,_) -> i1 - i2
197   | _, Node _ -> -1
198   | Node _ , _ -> 1
199 let equal t1 t2 = (compare t1 t2) == 0
200
201 let int_size = Sys.word_size/8
202 let ssize s = ((String.length s)/4 +1)*4 
203 let rec size = 
204   function Nil -> (int_size,1,0,0) 
205     | String s -> (int_size + (ssize s),0,1,0)
206     | Node(_,_,l,r,_) -> 
207         let sizel,nl,sl,il = size l 
208         and sizer,nr,sr,ir = size r 
209         in
210           (sizel+sizer+(7*int_size),nl+nr,sl+sr,il+ir+1)
211 let size t = 
212   let s,n,st,i = size t in
213     s/1024,n,st,i
214 end 
215
216
217 module XML = 
218 struct
219
220   type t
221   type 'a node = int
222   type node_kind = [`Text | `Tree ]
223
224   let compare : 'a node -> 'a node -> int = fun x y -> x - y
225   let equal : 'a node -> 'a node -> bool = fun x y -> x == y
226
227         (* abstract type, values are pointers to a XMLTree C++ object *)
228     
229     
230   external parse_xml_uri : string  -> t = "caml_call_shredder_uri"
231   let parse_xml_uri uri = parse_xml_uri uri
232     
233   external parse_xml_string :  string  -> t = "caml_call_shredder_string"
234   let parse_xml_string uri = parse_xml_string uri
235     
236
237   module Text =
238   struct
239     type t (* pointer to the text collection *)
240     (* Todo *)
241     external nullt : unit -> [`Text ] node = "caml_xml_tree_nullt"
242     let nil = nullt ()
243     external get_text : t -> [`Text] node -> string = "caml_text_collection_get_text"
244     let is_empty _ (n : [`Text] node) = equal nil n
245
246     end
247   module Tree = 
248   struct
249
250       
251     external serialize : string -> unit = "caml_xml_tree_serialize"
252     external unserialize : string -> t = "caml_xml_tree_unserialize"
253       
254     external root : t -> [`Tree] node = "caml_xml_tree_root"
255     external nullt : unit -> [`Tree ] node = "caml_xml_tree_nullt"
256
257     let nil = nullt ()
258     let is_nil x = equal x nil
259
260     external parent : t -> [`Tree] node -> [`Tree] node = "caml_xml_tree_first_child"
261     external parent_doc : t -> [`Text ] node -> [`Tree ] node = "caml_xml_tree_parent_doc"
262     external first_child : t -> [`Tree] node -> [`Tree] node = "caml_xml_tree_first_child"
263     external next_sibling : t -> [`Tree] node -> [`Tree] node = "caml_xml_tree_next_sibling"
264
265     external is_leaf : t  -> [`Tree] node -> bool = "caml_xml_tree_is_leaf"
266       
267     external tag : t -> [`Tree ] node -> Tag.t = "caml_xml_tree_tag"
268
269     external text_collection : t -> Text.t = "caml_xml_tree_text_collection"
270
271     let is_last t n = equal nil (next_sibling t n)
272     
273     external prev_text : t -> [`Tree] node -> [`Text ] node = "caml_xml_tree_prev_text"
274     external my_text : t -> [`Tree] node -> [`Text ] node = "caml_xml_tree_my_text"
275     external next_text : t -> [`Tree] node -> [`Text ] node = "caml_xml_tree_next_text"
276       
277     external text_xml_id : t -> [`Text ] node -> int = "caml_xml_tree_text_xml_id"
278     external node_xml_id : t -> [`Tree ] node -> int = "caml_xml_tree_node_xml_id"
279             
280   end
281       
282       
283   module Binary : BINARY = struct
284     
285     type node_content = 
286         [ `Node of [`Tree ] node 
287         | `String of [`Text ] node * [`Tree ] node ]
288     type string_content = [ `Text ] node
289     type descr = 
290       | Nil 
291       | Node of node_content
292       | String of string_content
293
294     type doc = t
295
296     type t = { doc : doc;
297                node : descr }
298         
299
300     open Tree                  
301     let node_of_t t = { doc= t; node= Node(`Node (root t)) }
302
303
304     let parse_xml_uri str = node_of_t (parse_xml_uri str)
305     let parse_xml_string str = node_of_t (parse_xml_string str)
306
307     let compare a b = match a.node,b.node  with
308       | Node(`Node i),Node(`Node j) -> compare i j
309       | _, Node(`Node( _ )) -> 1
310       | Node(`String (i,_)),Node(`String (j,_)) -> compare i j
311       | Node(`Node( _ )),Node(`String (_,_)) -> -1
312       | _, Node(`String (_,_)) -> 1
313       | String i, String j -> compare i j
314       | Node _ , String _ -> -1
315       | _ , String _ -> 1
316       | Nil, Nil -> 0
317       | _,Nil -> -1
318
319     let equal a b = (compare a b) == 0
320
321     let string t = match t.node with
322       | String i -> Text.get_text (text_collection t.doc) i
323       | _ -> assert false
324           
325     let norm (n : [`Tree ] node ) =  if is_nil n then Nil else Node (`Node n)
326         
327     let descr t = t.node
328
329     let first_child n = 
330       let node' = 
331         match n.node with
332           | Nil | String _ -> failwith "first_child"
333           | Node (`Node t) -> 
334               let fs = first_child n.doc t in
335               let txt = prev_text n.doc t in
336                 if Text.is_empty (text_collection n.doc) txt
337                 then norm fs
338                 else Node (`String (txt, fs))
339                   
340           | Node(`String (i,_)) -> String i
341       in
342         { n with node = node'}
343           
344     let next_sibling n = 
345       let node' =
346         match n.node with
347           | Nil | String _  -> failwith "next_sibling"
348           | Node (`String (_,ns)) -> norm ns
349           | Node(`Node t) ->
350               let ns = next_sibling n.doc t in
351               let txt = next_text n.doc t in
352                 if Text.is_empty (text_collection n.doc) txt
353                 then norm ns
354                 else Node (`String (txt, ns))
355       in
356         { n with node = node'}
357           
358           
359     let left = first_child
360     let right = next_sibling
361     let id = 
362       function  { doc=d; node=Node(`Node n)}  -> text_xml_id d n
363         | { doc=d;  node=Node(`String (i,_) )} -> node_xml_id d i
364         | _ -> failwith "id"
365             
366     let tag = 
367       function { node=Node(`String _) } -> Tag.pcdata
368         | { doc=d; node=Node(`Node n)} -> tag d n
369         | _ -> failwith "Tag"
370             
371             
372             
373     let print_xml_fast outc t =
374       let rec loop ?(print_right=true) t = match t.node with 
375         | Nil -> ()
376         | String (s) -> output_string outc (string t)
377         | Node _ when Tag.equal (tag t) Tag.pcdata -> loop (left t); loop (right t)
378             
379         | Node (_) -> 
380             let tg = Tag.to_string (tag t) in
381             let l = left t 
382             and r = right t 
383             in
384               output_char outc  '<';
385               output_string outc  tg;
386               ( match l.node with
387                     Nil -> output_string outc  "/>"
388                   | Node(_) when Tag.equal (tag l) Tag.attribute -> 
389                       (loop_attributes (left l);
390                        match (right l).node with
391                          | Nil -> output_string outc  "/>"
392                          | _ -> 
393                              output_char outc  '>'; 
394                              loop (right l);
395                              output_string outc  "</";
396                              output_string outc  tg;
397                              output_char outc '>' )
398                   | _ ->
399                       output_char outc  '>'; 
400                       loop (left l);            
401                       output_string outc  "</";
402                       output_string outc tg;
403                       output_char outc '>'
404               );if print_right then loop r
405       and loop_attributes a = match a.node with 
406         | Node(_) -> let value = string (left(left a)) in
407             output_char outc ' ';
408             output_string outc (Tag.to_string (tag a));
409             output_string outc "=\"";
410             output_string outc value;
411             output_char outc '"';
412             loop_attributes (right a)
413         | _ -> ()
414       in
415         loop ~print_right:false t
416           
417   end
418     
419 end
420 include XML