1 (* Copyright (C) 2004-2005, HELM Team.
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.
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.
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.
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,
22 * For details, see the HELM World-Wide-Web page,
23 * http://helm.cs.unibo.it/
30 let debug_print = if debug then prerr_endline else ignore
32 (** raised when one of the script margins (top or bottom) is reached *)
35 let safe_substring s i j =
36 try String.sub s i j with Invalid_argument _ -> assert false
38 let heading_nl_RE = Pcre.regexp "^\\s*\n\\s*"
39 let only_dust_RE = Pcre.regexp "^(\\s|\n|%%[^\n]*\n)*$"
40 let multiline_RE = Pcre.regexp "^\n[^\n]+$"
41 let newline_RE = Pcre.regexp "\n"
44 if Pcre.pmatch ~rex:multiline_RE str then
45 "\n(** " ^ (Pcre.replace ~rex:newline_RE str) ^ " **)"
47 "\n(**\n" ^ str ^ "\n**)"
50 let s = Pcre.replace ~rex:heading_nl_RE s in
52 let nl_pos = String.index s '\n' in
56 let prepend_text header base =
57 if Pcre.pmatch ~rex:heading_nl_RE base then
58 sprintf "\n%s%s" header base
60 sprintf "%s\n%s" header base
62 (** creates a statement AST for the Goal tactic, e.g. "goal 7" *)
64 let module A = TacticAst in
65 let loc = CicAst.dummy_floc in
66 A.Executable (loc, A.Tactical (loc, A.Tactic (loc, A.Goal (loc, n))))
68 let eval_with_engine status user_goal parsed_text st =
69 let module TA = TacticAst in
70 let module TAPp = TacticAstPp in
71 let parsed_text_length = String.length parsed_text in
73 match st with TA.Executable (loc,ex) -> loc, ex | _ -> assert false
75 let goal_changed = ref false in
77 match status.proof_status with
78 | Incomplete_proof (_, goal) when goal <> user_goal ->
80 MatitaEngine.eval_ast status (goal_ast user_goal)
83 let new_status = MatitaEngine.eval_ast status st in
86 | TA.Command (_, TA.Alias _) ->
87 DisambiguateTypes.Environment.empty
88 | _ -> MatitaSync.alias_diff ~from:status new_status
90 (* we remove the defined object since we consider them "automathic aliases" *)
92 let module DTE = DisambiguateTypes.Environment in
93 let module UM = UriManager in
95 fun k ((v,_) as value) acc ->
98 let v = UM.strip_xpointer (UM.uri_of_string v) in
99 List.exists (fun (s,_) -> s = v) new_status.objects
100 with UM.IllFormedUri _ -> false
106 ) new_aliases DTE.empty
109 if DisambiguateTypes.Environment.is_empty new_aliases then
112 prepend_text (CicTextualParser2.EnvironmentP3.to_string new_aliases)
116 if !goal_changed then
118 (TAPp.pp_tactic (TA.Goal (loc, user_goal))(* ^ "\n"*))
123 [ new_status, new_text ], parsed_text_length
125 let disambiguate term status =
126 let module MD = MatitaDisambiguator in
127 let dbd = MatitaDb.instance () in
128 let metasenv = MatitaMisc.get_proof_metasenv status in
129 let context = MatitaMisc.get_proof_context status in
130 let aliases = MatitaMisc.get_proof_aliases status in
131 let interps = MD.disambiguate_term dbd context metasenv aliases term in
136 let eval_macro status (mathviewer:MatitaTypes.mathViewer) urichooser parsed_text
139 let module TA = TacticAst in
140 let module TAPp = TacticAstPp in
141 let module MQ = MetadataQuery in
142 let module MDB = MatitaDb in
143 let module CTC = CicTypeChecker in
144 let module CU = CicUniv in
145 (* no idea why ocaml wants this *)
146 let advance ?statement () = script#advance ?statement () in
147 let parsed_text_length = String.length parsed_text in
148 let dbd = MatitaDb.instance () in
151 | TA.WMatch (loc, term) ->
152 let term = disambiguate term status in
153 let l = MQ.match_term ~dbd term in
154 let entry = `Whelp (TAPp.pp_macro_cic (TA.WMatch (loc, term)), l) in
155 mathviewer#show_uri_list ~reuse:true ~entry l;
156 [], parsed_text_length
157 | TA.WInstance (loc, term) ->
158 let term = disambiguate term status in
159 let l = MQ.instance ~dbd term in
160 let entry = `Whelp (TAPp.pp_macro_cic (TA.WInstance (loc, term)), l) in
161 mathviewer#show_uri_list ~reuse:true ~entry l;
162 [], parsed_text_length
163 | TA.WLocate (loc, s) ->
164 let l = MQ.locate ~dbd s in
165 let entry = `Whelp (TAPp.pp_macro_cic (TA.WLocate (loc, s)), l) in
166 mathviewer#show_uri_list ~reuse:true ~entry l;
167 [], parsed_text_length
168 | TA.WElim (loc, term) ->
169 let term = disambiguate term status in
172 | Cic.MutInd (uri,n,_) -> UriManager.string_of_uriref (uri,[n])
173 | _ -> failwith "Not a MutInd"
175 let l = MQ.elim ~dbd uri in
176 let entry = `Whelp (TAPp.pp_macro_cic (TA.WElim (loc, term)), l) in
177 mathviewer#show_uri_list ~reuse:true ~entry l;
178 [], parsed_text_length
179 | TA.WHint (loc, term) ->
180 let term = disambiguate term status in
181 let s = ((None,[0,[],term], Cic.Meta (0,[]) ,term),0) in
182 let l = List.map fst (MQ.experimental_hint ~dbd s) in
183 let entry = `Whelp (TAPp.pp_macro_cic (TA.WHint (loc, term)), l) in
184 mathviewer#show_uri_list ~reuse:true ~entry l;
185 [], parsed_text_length
188 let s = MatitaMisc.get_proof_status status in
189 let l = List.map fst (MQ.experimental_hint ~dbd s) in
190 let selected = urichooser l in
192 | [] -> [], parsed_text_length
198 TA.Apply (loc, CicAst.Uri (uri,None)))))))
200 let new_status = MatitaEngine.eval_ast status ast in
202 comment parsed_text ^
203 "\n" ^ TAPp.pp_statement ast
205 [ new_status , extra_text ], parsed_text_length
208 "The result of the urichooser should be only 1 uri, not:\n";
210 fun u -> MatitaLog.error (u ^ "\n")
213 | TA.Check (_,term) ->
214 let metasenv = MatitaMisc.get_proof_metasenv status in
215 let context = MatitaMisc.get_proof_context status in
216 let aliases = MatitaMisc.get_proof_aliases status in
218 MatitaDisambiguator.disambiguate_term
219 dbd context metasenv aliases term
221 let _, metasenv , term, ugraph =
226 let ty,_ = CTC.type_of_aux' metasenv context term ugraph in
227 let t_and_ty = Cic.Cast (term,ty) in
228 mathviewer#show_entry (`Cic (t_and_ty,metasenv));
229 [], parsed_text_length
232 let status = script#status.proof_status in
235 | _ -> script#retract ();go_back()
237 [], parsed_text_length, Some go_back
238 | TA.Redo (_, Some i) -> [], parsed_text_length,
239 Some (fun () -> for j = 1 to i do advance () done)
240 | TA.Redo (_, None) -> [], parsed_text_length,
241 Some (fun () -> advance ())
242 | TA.Undo (_, Some i) -> [], parsed_text_length,
243 Some (fun () -> for j = 1 to i do script#retract () done)
244 | TA.Undo (_, None) -> [], parsed_text_length,
245 Some (fun () -> script#retract ()) *)
247 | TA.Quit _ -> failwith "not implemented"
248 | TA.Print (_,kind) -> failwith "not implemented"
249 | TA.Search_pat (_, search_kind, str) -> failwith "not implemented"
250 | TA.Search_term (_, search_kind, term) -> failwith "not implemented"
253 let eval_executable status (mathviewer:MatitaTypes.mathViewer) urichooser
254 user_goal parsed_text script ex =
255 let module TA = TacticAst in
256 let module TAPp = TacticAstPp in
257 let module MD = MatitaDisambiguator in
258 let parsed_text_length = String.length parsed_text in
260 | TA.Command (loc, _) | TA.Tactical (loc, _) ->
261 eval_with_engine status user_goal parsed_text (TA.Executable (loc, ex))
262 | TA.Macro (_,mac) ->
263 eval_macro status mathviewer urichooser parsed_text script mac
265 let rec eval_statement status (mathviewer:MatitaTypes.mathViewer) urichooser
267 if Pcre.pmatch ~rex:only_dust_RE s then raise Margin;
268 let st = CicTextualParser2.parse_statement (Stream.of_string s) in
269 let text_of_loc loc =
270 let parsed_text_length = snd (CicAst.loc_of_floc loc) in
271 let parsed_text = safe_substring s 0 parsed_text_length in
272 parsed_text, parsed_text_length
275 | TacticAst.Comment (loc,_)->
276 let parsed_text, parsed_text_length = text_of_loc loc in
277 let remain_len = String.length s - parsed_text_length in
278 let s = String.sub s parsed_text_length remain_len in
280 eval_statement status mathviewer urichooser user_goal script s
283 | (status, text) :: tl ->
284 ((status, parsed_text ^ text)::tl), (parsed_text_length + len)
286 | TacticAst.Executable (loc, ex) ->
287 let parsed_text, parsed_text_length = text_of_loc loc in
289 status mathviewer urichooser user_goal parsed_text script ex
292 class script ~(buffer: GText.buffer) ~(init: MatitaTypes.status)
293 ~(mathviewer: MatitaTypes.mathViewer)
296 initializer self#reset ()
298 val mutable statements = []; (** executed statements *)
299 val mutable history = [ init ];
300 (** list of states before having executed statements. Head element of this
301 * list is the current state, last element is the state at the beginning of
303 * Invariant: this list length is 1 + length of statements *)
305 (** goal as seen by the user (i.e. metano corresponding to current tab) *)
306 val mutable userGoal = ~-1
308 (** text mark and tag representing locked part of a script *)
310 buffer#create_mark ~name:"locked" ~left_gravity:true buffer#start_iter
311 val locked_tag = buffer#create_tag [`BACKGROUND "lightblue"; `EDITABLE false]
313 (* history can't be empty, the invariant above grant that it contains at
314 * least the init status *)
315 method status = match history with hd :: _ -> hd | _ -> assert false
317 method private _advance ?statement () =
318 let s = match statement with Some s -> s | None -> self#getFuture in
319 MatitaLog.debug ("evaluating: " ^ first_line s ^ " ...");
320 let (entries, parsed_len) =
321 eval_statement self#status mathviewer urichooser userGoal self s in
322 let (new_statuses, new_statements) = List.split entries in
324 prerr_endline "evalStatement returned";
325 List.iter (fun s -> prerr_endline ("'" ^ s ^ "'")) new_statements;
327 history <- List.rev new_statuses @ history;
328 statements <- List.rev new_statements @ statements;
329 let start = buffer#get_iter_at_mark (`MARK locked_mark) in
330 if statement = None then begin
331 let stop = start#copy#forward_chars parsed_len in
332 buffer#delete ~start ~stop
334 let new_text = String.concat "" new_statements in
335 buffer#insert ~iter:start new_text;
336 self#moveMark (String.length new_text)
338 method private _retract () =
339 match statements, history with
340 | last_statement :: _, cur_status :: prev_status :: _ ->
341 MatitaSync.time_travel ~present:cur_status ~past:prev_status;
342 statements <- List.tl statements;
343 history <- List.tl history;
344 self#moveMark (- (String.length last_statement));
347 method advance ?statement () =
349 self#_advance ?statement ()
352 method retract () = try self#_retract () with Margin -> ()
354 method private getFuture =
355 buffer#get_text ~start:(buffer#get_iter_at_mark (`MARK locked_mark))
356 ~stop:buffer#end_iter ()
358 (** @param rel_offset relative offset from current position of locked_mark *)
359 method private moveMark rel_offset =
360 let mark = `MARK locked_mark in
361 let old_insert = buffer#get_iter_at_mark `INSERT in
362 buffer#remove_tag locked_tag ~start:buffer#start_iter ~stop:buffer#end_iter;
363 let current_mark_pos = buffer#get_iter_at_mark mark in
365 match rel_offset with
366 | 0 -> current_mark_pos
367 | n when n > 0 -> current_mark_pos#forward_chars n
368 | n (* when n < 0 *) -> current_mark_pos#backward_chars (abs n)
370 buffer#move_mark mark ~where:new_mark_pos;
371 buffer#apply_tag locked_tag ~start:buffer#start_iter ~stop:new_mark_pos;
372 buffer#move_mark `INSERT old_insert;
375 val mutable observers = []
377 method addObserver (o: MatitaTypes.status -> unit) =
378 observers <- o :: observers
380 method private notify =
381 let status = self#status in
382 List.iter (fun o -> o status) observers
384 method loadFrom fname =
385 buffer#set_text (MatitaMisc.input_file fname);
388 method saveTo fname =
389 let oc = open_out fname in
390 output_string oc (buffer#get_text ~start:buffer#start_iter
391 ~stop:buffer#end_iter ());
394 method private goto_top =
395 MatitaSync.time_travel ~present:self#status ~past:init;
400 buffer#remove_tag locked_tag ~start:buffer#start_iter ~stop:buffer#end_iter;
401 buffer#move_mark (`MARK locked_mark) ~where:buffer#start_iter
405 buffer#delete ~start:buffer#start_iter ~stop:buffer#end_iter
407 method goto (pos: [`Top | `Bottom | `Cursor]) () =
409 | `Top -> self#goto_top
411 (try while true do self#_advance () done with Margin -> ())
413 let locked_iter () = buffer#get_iter_at_mark (`NAME "locked") in
414 let cursor_iter () = buffer#get_iter_at_mark `INSERT in
415 let rec forward_until_cursor () = (* go forward until locked > cursor *)
417 if (locked_iter ())#compare (cursor_iter ()) < 0 then
418 forward_until_cursor ()
420 let rec back_until_cursor () = (* go backward until locked < cursor *)
422 if (locked_iter ())#compare (cursor_iter ()) > 0 then
425 let cmp = (locked_iter ())#compare (cursor_iter ()) in
427 if cmp < 0 then (* locked < cursor *)
428 forward_until_cursor ()
429 else if cmp > 0 then (* locked > cursor *)
431 else (* cursor = locked *)
435 method onGoingProof () =
436 match self#status.proof_status with
437 | No_proof | Proof _ -> false
438 | Incomplete_proof _ -> true
439 | Intermediate _ -> assert false
441 method proofStatus = MatitaMisc.get_proof_status self#status
442 method proofMetasenv = MatitaMisc.get_proof_metasenv self#status
443 method proofContext = MatitaMisc.get_proof_context self#status
444 method setGoal n = userGoal <- n
448 MatitaLog.debug "script status:";
449 MatitaLog.debug ("history size: " ^ string_of_int (List.length history));
450 MatitaLog.debug (sprintf "%d statements:" (List.length statements));
451 List.iter MatitaLog.debug statements;
455 let _script = ref None
457 let script ~buffer ~init ~mathviewer ~urichooser () =
458 let s = new script ~buffer ~init ~mathviewer ~urichooser () in
462 let instance () = match !_script with None -> assert false | Some s -> s