]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/mathql_interpreter/mQIMap.ml
ocaml 3.09 transition
[helm.git] / helm / ocaml / mathql_interpreter / mQIMap.ml
index 20923f982705f9ea46d391f7cc21754a713aadac..b215f366f212bf4988a6bb8a51c7e983615210a8 100644 (file)
@@ -34,22 +34,19 @@ type pg_tables = (bool * string) list
 
 type pg_alias = (string * string) list
 
-let empty_map () = "", [], []
+let empty_map () = [], []
 
 let read_map () =
-   let default_map = "mathql_db_map.txt" in
-   let map = 
-      try Sys.getenv "MATHQL_DB_MAP"
-      with Not_found -> default_map 
-   in
+   let map = Helm_registry.get "mathql_interpreter.db_map" in
    let ich = open_in map in 
-   let pgs = input_line ich in
    let rec aux r s =
       let d = input_line ich in 
       match Str.split (Str.regexp "[ \t]+") d with
         | []                  -> aux r s
+        | "#" :: _            -> aux r s
         | t ::      "<-" :: p -> aux ((p, (false, t, None)) :: r) s 
         | t :: c :: "<-" :: p -> aux ((p, (false, t, Some c)) :: r) s
+        | t ::      "<+" :: p -> aux ((p, (true, t, None)) :: r) s 
         | t :: c :: "<+" :: p -> aux ((p, (true, t, Some c)) :: r) s
         | [a; "->"; t]        -> aux r ((a, t) :: s) 
         | ["->"]              -> r, s
@@ -57,7 +54,7 @@ let read_map () =
    in
    let pgm, pga = aux [] [] in
    close_in ich;
-   pgs, pgm, pga
+   pgm, pga
 
 let comp c1 c2 = match c1, c2 with
    | (_, t1), (_, t2) when t1 < t2 -> U.Lt