]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/software/components/ng_refiner/nCicUnification.ml
Fixed a performance problem with unif_machines and small_delta_step.
[helm.git] / helm / software / components / ng_refiner / nCicUnification.ml
index a1a325fa541dd9c33a9ea7eb61b90f02363bc1fb..bfa8fff4758db1c620b7e5cc0fd40832f113a1b0 100644 (file)
@@ -74,7 +74,8 @@ let outside () = indent := String.sub !indent 0 (String.length !indent -1);;
 
 (*
 let pp s = 
- prerr_endline (Printf.sprintf "%-20s" !indent ^ " " ^ s);; 
+  prerr_endline (Printf.sprintf "%-20s" !indent ^ " " ^ Lazy.force s)
+;;  
 *)
 
 let pp _ = ();;
@@ -122,9 +123,10 @@ let rec beta_expand num test_eq_only swap metasenv subst context t arg =
     metasenv, subst, NCic.Lambda ("_", argty, NCicSubstitution.lift 1 arg)
 
 and beta_expand_many test_equality_only swap metasenv subst context t args =
-(*D*)  inside 'B'; try let rc =
-  pp (String.concat ", " (List.map (NCicPp.ppterm ~metasenv ~subst ~context)
-     args) ^ " ∈ " ^ NCicPp.ppterm ~metasenv ~subst ~context t);
+(* (*D*)  inside 'B'; try let rc = *)
+  pp (lazy (String.concat ", "
+     (List.map (NCicPp.ppterm ~metasenv ~subst ~context)
+     args) ^ " ∈ " ^ NCicPp.ppterm ~metasenv ~subst ~context t));
   let _, subst, metasenv, hd =
     List.fold_right
       (fun arg (num,subst,metasenv,t) ->
@@ -134,13 +136,13 @@ and beta_expand_many test_equality_only swap metasenv subst context t args =
            num+1,subst,metasenv,t)
       args (1,subst,metasenv,t) 
   in
-  pp ("Head syntesized by b-exp: " ^ 
-    NCicPp.ppterm ~metasenv ~subst ~context hd);
+  pp (lazy ("Head syntesized by b-exp: " ^ 
+    NCicPp.ppterm ~metasenv ~subst ~context hd));
     metasenv, subst, hd
-(*D*)  in outside (); rc with exn -> outside (); raise exn
+(* (*D*)  in outside (); rc with exn -> outside (); raise exn *)
 
 and instantiate test_eq_only metasenv subst context n lc t swap =
-(*D*)  inside 'I'; try let rc = 
+(* (*D*)  inside 'I'; try let rc =  *)
   let unify test_eq_only m s c t1 t2 = 
     if swap then unify test_eq_only m s c t2 t1 
     else unify test_eq_only m s c t1 t2
@@ -154,8 +156,9 @@ and instantiate test_eq_only metasenv subst context n lc t swap =
   in
   let name, ctx, ty = NCicUtils.lookup_meta n metasenv in
   let lty = NCicSubstitution.subst_meta lc ty in
-  pp ("On the types: " ^ NCicPp.ppterm ~metasenv ~subst ~context lty ^ " === "
-    ^ NCicPp.ppterm ~metasenv ~subst ~context ty_t); 
+  pp (lazy("On the types: " ^
+   NCicPp.ppterm ~metasenv ~subst ~context lty ^ " === "
+    ^ NCicPp.ppterm ~metasenv ~subst ~context ty_t)); 
   let metasenv, subst = unify test_eq_only metasenv subst context lty ty_t in
   let (metasenv, subst), t = 
     try NCicMetaSubst.delift metasenv subst context n lc t
@@ -172,18 +175,22 @@ and instantiate test_eq_only metasenv subst context n lc t swap =
     (* by cumulativity when unify(?,Type_i) 
      * we could ? := Type_j with j <= i... *)
     let subst = (n, (name, ctx, t, ty)) :: subst in
+    pp (lazy ("?"^string_of_int n^" := "^NCicPp.ppterm
+      ~metasenv ~subst ~context:ctx (NCicSubstitution.subst_meta lc t)));
     let metasenv = 
       List.filter (fun (m,_) -> not (n = m)) metasenv 
     in
     metasenv, subst
-(*D*)  in outside(); rc with exn -> outside (); raise exn
+(* (*D*)  in outside(); rc with exn -> outside (); raise exn *)
 
 and unify test_eq_only metasenv subst context t1 t2 =
-(*D*) inside 'U'; try let rc =
+(* (*D*) inside 'U'; try let rc = *)
    let fo_unif test_eq_only metasenv subst t1 t2 =
