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