]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/cic_transformations/cic2content.mli
CSC: tentative definition of the ocaml structure that represents
[helm.git] / helm / ocaml / cic_transformations / cic2content.mli
index 8e26bb897466a63782dcdc0f997437f21651aada..f3a38be5036a302ed98c129dfefd99987197f14d 100644 (file)
  * http://cs.unibo.it/helm/.
  *)
 
-(**************************************************************************)
-(*                                                                        *)
-(*                           PROJECT HELM                                 *)
-(*                                                                        *)
-(*                Andrea Asperti <asperti@cs.unibo.it>                    *)
-(*                             16/62003                                   *)
-(*                                                                        *)
-(**************************************************************************)
-
-type recursion_kind = NoRecursive | Recursive | CoRecursive;;
-
-type 
-      'term proof = 
-      { proof_name : string option;
-        proof_id   : string ;
-        proof_kind : recursion_kind ;
-        proof_context : ('term context_element) list ;
-        proof_apply_context: ('term proof) list;
-        proof_conclude : 'term conclude_item;
-      }
-and
-      'term context_element = 
-         Declaration of 'term declaration
-       | Hypothesis of 'term declaration
-       | Proof of 'term proof
-       | Definition of 'term definition
-       | Joint of 'term joint
-and
-      'term declaration =
+type id = string;;
+type joint_recursion_kind =
+ [ `Recursive
+ | `CoRecursive
+ | `Inductive of int    (* paramsno *)
+ | `CoInductive of int  (* paramsno *)
+ ]
+;;
+
+type var_or_const = Var | Const;;
+
+type 'term declaration =
        { dec_name : string option;
          dec_id : string ;
          dec_inductive : bool;
          dec_aref : string;
          dec_type : 'term 
        }
-and
-      'term definition =
+;;
+
+type 'term definition =
        { def_name : string option;
          def_id : string ;
          def_aref : string ;
          def_term : 'term 
        }
-and
-      'term joint =
+;;
+
+type 'term inductive =
+       { inductive_id : string ;
+         inductive_kind : bool;
+         inductive_type : 'term;
+         inductive_constructors : 'term declaration list
+       }
+;;
+
+type 'term decl_context_element = 
+       [ `Declaration of 'term declaration
+       | `Hypothesis of 'term declaration
+       ]
+;;
+
+type ('term,'proof) def_context_element = 
+       [ `Proof of 'proof
+       | `Definition of 'term definition
+       ]
+;;
+
+type ('term,'proof) in_joint_context_element =
+       [ `Inductive of 'term inductive
+       | 'term decl_context_element
+       | ('term,'proof) def_context_element
+       ]
+;;
+
+type ('term,'proof) joint =
        { joint_id : string ;
-         joint_kind : recursion_kind ;
-         joint_defs : 'term context_element list
+         joint_kind : joint_recursion_kind ;
+         joint_defs : ('term,'proof) in_joint_context_element list
        }
-and 
-      'term conclude_item =
+;;
+
+type ('term,'proof) joint_context_element = 
+       [ `Joint of ('term,'proof) joint ]
+;;
+
+type 'term proof = 
+      { proof_name : string option;
+        proof_id   : string ;
+        proof_context : 'term in_proof_context_element list ;
+        proof_apply_context: 'term proof list;
+        proof_conclude : 'term conclude_item
+      }
+
+and 'term in_proof_context_element =
+       [ 'term decl_context_element
+       | ('term,'term proof) def_context_element
+       | ('term,'term proof) joint_context_element
+       ]
+
+and 'term conclude_item =
        { conclude_id :string; 
          conclude_aref : string;
          conclude_method : string;
          conclude_args : ('term arg) list ;
          conclude_conclusion : 'term option 
        }
-and 
-      'term arg =
+
+and 'term arg =
          Aux of int
        | Premise of premise
        | Term of 'term
        | ArgProof of 'term proof
        | ArgMethod of string (* ???? *)
-and 
-      premise =
+
+and premise =
        { premise_id: string;
          premise_xref : string ;
          premise_binder : string option;
@@ -95,12 +126,31 @@ and
        }
 ;;
  
-val acic2content : 
-    int ref ->                                (* seed *)
-    ?name:string option ->                    (* name *)
-    ids_to_inner_sorts:(Cic.id, string) Hashtbl.t ->             
-                                              (* ids_to_inner_sorts *)
-    ids_to_inner_types:(Cic.id, Cic2acic.anntypes) Hashtbl.t ->  
-                                              (* ids_to_inner_types *)
-    Cic.annterm ->                            (* annotated term *)
-    Cic.annterm proof
+type 'term conjecture = id * int * 'term context * 'term
+
+and 'term context = 'term hypothesis list
+
+and 'term hypothesis =
+ id *
+ ['term decl_context_element | ('term,'term proof) def_context_element ] option
+;;
+
+type 'term in_object_context_element =
+       [ `Decl of var_or_const * 'term decl_context_element
+       | `Def of var_or_const * 'term * ('term,'term proof) def_context_element
+       | ('term,'term proof) joint_context_element
+       ]
+;;
+
+type 'term cobj  = 
+        id *                            (* id *)
+        UriManager.uri list *           (* params *)
+        'term conjecture list option *  (* optional metasenv *) 
+        'term in_object_context_element (* actual object *)
+;;
+
+val annobj2content :
+  ids_to_inner_sorts:(string, string) Hashtbl.t ->
+  ids_to_inner_types:(string, Cic2acic.anntypes) Hashtbl.t ->
+  Cic.annobj ->
+  Cic.annterm cobj