-   (*D*) inside 'F'; try let rc = 
-     pp ("  " ^ NCicPp.ppterm ~metasenv ~subst ~context t1 ^ " === " ^ 
-         NCicPp.ppterm ~metasenv ~subst ~context t2);
+(*    (*D*) inside 'F'; try let rc =  *)
+(*
+     pp (lazy("  " ^ NCicPp.ppterm ~metasenv ~subst ~context t1 ^ " === " ^ 
+         NCicPp.ppterm ~metasenv ~subst ~context t2));
+*)
      if t1 === t2 then
        metasenv, subst
      else
@@ -367,7 +374,7 @@ and unify test_eq_only metasenv subst context t1 t2 =
                raise (uncert_exc metasenv subst context t1 t2))
        | (C.Implicit _, _) | (_, C.Implicit _) -> assert false
        | _ -> raise (uncert_exc metasenv subst context t1 t2)
-    (*D*)  in outside(); rc with exn -> outside (); raise exn
+(*     (*D*)  in outside(); rc with exn -> outside (); raise exn *)
     in
     let height_of = function
      | NCic.Const (Ref.Ref (_,Ref.Def h)) 
@@ -389,7 +396,7 @@ and unify test_eq_only metasenv subst context t1 t2 =
         if flexible [t2] then max 0 (h1 - 1) else
         if h1 = h2 then max 0 (h1 -1) else min h1 h2 
       in
-      pp ("DELTA STEP TO: " ^ string_of_int delta);
+      pp (lazy("DELTA STEP TO: " ^ string_of_int delta));
       let m1' = NCicReduction.reduce_machine ~delta ~subst context m1 in
       let m2' = NCicReduction.reduce_machine ~delta ~subst context m2 in
       if (m1' == m1 && m2' == m2 && delta > 0) then
@@ -398,20 +405,22 @@ and unify test_eq_only metasenv subst context t1 t2 =
           * rec argument. if no reduction was performed we decrease delta to m-1
           * to reduce the other term *)
          let delta = delta - 1 in
-         pp ("DELTA STEP TO: " ^ string_of_int delta);
+         pp (lazy("DELTA STEP TO: " ^ string_of_int delta));
          let m1' = NCicReduction.reduce_machine ~delta ~subst context m1 in
          let m2' = NCicReduction.reduce_machine ~delta ~subst context m2 in
-         m1', m2', (m1 == m1' && m2 == m2') || delta = 0
-      else m1', m2', delta = 0
+         m1', m2', (m1 == m1' && m2 == m2') (* || delta = 0 *)
+      else m1', m2', (m1 == m1' && m2 == m2') (* delta = 0 *)
     in
     let rec unif_machines metasenv subst = 
       function
       | ((k1,e1,t1,s1 as m1),(k2,e2,t2,s2 as m2),are_normal) ->
-    (*D*) inside 'M'; try let rc =
-         pp ((if are_normal then "*" else " ") ^ " " ^
+(*     (*D*) inside 'M'; try let rc = *)
+(*
+         pp (lazy((if are_normal then "*" else " ") ^ " " ^
            NCicPp.ppterm ~metasenv ~subst ~context (NCicReduction.unwind m1) ^
            " === " ^ 
-           NCicPp.ppterm ~metasenv ~subst ~context (NCicReduction.unwind m2));
+           NCicPp.ppterm ~metasenv ~subst ~context (NCicReduction.unwind m2)));
+*)
           let relevance = [] (* TO BE UNDERSTOOD 
             match t1 with
             | C.Const r -> NCicEnvironment.get_relevance r
@@ -439,12 +448,10 @@ and unify test_eq_only metasenv subst context t1 t2 =
           in
         try check_stack (List.rev s1) (List.rev s2) relevance (metasenv,subst)
         with UnificationFailure _ | Uncertain _ when not are_normal ->
-(*
-          let delta = delta - 1 in 
-          let red = NCicReduction.reduce_machine ~delta ~subst context in
-*)
-          unif_machines metasenv subst (small_delta_step m1 m2)
-     (*D*)  in outside(); rc with exn -> outside (); raise exn
+         let m1,m2,normal as small = small_delta_step m1 m2 in
+           if not normal then unif_machines metasenv subst small
+           else raise (UnificationFailure (lazy "TEST x"))
+(*      (*D*)  in outside(); rc with exn -> outside (); raise exn *)
      in
      try fo_unif test_eq_only metasenv subst t1 t2
      with UnificationFailure msg | Uncertain msg as exn -> 
@@ -454,7 +461,7 @@ and unify test_eq_only metasenv subst context t1 t2 =
        with 
        | UnificationFailure _ -> raise (UnificationFailure msg)
        | Uncertain _ -> raise exn
-(*D*)  in outside(); rc with exn -> outside (); raise exn
+(* (*D*)  in outside(); rc with exn -> outside (); raise exn *)
 ;;
 
 let unify =