]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/mathql_interpreter/mQIConn.ml
- the mathql interpreter is not helm-dependent any more
[helm.git] / helm / ocaml / mathql_interpreter / mQIConn.ml
index a51242bef323373ca38be15b6efdda5c4d0d338b..11dbd1674a058ada15206614b505aee47dd8198f 100644 (file)
 
 type flag = Postgres | Galax | Stat | Quiet | Warn | Log
 
-type handle = {log : string -> unit;            (* logging function    *)
-               set : flag list;                 (* options             *)
-              pgc : Postgres.connection option (* Postgres connection *)
-             }
+type handle = {
+   log : string -> unit;             (* logging function        *)
+   set : flag list;                  (* options                 *)
+   pgc : Postgres.connection option; (* PG connection           *)
+   pgm : MQIMap.pg_map;              (* PG conversion function  *)
+   pga : MQIMap.pg_alias             (* PG table aliases        *)
+}
+
+let tables handle p = MQIMap.get_tables handle.pgm p
+
+let field handle p t = MQIMap.get_field handle.pgm p t
+
+let resolve handle a = MQIMap.resolve handle.pga a
 
 let log handle = handle.log
 
@@ -70,9 +79,15 @@ let flags_of_string s =
    string_fold_left (fun l c -> l @ flag_of_char c) [] s
 
 let init myflags mylog =
+   let s, m, a =
+      let g = 
+         if List.mem Galax myflags 
+           then MQIMap.empty_map else MQIMap.read_map
+      in g ()
+   in
    {log = mylog; set = myflags; 
-    pgc = if List.mem Galax myflags 
-       then None else MQIPostgres.init ()
+    pgc = if List.mem Galax myflags then None else MQIPostgres.init s;
+    pgm = m; pga = a
    }      
 
 let close handle =