]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/software/matita/matitaGui.ml
Estatus finally merged into the global status using inheritance.
[helm.git] / helm / software / matita / matitaGui.ml
index 5bab5ab0ab4dcad44763fca84578cbe89c966ea8..8b38950bb67d6b6ef6922e04cfbcef3b51a2c9c2 100644 (file)
@@ -33,6 +33,8 @@ open MatitaMisc
 
 exception Found of int
 
+let all_disambiguation_passes = ref false
+
 let gui_instance = ref None
 
 class type browserWin =
@@ -40,7 +42,7 @@ class type browserWin =
    * lablgladecc :-(((( *)
 object
   inherit MatitaGeneratedGui.browserWin
-  method browserUri: GEdit.combo_box_entry
+  method browserUri: GEdit.entry
 end
 
 class console ~(buffer: GText.buffer) () =
@@ -56,6 +58,7 @@ class console ~(buffer: GText.buffer) () =
     method clear () =
       buffer#delete ~start:buffer#start_iter ~stop:buffer#end_iter
     method log_callback (tag: HLog.log_tag) s =
+      let s = Pcre.replace ~pat:"\e\\[0;3.m([^\e]+)\e\\[0m" ~templ:"$1" s in
       match tag with
       | `Debug -> self#debug (s ^ "\n")
       | `Error -> self#error (s ^ "\n")
@@ -64,58 +67,31 @@ class console ~(buffer: GText.buffer) () =
   end
         
 let clean_current_baseuri grafite_status = 
-    try  
-      let baseuri = GrafiteTypes.get_string_option grafite_status "baseuri" in
-      LibraryClean.clean_baseuris [baseuri]
-    with GrafiteTypes.Option_error _ -> ()
+  LibraryClean.clean_baseuris [grafite_status#baseuri]
 
-let ask_and_save_moo_if_needed parent fname lexicon_status grafite_status = 
-  let baseuri =
-   try Some (GrafiteTypes.get_string_option grafite_status "baseuri")
-   with GrafiteTypes.Option_error _ -> None
+let save_moo grafite_status = 
+  let script = MatitaScript.current () in
+  let baseuri = grafite_status#baseuri in
+  let no_pstatus = 
+    grafite_status#proof_status = GrafiteTypes.No_proof 
   in
-  if (MatitaScript.current ())#eos &&
-     grafite_status.GrafiteTypes.proof_status = GrafiteTypes.No_proof &&
-     baseuri <> None
-  then
-   begin
-    let baseuri = match baseuri with Some b -> b | None -> assert false in
-    let moo_fname = 
-     LibraryMisc.obj_file_of_baseuri ~must_exist:false ~baseuri
-      ~writable:true in
-    let save () =
-      let lexicon_fname =
+  match script#bos, script#eos, no_pstatus with
+  | true, _, _ -> ()
+  | _, true, true ->
+     let moo_fname = 
+       LibraryMisc.obj_file_of_baseuri ~must_exist:false ~baseuri
+        ~writable:true in
+     let lexicon_fname =
        LibraryMisc.lexicon_file_of_baseuri 
          ~must_exist:false ~baseuri ~writable:true
-      in
-       GrafiteMarshal.save_moo moo_fname
-        grafite_status.GrafiteTypes.moo_content_rev;
-       LexiconMarshal.save_lexicon lexicon_fname
-        lexicon_status.LexiconEngine.lexicon_content_rev
-    in
-     begin
-       let rc = 
-         MatitaGtkMisc.ask_confirmation
-         ~title:"A .moo can be generated"
-         ~message:(Printf.sprintf 
-           "%s can be generated for %s.\n<i>Should I generate it?</i>"
-           (Filename.basename moo_fname) (Filename.basename fname))
-         ~parent ()
-       in
-       let b = 
-         match rc with 
-         | `YES -> true 
-         | `NO -> false 
-         | `CANCEL -> raise MatitaTypes.Cancel 
-       in
-       if b then
-           save ()
-       else
-         clean_current_baseuri grafite_status
-     end
-   end
-  else
-    clean_current_baseuri grafite_status 
+     in
+     GrafiteMarshal.save_moo moo_fname grafite_status#moo_content_rev;
+     LexiconMarshal.save_lexicon lexicon_fname
+      grafite_status#lstatus.LexiconEngine.lexicon_content_rev;
+     NRstatus.Serializer.serialize ~baseuri:(NUri.uri_of_string baseuri)
+      grafite_status#dump
+  | _ -> clean_current_baseuri grafite_status 
+;;
     
 let ask_unsaved parent =
   MatitaGtkMisc.ask_confirmation 
@@ -226,32 +202,51 @@ class interpErrorModel =
         tree_store#get ~row:iter ~column:interp_no_col
     end
 
+exception UseLibrary;;
 
-let rec interactive_error_interp ?(all_passes=false) (source_buffer:GSourceView.source_buffer) notify_exn offset errorll
+let rec interactive_error_interp ~all_passes
+  (source_buffer:GSourceView.source_buffer) notify_exn offset errorll filename
 = 
+  (* hook to save a script for each disambiguation error *)
+  if false then
+   (let text =
+     source_buffer#get_text ~start:source_buffer#start_iter
+      ~stop:source_buffer#end_iter () in
+    let md5 = Digest.to_hex (Digest.string text) in
+    let filename =
+     Filename.chop_extension filename ^ ".error." ^ md5 ^ ".ma"  in
+    let ch = open_out filename in
+     output_string ch text;
+    close_out ch
+   );
   assert (List.flatten errorll <> []);
   let errorll' =
    let remove_non_significant =
-     List.filter (fun (_env,_diff,_loc,_msg,significant) -> significant) in
-   if all_passes then errorll else
+     List.filter (fun (_env,_diff,_loc_msg,significant) -> significant) in
+   let annotated_errorll () =
+    List.rev
+     (snd
+       (List.fold_left (fun (pass,res) item -> pass+1,(pass+1,item)::res) (0,[])
+         errorll)) in
+   if all_passes then annotated_errorll () else
      let safe_list_nth l n = try List.nth l n with Failure _ -> [] in
     (* We remove passes 1,2 and 5,6 *)
      let res =
-      []::[]
-      ::(remove_non_significant (safe_list_nth errorll 2))
-      ::(remove_non_significant (safe_list_nth errorll 3))
-      ::[]::[]
+      (1,[])::(2,[])
+      ::(3,remove_non_significant (safe_list_nth errorll 2))
+      ::(4,remove_non_significant (safe_list_nth errorll 3))
+      ::(5,[])::(6,[])::[]
      in
-      if List.flatten res <> [] then res
+      if List.flatten (List.map snd res) <> [] then res
       else
        (* all errors (if any) are not significant: we keep them *)
        let res =
-        []::[]
-        ::(safe_list_nth errorll 2)
-        ::(safe_list_nth errorll 3)
-        ::[]::[]
+        (1,[])::(2,[])
+        ::(3,(safe_list_nth errorll 2))
+        ::(4,(safe_list_nth errorll 3))
+        ::(5,[])::(6,[])::[]
        in
-        if List.flatten res <> [] then
+        if List.flatten (List.map snd res) <> [] then
         begin
           HLog.warn
           "All disambiguation errors are not significant. Showing them anyway." ;
@@ -261,98 +256,17 @@ let rec interactive_error_interp ?(all_passes=false) (source_buffer:GSourceView.
          begin
           HLog.warn
           "No errors in phases 2 and 3. Showing all errors in all phases" ;
-          errorll
+          annotated_errorll ()
          end
    in
-  let choices =
-   let pass = ref 0 in
-   List.flatten
-    (List.map
-      (fun l ->
-        incr pass;
-        List.map
-         (fun (env,diff,offset,msg,significant) ->
-           offset, [[!pass], [[!pass], env, diff], msg, significant]) l
-      ) errorll') in
-  (* Here we are doing a stable sort and list_uniq returns the latter
-     "equal" element. I.e. we are showing the error corresponding to the
-     most advanced disambiguation pass *)
-  let choices =
-   let choices_compare (o1,_) (o2,_) = compare o1 o2 in
-   let choices_compare_by_passes (p1,_,_,_) (p2,_,_,_) =
-    compare p1 p2 in
-   let rec uniq =
-    function
-       [] -> []
-     | h::[] -> [h]
-     | (o1,res1)::(o2,res2)::tl when o1 = o2 ->
-        let merge_by_name errors =
-         let merge_by_env errors =
-          let choices_compare_by_env (_,e1,_) (_,e2,_) = compare e1 e2 in
-          let choices_compare_by_passes (p1,_,_) (p2,_,_) =
-           compare p1 p2 in
-          let rec uniq_by_env =
-           function
-              [] -> []
-            | h::[] -> [h]
-            | (p1,e1,_)::(p2,e2,d2)::tl when e1 = e2 ->
-                uniq_by_env ((p1@p2,e2,d2) :: tl) 
-            | h1::tl -> h1 :: uniq_by_env tl
-          in
-           List.sort choices_compare_by_passes
-            (uniq_by_env (List.stable_sort choices_compare_by_env errors))
-         in
-         let choices_compare_by_msg (_,_,m1,_) (_,_,m2,_) =
-          compare (Lazy.force m1) (Lazy.force m2) in
-         let rec uniq_by_msg =
-          function
-             [] -> []
-           | h::[] -> [h]
-           | (p1,i1,m1,s1)::(p2,i2,m2,s2)::tl
-             when Lazy.force m1 = Lazy.force m2 && s1 = s2 ->
-               uniq_by_msg ((p1@p2,merge_by_env (i1@i2),m2,s2) :: tl)
-           | h1::tl -> h1 :: uniq_by_msg tl
-         in
-          List.sort choices_compare_by_msg
-           (uniq_by_msg (List.stable_sort choices_compare_by_msg errors))
-        in
-         let res = merge_by_name (res1@res2) in
-          uniq ((o1,res) :: tl)
-     | h1::tl -> h1 :: uniq tl
-   in
-   (* Errors in phase 3 that are not also in phase 4 are filtered out *)
-   let filter_phase_3 choices =
-    if all_passes then choices
-    else
-     let filter =
-      HExtlib.filter_map
-       (function
-           (loffset,messages) ->
-              let filtered_messages =
-               HExtlib.filter_map
-                (function
-                    [3],_,_,_ -> None
-                  | item -> Some item
-                ) messages
-              in
-               if filtered_messages = [] then
-                None
-               else
-                Some (loffset,filtered_messages))
-     in
-      filter choices
-   in
-    filter_phase_3
-     (List.map (fun o,l -> o,List.sort choices_compare_by_passes l)
-       (uniq (List.stable_sort choices_compare choices)))
-  in
+  let choices = MatitaExcPp.compact_disambiguation_errors all_passes errorll' in
    match choices with
       [] -> assert false
     | [loffset,[_,envs_and_diffs,msg,significant]] ->
         let _,env,diff = List.hd envs_and_diffs in
          notify_exn
-          (GrafiteDisambiguator.DisambiguationError
-            (offset,[[env,diff,loffset,msg,significant]]));
+          (MultiPassDisambiguator.DisambiguationError
+            (offset,[[env,diff,lazy (loffset,Lazy.force msg),significant]]));
     | _::_ ->
        let dialog = new disambiguationErrors () in
        dialog#check_widgets ();
@@ -386,8 +300,8 @@ let rec interactive_error_interp ?(all_passes=false) (source_buffer:GSourceView.
              ~start:source_buffer#start_iter
              ~stop:source_buffer#end_iter;
            notify_exn
-            (GrafiteDisambiguator.DisambiguationError
-              (offset,[[env,diff,loffset,msg,significant]]))
+            (MultiPassDisambiguator.DisambiguationError
+              (offset,[[env,diff,lazy(loffset,Lazy.force msg),significant]]))
            ));
        let return _ =
          dialog#disambiguationErrors#destroy ();
@@ -415,10 +329,17 @@ let rec interactive_error_interp ?(all_passes=false) (source_buffer:GSourceView.
             String.concat "\n"
              ("" ::
                List.map
-                (fun k,value ->
-                  DisambiguatePp.pp_environment
-                   (DisambiguateTypes.Environment.add k value
-                     DisambiguateTypes.Environment.empty))
+                (fun k,desc -> 
+                  let alias =
+                   match k with
+                   | DisambiguateTypes.Id id ->
+                       LexiconAst.Ident_alias (id, desc)
+                   | DisambiguateTypes.Symbol (symb, i)-> 
+                       LexiconAst.Symbol_alias (symb, i, desc)
+                   | DisambiguateTypes.Num i ->
+                       LexiconAst.Number_alias (i, desc)
+                  in
+                   LexiconAstPp.pp_alias alias)
                 diff) ^ "\n"
            in
             source_buffer#insert
@@ -428,9 +349,7 @@ let rec interactive_error_interp ?(all_passes=false) (source_buffer:GSourceView.
             return ()
         );
        connect_button dialog#disambiguationErrorsMoreErrors
-        (fun _ -> return () ;
-          interactive_error_interp ~all_passes:true source_buffer notify_exn offset
-           errorll);
+        (fun _ -> return () ; raise UseLibrary);
        connect_button dialog#disambiguationErrorsCancelButton fail;
        dialog#disambiguationErrors#show ();
        GtkThread.main ()
@@ -451,8 +370,6 @@ class gui () =
   let main = new mainWin () in
   let fileSel = new fileSelectionWin () in
   let findRepl = new findReplWin () in
-  let develList = new develListWin () in
-  let newDevel = new newDevelWin () in
   let keyBindingBoxes = (* event boxes which should receive global key events *)
     [ main#mainWinEventBox ]
   in
@@ -470,19 +387,27 @@ class gui () =
     Helm_registry.get_opt_default Helm_registry.int
       ~default:BuildTimeConf.default_font_size "matita.font_size"
   in
+  let similarsymbols_tag_name = "similarsymbolos" in
+  let similarsymbols_tag = `NAME similarsymbols_tag_name in
   let source_buffer = source_view#source_buffer in
   object (self)
     val mutable chosen_file = None
     val mutable _ok_not_exists = false
     val mutable _only_directory = false
-    val mutable script_fname = None
     val mutable font_size = default_font_size
-    val mutable next_devel_must_contain = None
-    val mutable next_ligatures = []
+    val mutable similarsymbols = []
+    val mutable similarsymbols_orig = []
     val clipboard = GData.clipboard Gdk.Atom.clipboard
     val primary = GData.clipboard Gdk.Atom.primary
+      
+    method private reset_similarsymbols =
+      similarsymbols <- []; 
+      similarsymbols_orig <- []; 
+      try source_buffer#delete_mark similarsymbols_tag
+      with GText.No_such_mark _ -> ()
    
     initializer
+      let s () = MatitaScript.current () in
         (* glade's check widgets *)
       List.iter (fun w -> w#check_widgets ())
         (let c w = (w :> <check_widgets: unit -> unit>) in
@@ -519,14 +444,23 @@ class gui () =
         ~logo:(GdkPixbuf.from_file (MatitaMisc.image_path "/matita_medium.png"))
         ~name:"Matita"
         ~version:BuildTimeConf.version
-        ~website:"http://helm.cs.unibo.it"
+        ~website:"http://matita.cs.unibo.it"
         ()
       in
+      ignore(about_dialog#connect#response (fun _ ->about_dialog#misc#hide ()));
       connect_menu_item main#contentsMenuItem (fun () ->
-        let cmd =
-          sprintf "gnome-help ghelp://%s/C/matita.xml &" BuildTimeConf.help_dir
-        in
-        ignore (Sys.command cmd));
+        if 0 = Sys.command "which gnome-help" then
+          let cmd =
+            sprintf "gnome-help ghelp://%s/C/matita.xml &" BuildTimeConf.help_dir
+          in
+           ignore (Sys.command cmd)
+        else
+          MatitaGtkMisc.report_error ~title:"help system error"
+           ~message:(
+              "The program gnome-help is not installed\n\n"^
+              "To browse the user manal it is necessary to install "^
+              "the gnome help syste (also known as yelp)") 
+           ~parent:main#toplevel ());
       connect_menu_item main#aboutMenuItem about_dialog#present;
         (* findRepl win *)
       let show_find_Repl () = 
@@ -716,18 +650,20 @@ class gui () =
         source_buffer#move_mark `SEL_BOUND source_buffer#end_iter);
       connect_menu_item main#findReplMenuItem show_find_Repl;
       connect_menu_item main#externalEditorMenuItem self#externalEditor;
-      connect_menu_item main#ligatureButton self#nextLigature;
+      connect_menu_item main#ligatureButton self#nextSimilarSymbol;
+      ignore(source_buffer#connect#after#insert_text 
+       ~callback:(fun iter str -> 
+          if main#menuitemAutoAltL#active && (str = " " || str = "\n") then 
+            ignore(self#expand_virtual_if_any iter str)));
       ignore (findRepl#findEntry#connect#activate find_forward);
         (* interface lockers *)
       let lock_world _ =
         main#buttonsToolbar#misc#set_sensitive false;
-        develList#buttonsHbox#misc#set_sensitive false;
         main#scriptMenu#misc#set_sensitive false;
         source_view#set_editable false
       in
       let unlock_world _ =
         main#buttonsToolbar#misc#set_sensitive true;
-        develList#buttonsHbox#misc#set_sensitive true;
         main#scriptMenu#misc#set_sensitive true;
         source_view#set_editable true;
         (*The next line seems sufficient to avoid some unknown race condition *)
@@ -768,19 +704,33 @@ class gui () =
        let thread_main =
         fun () -> 
           lock_world ();
+          let saved_use_library= !MultiPassDisambiguator.use_library in
           try
+           MultiPassDisambiguator.use_library := !all_disambiguation_passes;
            f ();
+           MultiPassDisambiguator.use_library := saved_use_library;
            unlock_world ()
           with
-           | GrafiteDisambiguator.DisambiguationError (offset,errorll) ->
+           | MultiPassDisambiguator.DisambiguationError (offset,errorll) ->
               (try
-                interactive_error_interp source_buffer notify_exn offset
-                 errorll
+                interactive_error_interp 
+                 ~all_passes:!all_disambiguation_passes source_buffer
+                 notify_exn offset errorll (s())#filename
                with
-                exc -> notify_exn exc);
+                | UseLibrary ->
+                   MultiPassDisambiguator.use_library := true;
+                   (try f ()
+                    with
+                    | MultiPassDisambiguator.DisambiguationError (offset,errorll) ->
+                       interactive_error_interp ~all_passes:true source_buffer
+                        notify_exn offset errorll (s())#filename
+                    | exc ->
+                       notify_exn exc);
+                | exc -> notify_exn exc);
+              MultiPassDisambiguator.use_library := saved_use_library;
               unlock_world ()
            | exc ->
-              notify_exn exc;
+              (try notify_exn exc with Sys.Break as e -> notify_exn e);
               unlock_world ()
        in
        (*thread_main ();*)
@@ -811,125 +761,6 @@ class gui () =
           f (); source_view#misc#grab_focus ()
          with
           exc -> source_view#misc#grab_focus (); raise exc in
-        (* developments win *)
-      let model = 
-        new MatitaGtkMisc.multiStringListModel 
-          ~cols:2 develList#developmentsTreeview
-      in
-      let refresh_devels_win () =
-        model#list_store#clear ();
-        List.iter 
-          (fun (name, root) -> model#easy_mappend [name;root]) 
-          (MatitamakeLib.list_known_developments ())
-      in
-      let get_devel_selected () = 
-        match model#easy_mselection () with
-        | [[name;_]] -> MatitamakeLib.development_for_name name
-        | _ -> None
-      in
-      let refresh () = 
-        while Glib.Main.pending () do 
-          ignore(Glib.Main.iteration false); 
-        done
-      in
-      connect_button develList#newButton
-        (fun () -> 
-          next_devel_must_contain <- None;
-          newDevel#toplevel#misc#show());
-      connect_button develList#deleteButton
-        (locker (fun () -> 
-          (match get_devel_selected () with
-          | None -> ()
-          | Some d -> MatitamakeLib.destroy_development_in_bg refresh d);
-          refresh_devels_win ()));
-      connect_button develList#buildButton 
-        (locker (fun () -> 
-          match get_devel_selected () with
-          | None -> ()
-          | Some d -> 
-              let build = locker 
-                (fun () -> MatitamakeLib.build_development_in_bg refresh d)
-              in
-              ignore(build ())));
-      connect_button develList#cleanButton 
-        (locker (fun () -> 
-          match get_devel_selected () with
-          | None -> ()
-          | Some d -> 
-              let clean = locker 
-                (fun () -> MatitamakeLib.clean_development_in_bg refresh d)
-              in
-              ignore(clean ())));
-      connect_button develList#publishButton 
-        (locker (fun () -> 
-          match get_devel_selected () with
-          | None -> ()
-          | Some d -> 
-              let publish = locker (fun () ->
-                MatitamakeLib.publish_development_in_bg refresh d) in
-              ignore(publish ())));
-      connect_button develList#graphButton (fun () -> 
-        match get_devel_selected () with
-        | None -> ()
-        | Some d ->
-            (match MatitamakeLib.dot_for_development d with
-            | None -> ()
-            | Some _ ->
-                let browser = MatitaMathView.cicBrowser () in
-                browser#load (`Development
-                  (MatitamakeLib.name_for_development d))));
-      connect_button develList#closeButton 
-        (fun () -> develList#toplevel#misc#hide());
-      ignore(develList#toplevel#event#connect#delete 
-        (fun _ -> develList#toplevel#misc#hide();true));
-      connect_menu_item main#developmentsMenuItem
-        (fun () -> refresh_devels_win ();develList#toplevel#misc#show ());
-      
-        (* add development win *)
-      let check_if_root_contains root =
-        match next_devel_must_contain with
-        | None -> true
-        | Some path -> 
-            let is_prefix_of d1 d2 =
-              let d1 = MatitamakeLib.normalize_path d1 in
-              let d2 = MatitamakeLib.normalize_path d2 in
-              let len1 = String.length d1 in
-              let len2 = String.length d2 in
-              if len2 < len1 then 
-                false
-              else
-                let pref = String.sub d2 0 len1 in
-                pref = d1
-            in
-            is_prefix_of root path
-      in
-      connect_button newDevel#addButton 
-       (fun () -> 
-          let name = newDevel#nameEntry#text in
-          let root = newDevel#rootEntry#text in
-          if check_if_root_contains root then
-            begin
-              ignore (MatitamakeLib.initialize_development name root);
-              refresh_devels_win ();
-              newDevel#nameEntry#set_text "";
-              newDevel#rootEntry#set_text "";
-              newDevel#toplevel#misc#hide()
-            end
-          else
-            HLog.error ("The selected root does not contain " ^ 
-              match next_devel_must_contain with 
-              | Some x -> x 
-              | _ -> assert false));
-      connect_button newDevel#chooseRootButton 
-       (fun () ->
-         let path = self#chooseDir () in
-         match path with
-         | Some path -> newDevel#rootEntry#set_text path
-         | None -> ());
-      connect_button newDevel#cancelButton 
-       (fun () -> newDevel#toplevel#misc#hide ());
-      ignore(newDevel#toplevel#event#connect#delete 
-        (fun _ -> newDevel#toplevel#misc#hide();true));
       
         (* file selection win *)
       ignore (fileSel#fileSelectionWin#event#connect#delete (fun _ -> true));
@@ -964,9 +795,60 @@ class gui () =
         ignore (adj#connect#changed
                 (fun _ -> adj#set_value (adj#upper -. adj#page_size)));
       console#message (sprintf "\tMatita version %s\n" BuildTimeConf.version);
-      (* TO BE REMOVED *)
+        (* natural deduction palette *)
       main#tacticsButtonsHandlebox#misc#hide ();
-      main#tacticsBarMenuItem#misc#hide ();
+      MatitaGtkMisc.toggle_callback
+        ~callback:(fun b -> 
+          if b then main#tacticsButtonsHandlebox#misc#show ()
+          else main#tacticsButtonsHandlebox#misc#hide ())
+        ~check:main#menuitemPalette;
+      connect_button main#butImpl_intro
+        (fun () -> source_buffer#insert "apply rule (⇒#i […] (…));\n");
+      connect_button main#butAnd_intro
+        (fun () -> source_buffer#insert 
+          "apply rule (∧#i (…) (…));\n\t[\n\t|\n\t]\n");
+      connect_button main#butOr_intro_left
+        (fun () -> source_buffer#insert "apply rule (∨#i_l (…));\n");
+      connect_button main#butOr_intro_right
+        (fun () -> source_buffer#insert "apply rule (∨#i_r (…));\n");
+      connect_button main#butNot_intro
+        (fun () -> source_buffer#insert "apply rule (¬#i […] (…));\n");
+      connect_button main#butTop_intro
+        (fun () -> source_buffer#insert "apply rule (⊤#i);\n");
+      connect_button main#butImpl_elim
+        (fun () -> source_buffer#insert 
+          "apply rule (⇒#e (…) (…));\n\t[\n\t|\n\t]\n");
+      connect_button main#butAnd_elim_left
+        (fun () -> source_buffer#insert "apply rule (∧#e_l (…));\n");
+      connect_button main#butAnd_elim_right
+        (fun () -> source_buffer#insert "apply rule (∧#e_r (…));\n");
+      connect_button main#butOr_elim
+        (fun () -> source_buffer#insert 
+          "apply rule (∨#e (…) […] (…) […] (…));\n\t[\n\t|\n\t|\n\t]\n");
+      connect_button main#butNot_elim
+        (fun () -> source_buffer#insert 
+          "apply rule (¬#e (…) (…));\n\t[\n\t|\n\t]\n");
+      connect_button main#butBot_elim
+        (fun () -> source_buffer#insert "apply rule (⊥#e (…));\n");
+      connect_button main#butRAA
+        (fun () -> source_buffer#insert "apply rule (RAA […] (…));\n");
+      connect_button main#butUseLemma
+        (fun () -> source_buffer#insert "apply rule (lem #premises name â€¦);\n");
+      connect_button main#butDischarge
+        (fun () -> source_buffer#insert "apply rule (discharge […]);\n");
+      
+      connect_button main#butForall_intro
+        (fun () -> source_buffer#insert "apply rule (∀#i {…} (…));\n");
+      connect_button main#butForall_elim
+        (fun () -> source_buffer#insert "apply rule (∀#e {…} (…));\n");
+      connect_button main#butExists_intro
+        (fun () -> source_buffer#insert "apply rule (∃#i {…} (…));\n");
+      connect_button main#butExists_elim
+        (fun () -> source_buffer#insert 
+          "apply rule (∃#e (…) {…} […] (…));\n\t[\n\t|\n\t]\n");
+
+    
+      (* TO BE REMOVED *)
       main#scriptNotebook#remove_page 1;
       main#scriptNotebook#set_show_tabs false;
       (* / TO BE REMOVED *)
@@ -1000,7 +882,6 @@ class gui () =
            notify_exn exn
           else raise exn);
         (* script *)
-      ignore (source_buffer#connect#mark_set (fun _ _ -> next_ligatures <- []));
       let _ =
         match GSourceView.source_language_from_file BuildTimeConf.lang_file with
         | None ->
@@ -1010,42 +891,36 @@ class gui () =
             source_buffer#set_language matita_lang;
             source_buffer#set_highlight true
       in
-      let s () = MatitaScript.current () in
       let disableSave () =
-        script_fname <- None;
+        (s())#assignFileName None;
         main#saveMenuItem#misc#set_sensitive false
       in
       let saveAsScript () =
         let script = s () in
         match self#chooseFile ~ok_not_exists:true () with
         | Some f -> 
-              script#assignFileName f;
+              HExtlib.touch f;
+              script#assignFileName (Some f);
               script#saveToFile (); 
               console#message ("'"^f^"' saved.\n");
               self#_enableSaveTo f
         | None -> ()
       in
       let saveScript () =
-        match script_fname with
-        | None -> saveAsScript ()
-        | Some f -> 
-              (s ())#assignFileName f;
-              (s ())#saveToFile ();
-              console#message ("'"^f^"' saved.\n");
+        let script = s () in
+        if script#has_name then 
+          (script#saveToFile (); 
+          console#message ("'"^script#filename^"' saved.\n"))
+        else saveAsScript ()
       in
       let abandon_script () =
-        let lexicon_status = (s ())#lexicon_status in
         let grafite_status = (s ())#grafite_status in
         if source_view#buffer#modified then
           (match ask_unsaved main#toplevel with
           | `YES -> saveScript ()
           | `NO -> ()
           | `CANCEL -> raise MatitaTypes.Cancel);
-        (match script_fname with
-        | None -> ()
-        | Some fname ->
-           ask_and_save_moo_if_needed main#toplevel fname
-            lexicon_status grafite_status);
+        save_moo grafite_status
       in
       let loadScript () =
         let script = s () in 
@@ -1054,10 +929,12 @@ class gui () =
           | Some f -> 
               abandon_script ();
               script#reset (); 
-              script#assignFileName f;
+              script#assignFileName (Some f);
               source_view#source_buffer#begin_not_undoable_action ();
               script#loadFromFile f; 
               source_view#source_buffer#end_not_undoable_action ();
+              source_view#buffer#move_mark `INSERT source_view#buffer#start_iter;
+              source_view#buffer#place_cursor source_view#buffer#start_iter;
               console#message ("'"^f^"' loaded.\n");
               self#_enableSaveTo f
           | None -> ()
@@ -1070,7 +947,7 @@ class gui () =
         (s ())#template (); 
         source_view#source_buffer#end_not_undoable_action ();
         disableSave ();
-        script_fname <- None
+        (s ())#assignFileName None
       in
       let cursor () =
         source_buffer#place_cursor
@@ -1087,38 +964,18 @@ class gui () =
       let jump = locker (keep_focus jump) in
         (* quit *)
       self#setQuitCallback (fun () -> 
-        let lexicon_status = (MatitaScript.current ())#lexicon_status in
-        let grafite_status = (MatitaScript.current ())#grafite_status in
+        let script = MatitaScript.current () in
         if source_view#buffer#modified then
-          begin
-            let rc = ask_unsaved main#toplevel in 
-            try
-              match rc with
-              | `YES -> saveScript ();
-                        if not source_view#buffer#modified then
-                          begin
-                            (match script_fname with
-                            | None -> ()
-                            | Some fname -> 
-                               ask_and_save_moo_if_needed main#toplevel
-                                fname lexicon_status grafite_status);
-                          GMain.Main.quit ()
-                          end
-              | `NO -> GMain.Main.quit ()
-              | `CANCEL -> raise MatitaTypes.Cancel
-            with MatitaTypes.Cancel -> ()
-          end 
+          match ask_unsaved main#toplevel with
+          | `YES -> 
+               saveScript ();
+               save_moo script#grafite_status;
+               GMain.Main.quit ()
+          | `NO -> GMain.Main.quit ()
+          | `CANCEL -> ()
         else 
-          begin  
-            (match script_fname with
-            | None -> clean_current_baseuri grafite_status; GMain.Main.quit ()
-            | Some fname ->
-                try
-                  ask_and_save_moo_if_needed main#toplevel fname lexicon_status
-                   grafite_status;
-                  GMain.Main.quit ()
-                with MatitaTypes.Cancel -> ())
-          end);
+          (save_moo script#grafite_status;
+          GMain.Main.quit ()));
       connect_button main#scriptAdvanceButton advance;
       connect_button main#scriptRetractButton retract;
       connect_button main#scriptTopButton top;
@@ -1140,14 +997,25 @@ class gui () =
           c#load (`About `Coercions));
       connect_menu_item main#showAutoGuiMenuItem 
         (fun _ -> MatitaAutoGui.auto_dialog Auto.get_auto_status);
+      connect_menu_item main#showTermGrammarMenuItem 
+        (fun _ -> 
+          let c = MatitaMathView.cicBrowser () in
+          c#load (`About `Grammar));
+      connect_menu_item main#showUnicodeTable
+        (fun _ -> 
+          let c = MatitaMathView.cicBrowser () in
+          c#load (`About `TeX));
          (* script monospace font stuff *)  
       self#updateFontSize ();
         (* debug menu *)
       main#debugMenu#misc#hide ();
-        (* status bar *)
+        (* HBUGS *)
+      main#hintNotebook#misc#hide ();
+      (*
       main#hintLowImage#set_file (image_path "matita-bulb-low.png");
       main#hintMediumImage#set_file (image_path "matita-bulb-medium.png");
       main#hintHighImage#set_file (image_path "matita-bulb-high.png");
+      *)
         (* focus *)
       self#sourceView#misc#grab_focus ();
         (* main win dimension *)
@@ -1186,7 +1054,7 @@ class gui () =
            end));
       (* math view handling *)
       connect_menu_item main#newCicBrowserMenuItem (fun () ->
-        ignore (MatitaMathView.cicBrowser ()));
+        ignore(MatitaMathView.cicBrowser ()));
       connect_menu_item main#increaseFontSizeMenuItem (fun () ->
         self#increaseFontSize ();
         MatitaMathView.increase_font_size ();
@@ -1237,58 +1105,97 @@ class gui () =
     method pastePattern () =
       source_view#buffer#insert (MatitaMathView.paste_clipboard `Pattern)
     
-    method private nextLigature () =
-      let iter = source_buffer#get_iter_at_mark `INSERT in
-      let write_ligature len s =
+    method private expand_virtual_if_any iter tok =
+      try
+       let len = MatitaGtkMisc.utf8_string_length tok in
+       let last_word =
+        let prev = iter#copy#backward_chars len in
+         prev#get_slice ~stop:(prev#copy#backward_find_char 
+          (fun x -> Glib.Unichar.isspace x || x = Glib.Utf8.first_char "\\"))
+       in
+       let inplaceof, symb = Virtuals.symbol_of_virtual last_word in
+       self#reset_similarsymbols;
+       let s = Glib.Utf8.from_unichar symb in
+       let iter = source_buffer#get_iter_at_mark `INSERT in
+       assert(Glib.Utf8.validate s);
+       source_buffer#delete ~start:iter 
+         ~stop:(iter#copy#backward_chars
+           (MatitaGtkMisc.utf8_string_length inplaceof + len));
+       source_buffer#insert ~iter:(source_buffer#get_iter_at_mark `INSERT) 
+         (if inplaceof.[0] = '\\' then s else (s ^ tok));
+       true
+      with Virtuals.Not_a_virtual -> false
+         
+    val similar_memory = Hashtbl.create 97
+    val mutable old_used_memory = false
+
+    method private nextSimilarSymbol () = 
+      let write_similarsymbol s =
+        let s = Glib.Utf8.from_unichar s in
+        let iter = source_buffer#get_iter_at_mark `INSERT in
         assert(Glib.Utf8.validate s);
-        source_buffer#delete ~start:iter ~stop:(iter#copy#backward_chars len);
-        source_buffer#insert ~iter:(source_buffer#get_iter_at_mark `INSERT) s
+        source_buffer#delete ~start:iter ~stop:(iter#copy#backward_chars 1);
+        source_buffer#insert ~iter:(source_buffer#get_iter_at_mark `INSERT) s;
+        (try source_buffer#delete_mark similarsymbols_tag
+         with GText.No_such_mark _ -> ());
+        ignore(source_buffer#create_mark ~name:similarsymbols_tag_name
+          (source_buffer#get_iter_at_mark `INSERT));
       in
-      let get_ligature word =
-        let len = String.length word in
-        let aux_tex () =
-          try
-            for i = len - 1 downto 0 do
-              if HExtlib.is_alpha word.[i] then ()
-              else
-                (if word.[i] = '\\' then raise (Found i) else raise (Found ~-1))
-            done;
-            None
-          with Found i ->
-            if i = ~-1 then None else Some (String.sub word i (len - i))
-        in
-        let aux_ligature () =
-          try
-            for i = len - 1 downto 0 do
-              if CicNotationLexer.is_ligature_char word.[i] then ()
-              else raise (Found (i+1))
-            done;
-            raise (Found 0)
-          with
-          | Found i ->
-              (try
-                Some (String.sub word i (len - i))
-              with Invalid_argument _ -> None)
-        in
-        match aux_tex () with
-        | Some macro -> macro
-        | None -> (match aux_ligature () with Some l -> l | None -> word)
+      let new_similarsymbol =
+        try
+          let iter_ins = source_buffer#get_iter_at_mark `INSERT in
+          let iter_lig = source_buffer#get_iter_at_mark similarsymbols_tag in
+          not (iter_ins#equal iter_lig)
+        with GText.No_such_mark _ -> true
       in
-      (match next_ligatures with
-      | [] -> (* find ligatures and fill next_ligatures, then try again *)
-          let last_word =
-            iter#get_slice
-              ~stop:(iter#copy#backward_find_char Glib.Unichar.isspace)
+      if new_similarsymbol then
+        (if not(self#expand_virtual_if_any (source_buffer#get_iter_at_mark `INSERT) "")then
+          let last_symbol = 
+            let i = source_buffer#get_iter_at_mark `INSERT in
+            Glib.Utf8.first_char (i#get_slice ~stop:(i#copy#backward_chars 1))
           in
-          let ligature = get_ligature last_word in
-          (match CicNotationLexer.lookup_ligatures ligature with
-          | [] -> ()
-          | hd :: tl ->
-              write_ligature (MatitaGtkMisc.utf8_string_length ligature) hd;
-              next_ligatures <- tl @ [ hd ])
-      | hd :: tl ->
-          write_ligature 1 hd;
-          next_ligatures <- tl @ [ hd ])
+          (match Virtuals.similar_symbols last_symbol with
+          | [] ->  ()
+          | eqclass ->
+              similarsymbols_orig <- eqclass;
+              let is_used = 
+                try Hashtbl.find similar_memory similarsymbols_orig  
+                with Not_found -> 
+                  let is_used = List.map (fun x -> x,false) eqclass in
+                  Hashtbl.add similar_memory eqclass is_used; 
+                  is_used
+              in
+              let hd, next, tl = 
+                let used, unused = 
+                  List.partition (fun s -> List.assoc s is_used) eqclass 
+                in
+                match used @ unused with a::b::c -> a,b,c | _ -> assert false
+              in
+              let hd, tl = 
+                if hd = last_symbol then next, tl @ [hd] else hd, (next::tl)
+              in
+              old_used_memory <- List.assoc hd is_used;
+              let is_used = 
+                (hd,true) :: List.filter (fun (x,_) -> x <> hd) is_used
+              in
+              Hashtbl.replace similar_memory similarsymbols_orig is_used;
+              write_similarsymbol hd;
+              similarsymbols <- tl @ [ hd ]))
+      else 
+        match similarsymbols with
+        | [] -> ()
+        | hd :: tl ->
+            let is_used = Hashtbl.find similar_memory similarsymbols_orig in
+            let last = HExtlib.list_last tl in
+            let old_used_for_last = old_used_memory in
+            old_used_memory <- List.assoc hd is_used;
+            let is_used = 
+              (hd, true) :: (last,old_used_for_last) ::
+                List.filter (fun (x,_) -> x <> last && x <> hd) is_used 
+            in
+            Hashtbl.replace similar_memory similarsymbols_orig is_used;
+            similarsymbols <- tl @ [ hd ];
+            write_similarsymbol hd
 
     method private externalEditor () =
       let cmd = Helm_registry.get "matita.external_editor" in
@@ -1303,12 +1210,12 @@ class gui () =
         ask_text ~gui:self ~title:"External editor" ~msg ~multiline:false
           ~default:(Helm_registry.get "matita.external_editor") ()
       in *)
-      let fname = (MatitaScript.current ())#filename in
+      let script = MatitaScript.current () in
+      let fname = script#filename in
       let slice mark =
         source_buffer#start_iter#get_slice
           ~stop:(source_buffer#get_iter_at_mark mark)
       in
-      let script = MatitaScript.current () in
       let locked = `MARK script#locked_mark in
       let string_pos mark = string_of_int (String.length (slice mark)) in
       let cursor_pos = string_pos `INSERT in
@@ -1349,44 +1256,32 @@ class gui () =
     method loadScript file =       
       let script = MatitaScript.current () in
       script#reset (); 
-      if Pcre.pmatch ~pat:"\\.p$" file then
-        begin
-          let tptppath = 
-            Helm_registry.get_opt_default Helm_registry.string ~default:"./"
-              "matita.tptppath"
-          in
-          let data = Matitaprover.p_to_ma ~filename:file ~tptppath () in
-          let filename = Pcre.replace ~pat:"\\.p$" ~templ:".ma" file in
-          script#assignFileName filename;
-          source_view#source_buffer#begin_not_undoable_action ();
-          script#loadFromString data;
-          source_view#source_buffer#end_not_undoable_action ();
-          console#message ("'"^filename^"' loaded.");
-          self#_enableSaveTo filename
-        end
-      else
-        begin
-          script#assignFileName file;
-          let content =
-           if Sys.file_exists file then file
-           else BuildTimeConf.script_template
-          in
-           source_view#source_buffer#begin_not_undoable_action ();
-           script#loadFromFile content;
-           source_view#source_buffer#end_not_undoable_action ();
-           console#message ("'"^file^"' loaded.");
-           self#_enableSaveTo file
-        end
+      script#assignFileName (Some file);
+      let file = script#filename in
+      let content =
+       if Sys.file_exists file then file
+       else BuildTimeConf.script_template
+      in
+      source_view#source_buffer#begin_not_undoable_action ();
+      script#loadFromFile content;
+      source_view#source_buffer#end_not_undoable_action ();
+      source_view#buffer#move_mark `INSERT source_view#buffer#start_iter;
+      source_view#buffer#place_cursor source_view#buffer#start_iter;
+      console#message ("'"^file^"' loaded.");
+      self#_enableSaveTo file
       
-    method setStar name b =
-      let l = main#scriptLabel in
-      if b then
-        l#set_text (name ^  " *")
-      else
-        l#set_text (name)
+    method setStar b =
+      let s = MatitaScript.current () in
+      let w = main#toplevel in
+      let set x = w#set_title x in
+      let name = 
+        "Matita - " ^ Filename.basename s#filename ^ 
+        (if b then "*" else "") ^
+        " in " ^ s#buri_of_current_file 
+      in
+        set name
         
     method private _enableSaveTo file =
-      script_fname <- Some file;
       self#main#saveMenuItem#misc#set_sensitive true
         
     method console = console
@@ -1395,18 +1290,16 @@ class gui () =
     method fileSel = fileSel
     method findRepl = findRepl
     method main = main
-    method develList = develList
-    method newDevel = newDevel
 
     method newBrowserWin () =
       object (self)
         inherit browserWin ()
-        val combo = GEdit.combo_box_entry ()
+        val combo = GEdit.entry ()
         initializer
           self#check_widgets ();
           let combo_widget = combo#coerce in
           uriHBox#pack ~from:`END ~fill:true ~expand:true combo_widget;
-          combo#entry#misc#grab_focus ()
+          combo#misc#grab_focus ()
         method browserUri = combo
       end
 
@@ -1450,10 +1343,6 @@ class gui () =
       (* we should check that this is a directory *)
       chosen_file
   
-    method createDevelopment ~containing =
-      next_devel_must_contain <- containing;
-      newDevel#toplevel#misc#show()
-
     method askText ?(title = "") ?(msg = "") () =
       let dialog = new textDialog () in
       dialog#textDialog#set_title title;
@@ -1475,7 +1364,8 @@ class gui () =
 
     method private updateFontSize () =
       self#sourceView#misc#modify_font_by_name
-        (sprintf "%s %d" BuildTimeConf.script_font font_size)
+        (sprintf "%s %d" BuildTimeConf.script_font font_size);
+      MatitaAutoGui.set_font_size font_size
 
     method increaseFontSize () =
       font_size <- font_size + 1;
@@ -1619,9 +1509,10 @@ class interpModel =
         tree_store#get ~row:iter ~column:interp_no_col
     end
 
+
 let interactive_string_choice 
   text prefix_len ?(title = "") ?(msg = "") () ~id locs uris 
-=
+= 
   let gui = instance () in
     let dialog = gui#newUriDialog () in
     dialog#uriEntryHBox#misc#hide ();
@@ -1637,13 +1528,15 @@ let interactive_string_choice
     let rec colorize acc_len = function
       | [] -> 
           let floc = HExtlib.floc_of_loc (acc_len,hack_len) in
-          fst(MatitaGtkMisc.utf8_parsed_text text floc)
+          escape_pango_markup (fst(MatitaGtkMisc.utf8_parsed_text text floc))
       | he::tl -> 
           let start, stop =  HExtlib.loc_of_floc he in
           let floc1 = HExtlib.floc_of_loc (acc_len,start) in
           let str1,_=MatitaGtkMisc.utf8_parsed_text text floc1 in
           let str2,_ = MatitaGtkMisc.utf8_parsed_text text he in
-          str1 ^ "<b>" ^ str2 ^ "</b>" ^ colorize stop tl
+          escape_pango_markup str1 ^ "<b>" ^ 
+          escape_pango_markup str2 ^ "</b>" ^ 
+          colorize stop tl
     in
 (*     List.iter (fun l -> let start, stop = HExtlib.loc_of_floc l in
                 Printf.eprintf "(%d,%d)" start stop) locs; *)
@@ -1745,8 +1638,10 @@ let interactive_interp_choice () text prefix_len choices =
 
 let _ =
   (* disambiguator callbacks *)
-  GrafiteDisambiguator.set_choose_uris_callback (interactive_uri_choice ());
-  GrafiteDisambiguator.set_choose_interp_callback (interactive_interp_choice ());
+  Disambiguate.set_choose_uris_callback
+   (fun ~selection_mode ?ok ?(enable_button_for_non_vars=false) ~title ~msg ->
+     interactive_uri_choice ~selection_mode ?ok_label:ok ~title ~msg ());
+  Disambiguate.set_choose_interp_callback (interactive_interp_choice ());
   (* gtk initialization *)
   GtkMain.Rc.add_default_file BuildTimeConf.gtkrc_file; (* loads gtk rc *)
   GMathView.add_configuration_path BuildTimeConf.gtkmathview_conf;