]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/tactics/variousTactics.ml
Adding file match_concl
[helm.git] / helm / ocaml / tactics / variousTactics.ml
index 98c13e80b8b742b775df418788b1eaa215fc17e1..bb5be64d8837a8592560ecaf7ef8a3f6072672e1 100644 (file)
@@ -51,53 +51,87 @@ let search_theorems_in_context status =
     prerr_endline ("SIAM QUI = " ^ s); []
 ;;     
 
-
+exception NotAProposition;;
 exception NotApplicableTheorem;;
 exception MaxDepth;;
 
-let depth = 5;;
+let depth = 3;;
 
-let rec auto_tac mqi_handle level proof goal = 
-prerr_endline "Entro in Auto_rec";
+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
   (* (proof, [goal]) *)
-  (prerr_endline ("NON ci credo");
+  (prerr_endline ("MaxDepth");
    raise MaxDepth)
 else 
-  (* choices is a list of pairs proof and goallist *)
-  let choices  =
-    (search_theorems_in_context (proof,goal))@ 
-    (TacticChaser.searchTheorems mqi_handle (proof,goal))
-  in
-  let rec try_choices = function
-    [] -> raise NotApplicableTheorem
-  | (proof,goallist)::tl ->
+  (* let us verify that the metavariable is still an open goal --
+     it could have been closed by closing other goals -- and that
+     it is of sort Prop *)
+  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 (ey, ty) ->
+        prerr_endline ("CURRENT GOAL = " ^ (CicPp.ppterm ty));
+        (*
+        let time1 = Unix.gettimeofday() in
+       let _, all_paths = NewConstraints.prefixes 5 ty in
+        let time2 = Unix.gettimeofday() in
+        prerr_endline 
+         (Printf.sprintf "TEMPO DI CALCOLO = %1.3f" (time2 -. time1) );
+       prerr_endline 
+         ("ALL PATHS: n = " ^ string_of_int 
+            (List.length all_paths));
+       prerr_endline (NewConstraints.pp_prefixes all_paths); 
+        *)
+       (* if the goal does not have a sort Prop we return the
+          current proof and a list containing the goal *)
+       let ty_sort = CicTypeChecker.type_of_aux' metasenv ey ty in
+         if CicReduction.are_convertible 
+           ey (Cic.Sort Cic.Prop) ty_sort then
+           (* sort Prop *)
+           (* choices is a list of pairs proof and goallist *)
+           let choices  =
+             (search_theorems_in_context (proof,goal))@ 
+             (TacticChaser.searchTheorems mqi_handle (proof,goal)) 
+           in
+           let rec try_choices = function
+               [] -> raise NotApplicableTheorem
+             | (proof,goallist)::tl ->
 prerr_endline ("GOALLIST = " ^ string_of_int (List.length goallist));
-       (try 
-          List.fold_left 
-            (fun proof goal ->
-              (* It may happen that to close the first open goal
-                 also some other goals are closed *)
-              let _,metasenv,_,_ = proof in
-               if List.exists (fun (i,_,_) -> i = goal) metasenv then
-                let newproof =
-                 auto_tac mqi_handle (level-1) proof goal
-                in
-                 newproof
-               else
-                (* goal already closed *)
-                proof)
-          proof goallist
-        with 
-       | MaxDepth
-        | NotApplicableTheorem ->
-            try_choices tl) in
- try_choices choices;;
+                 (try 
+                    List.fold_left 
+                      (fun proof goal ->
+                           auto_tac_aux mqi_handle (level-1) proof goal)
+                      proof goallist
+                  with 
+                    | MaxDepth
+                    | NotApplicableTheorem 
+                     | NotAProposition ->
+                        try_choices tl) in
+             try_choices choices
+         else
+            (* CUT AND PASTE DI PROVA !! *)
+            let choices  =
+             (search_theorems_in_context (proof,goal))@ 
+             (TacticChaser.searchTheorems mqi_handle (proof,goal)) 
+           in
+           let rec try_choices = function
+               [] -> raise NotApplicableTheorem
+             | (proof,[])::tl -> proof
+              | _::tl -> try_choices tl in
+           try_choices choices
+           (* raise NotAProposition *)
+    | None -> proof
+;;
 
 let auto_tac mqi_handle (proof,goal) =
   prerr_endline "Entro in Auto";
   try 
-    let proof = auto_tac mqi_handle depth proof goal in
+    let proof = auto_tac_aux mqi_handle depth proof goal in
 prerr_endline "AUTO_TAC HA FINITO";
     (proof,[])
   with