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