]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/matita/matitaScript.ml
ported to new syntactic requirement about terms being surrounded by parens
[helm.git] / helm / matita / matitaScript.ml
index 48cc9111bdad5c9c8511ef8f36d35ef1ee3a4145..dcb0baebf155699fd7fbddc02e4c7b8110fc717b 100644 (file)
@@ -26,8 +26,8 @@
 open Printf
 open MatitaTypes
 
-let debug = true
-let debug_print = if  debug then prerr_endline else ignore
+let debug = false
+let debug_print = if debug then prerr_endline else ignore
 
   (** raised when one of the script margins (top or bottom) is reached *)
 exception Margin
@@ -36,15 +36,16 @@ let safe_substring s i j =
   try String.sub s i j with Invalid_argument _ -> assert false
 
 let heading_nl_RE = Pcre.regexp "^\\s*\n\\s*"
+let heading_nl_RE' = Pcre.regexp "^(\\s*\n\\s*)((.|\n)*)"
 let only_dust_RE = Pcre.regexp "^(\\s|\n|%%[^\n]*\n)*$"
 let multiline_RE = Pcre.regexp "^\n[^\n]+$"
 let newline_RE = Pcre.regexp "\n"
  
 let comment str =
   if Pcre.pmatch ~rex:multiline_RE str then
-    "\n(** " ^ (Pcre.replace ~rex:newline_RE str) ^ " **)"
+    "\n(** " ^ (Pcre.replace ~rex:newline_RE str) ^ " *)"
   else
-    "\n(**\n" ^ str ^ "\n**)"
+    "\n(**\n" ^ str ^ "\n*)"
                      
 let first_line s =
   let s = Pcre.replace ~rex:heading_nl_RE s in
@@ -53,16 +54,10 @@ let first_line s =
     String.sub s 0 nl_pos
   with Not_found -> s
 
-let prepend_text header base =
-  if Pcre.pmatch ~rex:heading_nl_RE base then
-    sprintf "\n%s%s" header base
-  else
-    sprintf "\n%s\n%s" header base
-
   (** creates a statement AST for the Goal tactic, e.g. "goal 7" *)
 let goal_ast n =
   let module A = GrafiteAst in
