]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/tactics/reductionTactics.ml
Defs in context may now have an optional type (when unknown).
[helm.git] / helm / ocaml / tactics / reductionTactics.ml
index b29873a1fceae31c4521c231bfd503ce29b65585..55eacc234c3da15ffb057255dc73cf30391407f1 100644 (file)
@@ -69,11 +69,12 @@ let reduction_tac ~also_in_hypotheses ~reduction ~terms ~status:(proof,goal) =
       List.fold_right
        (fun entry context ->
          match entry with
-            Some (name,Cic.Def  t) ->
-             (Some (name,Cic.Def  (replace context t)))::context
+            Some (name,Cic.Def (t,None)) ->
+             (Some (name,Cic.Def ((replace context t),None)))::context
           | Some (name,Cic.Decl t) ->
              (Some (name,Cic.Decl (replace context t)))::context
           | None -> None::context
+          | Some (_,Cic.Def (_,Some _)) -> assert false
        ) context []
      else
       context
@@ -110,8 +111,9 @@ let fold_tac ~reduction ~also_in_hypotheses ~term ~status:(proof,goal) =
        List.map
         (function
             Some (n,Cic.Decl t) -> Some (n,Cic.Decl (replace t))
-          | Some (n,Cic.Def t)  -> Some (n,Cic.Def  (replace t))
+          | Some (n,Cic.Def (t,None))  -> Some (n,Cic.Def ((replace t),None))
           | None -> None
+          | Some (_,Cic.Def (_,Some _)) -> assert false
         ) context
       else
        context