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