]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/cic/cic.ml
New experimental commit: metavariables representation is changed again,
[helm.git] / helm / ocaml / cic / cic.ml
index 0a43c4c571e80021fb625906c3d72a590442ddb6..550d4a8f6d306f14dd1caba58b7a183503784a8b 100644 (file)
@@ -52,7 +52,8 @@ and name =
 and term =
    Rel of int                                       (* DeBrujin index *)
  | Var of UriManager.uri                            (* uri *)
- | Meta of int                                      (* numeric id *)
+ | Meta of int * (term option) list                 (* numeric id,    *)
+                                                    (*  local context *)
  | Sort of sort                                     (* sort *)
  | Implicit                                         (* *)
  | Cast of term * term                              (* value, type *)
@@ -78,7 +79,7 @@ and obj =
  | Axiom of string * term *
     (int * UriManager.uri list) list              (* id, type, parameters     *)
  | Variable of string * term option * term        (* name, body, type         *)
- | CurrentProof of string * (int * term) list *   (* name, conjectures,       *)
+ | CurrentProof of string * metasenv *            (* name, conjectures,       *)
     term * term                                   (*  value, type             *)
  | InductiveDefinition of inductiveType list *    (* inductive types,         *)
     (int * UriManager.uri list) list * int        (*  parameters, n ind. pars *)
@@ -92,10 +93,15 @@ and inductiveFun =
 and coInductiveFun =
  string * term * term                         (* name, type, body *)
 
+and metasenv = (int * context * term) list (* a metasenv is a list of declarations of metas *)
+
+and annmetasenv = (int * anncontext * annterm) list (* a metasenv is a list of declarations of metas *)
+
 and annterm =
    ARel of id * int * string                        (* DeBrujin index, binder *)
  | AVar of id * UriManager.uri                      (* uri *)
- | AMeta of id * int                                (* numeric id *)
+ | AMeta of id * int * (annterm option) list        (* numeric id,    *)
+                                                    (*  local context *)
  | ASort of id * sort                               (* sort *)
  | AImplicit of id                                  (* *)
  | ACast of id * annterm * annterm                  (* value, type *)
@@ -124,7 +130,7 @@ and annobj =
  | AVariable of id *
     string * annterm option * annterm               (* name, body, type *)
  | ACurrentProof of id *
-    string * (int * annterm) list *                 (*  name, conjectures, *)
+    string * annmetasenv *                          (*  name, conjectures, *)
     annterm * annterm                               (*  value, type        *)
  | AInductiveDefinition of id *
     anninductiveType list *                         (* inductive types ,      *)
@@ -143,12 +149,15 @@ and annotation =
 and 'a exactness =
    Possible of 'a                            (* an approximation to something *)
  | Actual of 'a                              (* something *)
-;;
 
-(* Contexts are lists of context_entry *)
-type context_entry =
+and context_entry =                    (* Contexts are lists of context_entry *)
    Decl of term
  | Def of term
-;;
 
-type context = context_entry list;;
+and context = ((name * context_entry) option) list
+
+and anncontext_entry =                 (* Contexts are lists of context_entry *)
+   ADecl of annterm
+ | ADef of annterm
+
+and anncontext = ((name * anncontext_entry) option) list;;