]> matita.cs.unibo.it Git - helm.git/blob - matita/matita/matitaGui.ml
Large commit: refactoring of the code of the interface.
[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      GrafiteTypes.Serializer.serialize ~baseuri:(NUri.uri_of_string baseuri)
79       grafite_status
80   | _ -> clean_current_baseuri grafite_status 
81 ;;
82     
83 let ask_unsaved parent =
84   MatitaGtkMisc.ask_confirmation 
85     ~parent ~title:"Unsaved work!" 
86     ~message:("Your work is <b>unsaved</b>!\n\n"^
87          "<i>Do you want to save the script before continuing?</i>")
88     ()
89
90 class interpErrorModel =
91   let cols = new GTree.column_list in
92   let id_col = cols#add Gobject.Data.string in
93   let dsc_col = cols#add Gobject.Data.string in
94   let interp_no_col = cols#add Gobject.Data.caml in
95   let tree_store = GTree.tree_store cols in
96   let id_renderer = GTree.cell_renderer_text [], ["text", id_col] in
97   let dsc_renderer = GTree.cell_renderer_text [], ["text", dsc_col] in
98   let id_view_col = GTree.view_column ~renderer:id_renderer () in
99   let dsc_view_col = GTree.view_column ~renderer:dsc_renderer () in
100   fun (tree_view: GTree.view) choices ->
101     object
102       initializer
103         tree_view#set_model (Some (tree_store :> GTree.model));
104         ignore (tree_view#append_column id_view_col);
105         ignore (tree_view#append_column dsc_view_col);
106         tree_store#clear ();
107         let idx1 = ref ~-1 in
108         List.iter
109           (fun _,lll ->
110             incr idx1;
111             let loc_row =
112              if List.length choices = 1 then
113               None
114              else
115               (let loc_row = tree_store#append () in
116                 begin
117                  match lll with
118                     [passes,envs_and_diffs,_,_] ->
119                       tree_store#set ~row:loc_row ~column:id_col
120                        ("Error location " ^ string_of_int (!idx1+1) ^
121                         ", error message " ^ string_of_int (!idx1+1) ^ ".1" ^
122                         " (in passes " ^
123                         String.concat " " (List.map string_of_int passes) ^
124                         ")");
125                       tree_store#set ~row:loc_row ~column:interp_no_col
126                        (!idx1,Some 0,None);
127                   | _ ->
128                     tree_store#set ~row:loc_row ~column:id_col
129                      ("Error location " ^ string_of_int (!idx1+1));
130                     tree_store#set ~row:loc_row ~column:interp_no_col
131                      (!idx1,None,None);
132                 end ;
133                 Some loc_row) in
134             let idx2 = ref ~-1 in
135              List.iter
136               (fun passes,envs_and_diffs,_,_ ->
137                 incr idx2;
138                 let msg_row =
139                  if List.length lll = 1 then
140                   loc_row
141                  else
142                   let msg_row = tree_store#append ?parent:loc_row () in
143                    (tree_store#set ~row:msg_row ~column:id_col
144                      ("Error message " ^ string_of_int (!idx1+1) ^ "." ^
145                       string_of_int (!idx2+1) ^
146                       " (in passes " ^
147                       String.concat " " (List.map string_of_int passes) ^
148                       ")");
149                     tree_store#set ~row:msg_row ~column:interp_no_col
150                      (!idx1,Some !idx2,None);
151                     Some msg_row) in
152                 let idx3 = ref ~-1 in
153                 List.iter
154                  (fun (passes,env,_) ->
155                    incr idx3;
156                    let interp_row =
157                     match envs_and_diffs with
158                        _::_::_ ->
159                         let interp_row = tree_store#append ?parent:msg_row () in
160                         tree_store#set ~row:interp_row ~column:id_col
161                           ("Interpretation " ^ string_of_int (!idx3+1) ^
162                            " (in passes " ^
163                            String.concat " " (List.map string_of_int passes) ^
164                            ")");
165                         tree_store#set ~row:interp_row ~column:interp_no_col
166                          (!idx1,Some !idx2,Some !idx3);
167                         Some interp_row
168                      | [_] -> msg_row
169                      | [] -> assert false
170                    in
171                     List.iter
172                      (fun (_, id, dsc) ->
173                        let row = tree_store#append ?parent:interp_row () in
174                        tree_store#set ~row ~column:id_col id;
175                        tree_store#set ~row ~column:dsc_col dsc;
176                        tree_store#set ~row ~column:interp_no_col
177                         (!idx1,Some !idx2,Some !idx3)
178                      ) env
179                  ) envs_and_diffs
180               ) lll ;
181              if List.length lll > 1 then
182               HExtlib.iter_option
183                (fun p -> tree_view#expand_row (tree_store#get_path p))
184                loc_row
185           ) choices
186
187       method get_interp_no tree_path =
188         let iter = tree_store#get_iter tree_path in
189         tree_store#get ~row:iter ~column:interp_no_col
190     end
191
192 exception UseLibrary;;
193
194 let interactive_error_interp ~all_passes
195   (source_buffer:GSourceView2.source_buffer) notify_exn offset errorll filename
196
197   (* hook to save a script for each disambiguation error *)
198   if false then
199    (let text =
200      source_buffer#get_text ~start:source_buffer#start_iter
201       ~stop:source_buffer#end_iter () in
202     let md5 = Digest.to_hex (Digest.string text) in
203     let filename =
204      Filename.chop_extension filename ^ ".error." ^ md5 ^ ".ma"  in
205     let ch = open_out filename in
206      output_string ch text;
207     close_out ch
208    );
209   assert (List.flatten errorll <> []);
210   let errorll' =
211    let remove_non_significant =
212      List.filter (fun (_env,_diff,_loc_msg,significant) -> significant) in
213    let annotated_errorll () =
214     List.rev
215      (snd
216        (List.fold_left (fun (pass,res) item -> pass+1,(pass+1,item)::res) (0,[])
217          errorll)) in
218    if all_passes then annotated_errorll () else
219      let safe_list_nth l n = try List.nth l n with Failure _ -> [] in
220     (* We remove passes 1,2 and 5,6 *)
221      let res =
222       (1,[])::(2,[])
223       ::(3,remove_non_significant (safe_list_nth errorll 2))
224       ::(4,remove_non_significant (safe_list_nth errorll 3))
225       ::(5,[])::(6,[])::[]
226      in
227       if List.flatten (List.map snd res) <> [] then res
228       else
229        (* all errors (if any) are not significant: we keep them *)
230        let res =
231         (1,[])::(2,[])
232         ::(3,(safe_list_nth errorll 2))
233         ::(4,(safe_list_nth errorll 3))
234         ::(5,[])::(6,[])::[]
235        in
236         if List.flatten (List.map snd res) <> [] then
237          begin
238           HLog.warn
239            "All disambiguation errors are not significant. Showing them anyway." ;
240           res
241          end
242         else
243          begin
244           HLog.warn
245            "No errors in phases 2 and 3. Showing all errors in all phases" ;
246           annotated_errorll ()
247          end
248    in
249   let choices = MatitaExcPp.compact_disambiguation_errors all_passes errorll' in
250    match choices with
251       [] -> assert false
252     | [loffset,[_,envs_and_diffs,msg,significant]] ->
253         let _,env,diff = List.hd envs_and_diffs in
254          notify_exn
255           (MultiPassDisambiguator.DisambiguationError
256             (offset,[[env,diff,lazy (loffset,Lazy.force msg),significant]]));
257     | _::_ ->
258        let dialog = new disambiguationErrors () in
259        dialog#check_widgets ();
260        if all_passes then
261         dialog#disambiguationErrorsMoreErrors#misc#set_sensitive false;
262        let model = new interpErrorModel dialog#treeview choices in
263        dialog#disambiguationErrors#set_title "Disambiguation error";
264        dialog#disambiguationErrorsLabel#set_label
265         "Click on an error to see the corresponding message:";
266        ignore (dialog#treeview#connect#cursor_changed
267         (fun _ ->
268           let tree_path =
269            match fst (dialog#treeview#get_cursor ()) with
270               None -> assert false
271            | Some tp -> tp in
272           let idx1,idx2,idx3 = model#get_interp_no tree_path in
273           let loffset,lll = List.nth choices idx1 in
274           let _,envs_and_diffs,msg,significant =
275            match idx2 with
276               Some idx2 -> List.nth lll idx2
277             | None ->
278                 [],[],lazy "Multiple error messages. Please select one.",true
279           in
280           let _,env,diff =
281            match idx3 with
282               Some idx3 -> List.nth envs_and_diffs idx3
283             | None -> [],[],[] (* dymmy value, used *) in
284           let script = MatitaScript.current () in
285           let error_tag = script#error_tag in
286            source_buffer#remove_tag error_tag
287              ~start:source_buffer#start_iter
288              ~stop:source_buffer#end_iter;
289            notify_exn
290             (MultiPassDisambiguator.DisambiguationError
291               (offset,[[env,diff,lazy(loffset,Lazy.force msg),significant]]))
292            ));
293        let return _ =
294          dialog#disambiguationErrors#destroy ();
295          GMain.Main.quit ()
296        in
297        let fail _ = return () in
298        ignore(dialog#disambiguationErrors#event#connect#delete (fun _ -> true));
299        connect_button dialog#disambiguationErrorsOkButton
300         (fun _ ->
301           let tree_path =
302            match fst (dialog#treeview#get_cursor ()) with
303               None -> assert false
304            | Some tp -> tp in
305           let idx1,idx2,idx3 = model#get_interp_no tree_path in
306           let diff =
307            match idx2,idx3 with
308               Some idx2, Some idx3 ->
309                let _,lll = List.nth choices idx1 in
310                let _,envs_and_diffs,_,_ = List.nth lll idx2 in
311                let _,_,diff = List.nth envs_and_diffs idx3 in
312                 diff
313             | _,_ -> assert false
314           in
315            let newtxt =
316             String.concat "\n"
317              ("" ::
318                List.map
319                 (fun k,desc -> 
320                   let alias =
321                    match k with
322                    | DisambiguateTypes.Id id ->
323                        GrafiteAst.Ident_alias (id, desc)
324                    | DisambiguateTypes.Symbol (symb, i)-> 
325                        GrafiteAst.Symbol_alias (symb, i, desc)
326                    | DisambiguateTypes.Num i ->
327                        GrafiteAst.Number_alias (i, desc)
328                   in
329                    GrafiteAstPp.pp_alias alias)
330                 diff) ^ "\n"
331            in
332             source_buffer#insert
333              ~iter:
334                (source_buffer#get_iter_at_mark
335                 (`NAME "beginning_of_statement")) newtxt ;
336             return ()
337         );
338        connect_button dialog#disambiguationErrorsMoreErrors
339         (fun _ -> return () ; raise UseLibrary);
340        connect_button dialog#disambiguationErrorsCancelButton fail;
341        dialog#disambiguationErrors#show ();
342        GtkThread.main ()
343
344
345 class gui () =
346     (* creation order _is_ relevant for windows placement *)
347   let main = new mainWin () in
348   let fileSel = new fileSelectionWin () in
349   let findRepl = new findReplWin () in
350   let keyBindingBoxes = (* event boxes which should receive global key events *)
351     [ main#mainWinEventBox ]
352   in
353   let console = new console ~buffer:main#logTextView#buffer () in
354   let source_view () = (MatitaScript.current ())#source_view in
355   object (self)
356     val mutable chosen_file = None
357     val mutable _ok_not_exists = false
358     val mutable _only_directory = false
359       
360     initializer
361       let s () = MatitaScript.current () in
362         (* glade's check widgets *)
363       List.iter (fun w -> w#check_widgets ())
364         (let c w = (w :> <check_widgets: unit -> unit>) in
365         [ c fileSel; c main; c findRepl]);
366         (* key bindings *)
367       List.iter (* global key bindings *)
368         (fun (key, callback) -> self#addKeyBinding key callback)
369 (*
370         [ GdkKeysyms._F3,
371             toggle_win ~check:main#showProofMenuItem proof#proofWin;
372           GdkKeysyms._F4,
373             toggle_win ~check:main#showCheckMenuItem check#checkWin;
374 *)
375         [ ];
376         (* about win *)
377       let parse_txt_file file =
378        let ch = open_in (BuildTimeConf.runtime_base_dir ^ "/" ^ file) in
379        let l_rev = ref [] in
380        try
381         while true do
382          l_rev := input_line ch :: !l_rev;
383         done;
384         assert false
385        with
386         End_of_file ->
387          close_in ch;
388          List.rev !l_rev in 
389       let about_dialog =
390        GWindow.about_dialog
391         ~authors:(parse_txt_file "AUTHORS")
392         (*~comments:"comments"*)
393         ~copyright:"Copyright (C) 2005, the HELM team"
394         ~license:(String.concat "\n" (parse_txt_file "LICENSE"))
395         ~logo:(GdkPixbuf.from_file (MatitaMisc.image_path "/matita_medium.png"))
396         ~name:"Matita"
397         ~version:BuildTimeConf.version
398         ~website:"http://matita.cs.unibo.it"
399         ()
400       in
401       ignore(about_dialog#connect#response (fun _ ->about_dialog#misc#hide ()));
402       connect_menu_item main#contentsMenuItem (fun () ->
403         if 0 = Sys.command "which gnome-help" then
404           let cmd =
405             sprintf "gnome-help ghelp://%s/C/matita.xml &" BuildTimeConf.help_dir
406           in
407            ignore (Sys.command cmd)
408         else
409           MatitaGtkMisc.report_error ~title:"help system error"
410            ~message:(
411               "The program gnome-help is not installed\n\n"^
412               "To browse the user manal it is necessary to install "^
413               "the gnome help syste (also known as yelp)") 
414            ~parent:main#toplevel ());
415       connect_menu_item main#aboutMenuItem about_dialog#present;
416         (* findRepl win *)
417       let show_find_Repl () = 
418         findRepl#toplevel#misc#show ();
419         findRepl#toplevel#misc#grab_focus ()
420       in
421       let hide_find_Repl () = findRepl#toplevel#misc#hide () in
422       let find_forward _ = 
423           let source_view = source_view () in
424           let highlight start end_ =
425             source_view#source_buffer#move_mark `INSERT ~where:start;
426             source_view#source_buffer#move_mark `SEL_BOUND ~where:end_;
427             source_view#scroll_mark_onscreen `INSERT
428           in
429           let text = findRepl#findEntry#text in
430           let iter = source_view#source_buffer#get_iter `SEL_BOUND in
431           match iter#forward_search text with
432           | None -> 
433               (match source_view#source_buffer#start_iter#forward_search text with
434               | None -> ()
435               | Some (start,end_) -> highlight start end_)
436           | Some (start,end_) -> highlight start end_ 
437       in
438       let replace _ =
439         let source_view = source_view () in
440         let text = findRepl#replaceEntry#text in
441         let ins = source_view#source_buffer#get_iter `INSERT in
442         let sel = source_view#source_buffer#get_iter `SEL_BOUND in
443         if ins#compare sel < 0 then 
444           begin
445             ignore(source_view#source_buffer#delete_selection ());
446             source_view#source_buffer#insert text
447           end
448       in
449       connect_button findRepl#findButton find_forward;
450       connect_button findRepl#findReplButton replace;
451       connect_button findRepl#cancelButton (fun _ -> hide_find_Repl ());
452       ignore(findRepl#toplevel#event#connect#delete 
453         ~callback:(fun _ -> hide_find_Repl ();true));
454       connect_menu_item main#undoMenuItem
455        (fun () -> (MatitaScript.current ())#safe_undo);
456 (*CSC: XXX
457       ignore(source_view#source_buffer#connect#can_undo
458         ~callback:main#undoMenuItem#misc#set_sensitive);
459 *) main#undoMenuItem#misc#set_sensitive true;
460       connect_menu_item main#redoMenuItem
461        (fun () -> (MatitaScript.current ())#safe_redo);
462 (*CSC: XXX
463       ignore(source_view#source_buffer#connect#can_redo
464         ~callback:main#redoMenuItem#misc#set_sensitive);
465 *) main#redoMenuItem#misc#set_sensitive true;
466       connect_menu_item main#editMenu (fun () ->
467         main#copyMenuItem#misc#set_sensitive
468          (MatitaScript.current ())#canCopy;
469         main#cutMenuItem#misc#set_sensitive
470          (MatitaScript.current ())#canCut;
471         main#deleteMenuItem#misc#set_sensitive
472          (MatitaScript.current ())#canDelete;
473         main#pasteMenuItem#misc#set_sensitive
474          (MatitaScript.current ())#canPaste;
475         main#pastePatternMenuItem#misc#set_sensitive
476          (MatitaScript.current ())#canPastePattern);
477       connect_menu_item main#copyMenuItem
478          (fun () -> (MatitaScript.current ())#copy ());
479       connect_menu_item main#cutMenuItem
480          (fun () -> (MatitaScript.current ())#cut ());
481       connect_menu_item main#deleteMenuItem
482          (fun () -> (MatitaScript.current ())#delete ());
483       connect_menu_item main#pasteMenuItem
484          (fun () -> (MatitaScript.current ())#paste ());
485       connect_menu_item main#pastePatternMenuItem
486          (fun () -> (MatitaScript.current ())#pastePattern ());
487       connect_menu_item main#selectAllMenuItem (fun () ->
488        let source_view = source_view () in
489         source_view#source_buffer#move_mark `INSERT source_view#source_buffer#start_iter;
490         source_view#source_buffer#move_mark `SEL_BOUND source_view#source_buffer#end_iter);
491       connect_menu_item main#findReplMenuItem show_find_Repl;
492       connect_menu_item main#externalEditorMenuItem self#externalEditor;
493       connect_menu_item main#ligatureButton
494        (fun () -> (MatitaScript.current ())#nextSimilarSymbol);
495       ignore (findRepl#findEntry#connect#activate find_forward);
496         (* interface lockers *)
497       let lock_world _ =
498        let source_view = source_view () in
499         main#buttonsToolbar#misc#set_sensitive false;
500         main#scriptMenu#misc#set_sensitive false;
501         source_view#set_editable false
502       in
503       let unlock_world _ =
504        let source_view = source_view () in
505         main#buttonsToolbar#misc#set_sensitive true;
506         main#scriptMenu#misc#set_sensitive true;
507         source_view#set_editable true;
508         (*The next line seems sufficient to avoid some unknown race condition *)
509         GtkThread.sync (fun () -> ()) ()
510       in
511       let worker_thread = ref None in
512       let notify_exn (source_view : GSourceView2.source_view) exn =
513        let floc, msg = MatitaExcPp.to_string exn in
514         begin
515          match floc with
516             None -> ()
517           | Some floc ->
518              let (x, y) = HExtlib.loc_of_floc floc in
519              let script = MatitaScript.current () in
520              let locked_mark = script#locked_mark in
521              let error_tag = script#error_tag in
522              let baseoffset =
523               (source_view#source_buffer#get_iter_at_mark (`MARK locked_mark))#offset in
524              let x' = baseoffset + x in
525              let y' = baseoffset + y in
526              let x_iter = source_view#source_buffer#get_iter (`OFFSET x') in
527              let y_iter = source_view#source_buffer#get_iter (`OFFSET y') in
528              source_view#source_buffer#apply_tag error_tag ~start:x_iter ~stop:y_iter;
529              let id = ref None in
530              id := Some (source_view#source_buffer#connect#changed ~callback:(fun () ->
531                source_view#source_buffer#remove_tag error_tag
532                  ~start:source_view#source_buffer#start_iter
533                  ~stop:source_view#source_buffer#end_iter;
534                match !id with
535                | None -> assert false (* a race condition occurred *)
536                | Some id ->
537                    (new GObj.gobject_ops source_view#source_buffer#as_buffer)#disconnect id));
538              source_view#source_buffer#place_cursor
539               (source_view#source_buffer#get_iter (`OFFSET x'));
540         end;
541         HLog.error msg in
542       let locker f script =
543        let source_view = script#source_view in
544        let thread_main =
545         fun () -> 
546           lock_world ();
547           let saved_use_library= !MultiPassDisambiguator.use_library in
548           try
549            MultiPassDisambiguator.use_library := !all_disambiguation_passes;
550            f script;
551            MultiPassDisambiguator.use_library := saved_use_library;
552            unlock_world ()
553           with
554            | MultiPassDisambiguator.DisambiguationError (offset,errorll) ->
555               (try
556                 interactive_error_interp 
557                  ~all_passes:!all_disambiguation_passes source_view#source_buffer
558                  (notify_exn source_view) offset errorll (s())#filename
559                with
560                 | UseLibrary ->
561                    MultiPassDisambiguator.use_library := true;
562                    (try f script
563                     with
564                     | MultiPassDisambiguator.DisambiguationError (offset,errorll) ->
565                        interactive_error_interp ~all_passes:true source_view#source_buffer
566                         (notify_exn source_view) offset errorll (s())#filename
567                     | exc ->
568                        notify_exn source_view exc);
569                 | exc -> notify_exn source_view exc);
570               MultiPassDisambiguator.use_library := saved_use_library;
571               unlock_world ()
572            | exc ->
573               (try notify_exn source_view exc
574                with Sys.Break as e -> notify_exn source_view e);
575               unlock_world ()
576        in
577        (*thread_main ();*)
578        worker_thread := Some (Thread.create thread_main ())
579       in
580       let kill_worker =
581        (* the following lines are from Xavier Leroy: http://alan.petitepomme.net/cwn/2005.11.08.html *)
582        let interrupt = ref None in
583        let old_callback = ref (function _ -> ()) in
584        let force_interrupt n =
585          (* This function is called just before the thread's timeslice ends *)
586          !old_callback n;
587          if Some(Thread.id(Thread.self())) = !interrupt then
588           (interrupt := None; raise Sys.Break) in
589        let _ =
590         match Sys.signal Sys.sigvtalrm (Sys.Signal_handle force_interrupt) with
591            Sys.Signal_handle f -> old_callback := f
592          | Sys.Signal_ignore
593          | Sys.Signal_default -> assert false
594        in
595         fun () ->
596          match !worker_thread with
597             None -> assert false
598           | Some t -> interrupt := Some (Thread.id t) in
599       let keep_focus f (script: MatitaScript.script) =
600          try
601           f script; script#source_view#misc#grab_focus ()
602          with
603           exc -> script#source_view#misc#grab_focus (); raise exc in
604       
605         (* file selection win *)
606       ignore (fileSel#fileSelectionWin#event#connect#delete (fun _ -> true));
607       ignore (fileSel#fileSelectionWin#connect#response (fun event ->
608         let return r =
609           chosen_file <- r;
610           fileSel#fileSelectionWin#misc#hide ();
611           GMain.Main.quit ()
612         in
613         match event with
614         | `OK ->
615             let fname = fileSel#fileSelectionWin#filename in
616             if Sys.file_exists fname then
617               begin
618                 if HExtlib.is_regular fname && not (_only_directory) then 
619                   return (Some fname) 
620                 else if _only_directory && HExtlib.is_dir fname then 
621                   return (Some fname)
622               end
623             else
624               begin
625                 if _ok_not_exists then 
626                   return (Some fname)
627               end
628         | `CANCEL -> return None
629         | `HELP -> ()
630         | `DELETE_EVENT -> return None));
631         (* menus *)
632       List.iter (fun w -> w#misc#set_sensitive false) [ main#saveMenuItem ];
633         (* console *)
634       let adj = main#logScrolledWin#vadjustment in
635         ignore (adj#connect#changed
636                 (fun _ -> adj#set_value (adj#upper -. adj#page_size)));
637       console#message (sprintf "\tMatita version %s\n" BuildTimeConf.version);
638         (* natural deduction palette *)
639       main#tacticsButtonsHandlebox#misc#hide ();
640       MatitaGtkMisc.toggle_callback
641         ~callback:(fun b -> 
642           if b then main#tacticsButtonsHandlebox#misc#show ()
643           else main#tacticsButtonsHandlebox#misc#hide ())
644         ~check:main#menuitemPalette;
645       connect_button main#butImpl_intro
646         (fun () -> (source_view ())#source_buffer#insert "apply rule (⇒#i […] (…));\n");
647       connect_button main#butAnd_intro
648         (fun () -> (source_view ())#source_buffer#insert 
649           "apply rule (∧#i (…) (…));\n\t[\n\t|\n\t]\n");
650       connect_button main#butOr_intro_left
651         (fun () -> (source_view ())#source_buffer#insert "apply rule (∨#i_l (…));\n");
652       connect_button main#butOr_intro_right
653         (fun () -> (source_view ())#source_buffer#insert "apply rule (∨#i_r (…));\n");
654       connect_button main#butNot_intro
655         (fun () -> (source_view ())#source_buffer#insert "apply rule (¬#i […] (…));\n");
656       connect_button main#butTop_intro
657         (fun () -> (source_view ())#source_buffer#insert "apply rule (⊤#i);\n");
658       connect_button main#butImpl_elim
659         (fun () -> (source_view ())#source_buffer#insert 
660           "apply rule (⇒#e (…) (…));\n\t[\n\t|\n\t]\n");
661       connect_button main#butAnd_elim_left
662         (fun () -> (source_view ())#source_buffer#insert "apply rule (∧#e_l (…));\n");
663       connect_button main#butAnd_elim_right
664         (fun () -> (source_view ())#source_buffer#insert "apply rule (∧#e_r (…));\n");
665       connect_button main#butOr_elim
666         (fun () -> (source_view ())#source_buffer#insert 
667           "apply rule (∨#e (…) […] (…) […] (…));\n\t[\n\t|\n\t|\n\t]\n");
668       connect_button main#butNot_elim
669         (fun () -> (source_view ())#source_buffer#insert 
670           "apply rule (¬#e (…) (…));\n\t[\n\t|\n\t]\n");
671       connect_button main#butBot_elim
672         (fun () -> (source_view ())#source_buffer#insert "apply rule (⊥#e (…));\n");
673       connect_button main#butRAA
674         (fun () -> (source_view ())#source_buffer#insert "apply rule (RAA […] (…));\n");
675       connect_button main#butUseLemma
676         (fun () -> (source_view ())#source_buffer#insert "apply rule (lem #premises name â€¦);\n");
677       connect_button main#butDischarge
678         (fun () -> (source_view ())#source_buffer#insert "apply rule (discharge […]);\n");
679       
680       connect_button main#butForall_intro
681         (fun () -> (source_view ())#source_buffer#insert "apply rule (∀#i {…} (…));\n");
682       connect_button main#butForall_elim
683         (fun () -> (source_view ())#source_buffer#insert "apply rule (∀#e {…} (…));\n");
684       connect_button main#butExists_intro
685         (fun () -> (source_view ())#source_buffer#insert "apply rule (∃#i {…} (…));\n");
686       connect_button main#butExists_elim
687         (fun () -> (source_view ())#source_buffer#insert 
688           "apply rule (∃#e (…) {…} […] (…));\n\t[\n\t|\n\t]\n");
689
690     
691       let module Hr = Helm_registry in
692       MatitaGtkMisc.toggle_callback ~check:main#fullscreenMenuItem
693         ~callback:(function 
694           | true -> main#toplevel#fullscreen () 
695           | false -> main#toplevel#unfullscreen ());
696       main#fullscreenMenuItem#set_active false;
697       MatitaGtkMisc.toggle_callback ~check:main#ppNotationMenuItem
698         ~callback:(function b ->
699           let s = s () in
700           let status =
701            Interpretations.toggle_active_interpretations s#grafite_status b
702           in
703            assert false (* MATITA1.0 ???
704            s#set_grafite_status status*)
705          );
706       MatitaGtkMisc.toggle_callback ~check:main#hideCoercionsMenuItem
707         ~callback:(fun enabled -> Interpretations.hide_coercions := enabled);
708       MatitaGtkMisc.toggle_callback ~check:main#unicodeAsTexMenuItem
709         ~callback:(fun enabled ->
710           Helm_registry.set_bool "matita.paste_unicode_as_tex" enabled);
711       main#unicodeAsTexMenuItem#set_active
712         (Helm_registry.get_bool "matita.paste_unicode_as_tex");
713         (* log *)
714       HLog.set_log_callback self#console#log_callback;
715       GtkSignal.user_handler :=
716         (function 
717         | MatitaScript.ActionCancelled s -> HLog.error s
718         | exn ->
719           if not (Helm_registry.get_bool "matita.debug") then
720            (*CSC: MatitaScript.current ??? *)
721            notify_exn (MatitaScript.current ())#source_view exn
722           else raise exn);
723       let disableSave () =
724         (s())#assignFileName None;
725         main#saveMenuItem#misc#set_sensitive false
726       in
727       let saveAsScript () =
728         let script = s () in
729         match self#chooseFile ~ok_not_exists:true () with
730         | Some f -> 
731               HExtlib.touch f;
732               script#assignFileName (Some f);
733               script#saveToFile (); 
734               console#message ("'"^f^"' saved.\n");
735               self#_enableSaveTo f
736         | None -> ()
737       in
738       let saveScript () =
739         let script = s () in
740         if script#has_name then 
741           (script#saveToFile (); 
742           console#message ("'"^script#filename^"' saved.\n"))
743         else saveAsScript ()
744       in
745       let abandon_script () =
746        let source_view = source_view () in
747         let grafite_status = (s ())#grafite_status in
748         if source_view#buffer#modified then
749           (match ask_unsaved main#toplevel with
750           | `YES -> saveScript ()
751           | `NO -> ()
752           | `CANCEL -> raise MatitaTypes.Cancel);
753         save_moo grafite_status
754       in
755       let loadScript () =
756         let source_view = source_view () in
757         let script = s () in 
758         try 
759           match self#chooseFile () with
760           | Some f -> 
761               abandon_script ();
762               script#reset (); 
763               script#assignFileName (Some f);
764               source_view#source_buffer#begin_not_undoable_action ();
765               script#loadFromFile f; 
766               source_view#source_buffer#end_not_undoable_action ();
767               source_view#buffer#move_mark `INSERT source_view#buffer#start_iter;
768               source_view#buffer#place_cursor source_view#buffer#start_iter;
769               console#message ("'"^f^"' loaded.\n");
770               self#_enableSaveTo f
771           | None -> ()
772         with MatitaTypes.Cancel -> ()
773       in
774       let newScript () = 
775         let source_view = source_view () in
776         abandon_script ();
777         source_view#source_buffer#begin_not_undoable_action ();
778         (s ())#reset (); 
779         (s ())#template (); 
780         source_view#source_buffer#end_not_undoable_action ();
781         disableSave ()
782       in
783       let cursor () =
784        let source_view = source_view () in
785         source_view#source_buffer#place_cursor
786           (source_view#source_buffer#get_iter_at_mark (`NAME "locked")) in
787       let advance (script: MatitaScript.script) = script#advance (); cursor () in
788       let retract (script: MatitaScript.script) = script#retract (); cursor () in
789       let top (script: MatitaScript.script) = script#goto `Top (); cursor () in
790       let bottom (script: MatitaScript.script) = script#goto `Bottom (); cursor () in
791       let jump (script: MatitaScript.script) = script#goto `Cursor (); cursor () in
792       let advance () = locker (keep_focus advance) (MatitaScript.current ()) in
793       let retract () = locker (keep_focus retract) (MatitaScript.current ()) in
794       let top () = locker (keep_focus top) (MatitaScript.current ()) in
795       let bottom () = locker (keep_focus bottom) (MatitaScript.current ()) in
796       let jump () = locker (keep_focus jump) (MatitaScript.current ()) in
797         (* quit *)
798       self#setQuitCallback (fun () -> 
799 (*CSC: iterare su tutti gli script! 
800         let script = MatitaScript.current () in
801         if source_view#buffer#modified then
802           match ask_unsaved main#toplevel with
803           | `YES -> 
804                saveScript ();
805                save_moo script#grafite_status;
806                GMain.Main.quit ()
807           | `NO -> GMain.Main.quit ()
808           | `CANCEL -> ()
809         else 
810           (save_moo script#grafite_status;
811           GMain.Main.quit ())*) assert false);
812       connect_button main#scriptAdvanceButton advance;
813       connect_button main#scriptRetractButton retract;
814       connect_button main#scriptTopButton top;
815       connect_button main#scriptBottomButton bottom;
816       connect_button main#scriptJumpButton jump;
817       connect_button main#scriptAbortButton kill_worker;
818       connect_menu_item main#scriptAdvanceMenuItem advance;
819       connect_menu_item main#scriptRetractMenuItem retract;
820       connect_menu_item main#scriptTopMenuItem top;
821       connect_menu_item main#scriptBottomMenuItem bottom;
822       connect_menu_item main#scriptJumpMenuItem jump;
823       connect_menu_item main#openMenuItem   loadScript;
824       connect_menu_item main#saveMenuItem   saveScript;
825       connect_menu_item main#saveAsMenuItem saveAsScript;
826       connect_menu_item main#newMenuItem    newScript;
827       connect_menu_item main#showCoercionsGraphMenuItem 
828         (fun _ -> 
829           let c = MatitaMathView.cicBrowser () in
830           c#load (`About `Coercions));
831       connect_menu_item main#showHintsDbMenuItem 
832         (fun _ -> 
833           let c = MatitaMathView.cicBrowser () in
834           c#load (`About `Hints));
835       connect_menu_item main#showTermGrammarMenuItem 
836         (fun _ -> 
837           let c = MatitaMathView.cicBrowser () in
838           c#load (`About `Grammar));
839       connect_menu_item main#showUnicodeTable
840         (fun _ -> 
841           let c = MatitaMathView.cicBrowser () in
842           c#load (`About `TeX));
843         (* debug menu *)
844       main#debugMenu#misc#hide ();
845         (* HBUGS *)
846       main#hintNotebook#misc#hide ();
847       (*
848       main#hintLowImage#set_file (image_path "matita-bulb-low.png");
849       main#hintMediumImage#set_file (image_path "matita-bulb-medium.png");
850       main#hintHighImage#set_file (image_path "matita-bulb-high.png");
851       *)
852         (* main win dimension *)
853       let width = Gdk.Screen.width ~screen:(Gdk.Screen.default ()) () in
854       let height = Gdk.Screen.height ~screen:(Gdk.Screen.default ()) () in
855       (* hack for xinerama, no proper support of monitors from lablgtk *)
856       let width = if width > 1600 then width / 2 else width in
857       let height = if height > 1200 then height / 2 else height in
858       let main_w = width * 90 / 100 in 
859       let main_h = height * 80 / 100 in
860       let script_w = main_w * 6 / 10 in
861       main#toplevel#resize ~width:main_w ~height:main_h;
862       main#hpaneScriptSequent#set_position script_w;
863       (* math view handling *)
864       connect_menu_item main#newCicBrowserMenuItem (fun () ->
865         ignore(MatitaMathView.cicBrowser ()));
866       connect_menu_item main#increaseFontSizeMenuItem
867         MatitaMisc.increase_font_size;
868       connect_menu_item main#decreaseFontSizeMenuItem
869         MatitaMisc.decrease_font_size;
870       connect_menu_item main#normalFontSizeMenuItem
871         MatitaMisc.reset_font_size;
872
873     method private externalEditor () =
874      let source_view = source_view () in
875       let cmd = Helm_registry.get "matita.external_editor" in
876 (* ZACK uncomment to enable interactive ask of external editor command *)
877 (*      let cmd =
878          let msg =
879           "External editor command:
880 %f  will be substitute for the script name,
881 %p  for the cursor position in bytes,
882 %l  for the execution point in bytes."
883         in
884         ask_text ~gui:self ~title:"External editor" ~msg ~multiline:false
885           ~default:(Helm_registry.get "matita.external_editor") ()
886       in *)
887       let script = MatitaScript.current () in
888       let fname = script#filename in
889       let slice mark =
890         source_view#source_buffer#start_iter#get_slice
891           ~stop:(source_view#source_buffer#get_iter_at_mark mark)
892       in
893       let locked = `MARK script#locked_mark in
894       let string_pos mark = string_of_int (String.length (slice mark)) in
895       let cursor_pos = string_pos `INSERT in
896       let locked_pos = string_pos locked in
897       let cmd =
898         Pcre.replace ~pat:"%f" ~templ:fname
899           (Pcre.replace ~pat:"%p" ~templ:cursor_pos
900             (Pcre.replace ~pat:"%l" ~templ:locked_pos
901               cmd))
902       in
903       let locked_before = slice locked in
904       let locked_offset = (source_view#source_buffer#get_iter_at_mark locked)#offset in
905       ignore (Unix.system cmd);
906       source_view#source_buffer#set_text (HExtlib.input_file fname);
907       let locked_iter = source_view#source_buffer#get_iter (`OFFSET locked_offset) in
908       source_view#source_buffer#move_mark locked locked_iter;
909       source_view#source_buffer#apply_tag script#locked_tag
910         ~start:source_view#source_buffer#start_iter ~stop:locked_iter;
911       let locked_after = slice locked in
912       let line = ref 0 in
913       let col = ref 0 in
914       try
915         for i = 0 to String.length locked_before - 1 do
916           if locked_before.[i] <> locked_after.[i] then begin
917             source_view#source_buffer#place_cursor
918               ~where:(source_view#source_buffer#get_iter (`LINEBYTE (!line, !col)));
919             script#goto `Cursor ();
920             raise Exit
921           end else if locked_before.[i] = '\n' then begin
922             incr line;
923             col := 0
924           end
925         done
926       with
927       | Exit -> ()
928       | Invalid_argument _ -> script#goto `Bottom ()
929
930     method loadScript file =       
931      let source_view = source_view () in
932       let script = MatitaScript.current () in
933       script#reset (); 
934       script#assignFileName (Some file);
935       let file = script#filename in
936       let content =
937        if Sys.file_exists file then file
938        else BuildTimeConf.script_template
939       in
940       source_view#source_buffer#begin_not_undoable_action ();
941       script#loadFromFile content;
942       source_view#source_buffer#end_not_undoable_action ();
943       source_view#buffer#move_mark `INSERT source_view#buffer#start_iter;
944       source_view#buffer#place_cursor source_view#buffer#start_iter;
945       console#message ("'"^file^"' loaded.");
946       self#_enableSaveTo file
947       
948     method private _enableSaveTo file =
949       self#main#saveMenuItem#misc#set_sensitive true
950         
951     method console = console
952     method fileSel = fileSel
953     method findRepl = findRepl
954     method main = main
955
956     method newBrowserWin () =
957       object (self)
958         inherit browserWin ()
959         val combo = GEdit.entry ()
960         initializer
961           self#check_widgets ();
962           let combo_widget = combo#coerce in
963           uriHBox#pack ~from:`END ~fill:true ~expand:true combo_widget;
964           combo#misc#grab_focus ()
965         method browserUri = combo
966       end
967
968     method newUriDialog () =
969       let dialog = new uriChoiceDialog () in
970       dialog#check_widgets ();
971       dialog
972
973     method newConfirmationDialog () =
974       let dialog = new confirmationDialog () in
975       dialog#check_widgets ();
976       dialog
977
978     method newEmptyDialog () =
979       let dialog = new emptyDialog () in
980       dialog#check_widgets ();
981       dialog
982
983     method private addKeyBinding key callback =
984       List.iter (fun evbox -> add_key_binding key callback evbox)
985         keyBindingBoxes
986
987     method setQuitCallback callback =
988       connect_menu_item main#quitMenuItem callback;
989       ignore (main#toplevel#event#connect#delete 
990         (fun _ -> callback ();true));
991       self#addKeyBinding GdkKeysyms._q callback
992
993     method chooseFile ?(ok_not_exists = false) () =
994       _ok_not_exists <- ok_not_exists;
995       _only_directory <- false;
996       fileSel#fileSelectionWin#show ();
997       GtkThread.main ();
998       chosen_file
999
1000     method private chooseDir ?(ok_not_exists = false) () =
1001       _ok_not_exists <- ok_not_exists;
1002       _only_directory <- true;
1003       fileSel#fileSelectionWin#show ();
1004       GtkThread.main ();
1005       (* we should check that this is a directory *)
1006       chosen_file
1007   
1008     method askText ?(title = "") ?(msg = "") () =
1009       let dialog = new textDialog () in
1010       dialog#textDialog#set_title title;
1011       dialog#textDialogLabel#set_label msg;
1012       let text = ref None in
1013       let return v =
1014         text := v;
1015         dialog#textDialog#destroy ();
1016         GMain.Main.quit ()
1017       in
1018       ignore (dialog#textDialog#event#connect#delete (fun _ -> true));
1019       connect_button dialog#textDialogCancelButton (fun _ -> return None);
1020       connect_button dialog#textDialogOkButton (fun _ ->
1021         let text = dialog#textDialogTextView#buffer#get_text () in
1022         return (Some text));
1023       dialog#textDialog#show ();
1024       GtkThread.main ();
1025       !text
1026
1027   end
1028
1029 let gui () = 
1030   let g = new gui () in
1031   gui_instance := Some g;
1032   MatitaMisc.set_gui g;
1033   g
1034   
1035 let instance = singleton gui
1036
1037 let non p x = not (p x)
1038
1039 (* this is a shit and should be changed :-{ *)
1040 let interactive_uri_choice
1041   ?(selection_mode:[`SINGLE|`MULTIPLE] = `MULTIPLE) ?(title = "")
1042   ?(msg = "") ?(nonvars_button = false) ?(hide_uri_entry=false) 
1043   ?(hide_try=false) ?(ok_label="_Auto") ?(ok_action:[`SELECT|`AUTO] = `AUTO) 
1044   ?copy_cb ()
1045   ~id uris
1046 =
1047   let gui = instance () in
1048   if (selection_mode <> `SINGLE) &&
1049     (Helm_registry.get_opt_default Helm_registry.get_bool ~default:true "matita.auto_disambiguation")
1050   then
1051     uris
1052   else begin
1053     let dialog = gui#newUriDialog () in
1054     if hide_uri_entry then
1055       dialog#uriEntryHBox#misc#hide ();
1056     if hide_try then
1057       begin
1058       dialog#uriChoiceSelectedButton#misc#hide ();
1059       dialog#uriChoiceConstantsButton#misc#hide ();
1060       end;
1061     dialog#okLabel#set_label ok_label;  
1062     dialog#uriChoiceTreeView#selection#set_mode
1063       (selection_mode :> Gtk.Tags.selection_mode);
1064     let model = new stringListModel dialog#uriChoiceTreeView in
1065     let choices = ref None in
1066     (match copy_cb with
1067     | None -> ()
1068     | Some cb ->
1069         dialog#copyButton#misc#show ();
1070         connect_button dialog#copyButton 
1071         (fun _ ->
1072           match model#easy_selection () with
1073           | [u] -> (cb u)
1074           | _ -> ()));
1075     dialog#uriChoiceDialog#set_title title;
1076     dialog#uriChoiceLabel#set_text msg;
1077     List.iter model#easy_append (List.map NReference.string_of_reference uris);
1078     dialog#uriChoiceConstantsButton#misc#set_sensitive nonvars_button;
1079     let return v =
1080       choices := v;
1081       dialog#uriChoiceDialog#destroy ();
1082       GMain.Main.quit ()
1083     in
1084     ignore (dialog#uriChoiceDialog#event#connect#delete (fun _ -> true));
1085     connect_button dialog#uriChoiceConstantsButton (fun _ ->
1086       return (Some uris));
1087     if ok_action = `AUTO then
1088       connect_button dialog#uriChoiceAutoButton (fun _ ->
1089         Helm_registry.set_bool "matita.auto_disambiguation" true;
1090         return (Some uris))
1091     else
1092       connect_button dialog#uriChoiceAutoButton (fun _ ->
1093         match model#easy_selection () with
1094         | [] -> ()
1095         | uris -> return (Some (List.map NReference.reference_of_string uris)));
1096     connect_button dialog#uriChoiceSelectedButton (fun _ ->
1097       match model#easy_selection () with
1098       | [] -> ()
1099       | uris -> return (Some (List.map NReference.reference_of_string uris)));
1100     connect_button dialog#uriChoiceAbortButton (fun _ -> return None);
1101     dialog#uriChoiceDialog#show ();
1102     GtkThread.main ();
1103     (match !choices with 
1104     | None -> raise MatitaTypes.Cancel
1105     | Some uris -> uris)
1106   end
1107
1108 class interpModel =
1109   let cols = new GTree.column_list in
1110   let id_col = cols#add Gobject.Data.string in
1111   let dsc_col = cols#add Gobject.Data.string in
1112   let interp_no_col = cols#add Gobject.Data.int in
1113   let tree_store = GTree.tree_store cols in
1114   let id_renderer = GTree.cell_renderer_text [], ["text", id_col] in
1115   let dsc_renderer = GTree.cell_renderer_text [], ["text", dsc_col] in
1116   let id_view_col = GTree.view_column ~renderer:id_renderer () in
1117   let dsc_view_col = GTree.view_column ~renderer:dsc_renderer () in
1118   fun tree_view choices ->
1119     object
1120       initializer
1121         tree_view#set_model (Some (tree_store :> GTree.model));
1122         ignore (tree_view#append_column id_view_col);
1123         ignore (tree_view#append_column dsc_view_col);
1124         let name_of_interp =
1125           (* try to find a reasonable name for an interpretation *)
1126           let idx = ref 0 in
1127           fun interp ->
1128             try
1129               List.assoc "0" interp
1130             with Not_found ->
1131               incr idx; string_of_int !idx
1132         in
1133         tree_store#clear ();
1134         let idx = ref ~-1 in
1135         List.iter
1136           (fun interp ->
1137             incr idx;
1138             let interp_row = tree_store#append () in
1139             tree_store#set ~row:interp_row ~column:id_col
1140               (name_of_interp interp);
1141             tree_store#set ~row:interp_row ~column:interp_no_col !idx;
1142             List.iter
1143               (fun (id, dsc) ->
1144                 let row = tree_store#append ~parent:interp_row () in
1145                 tree_store#set ~row ~column:id_col id;
1146                 tree_store#set ~row ~column:dsc_col dsc;
1147                 tree_store#set ~row ~column:interp_no_col !idx)
1148               interp)
1149           choices
1150
1151       method get_interp_no tree_path =
1152         let iter = tree_store#get_iter tree_path in
1153         tree_store#get ~row:iter ~column:interp_no_col
1154     end
1155
1156
1157 let interactive_string_choice 
1158   text prefix_len ?(title = "") ?(msg = "") () ~id locs uris 
1159
1160   let gui = instance () in
1161     let dialog = gui#newUriDialog () in
1162     dialog#uriEntryHBox#misc#hide ();
1163     dialog#uriChoiceSelectedButton#misc#hide ();
1164     dialog#uriChoiceAutoButton#misc#hide ();
1165     dialog#uriChoiceConstantsButton#misc#hide ();
1166     dialog#uriChoiceTreeView#selection#set_mode
1167       (`SINGLE :> Gtk.Tags.selection_mode);
1168     let model = new stringListModel dialog#uriChoiceTreeView in
1169     let choices = ref None in
1170     dialog#uriChoiceDialog#set_title title; 
1171     let hack_len = MatitaGtkMisc.utf8_string_length text in
1172     let rec colorize acc_len = function
1173       | [] -> 
1174           let floc = HExtlib.floc_of_loc (acc_len,hack_len) in
1175           escape_pango_markup (fst(MatitaGtkMisc.utf8_parsed_text text floc))
1176       | he::tl -> 
1177           let start, stop =  HExtlib.loc_of_floc he in
1178           let floc1 = HExtlib.floc_of_loc (acc_len,start) in
1179           let str1,_=MatitaGtkMisc.utf8_parsed_text text floc1 in
1180           let str2,_ = MatitaGtkMisc.utf8_parsed_text text he in
1181           escape_pango_markup str1 ^ "<b>" ^ 
1182           escape_pango_markup str2 ^ "</b>" ^ 
1183           colorize stop tl
1184     in
1185 (*     List.iter (fun l -> let start, stop = HExtlib.loc_of_floc l in
1186                 Printf.eprintf "(%d,%d)" start stop) locs; *)
1187     let locs = 
1188       List.sort 
1189         (fun loc1 loc2 -> 
1190           fst (HExtlib.loc_of_floc loc1) - fst (HExtlib.loc_of_floc loc2)) 
1191         locs 
1192     in
1193 (*     prerr_endline "XXXXXXXXXXXXXXXXXXXX";
1194     List.iter (fun l -> let start, stop = HExtlib.loc_of_floc l in
1195                 Printf.eprintf "(%d,%d)" start stop) locs;
1196     prerr_endline "XXXXXXXXXXXXXXXXXXXX2"; *)
1197     dialog#uriChoiceLabel#set_use_markup true;
1198     let txt = colorize 0 locs in
1199     let txt,_ = MatitaGtkMisc.utf8_parsed_text txt
1200       (HExtlib.floc_of_loc (prefix_len,MatitaGtkMisc.utf8_string_length txt))
1201     in
1202     dialog#uriChoiceLabel#set_label txt;
1203     List.iter model#easy_append uris;
1204     let return v =
1205       choices := v;
1206       dialog#uriChoiceDialog#destroy ();
1207       GMain.Main.quit ()
1208     in
1209     ignore (dialog#uriChoiceDialog#event#connect#delete (fun _ -> true));
1210     connect_button dialog#uriChoiceForwardButton (fun _ ->
1211       match model#easy_selection () with
1212       | [] -> ()
1213       | uris -> return (Some uris));
1214     connect_button dialog#uriChoiceAbortButton (fun _ -> return None);
1215     dialog#uriChoiceDialog#show ();
1216     GtkThread.main ();
1217     (match !choices with 
1218     | None -> raise MatitaTypes.Cancel
1219     | Some uris -> uris)
1220
1221 let interactive_interp_choice () text prefix_len choices =
1222 (*List.iter (fun l -> prerr_endline "==="; List.iter (fun (_,id,dsc) -> prerr_endline (id ^ " = " ^ dsc)) l) choices;*)
1223  let filter_choices filter =
1224   let rec is_compatible filter =
1225    function
1226       [] -> true
1227     | ([],_,_)::tl -> is_compatible filter tl
1228     | (loc::tlloc,id,dsc)::tl ->
1229        try
1230         if List.assoc (loc,id) filter = dsc then
1231          is_compatible filter ((tlloc,id,dsc)::tl)
1232         else
1233          false
1234        with
1235         Not_found -> true
1236   in
1237    List.filter (fun (_,interp) -> is_compatible filter interp)
1238  in
1239  let rec get_choices loc id =
1240   function
1241      [] -> []
1242    | (_,he)::tl ->
1243       let _,_,dsc =
1244        List.find (fun (locs,id',_) -> id = id' && List.mem loc locs) he
1245       in
1246        dsc :: (List.filter (fun dsc' -> dsc <> dsc') (get_choices loc id tl))
1247  in
1248  let example_interp =
1249   match choices with
1250      [] -> assert false
1251    | he::_ -> he in
1252  let ask_user id locs choices =
1253   interactive_string_choice
1254    text prefix_len
1255    ~title:"Ambiguous input"
1256    ~msg:("Choose an interpretation for " ^ id) () ~id locs choices
1257  in
1258  let rec classify ids filter partial_interpretations =
1259   match ids with
1260      [] -> List.map fst partial_interpretations
1261    | ([],_,_)::tl -> classify tl filter partial_interpretations
1262    | (loc::tlloc,id,dsc)::tl ->
1263       let choices = get_choices loc id partial_interpretations in
1264       let chosen_dsc =
1265        match choices with
1266           [] -> prerr_endline ("NO CHOICES FOR " ^ id); assert false
1267         | [dsc] -> dsc
1268         | _ ->
1269           match ask_user id [loc] choices with
1270              [x] -> x
1271            | _ -> assert false
1272       in
1273        let filter = ((loc,id),chosen_dsc)::filter in
1274        let compatible_interps = filter_choices filter partial_interpretations in
1275         classify ((tlloc,id,dsc)::tl) filter compatible_interps
1276  in
1277  let enumerated_choices =
1278   let idx = ref ~-1 in
1279   List.map (fun interp -> incr idx; !idx,interp) choices
1280  in
1281   classify example_interp [] enumerated_choices
1282
1283 let _ =
1284   (* disambiguator callbacks *)
1285   Disambiguate.set_choose_uris_callback
1286    (fun ~selection_mode ?ok ?(enable_button_for_non_vars=false) ~title ~msg ->
1287      interactive_uri_choice ~selection_mode ?ok_label:ok ~title ~msg ());
1288   Disambiguate.set_choose_interp_callback (interactive_interp_choice ());
1289   (* gtk initialization *)
1290   GtkMain.Rc.add_default_file BuildTimeConf.gtkrc_file; (* loads gtk rc *)
1291   ignore (GMain.Main.init ())
1292