]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/mathql_interpreter/intersect.ml
intersect improved in speed
[helm.git] / helm / ocaml / mathql_interpreter / intersect.ml
index bd582a3b2ae8c1dbb9e6d56ede86ca1bea274a56..f869838f3fba9facb00ac2d3ba21d151d1c2db5c 100644 (file)
@@ -45,8 +45,7 @@ let xres_join_context h1 l1 h2 l2 =
      and m1 = List.combine h1 l1
      and m2 = List.combine h2 l2
      in
-      try 
-       (List.map
+       List.map
         (fun elem ->
          let value1 = try (List.assoc elem m1) with Not_found -> List.assoc elem m2
          and value2 = try (List.assoc elem m2) with Not_found -> List.assoc elem m1
@@ -54,54 +53,81 @@ let xres_join_context h1 l1 h2 l2 =
           if value1 = value2 then value1 else raise Join_must_be_empty
         )
         hh
-       ) with
-        Join_must_be_empty -> []
 ;;
 
 (*
- * implementazione del comando INTERSECT
+ *
  *)
-let intersect_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 ... *)
+let intersect_tails h1 t1 h2 t2 =
+ let rec aux t1 t2 =
+  match (t1, t2) with
+     ([], _)
+  |  (_, []) -> []
+  |  ((l1::tl1)::tll1, (l2::tl2)::tll2) ->
+       if l1 = l2 then
+        try
+         (*match xres_join_context h1 tl1 h2 tl2 with
+            [] -> aux tll1 tll2
+          | t  ->*) (l1::(xres_join_context h1 tl1 h2 tl2))::(aux tll1 tll2)
+       with
+        Join_must_be_empty -> aux tll1 tll2
+       else
+        if l1 < l2 then
+         aux tll1 t2
+        else
+         aux t1 tll2
+   | _ -> assert false
  in
-  match (head1, head2) with
-     ([], _) -> assert false (* gli header non devono mai essere vuoti *)
-  |  (_, []) -> assert false (* devono contenere almeno [retVal] *)
-  |  (_,  _) ->
-      (match (tail1, tail2) with
-          ([], _) -> [["retVal"]] (* se una delle due code e' vuota... *)
-       |  (_, []) -> [["retVal"]] (* ... l'intersezione e' vuota *)
-       |  (_,  _) ->
-           [head2 @
-            (List.find_all
-            (function t -> not (List.mem t head2))
-            head1
-           )
-          ] (* header del risultato finale *)
-          @
-          List.fold_left
-            (fun par1 elem1 -> par1 @
-             List.map
-             (fun elem2 ->
-              [(List.hd elem1)] @
-              (xres_join_context (List.tl head1) (List.tl elem1)
-                                 (List.tl head2) (List.tl elem2))
-             )
-              (List.find_all
-               (fun elem2 -> (* trova tutti gli elementi della lista tail2 *)
-               ((List.hd elem1) = (List.hd elem2)) && (* che stanno in tail1 *)
-               not ((xres_join_context (List.tl head1) (List.tl elem1)
-                                       (List.tl head2) (List.tl elem2)) = [])
-               (* e per i quali la xres_join_context non sia vuota *)
-              )
-               tail2
-             )
-             )
-           []
-           tail1 (* per ogni elemento di tail1 applica la List.fold_left *)
-      ) (* match *)
+  aux t1 t2
+;;
+
+(*
+ * implementazione del comando INTERSECT
+ *)
+let intersect_ex l1 l2 =
+ match (l1, l2) with
+    ((head1::tail1), (head2::tail2)) ->
+     (match (head1, head2) with
+         ([], _) -> assert false (* gli header non devono mai essere vuoti *)
+      |  (_, []) -> assert false (* devono contenere almeno [retVal] *)
+      |  (_,  _) ->
+          (match (tail1, tail2) with
+              ([], _) -> [["retVal"]] (* se una delle due code e' vuota... *)
+           |  (_, []) -> [["retVal"]] (* ... l'intersezione e' vuota *)
+           |  (_,  _) ->
+               [head2 @
+                (List.find_all
+                (function t -> not (List.mem t head2))
+                head1
+               )
+              ] (* header del risultato finale *)
+              @
+              intersect_tails (List.tl head1) tail1 (List.tl head2) tail2
+              (*
+              List.fold_left
+                (fun par1 elem1 -> par1 @
+                 List.map
+                 (fun elem2 ->
+                  [(List.hd elem1)] @
+                  (xres_join_context (List.tl head1) (List.tl elem1)
+                                     (List.tl head2) (List.tl elem2)
+                   )
+                 )
+                  (List.find_all (* *)
+                   (fun elem2 ->    (* trova tutti gli elementi della lista tail2 *)
+                   ((List.hd elem1) = (List.hd elem2)) && (* che stanno in tail1 *)
+                   not ((xres_join_context (List.tl head1) (List.tl elem1)
+                                           (List.tl head2) (List.tl elem2)) = [])
+                   (* e per i quali la xres_join_context non sia vuota *)
+                  )
+                   tail2 (* List.find_all *)
+                 )
+                 )
+               []
+               tail1 (* per ogni elemento di tail1 applica la List.fold_left *)
+              *)
+          ) (* match *)
+     )
+ | _ -> []
 ;;