]> matita.cs.unibo.it Git - helm.git/blob - matita/contribs/formal_topology/bin/theory_explorer.ml
New asserts.
[helm.git] / matita / contribs / formal_topology / bin / theory_explorer.ml
1 type rel = Equal | SubsetEqual | SupersetEqual
2
3 let string_of_rel =
4  function
5     Equal -> "="
6   | SubsetEqual -> "⊆"
7   | SupersetEqual -> "⊇"
8
9 (* operator *)
10 type op = I | C | M
11
12 let string_of_op =
13  function
14     I -> "i"
15   | C -> "c"
16   | M -> "-"
17
18 (* compound operator *)
19 type compound_operator = op list
20
21 let string_of_cop op =
22  if op = [] then "id" else String.concat "" (List.map string_of_op op)
23
24 let dot_of_cop op = "\"" ^ string_of_cop op ^ "\""
25
26 let rec matita_of_cop v =
27  function
28   | [] -> v
29   | I::tl -> "i (" ^ matita_of_cop v tl ^ ")"
30   | C::tl -> "c (" ^ matita_of_cop v tl ^ ")"
31   | M::tl -> "m (" ^ matita_of_cop v tl ^ ")"
32
33 (* representative, other elements in the equivalence class,
34    leq classes, geq classes *)
35 type equivalence_class =
36  compound_operator * compound_operator list *
37   equivalence_class list ref * equivalence_class list ref
38
39 let (===) (repr,_,_,_) (repr',_,_,_) = repr = repr';;
40 let (<=>) (repr,_,_,_) (repr',_,_,_) = repr <> repr';;
41
42 let string_of_equivalence_class (repr,others,leq,_) =
43  String.concat " = " (List.map string_of_cop (repr::others)) ^
44   (if !leq <> [] then
45     "\n" ^
46      String.concat "\n" 
47       (List.map
48         (function (repr',_,_,_) ->
49            string_of_cop repr ^ " ⊆ " ^ string_of_cop repr') !leq)
50    else
51     "")
52
53 let dot_of_equivalence_class (repr,others,leq,_) =
54  (if others <> [] then
55    let eq = String.concat " = " (List.map string_of_cop (repr::others)) in
56     dot_of_cop repr ^ "[label=\"" ^ eq ^ "\"];" ^
57      if !leq = [] then "" else "\n"
58   else if !leq = [] then
59    dot_of_cop repr ^ ";"
60   else
61    "") ^
62    String.concat "\n" 
63     (List.map
64       (function (repr',_,_,_) ->
65          dot_of_cop repr' ^ " -> " ^ dot_of_cop repr ^ ";") !leq)
66
67 (* set of equivalence classes, infima, suprema *)
68 type set =
69  equivalence_class list * equivalence_class list * equivalence_class list
70
71 let string_of_set (s,_,_) =
72  String.concat "\n" (List.map string_of_equivalence_class s)
73
74 let ps_of_set (to_be_considered,under_consideration,news) ?processing (s,inf,sup) =
75  let ch = open_out "xxx.dot" in
76   output_string ch "digraph G {\n";
77   (match under_consideration with
78       None -> ()
79     | Some repr ->
80        output_string ch (dot_of_cop repr ^ " [color=yellow];"));
81   List.iter
82    (function (repr,_,_,_) ->
83      if List.exists (function (repr',_,_,_) -> repr=repr') sup then
84       output_string ch (dot_of_cop repr ^ " [shape=Mdiamond];")
85      else
86       output_string ch (dot_of_cop repr ^ " [shape=diamond];")
87    ) inf ;
88   List.iter
89    (function (repr,_,_,_) ->
90      if not (List.exists (function (repr',_,_,_) -> repr=repr') inf) then
91       output_string ch (dot_of_cop repr ^ " [shape=polygon];")
92    ) sup ;
93   List.iter
94    (function repr -> output_string ch (dot_of_cop repr ^ " [color=green];")
95    ) to_be_considered ;
96   List.iter
97    (function repr -> output_string ch (dot_of_cop repr ^ " [color=navy];")
98    ) news ;
99   output_string ch (String.concat "\n" (List.map dot_of_equivalence_class s));
100   output_string ch "\n";
101   (match processing with
102       None -> ()
103     | Some (repr,rel,repr') ->
104        output_string ch (dot_of_cop repr ^ " [color=red];");
105        let repr,repr' =
106         match rel with
107            SupersetEqual -> repr',repr
108          | Equal
109          | SubsetEqual -> repr,repr'
110        in
111         output_string ch
112          (dot_of_cop repr' ^ " -> " ^ dot_of_cop repr ^
113           " [" ^
114           (match rel with Equal -> "arrowhead=none " | _ -> "") ^
115           "style=dashed];\n"));
116   output_string ch "}\n";
117   close_out ch;
118   (*ignore (Unix.system "tred xxx.dot > yyy.dot && dot -Tps yyy.dot > xxx.ps")*)
119   ignore (Unix.system "cp xxx.ps xxx_old.ps && dot -Tps xxx.dot > xxx.ps");
120   (*ignore (read_line ())*)
121 ;;
122
123 let test to_be_considered_and_now ((s,_,_) as set) rel candidate repr =
124  ps_of_set to_be_considered_and_now ~processing:(candidate,rel,repr) set;
125  print_string
126   (string_of_cop candidate ^ " " ^ string_of_rel rel ^ " " ^ string_of_cop repr ^ "? ");
127  flush stdout;
128  assert (Unix.system "cp formal_topology.ma xxx.ma" = Unix.WEXITED 0);
129  let ch = open_out_gen [Open_append] 0 "xxx.ma" in
130  let i = ref 0 in
131   List.iter
132    (function (repr,others,leq,_) ->
133      List.iter
134       (function repr' ->
135         incr i;
136         output_string ch
137          ("axiom ax" ^ string_of_int !i ^
138           ": \\forall A." ^
139            matita_of_cop "A" repr ^ " = " ^ matita_of_cop "A" repr' ^ ".\n");
140       ) others;
141      List.iter
142       (function (repr',_,_,_) ->
143         incr i;
144         output_string ch
145          ("axiom ax" ^ string_of_int !i ^
146           ": \\forall A." ^
147            matita_of_cop "A" repr ^ " ⊆ " ^ matita_of_cop "A" repr' ^ ".\n");
148       ) !leq;
149    ) s;
150   let candidate',rel',repr' =
151    match rel with
152       SupersetEqual -> repr,SubsetEqual,candidate
153     | Equal
154     | SubsetEqual -> candidate,rel,repr
155   in
156   output_string ch
157    ("theorem foo: \\forall A." ^ matita_of_cop "A" candidate' ^
158       " " ^ string_of_rel rel' ^ " " ^
159       matita_of_cop "A" repr' ^ ". intros; auto size=6 depth=4. qed.\n");
160   close_out ch;
161   let res =
162    (*Unix.system "../../../matitac.opt xxx.ma >> log 2>&1" = Unix.WEXITED 0*)
163    Unix.system "../../../matitac.opt xxx.ma > /dev/null 2>&1" = Unix.WEXITED 0
164   in
165    print_endline (if res then "y" else "n");
166    res
167
168 let remove node = List.filter (fun node' -> node <=> node');;
169
170 let add_leq_arc ((_,_,leq,_) as node) ((_,_,_,geq') as node') =
171  leq := node' :: !leq;
172  geq' := node :: !geq'
173 ;;
174
175 let add_geq_arc ((_,_,_,geq) as node) ((_,_,leq',_) as node') =
176  geq := node' :: !geq;
177  leq' := node :: !leq'
178 ;;
179
180 let remove_leq_arc ((_,_,leq,_) as node) ((_,_,_,geq') as node') =
181  leq := remove node' !leq;
182  geq' := remove node !geq'
183 ;;
184
185 let remove_geq_arc ((_,_,_,geq) as node) ((_,_,leq',_) as node') =
186  geq := remove node' !geq;
187  leq' := remove node !leq'
188 ;;
189
190 let leq_transitive_closure node node' =
191  add_leq_arc node node';
192  let rec remove_transitive_arcs ((_,_,_,geq) as node) (_,_,leq',_) =
193   let rec remove_arcs_to_ascendents =
194    function
195       [] -> ()
196     | (_,_,leq,_) as node'::tl ->
197        remove_leq_arc node node';
198        remove_arcs_to_ascendents (!leq@tl)
199   in
200    remove_arcs_to_ascendents !leq';
201    List.iter (function son -> remove_transitive_arcs son node) !geq
202  in
203   remove_transitive_arcs node node'
204 ;;
205
206 let geq_transitive_closure node node' =
207  add_geq_arc node node';
208  let rec remove_transitive_arcs ((_,_,leq,_) as node) (_,_,_,geq') =
209   let rec remove_arcs_to_descendents =
210    function
211       [] -> ()
212     | (_,_,_,geq) as node'::tl ->
213        remove_geq_arc node node';
214        remove_arcs_to_descendents (!geq@tl)
215   in
216    remove_arcs_to_descendents !geq';
217    List.iter (function father -> remove_transitive_arcs father node) !leq
218  in
219   remove_transitive_arcs node node'
220 ;;
221
222 let (@@) l1 n = if List.exists (function n' -> n===n') l1 then l1 else l1@[n]
223
224 let rec leq_reachable node =
225  function
226     [] -> false
227   | node'::_ when node === node' -> true
228   | (_,_,leq,_)::tl -> leq_reachable node (!leq@tl)
229 ;;
230
231 let rec geq_reachable node =
232  function
233     [] -> false
234   | node'::_ when node === node' -> true
235   | (_,_,_,geq)::tl -> geq_reachable node (!geq@tl)
236 ;;
237
238 let locate_using_leq to_be_considered_and_now ((repr,_,leq,_) as node)
239  set start
240 =
241  let rec aux ((nodes,inf,sup) as set) =
242   function
243      [] -> set
244    | (repr',_,_,geq') as node' :: tl ->
245        if repr=repr' then aux set (!geq'@tl)
246        else if leq_reachable node' !leq then
247         aux set tl
248        else if test to_be_considered_and_now set SubsetEqual repr repr' then
249         begin
250          let sup = remove node sup in
251          let inf = if !geq' = [] then (remove node' inf)@@node else inf in
252           leq_transitive_closure node node';
253           aux (nodes,inf,sup) (!geq'@tl)
254         end
255        else
256         aux set tl
257  in
258   aux set start
259 ;;
260
261 exception SameEquivalenceClass of equivalence_class * equivalence_class;;
262
263 let locate_using_geq to_be_considered_and_now ((repr,_,leq,geq) as node)
264  set start
265 =
266  let rec aux ((nodes,inf,sup) as set) =
267   function
268      [] -> set
269    | (repr',_,leq',_) as node' :: tl ->
270        if repr=repr' then aux set (!leq'@tl)
271        else if geq_reachable node' !geq then
272         aux set tl
273        else if test to_be_considered_and_now set SupersetEqual repr repr' then
274         begin
275          if List.exists (function n -> n===node') !leq then
276           (* We have found two equal nodes! *)
277           raise (SameEquivalenceClass (node,node'))
278          else
279           begin
280            let inf = remove node inf in
281            let sup = if !leq' = [] then (remove node' sup)@@node else sup in
282             geq_transitive_closure node node';
283             aux (nodes,inf,sup) (!leq'@tl)
284           end
285         end
286        else
287         aux set tl
288  in
289   aux set start
290 ;;
291
292 let analyze_one to_be_considered repr hecandidate (news,((nodes,inf,sup) as set)) =
293 if not (List.for_all (fun ((_,_,_,geq) as node) -> !geq = [] && let rec check_sups = function [] -> true | (_,_,leq,_) as node::tl -> if !leq = [] then List.exists (fun n -> n===node) sup && check_sups tl else check_sups (!leq@tl) in check_sups [node]) inf) then (ps_of_set ([],None,[]) set; assert false);
294 if not (List.for_all (fun ((_,_,leq,_) as node) -> !leq = [] && let rec check_infs = function [] -> true | (_,_,_,geq) as node::tl -> if !geq = [] then List.exists (fun n -> n===node) inf && check_infs tl else check_infs (!geq@tl) in check_infs [node]) sup) then (ps_of_set ([],None,[]) set; assert false);
295  let candidate = hecandidate::repr in
296   if List.length (List.filter ((=) M) candidate) > 1 then
297    news,set
298   else
299    try
300     let leq = ref [] in
301     let geq = ref [] in
302     let node = candidate,[],leq,geq in
303     let nodes = nodes@[node] in
304     let set = nodes,inf@[node],sup@[node] in
305     let start_inf,start_sup =
306      let repr_node =
307       match List.filter (fun (repr',_,_,_) -> repr=repr') nodes with
308          [node] -> node
309        | _ -> assert false
310      in
311 inf,sup(*
312      match hecandidate with
313         I -> inf,[repr_node]
314       | C -> [repr_node],sup
315       | M -> inf,sup
316 *)
317     in
318     let set =
319      locate_using_leq (to_be_considered,Some repr,news) node set start_sup in
320 (
321 let _,inf,sup = set in
322 if not (List.for_all (fun ((_,_,_,geq) as node) -> !geq = [] && let rec check_sups = function [] -> true | (_,_,leq,_) as node::tl -> if !leq = [] then List.exists (fun n -> n===node) sup && check_sups tl else check_sups (!leq@tl) in check_sups [node]) inf) then (ps_of_set ([],None,[]) set; assert false);
323 if not (List.for_all (fun ((_,_,leq,_) as node) -> !leq = [] && let rec check_infs = function [] -> true | (_,_,_,geq) as node::tl -> if !geq = [] then List.exists (fun n -> n===node) inf && check_infs tl else check_infs (!geq@tl) in check_infs [node]) sup) then (ps_of_set ([],None,[]) set; assert false);
324 );
325     let set =
326      locate_using_geq (to_be_considered,Some repr,news) node set start_inf
327     in
328 (
329 let _,inf,sup = set in
330 if not (List.for_all (fun ((_,_,_,geq) as node) -> !geq = [] && let rec check_sups = function [] -> true | (_,_,leq,_) as node::tl -> if !leq = [] then List.exists (fun n -> n===node) sup && check_sups tl else check_sups (!leq@tl) in check_sups [node]) inf) then (ps_of_set ([],None,[]) set; assert false);
331 if not (List.for_all (fun ((_,_,leq,_) as node) -> !leq = [] && let rec check_infs = function [] -> true | (_,_,_,geq) as node::tl -> if !geq = [] then List.exists (fun n -> n===node) inf && check_infs tl else check_infs (!geq@tl) in check_infs [node]) sup) then (ps_of_set ([],None,[]) set; assert false);
332 );
333      news@[candidate],set
334    with
335     SameEquivalenceClass ((_,_,leq_d,geq_d) as node_to_be_deleted,node') ->
336      let rec clean =
337       function
338          [] -> []
339        | (repr',others,leq,geq) as node::tl ->
340           leq :=
341            List.fold_right
342             (fun node l ->
343               if node_to_be_deleted <=> node then
344                node::l
345               else
346                !leq_d@l
347             ) !leq [];
348           geq :=
349            List.fold_right
350             (fun node l ->
351               if node_to_be_deleted <=> node then
352                node::l
353               else
354                !geq_d@l
355             ) !geq [];
356           if node===node' then
357            (repr',others@[candidate],leq,geq)::clean tl
358           else
359            node::clean tl
360      in
361      let nodes = clean nodes in
362       news,(nodes,inf,sup)
363 ;;
364
365 let rec explore i (set:set) news =
366  let rec aux news set =
367   function
368      [] -> news,set
369    | repr::tl ->
370       let news,set =
371        List.fold_right (analyze_one tl repr) [I;C;M] (news,set)
372       in
373        aux news set tl
374  in
375   let news,set = aux [] set news in
376    if news = [] then
377     begin
378      print_endline ("PUNTO FISSO RAGGIUNTO! i=" ^ string_of_int i);
379      print_endline (string_of_set set ^ "\n----------------");
380      ps_of_set ([],None,[]) set
381     end
382    else
383     begin
384      print_endline ("NUOVA ITERAZIONE, i=" ^ string_of_int i);
385      print_endline (string_of_set set ^ "\n----------------");
386      explore (i+1) set news
387     end
388 in
389  let id = [] in
390  let id_node = id,[],ref [], ref [] in
391  let set = [id_node],[id_node],[id_node] in
392   print_endline ("PRIMA ITERAZIONE, i=0, j=0");
393   print_endline (string_of_set set ^ "\n----------------");
394   (*ignore (Unix.system "rm -f log");*)
395   ps_of_set ([id],None,[]) set;
396   explore 1 set [id]
397 ;;