1 (* Copyright (C) 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/
31 let debug_print s = if debug then prerr_endline (Lazy.force s) else ()
33 exception Error of string lazy_t
34 let fail msg = raise (Error msg)
36 type goal = ProofEngineTypes.goal
40 type switch = Open of goal | Closed of goal
41 type locator = int * switch
42 type tag = [ `BranchTag | `FocusTag | `NoTag ]
43 type entry = locator list * locator list * locator list * tag
46 let empty = [ [], [], [], `NoTag ]
48 let fold ~env ~cont ~todo init stack =
49 let rec aux acc depth =
52 | (locs, todos, conts, tag) :: tl ->
53 let acc = List.fold_left (fun acc -> env acc depth tag) acc locs in
54 let acc = List.fold_left (fun acc -> cont acc depth tag) acc conts in
55 let acc = List.fold_left (fun acc -> todo acc depth tag) acc todos in
56 aux acc (depth + 1) tl
61 let iter ~env ~cont ~todo =
62 fold ~env:(fun _ -> env) ~cont:(fun _ -> cont) ~todo:(fun _ -> todo) ()
64 let map ~env ~cont ~todo =
65 let depth = ref ~-1 in
67 (fun (s, t, c, tag) ->
70 env d tag s, todo d tag t, cont d tag c, tag)
72 let is_open = function _, Open _ -> true | _ -> false
73 let close = function n, Open g -> n, Closed g | l -> l
74 let filter_open = List.filter is_open
76 function n, Open _ when n > 0 -> true | _,Closed _ -> true | _ -> false
77 let goal_of_loc = function _, Open g | _, Closed g -> g
78 let goal_of_switch = function Open g | Closed g -> g
79 let switch_of_loc = snd
81 let zero_pos = List.map (fun g -> 0, Open g)
84 let pos = ref 0 in (* positions are 1-based *)
85 List.map (function _, sw -> incr pos; !pos, sw) locs
90 | [] -> fail (lazy (sprintf "relative position %d not found" i))
91 | (i', _) as loc :: tl when i = i' -> loc, (List.rev acc) @ tl
92 | hd :: tl -> aux (hd :: acc) tl
98 List.map (fun l -> if List.mem (goal_of_loc l) gs then close l else l)
100 let rm _ _ = List.filter (fun l -> not (List.mem (goal_of_loc l) gs)) in
101 map ~env:close ~cont:rm ~todo:rm
105 | [] -> raise (Failure "Continuationals.find_goal")
106 | (l :: _, _ , _ , _) :: _ -> goal_of_loc l
107 | ( _ , _ , l :: _, _) :: _ -> goal_of_loc l
108 | ( _ , l :: _, _ , _) :: _ -> goal_of_loc l
109 | _ :: tl -> find_goal tl
114 | [ [], [], [], `NoTag ] -> true
117 let of_metasenv metasenv =
118 let goals = List.map (fun (g, _, _) -> g) metasenv in
119 [ zero_pos goals, [], [], `NoTag ]
121 let of_nmetasenv metasenv =
122 let goals = List.map (fun (g, _) -> g) metasenv in
123 [ zero_pos goals, [], [], `NoTag ]
127 | (locs, _, _, _) :: _ -> List.map switch_of_loc locs
132 | (locs, _, _, _) :: _ -> List.map goal_of_loc locs
137 | (_, _, _, tag) :: _ -> tag
142 | _ :: (locs, _, _, _) :: _ -> List.map goal_of_loc locs
146 let open_goals stack =
147 let add_open acc _ _ l = if is_open l then goal_of_loc l :: acc else acc in
148 List.rev (fold ~env:add_open ~cont:add_open ~todo:add_open [] stack)
150 let (@+) = (@) (* union *)
152 let (@-) s1 s2 = (* difference *)
154 (fun e acc -> if List.mem e s2 then acc else e :: acc)
157 let (@~-) locs gs = (* remove some goals from a locators list *)
159 (fun loc acc -> if List.mem (goal_of_loc loc) gs then acc else loc :: acc)
163 let pp_goal = string_of_int in
165 function Open g -> "o" ^ pp_goal g | Closed g -> "c" ^ pp_goal g
167 let pp_loc (i, s) = string_of_int i ^ pp_switch s in
168 let pp_env env = sprintf "[%s]" (String.concat ";" (List.map pp_loc env)) in
169 let pp_tag = function `BranchTag -> "B" | `FocusTag -> "F" | `NoTag -> "N" in
170 let pp_stack_entry (env, todo, cont, tag) =
171 sprintf "(%s, %s, %s, %s)" (pp_env env) (pp_env todo) (pp_env cont)
174 String.concat " :: " (List.map pp_stack_entry stack)
183 val mk_tactic : (input_status -> output_status) -> tactic
184 val apply_tactic : tactic -> input_status -> output_status
186 val goals : output_status -> goal list * goal list (** opened, closed goals *)
187 val get_stack : input_status -> Stack.t
188 val set_stack : Stack.t -> output_status -> output_status
190 val inject : input_status -> output_status
191 val focus : goal -> output_status -> input_status
217 | Tactical of tactical
219 val eval: t -> input_status -> output_status
222 module Make (S: Status) =
226 type input_status = S.input_status
227 type output_status = S.output_status
228 type tactic = S.tactic
244 | Tactical of tactical
249 | Semicolon -> "Semicolon"
252 | Pos i -> "Pos " ^ (String.concat "," (List.map string_of_int i))
253 | Wildcard -> "Wildcard"
256 sprintf "Focus [%s]" (String.concat "; " (List.map string_of_int gs))
257 | Unfocus -> "Unfocus"
258 | Tactical _ -> "Tactical <abs>"
260 let eval_tactical tactical ostatus switch =
261 match tactical, switch with
262 | Tactic tac, Open n ->
263 let ostatus = S.apply_tactic tac (S.focus n ostatus) in
264 let opened, closed = S.goals ostatus in
265 ostatus, opened, closed
266 | Skip, Closed n -> ostatus, [], [n]
267 | Tactic _, Closed _ -> fail (lazy "can't apply tactic to a closed goal")
268 | Skip, Open _ -> fail (lazy "can't skip an open goal")
270 let eval cmd istatus =
271 let stack = S.get_stack istatus in
272 debug_print (lazy (sprintf "EVAL CONT %s <- %s" (pp_t cmd) (pp stack)));
273 let new_stack stack = S.inject istatus, stack in
275 match cmd, stack with
276 | _, [] -> assert false
277 | Tactical tac, (g, t, k, tag) :: s ->
278 (* COMMENTED OUT TO ALLOW PARAMODULATION TO DO A
279 * auto paramodulation.try assumption.
280 * EVEN IF NO GOALS ARE LEFT OPEN BY AUTO.
282 if g = [] then fail (lazy "can't apply a tactic to zero goals");
285 debug_print (lazy ("context length " ^string_of_int (List.length g)));
286 let rec aux s go gc =
290 debug_print (lazy "inner eval tactical");
292 if List.exists ((=) (goal_of_loc loc)) gc then
295 let s, go', gc' = eval_tactical tac s (switch_of_loc loc) in
296 s, (go @- gc') @+ go', gc @+ gc'
300 let s0, go0, gc0 = S.inject istatus, [], [] in
301 let sn, gon, gcn = aux s0 go0 gc0 g in
302 debug_print (lazy ("opened: "
303 ^ String.concat " " (List.map string_of_int gon)));
304 debug_print (lazy ("closed: "
305 ^ String.concat " " (List.map string_of_int gcn)));
307 (zero_pos gon, t @~- gcn, k @~- gcn, tag) :: deep_close gcn s
310 | Dot, ([], _, [], _) :: _ ->
311 (* backward compatibility: do-nothing-dot *)
313 | Dot, (g, t, k, tag) :: s ->
314 (match filter_open g, k with
315 | loc :: loc_tl, _ -> new_stack (([ loc ], t, loc_tl @+ k, tag) :: s)
317 assert (is_open loc);
318 new_stack (([ loc ], t, k, tag) :: s)
319 | _ -> fail (lazy "can't use \".\" here"))
320 | Semicolon, _ -> new_stack stack
321 | Branch, (g, t, k, tag) :: s ->
322 (match init_pos g with
323 | [] | [ _ ] -> fail (lazy "too few goals to branch");
326 (([ loc ], [], [], `BranchTag) :: (loc_tl, t, k, tag) :: s))
327 | Shift, (g, t, k, `BranchTag) :: (g', t', k', tag) :: s ->
329 | [] -> fail (lazy "no more goals to shift")
332 (([ loc ], t @+ filter_open g @+ k, [],`BranchTag)
333 :: (loc_tl, t', k', tag) :: s))
334 | Shift, _ -> fail (lazy "can't shift goals here")
335 | Pos i_s, ([ loc ], t, [],`BranchTag) :: (g', t', k', tag) :: s
337 let l_js = List.filter (fun (i, _) -> List.mem i i_s) ([loc] @+ g') in
339 ((l_js, t , [],`BranchTag)
340 :: (([ loc ] @+ g') @- l_js, t', k', tag) :: s)
341 | Pos _, _ -> fail (lazy "can't use relative positioning here")
342 | Wildcard, ([ loc ] , t, [], `BranchTag) :: (g', t', k', tag) :: s
345 (([loc] @+ g', t, [], `BranchTag)
346 :: ([], t', k', tag) :: s)
347 | Wildcard, _ -> fail (lazy "can't use wildcard here")
348 | Merge, (g, t, k,`BranchTag) :: (g', t', k', tag) :: s ->
349 new_stack ((t @+ filter_open g @+ g' @+ k, t', k', tag) :: s)
350 | Merge, _ -> fail (lazy "can't merge goals here")
351 | Focus [], _ -> assert false
354 let add_l acc _ _ l = if is_open l then l :: acc else acc in
355 Stack.fold ~env:add_l ~cont:add_l ~todo:add_l [] s
359 if not (List.exists (fun l -> goal_of_loc l = g) stack_locs) then
360 fail (lazy (sprintf "goal %d not found (or closed)" g)))
362 new_stack ((zero_pos gs, [], [], `FocusTag) :: deep_close gs s)
363 | Unfocus, ([], [], [], `FocusTag) :: s -> new_stack s
364 | Unfocus, _ -> fail (lazy "can't unfocus, some goals are still open")
366 debug_print (lazy (sprintf "EVAL CONT %s -> %s" (pp_t cmd) (pp stack)));
367 S.set_stack stack ostatus