]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/mathql_interpreter/mQIProperty.ml
optimized and patched
[helm.git] / helm / ocaml / mathql_interpreter / mQIProperty.ml
index 357809a746e490ec4f669fb9f90cdb2fd54bf8bd..1e634d7c11c03c8312192f8047829dc0305bed93 100644 (file)
@@ -100,7 +100,7 @@ let pg_query h table cols ct cfl =
         | _                              -> []
    else
       exec ("select " ^ pg_cols ^ " from " ^ table ^ pg_where ^ 
-            " order by " ^ List.hd cols ^ " asc")
+            " order by " ^ List.hd cols ^ " asc") (* desc *) 
 
 (* Galax backend  ***********************************************************)
 
@@ -108,10 +108,7 @@ let gx_query h table cols ct cfl = not_supported "Galax"
 
 (* Common functions  ********************************************************)
 
-let pg_result distinct subj el res =
-  let res, compose =
-     if distinct then List.rev res, U.append_iter else res, U.iter 
-  in 
+let pg_result subj el res =
   let get_name = function (p, None) -> p | (_, Some p) -> p in
   let names = List.map get_name el in
   let mk_grp l = U.grp_iter2 I.grp_make names l in
@@ -119,7 +116,7 @@ let pg_result distinct subj el res =
      if subj = "" then I.make "" (mk_grp l) 
      else I.make (List.hd l) (mk_grp (List.tl l))
   in
-  compose mk_avs res
+  U.iter mk_avs res
 
 let get_table h mc ct cfl el =
    let aux_c ts (_, p, _) = A.refine_tables ts (C.tables h p) in
@@ -139,7 +136,7 @@ let exec_single h mc ct cfl el table =
    let cols = if first = "" then other_cols else first :: other_cols in
    let low_level = if C.set h C.Galax then gx_query else pg_query in
    let result = low_level h (C.resolve h table) cols cons_true cons_false in
-   pg_result false first el result 
+   pg_result first el result 
    
 let deadline = 100