]> matita.cs.unibo.it Git - helm.git/blob - matitaB/matita/matitaScript.ml
5b794a6d830b8d9c0c1690faa9578388c94699ca
[helm.git] / matitaB / matita / matitaScript.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 open GrafiteTypes
30
31 module TA = GrafiteAst
32
33 let debug = false
34 let debug_print = if debug then prerr_endline else ignore
35
36   (** raised when one of the script margins (top or bottom) is reached *)
37 exception Margin
38 exception NoUnfinishedProof
39 exception ActionCancelled of string
40
41 let safe_substring s i j =
42   try String.sub s i j with Invalid_argument _ -> assert false
43
44 let heading_nl_RE = Pcre.regexp "^\\s*\n\\s*"
45 let heading_nl_RE' = Pcre.regexp "^(\\s*\n\\s*)"
46 let only_dust_RE = Pcre.regexp "^(\\s|\n|%%[^\n]*\n)*$"
47 let multiline_RE = Pcre.regexp "^\n[^\n]+$"
48 let newline_RE = Pcre.regexp "\n"
49 let comment_RE = Pcre.regexp "\\(\\*(.|\n)*\\*\\)\n?" ~flags:[`UNGREEDY]
50  
51 let comment str =
52   if Pcre.pmatch ~rex:multiline_RE str then
53     "\n(** " ^ (Pcre.replace ~rex:newline_RE str) ^ " *)"
54   else
55     "\n(**\n" ^ str ^ "\n*)"
56
57 let strip_comments str =
58   Pcre.qreplace ~templ:"\n" ~pat:"\n\n" (Pcre.qreplace ~rex:comment_RE str)
59 ;;
60                      
61 let first_line s =
62   let s = Pcre.replace ~rex:heading_nl_RE s in
63   try
64     let nl_pos = String.index s '\n' in
65     String.sub s 0 nl_pos
66   with Not_found -> s
67
68 (* WR: skipped_txt, nonskipped_txt servono ancora?
69  * (ora non abbiamo più gli alias e il codice sembra più complicato
70  * del necessario)
71  * (rif. nota 11/05/11 *)
72 let eval_with_engine include_paths status skipped_txt nonskipped_txt st
73 =
74   let parsed_text_length =
75     String.length skipped_txt + String.length nonskipped_txt
76   in
77   let text = skipped_txt ^ nonskipped_txt in
78   let prefix_len = MatitaGtkMisc.utf8_string_length skipped_txt in
79   let new_status =
80    MatitaEngine.eval_ast ~include_paths ~do_heavy_checks:(Helm_registry.get_bool
81      "matita.do_heavy_checks")
82     status (text,prefix_len,st)
83   in
84   let res = new_status,skipped_txt ^ nonskipped_txt in
85   res,"",parsed_text_length
86 ;;
87
88 let pp_eager_statement_ast = GrafiteAstPp.pp_statement 
89
90 let eval_nmacro include_paths (buffer : GText.buffer) status unparsed_text parsed_text script mac =
91   let parsed_text_length = String.length parsed_text in
92   match mac with
93   | TA.Screenshot (_,name) -> 
94        let status = script#status in
95        let _,_,menv,subst,_ = status#obj in
96        let name = Filename.dirname (script#filename) ^ "/" ^ name in
97        let sequents = 
98          let selected = Continuationals.Stack.head_goals status#stack in
99          List.filter (fun x,_ -> List.mem x selected) menv         
100        in
101        CicMathView.screenshot status sequents menv subst name;
102        (status, parsed_text), "", parsed_text_length
103   | TA.NCheck (_,t) ->
104       let status = script#status in
105       let _,_,menv,subst,_ = status#obj in
106       let ctx = 
107        match Continuationals.Stack.head_goals status#stack with
108           [] -> []
109         | g::tl ->
110            if tl <> [] then
111             HLog.warn
112              "Many goals focused. Using the context of the first one\n";
113            let _, ctx, _ = NCicUtils.lookup_meta g menv in
114             ctx in
115       let m, s, status, t = 
116         GrafiteDisambiguate.disambiguate_nterm 
117           status None ctx menv subst (parsed_text,parsed_text_length,
118             NotationPt.Cast (t,NotationPt.Implicit `JustOne))  
119           (* XXX use the metasenv, if possible *)
120       in
121       MatitaMathView.cicBrowser (Some (`NCic (t,ctx,m,s)));
122       (status, parsed_text), "", parsed_text_length
123   | TA.NIntroGuess _loc ->
124       let names_ref = ref [] in
125       let s = NTactics.intros_tac ~names_ref [] script#status in
126       let rex = Pcre.regexp ~flags:[`MULTILINE] "\\A([\\n\\t\\r ]*).*\\Z" in
127       let nl = Pcre.replace ~rex ~templ:"$1" parsed_text in
128       (s, nl ^ "#" ^ String.concat " " !names_ref ^ ";"), "", parsed_text_length
129   | TA.NAutoInteractive (_loc, (None,a)) -> 
130       let trace_ref = ref [] in
131       let s = NnAuto.auto_tac ~params:(None,a) ~trace_ref script#status in
132       let depth = 
133         try List.assoc "depth" a
134         with Not_found -> ""
135       in
136       let trace = "/"^(if int_of_string depth > 1 then depth else "")^"/ by " in
137       let thms = 
138         match !trace_ref with
139         | [] -> "{}"
140         | thms -> 
141            String.concat ", "  
142              (HExtlib.filter_map (function 
143                | NotationPt.NRef r -> Some (NCicPp.r2s status true r) 
144                | _ -> None) 
145              thms)
146       in
147       let rex = Pcre.regexp ~flags:[`MULTILINE] "\\A([\\n\\t\\r ]*).*\\Z" in
148       let nl = Pcre.replace ~rex ~templ:"$1" parsed_text in
149       (s, nl ^ trace ^ thms ^ ";"), "", parsed_text_length
150   | TA.NAutoInteractive (_, (Some _,_)) -> assert false
151
152 let rec eval_executable include_paths (buffer : GText.buffer)
153 status unparsed_text skipped_txt nonskipped_txt script ex loc
154 =
155   try
156    ignore (buffer#move_mark (`NAME "beginning_of_statement")
157     ~where:((buffer#get_iter_at_mark (`NAME "locked"))#forward_chars
158        (Glib.Utf8.length skipped_txt))) ;
159    eval_with_engine include_paths status skipped_txt nonskipped_txt
160     (TA.Executable (loc, ex))
161   with
162      MatitaTypes.Cancel -> (status,skipped_txt), "", 0
163    | GrafiteEngine.NMacro (_loc,macro) ->
164        eval_nmacro include_paths buffer status
165         unparsed_text (skipped_txt ^ nonskipped_txt) script macro
166
167
168 and eval_statement include_paths (buffer : GText.buffer) status script
169  statement
170 =
171   let st,unparsed_text =
172     match statement with
173     | `Raw text ->
174         if Pcre.pmatch ~rex:only_dust_RE text then raise Margin;
175         let strm =
176          GrafiteParser.parsable_statement status
177           (Ulexing.from_utf8_string text) in
178         let ast = MatitaEngine.get_ast status include_paths strm in
179          ast, text
180     | `Ast (st, text) -> st, text
181   in
182   let text_of_loc floc = 
183     let nonskipped_txt,_ = MatitaGtkMisc.utf8_parsed_text unparsed_text floc in
184     let start, stop = HExtlib.loc_of_floc floc in 
185     let floc = HExtlib.floc_of_loc (0, start) in
186     let skipped_txt,_ = MatitaGtkMisc.utf8_parsed_text unparsed_text floc in
187     let floc = HExtlib.floc_of_loc (0, stop) in
188     let txt,len = MatitaGtkMisc.utf8_parsed_text unparsed_text floc in
189     txt,nonskipped_txt,skipped_txt,len
190   in 
191   match st with
192   | GrafiteAst.Executable (loc, ex) ->
193      let _, nonskipped, skipped, parsed_text_length = text_of_loc loc in
194       eval_executable include_paths buffer status unparsed_text
195        skipped nonskipped script ex loc
196   | GrafiteAst.Comment (loc, GrafiteAst.Code (_, ex))
197     when Helm_registry.get_bool "matita.execcomments" ->
198      let _, nonskipped, skipped, parsed_text_length = text_of_loc loc in
199       eval_executable include_paths buffer status unparsed_text
200        skipped nonskipped script ex loc
201   | GrafiteAst.Comment (loc, _) -> 
202       let parsed_text, _, _, parsed_text_length = text_of_loc loc in
203       let remain_len = String.length unparsed_text - parsed_text_length in
204       let s = String.sub unparsed_text parsed_text_length remain_len in
205       let s,text,len = 
206        try
207         eval_statement include_paths buffer status script (`Raw s)
208        with
209           HExtlib.Localized (floc, exn) ->
210            HExtlib.raise_localized_exception 
211              ~offset:(MatitaGtkMisc.utf8_string_length parsed_text) floc exn
212         | MultiPassDisambiguator.DisambiguationError (offset,errorll) ->
213            raise
214             (MultiPassDisambiguator.DisambiguationError
215               (offset+parsed_text_length, errorll))
216       in
217       assert (text=""); (* no macros inside comments, please! *)
218       let st,text = s in
219         (st,parsed_text ^ text),"",parsed_text_length + len
220   
221 let fresh_script_id =
222   let i = ref 0 in
223   fun () -> incr i; !i
224
225 (** Selection handling
226  * Two clipboards are used: "clipboard" and "primary".
227  * "primary" is used by X, when you hit the middle button mouse is content is
228  *    pasted between applications. In Matita this selection always contain the
229  *    textual version of the selected term.
230  * "clipboard" is used inside Matita only and support ATM two different targets:
231  *    "TERM" and "PATTERN", in the future other targets like "MATHMLCONTENT" may
232  *    be added
233  *)
234 class script ~(parent:GBin.scrolled_window) ~tab_label () =
235 let source_view =
236   GSourceView2.source_view
237     ~auto_indent:true
238     ~insert_spaces_instead_of_tabs:true ~tab_width:2
239     ~right_margin_position:80 ~show_right_margin:true
240     ~smart_home_end:`AFTER
241     ~packing:parent#add
242     () in
243 let buffer = source_view#buffer in
244 let source_buffer = source_view#source_buffer in
245 let similarsymbols_tag_name = "similarsymbolos" in
246 let similarsymbols_tag = `NAME similarsymbols_tag_name in
247 let initial_statuses current baseuri =
248  let status = new MatitaEngine.status baseuri in
249  (match current with
250      Some current ->
251       NCicLibrary.time_travel status;
252 (*
253       (* MATITA 1.0: there is a known bug in invalidation; temporary fix here *)
254       NCicEnvironment.invalidate () *)
255    | None -> ());
256   status
257 in
258 let read_include_paths file =
259  try 
260    let root, _buri, _fname, _tgt = 
261      Librarian.baseuri_of_script ~include_paths:[] file in 
262    let includes =
263     try
264      Str.split (Str.regexp " ") 
265       (List.assoc "include_paths" (Librarian.load_root_file (root^"/root")))
266     with Not_found -> []
267    in
268    let rc = root :: includes in
269     List.iter (HLog.debug) rc; rc
270  with Librarian.NoRootFor _ | Librarian.FileNotFound _ ->
271   []
272 in
273 let default_buri = "cic:/matita/tests" in
274 let default_fname = ".unnamed.ma" in
275 object (self)
276   val mutable include_paths_ = []
277   val clipboard = GData.clipboard Gdk.Atom.clipboard
278   (*val primary = GData.clipboard Gdk.Atom.primary*)
279   val mutable similarsymbols = []
280   val mutable similarsymbols_orig = []
281   val similar_memory = Hashtbl.create 97
282   val mutable old_used_memory = false
283
284   val scriptId = fresh_script_id ()
285
286   val mutable filename_ = (None : string option)
287
288   method has_name = filename_ <> None
289
290   method source_view = source_view
291   
292   method include_paths =
293     include_paths_ @ 
294     Helm_registry.get_list Helm_registry.string "matita.includes"
295
296   method private curdir =
297     try
298      let root, _buri, _fname, _tgt = 
299       Librarian.baseuri_of_script ~include_paths:self#include_paths
300        self#filename 
301      in 
302      root
303     with Librarian.NoRootFor _ -> Sys.getcwd ()
304
305   method buri_of_current_file =
306     match filename_ with
307     | None -> default_buri 
308     | Some f ->
309         try 
310           let _root, buri, _fname, _tgt = 
311             Librarian.baseuri_of_script ~include_paths:self#include_paths f 
312           in 
313           buri
314         with Librarian.NoRootFor _ | Librarian.FileNotFound _ -> default_buri
315
316   method filename = match filename_ with None -> default_fname | Some f -> f
317
318   initializer 
319     ignore
320      (source_view#source_buffer#begin_not_undoable_action ();
321       self#reset (); 
322       self#template (); 
323       source_view#source_buffer#end_not_undoable_action ());
324     MatitaMisc.observe_font_size (fun font_size ->
325      source_view#misc#modify_font_by_name
326         (sprintf "%s %d" BuildTimeConf.script_font font_size));
327     source_view#misc#grab_focus ();
328     ignore(source_view#source_buffer#set_language
329      (Some MatitaGtkMisc.matita_lang));
330     ignore(source_view#source_buffer#set_highlight_syntax true);
331     ignore(source_view#connect#after#paste_clipboard 
332         ~callback:(fun () -> self#clean_dirty_lock));
333     ignore (GMain.Timeout.add ~ms:300000 
334        ~callback:(fun _ -> self#_saveToBackupFile ();true));
335     ignore (buffer#connect#changed
336       (fun _ -> 
337          let curpos = buffer#cursor_position in
338          HLog.debug ("cursor at " ^ (string_of_int curpos))));
339     ignore (buffer#connect#modified_changed 
340       (fun _ -> self#set_star buffer#modified));
341     (* clean_locked is set to true only "during" a PRIMARY paste
342        operation (i.e. by clicking with the second mouse button) *)
343     let clean_locked = ref false in
344     ignore(source_view#event#connect#button_press
345       ~callback:
346         (fun button ->
347           if GdkEvent.Button.button button = 2 then
348            clean_locked := true;
349           false
350         ));
351     ignore(source_view#event#connect#button_release
352       ~callback:(fun button -> clean_locked := false; false));
353     ignore(source_view#buffer#connect#after#apply_tag
354      ~callback:(
355        fun tag ~start:_ ~stop:_ ->
356         if !clean_locked &&
357            tag#get_oid = self#locked_tag#get_oid
358         then
359          begin
360           clean_locked := false;
361           self#clean_dirty_lock;
362           clean_locked := true
363          end));
364     ignore(source_view#source_buffer#connect#after#insert_text 
365      ~callback:(fun iter str -> 
366         if (MatitaMisc.get_gui ())#main#menuitemAutoAltL#active && (str = " " || str = "\n") then 
367           ignore(self#expand_virtual_if_any iter str)));
368     ignore(source_view#connect#after#populate_popup
369      ~callback:(fun pre_menu ->
370        let menu = new GMenu.menu pre_menu in
371        let menuItems = menu#children in
372        let undoMenuItem, redoMenuItem =
373         match menuItems with
374            [undo;redo;sep1;cut;copy;paste;delete;sep2;
375             selectall;sep3;inputmethod;insertunicodecharacter] ->
376               List.iter menu#remove [ copy; cut; delete; paste ];
377               undo,redo
378          | _ -> assert false in
379        let add_menu_item =
380          let i = ref 2 in (* last occupied position *)
381          fun ?label ?stock () ->
382            incr i;
383            GMenu.image_menu_item ?label ?stock ~packing:(menu#insert ~pos:!i)
384             ()
385        in
386        let copy = add_menu_item ~stock:`COPY () in
387        let cut = add_menu_item ~stock:`CUT () in
388        let delete = add_menu_item ~stock:`DELETE () in
389        let paste = add_menu_item ~stock:`PASTE () in
390        let paste_pattern = add_menu_item ~label:"Paste as pattern" () in
391        copy#misc#set_sensitive self#canCopy;
392        cut#misc#set_sensitive self#canCut;
393        delete#misc#set_sensitive self#canDelete;
394        paste#misc#set_sensitive self#canPaste;
395        paste_pattern#misc#set_sensitive self#canPastePattern;
396        MatitaGtkMisc.connect_menu_item copy self#copy;
397        MatitaGtkMisc.connect_menu_item cut self#cut;
398        MatitaGtkMisc.connect_menu_item delete self#delete;
399        MatitaGtkMisc.connect_menu_item paste self#paste;
400        MatitaGtkMisc.connect_menu_item paste_pattern self#pastePattern;
401        let new_undoMenuItem =
402         GMenu.image_menu_item
403          ~image:(GMisc.image ~stock:`UNDO ())
404          ~use_mnemonic:true
405          ~label:"_Undo"
406          ~packing:(menu#insert ~pos:0) () in
407        new_undoMenuItem#misc#set_sensitive
408         (undoMenuItem#misc#get_flag `SENSITIVE);
409        menu#remove (undoMenuItem :> GMenu.menu_item);
410        MatitaGtkMisc.connect_menu_item new_undoMenuItem
411         (fun () -> self#safe_undo);
412        let new_redoMenuItem =
413         GMenu.image_menu_item
414          ~image:(GMisc.image ~stock:`REDO ())
415          ~use_mnemonic:true
416          ~label:"_Redo"
417          ~packing:(menu#insert ~pos:1) () in
418        new_redoMenuItem#misc#set_sensitive
419         (redoMenuItem#misc#get_flag `SENSITIVE);
420         menu#remove (redoMenuItem :> GMenu.menu_item);
421         MatitaGtkMisc.connect_menu_item new_redoMenuItem
422          (fun () -> self#safe_redo)));
423
424   val mutable statements = []    (** executed statements *)
425
426   val mutable history = [ initial_statuses None default_buri ]
427     (** list of states before having executed statements. Head element of this
428       * list is the current state, last element is the state at the beginning of
429       * the script.
430       * Invariant: this list length is 1 + length of statements *)
431
432   (** text mark and tag representing locked part of a script *)
433   val locked_mark =
434     buffer#create_mark ~name:"locked" ~left_gravity:true buffer#start_iter
435   val beginning_of_statement_mark =
436     buffer#create_mark ~name:"beginning_of_statement"
437      ~left_gravity:true buffer#start_iter
438   val locked_tag = buffer#create_tag [`BACKGROUND "lightblue"; `EDITABLE false]
439   val error_tag = buffer#create_tag [`UNDERLINE `SINGLE; `FOREGROUND "red"]
440
441   (** unicode handling *)
442   method nextSimilarSymbol = 
443     let write_similarsymbol s =
444       let s = Glib.Utf8.from_unichar s in
445       let iter = source_view#source_buffer#get_iter_at_mark `INSERT in
446       assert(Glib.Utf8.validate s);
447       source_view#source_buffer#delete ~start:iter ~stop:(iter#copy#backward_chars 1);
448       source_view#source_buffer#insert ~iter:(source_view#source_buffer#get_iter_at_mark `INSERT) s;
449       (try source_view#source_buffer#delete_mark similarsymbols_tag
450        with GText.No_such_mark _ -> ());
451       ignore(source_view#source_buffer#create_mark ~name:similarsymbols_tag_name
452         (source_view#source_buffer#get_iter_at_mark `INSERT));
453     in
454     let new_similarsymbol =
455       try
456         let iter_ins = source_view#source_buffer#get_iter_at_mark `INSERT in
457         let iter_lig = source_view#source_buffer#get_iter_at_mark similarsymbols_tag in
458         not (iter_ins#equal iter_lig)
459       with GText.No_such_mark _ -> true
460     in
461     if new_similarsymbol then
462       (if not(self#expand_virtual_if_any (source_view#source_buffer#get_iter_at_mark `INSERT) "")then
463         let last_symbol = 
464           let i = source_view#source_buffer#get_iter_at_mark `INSERT in
465           Glib.Utf8.first_char (i#get_slice ~stop:(i#copy#backward_chars 1))
466         in
467         (match Virtuals.similar_symbols last_symbol with
468         | [] ->  ()
469         | eqclass ->
470             similarsymbols_orig <- eqclass;
471             let is_used = 
472               try Hashtbl.find similar_memory similarsymbols_orig  
473               with Not_found -> 
474                 let is_used = List.map (fun x -> x,false) eqclass in
475                 Hashtbl.add similar_memory eqclass is_used; 
476                 is_used
477             in
478             let hd, next, tl = 
479               let used, unused = 
480                 List.partition (fun s -> List.assoc s is_used) eqclass 
481               in
482               match used @ unused with a::b::c -> a,b,c | _ -> assert false
483             in
484             let hd, tl = 
485               if hd = last_symbol then next, tl @ [hd] else hd, (next::tl)
486             in
487             old_used_memory <- List.assoc hd is_used;
488             let is_used = 
489               (hd,true) :: List.filter (fun (x,_) -> x <> hd) is_used
490             in
491             Hashtbl.replace similar_memory similarsymbols_orig is_used;
492             write_similarsymbol hd;
493             similarsymbols <- tl @ [ hd ]))
494     else 
495       match similarsymbols with
496       | [] -> ()
497       | hd :: tl ->
498           let is_used = Hashtbl.find similar_memory similarsymbols_orig in
499           let last = HExtlib.list_last tl in
500           let old_used_for_last = old_used_memory in
501           old_used_memory <- List.assoc hd is_used;
502           let is_used = 
503             (hd, true) :: (last,old_used_for_last) ::
504               List.filter (fun (x,_) -> x <> last && x <> hd) is_used 
505           in
506           Hashtbl.replace similar_memory similarsymbols_orig is_used;
507           similarsymbols <- tl @ [ hd ];
508           write_similarsymbol hd
509
510   method private reset_similarsymbols =
511    similarsymbols <- []; 
512    similarsymbols_orig <- []; 
513    try source_view#source_buffer#delete_mark similarsymbols_tag
514    with GText.No_such_mark _ -> ()
515  
516   method private expand_virtual_if_any iter tok =
517     try
518      let len = MatitaGtkMisc.utf8_string_length tok in
519      let last_word =
520       let prev = iter#copy#backward_chars len in
521        prev#get_slice ~stop:(prev#copy#backward_find_char 
522         (fun x -> Glib.Unichar.isspace x || x = Glib.Utf8.first_char "\\"))
523      in
524      let inplaceof, symb = Virtuals.symbol_of_virtual last_word in
525      self#reset_similarsymbols;
526      let s = Glib.Utf8.from_unichar symb in
527      assert(Glib.Utf8.validate s);
528      source_view#source_buffer#delete ~start:iter 
529        ~stop:(iter#copy#backward_chars
530          (MatitaGtkMisc.utf8_string_length inplaceof + len));
531      source_view#source_buffer#insert ~iter
532        (if inplaceof.[0] = '\\' then s else (s ^ tok));
533      true
534     with Virtuals.Not_a_virtual -> false
535     
536   (** selections / clipboards handling *)
537
538   method markupSelected = MatitaMathView.has_selection ()
539   method private textSelected =
540     (source_view#source_buffer#get_iter_at_mark `INSERT)#compare
541       (source_view#source_buffer#get_iter_at_mark `SEL_BOUND) <> 0
542   method private markupStored = MatitaMathView.has_clipboard ()
543   method private textStored = clipboard#text <> None
544   method canCopy = self#textSelected
545   method canCut = self#textSelected
546   method canDelete = self#textSelected
547   (*CSC: WRONG CODE: we should look in the clipboard instead! *)
548   method canPaste = self#markupStored || self#textStored
549   method canPastePattern = self#markupStored
550
551   method safe_undo =
552    (* phase 1: we save the actual status of the marks and we undo *)
553    let locked_mark = `MARK (self#locked_mark) in
554    let locked_iter = source_view#buffer#get_iter_at_mark locked_mark in
555    let locked_iter_offset = locked_iter#offset in
556    let mark2 =
557     `MARK
558       (source_view#buffer#create_mark ~name:"lock_point"
559         ~left_gravity:true locked_iter) in
560    source_view#source_buffer#undo ();
561    (* phase 2: we save the cursor position and we redo, restoring
562       the previous status of all the marks *)
563    let cursor_iter = source_view#buffer#get_iter_at_mark `INSERT in
564    let mark =
565     `MARK
566       (source_view#buffer#create_mark ~name:"undo_point"
567         ~left_gravity:true cursor_iter)
568    in
569     source_view#source_buffer#redo ();
570     let mark_iter = source_view#buffer#get_iter_at_mark mark in
571     let mark2_iter = source_view#buffer#get_iter_at_mark mark2 in
572     let mark2_iter = mark2_iter#set_offset locked_iter_offset in
573      source_view#buffer#move_mark locked_mark ~where:mark2_iter;
574      source_view#buffer#delete_mark mark;
575      source_view#buffer#delete_mark mark2;
576      (* phase 3: if after the undo the cursor was in the locked area,
577         then we move it there again and we perform a goto *)
578      if mark_iter#offset < locked_iter_offset then
579       begin
580        source_view#buffer#move_mark `INSERT ~where:mark_iter;
581        self#goto `Cursor ();
582       end;
583      (* phase 4: we perform again the undo. This time we are sure that
584         the text to undo is not locked *)
585      source_view#source_buffer#undo ();
586      source_view#misc#grab_focus ()
587
588   method safe_redo =
589    (* phase 1: we save the actual status of the marks, we redo and
590       we undo *)
591    let locked_mark = `MARK (self#locked_mark) in
592    let locked_iter = source_view#buffer#get_iter_at_mark locked_mark in
593    let locked_iter_offset = locked_iter#offset in
594    let mark2 =
595     `MARK
596       (source_view#buffer#create_mark ~name:"lock_point"
597         ~left_gravity:true locked_iter) in
598    source_view#source_buffer#redo ();
599    source_view#source_buffer#undo ();
600    (* phase 2: we save the cursor position and we restore
601       the previous status of all the marks *)
602    let cursor_iter = source_view#buffer#get_iter_at_mark `INSERT in
603    let mark =
604     `MARK
605       (source_view#buffer#create_mark ~name:"undo_point"
606         ~left_gravity:true cursor_iter)
607    in
608     let mark_iter = source_view#buffer#get_iter_at_mark mark in
609     let mark2_iter = source_view#buffer#get_iter_at_mark mark2 in
610     let mark2_iter = mark2_iter#set_offset locked_iter_offset in
611      source_view#buffer#move_mark locked_mark ~where:mark2_iter;
612      source_view#buffer#delete_mark mark;
613      source_view#buffer#delete_mark mark2;
614      (* phase 3: if after the undo the cursor is in the locked area,
615         then we move it there again and we perform a goto *)
616      if mark_iter#offset < locked_iter_offset then
617       begin
618        source_view#buffer#move_mark `INSERT ~where:mark_iter;
619        self#goto `Cursor ();
620       end;
621      (* phase 4: we perform again the redo. This time we are sure that
622         the text to redo is not locked *)
623      source_view#source_buffer#redo ();
624      source_view#misc#grab_focus ()
625    
626
627   method copy () =
628    if self#textSelected
629    then begin
630      MatitaMathView.empty_clipboard ();
631      source_view#buffer#copy_clipboard clipboard;
632    end else
633      MatitaMathView.copy_selection ()
634
635   method cut () =
636    source_view#buffer#cut_clipboard clipboard;
637    MatitaMathView.empty_clipboard ()
638
639   method delete () =
640    ignore (source_view#buffer#delete_selection ())
641
642   method paste () =
643     if MatitaMathView.has_clipboard ()
644     then source_view#buffer#insert (MatitaMathView.paste_clipboard `Term)
645     else source_view#buffer#paste_clipboard clipboard;
646     self#clean_dirty_lock
647
648   method pastePattern () =
649     source_view#buffer#insert (MatitaMathView.paste_clipboard `Pattern)
650
651   method locked_mark = locked_mark
652   method locked_tag = locked_tag
653   method error_tag = error_tag
654
655     (* history can't be empty, the invariant above grant that it contains at
656      * least the init grafite_status *)
657   method status = match history with s::_ -> s | _ -> assert false
658
659   method private _advance ?statement () =
660    let s = match statement with Some s -> s | None -> self#getFuture in
661    if self#bos then LibraryClean.clean_baseuris [self#buri_of_current_file];
662    HLog.debug ("evaluating: " ^ first_line s ^ " ...");
663    let time1 = Unix.gettimeofday () in
664    let entries, newtext, parsed_len = 
665     try
666      eval_statement self#include_paths buffer self#status self (`Raw s)
667     with End_of_file -> raise Margin
668    in
669    let time2 = Unix.gettimeofday () in
670    HLog.debug ("... done in " ^ string_of_float (time2 -. time1) ^ "s");
671    let new_statuses, new_statements = entries in
672    history <- new_statuses :: history;
673    statements <- new_statements :: statements;
674    let start = buffer#get_iter_at_mark (`MARK locked_mark) in
675    if statement <> None then
676       buffer#insert ~iter:start new_statements
677    else begin
678      let parsed_text = String.sub s 0 parsed_len in
679      if new_statements <> parsed_text then begin
680        let stop = start#copy#forward_chars (Glib.Utf8.length parsed_text) in
681        buffer#delete ~start ~stop;
682        buffer#insert ~iter:start new_statements;
683      end;
684    end;
685    self#moveMark (Glib.Utf8.length new_statements);
686    buffer#insert ~iter:(buffer#get_iter_at_mark (`MARK locked_mark))
687      newtext
688
689   method private _retract offset status new_statements new_history =
690     NCicLibrary.time_travel status;
691     statements <- new_statements;
692     history <- new_history;
693     self#moveMark (- offset)
694
695   method advance ?statement () =
696     try
697       self#_advance ?statement ();
698       self#notify
699     with 
700     | Margin -> self#notify
701     | Not_found -> assert false
702     | Invalid_argument "Array.make" -> HLog.error "The script is too big!\n"
703     | exc -> self#notify; raise exc
704
705   method retract () =
706     try
707       let cmp,new_statements,new_history,status =
708        match statements,history with
709           stat::statements, _::(status::_ as history) ->
710            assert (Glib.Utf8.validate stat);
711            Glib.Utf8.length stat, statements, history, status
712        | [],[_] -> raise Margin
713        | _,_ -> assert false
714       in
715        self#_retract cmp status new_statements new_history;
716        self#notify
717     with 
718     | Margin -> self#notify
719     | Invalid_argument "Array.make" -> HLog.error "The script is too big!\n"
720     | exc -> self#notify; raise exc
721
722   method private getFuture =
723     let lock = buffer#get_iter_at_mark (`MARK locked_mark) in
724     let text = buffer#get_text ~start:lock ~stop:buffer#end_iter () in
725     text
726
727   method expandAllVirtuals =
728     let lock = buffer#get_iter_at_mark (`MARK locked_mark) in
729     let text = buffer#get_text ~start:lock ~stop:buffer#end_iter () in
730     buffer#delete ~start:lock ~stop:buffer#end_iter;
731     let text = Pcre.replace ~pat:":=" ~templ:"\\def" text in
732     let text = Pcre.replace ~pat:"->" ~templ:"\\to" text in
733     let text = Pcre.replace ~pat:"=>" ~templ:"\\Rightarrow" text in
734     let text = 
735       Pcre.substitute_substrings 
736         ~subst:(fun str -> 
737            let pristine = Pcre.get_substring str 0 in
738            let input = 
739              if pristine.[0] = ' ' then
740                String.sub pristine 1 (String.length pristine -1) 
741              else pristine 
742            in
743            let input = 
744              if input.[String.length input-1] = ' ' then
745                String.sub input 0 (String.length input -1) 
746              else input
747            in
748            let before, after =  
749              if input = "\\forall" || 
750                 input = "\\lambda" || 
751                 input = "\\exists" then "","" else " ", " " 
752            in
753            try 
754              before ^ Glib.Utf8.from_unichar 
755                (snd (Virtuals.symbol_of_virtual input)) ^ after
756            with Virtuals.Not_a_virtual -> pristine) 
757         ~pat:" ?\\\\[a-zA-Z]+ ?" text
758     in
759     buffer#insert ~iter:lock text
760       
761   (** @param rel_offset relative offset from current position of locked_mark *)
762   method private moveMark rel_offset =
763     let mark = `MARK locked_mark in
764     let old_insert = buffer#get_iter_at_mark `INSERT in
765     buffer#remove_tag locked_tag ~start:buffer#start_iter ~stop:buffer#end_iter;
766     let current_mark_pos = buffer#get_iter_at_mark mark in
767     let new_mark_pos =
768       match rel_offset with
769       | 0 -> current_mark_pos
770       | n when n > 0 -> current_mark_pos#forward_chars n
771       | n (* when n < 0 *) -> current_mark_pos#backward_chars (abs n)
772     in
773     buffer#move_mark mark ~where:new_mark_pos;
774     buffer#apply_tag locked_tag ~start:buffer#start_iter ~stop:new_mark_pos;
775     buffer#move_mark `INSERT old_insert;
776     let mark_position = buffer#get_iter_at_mark mark in
777     if source_view#move_mark_onscreen mark then
778      begin
779       buffer#move_mark mark mark_position;
780       source_view#scroll_to_mark ~use_align:true ~xalign:1.0 ~yalign:0.1 mark;
781      end;
782     while Glib.Main.pending () do ignore(Glib.Main.iteration false); done
783
784   method clean_dirty_lock =
785     let lock_mark_iter = buffer#get_iter_at_mark (`MARK locked_mark) in
786     buffer#remove_tag locked_tag ~start:buffer#start_iter ~stop:buffer#end_iter;
787     buffer#apply_tag locked_tag ~start:buffer#start_iter ~stop:lock_mark_iter
788
789   val mutable observers = []
790
791   method addObserver (o: GrafiteTypes.status -> unit) =
792     observers <- o :: observers
793
794   method private notify =
795     let status = self#status in
796     List.iter (fun o -> o status) observers
797
798   method activate =
799     self#notify
800
801   method loadFromFile f =
802     let script = HExtlib.input_file f in
803     let hs = MatitaScriptLexer.get_hot_spots script in
804     let hstext = 
805       String.concat "\n" (List.map (fun (l1,l2,uri,desc) ->
806         let a,b = HExtlib.loc_of_floc l1 in
807         let c,d = HExtlib.loc_of_floc l2 in
808         let uri = match uri with None -> "()" | Some s -> s in
809         let desc = match desc with None -> "()" | Some s -> s in
810         Printf.sprintf "[%d,%d] [%d,%d] '%s' '%s'" a b c d uri desc) hs)
811     in
812     HLog.debug hstext;
813     buffer#set_text script;
814
815     (* this is the default tag for the whole script (mainly used for 
816      * setting the default behaviour when needed *)
817     let all_tag = buffer#create_tag [] in
818     buffer#apply_tag all_tag ~start:(buffer#get_iter `START)
819      ~stop:(buffer#get_iter `END);
820     ignore(all_tag#connect#event
821       ~callback:(fun ~origin event pos ->
822         match GdkEvent.get_type event with
823          | `MOTION_NOTIFY -> 
824              Gdk.Window.set_cursor
825               (match source_view#get_window `TEXT with None -> assert false | Some x -> x)
826               (Gdk.Cursor.create `ARROW);
827              (* code for removing message from statusbar *)
828              false
829          | _ -> false));
830
831     let invisible_tag   = buffer#create_tag [ `INVISIBLE true ] in
832     let apply_tag (l1,l2,uri,desc) =
833       let hyperlink_tag = 
834         buffer#create_tag [ `FOREGROUND "blue" ; `UNDERLINE `SINGLE] in
835       (* hyperlink_tag#connect#after#changed ~callback:(fun _ -> HLog.debug "***"); *)
836       let a,b = HExtlib.loc_of_floc l1 in
837       let c,d = HExtlib.loc_of_floc l2 in
838       (* setting invisibility for <A...> and </A> *)
839       buffer#apply_tag invisible_tag
840         ~start:(buffer#get_iter_at_char a)
841         ~stop:(buffer#get_iter_at_char b);
842       buffer#apply_tag invisible_tag
843         ~start:(buffer#get_iter_at_char c)
844         ~stop:(buffer#get_iter_at_char d);
845       (* setting hyperlink inside <A...> and </A> *)
846       (* XXX: I'm not sure why I'm required to put those -1 and +1
847        * otherwise I get too small a clickable area, especially for
848        * single characters hyperlinks. *)
849       buffer#apply_tag hyperlink_tag
850         ~start:(buffer#get_iter_at_char (b-1))
851         ~stop:(buffer#get_iter_at_char (c+1));
852       match uri with
853       | None -> ()
854       | Some uri -> 
855         ignore(hyperlink_tag#connect#event
856           ~callback:(fun ~origin event pos ->
857             match GdkEvent.get_type event with
858                `BUTTON_PRESS ->
859                   let uri' = NReference.reference_of_string uri in
860                   MatitaMathView.cicBrowser (Some (`NRef uri'));
861                   true 
862               | `MOTION_NOTIFY -> 
863                   Gdk.Window.set_cursor
864                    (match source_view#get_window `TEXT with None -> assert false | Some x -> x)
865                    (Gdk.Cursor.create `HAND1);
866                   (* let ctxt = (MatitaMisc.get_gui ())#main#statusBar#new_context ~name:"href" in
867                      let msg = ctxt#push uri in
868                      (* href_statusbar_msg <- Some (ctxt, msg);*) *)
869                   false
870               | _ -> false))
871     in
872     self#reset_buffer;
873     List.iter apply_tag hs; 
874     buffer#set_modified false
875
876   method assignFileName file =
877    match file with
878       None ->
879        tab_label#set_text default_fname;
880        filename_ <- None;
881        include_paths_ <- [];
882        self#reset_buffer
883     | Some file ->
884        let f = Librarian.absolutize file in
885         tab_label#set_text (Filename.basename f);
886         filename_ <- Some f;
887         include_paths_ <- read_include_paths f;
888         self#reset_buffer
889
890   method set_star b =
891    tab_label#set_text ((if b then "*" else "")^Filename.basename self#filename);
892    tab_label#misc#set_tooltip_text
893     ("URI: " ^ self#buri_of_current_file ^ "\nPATH: " ^ self#filename);
894     
895   method saveToFile () =
896     if self#has_name then
897       let oc = open_out self#filename in
898       output_string oc (buffer#get_text ~start:buffer#start_iter
899                         ~stop:buffer#end_iter ());
900       close_out oc;
901       self#set_star false;
902       buffer#set_modified false
903     else
904       HLog.error "Can't save, no filename selected"
905   
906   method private _saveToBackupFile () =
907     if buffer#modified then
908       begin
909         let f = self#filename in
910         let oc = open_out f in
911         output_string oc (buffer#get_text ~start:buffer#start_iter
912                             ~stop:buffer#end_iter ());
913         close_out oc;
914         HLog.debug ("backup " ^ f ^ " saved")                    
915       end
916   
917   method private reset_buffer = 
918     statements <- [];
919     history <- [ initial_statuses (Some self#status) self#buri_of_current_file ];
920     self#notify;
921     buffer#remove_tag locked_tag ~start:buffer#start_iter ~stop:buffer#end_iter;
922     buffer#move_mark (`MARK locked_mark) ~where:buffer#start_iter
923
924   method reset () =
925     self#reset_buffer;
926     source_buffer#begin_not_undoable_action ();
927     buffer#delete ~start:buffer#start_iter ~stop:buffer#end_iter;
928     source_buffer#end_not_undoable_action ();
929     buffer#set_modified false;
930   
931   method template () =
932     let template = HExtlib.input_file BuildTimeConf.script_template in 
933     buffer#insert ~iter:(buffer#get_iter `START) template;
934     buffer#set_modified false;
935     self#set_star false;
936
937   method goto (pos: [`Top | `Bottom | `Cursor]) () =
938   try  
939     let old_locked_mark =
940      `MARK
941        (buffer#create_mark ~name:"old_locked_mark"
942          ~left_gravity:true (buffer#get_iter_at_mark (`MARK locked_mark))) in
943     let getpos _ = buffer#get_iter_at_mark (`MARK locked_mark) in 
944     let getoldpos _ = buffer#get_iter_at_mark old_locked_mark in 
945     let dispose_old_locked_mark () = buffer#delete_mark old_locked_mark in
946     match pos with
947     | `Top -> 
948         dispose_old_locked_mark (); 
949         self#reset_buffer;
950         self#notify
951     | `Bottom ->
952         (try 
953           let rec dowhile () =
954             self#_advance ();
955             let newpos = getpos () in
956             if (getoldpos ())#compare newpos < 0 then
957               begin
958                 buffer#move_mark old_locked_mark newpos;
959                 dowhile ()
960               end
961           in
962           dowhile ();
963           dispose_old_locked_mark ();
964           self#notify 
965         with 
966         | Margin -> dispose_old_locked_mark (); self#notify
967         | exc -> dispose_old_locked_mark (); self#notify; raise exc)
968     | `Cursor ->
969         let locked_iter () = buffer#get_iter_at_mark (`NAME "locked") in
970         let cursor_iter () = buffer#get_iter_at_mark `INSERT in
971         let remember =
972          `MARK
973            (buffer#create_mark ~name:"initial_insert"
974              ~left_gravity:true (cursor_iter ())) in
975         let dispose_remember () = buffer#delete_mark remember in
976         let remember_iter () =
977          buffer#get_iter_at_mark (`NAME "initial_insert") in
978         let cmp () = (locked_iter ())#offset - (remember_iter ())#offset in
979         let icmp = cmp () in
980         let forward_until_cursor () = (* go forward until locked > cursor *)
981           let rec aux () =
982             self#_advance ();
983             if cmp () < 0 && (getoldpos ())#compare (getpos ()) < 0 
984             then
985              begin
986               buffer#move_mark old_locked_mark (getpos ());
987               aux ()
988              end
989           in
990           aux ()
991         in
992         let rec back_until_cursor len = (* go backward until locked < cursor *)
993          function
994             statements, ((status)::_ as history)
995             when len <= 0 ->
996              self#_retract (icmp - len) status statements
997               history
998           | statement::tl1, _::tl2 ->
999              back_until_cursor (len - MatitaGtkMisc.utf8_string_length statement) (tl1,tl2)
1000           | _,_ -> assert false
1001         in
1002         (try
1003           begin
1004            if icmp < 0 then       (* locked < cursor *)
1005              (forward_until_cursor (); self#notify)
1006            else if icmp > 0 then  (* locked > cursor *)
1007              (back_until_cursor icmp (statements,history); self#notify)
1008            else                  (* cursor = locked *)
1009                ()
1010           end ;
1011           dispose_remember ();
1012           dispose_old_locked_mark ();
1013         with 
1014         | Margin -> dispose_remember (); dispose_old_locked_mark (); self#notify
1015         | exc -> dispose_remember (); dispose_old_locked_mark ();
1016                  self#notify; raise exc)
1017   with Invalid_argument "Array.make" ->
1018      HLog.error "The script is too big!\n"
1019   
1020   method bos = 
1021     match history with
1022     | _::[] -> true
1023     | _ -> false
1024
1025   method eos = 
1026     let rec is_there_only_comments status s = 
1027       if Pcre.pmatch ~rex:only_dust_RE s then raise Margin;
1028       let strm =
1029        GrafiteParser.parsable_statement status
1030         (Ulexing.from_utf8_string s)in
1031       match GrafiteParser.parse_statement status strm with
1032       | GrafiteAst.Comment (loc,_) -> 
1033           let _,parsed_text_length = MatitaGtkMisc.utf8_parsed_text s loc in
1034           (* CSC: why +1 in the following lines ???? *)
1035           let parsed_text_length = parsed_text_length + 1 in
1036           let remain_len = String.length s - parsed_text_length in
1037           let next = String.sub s parsed_text_length remain_len in
1038           is_there_only_comments status next
1039       | GrafiteAst.Executable _ -> false
1040     in
1041     try is_there_only_comments self#status self#getFuture
1042     with 
1043     | NCicLibrary.IncludedFileNotCompiled _
1044     | HExtlib.Localized _
1045     | CicNotationParser.Parse_error _ -> false
1046     | Margin | End_of_file -> true
1047     | Invalid_argument "Array.make" -> false
1048
1049   (* debug *)
1050   method dump () =
1051     HLog.debug "script status:";
1052     HLog.debug ("history size: " ^ string_of_int (List.length history));
1053     HLog.debug (sprintf "%d statements:" (List.length statements));
1054     List.iter HLog.debug statements;
1055     HLog.debug ("Current file name: " ^ self#filename);
1056
1057   method has_parent (p : GObj.widget) = parent#coerce#misc#get_oid = p#misc#get_oid
1058 end
1059
1060 let _script = ref []
1061
1062 let script ~parent ~tab_label ()
1063 =
1064   let s = new script ~parent ~tab_label () in
1065   _script := s::!_script;
1066   s
1067
1068 let at_page page =
1069  let notebook = (MatitaMisc.get_gui ())#main#scriptNotebook in
1070  let parent = notebook#get_nth_page page in
1071   try
1072    List.find (fun s -> s#has_parent parent) !_script
1073   with
1074    Not_found -> assert false
1075 ;;
1076
1077 let current () =
1078  at_page ((MatitaMisc.get_gui ())#main#scriptNotebook#current_page)
1079
1080 let destroy page =
1081  let s = at_page page in
1082   _script := List.filter ((<>) s) !_script
1083 ;;
1084
1085 let iter_scripts f = List.iter f !_script;;
1086
1087 let _ =
1088  CicMathView.register_matita_script_current (current :> unit -> < advance: ?statement:string -> unit -> unit; status: GrafiteTypes.status >)
1089 ;;