]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/tactics/variousTactics.ml
Nuova implementazione di Auto "breadth-first".
[helm.git] / helm / ocaml / tactics / variousTactics.ml
index f8c9cfa94dd409b67f65cbbfe332681473978eef..0df44420c99ef25f52511d5a4ba46c1927afc2c8 100644 (file)
@@ -85,6 +85,7 @@ exception MaxDepth;;
 
 let depth = 3;;
 
+(*
 let rec auto_tac_aux mqi_handle level proof goal = 
 prerr_endline ("Entro in Auto_rec; level = " ^ (string_of_int level));
 if level = 0 then
@@ -168,6 +169,59 @@ prerr_endline "AUTO_TAC HA FINITO";
   | NotApplicableTheorem -> 
       prerr_endline("No applicable theorem");
       raise (ProofEngineTypes.Fail "No Applicable theorem");;
+*)
+
+(**** ESPERIMENTO ************************)
+
+let new_search_theorems f proof goal depth gtl =
+  let local_choices = f (proof,goal)
+  in 
+  List.map 
+    (function (proof, goallist) ->
+       (proof, (List.map (function g -> (g,depth)) goallist)@gtl))
+    local_choices 
+;;
+
+exception NoOtherChoices;;
+
+let rec auto_new mqi_handle = function
+    [] -> raise NoOtherChoices
+  | (proof, [])::tl -> (proof, [])::tl
+  | (proof, (goal,0)::gtl)::tl -> auto_new mqi_handle tl
+  | (proof, (goal,depth)::gtl)::tl ->
+      let _,metasenv,_,_ = proof in
+      let meta_inf = 
+       (try 
+          let (_, ey ,ty) = CicUtil.lookup_meta goal metasenv in
+            Some (ey, ty)
+        with _ -> None) in
+       match meta_inf with
+           Some _ ->
+             let local_choices =
+               new_search_theorems 
+                 search_theorems_in_context proof goal (depth-1) gtl in
+             let global_choices =
+               new_search_theorems 
+                 (TacticChaser.searchTheorems mqi_handle) 
+                 proof goal (depth-1) gtl in
+             let all_choices =
+               local_choices@global_choices@tl in
+             let reorder = all_choices in
+               auto_new mqi_handle reorder
+         | None -> auto_new mqi_handle ((proof,gtl)::tl)
+;;
+
+
+let auto_tac mqi_handle (proof,goal) =
+  prerr_endline "Entro in Auto";
+  try 
+    let (proof,_)::_ = auto_new mqi_handle [(proof, [(goal,depth)])] in
+prerr_endline "AUTO_TAC HA FINITO";
+    (proof,[])
+  with 
+  | NoOtherChoices ->
+      prerr_endline("Auto failed");
+      raise (ProofEngineTypes.Fail "No Applicable theorem");;
 
 (* TODO se ce n'e' piu' di una, prende la prima che trova... sarebbe meglio
 chiedere: find dovrebbe restituire una lista di hyp (?) da passare all'utonto con una