]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/matita/matitaScript.ml
compilation of needed modules now outputs to the log window
[helm.git] / helm / matita / matitaScript.ml
index 9ca48d9cab897d2dc4f996f6a0c3d48a56f4ba2d..e31dd7a1540e5642fde6d525bad6f4d1aac10a3f 100644 (file)
@@ -61,13 +61,30 @@ let prepend_text header base =
 
   (** creates a statement AST for the Goal tactic, e.g. "goal 7" *)
 let goal_ast n =
-  let module A = TacticAst in
-  let loc = CicAst.dummy_floc in
+  let module A = GrafiteAst in
+  let loc = Disambiguate.dummy_floc in
   A.Executable (loc, A.Tactical (loc, A.Tactic (loc, A.Goal (loc, n))))
 
-let eval_with_engine status user_goal parsed_text st =
-  let module TA = TacticAst in
-  let module TAPp = TacticAstPp in
+type guistuff = {
+  mathviewer:MatitaTypes.mathViewer;
+  urichooser: UriManager.uri list -> UriManager.uri list;
+  ask_confirmation: title:string -> message:string -> [`YES | `NO | `CANCEL];
+  develcreator: containing:string option -> unit;
+  mutable filenamedata: string option * MatitamakeLib.development option
+}
+
+let eval_with_engine guistuff status user_goal parsed_text st =
+  let module TA = GrafiteAst in
+  let module TAPp = GrafiteAstPp in
+  let include_ = 
+    match guistuff.filenamedata with
+    | None,None -> []
+    | None,Some devel -> [MatitamakeLib.root_for_development devel ]
+    | Some f,_ -> 
+        match MatitamakeLib.development_for_dir (Filename.dirname f) with
+        | None -> []
+        | Some devel -> [MatitamakeLib.root_for_development devel ]
+  in
   let parsed_text_length = String.length parsed_text in
   let loc, ex = 
     match st with TA.Executable (loc,ex) -> loc, ex | _ -> assert false 
@@ -77,10 +94,14 @@ let eval_with_engine status user_goal parsed_text st =
     match status.proof_status with
       | Incomplete_proof (_, goal) when goal <> user_goal ->
           goal_changed := true;
-          MatitaEngine.eval_ast status (goal_ast user_goal)
+          MatitaEngine.eval_ast ~include_paths:include_
+            ~do_heavy_checks:true status (goal_ast user_goal)
       | _ -> status
   in
-  let new_status = MatitaEngine.eval_ast status st in
+  let new_status = 
+    MatitaEngine.eval_ast 
+      ~include_paths:include_ ~do_heavy_checks:true status st 
+  in
   let new_aliases =
     match ex with
       | TA.Command (_, TA.Alias _)
@@ -109,7 +130,7 @@ let eval_with_engine status user_goal parsed_text st =
     if DisambiguateTypes.Environment.is_empty new_aliases then
       parsed_text
     else
-      prepend_text (CicTextualParser2.EnvironmentP3.to_string new_aliases)
+      prepend_text (DisambiguatePp.pp_environment new_aliases)
         parsed_text
   in
   let new_text =
@@ -122,6 +143,61 @@ let eval_with_engine status user_goal parsed_text st =
   in
     [ new_status, new_text ], parsed_text_length
 
+let eval_with_engine guistuff status user_goal parsed_text st =
+  try
+    eval_with_engine guistuff status user_goal parsed_text st
+  with
+    MatitaEngine.UnableToInclude what as exc ->
+      let compile_needed_and_go_on d =
+        let root = MatitamakeLib.root_for_development d in
+        let target = root ^ "/" ^ what in
+        let refresh_cb () = 
+          while Glib.Main.pending () do ignore(Glib.Main.iteration false); done
+        in
+        if not(MatitamakeLib.build_development_in_bg ~target refresh_cb d) then
+          raise exc
+        else
+          eval_with_engine guistuff status user_goal parsed_text st
+      in
+      let do_nothing () = [], 0 in
+      let handle_with_devel d =
+        let name = MatitamakeLib.name_for_development d in
+        let title = "Unable to include " ^ what in
+        let message = 
+          what ^ " is handled by development <b>" ^ name ^ "</b>.\n\n" ^
+          "<i>Should I compile it and Its dependencies?</i>"
+        in
+        (match guistuff.ask_confirmation ~title ~message with
+        | `YES -> compile_needed_and_go_on d
+        | `NO -> raise exc
+        | `CANCEL -> do_nothing ())
+      in
+      let handle_withoud_devel filename =
+        let title = "Unable to include " ^ what in
+        let message = 
+         what ^ " is <b>not</b> handled by a development.\n" ^
+         "All dependencies are authomatically solved for a development.\n\n" ^
+         "<i>Do you want to set up a development?</i>"
+        in
+        (match guistuff.ask_confirmation ~title ~message with
+        | `YES -> 
+            (match filename with
+            | Some f -> 
+                guistuff.develcreator ~containing:(Some (Filename.dirname f))
+            | None -> guistuff.develcreator ~containing:None);
+            do_nothing ()
+        | `NO -> raise exc
+        | `CANCEL -> do_nothing())
+      in
+      match guistuff.filenamedata with
+      | None,None -> handle_withoud_devel None
+      | None,Some d -> handle_with_devel d
+      | Some f,_ ->
+          match MatitamakeLib.development_for_dir (Filename.dirname f) with
+          | None -> handle_withoud_devel (Some f)
+          | Some d -> handle_with_devel d
+;;
+
 let disambiguate term status =
   let module MD = MatitaDisambiguator in
   let dbd = MatitaDb.instance () in
@@ -133,11 +209,10 @@ let disambiguate term status =
   | [_,_,x,_] -> x
   | _ -> assert false
  
-let eval_macro status (mathviewer:MatitaTypes.mathViewer) urichooser
- parsed_text script mac
+let eval_macro guistuff status parsed_text script mac
 =
-  let module TA = TacticAst in
-  let module TAPp = TacticAstPp in
+  let module TA = GrafiteAst in
+  let module TAPp = GrafiteAstPp in
   let module MQ = MetadataQuery in
   let module MDB = MatitaDb in
   let module CTC = CicTypeChecker in
@@ -152,18 +227,18 @@ let eval_macro status (mathviewer:MatitaTypes.mathViewer) urichooser
       let term = disambiguate term status in
       let l =  MQ.match_term ~dbd term in
       let entry = `Whelp (TAPp.pp_macro_cic (TA.WMatch (loc, term)), l) in
-      mathviewer#show_uri_list ~reuse:true ~entry l;
+      guistuff.mathviewer#show_uri_list ~reuse:true ~entry l;
       [], parsed_text_length
   | TA.WInstance (loc, term) ->
       let term = disambiguate term status in
       let l = MQ.instance ~dbd term in
       let entry = `Whelp (TAPp.pp_macro_cic (TA.WInstance (loc, term)), l) in
-      mathviewer#show_uri_list ~reuse:true ~entry l;
+      guistuff.mathviewer#show_uri_list ~reuse:true ~entry l;
       [], parsed_text_length
   | TA.WLocate (loc, s) -> 
       let l = MQ.locate ~dbd s in
       let entry = `Whelp (TAPp.pp_macro_cic (TA.WLocate (loc, s)), l) in
-      mathviewer#show_uri_list ~reuse:true ~entry l;
+      guistuff.mathviewer#show_uri_list ~reuse:true ~entry l;
       [], parsed_text_length
   | TA.WElim (loc, term) ->
       let term = disambiguate term status in
@@ -174,20 +249,20 @@ let eval_macro status (mathviewer:MatitaTypes.mathViewer) urichooser
       in
       let l = MQ.elim ~dbd uri in
       let entry = `Whelp (TAPp.pp_macro_cic (TA.WElim (loc, term)), l) in
-      mathviewer#show_uri_list ~reuse:true ~entry l;
+      guistuff.mathviewer#show_uri_list ~reuse:true ~entry l;
       [], parsed_text_length
   | TA.WHint (loc, term) ->
       let term = disambiguate term status in
       let s = ((None,[0,[],term], Cic.Meta (0,[]) ,term),0) in
       let l = List.map fst (MQ.experimental_hint ~dbd s) in
       let entry = `Whelp (TAPp.pp_macro_cic (TA.WHint (loc, term)), l) in
-      mathviewer#show_uri_list ~reuse:true ~entry l;
+      guistuff.mathviewer#show_uri_list ~reuse:true ~entry l;
       [], parsed_text_length
   (* REAL macro *)
   | TA.Hint loc -> 
       let s = MatitaMisc.get_proof_status status in
       let l = List.map fst (MQ.experimental_hint ~dbd s) in
-      let selected = urichooser l in
+      let selected = guistuff.urichooser l in
       (match selected with
       | [] -> [], parsed_text_length
       | [uri] -> 
@@ -195,7 +270,7 @@ let eval_macro status (mathviewer:MatitaTypes.mathViewer) urichooser
          TA.Executable (loc,
           (TA.Tactical (loc, 
             TA.Tactic (loc,
-             TA.Apply (loc, CicAst.Uri (UriManager.string_of_uri uri,None))))))
+             TA.Apply (loc, CicNotationPt.Uri (UriManager.string_of_uri uri,None))))))
         in
         let new_status = MatitaEngine.eval_ast status ast in
         let extra_text = 
