]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/matita/matitaInterpreter.ml
*** empty log message ***
[helm.git] / helm / matita / matitaInterpreter.ml
index 818f7fe943621d5c6ad233e5ef1f3b89c31832f4..c9d5a71612d7e1893c11b033307b518d54759eec 100644 (file)
@@ -47,6 +47,8 @@ let uri name =
 *)
 
 let baseuri = lazy (ref ("cic:/matita/" ^ Helm_registry.get "matita.owner"))
+let basedir = ref ((Unix.getpwuid (Unix.getuid ())).Unix.pw_dir) ;;
+
 let qualify name =
   let baseuri = !(Lazy.force baseuri) in
   if baseuri.[String.length baseuri - 1] = '/' then
@@ -156,11 +158,21 @@ class sharedState
           console#echo_message (sprintf "base uri is \"%s\""
             !(Lazy.force baseuri));
           Quiet
+      | TacticAst.Command (TacticAst.Basedir (Some path)) ->
+          basedir := path;
+          console#echo_message (sprintf "base dir set to \"%s\"" path);
+          Quiet
+      | TacticAst.Command (TacticAst.Basedir None) ->
+          console#echo_message (sprintf "base dir is \"%s\"" !basedir);
+          Quiet
       | TacticAst.Command (TacticAst.Check term) ->
           let (_, _, term,ugraph) = 
            disambiguate ~disambiguator ~currentProof term 
          in
           let (context, metasenv) = get_context_and_metasenv currentProof in
+(* this is the Eval Compute
+          let term = CicReduction.whd context term in
+*)         
           let dummyno = CicMkImplicit.new_meta metasenv [] in
           let ty,ugraph1 = 
            CicTypeChecker.type_of_aux' metasenv context term ugraph 
@@ -183,9 +195,16 @@ class sharedState
           Quiet
       | TacticAst.Command (TacticAst.Print `Env) ->
           let uris = CicEnvironment.list_uri () in
+          console#echo_message "Environment:";
           List.iter (fun u ->
-            console#echo_message (UriManager.string_of_uri u);
-            prerr_endline "x"
+            console#echo_message ("  " ^ (UriManager.string_of_uri u))
+          ) uris;
+          Quiet
+      | TacticAst.Command (TacticAst.Print `Coer) ->
+          let uris = CoercGraph.get_coercions_list () in
+          console#echo_message "Coercions:";
+          List.iter (fun (s,t,u) ->
+            console#echo_message ("  " ^ (UriManager.string_of_uri u))
           ) uris;
           Quiet
       | tactical ->
@@ -264,6 +283,57 @@ let inddef_of_ast params indTypes (disambiguator:MatitaTypes.disambiguator) =
   let cicIndTypes = List.rev cicIndTypes in
   (UriManager.uri_of_string uri, (cicIndTypes, [], paramsno))
 
