]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/mathql_interpreter/use.ml
* New operators (Subset, SetEqual and RVarOccurrence) added to MathQL
[helm.git] / helm / ocaml / mathql_interpreter / use.ml
index 7755ff20a78a14a60c05383761d10a6fa2bd37d2..ecc12f01d7a6ab4d0384638ca30fa18b6cd72b53 100644 (file)
@@ -45,17 +45,16 @@ open Dbconn;;
  *                           comando USE/USED BY
  *)
 let use_ex alist asvar usek =
- let _ = print_string ("USE ")
- and t = Unix.time () in
- let result =
- let c = pgc ()
- in
-  [ (List.hd alist) @ [asvar] ]
-  @
+let module S = Mathql_semantics in
+let _ = print_string ("USE ")
+and t = Unix.time () in
+let result =
+ let c = pgc () in
   Sort.list
-   (fun l m -> List.hd l < List.hd m)
+   (fun {S.uri = uri1} {S.uri = uri2} -> uri1 < uri2)
    (List.fold_left
-    (fun parziale xres ->
+    (fun parziale {S.uri = uri ; S.attributes = attributes} ->
+     print_string uri ;
      (*let r1 = helm_property_id usek
      and r2 = helm_property_id "position"
      and r3 = helm_property_id "occurrence"
@@ -65,22 +64,28 @@ let use_ex alist asvar usek =
        "where " ^ "t" ^ r1 ^ ".att0 = '" ^ (List.hd xres) ^ "' and t" ^ r1 ^
        ".att1 = t" ^ r2 ^ ".att0 and t" ^ r1 ^ ".att1 = t" ^ r3 ^
        ".att0 order by t" ^ r3 ^ ".att1 asc"*)
-      let tv = pgresult_to_string (c#exec ("select id from registry where uri='" ^ (List.hd xres) ^ "'")) in
-      let qq = "select uri, context from t" ^ tv ^ " where back_for='" ^ usek ^ "'"
+      let tv =
+       pgresult_to_string
+        (c#exec ("select id from registry where uri='" ^ uri ^ "'"))
+      in
+      let qq =
+       "select uri, context from t" ^ tv ^ " where back_for='" ^ usek ^
+        "' order by uri asc"
       in
       let res = c#exec qq in
        (List.map
-        (fun l -> [List.hd l] @ List.tl xres @ List.tl l)
-        res#get_list
-       )
-       @
+        (function
+            [uri;context] -> {S.uri = uri ; S.attributes = [asvar, context]}
+          | _ -> assert false
+        ) res#get_list
+       ) @
        parziale
-    )
-    []
-    (List.tl alist)
+    ) [] alist
    )
- in
-  let _ = print_endline (string_of_float (Unix.time () -. t)); flush stdout in
+in
+print_string (" = " ^ string_of_int (List.length result) ^ ": ") ; 
+print_endline (string_of_float (Unix.time () -. t) ^ "s") ;
+flush stdout ;
    result
 ;;