]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/grafite/grafiteAst.ml
test branch
[helm.git] / helm / ocaml / grafite / grafiteAst.ml
diff --git a/helm/ocaml/grafite/grafiteAst.ml b/helm/ocaml/grafite/grafiteAst.ml
new file mode 100644 (file)
index 0000000..c956715
--- /dev/null
@@ -0,0 +1,167 @@
+(* Copyright (C) 2004, HELM Team.
+ * 
+ * This file is part of HELM, an Hypertextual, Electronic
+ * Library of Mathematics, developed at the Computer Science
+ * Department, University of Bologna, Italy.
+ * 
+ * HELM is free software; you can redistribute it and/or
+ * modify it under the terms of the GNU General Public License
+ * as published by the Free Software Foundation; either version 2
+ * of the License, or (at your option) any later version.
+ * 
+ * HELM is distributed in the hope that it will be useful,
+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+ * GNU General Public License for more details.
+ *
+ * You should have received a copy of the GNU General Public License
+ * along with HELM; if not, write to the Free Software
+ * Foundation, Inc., 59 Temple Place - Suite 330, Boston,
+ * MA  02111-1307, USA.
+ * 
+ * For details, see the HELM World-Wide-Web page,
+ * http://helm.cs.unibo.it/
+ *)
+
+(* $Id$ *)
+
+type direction = [ `LeftToRight | `RightToLeft ]
+
+type loc = Token.flocation
+
+type ('term, 'lazy_term, 'ident) pattern =
+  'lazy_term option * ('ident * 'term) list * 'term option
+
+type ('term, 'ident) type_spec =
+   | Ident of 'ident
+   | Type of UriManager.uri * int 
+
+type 'lazy_term reduction =
+  [ `Normalize
+  | `Reduce
+  | `Simpl
+  | `Unfold of 'lazy_term option
+  | `Whd ]
+
+type ('term, 'lazy_term, 'reduction, 'ident) tactic =
+  | Absurd of loc * 'term
+  | Apply of loc * 'term
+  | Assumption of loc
+  | Auto of loc * int option * int option * string option * string option 
+      (* depth, width, paramodulation, full *) (* ALB *)
+  | Change of loc * ('term, 'lazy_term, 'ident) pattern * 'lazy_term
+  | Clear of loc * 'ident
+  | ClearBody of loc * 'ident
+  | Compare of loc * 'term
+  | Constructor of loc * int
+  | Contradiction of loc
+  | Cut of loc * 'ident option * 'term
+  | DecideEquality of loc
+  | Decompose of loc * ('term, 'ident) type_spec list * 'ident * 'ident list
+  | Discriminate of loc * 'term
+  | Elim of loc * 'term * 'term option * int option * 'ident list
+  | ElimType of loc * 'term * 'term option * int option * 'ident list
+  | Exact of loc * 'term
+  | Exists of loc
+  | Fail of loc
+  | Fold of loc * 'reduction * 'lazy_term * ('term, 'lazy_term, 'ident) pattern
+  | Fourier of loc
+  | FwdSimpl of loc * string * 'ident list
+  | Generalize of loc * ('term, 'lazy_term, 'ident) pattern * 'ident option
+  | Goal of loc * int (* change current goal, argument is goal number 1-based *)
+  | IdTac of loc
+  | Injection of loc * 'term
+  | Intros of loc * int option * 'ident list
+  | Inversion of loc * 'term
+  | LApply of loc * int option * 'term list * 'term * 'ident option
+  | Left of loc
+  | LetIn of loc * 'term * 'ident
+  | Reduce of loc * 'reduction * ('term, 'lazy_term, 'ident) pattern 
+  | Reflexivity of loc
+  | Replace of loc * ('term, 'lazy_term, 'ident) pattern * 'lazy_term
+  | Rewrite of loc * direction * 'term *
+      ('term, 'lazy_term, 'ident) pattern
+  | Right of loc
+  | Ring of loc
+  | Split of loc
+  | Symmetry of loc
+  | Transitivity of loc * 'term
+
+type search_kind = [ `Locate | `Hint | `Match | `Elim ]
+
+type print_kind = [ `Env | `Coer ]
+
+type 'term macro = 
+  (* Whelp's stuff *)
+  | WHint of loc * 'term 
+  | WMatch of loc * 'term 
+  | WInstance of loc * 'term 
+  | WLocate of loc * string
+  | WElim of loc * 'term
+  (* real macros *)
+(*   | Abort of loc *)
+  | Print of loc * string
+  | Check of loc * 'term 
+  | Hint of loc
+  | Quit of loc
+(*   | Redo of loc * int option
+  | Undo of loc * int option *)
+(*   | Print of loc * print_kind *)
+  | Search_pat of loc * search_kind * string  (* searches with string pattern *)
+  | Search_term of loc * search_kind * 'term  (* searches with term pattern *)
+
+(** To be increased each time the command type below changes, used for "safe"
+ * marshalling *)
+let magic = 5
+
+type 'obj command =
+  | Default of loc * string * UriManager.uri list
+  | Include of loc * string
+  | Set of loc * string * string
+  | Drop of loc
+  | Qed of loc
+  | Coercion of loc * UriManager.uri * bool (* add composites *)
+  | Obj of loc * 'obj
+
+type ('term, 'lazy_term, 'reduction, 'ident) tactical =
+  | Tactic of loc * ('term, 'lazy_term, 'reduction, 'ident) tactic
+  | Do of loc * int * ('term, 'lazy_term, 'reduction, 'ident) tactical
+  | Repeat of loc * ('term, 'lazy_term, 'reduction, 'ident) tactical
+  | Seq of loc * ('term, 'lazy_term, 'reduction, 'ident) tactical list
+      (* sequential composition *)
+  | Then of loc * ('term, 'lazy_term, 'reduction, 'ident) tactical *
+      ('term, 'lazy_term, 'reduction, 'ident) tactical list
+  | First of loc * ('term, 'lazy_term, 'reduction, 'ident) tactical list
+      (* try a sequence of loc * tactical until one succeeds, fail otherwise *)
+  | Try of loc * ('term, 'lazy_term, 'reduction, 'ident) tactical
+      (* try a tactical and mask failures *)
+  | Solve of loc * ('term, 'lazy_term, 'reduction, 'ident) tactical list
+
+  | Dot of loc
+  | Semicolon of loc
+  | Branch of loc
+  | Shift of loc
+  | Pos of loc * int
+  | Merge of loc
+  | Focus of loc * int list
+  | Unfocus of loc
+  | Skip of loc
+
+let is_punctuation =
+  function
+  | Dot _ | Semicolon _ | Branch _ | Shift _ | Merge _ | Pos _ -> true
+  | _ -> false
+
+type ('term, 'lazy_term, 'reduction, 'obj, 'ident) code =
+  | Command of loc * 'obj command
+  | Macro of loc * 'term macro 
+  | Tactical of loc * ('term, 'lazy_term, 'reduction, 'ident) tactical
+      * ('term, 'lazy_term, 'reduction, 'ident) tactical option(* punctuation *)
+             
+type ('term, 'lazy_term, 'reduction, 'obj, 'ident) comment =
+  | Note of loc * string
+  | Code of loc * ('term, 'lazy_term, 'reduction, 'obj, 'ident) code
+             
+type ('term, 'lazy_term, 'reduction, 'obj, 'ident) statement =
+  | Executable of loc * ('term, 'lazy_term, 'reduction, 'obj, 'ident) code
+  | Comment of loc * ('term, 'lazy_term, 'reduction, 'obj, 'ident) comment