]> matita.cs.unibo.it Git - helm.git/blob - helm/gTopLevel/xmlDiff.ml
Debugging stuff removed.
[helm.git] / helm / gTopLevel / xmlDiff.ml
1 (* Copyright (C) 2000-2002, HELM Team.
2  * 
3  * This file is part of HELM, an Hypertextual, Electronic
4  * Library of Mathematics, developed at the Computer Science
5  * Department, University of Bologna, Italy.
6  * 
7  * HELM is free software; you can redistribute it and/or
8  * modify it under the terms of the GNU General Public License
9  * as published by the Free Software Foundation; either version 2
10  * of the License, or (at your option) any later version.
11  * 
12  * HELM is distributed in the hope that it will be useful,
13  * but WITHOUT ANY WARRANTY; without even the implied warranty of
14  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15  * GNU General Public License for more details.
16  *
17  * You should have received a copy of the GNU General Public License
18  * along with HELM; if not, write to the Free Software
19  * Foundation, Inc., 59 Temple Place - Suite 330, Boston,
20  * MA  02111-1307, USA.
21  * 
22  * For details, see the HELM World-Wide-Web page,
23  * http://cs.unibo.it/helm/.
24  *)
25
26 let myprerr_endline = prerr_endline;;
27 let prerr_endline _ = ();;
28
29 let mathmlns = "http://www.w3.org/1998/Math/MathML";;
30 let xmldiffns = "http://helm.cs.unibo.it/XmlDiff";;
31 let helmns = "http://www.cs.unibo.it/helm";;
32
33 type highlighted_nodes = Gdome.node list;;
34
35 let rec make_visible (n: Gdome.node) =
36  match n#get_parentNode with
37     None -> ()
38   | Some p ->
39      match p#get_namespaceURI, p#get_localName with
40         Some nu, Some ln when
41          nu#to_string = mathmlns && ln#to_string = "maction" ->
42           (new Gdome.element_of_node p)#setAttribute
43             ~name:(Gdome.domString "selection")
44              ~value:(Gdome.domString "2") ;
45           make_visible p
46       | _,_ -> make_visible p
47 ;;
48
49 let highlight_node ?(color="yellow") (doc: Gdome.document) (n: Gdome.node) =
50  let highlight (n: Gdome.node) =
51   let highlighter =
52    doc#createElementNS
53     ~namespaceURI:(Some (Gdome.domString mathmlns))
54     ~qualifiedName:(Gdome.domString "m:mstyle")
55   in
56    highlighter#setAttribute ~name:(Gdome.domString "mathbackground")
57     ~value:(Gdome.domString color) ;
58    highlighter#setAttributeNS
59     ~namespaceURI:(Some (Gdome.domString xmldiffns))
60     ~qualifiedName:(Gdome.domString "xmldiff:type")
61     ~value:(Gdome.domString "fake") ;
62    let parent = 
63     match n#get_parentNode with
64        None -> assert false
65      | Some p -> p
66    in
67     ignore
68      (parent#replaceChild ~oldChild:n ~newChild:(highlighter :> Gdome.node)) ;
69     ignore (highlighter#appendChild n) ;
70     (highlighter :> Gdome.node)
71  in
72   let rec find_mstylable_node n =
73    match n#get_namespaceURI, n#get_localName with
74       Some nu, Some ln when
75        nu#to_string = mathmlns &&
76         let ln = ln#to_string in
77          ln <> "mtr" && ln <> "mtd" -> n
78     | Some nu, Some ln when
79        nu#to_string = mathmlns &&
80         let ln = ln#to_string in
81          ln = "mtr" || ln = "mtd" ->
82 prerr_endline "@@@ find_mstylable_node scendo";
83           let true_child =
84            match n#get_firstChild with
85               None -> assert false
86             | Some n -> n
87           in
88            find_mstylable_node true_child
89     | _,_ ->
90 prerr_endline ("@@@ find_mstylable_node salgo da  " ^ match n#get_localName with Some n -> n#to_string | None -> "_") ;
91       match n#get_parentNode with
92          None -> assert false
93        | Some p -> find_mstylable_node p
94   in
95    let highlighter = highlight (find_mstylable_node n) in
96     make_visible highlighter ;
97     highlighter
98 ;;
99
100 let iter_children ~f (n:Gdome.node) =
101  let rec aux =
102   function
103      None -> ()
104    | Some n ->
105       let sibling = n#get_nextSibling in
106        (f n) ;
107        aux sibling
108  in
109   aux n#get_firstChild
110 ;;
111
112 let highlight_nodes ~xrefs (doc:Gdome.document) =
113  let highlighted = ref [] in
114  let rec aux (n:Gdome.element) =
115   if
116    List.mem
117     (n#getAttributeNS ~namespaceURI:(Gdome.domString helmns)
118      ~localName:(Gdome.domString "xref"))#to_string
119     xrefs
120   then
121    highlighted :=
122     (highlight_node ~color:"#00ff00"(* light green *) doc (n :> Gdome.node))::
123     !highlighted ;
124    iter_children (n :> Gdome.node)
125     ~f:(function n ->
126          if n#get_nodeType = GdomeNodeTypeT.ELEMENT_NODE then
127           aux (new Gdome.element_of_node n))
128  in
129   aux doc#get_documentElement ;
130   !highlighted
131 ;;
132
133 let dim_nodes =
134  List.iter 
135   (function (n : Gdome.node) ->
136     assert
137      (n#get_nodeType = GdomeNodeTypeT.ELEMENT_NODE &&
138       ((new Gdome.element_of_node n)#getAttributeNS
139         ~namespaceURI:(Gdome.domString xmldiffns)
140         ~localName:(Gdome.domString "type"))#to_string = "fake") ;
141     let true_child =
142      match n#get_firstChild with
143         None -> assert false
144       | Some n -> n in
145     let p =
146      match n#get_parentNode with
147         None -> assert false
148       | Some n -> n
149     in
150      ignore (p#replaceChild ~oldChild:n ~newChild:true_child)
151   )
152 ;;
153
154 let update_dom ~(from : Gdome.document) (d : Gdome.document) =
155  let rec aux (p: Gdome.node) (f: Gdome.node) (t: Gdome.node) =
156 (* Perche' non andava?
157   if f#get_localName = t#get_localName &&
158      f#get_namespaceURI = t#get_namespaceURI
159 *)
160   match
161    f#get_nodeType,t#get_nodeType,
162    f#get_namespaceURI,t#get_namespaceURI,
163    f#get_localName,t#get_localName
164   with
165      GdomeNodeTypeT.TEXT_NODE,GdomeNodeTypeT.TEXT_NODE,_,_,_,_ when
166       match f#get_nodeValue, t#get_nodeValue with
167          Some v, Some v' -> v#to_string = v'#to_string
168        | _,_ -> assert false
169       ->
170 prerr_endline ("XML_DIFF: preservo il nodo testo " ^ match f#get_nodeValue with Some v -> v#to_string | None -> assert false);
171        ()
172    | GdomeNodeTypeT.ELEMENT_NODE,GdomeNodeTypeT.ELEMENT_NODE,
173       Some nu, Some nu', Some ln, Some ln' when
174        ln#to_string = ln'#to_string && nu#to_string = nu'#to_string ->
175 prerr_endline ("XML_DIFF: preservo il nodo "^ nu#to_string ^ ":" ^ln#to_string);
176         begin
177          match f#get_attributes, t#get_attributes with
178             Some fattrs, Some tattrs ->
179              let flen = fattrs#get_length in
180              let tlen = tattrs#get_length in
181               let processed = ref [] in
182               for i = 0 to flen -1 do
183                match fattrs#item i with
184                   None -> () (* CSC: sigh, togliere un nodo rompe fa decrescere la lunghezza ==> passare a un while *)
185                 | Some attr ->
186                     match attr#get_namespaceURI with
187                        None ->
188                         (* Back to DOM Level 1 ;-( *)
189                         begin
190                          let name = attr#get_nodeName in
191                           match tattrs#getNamedItem ~name with
192                              None ->
193 prerr_endline ("XML_DIFF: DOM 1; rimuovo l'attributo " ^ name#to_string);
194 (*  CSC: questo non mi toglieva solo l'attributo, ma anche altri nodi qui
195     e la' ;-(
196                              ignore (f#removeChild attr)
197 *)
198                              ignore (fattrs#removeNamedItem ~name)
199                            | Some attr' ->
200                               processed :=
201                                (None,Some name)::!processed ;
202                               match attr#get_nodeValue, attr'#get_nodeValue with
203                                  Some v1, Some v2 when
204                                      v1#to_string = v2#to_string
205                                   || (name#to_string = "selection" &&
206                                       nu#to_string =
207                                        "http://www.w3.org/1998/Math/MathML" &&
208                                       ln#to_string = "maction")
209                                   ->
210 prerr_endline ("XML_DIFF: DOM 1; preservo l'attributo " ^ name#to_string);
211                                    ()
212                                | Some v1, Some v2 ->
213 prerr_endline ("XML_DIFF: DOM 1; rimpiazzo l'attributo " ^ name#to_string ^ ": old value=" ^ v1#to_string ^ ", new value=" ^ v2#to_string);
214                                   let attr'' = from#importNode attr' true in
215                                    ignore (fattrs#setNamedItem attr'')
216                                | _,_ -> assert false
217                         end
218                      | Some namespaceURI ->
219                         let localName = 
220                          match attr#get_localName with
221                            Some v -> v
222                           | None -> assert false
223                         in
224                          match
225                           tattrs#getNamedItemNS ~namespaceURI ~localName
226                          with
227                             None ->
228 prerr_endline ("XML_DIFF: DOM 2; rimuovo l'attributo " ^ namespaceURI#to_string ^ ":" ^ localName#to_string);
229 (*  CSC: questo non mi toglieva solo l'attributo, ma anche altri nodi qui
230     e la' ;-(
231                              ignore (f#removeChild attr)
232 *)
233                              ignore
234                               (fattrs#removeNamedItemNS
235                                 ~namespaceURI ~localName)
236                           | Some attr' ->
237                              processed :=
238                               (Some namespaceURI,Some localName)::!processed ;
239                              (*CSC: questo mi dice read-only ;-( 
240                                attr#set_nodeValue attr'#get_nodeValue *)
241                              (*CSC: questo mi abortisce con una assert
242                              let attr'' = from#importNode attr' true in
243                               ignore(f#replaceChild ~newChild:attr'' ~oldChild:attr)*)
244                               match attr#get_nodeValue, attr'#get_nodeValue with
245                                  Some v1, Some v2 when
246                                   v1#to_string = v2#to_string ->
247 prerr_endline ("XML_DIFF: DOM 2; preservo l'attributo " ^ namespaceURI#to_string ^ ":" ^ localName#to_string);
248                                    ()
249                                | Some _, Some _ ->
250 prerr_endline ("XML_DIFF: DOM 2; rimpiazzo l'attributo " ^ namespaceURI#to_string ^ ":" ^ localName#to_string);
251                                   let attr'' = from#importNode attr' true in
252                                    ignore (fattrs#setNamedItem attr'')
253                                | _,_ -> assert false
254               done ;
255               for i = 0 to tlen -1 do
256                match tattrs#item i with
257                   None -> assert false
258                 | Some attr ->
259 let debugs = ref "" in
260                    let namespaceURI,localName =
261                     match attr#get_namespaceURI with
262                        None ->
263 debugs := ("XML_DIFF: DOM 1; creo un nuovo attributo " ^ attr#get_nodeName#to_string) ;
264                         None,attr#get_nodeName
265                      | Some namespaceURI as v ->
266 debugs := ("XML_DIFF: DOM 2; creo un nuovo attributo " ^ namespaceURI#to_string ^ ":" ^ match attr#get_localName with Some v -> v#to_string | None -> assert false);
267                        v, match attr#get_localName with
268                           None -> assert false
269                         | Some v -> v
270                    in
271                     if
272                      not
273                       (List.exists
274                         (function
275                             None,Some localName' ->
276                              (match namespaceURI with
277                                  None ->
278                                   localName#to_string = localName'#to_string
279                                | Some _ -> false)
280                           | Some namespaceURI', Some localName' ->
281                              (match namespaceURI with
282                                  None -> false
283                                | Some namespaceURI ->
284                                   localName#to_string = localName'#to_string &&
285                                   namespaceURI#to_string=namespaceURI'#to_string
286                              )
287                           | _,_ -> assert false
288                         ) !processed)
289                     then
290                      let attr' = from#importNode attr false in
291 prerr_endline !debugs ;
292                       ignore (fattrs#setNamedItem attr')
293               done
294           | _,_ -> assert false
295         end ;
296 (* debugging only
297         let fchildren = f#get_childNodes in
298         let tchildren = t#get_childNodes in
299 *)
300          let rec dumb_diff =
301           function
302              [],[] -> ()
303            | he1::tl1,he2::tl2 ->
304 prerr_endline "XML_DIFF: processo una coppia di figli" ;
305               aux f he1 he2 ;
306               dumb_diff (tl1,tl2)
307            | [],tl2 ->
308 prerr_endline ("XML_DIFF: appendo i nodi residui " ^ String.concat ", " (List.map (function n ->  match n#get_localName with Some s -> s#to_string | None -> "#" ^ (match n#get_nodeValue with Some s -> s#to_string | None -> "_") ^ "#") tl2)) ;
309               List.iter
310                (function n ->
311                  let n' = from#importNode n true in
312                    ignore (f#appendChild n') ;
313                    ignore (highlight_node from n')
314                ) tl2
315            | tl1,[] ->
316 prerr_endline ("XML_DIFF: cancello i nodi residui " ^ String.concat ", " (List.map (function n ->  match n#get_localName with Some s -> s#to_string | None -> "_") tl1)) ;
317               List.iter (function n -> ignore (f#removeChild n)) tl1
318          in
319           let node_list_of_nodeList n =
320            let rec aux =
321             function
322                None -> []
323              | Some n when
324                    n#get_nodeType = GdomeNodeTypeT.ELEMENT_NODE
325                 or n#get_nodeType = GdomeNodeTypeT.TEXT_NODE ->
326                  n::(aux n#get_nextSibling)
327              | Some n ->
328 prerr_endline ("XML_DIFF: mi sto perdendo i nodi di tipo " ^ string_of_int (Obj.magic n#get_nodeType)) ;
329                aux n#get_nextSibling
330            in
331             aux n#get_firstChild
332           in
333 (* debugging stuff only
334 for i = 0 to fchildren#get_length - 1 do
335 match fchildren#item i with
336 None -> prerr_endline "EUREKA: ma siamo matti?"
337 |Some n ->
338 match n#get_nodeType with GdomeNodeTypeT.ATTRIBUTE_NODE -> prerr_endline "EUREKA attr" | GdomeNodeTypeT.CDATA_SECTION_NODE -> prerr_endline "EUREKA text" | GdomeNodeTypeT.DOCUMENT_FRAGMENT_NODE -> prerr_endline "EUREKA document fragment" | _ -> prerr_endline ("EUREKA " ^ string_of_int (Obj.magic n#get_nodeType))
339 done ;
340 prerr_endline("XML_DIFF: from ha " ^ string_of_int fchildren#get_length ^ " nodi, ovvero " ^ string_of_int (List.length (node_list_of_nodeList f)) ^ " figli");
341 prerr_endline("XML_DIFF: to   ha " ^ string_of_int tchildren#get_length ^ " nodi, ovvero " ^ string_of_int (List.length (node_list_of_nodeList t)) ^ " figli");
342 prerr_endline ("XML_DIFF: chiamo dumb_diff su " ^ String.concat ", " (List.map (function n ->  match n#get_localName with Some s -> s#to_string | None -> "_") (node_list_of_nodeList fchildren)) ^ " e " ^ String.concat ", " (List.map (function n ->  match n#get_localName with Some s -> s#to_string | None -> "_") (node_list_of_nodeList tchildren))) ;
343 *)
344            dumb_diff
345             (node_list_of_nodeList f, node_list_of_nodeList t)
346    | t1,t2,_,_,_,_ when
347       (t1 = GdomeNodeTypeT.ELEMENT_NODE || t1 = GdomeNodeTypeT.TEXT_NODE) &&
348       (t2 = GdomeNodeTypeT.ELEMENT_NODE || t2 = GdomeNodeTypeT.TEXT_NODE) ->
349        if
350         t1 = GdomeNodeTypeT.ELEMENT_NODE &&
351         ((new Gdome.element_of_node f)#getAttributeNS
352           ~namespaceURI:(Gdome.domString xmldiffns)
353           ~localName:(Gdome.domString "type"))#to_string = "fake"
354        then
355         let true_child =
356          match f#get_firstChild with
357             None -> assert false
358           | Some n -> n
359         in
360          begin
361 prerr_endline ("%%% CANCELLO HIGHLIGHTER " ^ (match f#get_localName with Some s -> s#to_string | None -> "_") ^ " CON DENTRO " ^ (match true_child#get_localName with Some s -> s#to_string | None -> "_")) ;
362           ignore (p#replaceChild ~oldChild:f ~newChild:true_child) ;
363           aux p true_child t
364          end
365        else
366         let t' = from#importNode t true in
367 prerr_endline ("%%% XML_DIFF: importo il nodo " ^ match t'#get_localName with Some n -> n#to_string | None -> "_") ;
368 (*
369 prerr_endline ("Rimpiazzo" ^ (match f#get_namespaceURI with Some s -> s#to_string) ^ ":" ^ (match f#get_localName with Some s -> s#to_string) ^ " con " ^ (match t#get_namespaceURI with Some s -> s#to_string) ^ ":" ^ (match t#get_localName with Some s -> s#to_string) ^ " in " ^ (match p#get_localName with Some s -> s#to_string | None -> "_")) ;
370 *)
371          ignore (p#replaceChild ~newChild:t' ~oldChild:f) ;
372          ignore (highlight_node from t')
373    | _,_,_,_,_,_ -> assert false
374  in
375   try
376    aux (d :> Gdome.node)
377     (from#get_documentElement :> Gdome.node)
378     (d#get_documentElement :> Gdome.node)
379   with
380      (GdomeInit.DOMException (e,msg) as ex) ->
381 (* CSC: Non si puo' per problemi di linking ;-(
382     let module E = GdomeDOMExceptionT in
383 *)
384        prerr_endline
385         ("DOM EXCEPTION: " ^ msg ^ " --- " ^
386           match e with
387              GdomeDOMExceptionT.NO_ERR -> "NO_ERR"
388            | GdomeDOMExceptionT.INDEX_SIZE_ERR -> "INDEX_SIZE_ERR"
389            | GdomeDOMExceptionT.DOMSTRING_SIZE_ERR -> "DOMSTRING_SIZE_ERR"
390            | GdomeDOMExceptionT.HIERARCHY_REQUEST_ERR -> "HIERARCHY_REQUEST_ERR"
391            | GdomeDOMExceptionT.WRONG_DOCUMENT_ERR -> "WRONG_DOCUMENT_ERR"
392            | GdomeDOMExceptionT.INVALID_CHARACTER_ERR -> "INVALID_CHARACTER_ERR"
393            | GdomeDOMExceptionT.NO_DATA_ALLOWED_ERR -> "NO_DATA_ALLOWER_ERR"
394            | GdomeDOMExceptionT.NO_MODIFICATION_ALLOWED_ERR -> "NO_MODIFICATION_ALLOWED_ERR"
395            | GdomeDOMExceptionT.NOT_FOUND_ERR -> "NOT_FOUND_ERR"
396            | GdomeDOMExceptionT.NOT_SUPPORTED_ERR -> "NOT_SUPPORTED_ERR"
397            | GdomeDOMExceptionT.INUSE_ATTRIBUTE_ERR -> "INUSE_ATTRIBUTE_ERR"
398            | GdomeDOMExceptionT.INVALID_STATE_ERR -> "INVALID_STATE_ERR"
399            | GdomeDOMExceptionT.SYNTAX_ERR -> "SYNTAX_ERR"
400            | GdomeDOMExceptionT.INVALID_MODIFICATION_ERR -> "INVALID_MODIFICATION_ERR"
401            | GdomeDOMExceptionT.NAMESPACE_ERR -> "NAMESPACE_ERR"
402            | GdomeDOMExceptionT.INVALID_ACCESS_ERR -> "INVALID_ACCESS_ERR")
403   | e ->
404     prerr_endline "PROBLEMA" ;
405     raise e
406 ;;