]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/mathql_interpreter/diff.ml
sortedby implemented and new uri result format
[helm.git] / helm / ocaml / mathql_interpreter / diff.ml
diff --git a/helm/ocaml/mathql_interpreter/diff.ml b/helm/ocaml/mathql_interpreter/diff.ml
new file mode 100644 (file)
index 0000000..41e41c7
--- /dev/null
@@ -0,0 +1,117 @@
+(* Copyright (C) 2000, HELM Team.
+ * 
+ * This file is part of HELM, an Hypertextual, Electronic
+ * Library of Mathematics, developed at the Computer Science
+ * Department, University of Bologna, Italy.
+ * 
+ * HELM is free software; you can redistribute it and/or
+ * modify it under the terms of the GNU General Public License
+ * as published by the Free Software Foundation; either version 2
+ * of the License, or (at your option) any later version.
+ * 
+ * HELM is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License
+ * along with HELM; if not, write to the Free Software
+ * Foundation, Inc., 59 Temple Place - Suite 330, Boston,
+ * MA  02111-1307, USA.
+ * 
+ * For details, see the HELM World-Wide-Web page,
+ * http://cs.unibo.it/helm/.
+ *)
+
+(*
+ * implementazione del comando DIFF
+ *)
+
+(*
+ * 
+ *)
+let xres_fill_context hr h1 l1 =
+ match l1 with
+    [] -> []
+ |   _ ->
+     let hh = List.combine h1 l1
+     in
+      List.map
+       (fun x ->
+        if (List.mem_assoc x hh) then
+        List.assoc x hh
+       else
+        ""
+       )
+       hr
+;;
+
+(*
+ * implementazione del comando DIFF
+ *)
+let diff_ex alist1 alist2 =
+ let head1 = List.hd alist1
+ and tail1 = List.tl alist1
+ and head2 = List.hd alist2
+ and tail2 = List.tl alist2 (* e fin qui ... *)
+ in
+  match (head1, head2) with
+     ([], _) -> assert false (* gli header non devono mai essere vuoti *)
+  |  (_, []) -> assert false (* devono contenere almeno [retVal] *)
+  |  (_,  _) -> let headr = (head2 @
+                            (List.find_all
+                            (function t -> not (List.mem t head2))
+                            head1)
+                           ) in (* header del risultato finale *)
+      List.append (* il risultato finale e' la concatenazione ...*)
+       [headr] (* ... dell'header costruito prima ...*)
+       (match (tail1, tail2) with (* e di una coda "unione" *)
+           ([], _) -> tail2 (* va bene perche' l'altra lista e' vuota *)
+        |  (_, []) -> tail1 (* va bene perche' l'altra lista e' vuota *)
+        |  (_,  _) ->
+           let first = (* parte dell'unione che riguarda solo il primo set *)
+            List.map (fun l -> [List.hd l] @
+                      xres_fill_context
+                       (List.tl headr) (List.tl head1) (List.tl l)
+                     ) tail1
+            in
+            List.fold_left
+             (fun par x ->
+              let y = (* elemento candidato ad entrare *)
+               [List.hd x]
+               @
+               xres_fill_context
+                (List.tl headr) (List.tl head2) (List.tl x)
+              in
+               par @ if (List.find_all (fun t -> t = y) par) = [] then
+                      [y]
+                     else
+                      []
+             )
+             first
+             tail2
+(*          first @
+            List.map (fun l -> [List.hd l] @
+                      xres_fill_context
+                       (List.tl headr) (List.tl head2) (List.tl l)
+                     ) tail2
+*)
+       ) (* match *)
+;;
+
+(** TEST **)
+
+(*
+let h1 = ["retVal";     "a";      "b"];;
+let l1 = ["pippo";      "3";      "3"];;
+let l3 = ["pluto";      "7";      "8"]
+let r1 = [h1; l1; l3];;
+
+(*let h2 = ["retVal";               "b";      "c"];;
+let l2 = ["pippo";                "3";      "1"];;*)
+let h2 = ["retVal";     "a";      "b"];;
+let l2 = ["pippo";      "3";      "3"];;
+let r2 = [h2; l2];;
+
+List.map (fun l -> List.iter print_endline l) (xres_union (r1, r2));;
+*)