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