Merged from branch stable-succint-refactor
[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 INCLUDE "debug.ml"
8 module type BINARY =
9 sig
10   type node_content
11   type string_content
12   type descr = Nil | Node of node_content  |String of string_content 
13   type t
14   val parse_xml_uri : string -> t
15   val parse_xml_string : string -> t
16   val save : t -> string -> unit
17   val load : ?sample:int -> string -> t
18   val tag_pool : t -> Tag.pool
19   val string : t -> string
20   val descr : t -> descr
21   val is_node : t -> bool
22   val left : t -> t
23   val right : t -> t
24   val first_child : t -> t
25   val next_sibling : t -> t
26   val parent : t -> t
27   val id : t -> int
28   val tag : t -> Tag.t
29   val print_xml_fast : out_channel -> t -> unit
30   val compare : t -> t -> int
31   val equal : t -> t -> bool
32   module DocIdSet :
33   sig 
34     include Set.S 
35   end
36     with type elt = string_content
37   val string_below : t -> string_content -> bool
38   val contains : t -> string -> DocIdSet.t
39   val contains_old : t -> string -> bool
40   val dump : t -> unit
41   val get_string : t -> string_content -> string
42   val has_tagged_desc : t -> Tag.t -> bool
43   val has_tagged_foll : t -> Tag.t -> bool
44   val tagged_desc : t -> Tag.t -> t
45   val tagged_foll : t -> Tag.t -> t
46   val tagged_next : t -> Tag.t -> t
47   val subtree_tags : t -> Tag.t -> int
48 end
49
50 module XML = 
51 struct
52
53   type t
54   type 'a node = int
55   type node_kind = [`Text | `Tree ]
56
57   let compare : 'a node -> 'a node -> int = (-)
58   let equal : 'a node -> 'a node -> bool = (==)
59
60         (* abstract type, values are pointers to a XMLTree C++ object *)
61     
62   external int_of_node : 'a node -> int = "%identity"
63
64   external parse_xml_uri : string -> int -> bool -> bool -> t = "caml_call_shredder_uri"         
65   external parse_xml_string :  string -> int -> bool -> bool -> t = "caml_call_shredder_string"
66
67   external save_tree : t -> string -> unit = "caml_xml_tree_save"
68   external load_tree : string -> int -> t = "caml_xml_tree_load"
69
70
71   module Text =
72   struct
73     let equal : [`Text] node -> [`Text] node -> bool = equal
74       
75     (* Todo *)
76     external nullt : unit -> [`Text ] node = "caml_xml_tree_nullt"
77     let nil = nullt ()
78     external get_text : t -> [`Text] node -> string = "caml_text_collection_get_text"
79
80     let get_text t n = 
81       if equal nil n then "" 
82       else  get_text t n
83                 
84     external is_empty : t -> [`Text ] node -> bool = "caml_text_collection_empty_text"
85     let is_empty t n =
86       (equal nil n) || is_empty t n
87
88     external is_contains : t -> string -> bool = "caml_text_collection_is_contains"
89     external count_contains : t -> string -> int = "caml_text_collection_count_contains"
90     external contains : t -> string -> [`Text ] node array = "caml_text_collection_contains"
91   end
92
93
94   module Tree = 
95   struct
96
97     let equal : [`Tree ] node -> [`Tree] node -> bool = equal
98     external serialize : t -> string -> unit = "caml_xml_tree_serialize"
99     external unserialize : string -> t = "caml_xml_tree_unserialize"
100       
101     external root : t -> [`Tree] node = "caml_xml_tree_root"
102     external nullt : unit -> [`Tree ] node = "caml_xml_tree_nullt"
103
104     let nil = nullt ()
105     let is_nil x = equal x nil
106
107     external parent : t -> [`Tree] node -> [`Tree] node = "caml_xml_tree_parent"
108     external parent_doc : t -> [`Text ] node -> [`Tree ] node = "caml_xml_tree_parent_doc"
109     external first_child : t -> [`Tree] node -> [`Tree] node = "caml_xml_tree_first_child"
110       
111
112       
113     external next_sibling : t -> [`Tree] node -> [`Tree] node = "caml_xml_tree_next_sibling"
114
115     external is_leaf : t  -> [`Tree] node -> bool = "caml_xml_tree_is_leaf"
116     
117 (*    external tag : t -> [`Tree ] node -> T = "caml_xml_tree_tag"*)
118     external tag_id : t -> [`Tree ] node -> Tag.t = "caml_xml_tree_tag_id"
119
120     let is_last t n = equal nil (next_sibling t n)
121     
122     external prev_text : t -> [`Tree] node -> [`Text ] node = "caml_xml_tree_prev_text" 
123
124
125     external my_text : t -> [`Tree] node -> [`Text ] node = "caml_xml_tree_my_text"
126     external next_text : t -> [`Tree] node -> [`Text ] node = "caml_xml_tree_next_text"
127
128     external text_xml_id : t -> [`Text ] node -> int = "caml_xml_tree_text_xml_id"
129     external node_xml_id : t -> [`Tree ] node -> int = "caml_xml_tree_node_xml_id"
130     external is_ancestor : t -> [`Tree ] node -> [`Tree ] node -> bool = "caml_xml_tree_is_ancestor"
131     external tagged_desc : t -> [`Tree ] node -> Tag.t -> [`Tree ] node = "caml_xml_tree_tagged_desc"
132     external tagged_foll : t -> [`Tree ] node -> Tag.t -> [`Tree ] node = "caml_xml_tree_tagged_foll"
133     external tagged_next : t -> [`Tree ] node -> Tag.t -> [`Tree ] node = "caml_xml_tree_tagged_next"
134     external subtree_tags : t -> [`Tree ] node -> Tag.t -> int = "caml_xml_tree_subtree_tags"
135
136     let print_skel t =
137       let rec aux id = 
138         if (is_nil id)
139         then Printf.eprintf "#\n"
140         else 
141           begin
142             Printf.eprintf "Node %i has tag '%s' DocOrder=%i, DocID of PrevText,MyText,NextText : (%i = %s,%i = %s,%i = %s) parent_doc(my_text)=%i\n%!" 
143               (int_of_node id)
144               (Tag.to_string (tag_id t id))
145               (node_xml_id t id)
146               (int_of_node (prev_text t id))
147               (Text.get_text t (prev_text t id))
148               (int_of_node (my_text t id))
149               (Text.get_text t (my_text t id))
150               (int_of_node (next_text t id))
151               (Text.get_text t (next_text t id))
152               (int_of_node(parent_doc t (my_text t id)));
153     
154             aux(first_child t id);
155             aux(next_sibling t id);
156           end
157       in
158         aux (root t)
159
160     let traversal t = 
161         let rec aux id =
162           if not (is_nil id)
163           then
164             begin
165               (* ignore (tag t id);
166               ignore (Text.get_text t (prev_text t id));
167               if (is_leaf t id)
168                 then ignore (Text.get_text t (my_text t id));
169               if (is_last t id)
170                 then ignore (Text.get_text t (next_text t id)); *)
171               aux (first_child t id);
172               aux (next_sibling t id);
173             end
174         in
175           aux (root t)
176   end
177       
178       
179   module Binary  = struct
180
181     type node_content = 
182         NC of [`Tree ] node 
183       | SC of [`Text ] node * [`Tree ] node 
184     type string_content = [ `Text ] node
185     type descr = 
186       | Nil 
187       | Node of node_content
188       | String of string_content
189
190     type doc = t
191
192     type t = { doc : doc;              
193                node : descr }
194         
195     let dump { doc=t } = Tree.print_skel t
196     module DocIdSet = struct
197       include Set.Make (struct type t = string_content
198                                let compare = (-) end)
199                         
200     end
201     let is_node = function { node=Node(_) } -> true | _ -> false
202       
203     let get_string t (i:string_content) = Text.get_text t.doc i
204     open Tree                  
205     let node_of_t t = { doc= t; 
206                         node = Node(NC (root t)) }
207
208
209     let parse_xml_uri str = node_of_t       
210       (MM((parse_xml_uri str 
211              !Options.sample_factor 
212              !Options.index_empty_texts
213              !Options.disable_text_collection),__LOCATION__))
214
215     let parse_xml_string str = node_of_t 
216       (MM((parse_xml_string str
217          !Options.sample_factor 
218          !Options.index_empty_texts 
219          !Options.disable_text_collection),__LOCATION__))
220
221
222     let save t str = save_tree t.doc str
223
224     let load ?(sample=64) str = node_of_t (load_tree str sample)
225
226
227     external pool : doc -> Tag.pool = "%identity"
228     let tag_pool t = pool t.doc
229
230     let compare a b = match a.node,b.node  with
231       | Node(NC i),Node(NC j) -> compare i j
232       | _, Node(NC( _ )) -> 1
233       | Node(SC (i,_)),Node(SC (j,_)) -> compare i j
234       | Node(NC( _ )),Node(SC (_,_)) -> -1
235       | _, Node(SC (_,_)) -> 1
236       | String i, String j -> compare i j
237       | Node _ , String _ -> -1
238       | _ , String _ -> 1
239       | Nil, Nil -> 0
240       | _,Nil -> -1
241
242     let equal a b = (compare a b) == 0
243
244     let string t = match t.node with
245       | String i ->  Text.get_text t.doc i
246       | _ -> assert false
247           
248     let norm (n : [`Tree ] node ) =  if is_nil n then Nil else Node (NC n)
249         
250     let descr t = t.node
251
252     let nts = function
253         Nil -> "Nil"
254       | String i -> Printf.sprintf "String %i" i
255       | Node (NC t) -> Printf.sprintf "Node (NC %i)"  (int_of_node t)
256       | Node (SC (t,i)) -> Printf.sprintf "Node (SC (%i,%i))"  (int_of_node t) (int_of_node i)
257
258
259     let parent n = 
260       let node' =
261         match n.node with
262           | Node(NC t) | Node(SC (_,t)) -> 
263               if (Tree.root n.doc) == t
264               then Nil
265               else Node(NC(Tree.parent n.doc t)) (* A parent node can never be a SC *)
266           | _ -> assert false
267       in
268         { n with node = node' }
269
270     let first_child n = 
271       let node' = 
272         match n.node with
273           | Node (NC t) when is_leaf n.doc t ->
274               let txt = my_text n.doc t in
275                 if Text.is_empty n.doc txt
276                 then Nil
277                 else Node(SC (txt,Tree.nil))
278           | Node (NC t) -> 
279               let fs = first_child n.doc t in
280               let txt = prev_text n.doc fs in
281                 if Text.is_empty n.doc txt
282                 then norm fs
283                 else Node (SC (txt, fs))                  
284           | Node(SC (i,_)) -> String i
285           | Nil | String _ -> failwith "first_child"
286       in
287         { n with node = node'}
288
289           
290     let next_sibling n = 
291       let node' =
292         match n.node with
293           | Node (SC (_,ns)) -> norm ns
294           | Node(NC t) ->
295               let ns = next_sibling n.doc t in
296               let txt = next_text n.doc t in
297                 if Text.is_empty n.doc txt
298                 then norm ns
299                 else Node (SC (txt, ns))
300           | Nil | String _  -> failwith "next_sibling"
301       in
302         { n with node = node'}
303           
304           
305     let left = first_child 
306     let right = next_sibling
307     
308     let id = 
309       function  { doc=d; node=Node(NC n)}  -> node_xml_id d n
310         | { doc=d;  node=Node(SC (i,_) )} -> text_xml_id d i
311         | _ -> failwith "id"
312             
313     let tag = 
314       function { node=Node(SC _) } -> Tag.pcdata
315         | { doc=d; node=Node(NC n)} -> tag_id d n
316         | _ -> failwith "tag"
317     
318 (*    let tag_id = 
319       function  { node=Node(SC _) } -> ()
320         | { doc=d; node=Node(NC n)} -> tag_id d n
321         | _ -> ()
322 *)
323     let string_below t id =
324       let strid = parent_doc t.doc id in
325         match t.node with
326           | Node(NC(i)) -> 
327               (Tree.equal i strid) || (is_ancestor t.doc i strid)
328           | Node(SC(i,_)) -> Text.equal i id
329           | _ -> false
330
331
332     let tagged_foll t tag =
333       if tag = Tag.attribute || tag = Tag.pcdata then failwith "tagged_foll"
334       else match t with
335         | { doc=d; node=Node(NC n) } -> { t with node = norm (tagged_foll d n tag) }
336         | { doc=d; node=Node(SC (_,n)) } when is_nil n -> { t with node= Nil } 
337         | { doc=d; node=Node(SC (_,n)) } ->
338             let nnode = 
339               if tag_id d n == tag then n
340               else 
341                 let n' = tagged_desc d n tag in
342                   if is_nil n' then tagged_foll d n tag
343                   else n'
344             in {t with node= norm nnode}
345         | _ -> { t with node=Nil }
346             
347
348     let tagged_desc t tag =
349       if tag = Tag.attribute || tag = Tag.pcdata then failwith "tagged_desc"
350       else match t with
351         | { doc=d; node=Node(NC n) } -> { t with node = norm (tagged_desc d n tag) }
352         | _ -> { t with node=Nil }
353
354
355     let tagged_next t tag =
356       if tag = Tag.attribute || tag = Tag.pcdata then failwith "tagged_next"
357       else match t with
358         | { doc=d; node=Node(NC n) } -> { t with node = norm (tagged_next d n tag) }
359         | { doc=d; node=Node(SC (_,n)) } -> { t with node = norm (tagged_next d n tag) }
360         | _ -> { t with node=Nil }
361
362     let subtree_tags t tag =
363       match t with 
364           { doc = d; node = Node(NC n) } -> subtree_tags d n tag
365         | _ -> 0
366
367
368
369     let has_tagged_foll t tag = is_node (tagged_foll t tag)
370     let has_tagged_desc t tag = is_node (tagged_desc t tag)
371
372     let contains t s = 
373       Array.fold_left (fun a i -> DocIdSet.add i a) DocIdSet.empty (Text.contains t.doc s)
374
375     let contains_old t s = 
376       let regexp = Str.regexp_string s in
377       let matching arg = 
378         try
379           let _ = Str.search_forward regexp arg 0;
380           in true
381         with _ -> false
382       in
383       let rec find t = match t.node with
384         | Nil -> false
385         | String _ -> matching (string t)
386         | Node(_) -> (find (left t )) || (find (right t)) 
387       in
388         find t 
389
390     let print_xml_fast outc t =
391       let rec loop ?(print_right=true) t = match t.node with 
392         | Nil -> ()
393         | String (s) -> output_string outc (string t)
394         | Node _ when Tag.equal (tag t) Tag.pcdata -> 
395             loop (left t); 
396             if print_right then loop (right t)
397             
398         | Node (_) -> 
399             let tg = Tag.to_string (tag t) in
400             let l = left t 
401             and r = right t 
402             in
403               output_char outc  '<';
404               output_string outc  tg;
405               ( match l.node with
406                     Nil -> output_string outc  "/>"
407                   | String _ -> assert false
408                   | Node(_) when Tag.equal (tag l) Tag.attribute -> 
409                       (loop_attributes (left l);
410                        match (right l).node with
411                          | Nil -> output_string outc  "/>"
412                          | _ -> 
413                              output_char outc  '>'; 
414                              loop (right l);
415                              output_string outc  "</";
416                              output_string outc  tg;
417                              output_char outc '>' )
418                   | _ ->
419                       output_char outc  '>'; 
420                       loop l;
421                       output_string outc "</";
422                       output_string outc tg;
423                       output_char outc '>'
424               );if print_right then loop r
425       and loop_attributes a =
426
427         match a.node with 
428           | Node(_) ->
429               let value =
430                 match (left a).node with
431                   | Nil -> ""
432                   | _ -> string (left(left a)) 
433               in
434                 output_char outc ' ';
435                 output_string outc (Tag.to_string (tag a));
436                 output_string outc "=\"";
437                 output_string outc value;
438                 output_char outc '"';
439                 loop_attributes (right a)
440         | _ -> ()
441       in
442         loop ~print_right:false t
443
444
445     let print_xml_fast outc t = 
446       if Tag.to_string (tag t) = "" then
447         print_xml_fast outc (first_child t)
448       else print_xml_fast outc t
449         
450     let traversal t = Tree.traversal t.doc
451     let full_traversal t = 
452       let rec aux n =
453         match n.node with
454         | Nil -> ()
455         | String i -> () (*ignore(Text.get_text t.doc i)  *)
456         | Node(_) -> 
457             (* tag_id n; *)
458             aux (first_child n);
459             aux (next_sibling n)
460       in aux t
461
462     let print_stats _ = ()
463   end
464
465 end
466
467
468
469 IFDEF DEBUG
470 THEN
471 module DEBUGTREE 
472   = struct
473     
474     let _timings = Hashtbl.create 107
475     
476
477     let time _ref f arg = 
478       let t1 = Unix.gettimeofday () in
479       let r = f arg in
480       let t2 = Unix.gettimeofday () in 
481       let t = (1000. *.(t2 -. t1)) in
482
483       let (time,count) = try 
484         Hashtbl.find _timings _ref
485       with
486         | Not_found -> 0.,0
487       in
488       let time = time+. t 
489       and count = count + 1
490       in
491         Hashtbl.replace _timings _ref (time,count);r
492
493     include XML.Binary
494
495
496     let first_child_ doc node = 
497      time ("XMLTree.FirstChild()") (XML.Tree.first_child doc)  node
498     let next_sibling_ doc node = 
499       time ("XMLTree.NextSibling()") (XML.Tree.next_sibling doc) node
500
501     let is_empty_ text node = 
502       time ("TextCollection.IsEmpty()") (XML.Text.is_empty text) node
503
504     let prev_text_ doc node = 
505       time ("XMLTree.PrevText()") (XML.Tree.prev_text doc) node
506
507     let my_text_ doc node = 
508       time ("XMLTree.MyText()") (XML.Tree.my_text doc) node
509         
510     let next_text_ doc node = 
511       time ("XMLTree.NextText()") (XML.Tree.next_text doc) node
512
513     let is_leaf_ doc node =  
514       time ("XMLTree.IsLeaf()") (XML.Tree.is_leaf doc ) node
515         
516     let node_xml_id_ doc node =  
517       time ("XMLTree.NodeXMLId()") (XML.Tree.node_xml_id doc ) node
518         
519     let text_xml_id_ doc node =  
520       time ("XMLTree.TextXMLId()") (XML.Tree.text_xml_id doc ) node
521
522
523     let first_child n =
524       let node' =
525         match n.node with
526           | Node (NC t) when is_leaf_ n.doc t ->
527               let txt = my_text_ n.doc t in
528                 if is_empty_ n.doc txt
529                 then Nil
530                 else Node(SC (txt,XML.Tree.nil))
531           | Node (NC t) ->
532               let fs = first_child_ n.doc t in
533               let txt = prev_text_ n.doc fs in
534                 if is_empty_ n.doc txt
535                 then norm fs
536                 else Node (SC (txt, fs))
537           | Node(SC (i,_)) -> String i
538           | Nil | String _ -> failwith "first_child"
539       in
540         { n with node = node'}
541
542           
543     let next_sibling n =
544       let node' =
545         match n.node with
546           | Node (SC (_,ns)) -> norm ns
547           | Node(NC t) ->
548               let ns = next_sibling_ n.doc t in
549               let txt = 
550                 if XML.Tree.is_nil ns then
551                   next_text_ n.doc t 
552                 else prev_text_ n.doc ns
553               in
554                 if is_empty_ n.doc txt
555                 then norm ns
556                 else Node (SC (txt, ns))
557           | Nil | String _  -> failwith "next_sibling"
558       in
559         { n with node = node'}
560
561     let id = 
562       function  { doc=d; node=Node(NC n)}  -> node_xml_id_ d n
563         | { doc=d;  node=Node(SC (i,_) )} -> text_xml_id_ d i
564         | _ -> failwith "id"
565             
566     (* Wrapper around critical function *)
567     let string t = time ("TextCollection.GetText()") (string) t
568     let left = first_child
569     let right = next_sibling
570     let tag t =  time ("XMLTree.GetTag()") (tag) t
571       
572     let print_stats ppf = 
573       let total_time,total_calls =
574         Hashtbl.fold  (fun _ (t,c) (tacc,cacc) ->
575                          tacc+. t, cacc + c)  _timings (0.,0)
576
577       in
578         Format.fprintf ppf
579           "Timing : Function Name, number of calls,%% of total calls, mean time, total time, %% of total time\n%!";
580         Hashtbl.iter (fun name (time,count) ->
581                         Format.fprintf ppf  "%-27s% 8d\t% 4.2f%%\t% 4.6f ms\t% 4.6f ms\t%04.2f%%\n%!"
582                           name 
583                           count 
584                           (100. *. (float_of_int count)/.(float_of_int total_calls))
585                           (time /. (float_of_int count))
586                           time
587                           (100. *. time /.  total_time)) _timings;
588         Format.fprintf ppf  "-------------------------------------------------------------------\n";
589         Format.fprintf ppf "%-27s% 8d\t% 4.0f%%\t########## ms\t% 4.6f ms\t% 4.0f%%\n%!"
590           "Total" total_calls 100. total_time 100.
591                           
592
593     let print_xml_fast outc t =
594       let rec loop ?(print_right=true) t = match t.node with 
595         | Nil -> ()
596         | String (s) -> output_string outc (string t)
597         | Node _ when Tag.equal (tag t) Tag.pcdata -> loop (left t); loop (right t)
598             
599         | Node (_) -> 
600             let tg = Tag.to_string (tag t) in
601             let l = left t 
602             and r = right t 
603             in
604               output_char outc  '<';
605               output_string outc  tg;
606               ( match l.node with
607                     Nil -> output_string outc  "/>"
608                   | String _ -> assert false
609                   | Node(_) when Tag.equal (tag l) Tag.attribute -> 
610                       (loop_attributes (left l);
611                        match (right l).node with
612                          | Nil -> output_string outc  "/>"
613                          | _ -> 
614                              output_char outc  '>'; 
615                              loop (right l);
616                              output_string outc  "</";
617                              output_string outc  tg;
618                              output_char outc '>' )
619                   | _ ->
620                       output_char outc  '>'; 
621                       loop l;
622                       output_string outc "</";
623                       output_string outc tg;
624                       output_char outc '>'
625               );if print_right then loop r
626       and loop_attributes a =
627
628         match a.node with 
629           | Node(_) ->
630               let value =
631                 match (left a).node with
632                   | Nil -> ""
633                   | _ -> string (left(left a)) 
634               in
635                 output_char outc ' ';
636                 output_string outc (Tag.to_string (tag a));
637                 output_string outc "=\"";
638                 output_string outc value;
639                 output_char outc '"';
640                 loop_attributes (right a)
641         | _ -> ()
642       in
643         loop ~print_right:false t
644
645
646     let print_xml_fast outc t = 
647       if Tag.to_string (tag t) = "" then
648         print_xml_fast outc (first_child t)
649       else print_xml_fast outc t
650
651         
652
653
654 end
655
656 module Binary = DEBUGTREE
657 ELSE
658 module Binary = XML.Binary
659 END (* IFDEF DEBUG *)