-  let loc = Disambiguate.dummy_floc in
+  let loc = DisambiguateTypes.dummy_floc in
   A.Executable (loc, A.Tactical (loc, A.Tactic (loc, A.Goal (loc, n))))
 
 type guistuff = {
@@ -87,33 +82,43 @@ let eval_with_engine guistuff status user_goal parsed_text st =
   in
   let parsed_text_length = String.length parsed_text in
   let loc, ex = 
-    match st with TA.Executable (loc,ex) -> loc, ex | _ -> assert false 
-  in
-  let goal_changed = ref false in
-  let status =
+    match st with TA.Executable (loc,ex) -> loc, ex | _ -> assert false in
+  let initial_space,parsed_text =
+   try
+    let pieces = Pcre.extract ~rex:heading_nl_RE' parsed_text in
+     pieces.(1), pieces.(2)
+   with
+    Not_found -> "", parsed_text in
+  (* we add the goal command if needed *)
+  let inital_space,new_status,new_status_and_text_list' =
     match status.proof_status with
       | Incomplete_proof (_, goal) when goal <> user_goal ->
-          goal_changed := true;
+         let status =
           MatitaEngine.eval_ast ~include_paths:include_
-            ~do_heavy_checks:true status (goal_ast user_goal)
-      | _ -> status
-  in
+            ~do_heavy_checks:true status (goal_ast user_goal) in
+         let initial_space =
+          if initial_space = "" then "\n" else initial_space
+         in
+          "\n", status,
+           [status, initial_space ^ TAPp.pp_tactic (TA.Goal (loc, user_goal))]
+      | _ -> initial_space,status,[] in
   let new_status = 
     MatitaEngine.eval_ast 
-      ~include_paths:include_ ~do_heavy_checks:true status st 
+      ~include_paths:include_ ~do_heavy_checks:true new_status st 
   in
   let new_aliases =
     match ex with
       | TA.Command (_, TA.Alias _)
-      | TA.Command (_, TA.Include _) -> DisambiguateTypes.Environment.empty
+      | TA.Command (_, TA.Include _)
+      | TA.Command (_, TA.Interpretation _) -> []
       | _ -> MatitaSync.alias_diff ~from:status new_status
   in
   (* we remove the defined object since we consider them "automatic aliases" *)
-  let new_aliases = 
+  let initial_space,status,new_status_and_text_list_rev = 
     let module DTE = DisambiguateTypes.Environment in
     let module UM = UriManager in
-    DTE.fold (
-      fun k ((v,_) as value) acc -> 
+    List.fold_left (
+      fun (initial_space,status,acc) (k,((v,_) as value)) -> 
         let b = 
           try
             let v = UM.strip_xpointer (UM.uri_of_string v) in
@@ -121,33 +126,33 @@ let eval_with_engine guistuff status user_goal parsed_text st =
           with UM.IllFormedUri _ -> false
         in
         if b then 
-          acc
+          initial_space,status,acc
         else
-          DTE.add k value acc
-    ) new_aliases DTE.empty
-  in
-  let new_text =
-    if DisambiguateTypes.Environment.is_empty new_aliases then
-      parsed_text
-    else
-      prepend_text (DisambiguatePp.pp_environment new_aliases)
-        parsed_text
-  in
-  let new_text =
-    if !goal_changed then
-      prepend_text
-        (TAPp.pp_tactic (TA.Goal (loc, user_goal))(* ^ "\n"*))
-        new_text
-    else
-      new_text
+         let new_text =
+          let initial_space =
+           if initial_space = "" then "\n" else initial_space in
+            initial_space ^
+             DisambiguatePp.pp_environment
+              (DisambiguateTypes.Environment.add k value
+                DisambiguateTypes.Environment.empty) in
+         let new_status =
+          MatitaSync.set_proof_aliases status [k,value]
+         in
+          "\n",new_status,((new_status, new_text)::acc)
+    ) (initial_space,status,[]) new_aliases in
+  let parsed_text = initial_space ^ parsed_text in
+  let res =
+   List.rev new_status_and_text_list_rev @ new_status_and_text_list' @
+    [new_status, parsed_text]
   in
-    [ new_status, new_text ], parsed_text_length
+   res,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 ->
+  | MatitaEngine.UnableToInclude what 
+  | MatitaEngine.IncludedFileNotCompiled what as exc ->
       let compile_needed_and_go_on d =
         let target = what in
         let refresh_cb () = 
@@ -171,11 +176,11 @@ let eval_with_engine guistuff status user_goal parsed_text st =
         | `NO -> raise exc
         | `CANCEL -> do_nothing ())
       in
-      let handle_withoud_devel filename =
+      let handle_without_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" ^
+         "All dependencies are automatically solved for a development.\n\n" ^
          "<i>Do you want to set up a development?</i>"
         in
         (match guistuff.ask_confirmation ~title ~message with
@@ -189,11 +194,11 @@ let eval_with_engine guistuff status user_goal parsed_text st =
         | `CANCEL -> do_nothing())
       in
       match guistuff.filenamedata with
-      | None,None -> handle_withoud_devel None
+      | None,None -> handle_without_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)
+          | None -> handle_without_devel (Some f)
           | Some d -> handle_with_devel d
 ;;
 
@@ -202,14 +207,14 @@ let disambiguate term status =
   let dbd = MatitaDb.instance () in
   let metasenv = MatitaMisc.get_proof_metasenv status in
   let context = MatitaMisc.get_proof_context status in
-  let aliases = MatitaMisc.get_proof_aliases status in
-  let interps = MD.disambiguate_term dbd context metasenv aliases term in
+  let interps =
+   MD.disambiguate_term ~dbd ~context ~metasenv ~aliases:status.aliases
+    ~universe:(Some status.multi_aliases) term in
   match interps with 
-  | [_,_,x,_] -> x
+  | [_,_,x,_], _ -> x
   | _ -> assert false
  
-let eval_macro guistuff status parsed_text script mac
-=
+let eval_macro guistuff status unparsed_text parsed_text script mac =
   let module TA = GrafiteAst in
   let module TAPp = GrafiteAstPp in
   let module MQ = MetadataQuery in
@@ -225,7 +230,11 @@ let eval_macro guistuff status parsed_text script mac
   | TA.WMatch (loc, term) -> 
       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
+      let query_url =
+        MatitaMisc.strip_suffix ~suffix:"."
+          (HExtlib.trim_blanks unparsed_text)
+      in
+      let entry = `Whelp (query_url, l) in
       guistuff.mathviewer#show_uri_list ~reuse:true ~entry l;
       [], parsed_text_length
   | TA.WInstance (loc, term) ->
@@ -287,14 +296,13 @@ let eval_macro guistuff status parsed_text script mac
   | TA.Check (_,term) ->
       let metasenv = MatitaMisc.get_proof_metasenv status in
       let context = MatitaMisc.get_proof_context status in
-      let aliases = MatitaMisc.get_proof_aliases status in
       let interps = 
-        MatitaDisambiguator.disambiguate_term 
-          dbd context metasenv aliases term 
+        MatitaDisambiguator.disambiguate_term ~dbd ~context ~metasenv
+         ~aliases:status.aliases ~universe:(Some status.multi_aliases) term
       in
       let _, metasenv , term, ugraph =
         match interps with 
-        | [x] -> x
+        | [x], _ -> x
         | _ -> assert false
       in
       let ty,_ = CTC.type_of_aux' metasenv context term ugraph in
@@ -324,7 +332,9 @@ let eval_macro guistuff status parsed_text script mac
   | TA.Search_term (_, search_kind, term) -> failwith "not implemented"
 
                                 
-let eval_executable guistuff status user_goal parsed_text script ex =
+let eval_executable guistuff status user_goal unparsed_text parsed_text script
+  ex
+=
   let module TA = GrafiteAst in
   let module TAPp = GrafiteAstPp in
   let module MD = MatitaDisambiguator in
@@ -352,15 +362,15 @@ let eval_executable guistuff status user_goal parsed_text script ex =
           guistuff status user_goal parsed_text (TA.Executable (loc, ex))
       with MatitaTypes.Cancel -> [], 0)
   | TA.Macro (_,mac) ->
