]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/cic_unification/coercGraph.ml
ocaml 3.09 transition
[helm.git] / helm / ocaml / cic_unification / coercGraph.ml
index 469e334a7358e0b7dcbb03ea32607690a0d32fe5..d99fc6f798f67f72ccbee796adc50b8bd0db1474 100644 (file)
@@ -29,7 +29,7 @@ type coercion_search_result =
   | SomeCoercion of Cic.term
   | NoCoercion
   | NotMetaClosed
-  | NotHandled of string
+  | NotHandled of string Lazy.t
 
 let debug = false
 let debug_print s = if debug then prerr_endline (Lazy.force s) else ()
@@ -43,10 +43,23 @@ let look_for_coercion src tgt =
         (fun (s,t) -> CoercDb.eq_carr s src && CoercDb.eq_carr t tgt) 
     in
     match l with
-    | [] -> debug_print (lazy ":( coercion non trovata"); NoCoercion
+    | [] -> 
+        debug_print 
+          (lazy 
+            (sprintf ":-( coercion non trovata da %s a %s" 
+              (CoercDb.name_of_carr src) 
+              (CoercDb.name_of_carr tgt)));
+        NoCoercion
+    | [u] -> 
+        debug_print (lazy (
+          sprintf ":-) TROVATA 1 coercion da %s a %s: %s" 
+            (CoercDb.name_of_carr src) 
+            (CoercDb.name_of_carr tgt)
+            (UriManager.name_of_uri u)));
+        SomeCoercion (CicUtil.term_of_uri u)
     | u::_ -> 
         debug_print (lazy (
-          sprintf ":) TROVATE %d coercion(s) da %s a %s, prendo la prima: %s" 
+          sprintf ":-/ TROVATE %d coercion(s) da %s a %s, prendo la prima: %s" 
             (List.length l)
             (CoercDb.name_of_carr src) 
             (CoercDb.name_of_carr tgt)
@@ -67,13 +80,19 @@ let look_for_coercion src tgt =
  * (source, list of coercions to follow, target)
  *)
 let get_closure_coercions src tgt uri coercions =
+  let eq_carr s t = 
+    try
+      CoercDb.eq_carr s t
+    with
+    | CoercDb.EqCarrNotImplemented _ | CoercDb.EqCarrOnNonMetaClosed -> false
+  in
   match src,tgt with
   | CoercDb.Uri _, CoercDb.Uri _ ->
       let c_from_tgt = 
-        List.filter (fun (f,_,_) -> CoercDb.eq_carr f tgt) coercions 
+        List.filter (fun (f,_,_) -> eq_carr f tgt) coercions 
       in
       let c_to_src = 
-        List.filter (fun (_,t,_) -> CoercDb.eq_carr t src) coercions 
+        List.filter (fun (_,t,_) -> eq_carr t src) coercions 
       in
         (List.map (fun (_,t,u) -> src,[uri; u],t) c_from_tgt) @
         (List.map (fun (s,_,u) -> s,[u; uri],tgt) c_to_src) @
@@ -115,7 +134,7 @@ let generate_composite_closure c1 c2 univ =
       CicTypeChecker.type_of_aux' [] [] c univ
     with CicTypeChecker.TypeCheckerFailure s as exn ->
       debug_print (lazy (sprintf "Generated composite coercion:\n%s\n%s" 
-        (CicPp.ppterm c) s));
+        (CicPp.ppterm c) (Lazy.force s)));
       raise exn
   in
   let cleaned_ty =