]> matita.cs.unibo.it Git - helm.git/blob - matita/matita/matitaGui.ml
acic_procedural and tactics removed
[helm.git] / matita / matita / matitaGui.ml
1 (* Copyright (C) 2004-2005, HELM Team.
2  * 
3  * This file is part of HELM, an Hypertextual, Electronic
4  * Library of Mathematics, developed at the Computer Science
5  * Department, University of Bologna, Italy.
6  * 
7  * HELM is free software; you can redistribute it and/or
8  * modify it under the terms of the GNU General Public License
9  * as published by the Free Software Foundation; either version 2
10  * of the License, or (at your option) any later version.
11  * 
12  * HELM is distributed in the hope that it will be useful,
13  * but WITHOUT ANY WARRANTY; without even the implied warranty of
14  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15  * GNU General Public License for more details.
16  *
17  * You should have received a copy of the GNU General Public License
18  * along with HELM; if not, write to the Free Software
19  * Foundation, Inc., 59 Temple Place - Suite 330, Boston,
20  * MA  02111-1307, USA.
21  * 
22  * For details, see the HELM World-Wide-Web page,
23  * http://helm.cs.unibo.it/
24  *)
25
26 (* $Id$ *)
27
28 open Printf
29
30 open MatitaGeneratedGui
31 open MatitaGtkMisc
32 open MatitaMisc
33
34 exception Found of int
35
36 let all_disambiguation_passes = ref false
37
38 let gui_instance = ref None
39
40 class type browserWin =
41   (* this class exists only because GEdit.combo_box_entry is not supported by
42    * lablgladecc :-(((( *)
43 object
44   inherit MatitaGeneratedGui.browserWin
45   method browserUri: GEdit.entry
46 end
47
48 class console ~(buffer: GText.buffer) () =
49   object (self)
50     val error_tag   = buffer#create_tag [ `FOREGROUND "red" ]
51     val warning_tag = buffer#create_tag [ `FOREGROUND "orange" ]
52     val message_tag = buffer#create_tag []
53     val debug_tag   = buffer#create_tag [ `FOREGROUND "#888888" ]
54     method message s = buffer#insert ~iter:buffer#end_iter ~tags:[message_tag] s
55     method error s   = buffer#insert ~iter:buffer#end_iter ~tags:[error_tag] s
56     method warning s = buffer#insert ~iter:buffer#end_iter ~tags:[warning_tag] s
57     method debug s   = buffer#insert ~iter:buffer#end_iter ~tags:[debug_tag] s
58     method clear () =
59       buffer#delete ~start:buffer#start_iter ~stop:buffer#end_iter
60     method log_callback (tag: HLog.log_tag) s =
61       let s = Pcre.replace ~pat:"\e\\[0;3.m([^\e]+)\e\\[0m" ~templ:"$1" s in
62       match tag with
63       | `Debug -> self#debug (s ^ "\n")
64       | `Error -> self#error (s ^ "\n")
65       | `Message -> self#message (s ^ "\n")
66       | `Warning -> self#warning (s ^ "\n")
67   end
68         
69 let clean_current_baseuri grafite_status = 
70   LibraryClean.clean_baseuris [grafite_status#baseuri]
71
72 let save_moo grafite_status = 
73   let script = MatitaScript.current () in
74   let baseuri = grafite_status#baseuri in
75   match script#bos, script#eos with
76   | true, _ -> ()
77   | _, true ->
78      let moo_fname = 
79        LibraryMisc.obj_file_of_baseuri ~must_exist:false ~baseuri
80         ~writable:true in
81      let lexicon_fname =
82        LibraryMisc.lexicon_file_of_baseuri 
83          ~must_exist:false ~baseuri ~writable:true
84      in
85      GrafiteMarshal.save_moo moo_fname grafite_status#moo_content_rev;
86      LexiconMarshal.save_lexicon lexicon_fname
87       grafite_status#lstatus.LexiconEngine.lexicon_content_rev;
88      NCicLibrary.Serializer.serialize ~baseuri:(NUri.uri_of_string baseuri)
89       grafite_status#dump
90   | _ -> clean_current_baseuri grafite_status 
91 ;;
92     
93 let ask_unsaved parent =
94   MatitaGtkMisc.ask_confirmation 
95     ~parent ~title:"Unsaved work!" 
96     ~message:("Your work is <b>unsaved</b>!\n\n"^
97          "<i>Do you want to save the script before continuing?</i>")
98     ()
99
100 class interpErrorModel =
101   let cols = new GTree.column_list in
102   let id_col = cols#add Gobject.Data.string in
103   let dsc_col = cols#add Gobject.Data.string in
104   let interp_no_col = cols#add Gobject.Data.caml in
105   let tree_store = GTree.tree_store cols in
106   let id_renderer = GTree.cell_renderer_text [], ["text", id_col] in
107   let dsc_renderer = GTree.cell_renderer_text [], ["text", dsc_col] in
108   let id_view_col = GTree.view_column ~renderer:id_renderer () in
109   let dsc_view_col = GTree.view_column ~renderer:dsc_renderer () in
110   fun (tree_view: GTree.view) choices ->
111     object
112       initializer
113         tree_view#set_model (Some (tree_store :> GTree.model));
114         ignore (tree_view#append_column id_view_col);
115         ignore (tree_view#append_column dsc_view_col);
116         tree_store#clear ();
117         let idx1 = ref ~-1 in
118         List.iter
119           (fun _,lll ->
120             incr idx1;
121             let loc_row =
122              if List.length choices = 1 then
123               None
124              else
125               (let loc_row = tree_store#append () in
126                 begin
127                  match lll with
128                     [passes,envs_and_diffs,_,_] ->
129                       tree_store#set ~row:loc_row ~column:id_col
130                        ("Error location " ^ string_of_int (!idx1+1) ^
131                         ", error message " ^ string_of_int (!idx1+1) ^ ".1" ^
132                         " (in passes " ^
133                         String.concat " " (List.map string_of_int passes) ^
134                         ")");
135                       tree_store#set ~row:loc_row ~column:interp_no_col
136                        (!idx1,Some 0,None);
137                   | _ ->
138                     tree_store#set ~row:loc_row ~column:id_col
139                      ("Error location " ^ string_of_int (!idx1+1));
140                     tree_store#set ~row:loc_row ~column:interp_no_col
141                      (!idx1,None,None);
142                 end ;
143                 Some loc_row) in
144             let idx2 = ref ~-1 in
145              List.iter
146               (fun passes,envs_and_diffs,_,_ ->
147                 incr idx2;
148                 let msg_row =
149                  if List.length lll = 1 then
150                   loc_row
151                  else
152                   let msg_row = tree_store#append ?parent:loc_row () in
153                    (tree_store#set ~row:msg_row ~column:id_col
154                      ("Error message " ^ string_of_int (!idx1+1) ^ "." ^
155                       string_of_int (!idx2+1) ^
156                       " (in passes " ^
157                       String.concat " " (List.map string_of_int passes) ^
158                       ")");
159                     tree_store#set ~row:msg_row ~column:interp_no_col
160                      (!idx1,Some !idx2,None);
161                     Some msg_row) in
162                 let idx3 = ref ~-1 in
163                 List.iter
164                  (fun (passes,env,_) ->
165                    incr idx3;
166                    let interp_row =
167                     match envs_and_diffs with
168                        _::_::_ ->
169                         let interp_row = tree_store#append ?parent:msg_row () in
170                         tree_store#set ~row:interp_row ~column:id_col
171                           ("Interpretation " ^ string_of_int (!idx3+1) ^
172                            " (in passes " ^
173                            String.concat " " (List.map string_of_int passes) ^
174                            ")");
175                         tree_store#set ~row:interp_row ~column:interp_no_col
176                          (!idx1,Some !idx2,Some !idx3);
177                         Some interp_row
178                      | [_] -> msg_row
179                      | [] -> assert false
180                    in
181                     List.iter
182                      (fun (_, id, dsc) ->
183                        let row = tree_store#append ?parent:interp_row () in
184                        tree_store#set ~row ~column:id_col id;
185                        tree_store#set ~row ~column:dsc_col dsc;
186                        tree_store#set ~row ~column:interp_no_col
187                         (!idx1,Some !idx2,Some !idx3)
188                      ) env
189                  ) envs_and_diffs
190               ) lll ;
191              if List.length lll > 1 then
192               HExtlib.iter_option
193                (fun p -> tree_view#expand_row (tree_store#get_path p))
194                loc_row
195           ) choices
196
197       method get_interp_no tree_path =
198         let iter = tree_store#get_iter tree_path in
199         tree_store#get ~row:iter ~column:interp_no_col
200     end
201
202 exception UseLibrary;;
203
204 let rec interactive_error_interp ~all_passes
205   (source_buffer:GSourceView2.source_buffer) notify_exn offset errorll filename
206
207   (* hook to save a script for each disambiguation error *)
208   if false then
209    (let text =
210      source_buffer#get_text ~start:source_buffer#start_iter
211       ~stop:source_buffer#end_iter () in
212     let md5 = Digest.to_hex (Digest.string text) in
213     let filename =
214      Filename.chop_extension filename ^ ".error." ^ md5 ^ ".ma"  in
215     let ch = open_out filename in
216      output_string ch text;
217     close_out ch
218    );
219   assert (List.flatten errorll <> []);
220   let errorll' =
221    let remove_non_significant =
222      List.filter (fun (_env,_diff,_loc_msg,significant) -> significant) in
223    let annotated_errorll () =
224     List.rev
225      (snd
226        (List.fold_left (fun (pass,res) item -> pass+1,(pass+1,item)::res) (0,[])
227          errorll)) in
228    if all_passes then annotated_errorll () else
229      let safe_list_nth l n = try List.nth l n with Failure _ -> [] in
230     (* We remove passes 1,2 and 5,6 *)
231      let res =
232       (1,[])::(2,[])
233       ::(3,remove_non_significant (safe_list_nth errorll 2))
234       ::(4,remove_non_significant (safe_list_nth errorll 3))
235       ::(5,[])::(6,[])::[]
236      in
237       if List.flatten (List.map snd res) <> [] then res
238       else
239        (* all errors (if any) are not significant: we keep them *)
240        let res =
241         (1,[])::(2,[])
242         ::(3,(safe_list_nth errorll 2))
243         ::(4,(safe_list_nth errorll 3))
244         ::(5,[])::(6,[])::[]
245        in
246         if List.flatten (List.map snd res) <> [] then
247          begin
248           HLog.warn
249            "All disambiguation errors are not significant. Showing them anyway." ;
250           res
251          end
252         else
253          begin
254           HLog.warn
255            "No errors in phases 2 and 3. Showing all errors in all phases" ;
256           annotated_errorll ()
257          end
258    in
259   let choices = MatitaExcPp.compact_disambiguation_errors all_passes errorll' in
260    match choices with
261       [] -> assert false
262     | [loffset,[_,envs_and_diffs,msg,significant]] ->
263         let _,env,diff = List.hd envs_and_diffs in
264          notify_exn
265           (MultiPassDisambiguator.DisambiguationError
266             (offset,[[env,diff,lazy (loffset,Lazy.force msg),significant]]));
267     | _::_ ->
268        let dialog = new disambiguationErrors () in
269        dialog#check_widgets ();
270        if all_passes then
271         dialog#disambiguationErrorsMoreErrors#misc#set_sensitive false;
272        let model = new interpErrorModel dialog#treeview choices in
273        dialog#disambiguationErrors#set_title "Disambiguation error";
274        dialog#disambiguationErrorsLabel#set_label
275         "Click on an error to see the corresponding message:";
276        ignore (dialog#treeview#connect#cursor_changed
277         (fun _ ->
278           let tree_path =
279            match fst (dialog#treeview#get_cursor ()) with
280               None -> assert false
281            | Some tp -> tp in
282           let idx1,idx2,idx3 = model#get_interp_no tree_path in
283           let loffset,lll = List.nth choices idx1 in
284           let _,envs_and_diffs,msg,significant =
285            match idx2 with
286               Some idx2 -> List.nth lll idx2
287             | None ->
288                 [],[],lazy "Multiple error messages. Please select one.",true
289           in
290           let _,env,diff =
291            match idx3 with
292               Some idx3 -> List.nth envs_and_diffs idx3
293             | None -> [],[],[] (* dymmy value, used *) in
294           let script = MatitaScript.current () in
295           let error_tag = script#error_tag in
296            source_buffer#remove_tag error_tag
297              ~start:source_buffer#start_iter
298              ~stop:source_buffer#end_iter;
299            notify_exn
300             (MultiPassDisambiguator.DisambiguationError
301               (offset,[[env,diff,lazy(loffset,Lazy.force msg),significant]]))
302            ));
303        let return _ =
304          dialog#disambiguationErrors#destroy ();
305          GMain.Main.quit ()
306        in
307        let fail _ = return () in
308        ignore(dialog#disambiguationErrors#event#connect#delete (fun _ -> true));
309        connect_button dialog#disambiguationErrorsOkButton
310         (fun _ ->
311           let tree_path =
312            match fst (dialog#treeview#get_cursor ()) with
313               None -> assert false
314            | Some tp -> tp in
315           let idx1,idx2,idx3 = model#get_interp_no tree_path in
316           let diff =
317            match idx2,idx3 with
318               Some idx2, Some idx3 ->
319                let _,lll = List.nth choices idx1 in
320                let _,envs_and_diffs,_,_ = List.nth lll idx2 in
321                let _,_,diff = List.nth envs_and_diffs idx3 in
322                 diff
323             | _,_ -> assert false
324           in
325            let newtxt =
326             String.concat "\n"
327              ("" ::
328                List.map
329                 (fun k,desc -> 
330                   let alias =
331                    match k with
332                    | DisambiguateTypes.Id id ->
333                        LexiconAst.Ident_alias (id, desc)
334                    | DisambiguateTypes.Symbol (symb, i)-> 
335                        LexiconAst.Symbol_alias (symb, i, desc)
336                    | DisambiguateTypes.Num i ->
337                        LexiconAst.Number_alias (i, desc)
338                   in
339                    LexiconAstPp.pp_alias alias)
340                 diff) ^ "\n"
341            in
342             source_buffer#insert
343              ~iter:
344                (source_buffer#get_iter_at_mark
345                 (`NAME "beginning_of_statement")) newtxt ;
346             return ()
347         );
348        connect_button dialog#disambiguationErrorsMoreErrors
349         (fun _ -> return () ; raise UseLibrary);
350        connect_button dialog#disambiguationErrorsCancelButton fail;
351        dialog#disambiguationErrors#show ();
352        GtkThread.main ()
353
354
355 (** Selection handling
356  * Two clipboards are used: "clipboard" and "primary".
357  * "primary" is used by X, when you hit the middle button mouse is content is
358  *    pasted between applications. In Matita this selection always contain the
359  *    textual version of the selected term.
360  * "clipboard" is used inside Matita only and support ATM two different targets:
361  *    "TERM" and "PATTERN", in the future other targets like "MATHMLCONTENT" may
362  *    be added
363  *)
364
365 class gui () =
366     (* creation order _is_ relevant for windows placement *)
367   let main = new mainWin () in
368   let fileSel = new fileSelectionWin () in
369   let findRepl = new findReplWin () in
370   let keyBindingBoxes = (* event boxes which should receive global key events *)
371     [ main#mainWinEventBox ]
372   in
373   let console = new console ~buffer:main#logTextView#buffer () in
374   let (source_view: GSourceView2.source_view) =
375     GSourceView2.source_view
376       ~auto_indent:true
377       ~insert_spaces_instead_of_tabs:true ~tab_width:2
378       ~right_margin_position:80 ~show_right_margin:true
379       ~smart_home_end:`AFTER
380       ~packing:main#scriptScrolledWin#add
381       ()
382   in
383   let default_font_size =
384     Helm_registry.get_opt_default Helm_registry.int
385       ~default:BuildTimeConf.default_font_size "matita.font_size"
386   in
387   let similarsymbols_tag_name = "similarsymbolos" in
388   let similarsymbols_tag = `NAME similarsymbols_tag_name in
389   let source_buffer = source_view#source_buffer in
390   object (self)
391     val mutable chosen_file = None
392     val mutable _ok_not_exists = false
393     val mutable _only_directory = false
394     val mutable font_size = default_font_size
395     val mutable similarsymbols = []
396     val mutable similarsymbols_orig = []
397     val clipboard = GData.clipboard Gdk.Atom.clipboard
398     val primary = GData.clipboard Gdk.Atom.primary
399       
400     method private reset_similarsymbols =
401       similarsymbols <- []; 
402       similarsymbols_orig <- []; 
403       try source_buffer#delete_mark similarsymbols_tag
404       with GText.No_such_mark _ -> ()
405    
406     initializer
407       let s () = MatitaScript.current () in
408         (* glade's check widgets *)
409       List.iter (fun w -> w#check_widgets ())
410         (let c w = (w :> <check_widgets: unit -> unit>) in
411         [ c fileSel; c main; c findRepl]);
412         (* key bindings *)
413       List.iter (* global key bindings *)
414         (fun (key, callback) -> self#addKeyBinding key callback)
415 (*
416         [ GdkKeysyms._F3,
417             toggle_win ~check:main#showProofMenuItem proof#proofWin;
418           GdkKeysyms._F4,
419             toggle_win ~check:main#showCheckMenuItem check#checkWin;
420 *)
421         [ ];
422         (* about win *)
423       let parse_txt_file file =
424        let ch = open_in (BuildTimeConf.runtime_base_dir ^ "/" ^ file) in
425        let l_rev = ref [] in
426        try
427         while true do
428          l_rev := input_line ch :: !l_rev;
429         done;
430         assert false
431        with
432         End_of_file ->
433          close_in ch;
434          List.rev !l_rev in 
435       let about_dialog =
436        GWindow.about_dialog
437         ~authors:(parse_txt_file "AUTHORS")
438         (*~comments:"comments"*)
439         ~copyright:"Copyright (C) 2005, the HELM team"
440         ~license:(String.concat "\n" (parse_txt_file "LICENSE"))
441         ~logo:(GdkPixbuf.from_file (MatitaMisc.image_path "/matita_medium.png"))
442         ~name:"Matita"
443         ~version:BuildTimeConf.version
444         ~website:"http://matita.cs.unibo.it"
445         ()
446       in
447       ignore(about_dialog#connect#response (fun _ ->about_dialog#misc#hide ()));
448       connect_menu_item main#contentsMenuItem (fun () ->
449         if 0 = Sys.command "which gnome-help" then
450           let cmd =
451             sprintf "gnome-help ghelp://%s/C/matita.xml &" BuildTimeConf.help_dir
452           in
453            ignore (Sys.command cmd)
454         else
455           MatitaGtkMisc.report_error ~title:"help system error"
456            ~message:(
457               "The program gnome-help is not installed\n\n"^
458               "To browse the user manal it is necessary to install "^
459               "the gnome help syste (also known as yelp)") 
460            ~parent:main#toplevel ());
461       connect_menu_item main#aboutMenuItem about_dialog#present;
462         (* findRepl win *)
463       let show_find_Repl () = 
464         findRepl#toplevel#misc#show ();
465         findRepl#toplevel#misc#grab_focus ()
466       in
467       let hide_find_Repl () = findRepl#toplevel#misc#hide () in
468       let find_forward _ = 
469           let highlight start end_ =
470             source_buffer#move_mark `INSERT ~where:start;
471             source_buffer#move_mark `SEL_BOUND ~where:end_;
472             source_view#scroll_mark_onscreen `INSERT
473           in
474           let text = findRepl#findEntry#text in
475           let iter = source_buffer#get_iter `SEL_BOUND in
476           match iter#forward_search text with
477           | None -> 
478               (match source_buffer#start_iter#forward_search text with
479               | None -> ()
480               | Some (start,end_) -> highlight start end_)
481           | Some (start,end_) -> highlight start end_ 
482       in
483       let replace _ =
484         let text = findRepl#replaceEntry#text in
485         let ins = source_buffer#get_iter `INSERT in
486         let sel = source_buffer#get_iter `SEL_BOUND in
487         if ins#compare sel < 0 then 
488           begin
489             ignore(source_buffer#delete_selection ());
490             source_buffer#insert text
491           end
492       in
493       connect_button findRepl#findButton find_forward;
494       connect_button findRepl#findReplButton replace;
495       connect_button findRepl#cancelButton (fun _ -> hide_find_Repl ());
496       ignore(findRepl#toplevel#event#connect#delete 
497         ~callback:(fun _ -> hide_find_Repl ();true));
498       let safe_undo =
499        fun () ->
500         (* phase 1: we save the actual status of the marks and we undo *)
501         let locked_mark = `MARK ((MatitaScript.current ())#locked_mark) in
502         let locked_iter = source_view#buffer#get_iter_at_mark locked_mark in
503         let locked_iter_offset = locked_iter#offset in
504         let mark2 =
505          `MARK
506            (source_view#buffer#create_mark ~name:"lock_point"
507              ~left_gravity:true locked_iter) in
508         source_view#source_buffer#undo ();
509         (* phase 2: we save the cursor position and we redo, restoring
510            the previous status of all the marks *)
511         let cursor_iter = source_view#buffer#get_iter_at_mark `INSERT in
512         let mark =
513          `MARK
514            (source_view#buffer#create_mark ~name:"undo_point"
515              ~left_gravity:true cursor_iter)
516         in
517          source_view#source_buffer#redo ();
518          let mark_iter = source_view#buffer#get_iter_at_mark mark in
519          let mark2_iter = source_view#buffer#get_iter_at_mark mark2 in
520          let mark2_iter = mark2_iter#set_offset locked_iter_offset in
521           source_view#buffer#move_mark locked_mark ~where:mark2_iter;
522           source_view#buffer#delete_mark mark;
523           source_view#buffer#delete_mark mark2;
524           (* phase 3: if after the undo the cursor was in the locked area,
525              then we move it there again and we perform a goto *)
526           if mark_iter#offset < locked_iter_offset then
527            begin
528             source_view#buffer#move_mark `INSERT ~where:mark_iter;
529             (MatitaScript.current ())#goto `Cursor ();
530            end;
531           (* phase 4: we perform again the undo. This time we are sure that
532              the text to undo is not locked *)
533           source_view#source_buffer#undo ();
534           source_view#misc#grab_focus () in
535       let safe_redo =
536        fun () ->
537         (* phase 1: we save the actual status of the marks, we redo and
538            we undo *)
539         let locked_mark = `MARK ((MatitaScript.current ())#locked_mark) in
540         let locked_iter = source_view#buffer#get_iter_at_mark locked_mark in
541         let locked_iter_offset = locked_iter#offset in
542         let mark2 =
543          `MARK
544            (source_view#buffer#create_mark ~name:"lock_point"
545              ~left_gravity:true locked_iter) in
546         source_view#source_buffer#redo ();
547         source_view#source_buffer#undo ();
548         (* phase 2: we save the cursor position and we restore
549            the previous status of all the marks *)
550         let cursor_iter = source_view#buffer#get_iter_at_mark `INSERT in
551         let mark =
552          `MARK
553            (source_view#buffer#create_mark ~name:"undo_point"
554              ~left_gravity:true cursor_iter)
555         in
556          let mark_iter = source_view#buffer#get_iter_at_mark mark in
557          let mark2_iter = source_view#buffer#get_iter_at_mark mark2 in
558          let mark2_iter = mark2_iter#set_offset locked_iter_offset in
559           source_view#buffer#move_mark locked_mark ~where:mark2_iter;
560           source_view#buffer#delete_mark mark;
561           source_view#buffer#delete_mark mark2;
562           (* phase 3: if after the undo the cursor is in the locked area,
563              then we move it there again and we perform a goto *)
564           if mark_iter#offset < locked_iter_offset then
565            begin
566             source_view#buffer#move_mark `INSERT ~where:mark_iter;
567             (MatitaScript.current ())#goto `Cursor ();
568            end;
569           (* phase 4: we perform again the redo. This time we are sure that
570              the text to redo is not locked *)
571           source_view#source_buffer#redo ();
572           source_view#misc#grab_focus ()
573       in
574       connect_menu_item main#undoMenuItem safe_undo;
575 (*CSC: XXX
576       ignore(source_view#source_buffer#connect#can_undo
577         ~callback:main#undoMenuItem#misc#set_sensitive);
578 *) main#undoMenuItem#misc#set_sensitive true;
579       connect_menu_item main#redoMenuItem safe_redo;
580 (*CSC: XXX
581       ignore(source_view#source_buffer#connect#can_redo
582         ~callback:main#redoMenuItem#misc#set_sensitive);
583 *) main#redoMenuItem#misc#set_sensitive true;
584       ignore(source_view#connect#after#populate_popup
585        ~callback:(fun pre_menu ->
586          let menu = new GMenu.menu pre_menu in
587          let menuItems = menu#children in
588          let undoMenuItem, redoMenuItem =
589           match menuItems with
590              [undo;redo;sep1;cut;copy;paste;delete;sep2;
591               selectall;sep3;inputmethod;insertunicodecharacter] ->
592                 List.iter menu#remove [ copy; cut; delete; paste ];
593                 undo,redo
594            | _ -> assert false in
595          let add_menu_item =
596            let i = ref 2 in (* last occupied position *)
597            fun ?label ?stock () ->
598              incr i;
599              GMenu.image_menu_item ?label ?stock ~packing:(menu#insert ~pos:!i)
600               ()
601          in
602          let copy = add_menu_item ~stock:`COPY () in
603          let cut = add_menu_item ~stock:`CUT () in
604          let delete = add_menu_item ~stock:`DELETE () in
605          let paste = add_menu_item ~stock:`PASTE () in
606          let paste_pattern = add_menu_item ~label:"Paste as pattern" () in
607          copy#misc#set_sensitive self#canCopy;
608          cut#misc#set_sensitive self#canCut;
609          delete#misc#set_sensitive self#canDelete;
610          paste#misc#set_sensitive self#canPaste;
611          paste_pattern#misc#set_sensitive self#canPastePattern;
612          connect_menu_item copy self#copy;
613          connect_menu_item cut self#cut;
614          connect_menu_item delete self#delete;
615          connect_menu_item paste self#paste;
616          connect_menu_item paste_pattern self#pastePattern;
617          let new_undoMenuItem =
618           GMenu.image_menu_item
619            ~image:(GMisc.image ~stock:`UNDO ())
620            ~use_mnemonic:true
621            ~label:"_Undo"
622            ~packing:(menu#insert ~pos:0) () in
623          new_undoMenuItem#misc#set_sensitive
624           (undoMenuItem#misc#get_flag `SENSITIVE);
625          menu#remove (undoMenuItem :> GMenu.menu_item);
626          connect_menu_item new_undoMenuItem safe_undo;
627          let new_redoMenuItem =
628           GMenu.image_menu_item
629            ~image:(GMisc.image ~stock:`REDO ())
630            ~use_mnemonic:true
631            ~label:"_Redo"
632            ~packing:(menu#insert ~pos:1) () in
633          new_redoMenuItem#misc#set_sensitive
634           (redoMenuItem#misc#get_flag `SENSITIVE);
635           menu#remove (redoMenuItem :> GMenu.menu_item);
636           connect_menu_item new_redoMenuItem safe_redo));
637
638       connect_menu_item main#editMenu (fun () ->
639         main#copyMenuItem#misc#set_sensitive self#canCopy;
640         main#cutMenuItem#misc#set_sensitive self#canCut;
641         main#deleteMenuItem#misc#set_sensitive self#canDelete;
642         main#pasteMenuItem#misc#set_sensitive self#canPaste;
643         main#pastePatternMenuItem#misc#set_sensitive self#canPastePattern);
644       connect_menu_item main#copyMenuItem self#copy;
645       connect_menu_item main#cutMenuItem self#cut;
646       connect_menu_item main#deleteMenuItem self#delete;
647       connect_menu_item main#pasteMenuItem self#paste;
648       connect_menu_item main#pastePatternMenuItem self#pastePattern;
649       connect_menu_item main#selectAllMenuItem (fun () ->
650         source_buffer#move_mark `INSERT source_buffer#start_iter;
651         source_buffer#move_mark `SEL_BOUND source_buffer#end_iter);
652       connect_menu_item main#findReplMenuItem show_find_Repl;
653       connect_menu_item main#externalEditorMenuItem self#externalEditor;
654       connect_menu_item main#ligatureButton self#nextSimilarSymbol;
655       ignore(source_buffer#connect#after#insert_text 
656        ~callback:(fun iter str -> 
657           if main#menuitemAutoAltL#active && (str = " " || str = "\n") then 
658             ignore(self#expand_virtual_if_any iter str)));
659       ignore (findRepl#findEntry#connect#activate find_forward);
660         (* interface lockers *)
661       let lock_world _ =
662         main#buttonsToolbar#misc#set_sensitive false;
663         main#scriptMenu#misc#set_sensitive false;
664         source_view#set_editable false
665       in
666       let unlock_world _ =
667         main#buttonsToolbar#misc#set_sensitive true;
668         main#scriptMenu#misc#set_sensitive true;
669         source_view#set_editable true;
670         (*The next line seems sufficient to avoid some unknown race condition *)
671         GtkThread.sync (fun () -> ()) ()
672       in
673       let worker_thread = ref None in
674       let notify_exn exn =
675        let floc, msg = MatitaExcPp.to_string exn in
676         begin
677          match floc with
678             None -> ()
679           | Some floc ->
680              let (x, y) = HExtlib.loc_of_floc floc in
681              let script = MatitaScript.current () in
682              let locked_mark = script#locked_mark in
683              let error_tag = script#error_tag in
684              let baseoffset =
685               (source_buffer#get_iter_at_mark (`MARK locked_mark))#offset in
686              let x' = baseoffset + x in
687              let y' = baseoffset + y in
688              let x_iter = source_buffer#get_iter (`OFFSET x') in
689              let y_iter = source_buffer#get_iter (`OFFSET y') in
690              source_buffer#apply_tag error_tag ~start:x_iter ~stop:y_iter;
691              let id = ref None in
692              id := Some (source_buffer#connect#changed ~callback:(fun () ->
693                source_buffer#remove_tag error_tag
694                  ~start:source_buffer#start_iter
695                  ~stop:source_buffer#end_iter;
696                match !id with
697                | None -> assert false (* a race condition occurred *)
698                | Some id ->
699                    (new GObj.gobject_ops source_buffer#as_buffer)#disconnect id));
700              source_buffer#place_cursor
701               (source_buffer#get_iter (`OFFSET x'));
702         end;
703         HLog.error msg in
704       let locker f () =
705        let thread_main =
706         fun () -> 
707           lock_world ();
708           let saved_use_library= !MultiPassDisambiguator.use_library in
709           try
710            MultiPassDisambiguator.use_library := !all_disambiguation_passes;
711            f ();
712            MultiPassDisambiguator.use_library := saved_use_library;
713            unlock_world ()
714           with
715            | MultiPassDisambiguator.DisambiguationError (offset,errorll) ->
716               (try
717                 interactive_error_interp 
718                  ~all_passes:!all_disambiguation_passes source_buffer
719                  notify_exn offset errorll (s())#filename
720                with
721                 | UseLibrary ->
722                    MultiPassDisambiguator.use_library := true;
723                    (try f ()
724                     with
725                     | MultiPassDisambiguator.DisambiguationError (offset,errorll) ->
726                        interactive_error_interp ~all_passes:true source_buffer
727                         notify_exn offset errorll (s())#filename
728                     | exc ->
729                        notify_exn exc);
730                 | exc -> notify_exn exc);
731               MultiPassDisambiguator.use_library := saved_use_library;
732               unlock_world ()
733            | exc ->
734               (try notify_exn exc with Sys.Break as e -> notify_exn e);
735               unlock_world ()
736        in
737        (*thread_main ();*)
738        worker_thread := Some (Thread.create thread_main ())
739       in
740       let kill_worker =
741        (* the following lines are from Xavier Leroy: http://alan.petitepomme.net/cwn/2005.11.08.html *)
742        let interrupt = ref None in
743        let old_callback = ref (function _ -> ()) in
744        let force_interrupt n =
745          (* This function is called just before the thread's timeslice ends *)
746          !old_callback n;
747          if Some(Thread.id(Thread.self())) = !interrupt then
748           (interrupt := None; raise Sys.Break) in
749        let _ =
750         match Sys.signal Sys.sigvtalrm (Sys.Signal_handle force_interrupt) with
751            Sys.Signal_handle f -> old_callback := f
752          | Sys.Signal_ignore
753          | Sys.Signal_default -> assert false
754        in
755         fun () ->
756          match !worker_thread with
757             None -> assert false
758           | Some t -> interrupt := Some (Thread.id t) in
759       let keep_focus f =
760         fun () ->
761          try
762           f (); source_view#misc#grab_focus ()
763          with
764           exc -> source_view#misc#grab_focus (); raise exc in
765       
766         (* file selection win *)
767       ignore (fileSel#fileSelectionWin#event#connect#delete (fun _ -> true));
768       ignore (fileSel#fileSelectionWin#connect#response (fun event ->
769         let return r =
770           chosen_file <- r;
771           fileSel#fileSelectionWin#misc#hide ();
772           GMain.Main.quit ()
773         in
774         match event with
775         | `OK ->
776             let fname = fileSel#fileSelectionWin#filename in
777             if Sys.file_exists fname then
778               begin
779                 if HExtlib.is_regular fname && not (_only_directory) then 
780                   return (Some fname) 
781                 else if _only_directory && HExtlib.is_dir fname then 
782                   return (Some fname)
783               end
784             else
785               begin
786                 if _ok_not_exists then 
787                   return (Some fname)
788               end
789         | `CANCEL -> return None
790         | `HELP -> ()
791         | `DELETE_EVENT -> return None));
792         (* menus *)
793       List.iter (fun w -> w#misc#set_sensitive false) [ main#saveMenuItem ];
794         (* console *)
795       let adj = main#logScrolledWin#vadjustment in
796         ignore (adj#connect#changed
797                 (fun _ -> adj#set_value (adj#upper -. adj#page_size)));
798       console#message (sprintf "\tMatita version %s\n" BuildTimeConf.version);
799         (* natural deduction palette *)
800       main#tacticsButtonsHandlebox#misc#hide ();
801       MatitaGtkMisc.toggle_callback
802         ~callback:(fun b -> 
803           if b then main#tacticsButtonsHandlebox#misc#show ()
804           else main#tacticsButtonsHandlebox#misc#hide ())
805         ~check:main#menuitemPalette;
806       connect_button main#butImpl_intro
807         (fun () -> source_buffer#insert "apply rule (⇒#i […] (…));\n");
808       connect_button main#butAnd_intro
809         (fun () -> source_buffer#insert 
810           "apply rule (∧#i (…) (…));\n\t[\n\t|\n\t]\n");
811       connect_button main#butOr_intro_left
812         (fun () -> source_buffer#insert "apply rule (∨#i_l (…));\n");
813       connect_button main#butOr_intro_right
814         (fun () -> source_buffer#insert "apply rule (∨#i_r (…));\n");
815       connect_button main#butNot_intro
816         (fun () -> source_buffer#insert "apply rule (¬#i […] (…));\n");
817       connect_button main#butTop_intro
818         (fun () -> source_buffer#insert "apply rule (⊤#i);\n");
819       connect_button main#butImpl_elim
820         (fun () -> source_buffer#insert 
821           "apply rule (⇒#e (…) (…));\n\t[\n\t|\n\t]\n");
822       connect_button main#butAnd_elim_left
823         (fun () -> source_buffer#insert "apply rule (∧#e_l (…));\n");
824       connect_button main#butAnd_elim_right
825         (fun () -> source_buffer#insert "apply rule (∧#e_r (…));\n");
826       connect_button main#butOr_elim
827         (fun () -> source_buffer#insert 
828           "apply rule (∨#e (…) […] (…) […] (…));\n\t[\n\t|\n\t|\n\t]\n");
829       connect_button main#butNot_elim
830         (fun () -> source_buffer#insert 
831           "apply rule (¬#e (…) (…));\n\t[\n\t|\n\t]\n");
832       connect_button main#butBot_elim
833         (fun () -> source_buffer#insert "apply rule (⊥#e (…));\n");
834       connect_button main#butRAA
835         (fun () -> source_buffer#insert "apply rule (RAA […] (…));\n");
836       connect_button main#butUseLemma
837         (fun () -> source_buffer#insert "apply rule (lem #premises name â€¦);\n");
838       connect_button main#butDischarge
839         (fun () -> source_buffer#insert "apply rule (discharge […]);\n");
840       
841       connect_button main#butForall_intro
842         (fun () -> source_buffer#insert "apply rule (∀#i {…} (…));\n");
843       connect_button main#butForall_elim
844         (fun () -> source_buffer#insert "apply rule (∀#e {…} (…));\n");
845       connect_button main#butExists_intro
846         (fun () -> source_buffer#insert "apply rule (∃#i {…} (…));\n");
847       connect_button main#butExists_elim
848         (fun () -> source_buffer#insert 
849           "apply rule (∃#e (…) {…} […] (…));\n\t[\n\t|\n\t]\n");
850
851     
852       (* TO BE REMOVED *)
853       main#scriptNotebook#remove_page 1;
854       main#scriptNotebook#set_show_tabs false;
855       (* / TO BE REMOVED *)
856       let module Hr = Helm_registry in
857       MatitaGtkMisc.toggle_callback ~check:main#fullscreenMenuItem
858         ~callback:(function 
859           | true -> main#toplevel#fullscreen () 
860           | false -> main#toplevel#unfullscreen ());
861       main#fullscreenMenuItem#set_active false;
862       MatitaGtkMisc.toggle_callback ~check:main#ppNotationMenuItem
863         ~callback:(function
864           | true ->
865               CicNotation.set_active_notations
866                 (List.map fst (CicNotation.get_all_notations ()))
867           | false ->
868               CicNotation.set_active_notations []);
869       MatitaGtkMisc.toggle_callback ~check:main#hideCoercionsMenuItem
870         ~callback:(fun enabled -> Acic2content.hide_coercions := enabled);
871       MatitaGtkMisc.toggle_callback ~check:main#unicodeAsTexMenuItem
872         ~callback:(fun enabled ->
873           Helm_registry.set_bool "matita.paste_unicode_as_tex" enabled);
874       main#unicodeAsTexMenuItem#set_active
875         (Helm_registry.get_bool "matita.paste_unicode_as_tex");
876         (* log *)
877       HLog.set_log_callback self#console#log_callback;
878       GtkSignal.user_handler :=
879         (function 
880         | MatitaScript.ActionCancelled s -> HLog.error s
881         | exn ->
882           if not (Helm_registry.get_bool "matita.debug") then
883            notify_exn exn
884           else raise exn);
885         (* script *)
886       let _ =
887        source_buffer#set_language (Some MatitaGtkMisc.matita_lang);
888        source_buffer#set_highlight_syntax true
889       in
890       let disableSave () =
891         (s())#assignFileName None;
892         main#saveMenuItem#misc#set_sensitive false
893       in
894       let saveAsScript () =
895         let script = s () in
896         match self#chooseFile ~ok_not_exists:true () with
897         | Some f -> 
898               HExtlib.touch f;
899               script#assignFileName (Some f);
900               script#saveToFile (); 
901               console#message ("'"^f^"' saved.\n");
902               self#_enableSaveTo f
903         | None -> ()
904       in
905       let saveScript () =
906         let script = s () in
907         if script#has_name then 
908           (script#saveToFile (); 
909           console#message ("'"^script#filename^"' saved.\n"))
910         else saveAsScript ()
911       in
912       let abandon_script () =
913         let grafite_status = (s ())#grafite_status in
914         if source_view#buffer#modified then
915           (match ask_unsaved main#toplevel with
916           | `YES -> saveScript ()
917           | `NO -> ()
918           | `CANCEL -> raise MatitaTypes.Cancel);
919         save_moo grafite_status
920       in
921       let loadScript () =
922         let script = s () in 
923         try 
924           match self#chooseFile () with
925           | Some f -> 
926               abandon_script ();
927               script#reset (); 
928               script#assignFileName (Some f);
929               source_view#source_buffer#begin_not_undoable_action ();
930               script#loadFromFile f; 
931               source_view#source_buffer#end_not_undoable_action ();
932               source_view#buffer#move_mark `INSERT source_view#buffer#start_iter;
933               source_view#buffer#place_cursor source_view#buffer#start_iter;
934               console#message ("'"^f^"' loaded.\n");
935               self#_enableSaveTo f
936           | None -> ()
937         with MatitaTypes.Cancel -> ()
938       in
939       let newScript () = 
940         abandon_script ();
941         source_view#source_buffer#begin_not_undoable_action ();
942         (s ())#reset (); 
943         (s ())#template (); 
944         source_view#source_buffer#end_not_undoable_action ();
945         disableSave ();
946         (s ())#assignFileName None
947       in
948       let cursor () =
949         source_buffer#place_cursor
950           (source_buffer#get_iter_at_mark (`NAME "locked")) in
951       let advance _ = (MatitaScript.current ())#advance (); cursor () in
952       let retract _ = (MatitaScript.current ())#retract (); cursor () in
953       let top _ = (MatitaScript.current ())#goto `Top (); cursor () in
954       let bottom _ = (MatitaScript.current ())#goto `Bottom (); cursor () in
955       let jump _ = (MatitaScript.current ())#goto `Cursor (); cursor () in
956       let advance = locker (keep_focus advance) in
957       let retract = locker (keep_focus retract) in
958       let top = locker (keep_focus top) in
959       let bottom = locker (keep_focus bottom) in
960       let jump = locker (keep_focus jump) in
961         (* quit *)
962       self#setQuitCallback (fun () -> 
963         let script = MatitaScript.current () in
964         if source_view#buffer#modified then
965           match ask_unsaved main#toplevel with
966           | `YES -> 
967                saveScript ();
968                save_moo script#grafite_status;
969                GMain.Main.quit ()
970           | `NO -> GMain.Main.quit ()
971           | `CANCEL -> ()
972         else 
973           (save_moo script#grafite_status;
974           GMain.Main.quit ()));
975       connect_button main#scriptAdvanceButton advance;
976       connect_button main#scriptRetractButton retract;
977       connect_button main#scriptTopButton top;
978       connect_button main#scriptBottomButton bottom;
979       connect_button main#scriptJumpButton jump;
980       connect_button main#scriptAbortButton kill_worker;
981       connect_menu_item main#scriptAdvanceMenuItem advance;
982       connect_menu_item main#scriptRetractMenuItem retract;
983       connect_menu_item main#scriptTopMenuItem top;
984       connect_menu_item main#scriptBottomMenuItem bottom;
985       connect_menu_item main#scriptJumpMenuItem jump;
986       connect_menu_item main#openMenuItem   loadScript;
987       connect_menu_item main#saveMenuItem   saveScript;
988       connect_menu_item main#saveAsMenuItem saveAsScript;
989       connect_menu_item main#newMenuItem    newScript;
990       connect_menu_item main#showCoercionsGraphMenuItem 
991         (fun _ -> 
992           let c = MatitaMathView.cicBrowser () in
993           c#load (`About `Coercions));
994       connect_menu_item main#showHintsDbMenuItem 
995         (fun _ -> 
996           let c = MatitaMathView.cicBrowser () in
997           c#load (`About `Hints));
998       connect_menu_item main#showTermGrammarMenuItem 
999         (fun _ -> 
1000           let c = MatitaMathView.cicBrowser () in
1001           c#load (`About `Grammar));
1002       connect_menu_item main#showUnicodeTable
1003         (fun _ -> 
1004           let c = MatitaMathView.cicBrowser () in
1005           c#load (`About `TeX));
1006          (* script monospace font stuff *)  
1007       self#updateFontSize ();
1008         (* debug menu *)
1009       main#debugMenu#misc#hide ();
1010         (* HBUGS *)
1011       main#hintNotebook#misc#hide ();
1012       (*
1013       main#hintLowImage#set_file (image_path "matita-bulb-low.png");
1014       main#hintMediumImage#set_file (image_path "matita-bulb-medium.png");
1015       main#hintHighImage#set_file (image_path "matita-bulb-high.png");
1016       *)
1017         (* focus *)
1018       self#sourceView#misc#grab_focus ();
1019         (* main win dimension *)
1020       let width = Gdk.Screen.width ~screen:(Gdk.Screen.default ()) () in
1021       let height = Gdk.Screen.height ~screen:(Gdk.Screen.default ()) () in
1022       (* hack for xinerama, no proper support of monitors from lablgtk *)
1023       let width = if width > 1600 then width / 2 else width in
1024       let height = if height > 1200 then height / 2 else height in
1025       let main_w = width * 90 / 100 in 
1026       let main_h = height * 80 / 100 in
1027       let script_w = main_w * 6 / 10 in
1028       main#toplevel#resize ~width:main_w ~height:main_h;
1029       main#hpaneScriptSequent#set_position script_w;
1030         (* source_view *)
1031       ignore(source_view#connect#after#paste_clipboard 
1032         ~callback:(fun () -> (MatitaScript.current ())#clean_dirty_lock));
1033       (* clean_locked is set to true only "during" a PRIMARY paste
1034          operation (i.e. by clicking with the second mouse button) *)
1035       let clean_locked = ref false in
1036       ignore(source_view#event#connect#button_press
1037         ~callback:
1038           (fun button ->
1039             if GdkEvent.Button.button button = 2 then
1040              clean_locked := true;
1041             false
1042           ));
1043       ignore(source_view#event#connect#button_release
1044         ~callback:(fun button -> clean_locked := false; false));
1045       ignore(source_view#buffer#connect#after#apply_tag
1046        ~callback:(
1047          fun tag ~start:_ ~stop:_ ->
1048           if !clean_locked &&
1049              tag#get_oid = (MatitaScript.current ())#locked_tag#get_oid
1050           then
1051            begin
1052             clean_locked := false;
1053             (MatitaScript.current ())#clean_dirty_lock;
1054             clean_locked := true
1055            end));
1056       (* math view handling *)
1057       connect_menu_item main#newCicBrowserMenuItem (fun () ->
1058         ignore(MatitaMathView.cicBrowser ()));
1059       connect_menu_item main#increaseFontSizeMenuItem (fun () ->
1060         self#increaseFontSize ();
1061         MatitaMathView.increase_font_size ();
1062         MatitaMathView.update_font_sizes ());
1063       connect_menu_item main#decreaseFontSizeMenuItem (fun () ->
1064         self#decreaseFontSize ();
1065         MatitaMathView.decrease_font_size ();
1066         MatitaMathView.update_font_sizes ());
1067       connect_menu_item main#normalFontSizeMenuItem (fun () ->
1068         self#resetFontSize ();
1069         MatitaMathView.reset_font_size ();
1070         MatitaMathView.update_font_sizes ());
1071       MatitaMathView.reset_font_size ();
1072
1073       (** selections / clipboards handling *)
1074
1075     method markupSelected = MatitaMathView.has_selection ()
1076     method private textSelected =
1077       (source_buffer#get_iter_at_mark `INSERT)#compare
1078         (source_buffer#get_iter_at_mark `SEL_BOUND) <> 0
1079     method private somethingSelected = self#markupSelected || self#textSelected
1080     method private markupStored = MatitaMathView.has_clipboard ()
1081     method private textStored = clipboard#text <> None
1082     method private somethingStored = self#markupStored || self#textStored
1083
1084     method canCopy = self#somethingSelected
1085     method canCut = self#textSelected
1086     method canDelete = self#textSelected
1087     method canPaste = self#somethingStored
1088     method canPastePattern = self#markupStored
1089
1090     method copy () =
1091       if self#textSelected
1092       then begin
1093         MatitaMathView.empty_clipboard ();
1094         source_view#buffer#copy_clipboard clipboard;
1095       end else
1096         MatitaMathView.copy_selection ()
1097     method cut () =
1098       source_view#buffer#cut_clipboard clipboard;
1099       MatitaMathView.empty_clipboard ()
1100     method delete () = ignore (source_view#buffer#delete_selection ())
1101     method paste () =
1102       if MatitaMathView.has_clipboard ()
1103       then source_view#buffer#insert (MatitaMathView.paste_clipboard `Term)
1104       else source_view#buffer#paste_clipboard clipboard;
1105       (MatitaScript.current ())#clean_dirty_lock
1106     method pastePattern () =
1107       source_view#buffer#insert (MatitaMathView.paste_clipboard `Pattern)
1108     
1109     method private expand_virtual_if_any iter tok =
1110       try
1111        let len = MatitaGtkMisc.utf8_string_length tok in
1112        let last_word =
1113         let prev = iter#copy#backward_chars len in
1114          prev#get_slice ~stop:(prev#copy#backward_find_char 
1115           (fun x -> Glib.Unichar.isspace x || x = Glib.Utf8.first_char "\\"))
1116        in
1117        let inplaceof, symb = Virtuals.symbol_of_virtual last_word in
1118        self#reset_similarsymbols;
1119        let s = Glib.Utf8.from_unichar symb in
1120        assert(Glib.Utf8.validate s);
1121        source_buffer#delete ~start:iter 
1122          ~stop:(iter#copy#backward_chars
1123            (MatitaGtkMisc.utf8_string_length inplaceof + len));
1124        source_buffer#insert ~iter
1125          (if inplaceof.[0] = '\\' then s else (s ^ tok));
1126        true
1127       with Virtuals.Not_a_virtual -> false
1128          
1129     val similar_memory = Hashtbl.create 97
1130     val mutable old_used_memory = false
1131
1132     method private nextSimilarSymbol () = 
1133       let write_similarsymbol s =
1134         let s = Glib.Utf8.from_unichar s in
1135         let iter = source_buffer#get_iter_at_mark `INSERT in
1136         assert(Glib.Utf8.validate s);
1137         source_buffer#delete ~start:iter ~stop:(iter#copy#backward_chars 1);
1138         source_buffer#insert ~iter:(source_buffer#get_iter_at_mark `INSERT) s;
1139         (try source_buffer#delete_mark similarsymbols_tag
1140          with GText.No_such_mark _ -> ());
1141         ignore(source_buffer#create_mark ~name:similarsymbols_tag_name
1142           (source_buffer#get_iter_at_mark `INSERT));
1143       in
1144       let new_similarsymbol =
1145         try
1146           let iter_ins = source_buffer#get_iter_at_mark `INSERT in
1147           let iter_lig = source_buffer#get_iter_at_mark similarsymbols_tag in
1148           not (iter_ins#equal iter_lig)
1149         with GText.No_such_mark _ -> true
1150       in
1151       if new_similarsymbol then
1152         (if not(self#expand_virtual_if_any (source_buffer#get_iter_at_mark `INSERT) "")then
1153           let last_symbol = 
1154             let i = source_buffer#get_iter_at_mark `INSERT in
1155             Glib.Utf8.first_char (i#get_slice ~stop:(i#copy#backward_chars 1))
1156           in
1157           (match Virtuals.similar_symbols last_symbol with
1158           | [] ->  ()
1159           | eqclass ->
1160               similarsymbols_orig <- eqclass;
1161               let is_used = 
1162                 try Hashtbl.find similar_memory similarsymbols_orig  
1163                 with Not_found -> 
1164                   let is_used = List.map (fun x -> x,false) eqclass in
1165                   Hashtbl.add similar_memory eqclass is_used; 
1166                   is_used
1167               in
1168               let hd, next, tl = 
1169                 let used, unused = 
1170                   List.partition (fun s -> List.assoc s is_used) eqclass 
1171                 in
1172                 match used @ unused with a::b::c -> a,b,c | _ -> assert false
1173               in
1174               let hd, tl = 
1175                 if hd = last_symbol then next, tl @ [hd] else hd, (next::tl)
1176               in
1177               old_used_memory <- List.assoc hd is_used;
1178               let is_used = 
1179                 (hd,true) :: List.filter (fun (x,_) -> x <> hd) is_used
1180               in
1181               Hashtbl.replace similar_memory similarsymbols_orig is_used;
1182               write_similarsymbol hd;
1183               similarsymbols <- tl @ [ hd ]))
1184       else 
1185         match similarsymbols with
1186         | [] -> ()
1187         | hd :: tl ->
1188             let is_used = Hashtbl.find similar_memory similarsymbols_orig in
1189             let last = HExtlib.list_last tl in
1190             let old_used_for_last = old_used_memory in
1191             old_used_memory <- List.assoc hd is_used;
1192             let is_used = 
1193               (hd, true) :: (last,old_used_for_last) ::
1194                 List.filter (fun (x,_) -> x <> last && x <> hd) is_used 
1195             in
1196             Hashtbl.replace similar_memory similarsymbols_orig is_used;
1197             similarsymbols <- tl @ [ hd ];
1198             write_similarsymbol hd
1199
1200     method private externalEditor () =
1201       let cmd = Helm_registry.get "matita.external_editor" in
1202 (* ZACK uncomment to enable interactive ask of external editor command *)
1203 (*      let cmd =
1204          let msg =
1205           "External editor command:
1206 %f  will be substitute for the script name,
1207 %p  for the cursor position in bytes,
1208 %l  for the execution point in bytes."
1209         in
1210         ask_text ~gui:self ~title:"External editor" ~msg ~multiline:false
1211           ~default:(Helm_registry.get "matita.external_editor") ()
1212       in *)
1213       let script = MatitaScript.current () in
1214       let fname = script#filename in
1215       let slice mark =
1216         source_buffer#start_iter#get_slice
1217           ~stop:(source_buffer#get_iter_at_mark mark)
1218       in
1219       let locked = `MARK script#locked_mark in
1220       let string_pos mark = string_of_int (String.length (slice mark)) in
1221       let cursor_pos = string_pos `INSERT in
1222       let locked_pos = string_pos locked in
1223       let cmd =
1224         Pcre.replace ~pat:"%f" ~templ:fname
1225           (Pcre.replace ~pat:"%p" ~templ:cursor_pos
1226             (Pcre.replace ~pat:"%l" ~templ:locked_pos
1227               cmd))
1228       in
1229       let locked_before = slice locked in
1230       let locked_offset = (source_buffer#get_iter_at_mark locked)#offset in
1231       ignore (Unix.system cmd);
1232       source_buffer#set_text (HExtlib.input_file fname);
1233       let locked_iter = source_buffer#get_iter (`OFFSET locked_offset) in
1234       source_buffer#move_mark locked locked_iter;
1235       source_buffer#apply_tag script#locked_tag
1236         ~start:source_buffer#start_iter ~stop:locked_iter;
1237       let locked_after = slice locked in
1238       let line = ref 0 in
1239       let col = ref 0 in
1240       try
1241         for i = 0 to String.length locked_before - 1 do
1242           if locked_before.[i] <> locked_after.[i] then begin
1243             source_buffer#place_cursor
1244               ~where:(source_buffer#get_iter (`LINEBYTE (!line, !col)));
1245             script#goto `Cursor ();
1246             raise Exit
1247           end else if locked_before.[i] = '\n' then begin
1248             incr line;
1249             col := 0
1250           end
1251         done
1252       with
1253       | Exit -> ()
1254       | Invalid_argument _ -> script#goto `Bottom ()
1255
1256     method loadScript file =       
1257       let script = MatitaScript.current () in
1258       script#reset (); 
1259       script#assignFileName (Some file);
1260       let file = script#filename in
1261       let content =
1262        if Sys.file_exists file then file
1263        else BuildTimeConf.script_template
1264       in
1265       source_view#source_buffer#begin_not_undoable_action ();
1266       script#loadFromFile content;
1267       source_view#source_buffer#end_not_undoable_action ();
1268       source_view#buffer#move_mark `INSERT source_view#buffer#start_iter;
1269       source_view#buffer#place_cursor source_view#buffer#start_iter;
1270       console#message ("'"^file^"' loaded.");
1271       self#_enableSaveTo file
1272       
1273     method setStar b =
1274       let s = MatitaScript.current () in
1275       let w = main#toplevel in
1276       let set x = w#set_title x in
1277       let name = 
1278         "Matita - " ^ Filename.basename s#filename ^ 
1279         (if b then "*" else "") ^
1280         " in " ^ s#buri_of_current_file 
1281       in
1282         set name
1283         
1284     method private _enableSaveTo file =
1285       self#main#saveMenuItem#misc#set_sensitive true
1286         
1287     method console = console
1288     method sourceView: GSourceView2.source_view =
1289       (source_view: GSourceView2.source_view)
1290     method fileSel = fileSel
1291     method findRepl = findRepl
1292     method main = main
1293
1294     method newBrowserWin () =
1295       object (self)
1296         inherit browserWin ()
1297         val combo = GEdit.entry ()
1298         initializer
1299           self#check_widgets ();
1300           let combo_widget = combo#coerce in
1301           uriHBox#pack ~from:`END ~fill:true ~expand:true combo_widget;
1302           combo#misc#grab_focus ()
1303         method browserUri = combo
1304       end
1305
1306     method newUriDialog () =
1307       let dialog = new uriChoiceDialog () in
1308       dialog#check_widgets ();
1309       dialog
1310
1311     method newConfirmationDialog () =
1312       let dialog = new confirmationDialog () in
1313       dialog#check_widgets ();
1314       dialog
1315
1316     method newEmptyDialog () =
1317       let dialog = new emptyDialog () in
1318       dialog#check_widgets ();
1319       dialog
1320
1321     method private addKeyBinding key callback =
1322       List.iter (fun evbox -> add_key_binding key callback evbox)
1323         keyBindingBoxes
1324
1325     method setQuitCallback callback =
1326       connect_menu_item main#quitMenuItem callback;
1327       ignore (main#toplevel#event#connect#delete 
1328         (fun _ -> callback ();true));
1329       self#addKeyBinding GdkKeysyms._q callback
1330
1331     method chooseFile ?(ok_not_exists = false) () =
1332       _ok_not_exists <- ok_not_exists;
1333       _only_directory <- false;
1334       fileSel#fileSelectionWin#show ();
1335       GtkThread.main ();
1336       chosen_file
1337
1338     method private chooseDir ?(ok_not_exists = false) () =
1339       _ok_not_exists <- ok_not_exists;
1340       _only_directory <- true;
1341       fileSel#fileSelectionWin#show ();
1342       GtkThread.main ();
1343       (* we should check that this is a directory *)
1344       chosen_file
1345   
1346     method askText ?(title = "") ?(msg = "") () =
1347       let dialog = new textDialog () in
1348       dialog#textDialog#set_title title;
1349       dialog#textDialogLabel#set_label msg;
1350       let text = ref None in
1351       let return v =
1352         text := v;
1353         dialog#textDialog#destroy ();
1354         GMain.Main.quit ()
1355       in
1356       ignore (dialog#textDialog#event#connect#delete (fun _ -> true));
1357       connect_button dialog#textDialogCancelButton (fun _ -> return None);
1358       connect_button dialog#textDialogOkButton (fun _ ->
1359         let text = dialog#textDialogTextView#buffer#get_text () in
1360         return (Some text));
1361       dialog#textDialog#show ();
1362       GtkThread.main ();
1363       !text
1364
1365     method private updateFontSize () =
1366       self#sourceView#misc#modify_font_by_name
1367         (sprintf "%s %d" BuildTimeConf.script_font font_size)
1368
1369     method increaseFontSize () =
1370       font_size <- font_size + 1;
1371       self#updateFontSize ()
1372
1373     method decreaseFontSize () =
1374       font_size <- font_size - 1;
1375       self#updateFontSize ()
1376
1377     method resetFontSize () =
1378       font_size <- default_font_size;
1379       self#updateFontSize ()
1380
1381   end
1382
1383 let gui () = 
1384   let g = new gui () in
1385   gui_instance := Some g;
1386   MatitaMathView.set_gui g;
1387   g
1388   
1389 let instance = singleton gui
1390
1391 let non p x = not (p x)
1392
1393 (* this is a shit and should be changed :-{ *)
1394 let interactive_uri_choice
1395   ?(selection_mode:[`SINGLE|`MULTIPLE] = `MULTIPLE) ?(title = "")
1396   ?(msg = "") ?(nonvars_button = false) ?(hide_uri_entry=false) 
1397   ?(hide_try=false) ?(ok_label="_Auto") ?(ok_action:[`SELECT|`AUTO] = `AUTO) 
1398   ?copy_cb ()
1399   ~id uris
1400 =
1401   let gui = instance () in
1402   let nonvars_uris = lazy (List.filter (non UriManager.uri_is_var) uris) in
1403   if (selection_mode <> `SINGLE) &&
1404     (Helm_registry.get_opt_default Helm_registry.get_bool ~default:true "matita.auto_disambiguation")
1405   then
1406     Lazy.force nonvars_uris
1407   else begin
1408     let dialog = gui#newUriDialog () in
1409     if hide_uri_entry then
1410       dialog#uriEntryHBox#misc#hide ();
1411     if hide_try then
1412       begin
1413       dialog#uriChoiceSelectedButton#misc#hide ();
1414       dialog#uriChoiceConstantsButton#misc#hide ();
1415       end;
1416     dialog#okLabel#set_label ok_label;  
1417     dialog#uriChoiceTreeView#selection#set_mode
1418       (selection_mode :> Gtk.Tags.selection_mode);
1419     let model = new stringListModel dialog#uriChoiceTreeView in
1420     let choices = ref None in
1421     (match copy_cb with
1422     | None -> ()
1423     | Some cb ->
1424         dialog#copyButton#misc#show ();
1425         connect_button dialog#copyButton 
1426         (fun _ ->
1427           match model#easy_selection () with
1428           | [u] -> (cb u)
1429           | _ -> ()));
1430     dialog#uriChoiceDialog#set_title title;
1431     dialog#uriChoiceLabel#set_text msg;
1432     List.iter model#easy_append (List.map UriManager.string_of_uri uris);
1433     dialog#uriChoiceConstantsButton#misc#set_sensitive nonvars_button;
1434     let return v =
1435       choices := v;
1436       dialog#uriChoiceDialog#destroy ();
1437       GMain.Main.quit ()
1438     in
1439     ignore (dialog#uriChoiceDialog#event#connect#delete (fun _ -> true));
1440     connect_button dialog#uriChoiceConstantsButton (fun _ ->
1441       return (Some (Lazy.force nonvars_uris)));
1442     if ok_action = `AUTO then
1443       connect_button dialog#uriChoiceAutoButton (fun _ ->
1444         Helm_registry.set_bool "matita.auto_disambiguation" true;
1445         return (Some (Lazy.force nonvars_uris)))
1446     else
1447       connect_button dialog#uriChoiceAutoButton (fun _ ->
1448         match model#easy_selection () with
1449         | [] -> ()
1450         | uris -> return (Some (List.map UriManager.uri_of_string uris)));
1451     connect_button dialog#uriChoiceSelectedButton (fun _ ->
1452       match model#easy_selection () with
1453       | [] -> ()
1454       | uris -> return (Some (List.map UriManager.uri_of_string uris)));
1455     connect_button dialog#uriChoiceAbortButton (fun _ -> return None);
1456     dialog#uriChoiceDialog#show ();
1457     GtkThread.main ();
1458     (match !choices with 
1459     | None -> raise MatitaTypes.Cancel
1460     | Some uris -> uris)
1461   end
1462
1463 class interpModel =
1464   let cols = new GTree.column_list in
1465   let id_col = cols#add Gobject.Data.string in
1466   let dsc_col = cols#add Gobject.Data.string in
1467   let interp_no_col = cols#add Gobject.Data.int in
1468   let tree_store = GTree.tree_store cols in
1469   let id_renderer = GTree.cell_renderer_text [], ["text", id_col] in
1470   let dsc_renderer = GTree.cell_renderer_text [], ["text", dsc_col] in
1471   let id_view_col = GTree.view_column ~renderer:id_renderer () in
1472   let dsc_view_col = GTree.view_column ~renderer:dsc_renderer () in
1473   fun tree_view choices ->
1474     object
1475       initializer
1476         tree_view#set_model (Some (tree_store :> GTree.model));
1477         ignore (tree_view#append_column id_view_col);
1478         ignore (tree_view#append_column dsc_view_col);
1479         let name_of_interp =
1480           (* try to find a reasonable name for an interpretation *)
1481           let idx = ref 0 in
1482           fun interp ->
1483             try
1484               List.assoc "0" interp
1485             with Not_found ->
1486               incr idx; string_of_int !idx
1487         in
1488         tree_store#clear ();
1489         let idx = ref ~-1 in
1490         List.iter
1491           (fun interp ->
1492             incr idx;
1493             let interp_row = tree_store#append () in
1494             tree_store#set ~row:interp_row ~column:id_col
1495               (name_of_interp interp);
1496             tree_store#set ~row:interp_row ~column:interp_no_col !idx;
1497             List.iter
1498               (fun (id, dsc) ->
1499                 let row = tree_store#append ~parent:interp_row () in
1500                 tree_store#set ~row ~column:id_col id;
1501                 tree_store#set ~row ~column:dsc_col dsc;
1502                 tree_store#set ~row ~column:interp_no_col !idx)
1503               interp)
1504           choices
1505
1506       method get_interp_no tree_path =
1507         let iter = tree_store#get_iter tree_path in
1508         tree_store#get ~row:iter ~column:interp_no_col
1509     end
1510
1511
1512 let interactive_string_choice 
1513   text prefix_len ?(title = "") ?(msg = "") () ~id locs uris 
1514
1515   let gui = instance () in
1516     let dialog = gui#newUriDialog () in
1517     dialog#uriEntryHBox#misc#hide ();
1518     dialog#uriChoiceSelectedButton#misc#hide ();
1519     dialog#uriChoiceAutoButton#misc#hide ();
1520     dialog#uriChoiceConstantsButton#misc#hide ();
1521     dialog#uriChoiceTreeView#selection#set_mode
1522       (`SINGLE :> Gtk.Tags.selection_mode);
1523     let model = new stringListModel dialog#uriChoiceTreeView in
1524     let choices = ref None in
1525     dialog#uriChoiceDialog#set_title title; 
1526     let hack_len = MatitaGtkMisc.utf8_string_length text in
1527     let rec colorize acc_len = function
1528       | [] -> 
1529           let floc = HExtlib.floc_of_loc (acc_len,hack_len) in
1530           escape_pango_markup (fst(MatitaGtkMisc.utf8_parsed_text text floc))
1531       | he::tl -> 
1532           let start, stop =  HExtlib.loc_of_floc he in
1533           let floc1 = HExtlib.floc_of_loc (acc_len,start) in
1534           let str1,_=MatitaGtkMisc.utf8_parsed_text text floc1 in
1535           let str2,_ = MatitaGtkMisc.utf8_parsed_text text he in
1536           escape_pango_markup str1 ^ "<b>" ^ 
1537           escape_pango_markup str2 ^ "</b>" ^ 
1538           colorize stop tl
1539     in
1540 (*     List.iter (fun l -> let start, stop = HExtlib.loc_of_floc l in
1541                 Printf.eprintf "(%d,%d)" start stop) locs; *)
1542     let locs = 
1543       List.sort 
1544         (fun loc1 loc2 -> 
1545           fst (HExtlib.loc_of_floc loc1) - fst (HExtlib.loc_of_floc loc2)) 
1546         locs 
1547     in
1548 (*     prerr_endline "XXXXXXXXXXXXXXXXXXXX";
1549     List.iter (fun l -> let start, stop = HExtlib.loc_of_floc l in
1550                 Printf.eprintf "(%d,%d)" start stop) locs;
1551     prerr_endline "XXXXXXXXXXXXXXXXXXXX2"; *)
1552     dialog#uriChoiceLabel#set_use_markup true;
1553     let txt = colorize 0 locs in
1554     let txt,_ = MatitaGtkMisc.utf8_parsed_text txt
1555       (HExtlib.floc_of_loc (prefix_len,MatitaGtkMisc.utf8_string_length txt))
1556     in
1557     dialog#uriChoiceLabel#set_label txt;
1558     List.iter model#easy_append uris;
1559     let return v =
1560       choices := v;
1561       dialog#uriChoiceDialog#destroy ();
1562       GMain.Main.quit ()
1563     in
1564     ignore (dialog#uriChoiceDialog#event#connect#delete (fun _ -> true));
1565     connect_button dialog#uriChoiceForwardButton (fun _ ->
1566       match model#easy_selection () with
1567       | [] -> ()
1568       | uris -> return (Some uris));
1569     connect_button dialog#uriChoiceAbortButton (fun _ -> return None);
1570     dialog#uriChoiceDialog#show ();
1571     GtkThread.main ();
1572     (match !choices with 
1573     | None -> raise MatitaTypes.Cancel
1574     | Some uris -> uris)
1575
1576 let interactive_interp_choice () text prefix_len choices =
1577 (*List.iter (fun l -> prerr_endline "==="; List.iter (fun (_,id,dsc) -> prerr_endline (id ^ " = " ^ dsc)) l) choices;*)
1578  let filter_choices filter =
1579   let rec is_compatible filter =
1580    function
1581       [] -> true
1582     | ([],_,_)::tl -> is_compatible filter tl
1583     | (loc::tlloc,id,dsc)::tl ->
1584        try
1585         if List.assoc (loc,id) filter = dsc then
1586          is_compatible filter ((tlloc,id,dsc)::tl)
1587         else
1588          false
1589        with
1590         Not_found -> true
1591   in
1592    List.filter (fun (_,interp) -> is_compatible filter interp)
1593  in
1594  let rec get_choices loc id =
1595   function
1596      [] -> []
1597    | (_,he)::tl ->
1598       let _,_,dsc =
1599        List.find (fun (locs,id',_) -> id = id' && List.mem loc locs) he
1600       in
1601        dsc :: (List.filter (fun dsc' -> dsc <> dsc') (get_choices loc id tl))
1602  in
1603  let example_interp =
1604   match choices with
1605      [] -> assert false
1606    | he::_ -> he in
1607  let ask_user id locs choices =
1608   interactive_string_choice
1609    text prefix_len
1610    ~title:"Ambiguous input"
1611    ~msg:("Choose an interpretation for " ^ id) () ~id locs choices
1612  in
1613  let rec classify ids filter partial_interpretations =
1614   match ids with
1615      [] -> List.map fst partial_interpretations
1616    | ([],_,_)::tl -> classify tl filter partial_interpretations
1617    | (loc::tlloc,id,dsc)::tl ->
1618       let choices = get_choices loc id partial_interpretations in
1619       let chosen_dsc =
1620        match choices with
1621           [] -> prerr_endline ("NO CHOICES FOR " ^ id); assert false
1622         | [dsc] -> dsc
1623         | _ ->
1624           match ask_user id [loc] choices with
1625              [x] -> x
1626            | _ -> assert false
1627       in
1628        let filter = ((loc,id),chosen_dsc)::filter in
1629        let compatible_interps = filter_choices filter partial_interpretations in
1630         classify ((tlloc,id,dsc)::tl) filter compatible_interps
1631  in
1632  let enumerated_choices =
1633   let idx = ref ~-1 in
1634   List.map (fun interp -> incr idx; !idx,interp) choices
1635  in
1636   classify example_interp [] enumerated_choices
1637
1638 let _ =
1639   (* disambiguator callbacks *)
1640   Disambiguate.set_choose_uris_callback
1641    (fun ~selection_mode ?ok ?(enable_button_for_non_vars=false) ~title ~msg ->
1642      interactive_uri_choice ~selection_mode ?ok_label:ok ~title ~msg ());
1643   Disambiguate.set_choose_interp_callback (interactive_interp_choice ());
1644   (* gtk initialization *)
1645   GtkMain.Rc.add_default_file BuildTimeConf.gtkrc_file; (* loads gtk rc *)
1646   ignore (GMain.Main.init ())
1647