-      eval_macro guistuff status parsed_text script mac
+      eval_macro guistuff status unparsed_text parsed_text script mac
 
 let rec eval_statement baseoffset parsedlen error_tag (buffer : GText.buffer)
- guistuff status user_goal script s
+ guistuff status user_goal script unparsed_text
 =
-  if Pcre.pmatch ~rex:only_dust_RE s then raise Margin;
+  if Pcre.pmatch ~rex:only_dust_RE unparsed_text then raise Margin;
   let st =
    try
-    GrafiteParser.parse_statement (Stream.of_string s)
+    GrafiteParser.parse_statement (Ulexing.from_utf8_string unparsed_text)
    with
     CicNotationParser.Parse_error (floc,err) as exc ->
      let (x, y) = CicNotationPt.loc_of_floc floc in
@@ -390,14 +400,14 @@ let rec eval_statement baseoffset parsedlen error_tag (buffer : GText.buffer)
   in
   let text_of_loc loc =
     let parsed_text_length = snd (CicNotationPt.loc_of_floc loc) in
-    let parsed_text = safe_substring s 0 parsed_text_length in
+    let parsed_text = safe_substring unparsed_text 0 parsed_text_length in
     parsed_text, parsed_text_length
   in
   match st with
-  | GrafiteAst.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 remain_len = String.length unparsed_text - parsed_text_length in
+      let s = String.sub unparsed_text parsed_text_length remain_len in
       let s,len = 
         eval_statement baseoffset (parsedlen + parsed_text_length) error_tag
          buffer guistuff status user_goal script s 
@@ -408,13 +418,14 @@ let rec eval_statement baseoffset parsedlen error_tag (buffer : GText.buffer)
       | [] -> [], 0)
   | GrafiteAst.Executable (loc, ex) ->
       let parsed_text, parsed_text_length = text_of_loc loc in
-      eval_executable guistuff  status user_goal parsed_text script ex 
+      eval_executable guistuff status user_goal unparsed_text parsed_text
+        script ex 
   
 let fresh_script_id =
   let i = ref 0 in
   fun () -> incr i; !i
 
-class script  ~(view: GText.view)
+class script  ~(source_view: GSourceView.source_view)
               ~(init: MatitaTypes.status) 
               ~(mathviewer: MatitaTypes.mathViewer) 
               ~set_star
@@ -422,7 +433,8 @@ class script  ~(view: GText.view)
               ~urichooser 
               ~develcreator 
               () =
-let buffer = view#buffer in
+let buffer = source_view#buffer in
+let source_buffer = source_view#source_buffer in
 object (self)
   val scriptId = fresh_script_id ()
   
@@ -442,13 +454,10 @@ object (self)
     | None,_ -> sprintf ".unnamed%d.ma" scriptId
   
   initializer 
