]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/mathql/mQueryUtil.ml
- the mathql interpreter is not helm-dependent any more
[helm.git] / helm / ocaml / mathql / mQueryUtil.ml
index 3b16bb6b046d22a383b9c2f6bd03b5190a7dc6ed..349c2ac55038f6071aea89ddcddc8fddf1d346b1 100644 (file)
@@ -152,7 +152,6 @@ let text_of_query out x sep =
       | M.StatQuery x        -> out "stat "; txt_set x
       | M.Keep b l x         -> out "keep "; txt_allbut b; txt_path_list l;
                                 txt_set x
-
    in 
    txt_set x; out sep
 
@@ -187,6 +186,36 @@ let stop_time (s0, u0) =
    let u1 = Unix.time () in
    Printf.sprintf "%.2fs,%.2fs" (s1 -. s0) (u1 -. u0)
 
+(* operations on lists  *****************************************************)
+
+type 'a comparison = Lt 
+                   | Gt
+                  | Eq of 'a
+
+let list_join f l1 l2 =
+   let rec aux = function
+      | [], v
+      | v, []                                  -> v 
+      | ((h1 :: t1) as v1), ((h2 :: t2) as v2) -> begin
+         match f h1 h2 with
+           | Lt   -> h1 :: aux (t1, v2)
+           | Gt   -> h2 :: aux (v1, t2)
+            | Eq h -> h  :: aux (t1, t2)
+         end
+   in aux (l1, l2)
+
+let list_meet f l1 l2 =
+   let rec aux = function
+      | [], v
+      | v, []                                  -> [] 
+      | ((h1 :: t1) as v1), ((h2 :: t2) as v2) -> begin
+         match f h1 h2 with
+           | Lt   -> aux (t1, v2)
+           | Gt   -> aux (v1, t2)
+            | Eq h -> h :: aux (t1, t2)
+         end
+   in aux (l1, l2)
+
 (* conversion functions *****************************************************)
 
 type uriref = UriManager.uri * (int list)