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