]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/cic_transformations/tacticAst.ml
embedded commands ast into tacticals ast
[helm.git] / helm / ocaml / cic_transformations / tacticAst.ml
index fbb281c49d1467aa2ee753b866f308925111b56b..f0dad83e23b828372be01a031e8f1eeb71fac101 100644 (file)
@@ -65,17 +65,43 @@ type ('term, 'ident) tactic =
   | Symmetry
   | Transitivity of 'term
 
-type 'tactic tactical =
-  | LocatedTactical of CicAst.location * 'tactic tactical
+type thm_flavour =
+  [ `Definition
+  | `Fact
+  | `Goal
+  | `Lemma
+  | `Remark
+  | `Theorem
+  ]
+
+type 'term command =
+  | Proof
+  | Theorem of thm_flavour * string option * 'term * 'term option
+      (* flavour, name, type, body
+       * - name is absent when an unnamed theorem is being proved, tipically in
+       *   interactive usage
+       * - body is present when its given along with the command, otherwise it
+       *   will be given in proof editing mode using the tactical language
+       *)
+  | Qed of string option
+      (* name.
+       * Name is needed when theorem was started without providing a name
+       *)
+  | Quit
+
+type ('term, 'ident) tactical =
+  | LocatedTactical of CicAst.location * ('term, 'ident) tactical
+
+  | Tactic of ('term, 'ident) tactic
+  | Command of 'term command
 
   | Fail
-  | Do of int * 'tactic tactical
+  | Do of int * ('term, 'ident) tactical
   | IdTac
-  | Repeat of 'tactic tactical
-  | Seq of 'tactic tactical list (* sequential composition *)
-  | Tactic of 'tactic
-  | Then of 'tactic tactical * 'tactic tactical list
-  | Tries of 'tactic tactical list
+  | Repeat of ('term, 'ident) tactical
+  | Seq of ('term, 'ident) tactical list (* sequential composition *)
+  | Then of ('term, 'ident) tactical * ('term, 'ident) tactical list
+  | Tries of ('term, 'ident) tactical list
       (* try a sequence of tacticals until one succeeds, fail otherwise *)
-  | Try of 'tactic tactical (* try a tactical and mask failures *)
+  | Try of ('term, 'ident) tactical (* try a tactical and mask failures *)