]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/mathql_interpreter/mQIPostgres.ml
MySql database support added
[helm.git] / helm / ocaml / mathql_interpreter / mQIPostgres.ml
index cf82814e9fe0edf75d3ba46d3c2b8c1245f9691a..7b73451286d39550d7b0df83f82cfeb0462b1d61 100644 (file)
@@ -26,6 +26,8 @@
 (*  AUTOR: Ferruccio Guidi <fguidi@cs.unibo.it>
  *)
 
+module I = MathQL.I
+
 let init () =
    let connection_string =
       Helm_registry.get "mathql_interpreter.postgresql_connection_string"
@@ -53,15 +55,22 @@ let exec c table cols ct cfl =
       | [head]       -> f head 
       | head :: tail -> f head ^ sep ^ iter f sep tail
    in
+   let avs_iter f sep v =
+      let aux a s = function
+         | true  -> a ^ (f s) ^ sep
+        | false -> a ^ (f s)
+      in
+      I.iter aux "" v
+   in
    let pg_cols = iter (fun x -> x) ", " cols in
-   let pg_msval v = iter quote ", " v in
+   let pg_msval v = avs_iter quote ", " v in
    let pg_con (pat, col, v) = 
       if col <> "" then 
          let f s = col ^ " ~ " ^ quote ("^" ^ s ^ "$") in
-         if pat then "(" ^ iter f " or " v ^ ")"
-        else match v with 
-           | [s] -> col ^ " = " ^ (quote s)     
-           | v   -> col ^ " in (" ^ pg_msval v ^ ")"
+        if pat then "(" ^ avs_iter f " or " v ^ ")"
+        else match I.single v with 
+           | Some s -> col ^ " = " ^ (quote s)     
+           | None   -> col ^ " in (" ^ pg_msval v ^ ")"
       else "true"
    in
    let pg_cons l = iter pg_con " and " l in
@@ -80,7 +89,7 @@ let exec c table cols ct cfl =
         | _                              -> [], q
    else
       exec c ("select " ^ pg_cols ^ " from " ^ table ^ pg_where ^ 
-            " order by " ^ List.hd cols ^ " asc")
+            " order by " ^ List.hd cols ^ " asc") (* desc *) 
 
 (* funzioni vecchie  ********************************************************)
 (*