X-Git-Url: http://git.nguyen.vg/gitweb/?a=blobdiff_plain;f=tree.ml;h=487a057b30ad73301d11d3c9bef22f918df09c5c;hb=d4342e4bb9c853114de295567cd91ec86bb9e68f;hp=53872b3fb3a3c49788be7f24706fc1b0cd802598;hpb=705a37f90b2161deaae7d99cc6c95700613e2cb2;p=SXSI%2Fxpathcomp.git diff --git a/tree.ml b/tree.ml index 53872b3..487a057 100644 --- a/tree.ml +++ b/tree.ml @@ -4,6 +4,7 @@ (* Copyright NICTA 2008 *) (* Distributed under the terms of the LGPL (see LICENCE) *) (******************************************************************************) +INCLUDE "debug.ml" module type BINARY = sig type node_content @@ -12,208 +13,60 @@ sig type t val parse_xml_uri : string -> t val parse_xml_string : string -> t + val save : t -> string -> unit + val load : ?sample:int -> string -> t + val tag_pool : t -> Tag.pool val string : t -> string val descr : t -> descr + val is_node : t -> bool val left : t -> t val right : t -> t + val first_child : t -> t + val next_sibling : t -> t + val parent : t -> t + val root : t -> t + val is_root : t -> bool val id : t -> int val tag : t -> Tag.t val print_xml_fast : out_channel -> t -> unit val compare : t -> t -> int val equal : t -> t -> bool + module DocIdSet : + sig + include Set.S + end + with type elt = string_content + val string_below : t -> string_content -> bool + val contains : t -> string -> DocIdSet.t + val contains_old : t -> string -> DocIdSet.t + val contains_iter : t -> string -> DocIdSet.t + val count_contains : t -> string -> int + val count : t -> string -> int + val dump : t -> unit + val get_string : t -> string_content -> string + val has_tagged_desc : t -> Tag.t -> bool + val has_tagged_foll : t -> Tag.t -> bool + val tagged_desc : t -> Tag.t -> t + val tagged_foll : t -> Tag.t -> t + val tagged_below : t -> Ptset.t -> Ptset.t -> t + val tagged_next : t -> Ptset.t -> Ptset.t -> t -> t + val tagged_desc_only : t -> Ptset.t -> t + val tagged_foll_only : t -> Ptset.t -> t -> t + val text_below : t -> t + val text_next : t -> t -> t + val init_tagged_next : t -> Tag.t -> unit + val subtree_tags : t -> Tag.t -> int + val is_left : t -> bool + val print_id : Format.formatter -> t -> unit + val test_xml_tree : Format.formatter -> Ptset.t -> t -> unit + val init_contains : t -> string -> unit + val init_naive_contains : t -> string -> unit + val mk_nil : t -> t + val test_jump : t -> Tag.t -> unit + val time_xml_tree : t -> Tag.t -> int list + val time_xml_tree2 : t -> Tag.t -> int list end -module OldBinary = -struct - - type string_content = string - type descr = Nil | Node of node_content | String of string_content - and node_content = int*Tag.t * descr * descr * (descr ref) - type t = descr - - let descr t = t - - let string = function String s -> s | _ -> failwith "string" - - - external parse_xml_uri : string -> t = "caml_call_shredder_uri" - external parse_xml_string : string -> t = "caml_call_shredder_string" - - let parse_xml_uri s = Node(0,Tag.tag "",parse_xml_uri s,Nil,ref Nil) - let parse_xml_string s = Node(0,Tag.tag "",parse_xml_string s,Nil,ref Nil) - let tstring = function Nil -> "Nil" - | Node (_,_,_,_,_) -> "Node" - | String _ -> "String" - - -let print_xml fmt t = - let pp_str = Format.pp_print_string fmt in - let rec loop = function Nil -> () - | String (s) -> pp_str s - | Node (_,t,l,r,_) when Tag.equal t Tag.pcdata -> loop l;loop r - | Node (_,t,l,r,_) -> - pp_str ("<" ^ (Tag.to_string t)); - ( match l with - Nil -> pp_str "/>" - | Node(_,t',atts,children,_) when Tag.equal t' Tag.attribute -> - (loop_attributes atts; - match children with - | Nil -> pp_str "/>" - | _ -> - pp_str ">"; - loop children; - pp_str ("" ) - ) - | _ -> pp_str ">"; loop l; - pp_str ("" ); - );loop r - and loop_attributes = function - | Node(_,t,Node(_,_,String(s),_,_),r,_) -> - pp_str (" "^(Tag.to_string t)^"=\""^ s ^"\"") ; - loop_attributes r - | _ -> () - - in - loop t - -let print_xml fmt = - function Node(i,t,l,_,_) -> print_xml fmt (Node(i,t,l,Nil,ref Nil)) - | t -> print_xml fmt t - - -(* a bit ugly but inlining like this makes serialization faster *) - -let print_xml_fast outc t = - let rec loop = function Nil -> () - | String (s) -> output_string outc s - | Node (_,t,l,r,_) when Tag.equal t Tag.pcdata -> loop l;loop r - | Node (_,t,l,r,_) -> let t = Tag.to_string t in - output_char outc '<'; - output_string outc t; - ( match l with - Nil -> output_string outc "/>" - | Node(_,t',atts,children,_) when Tag.equal t' Tag.attribute -> - (loop_attributes atts; - match children with - | Nil -> output_string outc "/>" - | _ -> - output_char outc '>'; - loop children; - output_string outc "' ) - | _ -> - output_char outc '>'; - loop l; - output_string outc "' - );loop r - and loop_attributes = function - | Node(_,t,Node(_,_,String(s),_,_),r,_) -> - output_char outc ' '; - output_string outc (Tag.to_string t); - output_string outc "=\""; - output_string outc s; - output_char outc '"'; - loop_attributes r - | _ -> () - - in - loop t - -let print_xml_fast outc = - function Node(i,t,l,_,_) -> print_xml_fast outc (Node(i,t,l,Nil,ref Nil)) - | t -> print_xml_fast outc t - - - -let tabs = ref 0 - -let prtabs fmt = - for i = 0 to !tabs - do - Format.fprintf fmt " " - done - - -let rec dump fmt t = - incr tabs; - let _ = match t with - | Nil -> prtabs fmt; Format.fprintf fmt "#" - | String s -> prtabs fmt; Format.fprintf fmt "(String %s)" s - | Node(id,t,l,r,_) -> - prtabs fmt; - Format.fprintf fmt " (tag='"; - Tag.print fmt t; - Format.fprintf fmt "', id='%i')\n" id; - prtabs fmt; - dump fmt l; - Format.fprintf fmt "\n"; - prtabs fmt; - dump fmt r; - Format.fprintf fmt "\n"; - prtabs fmt;prtabs fmt; - Format.fprintf fmt "(id='%i'end )\n" id - in decr tabs - - -let dump fmt t = - tabs:=0; - dump fmt t; - tabs:=0 - -let id = function Node(i,_,_,_,_) -> i - | _ -> failwith "id" - -let tag = function Node(_,t,_,_,_) -> t - | _ -> failwith "tag" - -let left = function Node(_,_,l,_,_) -> l - | _ -> failwith "left" - -let right = function Node(_,_,_,r,_) -> r - | _ -> failwith "right" - -let first_child = left -let next_sibling = right - -let is_root = function Node (_,_,_,_,{contents=Nil}) -> true | _ -> false -let is_left n = match n with - | Node (_,_,_,_,{contents=p}) when not(is_root n) && (left p) == n -> true - | _ -> false - -let is_right n = match n with - | Node (_,_,_,_,{contents=p}) when not(is_root n) && (right p) == n -> true - | _ -> false - - -let compare t1 t2 = match t1,t2 with - | Nil,Nil -> 0 - | String s1, String s2 -> String.compare s1 s2 - | Nil, String _ -> -1 - | String _, Nil -> 1 - | Node(i1,_,_,_,_), Node(i2,_,_,_,_) -> i1 - i2 - | _, Node _ -> -1 - | Node _ , _ -> 1 -let equal t1 t2 = (compare t1 t2) == 0 - -let int_size = Sys.word_size/8 -let ssize s = ((String.length s)/4 +1)*4 -let rec size = - function Nil -> (int_size,1,0,0) - | String s -> (int_size + (ssize s),0,1,0) - | Node(_,_,l,r,_) -> - let sizel,nl,sl,il = size l - and sizer,nr,sr,ir = size r - in - (sizel+sizer+(7*int_size),nl+nr,sl+sr,il+ir+1) -let size t = - let s,n,st,i = size t in - s/1024,n,st,i -end - - module XML = struct @@ -221,34 +74,59 @@ struct type 'a node = int type node_kind = [`Text | `Tree ] - let compare : 'a node -> 'a node -> int = fun x y -> x - y - let equal : 'a node -> 'a node -> bool = fun x y -> x == y + let compare : 'a node -> 'a node -> int = (-) + let equal : 'a node -> 'a node -> bool = (==) (* abstract type, values are pointers to a XMLTree C++ object *) - - external parse_xml_uri : string -> t = "caml_call_shredder_uri" - let parse_xml_uri uri = parse_xml_uri uri - - external parse_xml_string : string -> t = "caml_call_shredder_string" - let parse_xml_string uri = parse_xml_string uri - + external int_of_node : 'a node -> int = "%identity" + + external parse_xml_uri : string -> int -> bool -> bool -> t = "caml_call_shredder_uri" + external parse_xml_string : string -> int -> bool -> bool -> t = "caml_call_shredder_string" + + external save_tree : t -> string -> unit = "caml_xml_tree_save" + external load_tree : string -> int -> t = "caml_xml_tree_load" + module Text = struct - type t (* pointer to the text collection *) + let equal : [`Text] node -> [`Text] node -> bool = equal + (* Todo *) external nullt : unit -> [`Text ] node = "caml_xml_tree_nullt" let nil = nullt () external get_text : t -> [`Text] node -> string = "caml_text_collection_get_text" - let is_empty _ (n : [`Text] node) = equal nil n - end +(* let get_text t n = + if equal nil n then "" + else get_text t n +*) + + external is_empty : t -> [`Text ] node -> bool = "caml_text_collection_empty_text" + + let is_empty t n = + (equal nil n) || is_empty t n + + external get_cached_text : t -> [`Text ] node -> string = "caml_text_collection_get_cached_text" + + + let get_text t n = + if equal nil n then "" + else get_cached_text t n + + external size : t -> int = "caml_text_collection_size" + external is_contains : t -> string -> bool = "caml_text_collection_is_contains" + external count_contains : t -> string -> int = "caml_text_collection_count_contains" + external count : t -> string -> int = "caml_text_collection_count" + external contains : t -> string -> [`Text ] node array = "caml_text_collection_contains" + end + + module Tree = struct - - external serialize : string -> unit = "caml_xml_tree_serialize" + let equal : [`Tree ] node -> [`Tree] node -> bool = equal + external serialize : t -> string -> unit = "caml_xml_tree_serialize" external unserialize : string -> t = "caml_xml_tree_unserialize" external root : t -> [`Tree] node = "caml_xml_tree_root" @@ -257,34 +135,203 @@ struct let nil = nullt () let is_nil x = equal x nil - external parent : t -> [`Tree] node -> [`Tree] node = "caml_xml_tree_first_child" + external parent : t -> [`Tree] node -> [`Tree] node = "caml_xml_tree_parent" external parent_doc : t -> [`Text ] node -> [`Tree ] node = "caml_xml_tree_parent_doc" + external prev_doc : t -> [`Text ] node -> [`Tree ] node = "caml_xml_tree_prev_doc" external first_child : t -> [`Tree] node -> [`Tree] node = "caml_xml_tree_first_child" - external next_sibling : t -> [`Tree] node -> [`Tree] node = "caml_xml_tree_next_sibling" + - external is_leaf : t -> [`Tree] node -> bool = "caml_xml_tree_is_leaf" - external tag : t -> [`Tree ] node -> Tag.t = "caml_xml_tree_tag" + external next_sibling : t -> [`Tree] node -> [`Tree] node = "caml_xml_tree_next_sibling" + external prev_sibling : t -> [`Tree] node -> [`Tree] node = "caml_xml_tree_prev_sibling" + external is_leaf : t -> [`Tree] node -> bool = "caml_xml_tree_is_leaf" + +(* external tag : t -> [`Tree ] node -> T = "caml_xml_tree_tag"*) + external tag_id : t -> [`Tree ] node -> Tag.t = "caml_xml_tree_tag_id" - external text_collection : t -> Text.t = "caml_xml_tree_text_collection" +(* + let tag_hash = Array.make 6_000_000 (Tag.nullt) + let tag_id t id = + let tag = tag_hash.(int_of_node id) + in + if tag != Tag.nullt then tag + else + let tag = tag_id t id in + (tag_hash.(int_of_node id) <- tag; tag) +*) let is_last t n = equal nil (next_sibling t n) - external prev_text : t -> [`Tree] node -> [`Text ] node = "caml_xml_tree_prev_text" + external prev_text : t -> [`Tree] node -> [`Text ] node = "caml_xml_tree_prev_text" + + external my_text : t -> [`Tree] node -> [`Text ] node = "caml_xml_tree_my_text" external next_text : t -> [`Tree] node -> [`Text ] node = "caml_xml_tree_next_text" - + external doc_ids : t -> [`Tree ] node -> [`Text ] node * [`Text ] node = "caml_xml_tree_doc_ids" external text_xml_id : t -> [`Text ] node -> int = "caml_xml_tree_text_xml_id" external node_xml_id : t -> [`Tree ] node -> int = "caml_xml_tree_node_xml_id" - + external is_ancestor : t -> [`Tree ] node -> [`Tree ] node -> bool = "caml_xml_tree_is_ancestor" + external tagged_desc : t -> [`Tree ] node -> Tag.t -> [`Tree ] node = "caml_xml_tree_tagged_desc" + external tagged_foll : t -> [`Tree ] node -> Tag.t -> [`Tree ] node = "caml_xml_tree_tagged_foll" + external subtree_tags : t -> [`Tree ] node -> Tag.t -> int = "caml_xml_tree_subtree_tags" + external tagged_below : t -> [`Tree ] node -> Ptset.int_vector -> Ptset.int_vector -> [`Tree ] node = "caml_xml_tree_tagged_below" + external tagged_desc_only : t -> [`Tree ] node -> Ptset.int_vector -> [`Tree ] node = "caml_xml_tree_tagged_desc_only" + external tagged_next : t -> [`Tree ] node -> Ptset.int_vector -> Ptset.int_vector -> [`Tree ] node -> [`Tree ] node = "caml_xml_tree_tagged_next" + external tagged_foll_only : t -> [`Tree ] node -> Ptset.int_vector -> [`Tree ] node -> [`Tree ] node = "caml_xml_tree_tagged_foll_only" + external tagged_desc_or_foll_only : t -> [`Tree ] node -> Ptset.int_vector -> [`Tree ] node -> [`Tree ] node = "caml_xml_tree_tagged_foll_only" + external tagged_foll_below : t -> [`Tree ] node -> Tag.t -> [`Tree ] node -> [`Tree ] node = "caml_xml_tree_tagged_foll_below" + + let test_jump tree tag = + let rec loop id ctx = + if id != nil + then + let first = tagged_desc tree id tag + and next = tagged_desc tree id tag + in + loop first id; + loop next ctx + in + loop (root tree) (root tree) + + + let test_xml_tree ppf tags v = + let pr x = Format.fprintf ppf x in + let rec aux id = + if (is_nil id) + then () + else + begin + pr "Node %i, (Tag) %i='%s' (GetTagName), NodeXMLId (Preorder)=%i\n%!" + (int_of_node id) + (tag_id v id) + (Tag.to_string (tag_id v id)) + (node_xml_id v id); + pr "DocID of PrevText,MyText,NextText : (%i = %s,%i = %s,%i = %s) ParentDoc(my_text)=%i PrevDoc(next_text)=%i\n%!" + (int_of_node (prev_text v id)) + (Text.get_text v (prev_text v id)) + (int_of_node (my_text v id)) + (Text.get_text v (my_text v id)) + (int_of_node (next_text v id)) + (Text.get_text v (next_text v id)) + (int_of_node(parent_doc v (my_text v id))) + (int_of_node(prev_doc v (next_text v id))); + let i1,i2 = doc_ids v id in + pr "Testing DocIds below (%i,%i)*\n%!" + (int_of_node i1) (int_of_node i2); + pr "Testing Tagged*\n%!"; + Ptset.iter (fun t -> + let str = Tag.to_string t in + if Tag.pcdata <> t + then begin + pr "Tag: %s : \n%!" str; + pr "TaggedDesc = %i%!, " (tagged_desc v id t); + pr "TaggedFoll = %i\n%!" (tagged_foll v id t); + pr "SubtreeTags = %i\n%!" (subtree_tags v id t); + end) tags; + pr "----------------------------\n"; + aux(first_child v id); + aux(next_sibling v id); + end + in + aux (root v) + + let rrrr = ref 0 + + let time_xml_tree v tag = + + let rec aux id acc = + incr rrrr; + if (is_nil id) + then acc + else begin + let acc = + if tag == (tag_id v id) + then + id::acc + else acc + in + aux (next_sibling v id) (aux (first_child v id) acc); + end + in + let r = aux (root v) [] in + Printf.eprintf "%i\n%!" !rrrr;r + + let rrrr2 = ref 0 + let time_xml_tree2 v tag = + let rec aux id acc ctx= + incr rrrr2; + if (is_nil id) + then acc + else begin + let acc = + if tag == (tag_id v id) + then + id::acc + else acc + in + aux (tagged_foll_below v id tag ctx) (aux (tagged_desc v id tag) acc id) ctx; + end + in + let r = aux (root v) [] (root v) in + Printf.eprintf "%i\n%!" !rrrr2; r + + + + + + + let print_skel t = + let rec aux id = + if (is_nil id) + then Printf.eprintf "#\n" + else + begin + Printf.eprintf "Node %i has tag '%i=%s' DocOrder=%i, DocID of PrevText,MyText,NextText : (%i = %s,%i = %s,%i = %s) parent_doc(my_text)=%i\n%!" + (int_of_node id) + (tag_id t id) + (Tag.to_string (tag_id t id)) + (node_xml_id t id) + (int_of_node (prev_text t id)) + (Text.get_text t (prev_text t id)) + (int_of_node (my_text t id)) + (Text.get_text t (my_text t id)) + (int_of_node (next_text t id)) + (Text.get_text t (next_text t id)) + (int_of_node(parent_doc t (my_text t id))); + + aux(first_child t id); + aux(next_sibling t id); + end + in + aux (root t) + + let traversal t = + let rec aux id = + if not (is_nil id) + then + begin + (* ignore (tag t id); + ignore (Text.get_text t (prev_text t id)); + if (is_leaf t id) + then ignore (Text.get_text t (my_text t id)); + if (is_last t id) + then ignore (Text.get_text t (next_text t id)); *) + aux (first_child t id); + aux (next_sibling t id); + end + in + aux (root t) + + + end - module Binary : BINARY = struct - + module Binary = struct + type node_content = - [ `Node of [`Tree ] node - | `String of [`Text ] node * [`Tree ] node ] + NC of [`Tree ] node + | SC of [`Text ] node * [`Tree ] node type string_content = [ `Text ] node type descr = | Nil @@ -293,23 +340,89 @@ struct type doc = t - type t = { doc : doc; + type t = { doc : doc; node : descr } + let dump { doc=t } = Tree.print_skel t + let test_xml_tree ppf tags { doc=t } = Tree.test_xml_tree ppf tags t + let time_xml_tree { doc=t } tag = Tree.time_xml_tree t tag + let time_xml_tree2 { doc=t } tag = Tree.time_xml_tree2 t tag + let test_jump { doc=t } tag = Tree.test_jump t tag + let contains_array = ref [| |] + + let init_contains t s = + let a = Text.contains t.doc s + in + Array.fast_sort (compare) a; + contains_array := a + + let init_naive_contains t s = + let i,j = Tree.doc_ids t.doc (Tree.root t.doc) + in + let regexp = Str.regexp_string s in + let matching arg = + try + let _ = Str.search_forward regexp arg 0; + in true + with _ -> false + in + let rec loop n acc l = + if n >= j then acc,l + else + let s = (*Printf.eprintf "%i \n%!" n;*)Text.get_cached_text t.doc n + in + if matching s + then loop (n+1) (n::acc) (l+1) + else loop (n+1) acc l + in + let acc,l = loop i [] 0 in + let a = Array.create l Text.nil in + let _ = List.fold_left (fun cpt e -> a.(cpt) <- e; (cpt-1)) (l-1) acc + in + contains_array := a + + + module DocIdSet = struct + include Set.Make (struct type t = string_content + let compare = (-) end) + + end + let is_node = function { node=Node(_) } -> true | _ -> false + + let get_string t (i:string_content) = Text.get_text t.doc i open Tree - let node_of_t t = { doc= t; node= Node(`Node (root t)) } + let node_of_t t = { doc= t; + node = Node(NC (root t)) } + + + let parse_xml_uri str = node_of_t + (MM((parse_xml_uri str + !Options.sample_factor + !Options.index_empty_texts + !Options.disable_text_collection),__LOCATION__)) + + let parse_xml_string str = node_of_t + (MM((parse_xml_string str + !Options.sample_factor + !Options.index_empty_texts + !Options.disable_text_collection),__LOCATION__)) + + let save t str = save_tree t.doc str - let parse_xml_uri str = node_of_t (parse_xml_uri str) - let parse_xml_string str = node_of_t (parse_xml_string str) + let load ?(sample=64) str = node_of_t (load_tree str sample) + + + external pool : doc -> Tag.pool = "%identity" + let tag_pool t = pool t.doc let compare a b = match a.node,b.node with - | Node(`Node i),Node(`Node j) -> compare i j - | _, Node(`Node( _ )) -> 1 - | Node(`String (i,_)),Node(`String (j,_)) -> compare i j - | Node(`Node( _ )),Node(`String (_,_)) -> -1 - | _, Node(`String (_,_)) -> 1 + | Node(NC i),Node(NC j) -> compare i j + | _, Node(NC( _ )) -> 1 + | Node(SC (i,_)),Node(SC (j,_)) -> compare i j + | Node(NC( _ )),Node(SC (_,_)) -> -1 + | _, Node(SC (_,_)) -> 1 | String i, String j -> compare i j | Node _ , String _ -> -1 | _ , String _ -> 1 @@ -319,62 +432,364 @@ struct let equal a b = (compare a b) == 0 let string t = match t.node with - | String i -> Text.get_text (text_collection t.doc) i + | String i -> Text.get_text t.doc i | _ -> assert false - let norm (n : [`Tree ] node ) = if is_nil n then Nil else Node (`Node n) + let norm (n : [`Tree ] node ) = if is_nil n then Nil else Node (NC n) let descr t = t.node + let nts = function + Nil -> "Nil" + | String i -> Printf.sprintf "String %i" i + | Node (NC t) -> Printf.sprintf "Node (NC %i)" (int_of_node t) + | Node (SC (t,i)) -> Printf.sprintf "Node (SC (%i,%i))" (int_of_node t) (int_of_node i) + + let mk_nil t = { t with node = Nil } + let root n = { n with node = norm (Tree.root n.doc) } + let is_root n = match n.node with + | Node(NC t) -> (int_of_node t) == 0 + | _ -> false + + let parent n = + if is_root n then { n with node=Nil} + else + let node' = + match n.node with + | Node(NC t) -> + let txt = prev_text n.doc t in + if Text.is_empty n.doc txt then + let ps = Tree.prev_sibling n.doc t in + if is_nil ps + then + Node(NC (Tree.parent n.doc t)) + else Node(NC ps) + else + Node(SC (txt,t)) + | Node(SC(i,t)) -> + let ps = Tree.prev_sibling n.doc t in + if is_nil ps + then Node (NC(parent_doc n.doc i)) + else Node(NC ps) + | _ -> failwith "parent" + in + { n with node = node' } + let first_child n = let node' = match n.node with - | Nil | String _ -> failwith "first_child" - | Node (`Node t) -> + | Node (NC t) when is_leaf n.doc t -> + let txt = my_text n.doc t in + if Text.is_empty n.doc txt + then Nil + else Node(SC (txt,Tree.nil)) + | Node (NC t) -> let fs = first_child n.doc t in - let txt = prev_text n.doc t in - if Text.is_empty (text_collection n.doc) txt + let txt = prev_text n.doc fs in + if Text.is_empty n.doc txt then norm fs - else Node (`String (txt, fs)) - - | Node(`String (i,_)) -> String i + else Node (SC (txt, fs)) + | Node(SC (i,_)) -> String i + | Nil | String _ -> failwith "first_child" in { n with node = node'} let next_sibling n = let node' = match n.node with - | Nil | String _ -> failwith "next_sibling" - | Node (`String (_,ns)) -> norm ns - | Node(`Node t) -> + | Node (SC (_,ns)) -> norm ns + | Node(NC t) -> let ns = next_sibling n.doc t in let txt = next_text n.doc t in - if Text.is_empty (text_collection n.doc) txt + if Text.is_empty n.doc txt then norm ns - else Node (`String (txt, ns)) + else Node (SC (txt, ns)) + | Nil | String _ -> failwith "next_sibling" in { n with node = node'} - let left = first_child + let left = first_child let right = next_sibling + let id = - function { doc=d; node=Node(`Node n)} -> text_xml_id d n - | { doc=d; node=Node(`String (i,_) )} -> node_xml_id d i - | _ -> failwith "id" + function { doc=d; node=Node(NC n)} -> node_xml_id d n + | { doc=d; node=Node(SC (i,_) )} -> text_xml_id d i + | _ -> -1 (* + Format.fprintf Format.err_formatter "Failure id on %s\n%!" (nts x.node); + failwith "id" *) let tag = - function { node=Node(`String _) } -> Tag.pcdata - | { doc=d; node=Node(`Node n)} -> tag d n - | _ -> failwith "Tag" + function { node=Node(SC _) } -> Tag.pcdata + | { doc=d; node=Node(NC n)} -> tag_id d n + | _ -> failwith "tag" + + let string_below t id = + let strid = parent_doc t.doc id in + match t.node with + | Node(NC(i)) -> + (Tree.equal i strid) || (is_ancestor t.doc i strid) + | Node(SC(i,_)) -> Text.equal i id + | _ -> false + + + let tagged_foll t tag = + if tag = Tag.attribute || tag = Tag.pcdata then failwith "tagged_foll" + else match t with + | { doc=d; node=Node(NC n) } -> { t with node = norm (tagged_foll d n tag) } + | { doc=d; node=Node(SC (_,n)) } when is_nil n -> { t with node= Nil } + | { doc=d; node=Node(SC (_,n)) } -> + let nnode = + if tag_id d n == tag then n + else + let n' = tagged_desc d n tag in + if is_nil n' then tagged_foll d n tag + else n' + in {t with node= norm nnode} + | _ -> { t with node=Nil } + + let tagged_desc t tag = + if tag = Tag.attribute || tag = Tag.pcdata then failwith "tagged_desc" + else match t with + | { doc=d; node=Node(NC n) } -> { t with node = norm (tagged_desc d n tag) } + | _ -> { t with node=Nil } + + let tagged_next t tb tf s = + match s with + | { node = Node (NC(below)) } -> begin + match t with + | { doc = d; node=Node(NC n) } -> + { t with node= norm (tagged_next d n (Ptset.to_int_vector tb) (Ptset.to_int_vector tf) below) } + | { doc = d; node=Node(SC (i,n) ) } when is_nil n -> + let p = parent_doc d i in + { t with node= norm (tagged_next d p (Ptset.to_int_vector tb) (Ptset.to_int_vector tf) below) } + | { doc = d; node=Node(SC (_,n) ) } -> + if Ptset.mem (tag_id d n) (Ptset.union tb tf) + then { t with node=Node(NC(n)) } + else + let vb = Ptset.to_int_vector tb in + let vf = Ptset.to_int_vector tf in + let node = + let dsc = tagged_below d n vb vf in + if is_nil dsc + then tagged_next d n vb vf below + else dsc + in + { t with node = norm node } + | _ -> {t with node=Nil } + end + | _ -> {t with node=Nil } + + let tagged_foll_only t tf s = + match s with + | { node = Node (NC(below)) } -> begin + match t with + | { doc = d; node=Node(NC n) } -> + { t with node= norm (tagged_foll_only d n (Ptset.to_int_vector tf) below) } + | { doc = d; node=Node(SC (i,n) ) } when is_nil n -> + let p = parent_doc d i in + { t with node= norm (tagged_foll_only d p (Ptset.to_int_vector tf) below) } + | { doc = d; node=Node(SC (_,n) ) } -> + if Ptset.mem (tag_id d n) tf + then { t with node=Node(NC(n)) } + else + let vf = Ptset.to_int_vector tf in + let node = + let dsc = tagged_desc_only d n vf in + if is_nil dsc + then tagged_foll_only d n vf below + else dsc + in + { t with node = norm node } + | _ -> {t with node=Nil } + end + + | _ -> {t with node=Nil } + + + let tagged_below t tc td = + match t with + | { doc = d; node=Node(NC n) } -> + let vc = Ptset.to_int_vector tc + in + let vd = Ptset.to_int_vector td + in + { t with node= norm(tagged_below d n vc vd) } + | _ -> { t with node=Nil } + + let tagged_desc_only t td = + match t with + | { doc = d; node=Node(NC n) } -> + let vd = Ptset.to_int_vector td + in + { t with node= norm(tagged_desc_only d n vd) } + | _ -> { t with node=Nil } + + + let last_idx = ref 0 + let array_find a i j = + let l = Array.length a in + let rec loop idx x y = + if x > y || idx >= l then Text.nil + else + if a.(idx) >= x then if a.(idx) > y then Text.nil else (last_idx := idx;a.(idx)) + else loop (idx+1) x y + in + if a.(0) > j || a.(l-1) < i then Text.nil + else loop !last_idx i j + + + let text_below t = + let l = Array.length !contains_array in + if l = 0 then { t with node=Nil } + else + match t with + | { doc = d; node=Node(NC n) } -> + let i,j = doc_ids t.doc n in + let id = array_find !contains_array i j + in + if id == Text.nil then + { t with node=Nil } + else + {t with node = Node(SC(id, Tree.next_sibling d (Tree.prev_doc d id))) } + | _ -> { t with node=Nil } + + let text_next t root = + let l = Array.length !contains_array in + if l = 0 then { t with node=Nil } + else + let inf = match t with + | { doc =d; node = Node(NC n) } -> snd(doc_ids d n)+1 + | { node = Node(SC(i,_)) } -> i+1 + | _ -> assert false + in + match root with + | { doc = d; node= Node (NC n) } -> + let _,j = doc_ids t.doc n in + + let id = array_find !contains_array inf j + in + if id == Text.nil then { doc = d; node= Nil } + else + {doc = d; node = Node(SC(id,Tree.next_sibling d (Tree.prev_doc d id))) } + | _ -> { t with node=Nil} + + + + let subtree_tags t tag = + match t with + { doc = d; node = Node(NC n) } -> + subtree_tags d n tag + | _ -> 0 + + let tagged_desc_array = ref [| |] + let idx = ref 0 + + let init_tagged_next t tagid = + let l = subtree_tags (root t) tagid + in + tagged_desc_array := Array.create l { t with node= Nil }; + let i = ref 0 in + let rec collect t = + if is_node t then begin + if tag t == tagid then + begin + !tagged_desc_array.(!i) <- t; + incr i; + end; + collect (first_child t); + collect (next_sibling t) + end; + in + collect t; + idx := 0 + + let print_id ppf v = + let pr x= Format.fprintf ppf x in + match v with + { node=Nil } -> pr "NULLT: -1" + | { node=String(i) } | { node=Node(SC(i,_)) } -> pr "DocID: %i" (int_of_node i) + | { node=Node(NC(i)) } -> pr "Node: %i" (int_of_node i) + + + +(* let tagged_next t tag = + if !idx >= Array.length !tagged_desc_array + then {t with node=Nil} + else + let r = !tagged_desc_array.(!idx) + in + incr idx; r +*) + + + let has_tagged_foll t tag = is_node (tagged_foll t tag) + let has_tagged_desc t tag = is_node (tagged_desc t tag) + + let contains t s = + Array.fold_left (fun a i -> DocIdSet.add i a) DocIdSet.empty (Text.contains t.doc s) + + + let contains_old t s = + let regexp = Str.regexp_string s in + let matching arg = + try + let _ = Str.search_forward regexp arg 0; + in true + with _ -> false + in + let rec find t acc = match t.node with + | Nil -> acc + | String i -> + if matching (string t) then DocIdSet.add i acc else acc + | Node(_) -> (find (left t )) ((find (right t)) acc) + in + find t DocIdSet.empty + + + let contains_iter t s = + let regexp = Str.regexp_string s in + let matching arg = + try + let _ = Str.search_forward regexp arg 0; + in true + with _ -> false + in + let size = Text.size t.doc in + let rec find acc n = + if n == size then acc + else + find + (if matching (Text.get_cached_text t.doc (Obj.magic n)) then + DocIdSet.add (Obj.magic n) acc + else acc) (n+1) + in + find DocIdSet.empty 0 + + + + + let count_contains t s = Text.count_contains t.doc s + let count t s = Text.count t.doc s + + let is_left t = + if is_root t then false + else + if tag (parent t) == Tag.pcdata then false + else + let u = left (parent t) in + (id t) == (id u) + let print_xml_fast outc t = let rec loop ?(print_right=true) t = match t.node with | Nil -> () - | String (s) -> output_string outc (string t) - | Node _ when Tag.equal (tag t) Tag.pcdata -> loop (left t); loop (right t) + | String (s) -> output_string outc (Text.get_text t.doc s) + | Node _ when Tag.equal (tag t) Tag.pcdata -> + loop (left t); + if print_right then loop (right t) | Node (_) -> let tg = Tag.to_string (tag t) in @@ -385,6 +800,7 @@ struct output_string outc tg; ( match l.node with Nil -> output_string outc "/>" + | String _ -> assert false | Node(_) when Tag.equal (tag l) Tag.attribute -> (loop_attributes (left l); match (right l).node with @@ -397,24 +813,247 @@ struct output_char outc '>' ) | _ -> output_char outc '>'; - loop (left l); - output_string outc "' );if print_right then loop r - and loop_attributes a = match a.node with - | Node(_) -> let value = string (left(left a)) in - output_char outc ' '; - output_string outc (Tag.to_string (tag a)); - output_string outc "=\""; - output_string outc value; - output_char outc '"'; - loop_attributes (right a) + and loop_attributes a = + + match a.node with + | Node(_) -> + let value = + match (left a).node with + | Nil -> "" + | _ -> string (left(left a)) + in + output_char outc ' '; + output_string outc (Tag.to_string (tag a)); + output_string outc "=\""; + output_string outc value; + output_char outc '"'; + loop_attributes (right a) | _ -> () in loop ~print_right:false t - + + + let print_xml_fast outc t = + if Tag.to_string (tag t) = "" then + print_xml_fast outc (first_child t) + else print_xml_fast outc t + + + + + + let traversal t = Tree.traversal t.doc + let full_traversal t = + let rec aux n = + match n.node with + | Nil -> () + | String i -> () (*ignore(Text.get_text t.doc i) *) + | Node(_) -> + (* tag_id n; *) + aux (first_child n); + aux (next_sibling n) + in aux t + + let print_stats _ = () end + +end + + + +IFDEF DEBUG +THEN +module DEBUGTREE + = struct + + let _timings = Hashtbl.create 107 + + let time _ref f arg = + let t1 = Unix.gettimeofday () in + let r = f arg in + let t2 = Unix.gettimeofday () in + let t = (1000. *.(t2 -. t1)) in + + let (time,count) = try + Hashtbl.find _timings _ref + with + | Not_found -> 0.,0 + in + let time = time+. t + and count = count + 1 + in + Hashtbl.replace _timings _ref (time,count);r + + include XML.Binary + + + let first_child_ doc node = + time ("XMLTree.FirstChild()") (XML.Tree.first_child doc) node + let next_sibling_ doc node = + time ("XMLTree.NextSibling()") (XML.Tree.next_sibling doc) node + + let is_empty_ text node = + time ("TextCollection.IsEmpty()") (XML.Text.is_empty text) node + + let prev_text_ doc node = + time ("XMLTree.PrevText()") (XML.Tree.prev_text doc) node + + let my_text_ doc node = + time ("XMLTree.MyText()") (XML.Tree.my_text doc) node + + let next_text_ doc node = + time ("XMLTree.NextText()") (XML.Tree.next_text doc) node + + let is_leaf_ doc node = + time ("XMLTree.IsLeaf()") (XML.Tree.is_leaf doc ) node + + let node_xml_id_ doc node = + time ("XMLTree.NodeXMLId()") (XML.Tree.node_xml_id doc ) node + + let text_xml_id_ doc node = + time ("XMLTree.TextXMLId()") (XML.Tree.text_xml_id doc ) node + + + let first_child n = + let node' = + match n.node with + | Node (NC t) when is_leaf_ n.doc t -> + let txt = my_text_ n.doc t in + if is_empty_ n.doc txt + then Nil + else Node(SC (txt,XML.Tree.nil)) + | Node (NC t) -> + let fs = first_child_ n.doc t in + let txt = prev_text_ n.doc fs in + if is_empty_ n.doc txt + then norm fs + else Node (SC (txt, fs)) + | Node(SC (i,_)) -> String i + | Nil | String _ -> failwith "first_child" + in + { n with node = node'} + + + let next_sibling n = + let node' = + match n.node with + | Node (SC (_,ns)) -> norm ns + | Node(NC t) -> + let ns = next_sibling_ n.doc t in + let txt = + if XML.Tree.is_nil ns then + next_text_ n.doc t + else prev_text_ n.doc ns + in + if is_empty_ n.doc txt + then norm ns + else Node (SC (txt, ns)) + | Nil | String _ -> failwith "next_sibling" + in + { n with node = node'} + + let id = + function { doc=d; node=Node(NC n)} -> node_xml_id_ d n + | { doc=d; node=Node(SC (i,_) )} -> text_xml_id_ d i + | _ -> failwith "id" + + (* Wrapper around critical function *) + let string t = time ("TextCollection.GetText()") (string) t + let left = first_child + let right = next_sibling + let tag t = time ("XMLTree.GetTag()") (tag) t + + let print_stats ppf = + let total_time,total_calls = + Hashtbl.fold (fun _ (t,c) (tacc,cacc) -> + tacc+. t, cacc + c) _timings (0.,0) + + in + Format.fprintf ppf + "Timing : Function Name, number of calls,%% of total calls, mean time, total time, %% of total time\n%!"; + Hashtbl.iter (fun name (time,count) -> + Format.fprintf ppf "%-27s% 8d\t% 4.2f%%\t% 4.6f ms\t% 4.6f ms\t%04.2f%%\n%!" + name + count + (100. *. (float_of_int count)/.(float_of_int total_calls)) + (time /. (float_of_int count)) + time + (100. *. time /. total_time)) _timings; + Format.fprintf ppf "-------------------------------------------------------------------\n"; + Format.fprintf ppf "%-27s% 8d\t% 4.0f%%\t########## ms\t% 4.6f ms\t% 4.0f%%\n%!" + "Total" total_calls 100. total_time 100. + + + let print_xml_fast outc t = + let rec loop ?(print_right=true) t = match t.node with + | Nil -> () + | String (s) -> output_string outc (string t) + | Node _ when Tag.equal (tag t) Tag.pcdata -> loop (left t); loop (right t) + + | Node (_) -> + let tg = Tag.to_string (tag t) in + let l = left t + and r = right t + in + output_char outc '<'; + output_string outc tg; + ( match l.node with + Nil -> output_string outc "/>" + | String _ -> assert false + | Node(_) when Tag.equal (tag l) Tag.attribute -> + (loop_attributes (left l); + match (right l).node with + | Nil -> output_string outc "/>" + | _ -> + output_char outc '>'; + loop (right l); + output_string outc "' ) + | _ -> + output_char outc '>'; + loop l; + output_string outc "' + );if print_right then loop r + and loop_attributes a = + + match a.node with + | Node(_) -> + let value = + match (left a).node with + | Nil -> "" + | _ -> string (left(left a)) + in + output_char outc ' '; + output_string outc (Tag.to_string (tag a)); + output_string outc "=\""; + output_string outc value; + output_char outc '"'; + loop_attributes (right a) + | _ -> () + in + loop ~print_right:false t + + + let print_xml_fast outc t = + if Tag.to_string (tag t) = "" then + print_xml_fast outc (first_child t) + else print_xml_fast outc t + + + + end -include XML + +module Binary = DEBUGTREE +ELSE +module Binary = XML.Binary +END (* IFDEF DEBUG *)