]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/mathql_interpreter/mQIMySql.ml
MySql database support added
[helm.git] / helm / ocaml / mathql_interpreter / mQIMySql.ml
index af50af8ff45fdf2b33626b3152cdfef119f9fb0b..591bfe87972c973a0390e48e852a3eef58a0db73 100644 (file)
@@ -26,6 +26,8 @@
 (*  AUTOR: Ferruccio Guidi <fguidi@cs.unibo.it>
  *)
 
+module I = MathQL.I
+
 let init () =
    try Mysql.quick_connect
        ~host:"mowgli.cs.unibo.it" ~database:"mowgli" ~user:"helm" ()
@@ -54,15 +56,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 ^ " regexp " ^ quote ("^" ^ s ^ "$") in
-         if pat then "(" ^ iter f " or " v ^ ")"
-        else match v with 
-           | [s] -> "binary " ^ col ^ " = " ^ (quote s)     
-           | v   -> "binary " ^ col ^ " in (" ^ pg_msval v ^ ")"
+        let f s = col ^ " regexp " ^ quote ("^" ^ s ^ "$") in
+        if pat then "(" ^ avs_iter f " or " v ^ ")"
+        else match I.single v with 
+           | Some s -> "binary " ^ col ^ " = " ^ (quote s)     
+           | None   -> "binary " ^ col ^ " in (" ^ pg_msval v ^ ")"
       else "1"
    in
    let pg_cons l = iter pg_con " and " l in
@@ -81,4 +90,4 @@ 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 *)