]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/cic_disambiguation/disambiguateChoices.ml
ocaml 3.09 transition
[helm.git] / helm / ocaml / cic_disambiguation / disambiguateChoices.ml
index c74566f20861c4e030621d6b49c0cf642cb1726b..b7f2410366dbf783059c0449ba2b068087d58862 100644 (file)
@@ -27,67 +27,41 @@ open Printf
 
 open DisambiguateTypes
 
-exception Invalid_choice
-exception Choice_not_found of string
+exception Choice_not_found of string Lazy.t
 
-let symbol_choices = Hashtbl.create 1023
 let num_choices = ref []
 
-let add_symbol_choice symbol codomain_item =
-  let current_choices =
-    try
-      Hashtbl.find symbol_choices symbol
-    with Not_found -> []
-  in
-  Hashtbl.replace symbol_choices symbol (codomain_item :: current_choices)
-
-let add_binary_op symbol dsc appl_head =
-  add_symbol_choice symbol
-    (dsc,
-      (fun env _ args ->
-        let t1, t2 =
-          match args with
-          | [t1; t2] -> t1, t2
-          | _ -> raise Invalid_choice
-        in
-        Cic.Appl [ appl_head; t1; t2 ]))
-
-let add_unary_op symbol dsc appl_head =
-  add_symbol_choice symbol
-    (dsc,
-      (fun env _ args ->
-        let t = match args with [t] -> t | _ -> raise Invalid_choice in
-        Cic.Appl [ appl_head; t ]))
-
 let add_num_choice choice = num_choices := choice :: !num_choices
 
-let lookup_symbol_choices symbol =
-  try
-    Hashtbl.find symbol_choices symbol
-  with Not_found -> []
-
-let lookup_num_choices () = !num_choices
-
 let has_description dsc = (fun x -> fst x = dsc)
 
-let lookup_symbol_by_dsc symb dsc =
-  try
-    List.find (has_description dsc) (Hashtbl.find symbol_choices symb)
-  with Not_found ->
-    raise (Choice_not_found (sprintf "Symbol %s, dsc %s" symb dsc))
+let lookup_num_choices () = !num_choices
 
 let lookup_num_by_dsc dsc =
   try
     List.find (has_description dsc) !num_choices
-  with Not_found -> raise (Choice_not_found ("Num with dsc " ^  dsc))
-
-  (** initial table contents *)
-
-let _ =
-  let uri s = UriManager.uri_of_string s in
-  let const s = Cic.Const (uri s, []) in
-  let mutind s = Cic.MutInd (uri s, 0, []) in
-  add_binary_op "exists" "exists" (mutind "cic:/Coq/Init/Logic/ex.ind");
-  add_binary_op "exists" "exists over terms with sort Type"
-    (mutind "cic:/Coq/Init/Logic_Type/exT.ind");
+  with Not_found -> raise (Choice_not_found (lazy ("Num with dsc " ^  dsc)))
+
+let mk_choice (dsc, args, appl_pattern) =
+  dsc,
+  (fun env _ cic_args ->
+    let env' =
+      let names =
+        List.map (function CicNotationPt.IdentArg (_, name) -> name) args
+      in
+      try
+        List.combine names cic_args
+      with Invalid_argument _ ->
+       raise (Invalid_choice (lazy "The notation expects a different number of arguments"))
+    in
+    CicNotationFwd.instantiate_appl_pattern env' appl_pattern)
+
+let lookup_symbol_by_dsc symbol dsc =
+  try
+    mk_choice
+      (List.find
+        (fun (dsc', _, _) -> dsc = dsc')
+        (CicNotationRew.lookup_interpretations symbol))
+  with CicNotationRew.Interpretation_not_found | Not_found ->
+    raise (Choice_not_found (lazy (sprintf "Symbol %s, dsc %s" symbol dsc)))