]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/tactics/introductionTactics.ml
got rid of ~status label so that tactics can now be applied partially,
[helm.git] / helm / ocaml / tactics / introductionTactics.ml
index b425f219af8585778f7b1a1bcc27fd57c774be39..9751b2b7478fdf0d05dc74ea092fbfc1b60c6774 100644 (file)
@@ -23,8 +23,7 @@
  * http://cs.unibo.it/helm/.
  *)
 
-
-let constructor_tac ~n ~status:(proof, goal) =
+let constructor_tac ~n (proof, goal) =
   let module C = Cic in
   let module R = CicReduction in
    let (_,metasenv,_,_) = proof in
@@ -34,27 +33,12 @@ let constructor_tac ~n ~status:(proof, goal) =
       | (C.Appl ((C.MutInd (uri, typeno, exp_named_subst))::_)) ->
          PrimitiveTactics.apply_tac 
           ~term: (C.MutConstruct (uri, typeno, n, exp_named_subst))
-          ~status:(proof, goal)
+          (proof, goal)
       | _ -> raise (ProofEngineTypes.Fail "Constructor: failed")
 ;;
 
-
-let exists_tac ~status =
-  constructor_tac ~n:1 ~status
-;;
-
-
-let split_tac ~status =
-  constructor_tac ~n:1 ~status
-;;
-
-
-let left_tac ~status =
-  constructor_tac ~n:1 ~status
-;;
-
-
-let right_tac ~status =
-  constructor_tac ~n:2 ~status
-;;
+let exists_tac status = constructor_tac ~n:1 status ;;
+let split_tac status = constructor_tac ~n:1 status ;;
+let left_tac status = constructor_tac ~n:1 status ;;
+let right_tac status = constructor_tac ~n:2 status ;;