]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/software/components/ng_cic_content/nTermCicContent.ml
1) the home button of CicBrowser now works also for NG
[helm.git] / helm / software / components / ng_cic_content / nTermCicContent.ml
index da8061fde197d56c3d482c071d75276ffa74cae1..62d69f5d166dd979ac37bf7d99769895ef07efb0 100644 (file)
@@ -387,13 +387,9 @@ let instantiate_appl_pattern
   aux appl_pattern
 *)
 
-let nmap_sequent ~subst (i,(n,context,ty):int * NCic.conjecture) =
+let nmap_sequent0 ~idref ~subst (i,(n,context,ty):int * NCic.conjecture) =
  let module K = Content in
- let ids_to_refs = Hashtbl.create 211 in
- let register_ref = Hashtbl.add ids_to_refs in
- let nast_of_cic =
-  nast_of_cic1 ~idref:(idref register_ref) ~output_type:`Term
-   ~subst in
+ let nast_of_cic = nast_of_cic1 ~idref ~output_type:`Term ~subst in
  let context',_ =
   List.fold_right
    (fun item (res,context) ->
@@ -422,6 +418,146 @@ let nmap_sequent ~subst (i,(n,context,ty):int * NCic.conjecture) =
              })::res,item::context
    ) context ([],[])
  in
-  ("-1",i,context',nast_of_cic ~context ty), ids_to_refs
+  ("-1",i,context',nast_of_cic ~context ty)
+;;
+
+let nmap_sequent ~subst metasenv =
+ let module K = Content in
+ let ids_to_refs = Hashtbl.create 211 in
+ let register_ref = Hashtbl.add ids_to_refs in
+  nmap_sequent0 ~idref:(idref register_ref) ~subst metasenv, ids_to_refs
+;;
+
+let object_prefix = "obj:";;
+let declaration_prefix = "decl:";;
+let definition_prefix = "def:";;
+
+let get_id =
+ function
+    Ast.AttributedTerm (`IdRef id, _) -> id
+  | _ -> assert false
+;;
+
+let gen_id prefix seed =
+ let res = prefix ^ string_of_int !seed in
+  incr seed ;
+  res
+;;
+
+let build_def_item seed context metasenv id n t ty =
+ let module K = Content in
+(*
+  try
+   let sort = Hashtbl.find ids_to_inner_sorts id in
+   if sort = `Prop then
+       (let p = 
+        (acic2content seed context metasenv ?name:(name_of n) ~ids_to_inner_sorts  ~ids_to_inner_types t)
+       in 
+        `Proof p;)
+   else 
+*)
+      `Definition
+        { K.def_name = Some n;
+          K.def_id = gen_id definition_prefix seed; 
+          K.def_aref = id;
+          K.def_term = t;
+          K.def_type = ty
+        }
+(*
+  with
+   Not_found -> assert false
+*)
+
+let build_decl_item seed id n s =
+ let module K = Content in
+(*
+ let sort =
+   try
+    Some (Hashtbl.find ids_to_inner_sorts (Cic2acic.source_id_of_id id))
+   with Not_found -> None
+ in
+ match sort with
+ | Some `Prop ->
+    `Hypothesis
+      { K.dec_name = name_of n;
+        K.dec_id = gen_id declaration_prefix seed; 
+        K.dec_inductive = false;
+        K.dec_aref = id;
+        K.dec_type = s
+      }
+ | _ ->
+*)
+    `Declaration
+      { K.dec_name = Some n;
+        K.dec_id = gen_id declaration_prefix seed; 
+        K.dec_inductive = false;
+        K.dec_aref = id;
+        K.dec_type = s
+      }
 ;;
 
+let nmap_obj (uri,_,metasenv,subst,kind) =
+  let module K = Content in
+  let ids_to_refs = Hashtbl.create 211 in
+  let register_ref = Hashtbl.add ids_to_refs in
+  let idref = idref register_ref in
+  let nast_of_cic =
+   nast_of_cic1 ~idref ~output_type:`Term ~subst in
+  let seed = ref 0 in
+  let conjectures =
+   match metasenv with
+      [] -> None
+    | _ -> (*Some (List.map (map_conjectures seed) metasenv)*)
+      (*CSC: used to be the previous line, that uses seed *)
+      Some (List.map (nmap_sequent0 ~idref ~subst) metasenv)
+  in
+  let res =
+   match kind with
+      NCic.Constant (_,_,Some bo,ty,_) ->
+       let ty = nast_of_cic ~context:[] ty in
+       let bo = nast_of_cic ~context:[] bo in
+        (gen_id object_prefix seed, [], conjectures,
+          `Def (K.Const,ty,
+            build_def_item seed [] [] (get_id bo) (NUri.name_of_uri uri) bo ty))
+    | NCic.Constant (_,_,None,ty,_) ->
+       let ty = nast_of_cic ~context:[] ty in
+         (gen_id object_prefix seed, [], conjectures,
+           `Decl (K.Const,
+             (*CSC: ??? get_id ty here used to be the id of the axiom! *)
+             build_decl_item seed (get_id ty) (NUri.name_of_uri uri) ty))
+(*
+    | C.AInductiveDefinition (id,l,params,nparams,_) ->
+         (gen_id object_prefix seed, params, conjectures,
+            `Joint
+              { K.joint_id = gen_id joint_prefix seed;
+                K.joint_kind = `Inductive nparams;
+                K.joint_defs = List.map (build_inductive seed) l
+              }) 
+
+and
+    build_inductive seed = 
+     let module K = Content in
+      fun (_,n,b,ty,l) ->
+        `Inductive
+          { K.inductive_id = gen_id inductive_prefix seed;
+            K.inductive_name = n;
+            K.inductive_kind = b;
+            K.inductive_type = ty;
+            K.inductive_constructors = build_constructors seed l
+           }
+
+and 
+    build_constructors seed l =
+     let module K = Content in
+      List.map 
+       (fun (n,t) ->
+           { K.dec_name = Some n;
+             K.dec_id = gen_id declaration_prefix seed;
+             K.dec_inductive = false;
+             K.dec_aref = "";
+             K.dec_type = t
+           }) l
+*)
+ in
+  res,ids_to_refs
+;;