@@ -225,7 +300,7 @@ let eval_macro status (mathviewer:MatitaTypes.mathViewer) urichooser
       in
       let ty,_ = CTC.type_of_aux' metasenv context term ugraph in
       let t_and_ty = Cic.Cast (term,ty) in
-      mathviewer#show_entry (`Cic (t_and_ty,metasenv));
+      guistuff.mathviewer#show_entry (`Cic (t_and_ty,metasenv));
       [], parsed_text_length
 (*   | TA.Abort _ -> 
       let rec go_back () =
@@ -250,45 +325,59 @@ let eval_macro status (mathviewer:MatitaTypes.mathViewer) urichooser
   | TA.Search_term (_, search_kind, term) -> failwith "not implemented"
 
                                 
-let eval_executable status (mathviewer:MatitaTypes.mathViewer) urichooser
-user_goal parsed_text script ex =
-  let module TA = TacticAst in
-  let module TAPp = TacticAstPp in
+let eval_executable guistuff status user_goal parsed_text script ex =
+  let module TA = GrafiteAst in
+  let module TAPp = GrafiteAstPp in
   let module MD = MatitaDisambiguator in
+  let module ML = MatitacleanLib in
   let parsed_text_length = String.length parsed_text in
   match ex with
   | TA.Command (loc, _) | TA.Tactical (loc, _) ->
-      eval_with_engine status user_goal parsed_text
-       (TA.Executable (loc, ex))
+      (try 
+        (match ML.baseuri_of_baseuri_decl (TA.Executable (loc,ex)) with
+        | None -> ()
+        | Some u -> 
+            if not (MatitacleanLib.is_empty u) then
+              match 
+                guistuff.ask_confirmation 
+                  ~title:"Baseuri redefinition" 
+                  ~message:(
+                    "Baseuri " ^ u ^ " already exists.\n" ^
+                    "Do you want to redefine the corresponding "^
+                    "part of the library?")
+              with
+              | `YES -> MatitacleanLib.clean_baseuris [u]
+              | `NO -> ()
+              | `CANCEL -> raise MatitaTypes.Cancel);
+        eval_with_engine 
+          guistuff status user_goal parsed_text (TA.Executable (loc, ex))
+      with MatitaTypes.Cancel -> [], 0)
   | TA.Macro (_,mac) ->
-      eval_macro status mathviewer urichooser parsed_text script mac
+      eval_macro guistuff status parsed_text script mac
 
-let rec eval_statement status (mathviewer:MatitaTypes.mathViewer)
- urichooser user_goal script s
-=
+let rec eval_statement guistuff status user_goal script s =
   if Pcre.pmatch ~rex:only_dust_RE s then raise Margin;
-  let st = CicTextualParser2.parse_statement (Stream.of_string s) in
+  let st = GrafiteParser.parse_statement (Stream.of_string s) in
   let text_of_loc loc =
-    let parsed_text_length = snd (CicAst.loc_of_floc loc) in
+    let parsed_text_length = snd (CicNotationPt.loc_of_floc loc) in
     let parsed_text = safe_substring s 0 parsed_text_length in
     parsed_text, parsed_text_length
   in
   match st with
-  | TacticAst.Comment (loc,_)-> 
+  | GrafiteAst.Comment (loc,_)-> 
       let parsed_text, parsed_text_length = text_of_loc loc in
       let remain_len = String.length s - parsed_text_length in
       let s = String.sub s parsed_text_length remain_len in
       let s,len = 
-        eval_statement status mathviewer urichooser user_goal script s 
+        eval_statement guistuff status user_goal script s 
       in
       (match s with
       | (status, text) :: tl ->
         ((status, parsed_text ^ text)::tl), (parsed_text_length + len)
       | [] -> [], 0)
-  | TacticAst.Executable (loc, ex) ->
+  | GrafiteAst.Executable (loc, ex) ->
       let parsed_text, parsed_text_length = text_of_loc loc in
-       eval_executable status mathviewer urichooser user_goal
-        parsed_text script ex
+      eval_executable guistuff  status user_goal parsed_text script ex 
   
 let fresh_script_id =
   let i = ref 0 in
@@ -297,25 +386,38 @@ let fresh_script_id =
 class script ~(buffer: GText.buffer) ~(init: MatitaTypes.status) 
               ~(mathviewer: MatitaTypes.mathViewer) 
               ~set_star
-              ~urichooser () =
+              ~ask_confirmation
+              ~urichooser 
+              ~develcreator 
+              () =
 object (self)
-  val mutable filename = None
   val scriptId = fresh_script_id ()
+  
+  val guistuff = {
+    mathviewer = mathviewer;
+    urichooser = urichooser;
+    ask_confirmation = ask_confirmation;
+    develcreator = develcreator;
+    filenamedata = (None, None)} 
+  
   method private getFilename =
-    match filename with Some f -> f | _ -> assert false
+    match guistuff.filenamedata with Some f,_ -> f | _ -> assert false
+    
   method private ppFilename =
-    match filename with Some f -> f | None -> sprintf ".unnamed%d.ma" scriptId
+    match guistuff.filenamedata with 
+    | Some f,_ -> f 
+    | None,_ -> sprintf ".unnamed%d.ma" scriptId
   
   initializer 
-    ignore(GMain.Timeout.add ~ms:30000 
+    ignore(GMain.Timeout.add ~ms:300000 
        ~callback:(fun _ -> self#_saveToBackuptFile ();true));
-    set_star self#ppFilename false;
     ignore(buffer#connect#modified_changed 
        (fun _ -> if buffer#modified then 
           set_star self#ppFilename true 
         else 
           set_star self#ppFilename false));
-    self#reset ()
+    self#reset ();
+    self#template ()
 
   val mutable statements = [];    (** executed statements *)
   val mutable history = [ init ];
@@ -327,7 +429,6 @@ object (self)
   (** goal as seen by the user (i.e. metano corresponding to current tab) *)
   val mutable userGoal = ~-1
 
-
   (** text mark and tag representing locked part of a script *)
   val locked_mark =
     buffer#create_mark ~name:"locked" ~left_gravity:true buffer#start_iter
@@ -341,7 +442,8 @@ object (self)
     let s = match statement with Some s -> s | None -> self#getFuture in
     MatitaLog.debug ("evaluating: " ^ first_line s ^ " ...");
     let (entries, parsed_len) = 
-      eval_statement self#status mathviewer urichooser userGoal self s in
+      eval_statement guistuff self#status userGoal self s
+    in
     let (new_statuses, new_statements) = List.split entries in
 (*
 prerr_endline "evalStatement returned";
@@ -373,15 +475,25 @@ List.iter (fun s -> prerr_endline ("'" ^ s ^ "'")) new_statements;
 
   method advance ?statement () =
     try
-      self#_advance ?statement ()
-    with Margin -> ()
+      self#_advance ?statement ();
+      self#notify
+    with 
+    | Margin -> self#notify
+    | exc -> self#notify; raise exc
 
-  method retract () = try self#_retract () with Margin -> ()
+  method retract () =
+    try
+      self#_retract ();
+      self#notify
+    with 
+    | Margin -> self#notify
+    | exc -> self#notify; raise exc
 
   method private getFuture =
     buffer#get_text ~start:(buffer#get_iter_at_mark (`MARK locked_mark))
       ~stop:buffer#end_iter ()
 
+      
   (** @param rel_offset relative offset from current position of locked_mark *)
   method private moveMark rel_offset =
     let mark = `MARK locked_mark in
@@ -397,7 +509,17 @@ List.iter (fun s -> prerr_endline ("'" ^ s ^ "'")) new_statements;
     buffer#move_mark mark ~where:new_mark_pos;
     buffer#apply_tag locked_tag ~start:buffer#start_iter ~stop:new_mark_pos;
     buffer#move_mark `INSERT old_insert;
-    self#notify
+    begin
+     match self#status.proof_status with
+        Incomplete_proof (_,goal) -> self#setGoal goal
+      | _ -> ()
+    end ;
+    while Glib.Main.pending () do ignore(Glib.Main.iteration false); done
+
+  method clean_dirty_lock =
+    let lock_mark_iter = buffer#get_iter_at_mark (`MARK locked_mark) in
+    buffer#remove_tag locked_tag ~start:buffer#start_iter ~stop:buffer#end_iter;
+    buffer#apply_tag locked_tag ~start:buffer#start_iter ~stop:lock_mark_iter
 
   val mutable observers = []
 
@@ -414,7 +536,9 @@ List.iter (fun s -> prerr_endline ("'" ^ s ^ "'")) new_statements;
     buffer#set_modified false
     
   method assignFileName file =
-    filename <- Some file;
+    let abspath = MatitaMisc.absolute_path file in
+    let devel = MatitamakeLib.development_for_dir (Filename.dirname abspath) in
+    guistuff.filenamedata <- Some abspath, devel
     
   method saveToFile () =
     let oc = open_out self#getFilename in
@@ -439,26 +563,51 @@ List.iter (fun s -> prerr_endline ("'" ^ s ^ "'")) new_statements;
     statements <- [];
     history <- [ init ];
     userGoal <- ~-1;
-    self#notify;
     buffer#remove_tag locked_tag ~start:buffer#start_iter ~stop:buffer#end_iter;
     buffer#move_mark (`MARK locked_mark) ~where:buffer#start_iter
 
   method reset () =
     self#goto_top;
-    buffer#delete ~start:buffer#start_iter ~stop:buffer#end_iter
+    buffer#delete ~start:buffer#start_iter ~stop:buffer#end_iter;
+    self#notify;
+    buffer#set_modified false
+
+  method template () =
+    let template = MatitaMisc.input_file BuildTimeConf.script_template in 
+    buffer#insert ~iter:(buffer#get_iter `START) template;
+    guistuff.filenamedata <- 
+      (None,MatitamakeLib.development_for_dir (Unix.getcwd ()));
+    buffer#set_modified false;
+    set_star self#ppFilename false
 
   method goto (pos: [`Top | `Bottom | `Cursor]) () =
+    let getpos _ = buffer#get_iter_at_mark (`MARK locked_mark) in 
     match pos with
-    | `Top -> self#goto_top
+    | `Top -> self#goto_top; self#notify
     | `Bottom ->
-        (try while true do self#_advance () done with Margin -> ())
+        (try 
+          let rec dowhile pos =
+            self#_advance ();
+            if pos#compare (getpos ()) < 0 then
+              dowhile (getpos ())
+          in
+          dowhile (getpos ());
+          self#notify 
+        with 
+        | Margin -> self#notify
+        | exc -> self#notify; raise exc)
     | `Cursor ->
         let locked_iter () = buffer#get_iter_at_mark (`NAME "locked") in
         let cursor_iter () = buffer#get_iter_at_mark `INSERT in
-        let rec forward_until_cursor () = (* go forward until locked > cursor *)
-          self#_advance ();
-          if (locked_iter ())#compare (cursor_iter ()) < 0 then
-            forward_until_cursor ()
+        let forward_until_cursor () = (* go forward until locked > cursor *)
+          let rec aux oldpos =
+            self#_advance ();
+            if (locked_iter ())#compare (cursor_iter ()) < 0 &&
+               oldpos#compare (getpos ()) < 0 
+            then
+              aux (getpos ())
+          in
+          aux (getpos ())
         in
         let rec back_until_cursor () = (* go backward until locked < cursor *)
           self#_retract ();
@@ -468,13 +617,15 @@ List.iter (fun s -> prerr_endline ("'" ^ s ^ "'")) new_statements;
         let cmp = (locked_iter ())#compare (cursor_iter ()) in
         (try
           if cmp < 0 then       (* locked < cursor *)
-            forward_until_cursor ()
+            (forward_until_cursor (); self#notify)
           else if cmp > 0 then  (* locked > cursor *)
-            back_until_cursor ()
+            (back_until_cursor (); self#notify)
           else                  (* cursor = locked *)
               ()
-        with Margin -> ())
-
+        with 
+        | Margin -> self#notify
+        | exc -> self#notify; raise exc)
+              
   method onGoingProof () =
     match self#status.proof_status with
     | No_proof | Proof _ -> false
@@ -486,6 +637,27 @@ List.iter (fun s -> prerr_endline ("'" ^ s ^ "'")) new_statements;
   method proofContext = MatitaMisc.get_proof_context self#status
   method setGoal n = userGoal <- n
 
+  method eos = 
+    let s = self#getFuture in
+    let rec is_there_and_executable s = 
+      if Pcre.pmatch ~rex:only_dust_RE s then raise Margin;
+      let st = GrafiteParser.parse_statement (Stream.of_string s) in
+      match st with
+      | GrafiteAst.Comment (loc,_)-> 
+          let parsed_text_length = snd (CicNotationPt.loc_of_floc loc) in
+          let remain_len = String.length s - parsed_text_length in
+          let next = String.sub s parsed_text_length remain_len in
+          is_there_and_executable next
+      | GrafiteAst.Executable (loc, ex) -> false
+    in
+    try
+      is_there_and_executable s
+    with 
+    | CicNotationParser.Parse_error _ -> false
+    | Margin -> true
+      
+    
+    
   (* debug *)
   method dump () =
     MatitaLog.debug "script status:";
@@ -493,14 +665,19 @@ List.iter (fun s -> prerr_endline ("'" ^ s ^ "'")) new_statements;
     MatitaLog.debug (sprintf "%d statements:" (List.length statements));
     List.iter MatitaLog.debug statements;
     MatitaLog.debug ("Current file name: " ^
-      (match filename with None -> "[ no name ]" | Some f -> f));
+      (match guistuff.filenamedata with 
+      |None,_ -> "[ no name ]" 
+      | Some f,_ -> f));
 
 end
 
 let _script = ref None
 
-let script ~buffer ~init ~mathviewer ~urichooser ~set_star () =
-  let s = new script ~buffer ~init ~mathviewer ~urichooser ~set_star () in
+let script ~buffer ~init ~mathviewer ~urichooser ~develcreator ~ask_confirmation ~set_star ()
+=
+  let s = new script 
+    ~buffer ~init ~mathviewer ~ask_confirmation ~urichooser ~develcreator ~set_star () 
+  in
   _script := Some s;
   s