]> matita.cs.unibo.it Git - helm.git/blob - helm/software/matita/matitaGui.ml
EXPERIMENTAL COMMIT (by CSC,actuall :-)
[helm.git] / helm / software / 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 [GrafiteTypes.get_baseuri grafite_status]
71
72 let save_moo grafite_status = 
73   let script = MatitaScript.current () in
74   let baseuri = GrafiteTypes.get_baseuri grafite_status in
75   let no_pstatus = 
76     grafite_status.GrafiteTypes.proof_status = GrafiteTypes.No_proof 
77   in
78   match script#bos, script#eos, no_pstatus with
79   | true, _, _ -> ()
80   | _, true, true ->
81      let moo_fname = 
82        LibraryMisc.obj_file_of_baseuri ~must_exist:false ~baseuri
83         ~writable:true in
84      let lexicon_fname =
85        LibraryMisc.lexicon_file_of_baseuri 
86          ~must_exist:false ~baseuri ~writable:true
87      in
88      GrafiteMarshal.save_moo moo_fname
89        grafite_status.GrafiteTypes.moo_content_rev;
90      LexiconMarshal.save_lexicon lexicon_fname
91        (GrafiteTypes.get_lexicon grafite_status).LexiconEngine.lexicon_content_rev;
92      NCicLibrary.serialize ~baseuri:(NUri.uri_of_string baseuri)
93       (GrafiteTypes.get_dump grafite_status)
94   | _ -> clean_current_baseuri grafite_status 
95 ;;
96     
97 let ask_unsaved parent =
98   MatitaGtkMisc.ask_confirmation 
99     ~parent ~title:"Unsaved work!" 
100     ~message:("Your work is <b>unsaved</b>!\n\n"^
101          "<i>Do you want to save the script before continuing?</i>")
102     ()
103
104 class interpErrorModel =
105   let cols = new GTree.column_list in
106   let id_col = cols#add Gobject.Data.string in
107   let dsc_col = cols#add Gobject.Data.string in
108   let interp_no_col = cols#add Gobject.Data.caml in
109   let tree_store = GTree.tree_store cols in
110   let id_renderer = GTree.cell_renderer_text [], ["text", id_col] in
111   let dsc_renderer = GTree.cell_renderer_text [], ["text", dsc_col] in
112   let id_view_col = GTree.view_column ~renderer:id_renderer () in
113   let dsc_view_col = GTree.view_column ~renderer:dsc_renderer () in
114   fun (tree_view: GTree.view) choices ->
115     object
116       initializer
117         tree_view#set_model (Some (tree_store :> GTree.model));
118         ignore (tree_view#append_column id_view_col);
119         ignore (tree_view#append_column dsc_view_col);
120         tree_store#clear ();
121         let idx1 = ref ~-1 in
122         List.iter
123           (fun _,lll ->
124             incr idx1;
125             let loc_row =
126              if List.length choices = 1 then
127               None
128              else
129               (let loc_row = tree_store#append () in
130                 begin
131                  match lll with
132                     [passes,envs_and_diffs,_,_] ->
133                       tree_store#set ~row:loc_row ~column:id_col
134                        ("Error location " ^ string_of_int (!idx1+1) ^
135                         ", error message " ^ string_of_int (!idx1+1) ^ ".1" ^
136                         " (in passes " ^
137                         String.concat " " (List.map string_of_int passes) ^
138                         ")");
139                       tree_store#set ~row:loc_row ~column:interp_no_col
140                        (!idx1,Some 0,None);
141                   | _ ->
142                     tree_store#set ~row:loc_row ~column:id_col
143                      ("Error location " ^ string_of_int (!idx1+1));
144                     tree_store#set ~row:loc_row ~column:interp_no_col
145                      (!idx1,None,None);
146                 end ;
147                 Some loc_row) in
148             let idx2 = ref ~-1 in
149              List.iter
150               (fun passes,envs_and_diffs,_,_ ->
151                 incr idx2;
152                 let msg_row =
153                  if List.length lll = 1 then
154                   loc_row
155                  else
156                   let msg_row = tree_store#append ?parent:loc_row () in
157                    (tree_store#set ~row:msg_row ~column:id_col
158                      ("Error message " ^ string_of_int (!idx1+1) ^ "." ^
159                       string_of_int (!idx2+1) ^
160                       " (in passes " ^
161                       String.concat " " (List.map string_of_int passes) ^
162                       ")");
163                     tree_store#set ~row:msg_row ~column:interp_no_col
164                      (!idx1,Some !idx2,None);
165                     Some msg_row) in
166                 let idx3 = ref ~-1 in
167                 List.iter
168                  (fun (passes,env,_) ->
169                    incr idx3;
170                    let interp_row =
171                     match envs_and_diffs with
172                        _::_::_ ->
173                         let interp_row = tree_store#append ?parent:msg_row () in
174                         tree_store#set ~row:interp_row ~column:id_col
175                           ("Interpretation " ^ string_of_int (!idx3+1) ^
176                            " (in passes " ^
177                            String.concat " " (List.map string_of_int passes) ^
178                            ")");
179                         tree_store#set ~row:interp_row ~column:interp_no_col
180                          (!idx1,Some !idx2,Some !idx3);
181                         Some interp_row
182                      | [_] -> msg_row
183                      | [] -> assert false
184                    in
185                     List.iter
186                      (fun (_, id, dsc) ->
187                        let row = tree_store#append ?parent:interp_row () in
188                        tree_store#set ~row ~column:id_col id;
189                        tree_store#set ~row ~column:dsc_col dsc;
190                        tree_store#set ~row ~column:interp_no_col
191                         (!idx1,Some !idx2,Some !idx3)
192                      ) env
193                  ) envs_and_diffs
194               ) lll ;
195              if List.length lll > 1 then
196               HExtlib.iter_option
197                (fun p -> tree_view#expand_row (tree_store#get_path p))
198                loc_row
199           ) choices
200
201       method get_interp_no tree_path =
202         let iter = tree_store#get_iter tree_path in
203         tree_store#get ~row:iter ~column:interp_no_col
204     end
205
206 exception UseLibrary;;
207
208 let rec interactive_error_interp ~all_passes
209   (source_buffer:GSourceView.source_buffer) notify_exn offset errorll filename
210
211   (* hook to save a script for each disambiguation error *)
212   if false then
213    (let text =
214      source_buffer#get_text ~start:source_buffer#start_iter
215       ~stop:source_buffer#end_iter () in
216     let md5 = Digest.to_hex (Digest.string text) in
217     let filename =
218      Filename.chop_extension filename ^ ".error." ^ md5 ^ ".ma"  in
219     let ch = open_out filename in
220      output_string ch text;
221     close_out ch
222    );
223   assert (List.flatten errorll <> []);
224   let errorll' =
225    let remove_non_significant =
226      List.filter (fun (_env,_diff,_loc_msg,significant) -> significant) in
227    let annotated_errorll () =
228     List.rev
229      (snd
230        (List.fold_left (fun (pass,res) item -> pass+1,(pass+1,item)::res) (0,[])
231          errorll)) in
232    if all_passes then annotated_errorll () else
233      let safe_list_nth l n = try List.nth l n with Failure _ -> [] in
234     (* We remove passes 1,2 and 5,6 *)
235      let res =
236       (1,[])::(2,[])
237       ::(3,remove_non_significant (safe_list_nth errorll 2))
238       ::(4,remove_non_significant (safe_list_nth errorll 3))
239       ::(5,[])::(6,[])::[]
240      in
241       if List.flatten (List.map snd res) <> [] then res
242       else
243        (* all errors (if any) are not significant: we keep them *)
244        let res =
245         (1,[])::(2,[])
246         ::(3,(safe_list_nth errorll 2))
247         ::(4,(safe_list_nth errorll 3))
248         ::(5,[])::(6,[])::[]
249        in
250         if List.flatten (List.map snd res) <> [] then
251          begin
252           HLog.warn
253            "All disambiguation errors are not significant. Showing them anyway." ;
254           res
255          end
256         else
257          begin
258           HLog.warn
259            "No errors in phases 2 and 3. Showing all errors in all phases" ;
260           annotated_errorll ()
261          end
262    in
263   let choices = MatitaExcPp.compact_disambiguation_errors all_passes errorll' in
264    match choices with
265       [] -> assert false
266     | [loffset,[_,envs_and_diffs,msg,significant]] ->
267         let _,env,diff = List.hd envs_and_diffs in
268          notify_exn
269           (MultiPassDisambiguator.DisambiguationError
270             (offset,[[env,diff,lazy (loffset,Lazy.force msg),significant]]));
271     | _::_ ->
272        let dialog = new disambiguationErrors () in
273        dialog#check_widgets ();
274        if all_passes then
275         dialog#disambiguationErrorsMoreErrors#misc#set_sensitive false;
276        let model = new interpErrorModel dialog#treeview choices in
277        dialog#disambiguationErrors#set_title "Disambiguation error";
278        dialog#disambiguationErrorsLabel#set_label
279         "Click on an error to see the corresponding message:";
280        ignore (dialog#treeview#connect#cursor_changed
281         (fun _ ->
282           let tree_path =
283            match fst (dialog#treeview#get_cursor ()) with
284               None -> assert false
285            | Some tp -> tp in
286           let idx1,idx2,idx3 = model#get_interp_no tree_path in
287           let loffset,lll = List.nth choices idx1 in
288           let _,envs_and_diffs,msg,significant =
289            match idx2 with
290               Some idx2 -> List.nth lll idx2
291             | None ->
292                 [],[],lazy "Multiple error messages. Please select one.",true
293           in
294           let _,env,diff =
295            match idx3 with
296               Some idx3 -> List.nth envs_and_diffs idx3
297             | None -> [],[],[] (* dymmy value, used *) in
298           let script = MatitaScript.current () in
299           let error_tag = script#error_tag in
300            source_buffer#remove_tag error_tag
301              ~start:source_buffer#start_iter
302              ~stop:source_buffer#end_iter;
303            notify_exn
304             (MultiPassDisambiguator.DisambiguationError
305               (offset,[[env,diff,lazy(loffset,Lazy.force msg),significant]]))
306            ));
307        let return _ =
308          dialog#disambiguationErrors#destroy ();
309          GMain.Main.quit ()
310        in
311        let fail _ = return () in
312        ignore(dialog#disambiguationErrors#event#connect#delete (fun _ -> true));
313        connect_button dialog#disambiguationErrorsOkButton
314         (fun _ ->
315           let tree_path =
316            match fst (dialog#treeview#get_cursor ()) with
317               None -> assert false
318            | Some tp -> tp in
319           let idx1,idx2,idx3 = model#get_interp_no tree_path in
320           let diff =
321            match idx2,idx3 with
322               Some idx2, Some idx3 ->
323                let _,lll = List.nth choices idx1 in
324                let _,envs_and_diffs,_,_ = List.nth lll idx2 in
325                let _,_,diff = List.nth envs_and_diffs idx3 in
326                 diff
327             | _,_ -> assert false
328           in
329            let newtxt =
330             String.concat "\n"
331              ("" ::
332                List.map
333                 (fun k,desc -> 
334                   let alias =
335                    match k with
336                    | DisambiguateTypes.Id id ->
337                        LexiconAst.Ident_alias (id, desc)
338                    | DisambiguateTypes.Symbol (symb, i)-> 
339                        LexiconAst.Symbol_alias (symb, i, desc)
340                    | DisambiguateTypes.Num i ->
341                        LexiconAst.Number_alias (i, desc)
342                   in
343                    LexiconAstPp.pp_alias alias)
344                 diff) ^ "\n"
345            in
346             source_buffer#insert
347              ~iter:
348                (source_buffer#get_iter_at_mark
349                 (`NAME "beginning_of_statement")) newtxt ;
350             return ()
351         );
352        connect_button dialog#disambiguationErrorsMoreErrors
353         (fun _ -> return () ; raise UseLibrary);
354        connect_button dialog#disambiguationErrorsCancelButton fail;
355        dialog#disambiguationErrors#show ();
356        GtkThread.main ()
357
358
359 (** Selection handling
360  * Two clipboards are used: "clipboard" and "primary".
361  * "primary" is used by X, when you hit the middle button mouse is content is
362  *    pasted between applications. In Matita this selection always contain the
363  *    textual version of the selected term.
364  * "clipboard" is used inside Matita only and support ATM two different targets:
365  *    "TERM" and "PATTERN", in the future other targets like "MATHMLCONTENT" may
366  *    be added
367  *)
368
369 class gui () =
370     (* creation order _is_ relevant for windows placement *)
371   let main = new mainWin () in
372   let fileSel = new fileSelectionWin () in
373   let findRepl = new findReplWin () in
374   let keyBindingBoxes = (* event boxes which should receive global key events *)
375     [ main#mainWinEventBox ]
376   in
377   let console = new console ~buffer:main#logTextView#buffer () in
378   let (source_view: GSourceView.source_view) =
379     GSourceView.source_view
380       ~auto_indent:true
381       ~insert_spaces_instead_of_tabs:true ~tabs_width:2
382       ~margin:80 ~show_margin:true
383       ~smart_home_end:true
384       ~packing:main#scriptScrolledWin#add
385       ()
386   in
387   let default_font_size =
388     Helm_registry.get_opt_default Helm_registry.int
389       ~default:BuildTimeConf.default_font_size "matita.font_size"
390   in
391   let similarsymbols_tag_name = "similarsymbolos" in
392   let similarsymbols_tag = `NAME similarsymbols_tag_name in
393   let source_buffer = source_view#source_buffer in
394   object (self)
395     val mutable chosen_file = None
396     val mutable _ok_not_exists = false
397     val mutable _only_directory = false
398     val mutable font_size = default_font_size
399     val mutable similarsymbols = []
400     val mutable similarsymbols_orig = []
401     val clipboard = GData.clipboard Gdk.Atom.clipboard
402     val primary = GData.clipboard Gdk.Atom.primary
403       
404     method private reset_similarsymbols =
405       similarsymbols <- []; 
406       similarsymbols_orig <- []; 
407       try source_buffer#delete_mark similarsymbols_tag
408       with GText.No_such_mark _ -> ()
409    
410     initializer
411       let s () = MatitaScript.current () in
412         (* glade's check widgets *)
413       List.iter (fun w -> w#check_widgets ())
414         (let c w = (w :> <check_widgets: unit -> unit>) in
415         [ c fileSel; c main; c findRepl]);
416         (* key bindings *)
417       List.iter (* global key bindings *)
418         (fun (key, callback) -> self#addKeyBinding key callback)
419 (*
420         [ GdkKeysyms._F3,
421             toggle_win ~check:main#showProofMenuItem proof#proofWin;
422           GdkKeysyms._F4,
423             toggle_win ~check:main#showCheckMenuItem check#checkWin;
424 *)
425         [ ];
426         (* about win *)
427       let parse_txt_file file =
428        let ch = open_in (BuildTimeConf.runtime_base_dir ^ "/" ^ file) in
429        let l_rev = ref [] in
430        try
431         while true do
432          l_rev := input_line ch :: !l_rev;
433         done;
434         assert false
435        with
436         End_of_file ->
437          close_in ch;
438          List.rev !l_rev in 
439       let about_dialog =
440        GWindow.about_dialog
441         ~authors:(parse_txt_file "AUTHORS")
442         (*~comments:"comments"*)
443         ~copyright:"Copyright (C) 2005, the HELM team"
444         ~license:(String.concat "\n" (parse_txt_file "LICENSE"))
445         ~logo:(GdkPixbuf.from_file (MatitaMisc.image_path "/matita_medium.png"))
446         ~name:"Matita"
447         ~version:BuildTimeConf.version
448         ~website:"http://matita.cs.unibo.it"
449         ()
450       in
451       ignore(about_dialog#connect#response (fun _ ->about_dialog#misc#hide ()));
452       connect_menu_item main#contentsMenuItem (fun () ->
453         if 0 = Sys.command "which gnome-help" then
454           let cmd =
455             sprintf "gnome-help ghelp://%s/C/matita.xml &" BuildTimeConf.help_dir
456           in
457            ignore (Sys.command cmd)
458         else
459           MatitaGtkMisc.report_error ~title:"help system error"
460            ~message:(
461               "The program gnome-help is not installed\n\n"^
462               "To browse the user manal it is necessary to install "^
463               "the gnome help syste (also known as yelp)") 
464            ~parent:main#toplevel ());
465       connect_menu_item main#aboutMenuItem about_dialog#present;
466         (* findRepl win *)
467       let show_find_Repl () = 
468         findRepl#toplevel#misc#show ();
469         findRepl#toplevel#misc#grab_focus ()
470       in
471       let hide_find_Repl () = findRepl#toplevel#misc#hide () in
472       let find_forward _ = 
473           let highlight start end_ =
474             source_buffer#move_mark `INSERT ~where:start;
475             source_buffer#move_mark `SEL_BOUND ~where:end_;
476             source_view#scroll_mark_onscreen `INSERT
477           in
478           let text = findRepl#findEntry#text in
479           let iter = source_buffer#get_iter `SEL_BOUND in
480           match iter#forward_search text with
481           | None -> 
482               (match source_buffer#start_iter#forward_search text with
483               | None -> ()
484               | Some (start,end_) -> highlight start end_)
485           | Some (start,end_) -> highlight start end_ 
486       in
487       let replace _ =
488         let text = findRepl#replaceEntry#text in
489         let ins = source_buffer#get_iter `INSERT in
490         let sel = source_buffer#get_iter `SEL_BOUND in
491         if ins#compare sel < 0 then 
492           begin
493             ignore(source_buffer#delete_selection ());
494             source_buffer#insert text
495           end
496       in
497       connect_button findRepl#findButton find_forward;
498       connect_button findRepl#findReplButton replace;
499       connect_button findRepl#cancelButton (fun _ -> hide_find_Repl ());
500       ignore(findRepl#toplevel#event#connect#delete 
501         ~callback:(fun _ -> hide_find_Repl ();true));
502       let safe_undo =
503        fun () ->
504         (* phase 1: we save the actual status of the marks and we undo *)
505         let locked_mark = `MARK ((MatitaScript.current ())#locked_mark) in
506         let locked_iter = source_view#buffer#get_iter_at_mark locked_mark in
507         let locked_iter_offset = locked_iter#offset in
508         let mark2 =
509          `MARK
510            (source_view#buffer#create_mark ~name:"lock_point"
511              ~left_gravity:true locked_iter) in
512         source_view#source_buffer#undo ();
513         (* phase 2: we save the cursor position and we redo, restoring
514            the previous status of all the marks *)
515         let cursor_iter = source_view#buffer#get_iter_at_mark `INSERT in
516         let mark =
517          `MARK
518            (source_view#buffer#create_mark ~name:"undo_point"
519              ~left_gravity:true cursor_iter)
520         in
521          source_view#source_buffer#redo ();
522          let mark_iter = source_view#buffer#get_iter_at_mark mark in
523          let mark2_iter = source_view#buffer#get_iter_at_mark mark2 in
524          let mark2_iter = mark2_iter#set_offset locked_iter_offset in
525           source_view#buffer#move_mark locked_mark ~where:mark2_iter;
526           source_view#buffer#delete_mark mark;
527           source_view#buffer#delete_mark mark2;
528           (* phase 3: if after the undo the cursor was in the locked area,
529              then we move it there again and we perform a goto *)
530           if mark_iter#offset < locked_iter_offset then
531            begin
532             source_view#buffer#move_mark `INSERT ~where:mark_iter;
533             (MatitaScript.current ())#goto `Cursor ();
534            end;
535           (* phase 4: we perform again the undo. This time we are sure that
536              the text to undo is not locked *)
537           source_view#source_buffer#undo ();
538           source_view#misc#grab_focus () in
539       let safe_redo =
540        fun () ->
541         (* phase 1: we save the actual status of the marks, we redo and
542            we undo *)
543         let locked_mark = `MARK ((MatitaScript.current ())#locked_mark) in
544         let locked_iter = source_view#buffer#get_iter_at_mark locked_mark in
545         let locked_iter_offset = locked_iter#offset in
546         let mark2 =
547          `MARK
548            (source_view#buffer#create_mark ~name:"lock_point"
549              ~left_gravity:true locked_iter) in
550         source_view#source_buffer#redo ();
551         source_view#source_buffer#undo ();
552         (* phase 2: we save the cursor position and we restore
553            the previous status of all the marks *)
554         let cursor_iter = source_view#buffer#get_iter_at_mark `INSERT in
555         let mark =
556          `MARK
557            (source_view#buffer#create_mark ~name:"undo_point"
558              ~left_gravity:true cursor_iter)
559         in
560          let mark_iter = source_view#buffer#get_iter_at_mark mark in
561          let mark2_iter = source_view#buffer#get_iter_at_mark mark2 in
562          let mark2_iter = mark2_iter#set_offset locked_iter_offset in
563           source_view#buffer#move_mark locked_mark ~where:mark2_iter;
564           source_view#buffer#delete_mark mark;
565           source_view#buffer#delete_mark mark2;
566           (* phase 3: if after the undo the cursor is in the locked area,
567              then we move it there again and we perform a goto *)
568           if mark_iter#offset < locked_iter_offset then
569            begin
570             source_view#buffer#move_mark `INSERT ~where:mark_iter;
571             (MatitaScript.current ())#goto `Cursor ();
572            end;
573           (* phase 4: we perform again the redo. This time we are sure that
574              the text to redo is not locked *)
575           source_view#source_buffer#redo ();
576           source_view#misc#grab_focus ()
577       in
578       connect_menu_item main#undoMenuItem safe_undo;
579       ignore(source_view#source_buffer#connect#can_undo
580         ~callback:main#undoMenuItem#misc#set_sensitive);
581       connect_menu_item main#redoMenuItem safe_redo;
582       ignore(source_view#source_buffer#connect#can_redo
583         ~callback:main#redoMenuItem#misc#set_sensitive);
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         match GSourceView.source_language_from_file BuildTimeConf.lang_file with
888         | None ->
889             HLog.warn (sprintf "can't load language file %s"
890               BuildTimeConf.lang_file)
891         | Some matita_lang ->
892             source_buffer#set_language matita_lang;
893             source_buffer#set_highlight true
894       in
895       let disableSave () =
896         (s())#assignFileName None;
897         main#saveMenuItem#misc#set_sensitive false
898       in
899       let saveAsScript () =
900         let script = s () in
901         match self#chooseFile ~ok_not_exists:true () with
902         | Some f -> 
903               HExtlib.touch f;
904               script#assignFileName (Some f);
905               script#saveToFile (); 
906               console#message ("'"^f^"' saved.\n");
907               self#_enableSaveTo f
908         | None -> ()
909       in
910       let saveScript () =
911         let script = s () in
912         if script#has_name then 
913           (script#saveToFile (); 
914           console#message ("'"^script#filename^"' saved.\n"))
915         else saveAsScript ()
916       in
917       let abandon_script () =
918         let grafite_status = (s ())#grafite_status in
919         if source_view#buffer#modified then
920           (match ask_unsaved main#toplevel with
921           | `YES -> saveScript ()
922           | `NO -> ()
923           | `CANCEL -> raise MatitaTypes.Cancel);
924         save_moo grafite_status
925       in
926       let loadScript () =
927         let script = s () in 
928         try 
929           match self#chooseFile () with
930           | Some f -> 
931               abandon_script ();
932               script#reset (); 
933               script#assignFileName (Some f);
934               source_view#source_buffer#begin_not_undoable_action ();
935               script#loadFromFile f; 
936               source_view#source_buffer#end_not_undoable_action ();
937               source_view#buffer#move_mark `INSERT source_view#buffer#start_iter;
938               source_view#buffer#place_cursor source_view#buffer#start_iter;
939               console#message ("'"^f^"' loaded.\n");
940               self#_enableSaveTo f
941           | None -> ()
942         with MatitaTypes.Cancel -> ()
943       in
944       let newScript () = 
945         abandon_script ();
946         source_view#source_buffer#begin_not_undoable_action ();
947         (s ())#reset (); 
948         (s ())#template (); 
949         source_view#source_buffer#end_not_undoable_action ();
950         disableSave ();
951         (s ())#assignFileName None
952       in
953       let cursor () =
954         source_buffer#place_cursor
955           (source_buffer#get_iter_at_mark (`NAME "locked")) in
956       let advance _ = (MatitaScript.current ())#advance (); cursor () in
957       let retract _ = (MatitaScript.current ())#retract (); cursor () in
958       let top _ = (MatitaScript.current ())#goto `Top (); cursor () in
959       let bottom _ = (MatitaScript.current ())#goto `Bottom (); cursor () in
960       let jump _ = (MatitaScript.current ())#goto `Cursor (); cursor () in
961       let advance = locker (keep_focus advance) in
962       let retract = locker (keep_focus retract) in
963       let top = locker (keep_focus top) in
964       let bottom = locker (keep_focus bottom) in
965       let jump = locker (keep_focus jump) in
966         (* quit *)
967       self#setQuitCallback (fun () -> 
968         let script = MatitaScript.current () in
969         if source_view#buffer#modified then
970           match ask_unsaved main#toplevel with
971           | `YES -> 
972                saveScript ();
973                save_moo script#grafite_status;
974                GMain.Main.quit ()
975           | `NO -> GMain.Main.quit ()
976           | `CANCEL -> ()
977         else 
978           (save_moo script#grafite_status;
979           GMain.Main.quit ()));
980       connect_button main#scriptAdvanceButton advance;
981       connect_button main#scriptRetractButton retract;
982       connect_button main#scriptTopButton top;
983       connect_button main#scriptBottomButton bottom;
984       connect_button main#scriptJumpButton jump;
985       connect_button main#scriptAbortButton kill_worker;
986       connect_menu_item main#scriptAdvanceMenuItem advance;
987       connect_menu_item main#scriptRetractMenuItem retract;
988       connect_menu_item main#scriptTopMenuItem top;
989       connect_menu_item main#scriptBottomMenuItem bottom;
990       connect_menu_item main#scriptJumpMenuItem jump;
991       connect_menu_item main#openMenuItem   loadScript;
992       connect_menu_item main#saveMenuItem   saveScript;
993       connect_menu_item main#saveAsMenuItem saveAsScript;
994       connect_menu_item main#newMenuItem    newScript;
995       connect_menu_item main#showCoercionsGraphMenuItem 
996         (fun _ -> 
997           let c = MatitaMathView.cicBrowser () in
998           c#load (`About `Coercions));
999       connect_menu_item main#showAutoGuiMenuItem 
1000         (fun _ -> MatitaAutoGui.auto_dialog Auto.get_auto_status);
1001       connect_menu_item main#showTermGrammarMenuItem 
1002         (fun _ -> 
1003           let c = MatitaMathView.cicBrowser () in
1004           c#load (`About `Grammar));
1005       connect_menu_item main#showUnicodeTable
1006         (fun _ -> 
1007           let c = MatitaMathView.cicBrowser () in
1008           c#load (`About `TeX));
1009          (* script monospace font stuff *)  
1010       self#updateFontSize ();
1011         (* debug menu *)
1012       main#debugMenu#misc#hide ();
1013         (* HBUGS *)
1014       main#hintNotebook#misc#hide ();
1015       (*
1016       main#hintLowImage#set_file (image_path "matita-bulb-low.png");
1017       main#hintMediumImage#set_file (image_path "matita-bulb-medium.png");
1018       main#hintHighImage#set_file (image_path "matita-bulb-high.png");
1019       *)
1020         (* focus *)
1021       self#sourceView#misc#grab_focus ();
1022         (* main win dimension *)
1023       let width = Gdk.Screen.width () in
1024       let height = Gdk.Screen.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        let iter = source_buffer#get_iter_at_mark `INSERT in
1121        assert(Glib.Utf8.validate s);
1122        source_buffer#delete ~start:iter 
1123          ~stop:(iter#copy#backward_chars
1124            (MatitaGtkMisc.utf8_string_length inplaceof + len));
1125        source_buffer#insert ~iter:(source_buffer#get_iter_at_mark `INSERT) 
1126          (if inplaceof.[0] = '\\' then s else (s ^ tok));
1127        true
1128       with Virtuals.Not_a_virtual -> false
1129          
1130     val similar_memory = Hashtbl.create 97
1131     val mutable old_used_memory = false
1132
1133     method private nextSimilarSymbol () = 
1134       let write_similarsymbol s =
1135         let s = Glib.Utf8.from_unichar s in
1136         let iter = source_buffer#get_iter_at_mark `INSERT in
1137         assert(Glib.Utf8.validate s);
1138         source_buffer#delete ~start:iter ~stop:(iter#copy#backward_chars 1);
1139         source_buffer#insert ~iter:(source_buffer#get_iter_at_mark `INSERT) s;
1140         (try source_buffer#delete_mark similarsymbols_tag
1141          with GText.No_such_mark _ -> ());
1142         ignore(source_buffer#create_mark ~name:similarsymbols_tag_name
1143           (source_buffer#get_iter_at_mark `INSERT));
1144       in
1145       let new_similarsymbol =
1146         try
1147           let iter_ins = source_buffer#get_iter_at_mark `INSERT in
1148           let iter_lig = source_buffer#get_iter_at_mark similarsymbols_tag in
1149           not (iter_ins#equal iter_lig)
1150         with GText.No_such_mark _ -> true
1151       in
1152       if new_similarsymbol then
1153         (if not(self#expand_virtual_if_any (source_buffer#get_iter_at_mark `INSERT) "")then
1154           let last_symbol = 
1155             let i = source_buffer#get_iter_at_mark `INSERT in
1156             Glib.Utf8.first_char (i#get_slice ~stop:(i#copy#backward_chars 1))
1157           in
1158           (match Virtuals.similar_symbols last_symbol with
1159           | [] ->  ()
1160           | eqclass ->
1161               similarsymbols_orig <- eqclass;
1162               let is_used = 
1163                 try Hashtbl.find similar_memory similarsymbols_orig  
1164                 with Not_found -> 
1165                   let is_used = List.map (fun x -> x,false) eqclass in
1166                   Hashtbl.add similar_memory eqclass is_used; 
1167                   is_used
1168               in
1169               let hd, next, tl = 
1170                 let used, unused = 
1171                   List.partition (fun s -> List.assoc s is_used) eqclass 
1172                 in
1173                 match used @ unused with a::b::c -> a,b,c | _ -> assert false
1174               in
1175               let hd, tl = 
1176                 if hd = last_symbol then next, tl @ [hd] else hd, (next::tl)
1177               in
1178               old_used_memory <- List.assoc hd is_used;
1179               let is_used = 
1180                 (hd,true) :: List.filter (fun (x,_) -> x <> hd) is_used
1181               in
1182               Hashtbl.replace similar_memory similarsymbols_orig is_used;
1183               write_similarsymbol hd;
1184               similarsymbols <- tl @ [ hd ]))
1185       else 
1186         match similarsymbols with
1187         | [] -> ()
1188         | hd :: tl ->
1189             let is_used = Hashtbl.find similar_memory similarsymbols_orig in
1190             let last = HExtlib.list_last tl in
1191             let old_used_for_last = old_used_memory in
1192             old_used_memory <- List.assoc hd is_used;
1193             let is_used = 
1194               (hd, true) :: (last,old_used_for_last) ::
1195                 List.filter (fun (x,_) -> x <> last && x <> hd) is_used 
1196             in
1197             Hashtbl.replace similar_memory similarsymbols_orig is_used;
1198             similarsymbols <- tl @ [ hd ];
1199             write_similarsymbol hd
1200
1201     method private externalEditor () =
1202       let cmd = Helm_registry.get "matita.external_editor" in
1203 (* ZACK uncomment to enable interactive ask of external editor command *)
1204 (*      let cmd =
1205          let msg =
1206           "External editor command:
1207 %f  will be substitute for the script name,
1208 %p  for the cursor position in bytes,
1209 %l  for the execution point in bytes."
1210         in
1211         ask_text ~gui:self ~title:"External editor" ~msg ~multiline:false
1212           ~default:(Helm_registry.get "matita.external_editor") ()
1213       in *)
1214       let script = MatitaScript.current () in
1215       let fname = script#filename in
1216       let slice mark =
1217         source_buffer#start_iter#get_slice
1218           ~stop:(source_buffer#get_iter_at_mark mark)
1219       in
1220       let locked = `MARK script#locked_mark in
1221       let string_pos mark = string_of_int (String.length (slice mark)) in
1222       let cursor_pos = string_pos `INSERT in
1223       let locked_pos = string_pos locked in
1224       let cmd =
1225         Pcre.replace ~pat:"%f" ~templ:fname
1226           (Pcre.replace ~pat:"%p" ~templ:cursor_pos
1227             (Pcre.replace ~pat:"%l" ~templ:locked_pos
1228               cmd))
1229       in
1230       let locked_before = slice locked in
1231       let locked_offset = (source_buffer#get_iter_at_mark locked)#offset in
1232       ignore (Unix.system cmd);
1233       source_buffer#set_text (HExtlib.input_file fname);
1234       let locked_iter = source_buffer#get_iter (`OFFSET locked_offset) in
1235       source_buffer#move_mark locked locked_iter;
1236       source_buffer#apply_tag script#locked_tag
1237         ~start:source_buffer#start_iter ~stop:locked_iter;
1238       let locked_after = slice locked in
1239       let line = ref 0 in
1240       let col = ref 0 in
1241       try
1242         for i = 0 to String.length locked_before - 1 do
1243           if locked_before.[i] <> locked_after.[i] then begin
1244             source_buffer#place_cursor
1245               ~where:(source_buffer#get_iter (`LINEBYTE (!line, !col)));
1246             script#goto `Cursor ();
1247             raise Exit
1248           end else if locked_before.[i] = '\n' then begin
1249             incr line;
1250             col := 0
1251           end
1252         done
1253       with
1254       | Exit -> ()
1255       | Invalid_argument _ -> script#goto `Bottom ()
1256
1257     method loadScript file =       
1258       let script = MatitaScript.current () in
1259       script#reset (); 
1260       script#assignFileName (Some file);
1261       let file = script#filename in
1262       let content =
1263        if Sys.file_exists file then file
1264        else BuildTimeConf.script_template
1265       in
1266       source_view#source_buffer#begin_not_undoable_action ();
1267       script#loadFromFile content;
1268       source_view#source_buffer#end_not_undoable_action ();
1269       source_view#buffer#move_mark `INSERT source_view#buffer#start_iter;
1270       source_view#buffer#place_cursor source_view#buffer#start_iter;
1271       console#message ("'"^file^"' loaded.");
1272       self#_enableSaveTo file
1273       
1274     method setStar b =
1275       let s = MatitaScript.current () in
1276       let w = main#toplevel in
1277       let set x = w#set_title x in
1278       let name = 
1279         "Matita - " ^ Filename.basename s#filename ^ 
1280         (if b then "*" else "") ^
1281         " in " ^ s#buri_of_current_file 
1282       in
1283         set name
1284         
1285     method private _enableSaveTo file =
1286       self#main#saveMenuItem#misc#set_sensitive true
1287         
1288     method console = console
1289     method sourceView: GSourceView.source_view =
1290       (source_view: GSourceView.source_view)
1291     method fileSel = fileSel
1292     method findRepl = findRepl
1293     method main = main
1294
1295     method newBrowserWin () =
1296       object (self)
1297         inherit browserWin ()
1298         val combo = GEdit.entry ()
1299         initializer
1300           self#check_widgets ();
1301           let combo_widget = combo#coerce in
1302           uriHBox#pack ~from:`END ~fill:true ~expand:true combo_widget;
1303           combo#misc#grab_focus ()
1304         method browserUri = combo
1305       end
1306
1307     method newUriDialog () =
1308       let dialog = new uriChoiceDialog () in
1309       dialog#check_widgets ();
1310       dialog
1311
1312     method newConfirmationDialog () =
1313       let dialog = new confirmationDialog () in
1314       dialog#check_widgets ();
1315       dialog
1316
1317     method newEmptyDialog () =
1318       let dialog = new emptyDialog () in
1319       dialog#check_widgets ();
1320       dialog
1321
1322     method private addKeyBinding key callback =
1323       List.iter (fun evbox -> add_key_binding key callback evbox)
1324         keyBindingBoxes
1325
1326     method setQuitCallback callback =
1327       connect_menu_item main#quitMenuItem callback;
1328       ignore (main#toplevel#event#connect#delete 
1329         (fun _ -> callback ();true));
1330       self#addKeyBinding GdkKeysyms._q callback
1331
1332     method chooseFile ?(ok_not_exists = false) () =
1333       _ok_not_exists <- ok_not_exists;
1334       _only_directory <- false;
1335       fileSel#fileSelectionWin#show ();
1336       GtkThread.main ();
1337       chosen_file
1338
1339     method private chooseDir ?(ok_not_exists = false) () =
1340       _ok_not_exists <- ok_not_exists;
1341       _only_directory <- true;
1342       fileSel#fileSelectionWin#show ();
1343       GtkThread.main ();
1344       (* we should check that this is a directory *)
1345       chosen_file
1346   
1347     method askText ?(title = "") ?(msg = "") () =
1348       let dialog = new textDialog () in
1349       dialog#textDialog#set_title title;
1350       dialog#textDialogLabel#set_label msg;
1351       let text = ref None in
1352       let return v =
1353         text := v;
1354         dialog#textDialog#destroy ();
1355         GMain.Main.quit ()
1356       in
1357       ignore (dialog#textDialog#event#connect#delete (fun _ -> true));
1358       connect_button dialog#textDialogCancelButton (fun _ -> return None);
1359       connect_button dialog#textDialogOkButton (fun _ ->
1360         let text = dialog#textDialogTextView#buffer#get_text () in
1361         return (Some text));
1362       dialog#textDialog#show ();
1363       GtkThread.main ();
1364       !text
1365
1366     method private updateFontSize () =
1367       self#sourceView#misc#modify_font_by_name
1368         (sprintf "%s %d" BuildTimeConf.script_font font_size);
1369       MatitaAutoGui.set_font_size font_size
1370
1371     method increaseFontSize () =
1372       font_size <- font_size + 1;
1373       self#updateFontSize ()
1374
1375     method decreaseFontSize () =
1376       font_size <- font_size - 1;
1377       self#updateFontSize ()
1378
1379     method resetFontSize () =
1380       font_size <- default_font_size;
1381       self#updateFontSize ()
1382
1383   end
1384
1385 let gui () = 
1386   let g = new gui () in
1387   gui_instance := Some g;
1388   MatitaMathView.set_gui g;
1389   g
1390   
1391 let instance = singleton gui
1392
1393 let non p x = not (p x)
1394
1395 (* this is a shit and should be changed :-{ *)
1396 let interactive_uri_choice
1397   ?(selection_mode:[`SINGLE|`MULTIPLE] = `MULTIPLE) ?(title = "")
1398   ?(msg = "") ?(nonvars_button = false) ?(hide_uri_entry=false) 
1399   ?(hide_try=false) ?(ok_label="_Auto") ?(ok_action:[`SELECT|`AUTO] = `AUTO) 
1400   ?copy_cb ()
1401   ~id uris
1402 =
1403   let gui = instance () in
1404   let nonvars_uris = lazy (List.filter (non UriManager.uri_is_var) uris) in
1405   if (selection_mode <> `SINGLE) &&
1406     (Helm_registry.get_opt_default Helm_registry.get_bool ~default:true "matita.auto_disambiguation")
1407   then
1408     Lazy.force nonvars_uris
1409   else begin
1410     let dialog = gui#newUriDialog () in
1411     if hide_uri_entry then
1412       dialog#uriEntryHBox#misc#hide ();
1413     if hide_try then
1414       begin
1415       dialog#uriChoiceSelectedButton#misc#hide ();
1416       dialog#uriChoiceConstantsButton#misc#hide ();
1417       end;
1418     dialog#okLabel#set_label ok_label;  
1419     dialog#uriChoiceTreeView#selection#set_mode
1420       (selection_mode :> Gtk.Tags.selection_mode);
1421     let model = new stringListModel dialog#uriChoiceTreeView in
1422     let choices = ref None in
1423     (match copy_cb with
1424     | None -> ()
1425     | Some cb ->
1426         dialog#copyButton#misc#show ();
1427         connect_button dialog#copyButton 
1428         (fun _ ->
1429           match model#easy_selection () with
1430           | [u] -> (cb u)
1431           | _ -> ()));
1432     dialog#uriChoiceDialog#set_title title;
1433     dialog#uriChoiceLabel#set_text msg;
1434     List.iter model#easy_append (List.map UriManager.string_of_uri uris);
1435     dialog#uriChoiceConstantsButton#misc#set_sensitive nonvars_button;
1436     let return v =
1437       choices := v;
1438       dialog#uriChoiceDialog#destroy ();
1439       GMain.Main.quit ()
1440     in
1441     ignore (dialog#uriChoiceDialog#event#connect#delete (fun _ -> true));
1442     connect_button dialog#uriChoiceConstantsButton (fun _ ->
1443       return (Some (Lazy.force nonvars_uris)));
1444     if ok_action = `AUTO then
1445       connect_button dialog#uriChoiceAutoButton (fun _ ->
1446         Helm_registry.set_bool "matita.auto_disambiguation" true;
1447         return (Some (Lazy.force nonvars_uris)))
1448     else
1449       connect_button dialog#uriChoiceAutoButton (fun _ ->
1450         match model#easy_selection () with
1451         | [] -> ()
1452         | uris -> return (Some (List.map UriManager.uri_of_string uris)));
1453     connect_button dialog#uriChoiceSelectedButton (fun _ ->
1454       match model#easy_selection () with
1455       | [] -> ()
1456       | uris -> return (Some (List.map UriManager.uri_of_string uris)));
1457     connect_button dialog#uriChoiceAbortButton (fun _ -> return None);
1458     dialog#uriChoiceDialog#show ();
1459     GtkThread.main ();
1460     (match !choices with 
1461     | None -> raise MatitaTypes.Cancel
1462     | Some uris -> uris)
1463   end
1464
1465 class interpModel =
1466   let cols = new GTree.column_list in
1467   let id_col = cols#add Gobject.Data.string in
1468   let dsc_col = cols#add Gobject.Data.string in
1469   let interp_no_col = cols#add Gobject.Data.int in
1470   let tree_store = GTree.tree_store cols in
1471   let id_renderer = GTree.cell_renderer_text [], ["text", id_col] in
1472   let dsc_renderer = GTree.cell_renderer_text [], ["text", dsc_col] in
1473   let id_view_col = GTree.view_column ~renderer:id_renderer () in
1474   let dsc_view_col = GTree.view_column ~renderer:dsc_renderer () in
1475   fun tree_view choices ->
1476     object
1477       initializer
1478         tree_view#set_model (Some (tree_store :> GTree.model));
1479         ignore (tree_view#append_column id_view_col);
1480         ignore (tree_view#append_column dsc_view_col);
1481         let name_of_interp =
1482           (* try to find a reasonable name for an interpretation *)
1483           let idx = ref 0 in
1484           fun interp ->
1485             try
1486               List.assoc "0" interp
1487             with Not_found ->
1488               incr idx; string_of_int !idx
1489         in
1490         tree_store#clear ();
1491         let idx = ref ~-1 in
1492         List.iter
1493           (fun interp ->
1494             incr idx;
1495             let interp_row = tree_store#append () in
1496             tree_store#set ~row:interp_row ~column:id_col
1497               (name_of_interp interp);
1498             tree_store#set ~row:interp_row ~column:interp_no_col !idx;
1499             List.iter
1500               (fun (id, dsc) ->
1501                 let row = tree_store#append ~parent:interp_row () in
1502                 tree_store#set ~row ~column:id_col id;
1503                 tree_store#set ~row ~column:dsc_col dsc;
1504                 tree_store#set ~row ~column:interp_no_col !idx)
1505               interp)
1506           choices
1507
1508       method get_interp_no tree_path =
1509         let iter = tree_store#get_iter tree_path in
1510         tree_store#get ~row:iter ~column:interp_no_col
1511     end
1512
1513
1514 let interactive_string_choice 
1515   text prefix_len ?(title = "") ?(msg = "") () ~id locs uris 
1516
1517   let gui = instance () in
1518     let dialog = gui#newUriDialog () in
1519     dialog#uriEntryHBox#misc#hide ();
1520     dialog#uriChoiceSelectedButton#misc#hide ();
1521     dialog#uriChoiceAutoButton#misc#hide ();
1522     dialog#uriChoiceConstantsButton#misc#hide ();
1523     dialog#uriChoiceTreeView#selection#set_mode
1524       (`SINGLE :> Gtk.Tags.selection_mode);
1525     let model = new stringListModel dialog#uriChoiceTreeView in
1526     let choices = ref None in
1527     dialog#uriChoiceDialog#set_title title; 
1528     let hack_len = MatitaGtkMisc.utf8_string_length text in
1529     let rec colorize acc_len = function
1530       | [] -> 
1531           let floc = HExtlib.floc_of_loc (acc_len,hack_len) in
1532           escape_pango_markup (fst(MatitaGtkMisc.utf8_parsed_text text floc))
1533       | he::tl -> 
1534           let start, stop =  HExtlib.loc_of_floc he in
1535           let floc1 = HExtlib.floc_of_loc (acc_len,start) in
1536           let str1,_=MatitaGtkMisc.utf8_parsed_text text floc1 in
1537           let str2,_ = MatitaGtkMisc.utf8_parsed_text text he in
1538           escape_pango_markup str1 ^ "<b>" ^ 
1539           escape_pango_markup str2 ^ "</b>" ^ 
1540           colorize stop tl
1541     in
1542 (*     List.iter (fun l -> let start, stop = HExtlib.loc_of_floc l in
1543                 Printf.eprintf "(%d,%d)" start stop) locs; *)
1544     let locs = 
1545       List.sort 
1546         (fun loc1 loc2 -> 
1547           fst (HExtlib.loc_of_floc loc1) - fst (HExtlib.loc_of_floc loc2)) 
1548         locs 
1549     in
1550 (*     prerr_endline "XXXXXXXXXXXXXXXXXXXX";
1551     List.iter (fun l -> let start, stop = HExtlib.loc_of_floc l in
1552                 Printf.eprintf "(%d,%d)" start stop) locs;
1553     prerr_endline "XXXXXXXXXXXXXXXXXXXX2"; *)
1554     dialog#uriChoiceLabel#set_use_markup true;
1555     let txt = colorize 0 locs in
1556     let txt,_ = MatitaGtkMisc.utf8_parsed_text txt
1557       (HExtlib.floc_of_loc (prefix_len,MatitaGtkMisc.utf8_string_length txt))
1558     in
1559     dialog#uriChoiceLabel#set_label txt;
1560     List.iter model#easy_append uris;
1561     let return v =
1562       choices := v;
1563       dialog#uriChoiceDialog#destroy ();
1564       GMain.Main.quit ()
1565     in
1566     ignore (dialog#uriChoiceDialog#event#connect#delete (fun _ -> true));
1567     connect_button dialog#uriChoiceForwardButton (fun _ ->
1568       match model#easy_selection () with
1569       | [] -> ()
1570       | uris -> return (Some uris));
1571     connect_button dialog#uriChoiceAbortButton (fun _ -> return None);
1572     dialog#uriChoiceDialog#show ();
1573     GtkThread.main ();
1574     (match !choices with 
1575     | None -> raise MatitaTypes.Cancel
1576     | Some uris -> uris)
1577
1578 let interactive_interp_choice () text prefix_len choices =
1579 (*List.iter (fun l -> prerr_endline "==="; List.iter (fun (_,id,dsc) -> prerr_endline (id ^ " = " ^ dsc)) l) choices;*)
1580  let filter_choices filter =
1581   let rec is_compatible filter =
1582    function
1583       [] -> true
1584     | ([],_,_)::tl -> is_compatible filter tl
1585     | (loc::tlloc,id,dsc)::tl ->
1586        try
1587         if List.assoc (loc,id) filter = dsc then
1588          is_compatible filter ((tlloc,id,dsc)::tl)
1589         else
1590          false
1591        with
1592         Not_found -> true
1593   in
1594    List.filter (fun (_,interp) -> is_compatible filter interp)
1595  in
1596  let rec get_choices loc id =
1597   function
1598      [] -> []
1599    | (_,he)::tl ->
1600       let _,_,dsc =
1601        List.find (fun (locs,id',_) -> id = id' && List.mem loc locs) he
1602       in
1603        dsc :: (List.filter (fun dsc' -> dsc <> dsc') (get_choices loc id tl))
1604  in
1605  let example_interp =
1606   match choices with
1607      [] -> assert false
1608    | he::_ -> he in
1609  let ask_user id locs choices =
1610   interactive_string_choice
1611    text prefix_len
1612    ~title:"Ambiguous input"
1613    ~msg:("Choose an interpretation for " ^ id) () ~id locs choices
1614  in
1615  let rec classify ids filter partial_interpretations =
1616   match ids with
1617      [] -> List.map fst partial_interpretations
1618    | ([],_,_)::tl -> classify tl filter partial_interpretations
1619    | (loc::tlloc,id,dsc)::tl ->
1620       let choices = get_choices loc id partial_interpretations in
1621       let chosen_dsc =
1622        match choices with
1623           [] -> prerr_endline ("NO CHOICES FOR " ^ id); assert false
1624         | [dsc] -> dsc
1625         | _ ->
1626           match ask_user id [loc] choices with
1627              [x] -> x
1628            | _ -> assert false
1629       in
1630        let filter = ((loc,id),chosen_dsc)::filter in
1631        let compatible_interps = filter_choices filter partial_interpretations in
1632         classify ((tlloc,id,dsc)::tl) filter compatible_interps
1633  in
1634  let enumerated_choices =
1635   let idx = ref ~-1 in
1636   List.map (fun interp -> incr idx; !idx,interp) choices
1637  in
1638   classify example_interp [] enumerated_choices
1639
1640 let _ =
1641   (* disambiguator callbacks *)
1642   Disambiguate.set_choose_uris_callback
1643    (fun ~selection_mode ?ok ?(enable_button_for_non_vars=false) ~title ~msg ->
1644      interactive_uri_choice ~selection_mode ?ok_label:ok ~title ~msg ());
1645   Disambiguate.set_choose_interp_callback (interactive_interp_choice ());
1646   (* gtk initialization *)
1647   GtkMain.Rc.add_default_file BuildTimeConf.gtkrc_file; (* loads gtk rc *)
1648   GMathView.add_configuration_path BuildTimeConf.gtkmathview_conf;
1649   ignore (GMain.Main.init ())
1650