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