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