-    ignore(GMain.Timeout.add ~ms:300000 
-       ~callback:(fun _ -> self#_saveToBackuptFile ();true));
-    ignore(buffer#connect#modified_changed 
-       (fun _ -> if buffer#modified then 
-          set_star self#ppFilename true 
-        else 
-          set_star self#ppFilename false))
+    ignore (GMain.Timeout.add ~ms:300000 
+       ~callback:(fun _ -> self#_saveToBackupFile ();true));
+    ignore (buffer#connect#modified_changed 
+      (fun _ -> set_star (Filename.basename self#ppFilename) buffer#modified))
 
   val mutable statements = [];    (** executed statements *)
   val mutable history = [ init ];
@@ -552,10 +561,10 @@ object (self)
       | _ -> ()
     end ;
     let mark_position = buffer#get_iter_at_mark mark in
-    if view#move_mark_onscreen mark then
+    if source_view#move_mark_onscreen mark then
      begin
       buffer#move_mark mark mark_position;
-      view#scroll_to_mark ~use_align:true ~xalign:1.0 ~yalign:0.1 mark;
+      source_view#scroll_to_mark ~use_align:true ~xalign:1.0 ~yalign:0.1 mark;
      end;
     while Glib.Main.pending () do ignore(Glib.Main.iteration false); done
 
@@ -574,8 +583,8 @@ object (self)
     List.iter (fun o -> o status) observers
 
   method loadFromFile f =
-    buffer#set_text (MatitaMisc.input_file f);
-    self#goto_top;
+    buffer#set_text (HExtlib.input_file f);
+    self#reset_buffer;
     buffer#set_modified false
     
   method assignFileName file =
@@ -590,7 +599,7 @@ object (self)
     close_out oc;
     buffer#set_modified false
   
-  method private _saveToBackuptFile () =
+  method private _saveToBackupFile () =
     if buffer#modified then
       begin
         let f = self#ppFilename ^ "~" in
@@ -602,26 +611,30 @@ object (self)
       end
   
   method private goto_top =
-    MatitaSync.time_travel ~present:self#status ~past:init;
+    MatitaSync.time_travel ~present:self#status ~past:init
+
+  method private reset_buffer = 
     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;
+    self#reset_buffer;
+    source_buffer#begin_not_undoable_action ();
     buffer#delete ~start:buffer#start_iter ~stop:buffer#end_iter;
-    self#notify;
+    source_buffer#end_not_undoable_action ();
     buffer#set_modified false
-
+  
   method template () =
-    let template = MatitaMisc.input_file BuildTimeConf.script_template in 
+    let template = HExtlib.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
+    set_star (Filename.basename self#ppFilename) false
 
   method goto (pos: [`Top | `Bottom | `Cursor]) () =
     let old_locked_mark =
@@ -632,7 +645,11 @@ object (self)
     let getoldpos _ = buffer#get_iter_at_mark old_locked_mark in 
     let dispose_old_locked_mark () = buffer#delete_mark old_locked_mark in
     match pos with
-    | `Top -> dispose_old_locked_mark (); self#goto_top; self#notify
+    | `Top -> 
+        dispose_old_locked_mark (); 
+        self#goto_top; 
+        self#reset_buffer;
+        self#notify
     | `Bottom ->
         (try 
           let rec dowhile () =
@@ -707,13 +724,14 @@ object (self)
   method proofStatus = MatitaMisc.get_proof_status self#status
   method proofMetasenv = MatitaMisc.get_proof_metasenv self#status
   method proofContext = MatitaMisc.get_proof_context self#status
+  method proofConclusion = MatitaMisc.get_proof_conclusion 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
+      let st = GrafiteParser.parse_statement (Ulexing.from_utf8_string s) in
       match st with
       | GrafiteAst.Comment (loc,_)-> 
           let parsed_text_length = snd (CicNotationPt.loc_of_floc loc) in
@@ -745,10 +763,10 @@ end
 
 let _script = ref None
 
-let script ~view ~init ~mathviewer ~urichooser ~develcreator ~ask_confirmation ~set_star ()
+let script ~source_view ~init ~mathviewer ~urichooser ~develcreator ~ask_confirmation ~set_star ()
 =
   let s = new script 
-    ~view ~init ~mathviewer ~ask_confirmation ~urichooser ~develcreator ~set_star () 
+    ~source_view ~init ~mathviewer ~ask_confirmation ~urichooser ~develcreator ~set_star () 
   in
   _script := Some s;
   s