]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/cic_disambiguation/disambiguateTypes.ml
ocaml 3.09 transition
[helm.git] / helm / ocaml / cic_disambiguation / disambiguateTypes.ml
index 3e969c87a16e92d6e8dff37d318d31c9f8f6282b..b323f9231972b9dcda2368d2807af5e56f651738 100644 (file)
@@ -36,7 +36,7 @@ type domain_item =
   | Symbol of string * int     (* literal, instance num *)
   | Num of int                 (* instance num *)
 
-exception Invalid_choice
+exception Invalid_choice of string Lazy.t
 
 module OrderedDomain =
   struct
@@ -73,20 +73,21 @@ end
 
 type codomain_item =
   string *  (* description *)
-  (singleton_environment -> string -> Cic.term list -> Cic.term)
+  (environment -> string -> Cic.term list -> Cic.term)
     (* environment, literal number, arguments as needed *)
 
-and environment = codomain_item list Environment.t
+and environment = codomain_item Environment.t
+
+type multiple_environment = codomain_item list Environment.t
 
-and singleton_environment = codomain_item Environment.t
 
 (** adds a (name,uri) list l to a disambiguation environment e **)
-let env_of_list l e = 
+let multiple_env_of_list l e = 
   List.fold_left
    (fun e (name,descr,t) -> Environment.cons (Id name) (descr,fun _ _ _ -> t) e)
    e l
 
-let singleton_env_of_list l e = 
+let env_of_list l e = 
   List.fold_left
    (fun e (name,descr,t) -> Environment.add (Id name) (descr,fun _ _ _ -> t) e)
    e l
@@ -113,8 +114,6 @@ let string_of_domain_item = function
 let string_of_domain dom =
   String.concat "; " (List.map string_of_domain_item dom)
 
-let empty_environment = Environment.empty
-
 let floc_of_loc (loc_begin, loc_end) =
   let floc_begin =
     { Lexing.pos_fname = ""; Lexing.pos_lnum = -1; Lexing.pos_bol = -1;