+let 
+ save_object_to_disk uri obj 
+=
+  (* generate annobj, ids_to_inner_sorts and ids_to_inner_types *)
+  let annobj,_,_,ids_to_inner_sorts,ids_to_inner_types,_,_ =
+    Cic2acic.acic_object_of_cic_object ~eta_fix:false obj
+  in 
+
+  (* prepare XML *)
+  let xml, bodyxml =
+   Cic2Xml.print_object uri ~ids_to_inner_sorts ~ask_dtd_to_the_getter:false
+    annobj 
+  in
+  let xmlinnertypes =
+   Cic2Xml.print_inner_types uri ~ids_to_inner_sorts ~ids_to_inner_types
+    ~ask_dtd_to_the_getter:false
+  in
+  
+  (* prepare URIs and paths *)
+  let innertypesuri = UriManager.innertypesuri_of_uri uri in
+  let bodyuri = UriManager.bodyuri_of_uri uri in
+  let innertypesfilename = Str.replace_first (Str.regexp "^cic:") ""
+        (UriManager.string_of_uri innertypesuri) ^ ".xml" in
+  let innertypespath = !basedir ^ "/" ^ innertypesfilename in
+  let xmlfilename = Str.replace_first (Str.regexp "^cic:") ""
+        (UriManager.string_of_uri uri) ^ ".xml" in
+  let xmlpath = !basedir ^ "/" ^ xmlfilename in
+  let xmlbodyfilename = Str.replace_first (Str.regexp "^cic:") ""
+        (UriManager.string_of_uri uri) ^ ".body.xml" in
+  let xmlbodypath = !basedir ^ "/" ^  xmlbodyfilename in
+  let path_scheme_of path = "file:/" ^ path in
+
+   (* now write to disk *)
+    Xml.pp ~quiet:true xmlinnertypes (Some innertypespath) ;
+    Xml.pp ~quiet:true xml (Some xmlpath) ;
+
+   (* now register to the getter *)
+    Http_getter.register' innertypesuri (path_scheme_of innertypespath); 
+    Http_getter.register' uri (path_scheme_of xmlpath);
+   
+    (* now the optional body, both write and register *)
+    (match bodyxml,bodyuri with
+       None,None -> ()
+     | Some bodyxml,Some bodyuri->
+         Xml.pp ~quiet:true bodyxml (Some xmlbodypath) ;
+         Http_getter.register' bodyuri (path_scheme_of xmlbodypath)
+     | _-> assert false) 
+;;
+
+
+
   (* TODO Zack a lot more to be done here:
     * - save object to disk in xml format
     * - register uri to the getter 
@@ -281,6 +351,7 @@ let add_constant_to_world ~(console:MatitaTypes.console)
     CicEnvironment.add_type_checked_term uri (obj, ugraph);
     MetadataDb.index_constant ~dbd
       ~owner:(Helm_registry.get "matita.owner") ~uri ~body ~ty;
+    save_object_to_disk uri obj;  
     console#echo_message (sprintf "%s constant defined" suri)
   end
 
@@ -297,6 +368,7 @@ let add_inductive_def_to_world ~(console:MatitaTypes.console)
     CicEnvironment.put_inductive_definition uri (obj, ugraph);
     MetadataDb.index_inductive_def ~dbd
       ~owner:(Helm_registry.get "matita.owner") ~uri ~types:indTypes;
+    save_object_to_disk uri obj;  
     console#echo_message (sprintf "%s inductive type defined" suri);
     let elim sort =
       try
@@ -380,8 +452,6 @@ class commandState
             (* do nothing, just for compatibility with coq syntax *)
           New_state Command
       | TacticAst.Command (TacticAst.Coercion c_ast) ->
-          prerr_endline ("beccata la coercion " ^ (CicAstPp.pp_term c_ast));
-
           let env, metasenv, coercion, ugraph = 
             disambiguator#disambiguateTermAst c_ast 
           in
@@ -424,14 +494,18 @@ class commandState
             in  
             aux ty
           in
-          let uri_of_term = function
+          let rec uri_of_term = function
             | Cic.Const(u,_) -> u
             | Cic.MutInd (u, i , _) ->
                 (* we have to build by hand the #xpointer *)
                 let base = UriManager.string_of_uri u in
                 let xp = "#xpointer(1/" ^ (string_of_int (i+1)) ^ ")" in
                   UriManager.uri_of_string (base ^ xp)
-            | _ -> assert false 
+            | Cic.Appl (he::_) -> uri_of_term he
+            | t -> 
+                prerr_endline ("Fallisco a estrarre la uri di " ^ 
+                  (CicPp.ppterm t));
+                assert false 
           in
           let ty_src,ty_tgt = extract_last_two_p coer_ty in
           let src_uri = uri_of_term ty_src in
@@ -442,12 +516,14 @@ class commandState
           (* FIXME: we should chek it this object can be a coercion 
            * maybe add the check to extract_last_two_p
            *)
+          console#echo_message (sprintf "Coercion %s"
+            (UriManager.string_of_uri coer_uri));
           List.iter (fun (uri,obj,ugraph) -> 
-            (*
-            prerr_endline (Printf.sprintf 
-             "Aggiungo la coercion %s\n%s\n\n"
-             (UriManager.string_of_uri uri) (CicPp.ppobj obj));
-            *)
+          (*  
+            console#echo_message 
+             (sprintf "Coercion (automatic) %s" 
+               (UriManager.string_of_uri uri));
+          *)
             let (name, body, ty, attrs) = split_obj obj in
             add_constant_to_world ~console 
               ~dbd ~uri ?body ~ty ~attrs ~ugraph ();