]> matita.cs.unibo.it Git - helm.git/blob - helm/gTopLevel/xmlDiff.ml
e162100285afeee0fc8e5f014785c2121d0ecbd7
[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 "background")
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 (highlighter#appendChild n) ;
68     ignore (parent#appendChild (highlighter :> Gdome.node)) ;
69     (highlighter :> Gdome.node)
70  in
71   let rec find_mstylable_node n =
72    match n#get_namespaceURI, n#get_localName with
73       Some nu, Some ln when
74        nu#to_string = mathmlns &&
75         let ln = ln#to_string in
76          ln <> "mtr" && ln <> "mtd" -> n
77     | Some nu, Some ln when
78        nu#to_string = mathmlns &&
79         let ln = ln#to_string in
80          ln = "mtr" || ln = "mtd" ->
81 prerr_endline "@@@ find_mstylable_node scendo";
82           let true_child =
83            match n#get_firstChild with
84               None -> assert false
85             | Some n -> n
86           in
87            find_mstylable_node true_child
88     | _,_ ->
89 prerr_endline ("@@@ find_mstylable_node salgo da  " ^ match n#get_localName with Some n -> n#to_string | None -> "_") ;
90       match n#get_parentNode with
91          None -> assert false
92        | Some p -> find_mstylable_node p
93   in
94    let highlighter = highlight (find_mstylable_node n) in
95     make_visible highlighter ;
96     highlighter
97 ;;
98
99 let highlight_nodes ~xrefs (doc:Gdome.document) =
100  let highlighted = ref [] in
101  let rec aux (n:Gdome.element) =
102   if
103    List.mem
104     (n#getAttributeNS ~namespaceURI:(Gdome.domString helmns)
105      ~localName:(Gdome.domString "xref"))#to_string
106     xrefs
107   then
108    highlighted :=
109     (highlight_node ~color:"#00ff00"(* light green *) doc (n :> Gdome.node))::
110     !highlighted ;
111   let children = n#get_childNodes in
112    for i = 0 to children#get_length - 1 do
113     match children#item i with
114        None -> assert false
115      | Some n ->
116         if n#get_nodeType = GdomeNodeTypeT.ELEMENT_NODE then
117          aux (new Gdome.element_of_node n)
118    done
119  in
120   aux doc#get_documentElement ;
121   !highlighted
122 ;;
123
124 let dim_nodes =
125  List.iter 
126   (function (n : Gdome.node) ->
127     assert
128      (n#get_nodeType = GdomeNodeTypeT.ELEMENT_NODE &&
129       ((new Gdome.element_of_node n)#getAttributeNS
130         ~namespaceURI:(Gdome.domString xmldiffns)
131         ~localName:(Gdome.domString "type"))#to_string = "fake") ;
132     let true_child =
133      match n#get_firstChild with
134         None -> assert false
135       | Some n -> n in
136     let p =
137      match n#get_parentNode with
138         None -> assert false
139       | Some n -> n
140     in
141      ignore (p#replaceChild ~oldChild:n ~newChild:true_child)
142   )
143 ;;
144
145 let update_dom ~(from : Gdome.document) (d : Gdome.document) =
146  let rec aux (p: Gdome.node) (f: Gdome.node) (t: Gdome.node) =
147 (* Perche' non andava?
148   if f#get_localName = t#get_localName &&
149      f#get_namespaceURI = t#get_namespaceURI
150 *)
151   match
152    f#get_nodeType,t#get_nodeType,
153    f#get_namespaceURI,t#get_namespaceURI,
154    f#get_localName,t#get_localName
155   with
156      GdomeNodeTypeT.TEXT_NODE,GdomeNodeTypeT.TEXT_NODE,_,_,_,_ when
157       match f#get_nodeValue, t#get_nodeValue with
158          Some v, Some v' -> v#to_string = v'#to_string
159        | _,_ -> assert false
160       ->
161 prerr_endline ("XML_DIFF: preservo il nodo testo " ^ match f#get_nodeValue with Some v -> v#to_string | None -> assert false);
162        ()
163    | GdomeNodeTypeT.ELEMENT_NODE,GdomeNodeTypeT.ELEMENT_NODE,
164       Some nu, Some nu', Some ln, Some ln' when
165        ln#to_string = ln'#to_string && nu#to_string = nu'#to_string ->
166 prerr_endline ("XML_DIFF: preservo il nodo "^ nu#to_string ^ ":" ^ln#to_string);
167         begin
168          match f#get_attributes, t#get_attributes with
169             Some fattrs, Some tattrs ->
170              let flen = fattrs#get_length in
171              let tlen = tattrs#get_length in
172               let processed = ref [] in
173               for i = 0 to flen -1 do
174                match fattrs#item i with
175                   None -> () (* CSC: sigh, togliere un nodo rompe fa decrescere la lunghezza ==> passare a un while *)
176                 | Some attr ->
177                     match attr#get_namespaceURI with
178                        None ->
179                         (* Back to DOM Level 1 ;-( *)
180                         begin
181                          let name = attr#get_nodeName in
182                           match tattrs#getNamedItem ~name with
183                              None ->
184 prerr_endline ("XML_DIFF: DOM 1; rimuovo l'attributo " ^ name#to_string);
185 (*  CSC: questo non mi toglieva solo l'attributo, ma anche altri nodi qui
186     e la' ;-(
187                              ignore (f#removeChild attr)
188 *)
189                              ignore (fattrs#removeNamedItem ~name)
190                            | Some attr' ->
191                               processed :=
192                                (None,Some name)::!processed ;
193                               match attr#get_nodeValue, attr'#get_nodeValue with
194                                  Some v1, Some v2 when
195                                      v1#to_string = v2#to_string
196                                   || (name#to_string = "selection" &&
197                                       nu#to_string =
198                                        "http://www.w3.org/1998/Math/MathML" &&
199                                       ln#to_string = "maction")
200                                   ->
201 prerr_endline ("XML_DIFF: DOM 1; preservo l'attributo " ^ name#to_string);
202                                    ()
203                                | Some v1, Some v2 ->
204 prerr_endline ("XML_DIFF: DOM 1; rimpiazzo l'attributo " ^ name#to_string ^ ": old value=" ^ v1#to_string ^ ", new value=" ^ v2#to_string);
205                                   let attr'' = from#importNode attr' true in
206                                    ignore (fattrs#setNamedItem attr'')
207                                | _,_ -> assert false
208                         end
209                      | Some namespaceURI ->
210                         let localName = 
211                          match attr#get_localName with
212                            Some v -> v
213                           | None -> assert false
214                         in
215                          match
216                           tattrs#getNamedItemNS ~namespaceURI ~localName
217                          with
218                             None ->
219 prerr_endline ("XML_DIFF: DOM 2; rimuovo l'attributo " ^ namespaceURI#to_string ^ ":" ^ localName#to_string);
220 (*  CSC: questo non mi toglieva solo l'attributo, ma anche altri nodi qui
221     e la' ;-(
222                              ignore (f#removeChild attr)
223 *)
224                              ignore
225                               (fattrs#removeNamedItemNS
226                                 ~namespaceURI ~localName)
227                           | Some attr' ->
228                              processed :=
229                               (Some namespaceURI,Some localName)::!processed ;
230                              (*CSC: questo mi dice read-only ;-( 
231                                attr#set_nodeValue attr'#get_nodeValue *)
232                              (*CSC: questo mi abortisce con una assert
233                              let attr'' = from#importNode attr' true in
234                               ignore(f#replaceChild ~newChild:attr'' ~oldChild:attr)*)
235                               match attr#get_nodeValue, attr'#get_nodeValue with
236                                  Some v1, Some v2 when
237                                   v1#to_string = v2#to_string ->
238 prerr_endline ("XML_DIFF: DOM 2; preservo l'attributo " ^ namespaceURI#to_string ^ ":" ^ localName#to_string);
239                                    ()
240                                | Some _, Some _ ->
241 prerr_endline ("XML_DIFF: DOM 2; rimpiazzo l'attributo " ^ namespaceURI#to_string ^ ":" ^ localName#to_string);
242                                   let attr'' = from#importNode attr' true in
243                                    ignore (fattrs#setNamedItem attr'')
244                                | _,_ -> assert false
245               done ;
246               for i = 0 to tlen -1 do
247                match tattrs#item i with
248                   None -> assert false
249                 | Some attr ->
250 let debugs = ref "" in
251                    let namespaceURI,localName =
252                     match attr#get_namespaceURI with
253                        None ->
254 debugs := ("XML_DIFF: DOM 1; creo un nuovo attributo " ^ attr#get_nodeName#to_string) ;
255                         None,attr#get_nodeName
256                      | Some namespaceURI as v ->
257 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);
258                        v, match attr#get_localName with
259                           None -> assert false
260                         | Some v -> v
261                    in
262                     if
263                      not
264                       (List.exists
265                         (function
266                             None,Some localName' ->
267                              (match namespaceURI with
268                                  None ->
269                                   localName#to_string = localName'#to_string
270                                | Some _ -> false)
271                           | Some namespaceURI', Some localName' ->
272                              (match namespaceURI with
273                                  None -> false
274                                | Some namespaceURI ->
275                                   localName#to_string = localName'#to_string &&
276                                   namespaceURI#to_string=namespaceURI'#to_string
277                              )
278                           | _,_ -> assert false
279                         ) !processed)
280                     then
281                      let attr' = from#importNode attr false in
282 prerr_endline !debugs ;
283                       ignore (fattrs#setNamedItem attr')
284               done
285           | _,_ -> assert false
286         end ;
287         let fchildren = f#get_childNodes in
288         let tchildren = t#get_childNodes in
289          let rec dumb_diff =
290           function
291              [],[] -> ()
292            | he1::tl1,he2::tl2 ->
293 prerr_endline "XML_DIFF: processo una coppia di figli" ;
294               aux f he1 he2 ;
295               dumb_diff (tl1,tl2)
296            | [],tl2 ->
297 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)) ;
298               List.iter
299                (function n ->
300                  let n' = from#importNode n true in
301                    ignore (f#appendChild n') ;
302                    ignore (highlight_node from n')
303                ) tl2
304            | tl1,[] ->
305 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)) ;
306               List.iter (function n -> ignore (f#removeChild n)) tl1
307          in
308           let node_list_of_nodeList nl =
309            let rec aux i =
310             match nl#item ~index:i with
311                None -> []
312              | Some n when
313                    n#get_nodeType = GdomeNodeTypeT.ELEMENT_NODE
314                 or n#get_nodeType = GdomeNodeTypeT.TEXT_NODE ->
315                  n::(aux (i+1))
316              | Some n ->
317 prerr_endline ("XML_DIFF: mi sto perdendo i nodi di tipo " ^ string_of_int (Obj.magic n#get_nodeType)) ;
318                aux (i+1)
319            in
320             aux 0
321           in
322 for i = 0 to fchildren#get_length - 1 do
323 match fchildren#item i with
324 None -> prerr_endline "EUREKA: ma siamo matti?"
325 |Some n ->
326 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))
327 done ;
328 prerr_endline("XML_DIFF: from ha " ^ string_of_int fchildren#get_length ^ " nodi, ovvero " ^ string_of_int (List.length (node_list_of_nodeList fchildren)) ^ " figli");
329 prerr_endline("XML_DIFF: to   ha " ^ string_of_int tchildren#get_length ^ " nodi, ovvero " ^ string_of_int (List.length (node_list_of_nodeList tchildren)) ^ " figli");
330 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))) ;
331            dumb_diff
332             (node_list_of_nodeList fchildren, node_list_of_nodeList tchildren)
333    | t1,t2,_,_,_,_ when
334       (t1 = GdomeNodeTypeT.ELEMENT_NODE || t1 = GdomeNodeTypeT.TEXT_NODE) &&
335       (t2 = GdomeNodeTypeT.ELEMENT_NODE || t2 = GdomeNodeTypeT.TEXT_NODE) ->
336        if
337         t1 = GdomeNodeTypeT.ELEMENT_NODE &&
338         ((new Gdome.element_of_node f)#getAttributeNS
339           ~namespaceURI:(Gdome.domString xmldiffns)
340           ~localName:(Gdome.domString "type"))#to_string = "fake"
341        then
342         let true_child =
343          match f#get_firstChild with
344             None -> assert false
345           | Some n -> n
346         in
347          begin
348 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 -> "_")) ;
349           ignore (p#replaceChild ~oldChild:f ~newChild:true_child) ;
350           aux p true_child t
351          end
352        else
353         let t' = from#importNode t true in
354 prerr_endline ("%%% XML_DIFF: importo il nodo " ^ match t'#get_localName with Some n -> n#to_string | None -> "_") ;
355 (*
356 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 -> "_")) ;
357 *)
358          ignore (p#replaceChild ~newChild:t' ~oldChild:f) ;
359          ignore (highlight_node from t')
360    | _,_,_,_,_,_ -> assert false
361  in
362   try
363    aux (d :> Gdome.node)
364     (from#get_documentElement :> Gdome.node)
365     (d#get_documentElement :> Gdome.node)
366   with
367      (GdomeInit.DOMException (e,msg) as ex) ->
368 (*
369     let module E = GdomeDOMExceptionT in
370 *)
371        prerr_endline
372         ("DOM EXCEPTION: " ^ msg ^ " --- " ^
373 string_of_int (Obj.magic e)) ;
374        raise ex
375  (*
376         match e with
377            E.NO_ERR -> "NO_ERR"
378          | E.INDEX_SIZE_ERR -> "INDEX_SIZE_ERR"
379          | E.DOMSTRING_SIZE_ERR -> "DOMSTRING_SIZE_ERR"
380          | E.HIERARCHY_REQUEST_ERR -> "HIERARCHY_REQUEST_ERR"
381          | E.WRONG_DOCUMENT_ERR -> "WRONG_DOCUMENT_ERR"
382          | E.INVALID_CHARACTER_ERR -> "INVALID_CHARACTER_ERR"
383          | E.NO_DATA_ALLOWED_ERR -> "NO_DATA_ALLOWER_ERR"
384          | E.NO_MODIFICATION_ALLOWED_ERR -> "NO_MODIFICATION_ALLOWED_ERR"
385          | E.NOT_FOUND_ERR -> "NOT_FOUND_ERR"
386          | E.NOT_SUPPORTED_ERR -> "NOT_SUPPORTED_ERR"
387          | E.INUSE_ATTRIBUTE_ERR -> "INUSE_ATTRIBUTE_ERR"
388          | E.INVALID_STATE_ERR -> "INVALID_STATE_ERR"
389          | E.SYNTAX_ERR -> "SYNTAX_ERR"
390          | E.INVALID_MODIFICATION_ERR -> "INVALID_MODIFICATION_ERR"
391          | E.NAMESPACE_ERR -> "NAMESPACE_ERR"
392          | E.INVALID_ACCESS_ERR -> "INVALID_ACCESS_ERR"
393 *)
394   | e ->
395     prerr_endline "PROBLEMA" ;
396     raise e
397 ;;