Coccinelle release 1.0.0-rc14
[bpt/coccinelle.git] / ctl / ctl_engine.ml
CommitLineData
f537ebc4 1(*
17ba0788
C
2 * Copyright 2012, INRIA
3 * Julia Lawall, Gilles Muller
4 * Copyright 2010-2011, INRIA, University of Copenhagen
f537ebc4
C
5 * Julia Lawall, Rene Rydhof Hansen, Gilles Muller, Nicolas Palix
6 * Copyright 2005-2009, Ecole des Mines de Nantes, University of Copenhagen
7 * Yoann Padioleau, Julia Lawall, Rene Rydhof Hansen, Henrik Stuart, Gilles Muller, Nicolas Palix
8 * This file is part of Coccinelle.
9 *
10 * Coccinelle is free software: you can redistribute it and/or modify
11 * it under the terms of the GNU General Public License as published by
12 * the Free Software Foundation, according to version 2 of the License.
13 *
14 * Coccinelle is distributed in the hope that it will be useful,
15 * but WITHOUT ANY WARRANTY; without even the implied warranty of
16 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
17 * GNU General Public License for more details.
18 *
19 * You should have received a copy of the GNU General Public License
20 * along with Coccinelle. If not, see <http://www.gnu.org/licenses/>.
21 *
22 * The authors reserve the right to distribute this or future versions of
23 * Coccinelle under other licenses.
24 *)
25
26
feec80c3 27# 0 "./ctl_engine.ml"
34e49164
C
28(*external c_counter : unit -> int = "c_counter"*)
29let timeout = 800
30(* Optimize triples_conj by first extracting the intersection of the two sets,
31which can certainly be in the intersection *)
32let pTRIPLES_CONJ_OPT = ref true
33(* For complement, make NegState for the negation of a single state *)
34let pTRIPLES_COMPLEMENT_OPT = ref true
35(* For complement, do something special for the case where the environment
36and witnesses are empty *)
37let pTRIPLES_COMPLEMENT_SIMPLE_OPT = ref true
38(* "Double negate" the arguments of the path operators *)
39let pDOUBLE_NEGATE_OPT = ref true
40(* Only do pre_forall/pre_exists on new elements in fixpoint iteration *)
41let pNEW_INFO_OPT = ref true
42(* Filter the result of the label function to drop entries that aren't
43compatible with any of the available environments *)
44let pREQUIRED_ENV_OPT = ref true
45(* Memoize the raw result of the label function *)
46let pSATLABEL_MEMO_OPT = ref true
47(* Filter results according to the required states *)
48let pREQUIRED_STATES_OPT = ref true
49(* Drop negative witnesses at Uncheck *)
50let pUNCHECK_OPT = ref true
51let pANY_NEG_OPT = ref true
52let pLazyOpt = ref true
53
485bce71
C
54(* Nico: This stack is use for graphical traces *)
55let graph_stack = ref ([] : string list)
56let graph_hash = (Hashtbl.create 101)
57
34e49164
C
58(*
59let pTRIPLES_CONJ_OPT = ref false
60let pTRIPLES_COMPLEMENT_OPT = ref false
61let pTRIPLES_COMPLEMENT_SIMPLE_OPT = ref false
62let pDOUBLE_NEGATE_OPT = ref false
63let pNEW_INFO_OPT = ref false
64let pREQUIRED_ENV_OPT = ref false
65let pSATLABEL_MEMO_OPT = ref false
66let pREQUIRED_STATES_OPT = ref false
67let pUNCHECK_OPT = ref false
68let pANY_NEG_OPT = ref false
69let pLazyOpt = ref false
70*)
71
72
73let step_count = ref 0
74exception Steps
75let inc_step _ =
76 if not (!step_count = 0)
77 then
78 begin
79 step_count := !step_count - 1;
80 if !step_count = 0 then raise Steps
81 end
82
83let inc cell = cell := !cell + 1
84
85let satEU_calls = ref 0
86let satAW_calls = ref 0
87let satAU_calls = ref 0
88let satEF_calls = ref 0
89let satAF_calls = ref 0
90let satEG_calls = ref 0
91let satAG_calls = ref 0
92
93let triples = ref 0
94
95let ctr = ref 0
96let new_let _ =
97 let c = !ctr in
98 ctr := c + 1;
99 Printf.sprintf "_fresh_r_%d" c
100
101(* **********************************************************************
102 *
ae4735db
C
103 * Implementation of a Witness Tree model checking engine for CTL-FVex
104 *
34e49164
C
105 *
106 * **********************************************************************)
107
108(* ********************************************************************** *)
109(* Module: SUBST (substitutions: meta. vars and values) *)
110(* ********************************************************************** *)
111
112module type SUBST =
113 sig
114 type value
115 type mvar
116 val eq_mvar: mvar -> mvar -> bool
117 val eq_val: value -> value -> bool
118 val merge_val: value -> value -> value
119 val print_mvar : mvar -> unit
120 val print_value : value -> unit
121 end
122;;
123
124(* ********************************************************************** *)
125(* Module: GRAPH (control flow graphs / model) *)
126(* ********************************************************************** *)
127
128module type GRAPH =
129 sig
130 type node
131 type cfg
132 val predecessors: cfg -> node -> node list
133 val successors: cfg -> node -> node list
134 val extract_is_loop : cfg -> node -> bool
135 val print_node : node -> unit
136 val size : cfg -> int
485bce71
C
137 val print_graph : cfg -> string option ->
138 (node * string) list -> (node * string) list -> string -> unit
34e49164
C
139 end
140;;
141
ae4735db 142module OGRAPHEXT_GRAPH =
34e49164
C
143 struct
144 type node = int;;
145 type cfg = (string,unit) Ograph_extended.ograph_mutable;;
146 let predecessors cfg n = List.map fst ((cfg#predecessors n)#tolist);;
147 let print_node i = Format.print_string (Common.i_to_s i)
148 end
149;;
150
151(* ********************************************************************** *)
152(* Module: PREDICATE (predicates for CTL formulae) *)
153(* ********************************************************************** *)
154
155module type PREDICATE =
156sig
157 type t
158 val print_predicate : t -> unit
159end
160
161
162(* ********************************************************************** *)
163
164(* ---------------------------------------------------------------------- *)
165(* Misc. useful generic functions *)
166(* ---------------------------------------------------------------------- *)
167
485bce71
C
168let get_graph_files () = !graph_stack
169let get_graph_comp_files outfile = Hashtbl.find_all graph_hash outfile
170
34e49164
C
171let head = List.hd
172
ae4735db 173let tail l =
34e49164
C
174 match l with
175 [] -> []
176 | (x::xs) -> xs
177;;
178
179let foldl = List.fold_left;;
180
181let foldl1 f xs = foldl f (head xs) (tail xs)
182
183type 'a esc = ESC of 'a | CONT of 'a
184
185let foldr = List.fold_right;;
186
187let concat = List.concat;;
188
189let map = List.map;;
190
191let filter = List.filter;;
192
193let partition = List.partition;;
194
195let concatmap f l = List.concat (List.map f l);;
196
197let maybe f g opt =
198 match opt with
199 | None -> g
200 | Some x -> f x
201;;
202
203let some_map f opts = map (maybe (fun x -> Some (f x)) None) opts
204
205let some_tolist_alt opts = concatmap (maybe (fun x -> [x]) []) opts
206
207let rec some_tolist opts =
208 match opts with
209 | [] -> []
210 | (Some x)::rest -> x::(some_tolist rest)
ae4735db 211 | _::rest -> some_tolist rest
34e49164
C
212;;
213
214let rec groupBy eq l =
215 match l with
216 [] -> []
ae4735db 217 | (x::xs) ->
34e49164
C
218 let (xs1,xs2) = partition (fun x' -> eq x x') xs in
219 (x::xs1)::(groupBy eq xs2)
220;;
221
222let group l = groupBy (=) l;;
223
224let rec memBy eq x l =
225 match l with
226 [] -> false
227 | (y::ys) -> if (eq x y) then true else (memBy eq x ys)
228;;
229
230let rec nubBy eq ls =
231 match ls with
232 [] -> []
233 | (x::xs) when (memBy eq x xs) -> nubBy eq xs
234 | (x::xs) -> x::(nubBy eq xs)
235;;
236
237let rec nub ls =
238 match ls with
239 [] -> []
240 | (x::xs) when (List.mem x xs) -> nub xs
241 | (x::xs) -> x::(nub xs)
242;;
243
244let state_compare (s1,_,_) (s2,_,_) = compare s1 s2
245
246let setifyBy eq xs = nubBy eq xs;;
247
248let setify xs = nub xs;;
249
250let inner_setify xs = List.sort compare (nub xs);;
251
252let unionBy compare eq xs = function
253 [] -> xs
254 | ys ->
255 let rec loop = function
256 [] -> ys
257 | x::xs -> if memBy eq x ys then loop xs else x::(loop xs) in
258 List.sort compare (loop xs)
259;;
260
261let union xs ys = unionBy state_compare (=) xs ys;;
262
263let setdiff xs ys = filter (fun x -> not (List.mem x ys)) xs;;
264
265let subseteqBy eq xs ys = List.for_all (fun x -> memBy eq x ys) xs;;
266
267let subseteq xs ys = List.for_all (fun x -> List.mem x ys) xs;;
268let supseteq xs ys = subseteq ys xs
269
270let setequalBy eq xs ys = (subseteqBy eq xs ys) & (subseteqBy eq ys xs);;
271
272let setequal xs ys = (subseteq xs ys) & (subseteq ys xs);;
273
274(* Fix point calculation *)
275let rec fix eq f x =
276 let x' = f x in if (eq x' x) then x' else fix eq f x'
277;;
278
279(* Fix point calculation on set-valued functions *)
280let setfix f x = (fix subseteq f x) (*if new is a subset of old, stop*)
281let setgfix f x = (fix supseteq f x) (*if new is a supset of old, stop*)
282
283let get_states l = nub (List.map (function (s,_,_) -> s) l)
284
285(* ********************************************************************** *)
286(* Module: CTL_ENGINE *)
287(* ********************************************************************** *)
288
289module CTL_ENGINE =
ae4735db 290 functor (SUB : SUBST) ->
34e49164
C
291 functor (G : GRAPH) ->
292 functor (P : PREDICATE) ->
293struct
294
295module A = Ast_ctl
296
297type substitution = (SUB.mvar, SUB.value) Ast_ctl.generic_substitution
298
299type ('pred,'anno) witness =
300 (G.node, substitution,
301 ('pred, SUB.mvar, 'anno) Ast_ctl.generic_ctl list)
302 Ast_ctl.generic_witnesstree
303
304type ('pred,'anno) triples =
305 (G.node * substitution * ('pred,'anno) witness list) list
306
307(* ---------------------------------------------------------------------- *)
308(* Pretty printing functions *)
309(* ---------------------------------------------------------------------- *)
310
311let (print_generic_substitution : substitution -> unit) = fun substxs ->
312 let print_generic_subst = function
313 A.Subst (mvar, v) ->
190f1acf 314 SUB.print_mvar mvar; Format.print_string " --> "; SUB.print_value v
ae4735db 315 | A.NegSubst (mvar, v) ->
34e49164
C
316 SUB.print_mvar mvar; Format.print_string " -/-> "; SUB.print_value v in
317 Format.print_string "[";
318 Common.print_between (fun () -> Format.print_string ";" )
319 print_generic_subst substxs;
320 Format.print_string "]"
321
322let rec (print_generic_witness: ('pred, 'anno) witness -> unit) =
323 function
ae4735db 324 | A.Wit (state, subst, anno, childrens) ->
34e49164
C
325 Format.print_string "wit ";
326 G.print_node state;
327 print_generic_substitution subst;
328 (match childrens with
329 [] -> Format.print_string "{}"
ae4735db 330 | _ ->
34e49164
C
331 Format.force_newline(); Format.print_string " "; Format.open_box 0;
332 print_generic_witnesstree childrens; Format.close_box())
ae4735db 333 | A.NegWit(wit) ->
34e49164
C
334 Format.print_string "!";
335 print_generic_witness wit
336
337and (print_generic_witnesstree: ('pred,'anno) witness list -> unit) =
338 fun witnesstree ->
339 Format.open_box 1;
340 Format.print_string "{";
341 Common.print_between
ae4735db 342 (fun () -> Format.print_string ";"; Format.force_newline() )
34e49164
C
343 print_generic_witness witnesstree;
344 Format.print_string "}";
345 Format.close_box()
ae4735db 346
34e49164
C
347and print_generic_triple (node,subst,tree) =
348 G.print_node node;
349 print_generic_substitution subst;
350 print_generic_witnesstree tree
351
ae4735db 352and (print_generic_algo : ('pred,'anno) triples -> unit) = fun xs ->
34e49164
C
353 Format.print_string "<";
354 Common.print_between
355 (fun () -> Format.print_string ";"; Format.force_newline())
356 print_generic_triple xs;
357 Format.print_string ">"
358;;
359
360let print_state (str : string) (l : ('pred,'anno) triples) =
361 Printf.printf "%s\n" str;
362 List.iter (function x ->
363 print_generic_triple x; Format.print_newline(); flush stdout)
364 (List.sort compare l);
365 Printf.printf "\n"
ae4735db 366
34e49164
C
367let print_required_states = function
368 None -> Printf.printf "no required states\n"
369 | Some states ->
370 Printf.printf "required states: ";
371 List.iter
372 (function x ->
373 G.print_node x; Format.print_string " "; Format.print_flush())
374 states;
375 Printf.printf "\n"
376
377let mkstates states = function
378 None -> states
379 | Some states -> states
485bce71
C
380
381let print_graph grp required_states res str = function
382 A.Exists (keep,v,phi) -> ()
383 | phi ->
384 if !Flag_ctl.graphical_trace && not !Flag_ctl.checking_reachability
385 then
386 match phi with
387 | A.Exists (keep,v,phi) -> ()
388 | _ ->
389 let label =
390 Printf.sprintf "%s%s"
391 (String.escaped
392 (Common.format_to_string
393 (function _ ->
394 Pretty_print_ctl.pp_ctl
395 (P.print_predicate, SUB.print_mvar)
396 false phi)))
397 str in
398 let file = (match !Flag.currentfile with
399 None -> "graphical_trace"
400 | Some f -> f
401 ) in
402 (if not (List.mem file !graph_stack) then
403 graph_stack := file :: !graph_stack);
ae4735db
C
404 let filename = Filename.temp_file (file^":") ".dot" in
405 Hashtbl.add graph_hash file filename;
485bce71
C
406 G.print_graph grp
407 (if !Flag_ctl.gt_without_label then None else (Some label))
408 (match required_states with
409 None -> []
410 | Some required_states ->
411 (List.map (function s -> (s,"blue")) required_states))
412 (List.map (function (s,_,_) -> (s,"\"#FF8080\"")) res) filename
413
414let print_graph_c grp required_states res ctr phi =
415 let str = "iter: "^(string_of_int !ctr) in
416 print_graph grp required_states res str phi
417
34e49164
C
418(* ---------------------------------------------------------------------- *)
419(* *)
420(* ---------------------------------------------------------------------- *)
ae4735db
C
421
422
34e49164
C
423(* ************************* *)
424(* Substitutions *)
425(* ************************* *)
ae4735db 426
34e49164
C
427let dom_sub sub =
428 match sub with
429 | A.Subst(x,_) -> x
430 | A.NegSubst(x,_) -> x
431;;
ae4735db 432
34e49164
C
433let ran_sub sub =
434 match sub with
435 | A.Subst(_,x) -> x
436 | A.NegSubst(_,x) -> x
437;;
ae4735db 438
34e49164 439let eq_subBy eqx eqv sub sub' =
ae4735db 440 match (sub,sub') with
34e49164
C
441 | (A.Subst(x,v),A.Subst(x',v')) -> (eqx x x') && (eqv v v')
442 | (A.NegSubst(x,v),A.NegSubst(x',v')) -> (eqx x x') && (eqv v v')
443 | _ -> false
444;;
445
446(* NOTE: functor *)
447let eq_sub sub sub' = eq_subBy SUB.eq_mvar SUB.eq_val sub sub'
448
449let eq_subst th th' = setequalBy eq_sub th th';;
450
451let merge_subBy eqx (===) (>+<) sub sub' =
452 (* variable part is guaranteed to be the same *)
453 match (sub,sub') with
ae4735db 454 (A.Subst (x,v),A.Subst (x',v')) ->
34e49164
C
455 if (v === v')
456 then Some [A.Subst(x, v >+< v')]
457 else None
458 | (A.NegSubst(x,v),A.Subst(x',v')) ->
459 if (not (v === v'))
460 then Some [A.Subst(x',v')]
461 else None
462 | (A.Subst(x,v),A.NegSubst(x',v')) ->
463 if (not (v === v'))
464 then Some [A.Subst(x,v)]
465 else None
466 | (A.NegSubst(x,v),A.NegSubst(x',v')) ->
467 if (v === v')
468 then
469 let merged = v >+< v' in
470 if merged = v && merged = v'
471 then Some [A.NegSubst(x,v >+< v')]
472 else
473 (* positions are compatible, but not identical. keep apart. *)
474 Some [A.NegSubst(x,v);A.NegSubst(x',v')]
475 else Some [A.NegSubst(x,v);A.NegSubst(x',v')]
476;;
477
478(* NOTE: functor *)
5636bb2c 479(* How could we accomadate subterm constraints here??? *)
ae4735db 480let merge_sub sub sub' =
34e49164
C
481 merge_subBy SUB.eq_mvar SUB.eq_val SUB.merge_val sub sub'
482
483let clean_substBy eq cmp theta = List.sort cmp (nubBy eq theta);;
484
485(* NOTE: we sort by using the generic "compare" on (meta-)variable
ae4735db 486 * names; we could also require a definition of compare for meta-variables
34e49164
C
487 * or substitutions but that seems like overkill for sorting
488 *)
ae4735db
C
489let clean_subst theta =
490 let res =
34e49164
C
491 clean_substBy eq_sub
492 (fun s s' ->
493 let res = compare (dom_sub s) (dom_sub s') in
494 if res = 0
495 then
496 match (s,s') with
497 (A.Subst(_,_),A.NegSubst(_,_)) -> -1
498 | (A.NegSubst(_,_),A.Subst(_,_)) -> 1
499 | _ -> compare (ran_sub s) (ran_sub s')
500 else res)
501 theta in
502 let rec loop = function
503 [] -> []
504 | (A.Subst(x,v)::A.NegSubst(y,v')::rest) when SUB.eq_mvar x y ->
505 loop (A.Subst(x,v)::rest)
506 | x::xs -> x::(loop xs) in
507 loop res
508
509let top_subst = [];; (* Always TRUE subst. *)
510
511(* Split a theta in two parts: one with (only) "x" and one without *)
512(* NOTE: functor *)
ae4735db 513let split_subst theta x =
34e49164
C
514 partition (fun sub -> SUB.eq_mvar (dom_sub sub) x) theta;;
515
516exception SUBST_MISMATCH
517let conj_subst theta theta' =
518 match (theta,theta') with
519 | ([],_) -> Some theta'
520 | (_,[]) -> Some theta
521 | _ ->
522 let rec classify = function
523 [] -> []
524 | [x] -> [(dom_sub x,[x])]
525 | x::xs ->
526 (match classify xs with
527 ((nm,y)::ys) as res ->
528 if dom_sub x = nm
529 then (nm,x::y)::ys
530 else (dom_sub x,[x])::res
531 | _ -> failwith "not possible") in
532 let merge_all theta theta' =
533 foldl
534 (function rest ->
535 function sub ->
536 foldl
537 (function rest ->
538 function sub' ->
539 match (merge_sub sub sub') with
540 Some subs -> subs @ rest
541 | _ -> raise SUBST_MISMATCH)
542 rest theta')
543 [] theta in
544 let rec loop = function
545 ([],ctheta') ->
546 List.concat (List.map (function (_,ths) -> ths) ctheta')
547 | (ctheta,[]) ->
548 List.concat (List.map (function (_,ths) -> ths) ctheta)
549 | ((x,ths)::xs,(y,ths')::ys) ->
550 (match compare x y with
551 0 -> (merge_all ths ths') @ loop (xs,ys)
552 | -1 -> ths @ loop (xs,((y,ths')::ys))
553 | 1 -> ths' @ loop (((x,ths)::xs),ys)
554 | _ -> failwith "not possible") in
555 try Some (clean_subst(loop (classify theta, classify theta')))
556 with SUBST_MISMATCH -> None
557;;
558
559(* theta' must be a subset of theta *)
560let conj_subst_none theta theta' =
561 match (theta,theta') with
562 | (_,[]) -> Some theta
563 | ([],_) -> None
564 | _ ->
565 let rec classify = function
566 [] -> []
567 | [x] -> [(dom_sub x,[x])]
568 | x::xs ->
569 (match classify xs with
570 ((nm,y)::ys) as res ->
571 if dom_sub x = nm
572 then (nm,x::y)::ys
573 else (dom_sub x,[x])::res
574 | _ -> failwith "not possible") in
575 let merge_all theta theta' =
576 foldl
577 (function rest ->
578 function sub ->
579 foldl
580 (function rest ->
581 function sub' ->
582 match (merge_sub sub sub') with
583 Some subs -> subs @ rest
584 | _ -> raise SUBST_MISMATCH)
585 rest theta')
586 [] theta in
587 let rec loop = function
588 (ctheta,[]) ->
589 List.concat (List.map (function (_,ths) -> ths) ctheta)
590 | ([],ctheta') -> raise SUBST_MISMATCH
591 | ((x,ths)::xs,(y,ths')::ys) ->
592 (match compare x y with
593 0 -> (merge_all ths ths') @ loop (xs,ys)
594 | -1 -> ths @ loop (xs,((y,ths')::ys))
595 | 1 -> raise SUBST_MISMATCH
596 | _ -> failwith "not possible") in
597 try Some (clean_subst(loop (classify theta, classify theta')))
598 with SUBST_MISMATCH -> None
599;;
600
601let negate_sub sub =
602 match sub with
603 | A.Subst(x,v) -> A.NegSubst (x,v)
604 | A.NegSubst(x,v) -> A.Subst(x,v)
605;;
606
607(* Turn a (big) theta into a list of (small) thetas *)
608let negate_subst theta = (map (fun sub -> [negate_sub sub]) theta);;
609
610
611(* ************************* *)
612(* Witnesses *)
613(* ************************* *)
614
615(* Always TRUE witness *)
616let top_wit = ([] : (('pred, 'anno) witness list));;
617
618let eq_wit wit wit' = wit = wit';;
619
620let union_wit wit wit' = (*List.sort compare (wit' @ wit) for popl*)
621 let res = unionBy compare (=) wit wit' in
622 let anynegwit = (* if any is neg, then all are *)
623 List.exists (function A.NegWit _ -> true | A.Wit _ -> false) in
624 if anynegwit res
625 then List.filter (function A.NegWit _ -> true | A.Wit _ -> false) res
626 else res
627
628let negate_wit wit = A.NegWit wit (*
629 match wit with
630 | A.Wit(s,th,anno,ws) -> A.NegWitWit(s,th,anno,ws)
631 | A.NegWitWit(s,th,anno,ws) -> A.Wit(s,th,anno,ws)*)
632;;
633
634let negate_wits wits =
635 List.sort compare (map (fun wit -> [negate_wit wit]) wits);;
636
637let unwitify trips =
638 let anynegwit = (* if any is neg, then all are *)
639 List.exists (function A.NegWit _ -> true | A.Wit _ -> false) in
640 setify
641 (List.fold_left
642 (function prev ->
643 function (s,th,wit) ->
644 if anynegwit wit then prev else (s,th,top_wit)::prev)
645 [] trips)
646
647(* ************************* *)
648(* Triples *)
649(* ************************* *)
650
651(* Triples are equal when the constituents are equal *)
652let eq_trip (s,th,wit) (s',th',wit') =
653 (s = s') && (eq_wit wit wit') && (eq_subst th th');;
654
655let triples_top states = map (fun s -> (s,top_subst,top_wit)) states;;
656
657let normalize trips =
658 List.map
659 (function (st,th,wit) -> (st,List.sort compare th,List.sort compare wit))
660 trips
ae4735db 661
34e49164
C
662
663(* conj opt doesn't work ((1,[],{{x=3}}) v (1,[],{{x=4}})) & (1,[],{{x=4}}) =
664(1,[],{{x=3},{x=4}}), not (1,[],{{x=4}}) *)
665let triples_conj trips trips' =
666 let (trips,shared,trips') =
667 if false && !pTRIPLES_CONJ_OPT (* see comment above *)
668 then
669 let (shared,trips) =
670 List.partition (function t -> List.mem t trips') trips in
671 let trips' =
672 List.filter (function t -> not(List.mem t shared)) trips' in
673 (trips,shared,trips')
674 else (trips,[],trips') in
675 foldl (* returns a set - setify inlined *)
676 (function rest ->
677 function (s1,th1,wit1) ->
678 foldl
679 (function rest ->
680 function (s2,th2,wit2) ->
681 if (s1 = s2) then
682 (match (conj_subst th1 th2) with
683 Some th ->
684 let t = (s1,th,union_wit wit1 wit2) in
685 if List.mem t rest then rest else t::rest
686 | _ -> rest)
687 else rest)
688 rest trips')
689 shared trips
690;;
691
692(* ignore the state in the right argument. always pretend it is the same as
693the left one *)
694(* env on right has to be a subset of env on left *)
695let triples_conj_none trips trips' =
696 let (trips,shared,trips') =
697 if false && !pTRIPLES_CONJ_OPT (* see comment above *)
698 then
699 let (shared,trips) =
700 List.partition (function t -> List.mem t trips') trips in
701 let trips' =
702 List.filter (function t -> not(List.mem t shared)) trips' in
703 (trips,shared,trips')
704 else (trips,[],trips') in
705 foldl (* returns a set - setify inlined *)
706 (function rest ->
707 function (s1,th1,wit1) ->
708 foldl
709 (function rest ->
710 function (s2,th2,wit2) ->
711 match (conj_subst_none th1 th2) with
712 Some th ->
713 let t = (s1,th,union_wit wit1 wit2) in
714 if List.mem t rest then rest else t::rest
715 | _ -> rest)
716 rest trips')
717 shared trips
718;;
719
720exception AW
721
722let triples_conj_AW trips trips' =
723 let (trips,shared,trips') =
724 if false && !pTRIPLES_CONJ_OPT
725 then
726 let (shared,trips) =
727 List.partition (function t -> List.mem t trips') trips in
728 let trips' =
729 List.filter (function t -> not(List.mem t shared)) trips' in
730 (trips,shared,trips')
731 else (trips,[],trips') in
732 foldl (* returns a set - setify inlined *)
733 (function rest ->
734 function (s1,th1,wit1) ->
735 foldl
736 (function rest ->
737 function (s2,th2,wit2) ->
738 if (s1 = s2) then
739 (match (conj_subst th1 th2) with
740 Some th ->
741 let t = (s1,th,union_wit wit1 wit2) in
742 if List.mem t rest then rest else t::rest
743 | _ -> raise AW)
744 else rest)
745 rest trips')
746 shared trips
747;;
748
749(* *************************** *)
750(* NEGATION (NegState style) *)
751(* *************************** *)
752
753(* Constructive negation at the state level *)
754type ('a) state =
755 PosState of 'a
756 | NegState of 'a list
757;;
758
759let compatible_states = function
ae4735db 760 (PosState s1, PosState s2) ->
34e49164 761 if s1 = s2 then Some (PosState s1) else None
ae4735db 762 | (PosState s1, NegState s2) ->
34e49164 763 if List.mem s1 s2 then None else Some (PosState s1)
ae4735db 764 | (NegState s1, PosState s2) ->
34e49164
C
765 if List.mem s2 s1 then None else Some (PosState s2)
766 | (NegState s1, NegState s2) -> Some (NegState (s1 @ s2))
767;;
768
769(* Conjunction on triples with "special states" *)
770let triples_state_conj trips trips' =
771 let (trips,shared,trips') =
772 if !pTRIPLES_CONJ_OPT
773 then
774 let (shared,trips) =
775 List.partition (function t -> List.mem t trips') trips in
776 let trips' =
777 List.filter (function t -> not(List.mem t shared)) trips' in
778 (trips,shared,trips')
779 else (trips,[],trips') in
780 foldl
781 (function rest ->
782 function (s1,th1,wit1) ->
783 foldl
784 (function rest ->
785 function (s2,th2,wit2) ->
786 match compatible_states(s1,s2) with
787 Some s ->
788 (match (conj_subst th1 th2) with
789 Some th ->
790 let t = (s,th,union_wit wit1 wit2) in
791 if List.mem t rest then rest else t::rest
792 | _ -> rest)
793 | _ -> rest)
794 rest trips')
795 shared trips
796;;
797
ae4735db 798let triple_negate (s,th,wits) =
34e49164
C
799 let negstates = (NegState [s],top_subst,top_wit) in
800 let negths = map (fun th -> (PosState s,th,top_wit)) (negate_subst th) in
801 let negwits = map (fun nwit -> (PosState s,th,nwit)) (negate_wits wits) in
802 negstates :: (negths @ negwits) (* all different *)
803
804(* FIX ME: it is not necessary to do full conjunction *)
805let triples_complement states (trips : ('pred, 'anno) triples) =
806 if !pTRIPLES_COMPLEMENT_OPT
807 then
808 (let cleanup (s,th,wit) =
809 match s with
810 PosState s' -> [(s',th,wit)]
811 | NegState ss ->
812 assert (th=top_subst);
813 assert (wit=top_wit);
814 map (fun st -> (st,top_subst,top_wit)) (setdiff states ss) in
815 let (simple,complex) =
816 if !pTRIPLES_COMPLEMENT_SIMPLE_OPT
817 then
818 let (simple,complex) =
819 List.partition (function (s,[],[]) -> true | _ -> false) trips in
820 let simple =
821 [(NegState(List.map (function (s,_,_) -> s) simple),
822 top_subst,top_wit)] in
823 (simple,complex)
824 else ([(NegState [],top_subst,top_wit)],trips) in
825 let rec compl trips =
826 match trips with
827 [] -> simple
828 | (t::ts) -> triples_state_conj (triple_negate t) (compl ts) in
829 let compld = (compl complex) in
830 let compld = concatmap cleanup compld in
831 compld)
832 else
833 let negstates (st,th,wits) =
834 map (function st -> (st,top_subst,top_wit)) (setdiff states [st]) in
835 let negths (st,th,wits) =
836 map (function th -> (st,th,top_wit)) (negate_subst th) in
837 let negwits (st,th,wits) =
838 map (function nwit -> (st,th,nwit)) (negate_wits wits) in
839 match trips with
840 [] -> map (function st -> (st,top_subst,top_wit)) states
841 | x::xs ->
842 setify
843 (foldl
844 (function prev ->
845 function cur ->
846 triples_conj (negstates cur @ negths cur @ negwits cur) prev)
847 (negstates x @ negths x @ negwits x) xs)
848;;
849
ae4735db 850let triple_negate (s,th,wits) =
34e49164
C
851 let negths = map (fun th -> (s,th,top_wit)) (negate_subst th) in
852 let negwits = map (fun nwit -> (s,th,nwit)) (negate_wits wits) in
853 ([s], negths @ negwits) (* all different *)
854
855let print_compl_state str (n,p) =
856 Printf.printf "%s neg: " str;
857 List.iter
858 (function x -> G.print_node x; Format.print_flush(); Printf.printf " ")
859 n;
860 Printf.printf "\n";
861 print_state "pos" p
862
863let triples_complement states (trips : ('pred, 'anno) triples) =
864 if trips = []
865 then map (function st -> (st,top_subst,top_wit)) states
866 else
867 let cleanup (neg,pos) =
868 let keep_pos =
869 List.filter (function (s,_,_) -> List.mem s neg) pos in
870 (map (fun st -> (st,top_subst,top_wit)) (setdiff states neg)) @
871 keep_pos in
872 let trips = List.sort state_compare trips in
873 let all_negated = List.map triple_negate trips in
874 let merge_one (neg1,pos1) (neg2,pos2) =
875 let (pos1conj,pos1keep) =
876 List.partition (function (s,_,_) -> List.mem s neg2) pos1 in
877 let (pos2conj,pos2keep) =
878 List.partition (function (s,_,_) -> List.mem s neg1) pos2 in
879 (Common.union_set neg1 neg2,
880 (triples_conj pos1conj pos2conj) @ pos1keep @ pos2keep) in
881 let rec inner_loop = function
882 x1::x2::rest -> (merge_one x1 x2) :: (inner_loop rest)
883 | l -> l in
884 let rec outer_loop = function
885 [x] -> x
886 | l -> outer_loop (inner_loop l) in
887 cleanup (outer_loop all_negated)
888
889(* ********************************** *)
890(* END OF NEGATION (NegState style) *)
891(* ********************************** *)
892
893(* now this is always true, so we could get rid of it *)
894let something_dropped = ref true
895
896let triples_union trips trips' =
897 (*unionBy compare eq_trip trips trips';;*)
898 (* returns -1 is t1 > t2, 1 if t2 >= t1, and 0 otherwise *)
899(*
900The following does not work. Suppose we have ([x->3],{A}) and ([],{A,B}).
901Then, the following says that since the first is a more restrictive
902environment and has fewer witnesses, then it should be dropped. But having
903fewer witnesses is not necessarily less informative than having more,
904because fewer witnesses can mean the absence of the witness-causing thing.
905So the fewer witnesses have to be kept around.
906subseteq changed to = to make it hopefully work
907*)
908 if !pNEW_INFO_OPT
909 then
910 begin
911 something_dropped := false;
912 if trips = trips'
913 then (something_dropped := true; trips)
914 else
915 let subsumes (s1,th1,wit1) (s2,th2,wit2) =
916 if s1 = s2
917 then
918 (match conj_subst th1 th2 with
919 Some conj ->
920 if conj = th1
921 then if (*subseteq*) wit1 = wit2 then 1 else 0
922 else
923 if conj = th2
924 then if (*subseteq*) wit2 = wit1 then (-1) else 0
925 else 0
926 | None -> 0)
927 else 0 in
928 let rec first_loop second = function
929 [] -> second
930 | x::xs -> first_loop (second_loop x second) xs
931 and second_loop x = function
932 [] -> [x]
933 | (y::ys) as all ->
934 match subsumes x y with
935 1 -> something_dropped := true; all
936 | (-1) -> second_loop x ys
937 | _ -> y::(second_loop x ys) in
938 first_loop trips trips'
939 end
940 else unionBy compare eq_trip trips trips'
941
942
943let triples_witness x unchecked not_keep trips =
944 let anyneg = (* if any is neg, then all are *)
945 List.exists (function A.NegSubst _ -> true | A.Subst _ -> false) in
946 let anynegwit = (* if any is neg, then all are *)
947 List.exists (function A.NegWit _ -> true | A.Wit _ -> false) in
948 let allnegwit = (* if any is neg, then all are *)
949 List.for_all (function A.NegWit _ -> true | A.Wit _ -> false) in
950 let negtopos =
951 List.map (function A.NegWit w -> w | A.Wit _ -> failwith "bad wit")in
ae4735db 952 let res =
34e49164
C
953 List.fold_left
954 (function prev ->
955 function (s,th,wit) as t ->
956 let (th_x,newth) = split_subst th x in
957 match th_x with
958 [] ->
959 (* one consider whether if not not_keep is true, then we should
960 fail. but it could be that the variable is a used_after and
961 then it is the later rule that should fail and not this one *)
962 if not not_keep && !Flag_ctl.verbose_ctl_engine
963 then
964 (SUB.print_mvar x; Format.print_flush();
965 print_state ": empty witness from" [t]);
966 t::prev
967 | l when anyneg l && !pANY_NEG_OPT -> prev
968 (* see tests/nestseq for how neg bindings can come up even
969 without eg partial matches
970 (* negated substitution only allowed with negwits.
971 just dropped *)
972 if anynegwit wit && allnegwit wit (* nonempty negwit list *)
973 then prev
974 else
975 (print_generic_substitution l; Format.print_newline();
976 failwith"unexpected negative binding with positive witnesses")*)
977 | _ ->
978 let new_triple =
979 if unchecked or not_keep
980 then (s,newth,wit)
981 else
982 if anynegwit wit && allnegwit wit
983 then (s,newth,[A.NegWit(A.Wit(s,th_x,[],negtopos wit))])
984 else (s,newth,[A.Wit(s,th_x,[],wit)]) in
985 new_triple::prev)
986 [] trips in
987 if unchecked || !Flag_ctl.partial_match (* the only way to have a NegWit *)
988 then setify res
989 else List.rev res
990;;
991
992
993(* ---------------------------------------------------------------------- *)
994(* SAT - Model Checking Algorithm for CTL-FVex *)
995(* *)
996(* TODO: Implement _all_ operators (directly) *)
997(* ---------------------------------------------------------------------- *)
998
999
1000(* ************************************* *)
1001(* The SAT algorithm and special helpers *)
1002(* ************************************* *)
1003
1004let rec pre_exist dir (grp,_,_) y reqst =
1005 let check s =
1006 match reqst with None -> true | Some reqst -> List.mem s reqst in
1007 let exp (s,th,wit) =
1008 concatmap
1009 (fun s' -> if check s' then [(s',th,wit)] else [])
1010 (match dir with
1011 A.FORWARD -> G.predecessors grp s
1012 | A.BACKWARD -> G.successors grp s) in
1013 setify (concatmap exp y)
1014;;
1015
1016exception Empty
1017
1018let pre_forall dir (grp,_,states) y all reqst =
1019 let check s =
1020 match reqst with
1021 None -> true | Some reqst -> List.mem s reqst in
1022 let pred =
1023 match dir with
1024 A.FORWARD -> G.predecessors | A.BACKWARD -> G.successors in
1025 let succ =
1026 match dir with
1027 A.FORWARD -> G.successors | A.BACKWARD -> G.predecessors in
1028 let neighbors =
1029 List.map
1030 (function p -> (p,succ grp p))
1031 (setify
1032 (concatmap
1033 (function (s,_,_) -> List.filter check (pred grp s)) y)) in
1034 (* would a hash table be more efficient? *)
1035 let all = List.sort state_compare all in
1036 let rec up_nodes child s = function
1037 [] -> []
1038 | (s1,th,wit)::xs ->
1039 (match compare s1 child with
1040 -1 -> up_nodes child s xs
1041 | 0 -> (s,th,wit)::(up_nodes child s xs)
1042 | _ -> []) in
1043 let neighbor_triples =
1044 List.fold_left
1045 (function rest ->
1046 function (s,children) ->
1047 try
1048 (List.map
1049 (function child ->
1050 match up_nodes child s all with [] -> raise Empty | l -> l)
1051 children) :: rest
1052 with Empty -> rest)
1053 [] neighbors in
1054 match neighbor_triples with
1055 [] -> []
1056 | _ ->
1057 (*normalize*)
1058 (foldl1 (@) (List.map (foldl1 triples_conj) neighbor_triples))
ae4735db 1059
34e49164
C
1060let pre_forall_AW dir (grp,_,states) y all reqst =
1061 let check s =
1062 match reqst with
1063 None -> true | Some reqst -> List.mem s reqst in
1064 let pred =
1065 match dir with
1066 A.FORWARD -> G.predecessors | A.BACKWARD -> G.successors in
1067 let succ =
1068 match dir with
1069 A.FORWARD -> G.successors | A.BACKWARD -> G.predecessors in
1070 let neighbors =
1071 List.map
1072 (function p -> (p,succ grp p))
1073 (setify
1074 (concatmap
1075 (function (s,_,_) -> List.filter check (pred grp s)) y)) in
1076 (* would a hash table be more efficient? *)
1077 let all = List.sort state_compare all in
1078 let rec up_nodes child s = function
1079 [] -> []
1080 | (s1,th,wit)::xs ->
1081 (match compare s1 child with
1082 -1 -> up_nodes child s xs
1083 | 0 -> (s,th,wit)::(up_nodes child s xs)
1084 | _ -> []) in
1085 let neighbor_triples =
1086 List.fold_left
1087 (function rest ->
1088 function (s,children) ->
1089 (List.map
1090 (function child ->
1091 match up_nodes child s all with [] -> raise AW | l -> l)
1092 children) :: rest)
1093 [] neighbors in
1094 match neighbor_triples with
1095 [] -> []
1096 | _ -> foldl1 (@) (List.map (foldl1 triples_conj_AW) neighbor_triples)
ae4735db 1097
34e49164
C
1098(* drop_negwits will call setify *)
1099let satEX dir m s reqst = pre_exist dir m s reqst;;
ae4735db 1100
34e49164
C
1101let satAX dir m s reqst = pre_forall dir m s s reqst
1102;;
1103
1104(* E[phi1 U phi2] == phi2 \/ (phi1 /\ EXE[phi1 U phi2]) *)
ae4735db 1105let satEU dir ((_,_,states) as m) s1 s2 reqst print_graph =
978fd7e5
C
1106 (*Printf.printf "EU\n";
1107 let ctr = ref 0 in*)
34e49164
C
1108 inc satEU_calls;
1109 if s1 = []
1110 then s2
1111 else
1112 (*let ctr = ref 0 in*)
1113 if !pNEW_INFO_OPT
1114 then
1115 let rec f y new_info =
1116 inc_step();
1117 match new_info with
1118 [] -> y
1119 | new_info ->
978fd7e5
C
1120 (*ctr := !ctr + 1;
1121 print_graph y ctr;*)
34e49164
C
1122 let first = triples_conj s1 (pre_exist dir m new_info reqst) in
1123 let res = triples_union first y in
1124 let new_info = setdiff res y in
1125 (*Printf.printf "iter %d res %d new_info %d\n"
1126 !ctr (List.length res) (List.length new_info);
978fd7e5
C
1127 print_state "res" res;
1128 print_state "new_info" new_info;
34e49164
C
1129 flush stdout;*)
1130 f res new_info in
1131 f s2 s2
1132 else
1133 let f y =
1134 inc_step();
978fd7e5
C
1135 (*ctr := !ctr + 1;
1136 print_graph y ctr;*)
34e49164
C
1137 let pre = pre_exist dir m y reqst in
1138 triples_union s2 (triples_conj s1 pre) in
1139 setfix f s2
1140;;
1141
1142(* EF phi == E[true U phi] *)
ae4735db 1143let satEF dir m s2 reqst =
34e49164
C
1144 inc satEF_calls;
1145 (*let ctr = ref 0 in*)
1146 if !pNEW_INFO_OPT
1147 then
1148 let rec f y new_info =
1149 inc_step();
1150 match new_info with
1151 [] -> y
1152 | new_info ->
1153 (*ctr := !ctr + 1;
1154 print_state (Printf.sprintf "iteration %d\n" !ctr) y;*)
1155 let first = pre_exist dir m new_info reqst in
1156 let res = triples_union first y in
1157 let new_info = setdiff res y in
1158 (*Printf.printf "EF %s iter %d res %d new_info %d\n"
1159 (if dir = A.BACKWARD then "reachable" else "real ef")
1160 !ctr (List.length res) (List.length new_info);
1161 print_state "new info" new_info;
1162 flush stdout;*)
1163 f res new_info in
1164 f s2 s2
1165 else
1166 let f y =
1167 inc_step();
1168 let pre = pre_exist dir m y reqst in
1169 triples_union s2 pre in
1170 setfix f s2
1171
1172
1173type ('pred,'anno) auok =
1174 AUok of ('pred,'anno) triples | AUfailed of ('pred,'anno) triples
1175
1176(* A[phi1 U phi2] == phi2 \/ (phi1 /\ AXA[phi1 U phi2]) *)
485bce71
C
1177let satAU dir ((cfg,_,states) as m) s1 s2 reqst print_graph =
1178 let ctr = ref 0 in
34e49164
C
1179 inc satAU_calls;
1180 if s1 = []
1181 then AUok s2
1182 else
1183 (*let ctr = ref 0 in*)
1184 let pre_forall =
1185 if !Flag_ctl.loop_in_src_code
1186 then pre_forall_AW
1187 else pre_forall in
1188 if !pNEW_INFO_OPT
1189 then
1190 let rec f y newinfo =
1191 inc_step();
1192 match newinfo with
1193 [] -> AUok y
1194 | new_info ->
485bce71
C
1195 ctr := !ctr + 1;
1196 (*print_state (Printf.sprintf "iteration %d\n" !ctr) y;
34e49164 1197 flush stdout;*)
485bce71 1198 print_graph y ctr;
34e49164
C
1199 let pre =
1200 try Some (pre_forall dir m new_info y reqst)
1201 with AW -> None in
1202 match pre with
1203 None -> AUfailed y
1204 | Some pre ->
1205 match triples_conj s1 pre with
1206 [] -> AUok y
1207 | first ->
1208 (*print_state "s1" s1;
1209 print_state "pre" pre;
1210 print_state "first" first;*)
1211 let res = triples_union first y in
1212 let new_info =
1213 if not !something_dropped
1214 then first
1215 else setdiff res y in
1216 (*Printf.printf
1217 "iter %d res %d new_info %d\n"
1218 !ctr (List.length res) (List.length new_info);
1219 flush stdout;*)
1220 f res new_info in
1221 f s2 s2
1222 else
1223 if !Flag_ctl.loop_in_src_code
1224 then AUfailed s2
1225 else
1226 (*let setfix =
1227 fix (function s1 -> function s2 ->
1228 let s1 = List.map (function (s,th,w) -> (s,th,nub w)) s1 in
1229 let s2 = List.map (function (s,th,w) -> (s,th,nub w)) s2 in
1230 subseteq s1 s2) in for popl *)
1231 let f y =
1232 inc_step();
485bce71
C
1233 ctr := !ctr + 1;
1234 print_graph y ctr;
34e49164
C
1235 let pre = pre_forall dir m y y reqst in
1236 triples_union s2 (triples_conj s1 pre) in
1237 AUok (setfix f s2)
1238;;
1239
1240
1241(* reqst could be the states of s1 *)
1242 (*
1243 let lstates = mkstates states reqst in
1244 let initial_removed =
1245 triples_complement lstates (triples_union s1 s2) in
1246 let initial_base = triples_conj s1 (triples_complement lstates s2) in
1247 let rec loop base removed =
1248 let new_removed =
1249 triples_conj base (pre_exist dir m removed reqst) in
1250 let new_base =
1251 triples_conj base (triples_complement lstates new_removed) in
1252 if supseteq new_base base
1253 then triples_union base s2
1254 else loop new_base new_removed in
1255 loop initial_base initial_removed *)
1256
1257let satAW dir ((grp,_,states) as m) s1 s2 reqst =
1258 inc satAW_calls;
1259 if s1 = []
1260 then s2
1261 else
1262 (*
1263 This works extremely badly when the region is small and the end of the
1264 region is very ambiguous, eg free(x) ... x
1265 see free.c
1266 if !pNEW_INFO_OPT
1267 then
1268 let get_states l = setify(List.map (function (s,_,_) -> s) l) in
1269 let ostates = Common.union_set (get_states s1) (get_states s2) in
1270 let succ =
1271 (match dir with
1272 A.FORWARD -> G.successors grp
1273 | A.BACKWARD -> G.predecessors grp) in
1274 let states =
1275 List.fold_left Common.union_set ostates (List.map succ ostates) in
1276 let negphi = triples_complement states s1 in
1277 let negpsi = triples_complement states s2 in
1278 triples_complement ostates
1279 (satEU dir m negpsi (triples_conj negphi negpsi) (Some ostates))
1280 else
1281 *)
1282 (*let ctr = ref 0 in*)
1283 let f y =
1284 inc_step();
1285 (*ctr := !ctr + 1;
1286 Printf.printf "iter %d y %d\n" !ctr (List.length y);
1287 print_state "y" y;
1288 flush stdout;*)
1289 let pre = pre_forall dir m y y reqst in
978fd7e5 1290 (*print_state "pre" pre;*)
34e49164
C
1291 let conj = triples_conj s1 pre in (* or triples_conj_AW *)
1292 triples_union s2 conj in
978fd7e5
C
1293 let drop_wits = List.map (function (s,e,_) -> (s,e,[])) in
1294 (* drop wits on s1 represents that we don't want any witnesses from
1295 the case that infinitely loops, only from the case that gets
1296 out of the loop. s1 is like a guard. To see the problem, consider
1297 an example where both s1 and s2 match some code after the loop.
1298 we only want the witness from s2. *)
fc1ad971 1299 setgfix f (triples_union (nub(drop_wits s1)) s2)
34e49164
C
1300;;
1301
ae4735db 1302let satAF dir m s reqst =
34e49164
C
1303 inc satAF_calls;
1304 if !pNEW_INFO_OPT
1305 then
1306 let rec f y newinfo =
1307 inc_step();
1308 match newinfo with
1309 [] -> y
1310 | new_info ->
1311 let first = pre_forall dir m new_info y reqst in
1312 let res = triples_union first y in
1313 let new_info = setdiff res y in
1314 f res new_info in
1315 f s s
1316 else
1317 let f y =
1318 inc_step();
1319 let pre = pre_forall dir m y y reqst in
1320 triples_union s pre in
1321 setfix f s
1322
1323let satAG dir ((_,_,states) as m) s reqst =
1324 inc satAG_calls;
1325 let f y =
1326 inc_step();
1327 let pre = pre_forall dir m y y reqst in
1328 triples_conj y pre in
1329 setgfix f s
1330
1331let satEG dir ((_,_,states) as m) s reqst =
1332 inc satEG_calls;
1333 let f y =
1334 inc_step();
1335 let pre = pre_exist dir m y reqst in
1336 triples_conj y pre in
1337 setgfix f s
1338
1339(* **************************************************************** *)
1340(* Inner And - a way of dealing with multiple matches within a node *)
1341(* **************************************************************** *)
1342(* applied to the result of matching a node. collect witnesses when the
1343states and environments are the same *)
5626f154
C
1344(* not a good idea, poses problem for unparsing, because don't realize that
1345adjacent things come from different matches, leading to loss of newlines etc.
1346exple struct I { ... - int x; + int y; ...} *)
34e49164 1347
5626f154 1348let inner_and trips = trips (*
34e49164
C
1349 let rec loop = function
1350 [] -> ([],[])
1351 | (s,th,w)::trips ->
1352 let (cur,acc) = loop trips in
1353 (match cur with
1354 (s',_,_)::_ when s = s' ->
1355 let rec loop' = function
1356 [] -> [(s,th,w)]
1357 | ((_,th',w') as t')::ts' ->
1358 (match conj_subst th th' with
1359 Some th'' -> (s,th'',union_wit w w')::ts'
1360 | None -> t'::(loop' ts')) in
1361 (loop' cur,acc)
1362 | _ -> ([(s,th,w)],cur@acc)) in
1363 let (cur,acc) =
1364 loop (List.sort state_compare trips) (* is this sort needed? *) in
5626f154 1365 cur@acc *)
34e49164
C
1366
1367(* *************** *)
1368(* Partial matches *)
1369(* *************** *)
1370
1371let filter_conj states unwanted partial_matches =
1372 let x =
1373 triples_conj (triples_complement states (unwitify unwanted))
1374 partial_matches in
1375 triples_conj (unwitify x) (triples_complement states x)
1376
1377let strict_triples_conj strict states trips trips' =
1378 let res = triples_conj trips trips' in
1379 if !Flag_ctl.partial_match && strict = A.STRICT
1380 then
1381 let fail_left = filter_conj states trips trips' in
1382 let fail_right = filter_conj states trips' trips in
1383 let ors = triples_union fail_left fail_right in
1384 triples_union res ors
1385 else res
1386
1387let strict_triples_conj_none strict states trips trips' =
1388 let res = triples_conj_none trips trips' in
1389 if !Flag_ctl.partial_match && strict = A.STRICT
1390 then
1391 let fail_left = filter_conj states trips trips' in
1392 let fail_right = filter_conj states trips' trips in
1393 let ors = triples_union fail_left fail_right in
1394 triples_union res ors
1395 else res
1396
1397let left_strict_triples_conj strict states trips trips' =
1398 let res = triples_conj trips trips' in
1399 if !Flag_ctl.partial_match && strict = A.STRICT
1400 then
1401 let fail_left = filter_conj states trips trips' in
1402 triples_union res fail_left
1403 else res
1404
ae4735db 1405let strict_A1 strict op failop dir ((_,_,states) as m) trips required_states =
34e49164
C
1406 let res = op dir m trips required_states in
1407 if !Flag_ctl.partial_match && strict = A.STRICT
1408 then
1409 let states = mkstates states required_states in
1410 let fail = filter_conj states res (failop dir m trips required_states) in
1411 triples_union res fail
1412 else res
1413
1414let strict_A2 strict op failop dir ((_,_,states) as m) trips trips'
ae4735db 1415 required_states =
34e49164
C
1416 let res = op dir m trips trips' required_states in
1417 if !Flag_ctl.partial_match && strict = A.STRICT
1418 then
1419 let states = mkstates states required_states in
1420 let fail = filter_conj states res (failop dir m trips' required_states) in
1421 triples_union res fail
1422 else res
ae4735db 1423
34e49164 1424let strict_A2au strict op failop dir ((_,_,states) as m) trips trips'
ae4735db 1425 required_states print_graph =
485bce71 1426 match op dir m trips trips' required_states print_graph with
34e49164
C
1427 AUok res ->
1428 if !Flag_ctl.partial_match && strict = A.STRICT
1429 then
1430 let states = mkstates states required_states in
1431 let fail =
1432 filter_conj states res (failop dir m trips' required_states) in
1433 AUok (triples_union res fail)
1434 else AUok res
1435 | AUfailed res -> AUfailed res
ae4735db 1436
34e49164
C
1437(* ********************* *)
1438(* Environment functions *)
1439(* ********************* *)
1440
1441let drop_wits required_states s phi =
1442 match required_states with
1443 None -> s
1444 | Some states -> List.filter (function (s,_,_) -> List.mem s states) s
1445
1446
1447let print_required required =
1448 List.iter
1449 (function l ->
1450 Format.print_string "{";
1451 List.iter
1452 (function reqd ->
1453 print_generic_substitution reqd; Format.print_newline())
1454 l;
1455 Format.print_string "}";
1456 Format.print_newline())
1457 required
1458
1459exception Too_long
1460
1461let extend_required trips required =
1462 if !Flag_ctl.partial_match
1463 then required
1464 else
1465 if !pREQUIRED_ENV_OPT
1466 then
1467 (* make it a set *)
1468 let envs =
1469 List.fold_left
1470 (function rest ->
1471 function (_,t,_) -> if List.mem t rest then rest else t::rest)
1472 [] trips in
1473 let envs = if List.mem [] envs then [] else envs in
1474 match (envs,required) with
1475 ([],_) -> required
1476 | (envs,hd::tl) ->
1477 (try
1478 let hdln = List.length hd + 5 (* let it grow a little bit *) in
1479 let (_,merged) =
1480 let add x (ln,y) =
1481 if List.mem x y
1482 then (ln,y)
1483 else if ln + 1 > hdln then raise Too_long else (ln+1,x::y) in
1484 foldl
1485 (function rest ->
1486 function t ->
1487 foldl
1488 (function rest ->
1489 function r ->
1490 match conj_subst t r with
1491 None -> rest | Some th -> add th rest)
1492 rest hd)
1493 (0,[]) envs in
1494 merged :: tl
1495 with Too_long -> envs :: required)
1496 | (envs,_) -> envs :: required
1497 else required
1498
1499let drop_required v required =
1500 if !pREQUIRED_ENV_OPT
1501 then
1502 let res =
1503 inner_setify
1504 (List.map
1505 (function l ->
1506 inner_setify
1507 (List.map (List.filter (function sub -> not(dom_sub sub = v))) l))
1508 required) in
1509 (* check whether an entry has become useless *)
1510 List.filter (function l -> not (List.exists (function x -> x = []) l)) res
1511 else required
1512
1513(* no idea how to write this function ... *)
1514let memo_label =
1515 (Hashtbl.create(50) : (P.t, (G.node * substitution) list) Hashtbl.t)
1516
1517let satLabel label required p =
1518 let triples =
1519 if !pSATLABEL_MEMO_OPT
1520 then
1521 try
1522 let states_subs = Hashtbl.find memo_label p in
1523 List.map (function (st,th) -> (st,th,[])) states_subs
1524 with
1525 Not_found ->
1526 let triples = setify(label p) in
1527 Hashtbl.add memo_label p
1528 (List.map (function (st,th,_) -> (st,th)) triples);
1529 triples
1530 else setify(label p) in
65038c61
C
1531 (* normalize first; conj_subst relies on sorting *)
1532 let ntriples = normalize triples in
1533 if !pREQUIRED_ENV_OPT
1534 then
1535 foldl
1536 (function rest ->
1537 function ((s,th,_) as t) ->
1538 if List.for_all
1539 (List.exists (function th' -> not(conj_subst th th' = None)))
1540 required
1541 then t::rest
1542 else rest)
1543 [] ntriples
1544 else ntriples
34e49164
C
1545
1546let get_required_states l =
1547 if !pREQUIRED_STATES_OPT && not !Flag_ctl.partial_match
1548 then
1549 Some(inner_setify (List.map (function (s,_,_) -> s) l))
1550 else None
1551
1552let get_children_required_states dir (grp,_,_) required_states =
1553 if !pREQUIRED_STATES_OPT && not !Flag_ctl.partial_match
1554 then
1555 match required_states with
1556 None -> None
1557 | Some states ->
1558 let fn =
1559 match dir with
1560 A.FORWARD -> G.successors
1561 | A.BACKWARD -> G.predecessors in
1562 Some (inner_setify (List.concat (List.map (fn grp) states)))
1563 else None
1564
1565let reachable_table =
1566 (Hashtbl.create(50) : (G.node * A.direction, G.node list) Hashtbl.t)
1567
1568(* like satEF, but specialized for get_reachable *)
1569let reachsatEF dir (grp,_,_) s2 =
1570 let dirop =
1571 match dir with A.FORWARD -> G.successors | A.BACKWARD -> G.predecessors in
1572 let union = unionBy compare (=) in
1573 let rec f y = function
1574 [] -> y
1575 | new_info ->
1576 let (pre_collected,new_info) =
1577 List.partition (function Common.Left x -> true | _ -> false)
1578 (List.map
1579 (function x ->
1580 try Common.Left (Hashtbl.find reachable_table (x,dir))
1581 with Not_found -> Common.Right x)
1582 new_info) in
1583 let y =
1584 List.fold_left
1585 (function rest ->
1586 function Common.Left x -> union x rest
1587 | _ -> failwith "not possible")
1588 y pre_collected in
1589 let new_info =
1590 List.map
1591 (function Common.Right x -> x | _ -> failwith "not possible")
1592 new_info in
1593 let first = inner_setify (concatmap (dirop grp) new_info) in
1594 let new_info = setdiff first y in
1595 let res = new_info @ y in
1596 f res new_info in
1597 List.rev(f s2 s2) (* put root first *)
1598
1599let get_reachable dir m required_states =
1600 match required_states with
1601 None -> None
1602 | Some states ->
1603 Some
1604 (List.fold_left
1605 (function rest ->
1606 function cur ->
1607 if List.mem cur rest
1608 then rest
1609 else
1610 Common.union_set
1611 (try Hashtbl.find reachable_table (cur,dir)
1612 with
1613 Not_found ->
1614 let states = reachsatEF dir m [cur] in
1615 Hashtbl.add reachable_table (cur,dir) states;
1616 states)
1617 rest)
1618 [] states)
1619
1620let ctr = ref 0
1621let new_var _ =
1622 let c = !ctr in
1623 ctr := !ctr + 1;
1624 Printf.sprintf "_c%d" c
1625
1626(* **************************** *)
1627(* End of environment functions *)
1628(* **************************** *)
1629
1630type ('code,'value) cell = Frozen of 'code | Thawed of 'value
1631
1632let rec satloop unchecked required required_states
1633 ((grp,label,states) as m) phi env =
1634 let rec loop unchecked required required_states phi =
34e49164
C
1635 let res =
1636 match phi with
1637 A.False -> []
1638 | A.True -> triples_top states
1639 | A.Pred(p) -> satLabel label required p
1640 | A.Uncheck(phi1) ->
1641 let unchecked = if !pUNCHECK_OPT then true else false in
1642 loop unchecked required required_states phi1
1643 | A.Not(phi) ->
1644 let phires = loop unchecked required required_states phi in
1645 (*let phires =
1646 List.map (function (s,th,w) -> (s,th,[])) phires in*)
1647 triples_complement (mkstates states required_states)
1648 phires
1649 | A.Or(phi1,phi2) ->
1650 triples_union
1651 (loop unchecked required required_states phi1)
1652 (loop unchecked required required_states phi2)
17ba0788 1653 | A.SeqOr(phi1,phi2) ->
34e49164
C
1654 let res1 = loop unchecked required required_states phi1 in
1655 let res2 = loop unchecked required required_states phi2 in
1656 let res1neg = unwitify res1 in
17ba0788
C
1657 let pm = !Flag_ctl.partial_match in
1658 (match (pm,res1,res2) with
1659 (false,res1,[]) -> res1
1660 | (false,[],res2) -> res2
1661 | _ ->
1662 triples_union res1
1663 (triples_conj
1664 (triples_complement (mkstates states required_states) res1neg)
1665 res2))
34e49164
C
1666 | A.And(strict,phi1,phi2) ->
1667 (* phi1 is considered to be more likely to be [], because of the
1668 definition of asttoctl. Could use heuristics such as the size of
1669 the term *)
1670 let pm = !Flag_ctl.partial_match in
1671 (match (pm,loop unchecked required required_states phi1) with
1672 (false,[]) when !pLazyOpt -> []
1673 | (_,phi1res) ->
1674 let new_required = extend_required phi1res required in
1675 let new_required_states = get_required_states phi1res in
1676 (match (pm,loop unchecked new_required new_required_states phi2)
1677 with
1678 (false,[]) when !pLazyOpt -> []
1679 | (_,phi2res) ->
1680 strict_triples_conj strict
1681 (mkstates states required_states)
1682 phi1res phi2res))
1683 | A.AndAny(dir,strict,phi1,phi2) ->
1684 (* phi2 can appear anywhere that is reachable *)
1685 let pm = !Flag_ctl.partial_match in
1686 (match (pm,loop unchecked required required_states phi1) with
1687 (false,[]) -> []
1688 | (_,phi1res) ->
1689 let new_required = extend_required phi1res required in
1690 let new_required_states = get_required_states phi1res in
1691 let new_required_states =
1692 get_reachable dir m new_required_states in
1693 (match (pm,loop unchecked new_required new_required_states phi2)
1694 with
1695 (false,[]) -> phi1res
1696 | (_,phi2res) ->
1697 (match phi1res with
1698 [] -> (* !Flag_ctl.partial_match must be true *)
1699 if phi2res = []
1700 then []
1701 else
1702 let s = mkstates states required_states in
1703 List.fold_left
1704 (function a -> function b ->
1705 strict_triples_conj strict s a [b])
1706 [List.hd phi2res] (List.tl phi2res)
1707 | [(state,_,_)] ->
1708 let phi2res =
1709 List.map (function (s,e,w) -> [(state,e,w)]) phi2res in
1710 let s = mkstates states required_states in
1711 List.fold_left
1712 (function a -> function b ->
1713 strict_triples_conj strict s a b)
1714 phi1res phi2res
1715 | _ ->
1716 failwith
1717 "only one result allowed for the left arg of AndAny")))
1718 | A.HackForStmt(dir,strict,phi1,phi2) ->
1719 (* phi2 can appear anywhere that is reachable *)
1720 let pm = !Flag_ctl.partial_match in
1721 (match (pm,loop unchecked required required_states phi1) with
1722 (false,[]) -> []
1723 | (_,phi1res) ->
1724 let new_required = extend_required phi1res required in
1725 let new_required_states = get_required_states phi1res in
1726 let new_required_states =
1727 get_reachable dir m new_required_states in
1728 (match (pm,loop unchecked new_required new_required_states phi2)
1729 with
1730 (false,[]) -> phi1res
1731 | (_,phi2res) ->
1732 (* if there is more than one state, something about the
1733 environment has to ensure that the right triples of
1734 phi2 get associated with the triples of phi1.
1735 the asttoctl2 has to ensure that that is the case.
1736 these should thus be structural properties.
1737 env of phi2 has to be a proper subset of env of phi1
1738 to ensure all end up being consistent. no new triples
1739 should be generated. strict_triples_conj_none takes
1740 care of this.
1741 *)
1742 let s = mkstates states required_states in
1743 List.fold_left
1744 (function acc ->
1745 function (st,th,_) as phi2_elem ->
1746 let inverse =
1747 triples_complement [st] [(st,th,[])] in
1748 strict_triples_conj_none strict s acc
1749 (phi2_elem::inverse))
1750 phi1res phi2res))
1751 | A.InnerAnd(phi) ->
1752 inner_and(loop unchecked required required_states phi)
17ba0788 1753 | A.EX(dir,phi) ->
34e49164
C
1754 let new_required_states =
1755 get_children_required_states dir m required_states in
1756 satEX dir m (loop unchecked required new_required_states phi)
1757 required_states
17ba0788 1758 | A.AX(dir,strict,phi) ->
34e49164
C
1759 let new_required_states =
1760 get_children_required_states dir m required_states in
1761 let res = loop unchecked required new_required_states phi in
1762 strict_A1 strict satAX satEX dir m res required_states
17ba0788 1763 | A.EF(dir,phi) ->
34e49164
C
1764 let new_required_states = get_reachable dir m required_states in
1765 satEF dir m (loop unchecked required new_required_states phi)
1766 new_required_states
17ba0788 1767 | A.AF(dir,strict,phi) ->
34e49164
C
1768 if !Flag_ctl.loop_in_src_code
1769 then
1770 loop unchecked required required_states
1771 (A.AU(dir,strict,A.True,phi))
1772 else
1773 let new_required_states = get_reachable dir m required_states in
1774 let res = loop unchecked required new_required_states phi in
1775 strict_A1 strict satAF satEF dir m res new_required_states
17ba0788 1776 | A.EG(dir,phi) ->
34e49164
C
1777 let new_required_states = get_reachable dir m required_states in
1778 satEG dir m (loop unchecked required new_required_states phi)
1779 new_required_states
17ba0788 1780 | A.AG(dir,strict,phi) ->
34e49164
C
1781 let new_required_states = get_reachable dir m required_states in
1782 let res = loop unchecked required new_required_states phi in
1783 strict_A1 strict satAG satEF dir m res new_required_states
17ba0788 1784 | A.EU(dir,phi1,phi2) ->
34e49164
C
1785 let new_required_states = get_reachable dir m required_states in
1786 (match loop unchecked required new_required_states phi2 with
1787 [] when !pLazyOpt -> []
1788 | s2 ->
1789 let new_required = extend_required s2 required in
1790 let s1 = loop unchecked new_required new_required_states phi1 in
485bce71
C
1791 satEU dir m s1 s2 new_required_states
1792 (fun y ctr -> print_graph_c grp new_required_states y ctr phi))
34e49164
C
1793 | A.AW(dir,strict,phi1,phi2) ->
1794 let new_required_states = get_reachable dir m required_states in
1795 (match loop unchecked required new_required_states phi2 with
1796 [] when !pLazyOpt -> []
1797 | s2 ->
1798 let new_required = extend_required s2 required in
1799 let s1 = loop unchecked new_required new_required_states phi1 in
1800 strict_A2 strict satAW satEF dir m s1 s2 new_required_states)
1801 | A.AU(dir,strict,phi1,phi2) ->
1802 (*Printf.printf "using AU\n"; flush stdout;*)
1803 let new_required_states = get_reachable dir m required_states in
1804 (match loop unchecked required new_required_states phi2 with
1805 [] when !pLazyOpt -> []
1806 | s2 ->
1807 let new_required = extend_required s2 required in
1808 let s1 = loop unchecked new_required new_required_states phi1 in
1809 let res =
485bce71
C
1810 strict_A2au strict satAU satEF dir m s1 s2 new_required_states
1811 (fun y ctr ->
1812 print_graph_c grp new_required_states y ctr phi) in
34e49164
C
1813 match res with
1814 AUok res -> res
1815 | AUfailed tmp_res ->
1816 (* found a loop, have to try AW *)
1817 (* the formula is
1818 A[E[phi1 U phi2] & phi1 W phi2]
1819 the and is nonstrict *)
1820 (* tmp_res is bigger than s2, so perhaps closer to s1 *)
1821 (*Printf.printf "using AW\n"; flush stdout;*)
1822 let s1 =
485bce71
C
1823 triples_conj
1824 (satEU dir m s1 tmp_res new_required_states
1825 (* no graph, for the moment *)
1826 (fun y str -> ()))
34e49164 1827 s1 in
978fd7e5
C
1828 strict_A2 strict satAW satEF dir m s1 s2 new_required_states
1829 )
34e49164
C
1830 | A.Implies(phi1,phi2) ->
1831 loop unchecked required required_states (A.Or(A.Not phi1,phi2))
17ba0788 1832 | A.Exists (keep,v,phi) ->
34e49164
C
1833 let new_required = drop_required v required in
1834 triples_witness v unchecked (not keep)
1835 (loop unchecked new_required required_states phi)
17ba0788
C
1836
1837 | A.Let(v,phi1,phi2) ->
34e49164
C
1838 (* should only be used when the properties unchecked, required,
1839 and required_states are known to be the same or at least
1840 compatible between all the uses. this is not checked. *)
1841 let res = loop unchecked required required_states phi1 in
1842 satloop unchecked required required_states m phi2 ((v,res) :: env)
17ba0788 1843 | A.LetR(dir,v,phi1,phi2) ->
34e49164
C
1844 (* should only be used when the properties unchecked, required,
1845 and required_states are known to be the same or at least
1846 compatible between all the uses. this is not checked. *)
485bce71 1847 (* doesn't seem to be used any more *)
34e49164
C
1848 let new_required_states = get_reachable dir m required_states in
1849 let res = loop unchecked required new_required_states phi1 in
1850 satloop unchecked required required_states m phi2 ((v,res) :: env)
17ba0788 1851 | A.Ref(v) ->
34e49164
C
1852 let res = List.assoc v env in
1853 if unchecked
1854 then List.map (function (s,th,_) -> (s,th,[])) res
1855 else res
1856 | A.XX(phi) -> failwith "should have been removed" in
1857 if !Flag_ctl.bench > 0 then triples := !triples + (List.length res);
485bce71
C
1858 let res = drop_wits required_states res phi (* ) *) in
1859 print_graph grp required_states res "" phi;
1860 res in
ae4735db 1861
34e49164 1862 loop unchecked required required_states phi
ae4735db 1863;;
34e49164
C
1864
1865
1866(* SAT with tracking *)
17ba0788
C
1867let output str =
1868 Printf.printf "%s\n" str
1869
34e49164
C
1870let rec sat_verbose_loop unchecked required required_states annot maxlvl lvl
1871 ((_,label,states) as m) phi env =
1872 let anno res children = (annot lvl phi res children,res) in
1873 let satv unchecked required required_states phi0 env =
1874 sat_verbose_loop unchecked required required_states annot maxlvl (lvl+1)
1875 m phi0 env in
1876 if (lvl > maxlvl) && (maxlvl > -1) then
1877 anno (satloop unchecked required required_states m phi env) []
1878 else
1879 let (child,res) =
1880 match phi with
1881 A.False -> anno [] []
1882 | A.True -> anno (triples_top states) []
1883 | A.Pred(p) ->
17ba0788 1884 output "label";
34e49164
C
1885 anno (satLabel label required p) []
1886 | A.Uncheck(phi1) ->
1887 let unchecked = if !pUNCHECK_OPT then true else false in
1888 let (child1,res1) = satv unchecked required required_states phi1 env in
17ba0788 1889 output "uncheck";
34e49164 1890 anno res1 [child1]
ae4735db 1891 | A.Not(phi1) ->
34e49164
C
1892 let (child,res) =
1893 satv unchecked required required_states phi1 env in
17ba0788 1894 output "not";
34e49164 1895 anno (triples_complement (mkstates states required_states) res) [child]
ae4735db 1896 | A.Or(phi1,phi2) ->
34e49164
C
1897 let (child1,res1) =
1898 satv unchecked required required_states phi1 env in
1899 let (child2,res2) =
1900 satv unchecked required required_states phi2 env in
17ba0788 1901 output "or";
34e49164 1902 anno (triples_union res1 res2) [child1; child2]
ae4735db 1903 | A.SeqOr(phi1,phi2) ->
34e49164
C
1904 let (child1,res1) =
1905 satv unchecked required required_states phi1 env in
1906 let (child2,res2) =
1907 satv unchecked required required_states phi2 env in
1908 let res1neg =
1909 List.map (function (s,th,_) -> (s,th,[])) res1 in
17ba0788
C
1910 output "seqor";
1911 let pm = !Flag_ctl.partial_match in
1912 (match (pm,res1,res2) with
1913 (false,res1,[]) -> anno res1 [child1; child2]
1914 | (false,[],res2) -> anno res2 [child1; child2]
1915 | _ ->
1916 anno (triples_union res1
1917 (triples_conj
1918 (triples_complement (mkstates states required_states)
1919 res1neg)
1920 res2))
1921 [child1; child2])
ae4735db 1922 | A.And(strict,phi1,phi2) ->
34e49164
C
1923 let pm = !Flag_ctl.partial_match in
1924 (match (pm,satv unchecked required required_states phi1 env) with
1925 (false,(child1,[])) ->
17ba0788 1926 output "and"; anno [] [child1]
34e49164
C
1927 | (_,(child1,res1)) ->
1928 let new_required = extend_required res1 required in
1929 let new_required_states = get_required_states res1 in
1930 (match (pm,satv unchecked new_required new_required_states phi2
1931 env) with
1932 (false,(child2,[])) ->
17ba0788 1933 output "and"; anno [] [child1;child2]
34e49164 1934 | (_,(child2,res2)) ->
17ba0788 1935 output "and";
34e49164
C
1936 let res =
1937 strict_triples_conj strict
1938 (mkstates states required_states)
1939 res1 res2 in
1940 anno res [child1; child2]))
1941 | A.AndAny(dir,strict,phi1,phi2) ->
ae4735db 1942 let pm = !Flag_ctl.partial_match in
34e49164
C
1943 (match (pm,satv unchecked required required_states phi1 env) with
1944 (false,(child1,[])) ->
17ba0788 1945 output "and"; anno [] [child1]
34e49164
C
1946 | (_,(child1,res1)) ->
1947 let new_required = extend_required res1 required in
1948 let new_required_states = get_required_states res1 in
1949 let new_required_states =
1950 get_reachable dir m new_required_states in
1951 (match (pm,satv unchecked new_required new_required_states phi2
1952 env) with
1953 (false,(child2,[])) ->
17ba0788 1954 output "andany";
34e49164
C
1955 anno res1 [child1;child2]
1956 | (_,(child2,res2)) ->
1957 (match res1 with
1958 [] -> (* !Flag_ctl.partial_match must be true *)
1959 if res2 = []
1960 then anno [] [child1; child2]
ae4735db 1961 else
34e49164
C
1962 let res =
1963 let s = mkstates states required_states in
1964 List.fold_left
1965 (function a -> function b ->
1966 strict_triples_conj strict s a [b])
1967 [List.hd res2] (List.tl res2) in
1968 anno res [child1; child2]
1969 | [(state,_,_)] ->
1970 let res2 =
1971 List.map (function (s,e,w) -> [(state,e,w)]) res2 in
17ba0788 1972 output "andany";
34e49164
C
1973 let res =
1974 let s = mkstates states required_states in
1975 List.fold_left
1976 (function a -> function b ->
1977 strict_triples_conj strict s a b)
1978 res1 res2 in
1979 anno res [child1; child2]
1980 | _ ->
1981 failwith
1982 "only one result allowed for the left arg of AndAny")))
1983 | A.HackForStmt(dir,strict,phi1,phi2) ->
ae4735db 1984 let pm = !Flag_ctl.partial_match in
34e49164
C
1985 (match (pm,satv unchecked required required_states phi1 env) with
1986 (false,(child1,[])) ->
17ba0788 1987 output "and"; anno [] [child1]
34e49164
C
1988 | (_,(child1,res1)) ->
1989 let new_required = extend_required res1 required in
1990 let new_required_states = get_required_states res1 in
1991 let new_required_states =
1992 get_reachable dir m new_required_states in
1993 (match (pm,satv unchecked new_required new_required_states phi2
1994 env) with
1995 (false,(child2,[])) ->
17ba0788 1996 output "andany";
34e49164
C
1997 anno res1 [child1;child2]
1998 | (_,(child2,res2)) ->
1999 let res =
2000 let s = mkstates states required_states in
2001 List.fold_left
2002 (function acc ->
2003 function (st,th,_) as phi2_elem ->
2004 let inverse =
2005 triples_complement [st] [(st,th,[])] in
2006 strict_triples_conj_none strict s acc
2007 (phi2_elem::inverse))
2008 res1 res2 in
2009 anno res [child1; child2]))
2010 | A.InnerAnd(phi1) ->
2011 let (child1,res1) = satv unchecked required required_states phi1 env in
17ba0788 2012 output "uncheck";
34e49164 2013 anno (inner_and res1) [child1]
ae4735db 2014 | A.EX(dir,phi1) ->
34e49164
C
2015 let new_required_states =
2016 get_children_required_states dir m required_states in
2017 let (child,res) =
2018 satv unchecked required new_required_states phi1 env in
17ba0788 2019 output "EX";
34e49164 2020 anno (satEX dir m res required_states) [child]
ae4735db 2021 | A.AX(dir,strict,phi1) ->
34e49164
C
2022 let new_required_states =
2023 get_children_required_states dir m required_states in
2024 let (child,res) =
2025 satv unchecked required new_required_states phi1 env in
17ba0788 2026 output "AX";
34e49164
C
2027 let res = strict_A1 strict satAX satEX dir m res required_states in
2028 anno res [child]
ae4735db 2029 | A.EF(dir,phi1) ->
34e49164
C
2030 let new_required_states = get_reachable dir m required_states in
2031 let (child,res) =
2032 satv unchecked required new_required_states phi1 env in
17ba0788 2033 output "EF";
34e49164 2034 anno (satEF dir m res new_required_states) [child]
ae4735db 2035 | A.AF(dir,strict,phi1) ->
34e49164
C
2036 if !Flag_ctl.loop_in_src_code
2037 then
2038 satv unchecked required required_states
2039 (A.AU(dir,strict,A.True,phi1))
2040 env
2041 else
2042 (let new_required_states = get_reachable dir m required_states in
2043 let (child,res) =
2044 satv unchecked required new_required_states phi1 env in
17ba0788 2045 output "AF";
34e49164
C
2046 let res =
2047 strict_A1 strict satAF satEF dir m res new_required_states in
2048 anno res [child])
ae4735db 2049 | A.EG(dir,phi1) ->
34e49164
C
2050 let new_required_states = get_reachable dir m required_states in
2051 let (child,res) =
2052 satv unchecked required new_required_states phi1 env in
17ba0788 2053 output "EG";
34e49164 2054 anno (satEG dir m res new_required_states) [child]
ae4735db 2055 | A.AG(dir,strict,phi1) ->
34e49164
C
2056 let new_required_states = get_reachable dir m required_states in
2057 let (child,res) =
2058 satv unchecked required new_required_states phi1 env in
17ba0788 2059 output "AG";
34e49164
C
2060 let res = strict_A1 strict satAG satEF dir m res new_required_states in
2061 anno res [child]
ae4735db
C
2062
2063 | A.EU(dir,phi1,phi2) ->
34e49164
C
2064 let new_required_states = get_reachable dir m required_states in
2065 (match satv unchecked required new_required_states phi2 env with
2066 (child2,[]) ->
17ba0788 2067 output "EU";
34e49164
C
2068 anno [] [child2]
2069 | (child2,res2) ->
2070 let new_required = extend_required res2 required in
2071 let (child1,res1) =
2072 satv unchecked new_required new_required_states phi1 env in
17ba0788 2073 output "EU";
485bce71
C
2074 anno (satEU dir m res1 res2 new_required_states (fun y str -> ()))
2075 [child1; child2])
ae4735db 2076 | A.AW(dir,strict,phi1,phi2) ->
34e49164
C
2077 failwith "should not be used" (*
2078 let new_required_states = get_reachable dir m required_states in
2079 (match satv unchecked required new_required_states phi2 env with
2080 (child2,[]) ->
17ba0788 2081 output (Printf.sprintf "AW %b" unchecked); anno [] [child2]
34e49164
C
2082 | (child2,res2) ->
2083 let new_required = extend_required res2 required in
2084 let (child1,res1) =
2085 satv unchecked new_required new_required_states phi1 env in
17ba0788 2086 output (Printf.sprintf "AW %b" unchecked);
34e49164
C
2087 let res =
2088 strict_A2 strict satAW satEF dir m res1 res2
2089 new_required_states in
2090 anno res [child1; child2]) *)
ae4735db 2091 | A.AU(dir,strict,phi1,phi2) ->
34e49164
C
2092 let new_required_states = get_reachable dir m required_states in
2093 (match satv unchecked required new_required_states phi2 env with
2094 (child2,[]) ->
17ba0788 2095 output "AU"; anno [] [child2]
34e49164
C
2096 | (child2,s2) ->
2097 let new_required = extend_required s2 required in
2098 let (child1,s1) =
2099 satv unchecked new_required new_required_states phi1 env in
17ba0788 2100 output "AU";
34e49164 2101 let res =
485bce71
C
2102 strict_A2au strict satAU satEF dir m s1 s2 new_required_states
2103 (fun y str -> ()) in
34e49164
C
2104 (match res with
2105 AUok res ->
2106 anno res [child1; child2]
2107 | AUfailed tmp_res ->
2108 (* found a loop, have to try AW *)
2109 (* the formula is
2110 A[E[phi1 U phi2] & phi1 W phi2]
2111 the and is nonstrict *)
2112 (* tmp_res is bigger than s2, so perhaps closer to s1 *)
17ba0788 2113 output "AW";
34e49164 2114 let s1 =
485bce71
C
2115 triples_conj
2116 (satEU dir m s1 tmp_res new_required_states
2117 (* no graph, for the moment *)
2118 (fun y str -> ()))
2119 s1 in
34e49164
C
2120 let res =
2121 strict_A2 strict satAW satEF dir m s1 s2 new_required_states in
2122 anno res [child1; child2]))
ae4735db 2123 | A.Implies(phi1,phi2) ->
34e49164
C
2124 satv unchecked required required_states
2125 (A.Or(A.Not phi1,phi2))
2126 env
ae4735db 2127 | A.Exists (keep,v,phi1) ->
34e49164
C
2128 let new_required = drop_required v required in
2129 let (child,res) =
2130 satv unchecked new_required required_states phi1 env in
17ba0788 2131 output "exists";
34e49164
C
2132 anno (triples_witness v unchecked (not keep) res) [child]
2133 | A.Let(v,phi1,phi2) ->
2134 let (child1,res1) =
2135 satv unchecked required required_states phi1 env in
2136 let (child2,res2) =
2137 satv unchecked required required_states phi2 ((v,res1) :: env) in
2138 anno res2 [child1;child2]
2139 | A.LetR(dir,v,phi1,phi2) ->
2140 let new_required_states = get_reachable dir m required_states in
2141 let (child1,res1) =
2142 satv unchecked required new_required_states phi1 env in
2143 let (child2,res2) =
2144 satv unchecked required required_states phi2 ((v,res1) :: env) in
2145 anno res2 [child1;child2]
2146 | A.Ref(v) ->
17ba0788 2147 output "Ref";
34e49164
C
2148 let res = List.assoc v env in
2149 let res =
2150 if unchecked
2151 then List.map (function (s,th,_) -> (s,th,[])) res
2152 else res in
2153 anno res []
2154 | A.XX(phi) -> failwith "should have been removed" in
2155 let res1 = drop_wits required_states res phi in
2156 if not(res1 = res)
2157 then
2158 begin
2159 print_required_states required_states;
2160 print_state "after drop_wits" res1 end;
2161 (child,res1)
ae4735db 2162
34e49164
C
2163;;
2164
2165let sat_verbose annotate maxlvl lvl m phi =
2166 sat_verbose_loop false [] None annotate maxlvl lvl m phi []
2167
2168(* Type for annotations collected in a tree *)
2169type ('a) witAnnoTree = WitAnno of ('a * ('a witAnnoTree) list);;
2170
2171let sat_annotree annotate m phi =
2172 let tree_anno l phi res chld = WitAnno(annotate l phi res,chld) in
2173 sat_verbose_loop false [] None tree_anno (-1) 0 m phi []
2174;;
2175
2176(*
2177let sat m phi = satloop m phi []
2178;;
2179*)
2180
2181let simpleanno l phi res =
ae4735db
C
2182 let pp s =
2183 Format.print_string ("\n" ^ s ^ "\n------------------------------\n");
34e49164
C
2184 print_generic_algo (List.sort compare res);
2185 Format.print_string "\n------------------------------\n\n" in
2186 let pp_dir = function
2187 A.FORWARD -> ()
2188 | A.BACKWARD -> pp "^" in
2189 match phi with
2190 | A.False -> pp "False"
2191 | A.True -> pp "True"
2192 | A.Pred(p) -> pp ("Pred" ^ (Common.dump p))
2193 | A.Not(phi) -> pp "Not"
2194 | A.Exists(_,v,phi) -> pp ("Exists " ^ (Common.dump(v)))
2195 | A.And(_,phi1,phi2) -> pp "And"
2196 | A.AndAny(dir,_,phi1,phi2) -> pp "AndAny"
2197 | A.HackForStmt(dir,_,phi1,phi2) -> pp "HackForStmt"
2198 | A.Or(phi1,phi2) -> pp "Or"
2199 | A.SeqOr(phi1,phi2) -> pp "SeqOr"
2200 | A.Implies(phi1,phi2) -> pp "Implies"
2201 | A.AF(dir,_,phi1) -> pp "AF"; pp_dir dir
2202 | A.AX(dir,_,phi1) -> pp "AX"; pp_dir dir
2203 | A.AG(dir,_,phi1) -> pp "AG"; pp_dir dir
2204 | A.AW(dir,_,phi1,phi2)-> pp "AW"; pp_dir dir
2205 | A.AU(dir,_,phi1,phi2)-> pp "AU"; pp_dir dir
2206 | A.EF(dir,phi1) -> pp "EF"; pp_dir dir
2207 | A.EX(dir,phi1) -> pp "EX"; pp_dir dir
2208 | A.EG(dir,phi1) -> pp "EG"; pp_dir dir
2209 | A.EU(dir,phi1,phi2) -> pp "EU"; pp_dir dir
2210 | A.Let (x,phi1,phi2) -> pp ("Let"^" "^x)
2211 | A.LetR (dir,x,phi1,phi2) -> pp ("LetR"^" "^x); pp_dir dir
2212 | A.Ref(s) -> pp ("Ref("^s^")")
2213 | A.Uncheck(s) -> pp "Uncheck"
2214 | A.InnerAnd(s) -> pp "InnerAnd"
2215 | A.XX(phi1) -> pp "XX"
2216;;
2217
2218
2219(* pad: Rene, you can now use the module pretty_print_ctl.ml to
2220 print a ctl formula more accurately if you want.
ae4735db 2221 Use the print_xxx provided in the different module to call
34e49164
C
2222 Pretty_print_ctl.pp_ctl.
2223 *)
2224
ae4735db 2225let simpleanno2 l phi res =
34e49164
C
2226 begin
2227 Pretty_print_ctl.pp_ctl (P.print_predicate, SUB.print_mvar) false phi;
2228 Format.print_newline ();
2229 Format.print_string "----------------------------------------------------";
2230 Format.print_newline ();
2231 print_generic_algo (List.sort compare res);
2232 Format.print_newline ();
2233 Format.print_string "----------------------------------------------------";
2234 Format.print_newline ();
2235 Format.print_newline ();
2236 end
2237
2238
2239(* ---------------------------------------------------------------------- *)
2240(* Benchmarking *)
2241(* ---------------------------------------------------------------------- *)
2242
2243type optentry = bool ref * string
2244type options = {label : optentry; unch : optentry;
2245 conj : optentry; compl1 : optentry; compl2 : optentry;
2246 newinfo : optentry;
2247 reqenv : optentry; reqstates : optentry}
2248
2249let options =
2250 {label = (pSATLABEL_MEMO_OPT,"satlabel_memo_opt");
2251 unch = (pUNCHECK_OPT,"uncheck_opt");
2252 conj = (pTRIPLES_CONJ_OPT,"triples_conj_opt");
2253 compl1 = (pTRIPLES_COMPLEMENT_OPT,"triples_complement_opt");
2254 compl2 = (pTRIPLES_COMPLEMENT_SIMPLE_OPT,"triples_complement_simple_opt");
2255 newinfo = (pNEW_INFO_OPT,"new_info_opt");
2256 reqenv = (pREQUIRED_ENV_OPT,"required_env_opt");
2257 reqstates = (pREQUIRED_STATES_OPT,"required_states_opt")}
2258
2259let baseline =
2260 [("none ",[]);
2261 ("label ",[options.label]);
2262 ("unch ",[options.unch]);
2263 ("unch and label ",[options.label;options.unch])]
2264
2265let conjneg =
2266 [("conj ", [options.conj]);
2267 ("compl1 ", [options.compl1]);
2268 ("compl12 ", [options.compl1;options.compl2]);
2269 ("conj/compl12 ", [options.conj;options.compl1;options.compl2]);
2270 ("conj unch satl ", [options.conj;options.unch;options.label]);
2271(*
2272 ("compl1 unch satl ", [options.compl1;options.unch;options.label]);
2273 ("compl12 unch satl ",
2274 [options.compl1;options.compl2;options.unch;options.label]); *)
2275 ("conj/compl12 unch satl ",
2276 [options.conj;options.compl1;options.compl2;options.unch;options.label])]
2277
2278let path =
2279 [("newinfo ", [options.newinfo]);
2280 ("newinfo unch satl ", [options.newinfo;options.unch;options.label])]
2281
2282let required =
2283 [("reqenv ", [options.reqenv]);
2284 ("reqstates ", [options.reqstates]);
2285 ("reqenv/states ", [options.reqenv;options.reqstates]);
2286(* ("reqenv unch satl ", [options.reqenv;options.unch;options.label]);
2287 ("reqstates unch satl ",
2288 [options.reqstates;options.unch;options.label]);*)
2289 ("reqenv/states unch satl ",
2290 [options.reqenv;options.reqstates;options.unch;options.label])]
2291
2292let all_options =
2293 [options.label;options.unch;options.conj;options.compl1;options.compl2;
2294 options.newinfo;options.reqenv;options.reqstates]
2295
2296let all =
2297 [("all ",all_options)]
2298
2299let all_options_but_path =
2300 [options.label;options.unch;options.conj;options.compl1;options.compl2;
2301 options.reqenv;options.reqstates]
2302
2303let all_but_path = ("all but path ",all_options_but_path)
2304
2305let counters =
2306 [(satAW_calls, "satAW", ref 0);
2307 (satAU_calls, "satAU", ref 0);
2308 (satEF_calls, "satEF", ref 0);
2309 (satAF_calls, "satAF", ref 0);
2310 (satEG_calls, "satEG", ref 0);
2311 (satAG_calls, "satAG", ref 0);
2312 (satEU_calls, "satEU", ref 0)]
2313
2314let perms =
2315 map
2316 (function (opt,x) ->
2317 (opt,x,ref 0.0,ref 0,
2318 List.map (function _ -> (ref 0, ref 0, ref 0)) counters))
2319 [List.hd all;all_but_path]
2320 (*(all@baseline@conjneg@path@required)*)
2321
2322exception Out
2323
2324let rec iter fn = function
2325 1 -> fn()
2326 | n -> let _ = fn() in
2327 (Hashtbl.clear reachable_table;
2328 Hashtbl.clear memo_label;
2329 triples := 0;
2330 iter fn (n-1))
2331
2332let copy_to_stderr fl =
2333 let i = open_in fl in
2334 let rec loop _ =
2335 Printf.fprintf stderr "%s\n" (input_line i);
2336 loop() in
2337 try loop() with _ -> ();
2338 close_in i
2339
2340let bench_sat (_,_,states) fn =
2341 List.iter (function (opt,_) -> opt := false) all_options;
2342 let answers =
2343 concatmap
2344 (function (name,options,time,trips,counter_info) ->
2345 let iterct = !Flag_ctl.bench in
2346 if !time > float_of_int timeout then time := -100.0;
2347 if not (!time = -100.0)
2348 then
2349 begin
2350 Hashtbl.clear reachable_table;
2351 Hashtbl.clear memo_label;
2352 List.iter (function (opt,_) -> opt := true) options;
2353 List.iter (function (calls,_,save_calls) -> save_calls := !calls)
2354 counters;
2355 triples := 0;
2356 let res =
2357 let bef = Sys.time() in
2358 try
2359 Common.timeout_function timeout
2360 (fun () ->
2361 let bef = Sys.time() in
2362 let res = iter fn iterct in
2363 let aft = Sys.time() in
2364 time := !time +. (aft -. bef);
2365 trips := !trips + !triples;
2366 List.iter2
2367 (function (calls,_,save_calls) ->
2368 function (current_calls,current_cfg,current_max_cfg) ->
2369 current_calls :=
2370 !current_calls + (!calls - !save_calls);
2371 if (!calls - !save_calls) > 0
2372 then
2373 (let st = List.length states in
2374 current_cfg := !current_cfg + st;
2375 if st > !current_max_cfg
2376 then current_max_cfg := st))
2377 counters counter_info;
2378 [res])
2379 with
2380 Common.Timeout ->
2381 begin
2382 let aft = Sys.time() in
2383 time := -100.0;
2384 Printf.fprintf stderr "Timeout at %f on: %s\n"
2385 (aft -. bef) name;
2386 []
2387 end in
2388 List.iter (function (opt,_) -> opt := false) options;
2389 res
2390 end
2391 else [])
2392 perms in
2393 Printf.fprintf stderr "\n";
2394 match answers with
2395 [] -> []
2396 | res::rest ->
2397 (if not(List.for_all (function x -> x = res) rest)
2398 then
2399 (List.iter (print_state "a state") answers;
2400 Printf.printf "something doesn't work\n");
2401 res)
ae4735db 2402
34e49164
C
2403let print_bench _ =
2404 let iterct = !Flag_ctl.bench in
2405 if iterct > 0
2406 then
2407 (List.iter
2408 (function (name,options,time,trips,counter_info) ->
2409 Printf.fprintf stderr "%s Numbers: %f %d "
2410 name (!time /. (float_of_int iterct)) !trips;
2411 List.iter
2412 (function (calls,cfg,max_cfg) ->
2413 Printf.fprintf stderr "%d %d %d " (!calls / iterct) !cfg !max_cfg)
2414 counter_info;
2415 Printf.fprintf stderr "\n")
2416 perms)
2417
2418(* ---------------------------------------------------------------------- *)
2419(* preprocessing: ignore irrelevant functions *)
2420
2421let preprocess (cfg,_,_) label = function
2422 [] -> true (* no information, try everything *)
2423 | l ->
2424 let sz = G.size cfg in
2425 let verbose_output pred = function
2426 [] ->
2427 Printf.printf "did not find:\n";
2428 P.print_predicate pred; Format.print_newline()
2429 | _ ->
2430 Printf.printf "found:\n";
2431 P.print_predicate pred; Format.print_newline();
2432 Printf.printf "but it was not enough\n" in
2433 let get_any verbose x =
2434 let res =
2435 try Hashtbl.find memo_label x
2436 with
2437 Not_found ->
2438 (let triples = label x in
2439 let filtered =
2440 List.map (function (st,th,_) -> (st,th)) triples in
2441 Hashtbl.add memo_label x filtered;
2442 filtered) in
2443 if verbose then verbose_output x res;
2444 not([] = res) in
2445 let get_all l =
2446 (* don't bother testing when there are more patterns than nodes *)
2447 if List.length l > sz-2
2448 then false
2449 else List.for_all (get_any false) l in
2450 if List.exists get_all l
2451 then true
2452 else
2453 (if !Flag_ctl.verbose_match
2454 then
2455 List.iter (List.iter (function x -> let _ = get_any true x in ()))
2456 l;
2457 false)
2458
2459let filter_partial_matches trips =
2460 if !Flag_ctl.partial_match
2461 then
2462 let anynegwit = (* if any is neg, then all are *)
2463 List.exists (function A.NegWit _ -> true | A.Wit _ -> false) in
2464 let (bad,good) =
2465 List.partition (function (s,th,wit) -> anynegwit wit) trips in
2466 (match bad with
2467 [] -> ()
2468 | _ -> print_state "partial matches" bad; Format.print_newline());
2469 good
2470 else trips
2471
2472(* ---------------------------------------------------------------------- *)
2473(* Main entry point for engine *)
2474let sat m phi reqopt =
2475 try
2476 (match !Flag_ctl.steps with
2477 None -> step_count := 0
2478 | Some x -> step_count := x);
2479 Hashtbl.clear reachable_table;
2480 Hashtbl.clear memo_label;
2481 let (x,label,states) = m in
2482 if (!Flag_ctl.bench > 0) or (preprocess m label reqopt)
2483 then
2484 ((* to drop when Yoann initialized this flag *)
2485 if List.exists (G.extract_is_loop x) states
2486 then Flag_ctl.loop_in_src_code := true;
2487 let m = (x,label,List.sort compare states) in
2488 let res =
2489 if(!Flag_ctl.verbose_ctl_engine)
2490 then
2491 let fn _ = snd (sat_annotree simpleanno2 m phi) in
2492 if !Flag_ctl.bench > 0
2493 then bench_sat m fn
2494 else fn()
2495 else
2496 let fn _ = satloop false [] None m phi [] in
2497 if !Flag_ctl.bench > 0
2498 then bench_sat m fn
2499 else Common.profile_code "ctl" (fun _ -> fn()) in
2500 let res = filter_partial_matches res in
2501 (*
2502 Printf.printf "steps: start %d, stop %d\n"
2503 (match !Flag_ctl.steps with Some x -> x | _ -> 0)
2504 !step_count;
2505 Printf.printf "triples: %d\n" !triples;
2506 print_state "final result" res;
2507 *)
708f4980 2508 List.sort compare res)
34e49164
C
2509 else
2510 (if !Flag_ctl.verbose_ctl_engine
2511 then Common.pr2 "missing something required";
2512 [])
2513 with Steps -> []
34e49164
C
2514
2515(* ********************************************************************** *)
2516(* End of Module: CTL_ENGINE *)
2517(* ********************************************************************** *)
2518end
2519;;