Coccinelle release-1.0.0-rc11
[bpt/coccinelle.git] / engine / ctlcocci_integration.ml
1 (*
2 * Copyright 2012, INRIA
3 * Julia Lawall, Gilles Muller
4 * Copyright 2010-2011, INRIA, University of Copenhagen
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
27 open Common
28
29 open Ograph_extended
30
31 module F = Control_flow_c
32
33 (*****************************************************************************)
34 (* Debugging functions *)
35 (*****************************************************************************)
36 let show_or_not_predicate pred =
37 if !Flag_matcher.debug_engine then begin
38 indent_do (fun () ->
39 adjust_pp_with_indent_and_header "labeling: pred = " (fun () ->
40 Pretty_print_engine.pp_predicate pred;
41 );
42 )
43 end
44
45 let show_or_not_nodes nodes =
46 if !Flag_matcher.debug_engine then begin
47 indent_do (fun () ->
48 adjust_pp_with_indent_and_header "labeling: result = " (fun () ->
49 Common.pp_do_in_box (fun () ->
50 pp "{";
51 Common.print_between
52 (fun () -> pp ";"; Format.print_cut())
53 (fun (nodei, (_predTODO, subst)) ->
54 Format.print_int nodei;
55 Common.pp_do_in_box (fun () ->
56 Pretty_print_engine.pp_binding2_ctlsubst subst
57 )
58 ) nodes;
59 pp "}";
60 );
61 )
62 )
63 end
64
65 let show_isos rule_elem =
66 match Ast_cocci.get_isos rule_elem with
67 [] -> ()
68 | isos ->
69 let line = Ast_cocci.get_line rule_elem in
70 Printf.printf "rule elem: ";
71 Pretty_print_cocci.rule_elem "" rule_elem;
72 Format.print_newline();
73 List.iter
74 (function (nm,x) ->
75 Printf.printf " iso: %s(%d): " nm line;
76 Pretty_print_cocci.pp_print_anything x;
77 Format.print_newline())
78 isos
79
80 (*****************************************************************************)
81 (* Labeling function *)
82 (*****************************************************************************)
83 let (-->) x v = Ast_ctl.Subst (x,v);;
84
85 (* Take list of predicate and for each predicate returns where in the
86 * control flow it matches, and the set of subsitutions for this match.
87 *)
88 let (labels_for_ctl: string list (* dropped isos *) ->
89 (nodei * F.node) list -> Lib_engine.metavars_binding ->
90 Lib_engine.label_ctlcocci) =
91 fun dropped_isos nodes binding ->
92
93 (fun p ->
94 show_or_not_predicate p;
95
96 let nodes' = nodes +> List.map (fun (nodei, node) ->
97 (* todo? put part of this code in pattern ? *)
98 (match p, F.unwrap node with
99 | Lib_engine.Paren s, (F.SeqStart (_, bracelevel, _)) ->
100 let make_var x = ("",i_to_s x) in
101 [(nodei, (p,[(s --> (Lib_engine.ParenVal (make_var bracelevel)))]))]
102 | Lib_engine.Paren s, (F.SeqEnd (bracelevel, _)) ->
103 let make_var x = ("",i_to_s x) in
104 [(nodei, (p,[(s --> (Lib_engine.ParenVal (make_var bracelevel)))]))]
105 | Lib_engine.Paren _, _ -> []
106 | Lib_engine.Label s, _ ->
107 let labels = F.extract_labels node in
108 [(nodei,
109 (p,[(s --> (Lib_engine.LabelVal (Lib_engine.Absolute labels)))]))]
110 | Lib_engine.BCLabel s, _ ->
111 (match F.extract_bclabels node with
112 [] -> [] (* null for all nodes that are not break or continue *)
113 | labels ->
114 [(nodei,
115 (p,[(s -->
116 (Lib_engine.LabelVal (Lib_engine.Absolute labels)))]))])
117 | Lib_engine.PrefixLabel s, _ ->
118 let labels = F.extract_labels node in
119 [(nodei,
120 (p,[(s --> (Lib_engine.LabelVal (Lib_engine.Prefix labels)))]))]
121
122 | Lib_engine.Match (re), _unwrapnode ->
123 let substs =
124 Pattern_c.match_re_node dropped_isos re node binding
125 +> List.map (fun (re', subst) ->
126 Lib_engine.Match (re'), subst
127 )
128 in
129 substs +> List.map (fun (p', subst) ->
130 (nodei,
131 (p',
132 subst +> List.map (fun (s, meta) ->
133 s --> Lib_engine.NormalMetaVal meta
134 ))))
135
136 | Lib_engine.InLoop, F.InLoopNode -> [nodei, (p,[])]
137 | Lib_engine.TrueBranch , F.TrueNode -> [nodei, (p,[])]
138 | Lib_engine.FalseBranch, F.FalseNode -> [nodei, (p,[])]
139 | Lib_engine.After, F.AfterNode -> [nodei, (p,[])]
140 | Lib_engine.FallThrough, F.FallThroughNode -> [nodei,(p,[])]
141 | Lib_engine.LoopFallThrough, F.LoopFallThroughNode -> [nodei,(p,[])]
142 | Lib_engine.FunHeader, F.FunHeader _ -> [nodei, (p,[])]
143 | Lib_engine.Top, F.TopNode -> [nodei, (p,[])]
144 | Lib_engine.Exit, F.Exit -> [nodei, (p,[])]
145 | Lib_engine.ErrorExit, F.ErrorExit -> [nodei, (p,[])]
146 | Lib_engine.Goto, F.Goto(_,_,_) -> [nodei, (p,[])]
147
148 | Lib_engine.UnsafeBrace, node ->
149 (* cases where it it not safe to put something on the outer side
150 of braces *)
151 (match node with
152 F.FunHeader _ | F.DoHeader _ | F.TrueNode _ | F.Else _
153 | F.InLoopNode _ (* while, for *) | F.SwitchHeader _ ->
154 [nodei, (p,[])]
155 | _ -> [])
156
157 | Lib_engine.InLoop , _ -> []
158 | Lib_engine.TrueBranch , _ -> []
159 | Lib_engine.FalseBranch, _ -> []
160 | Lib_engine.After, _ -> []
161 | Lib_engine.FallThrough, _ -> []
162 | Lib_engine.LoopFallThrough, _ -> []
163 | Lib_engine.FunHeader, _ -> []
164 | Lib_engine.Top, _ -> []
165 | Lib_engine.Exit, _ -> []
166 | Lib_engine.ErrorExit, _ -> []
167 | Lib_engine.Goto, _ -> []
168
169 | Lib_engine.BindGood s, _ -> [(nodei, (p,[(s --> Lib_engine.GoodVal)]))]
170 | Lib_engine.BindBad s, _ -> [(nodei, (p,[(s --> Lib_engine.BadVal)]))]
171 | Lib_engine.FakeBrace, _ ->
172 if F.extract_is_fake node then [nodei, (p,[])] else []
173
174 | Lib_engine.Return, node ->
175 (match node with
176 (* todo? should match the Exit code ?
177 * todo: one day try also to match the special function
178 * such as panic();
179 *)
180 | F.Return _ -> [nodei, (p,[])]
181 | F.ReturnExpr _ -> [nodei, (p,[])]
182 | _ -> []
183 )
184 )
185 ) +> List.concat
186 in
187
188 show_or_not_nodes nodes';
189 nodes'
190 )
191
192 (*****************************************************************************)
193 (* Some fix flow, for CTL, for unparse *)
194 (*****************************************************************************)
195 (* could erase info on nodes, and edge, because they are not used by rene *)
196 let (control_flow_for_ctl: F.cflow -> ('a, 'b) ograph_mutable) =
197 fun cflow -> cflow
198
199
200
201 (* Just make the final node of the control flow loop over itself.
202 * It seems that one hypothesis of the SAT algorithm is that each node as at
203 * least a successor.
204 *
205 * update: do same for errorexit node.
206 *
207 * update: also erase the fake nodes (and adjust the edges accordingly),
208 * so that AX in CTL can now work.
209 * Indeed, à la fin de la branche then (et else), on devrait aller directement
210 * au suivant du endif, sinon si ecrit if(1) { foo(); }; bar();
211 * sans '...' entre le if et bar(), alors ca matchera pas car le CTL
212 * generera un AX bar() qui il tombera d'abord sur le [endif] :(
213 * Mais chiant de changer l'algo de generation, marche pas tres bien avec
214 * ma facon de faire recursive et compositionnel.
215 * => faire une fonction qui applique des fixes autour de ce control flow,
216 * comme ca passe un bon flow a rene, mais garde un flow a moi pour pouvoir
217 * facilement generate back the ast.
218 * alt: faire un wrapper autourde mon graphe pour lui passer dans le module CFG
219 * une fonction qui passe a travers les Fake, mais bof.
220 *
221 * update: also make loop the deadcode nodes, the one that have
222 * no predecessor.
223 *)
224 let (fix_flow_ctl2: F.cflow -> F.cflow) = fun flow ->
225 let g = ref flow in
226
227 let topi = F.first_node !g in
228 !g#add_arc ((topi, topi), F.Direct);
229
230 (* for the #define CFG who have no Exit but have at least a EndNode *)
231 (try
232 let endi = F.find_node (fun x -> x =*= F.EndNode) !g in
233 !g#add_arc ((endi, endi), F.Direct);
234 with Not_found -> ()
235 );
236
237 (* for the regular functions *)
238 (try
239 let exitnodei = F.find_node (fun x -> x =*= F.Exit) !g in
240 let errornodei = F.find_node (fun x -> x =*= F.ErrorExit) !g in
241
242 !g#add_arc ((exitnodei, exitnodei), F.Direct);
243
244 if null ((!g#successors errornodei)#tolist) &&
245 null ((!g#predecessors errornodei)#tolist)
246 then !g#del_node errornodei
247 else !g#add_arc ((errornodei, errornodei), F.Direct);
248 with Not_found -> ()
249 );
250
251 let fake_nodes = !g#nodes#tolist +> List.filter (fun (nodei, node) ->
252 match F.unwrap node with
253 | F.CaseNode _
254 | F.Enter
255 (*| F.Fake*) (* [endif], [endswitch], ... *)
256 -> true
257 | _ -> false
258 ) in
259
260 fake_nodes +> List.iter (fun (nodei, node) -> F.remove_one_node nodei !g);
261
262 (* even when have deadcode, julia want loop over those nodes *)
263 !g#nodes#tolist +> List.iter (fun (nodei, node) ->
264 if (!g#predecessors nodei)#null
265 then begin
266 let fakei = !g#add_node (F.mk_node F.Fake [] [] "DEADCODELOOP") in
267 !g#add_arc ((fakei, nodei), F.Direct);
268 !g#add_arc ((fakei, fakei), F.Direct);
269 end
270 );
271
272 !g#nodes#tolist +> List.iter (fun (nodei, node) ->
273 assert (List.length ((!g#successors nodei)#tolist) >= 1);
274 (* no: && List.length ((!g#predecessors nodei)#tolist) >= 1
275 because the enter node at least have no predecessors *)
276 );
277
278 !g
279 let fix_flow_ctl a =
280 Common.profile_code "fix_flow" (fun () -> fix_flow_ctl2 a)
281
282
283
284
285
286 (*****************************************************************************)
287 (* subtil: the label must operate on newflow, not (old) cflow
288 * update: now I supposed that we give me a fixed_flow
289 *)
290 let model_for_ctl dropped_isos cflow binding =
291 let newflow = cflow (* old: fix_flow_ctl (control_flow_for_ctl cflow) *) in
292 let labels = labels_for_ctl dropped_isos (newflow#nodes#tolist) binding in
293 let states = List.map fst newflow#nodes#tolist in
294 newflow, labels, states
295
296
297 (*****************************************************************************)
298
299 module PRED =
300 struct
301 type t = Lib_engine.predicate
302 let print_predicate x =
303 Pretty_print_cocci.print_plus_flag := false;
304 Pretty_print_cocci.print_minus_flag := false;
305 Pretty_print_engine.pp_predicate x
306 end
307
308 (* prefix has to be nonempty *)
309 let prefix l1 l2 =
310 let rec loop = function
311 ([],_) -> true
312 | (_,[]) -> false
313 | (x::xs,y::ys) when x = y -> loop (xs,ys)
314 | _ -> false in
315 loop(l1,l2)
316
317 let compatible_labels l1 l2 =
318 match (l1,l2) with
319 (Lib_engine.Absolute(l1),Lib_engine.Absolute(l2)) -> l1 =*= l2
320 | (Lib_engine.Absolute(l1),Lib_engine.Prefix(l2)) -> prefix l1 l2
321 | (Lib_engine.Prefix(l1),Lib_engine.Absolute(l2)) -> prefix l2 l1
322 | (Lib_engine.Prefix(l1),Lib_engine.Prefix(l2)) ->
323 not (l1 = []) && not (l2 = []) &&
324 List.hd l1 =*= List.hd l2 (* labels are never empty *)
325
326 let merge_labels l1 l2 =
327 match (l1,l2) with
328 (* known to be compatible *)
329 (Lib_engine.Absolute(_),Lib_engine.Absolute(_)) -> l1
330 | (Lib_engine.Absolute(_),Lib_engine.Prefix(_)) -> l1
331 | (Lib_engine.Prefix(_),Lib_engine.Absolute(_)) -> l2
332 | (Lib_engine.Prefix(l1),Lib_engine.Prefix(l2)) ->
333 let rec max_prefix = function
334 (x::xs,y::ys) when x = y -> x::(max_prefix(xs,ys))
335 | (l1,l2) -> [] in
336 Lib_engine.Prefix(max_prefix(l1,l2))
337
338 module ENV =
339 struct
340 type value = Lib_engine.metavar_binding_kind2
341 type mvar = Ast_cocci.meta_name
342 let eq_mvar x x' = x =*= x'
343 let eq_val v v' =
344 (* v = v' *)
345 match (v,v') with
346 (Lib_engine.NormalMetaVal(Ast_c.MetaPosVal(min1,max1)),
347 Lib_engine.NormalMetaVal(Ast_c.MetaPosVal(min2,max2))) ->
348 ((min1 <= min2) && (max1 >= max2)) or
349 ((min2 <= min1) && (max2 >= max1))
350 | (Lib_engine.NormalMetaVal(Ast_c.MetaTypeVal a),
351 Lib_engine.NormalMetaVal(Ast_c.MetaTypeVal b)) ->
352 C_vs_c.eq_type a b
353 | (Lib_engine.LabelVal(l1),Lib_engine.LabelVal(l2)) ->
354 compatible_labels l1 l2
355 | _ -> v =*= v'
356 let merge_val v v' = (* values guaranteed to be compatible *)
357 (* v *)
358 match (v,v') with
359 (Lib_engine.NormalMetaVal(Ast_c.MetaPosVal(min1,max1)),
360 Lib_engine.NormalMetaVal(Ast_c.MetaPosVal(min2,max2))) ->
361 if (min1 <= min2) && (max1 >= max2)
362 then Lib_engine.NormalMetaVal(Ast_c.MetaPosVal(min1,max1))
363 else
364 if (min2 <= min1) && (max2 >= max1)
365 then Lib_engine.NormalMetaVal(Ast_c.MetaPosVal(min2,max2))
366 else failwith "incompatible positions give to merge"
367 | (Lib_engine.NormalMetaVal(Ast_c.MetaTypeVal a),
368 Lib_engine.NormalMetaVal(Ast_c.MetaTypeVal b)) ->
369 Lib_engine.NormalMetaVal (Ast_c.MetaTypeVal (C_vs_c.merge_type a b))
370 | (Lib_engine.LabelVal(l1),Lib_engine.LabelVal(l2)) ->
371 Lib_engine.LabelVal(merge_labels l1 l2)
372
373 | _ -> v
374 let print_mvar (_,s) = Format.print_string s
375 let print_value x = Pretty_print_engine.pp_binding_kind2 x
376 end
377
378 module CFG =
379 struct
380 type node = Ograph_extended.nodei
381 type cfg = (F.node, F.edge) Ograph_extended.ograph_mutable
382 let predecessors cfg n = List.map fst ((cfg#predecessors n)#tolist)
383 let successors cfg n = List.map fst ((cfg#successors n)#tolist)
384 let extract_is_loop cfg n =
385 Control_flow_c.extract_is_loop (cfg#nodes#find n)
386 let print_node i = Format.print_string (i_to_s i)
387 let size cfg = cfg#nodes#length
388
389 (* In ctl_engine, we use 'node' for the node but in the Ograph_extended
390 * terminology, this 'node' is in fact an index to access the real
391 * node information (that ctl/ wants to abstract away to be more generic),
392 * the 'Ograph_extended.nodei'.
393 *)
394 let print_graph cfg label border_colors fill_colors filename =
395 Ograph_extended.print_ograph_mutable_generic cfg label
396 (fun (nodei, (node: F.node)) ->
397 (* the string julia wants to put ? *)
398 let bc = try Some(List.assoc nodei border_colors) with _ -> None in
399 let fc = try Some(List.assoc nodei fill_colors) with _ -> None in
400 (* the string yoann put as debug information in the cfg *)
401 let str = snd node in
402 (str,bc,fc)
403 )
404 ~output_file:filename
405 ~launch_gv:false
406 end
407
408
409 module WRAPPED_ENGINE = Wrapper_ctl.CTL_ENGINE_BIS (ENV) (CFG) (PRED)
410
411 let print_bench _ = WRAPPED_ENGINE.print_bench()
412
413 type pred = Lib_engine.predicate * Ast_cocci.meta_name Ast_ctl.modif
414
415 (*****************************************************************************)
416 let metavars_binding2_to_binding binding2 =
417 binding2 +> Common.map_filter (fun (s, kind2) ->
418 match kind2 with
419 | Lib_engine.NormalMetaVal kind -> Some (s, kind)
420 (* I thought it was Impossible to have this when called from
421 satbis_to_trans_info but it does not seems so *)
422 | Lib_engine.ParenVal _ -> None
423 | Lib_engine.LabelVal _ -> None
424 | Lib_engine.BadVal -> None (* should not occur *)
425 | Lib_engine.GoodVal -> None (* should not occur *)
426 )
427
428 let metavars_binding_to_binding2 binding =
429 binding +> List.map (fun (s, kind) -> s, Lib_engine.NormalMetaVal kind)
430
431
432 let (satbis_to_trans_info:
433 (int list *
434 (nodei * Lib_engine.metavars_binding2 * Lib_engine.predicate)) list ->
435 (int list *
436 (nodei * Lib_engine.metavars_binding * Ast_cocci.rule_elem)) list) =
437 fun xs ->
438 xs +> List.fold_left (fun prev (index,(nodei, binding2, pred)) ->
439 match pred with
440 | Lib_engine.Match (rule_elem) ->
441 if !Flag.track_iso_usage then show_isos rule_elem;
442 (index,
443 (nodei, metavars_binding2_to_binding binding2, rule_elem))
444 ::prev
445 (* see BindGood in asttotctl2 *)
446 | Lib_engine.BindGood (_) -> prev
447 | _ -> raise Impossible
448 ) []
449
450 (*****************************************************************************)
451
452 let rec coalesce_positions = function
453 [] -> []
454 | (x,Ast_c.MetaPosValList l)::rest ->
455 let (same,others) = List.partition (function (x1,_) -> x =*= x1) rest in
456 let ls =
457 List.concat
458 (List.map
459 (function
460 (_,Ast_c.MetaPosValList l) -> l
461 | _ -> failwith "unexpected non-position")
462 same) in
463 let new_ls = List.sort compare (l@ls) in
464 (x,Ast_c.MetaPosValList new_ls) :: coalesce_positions others
465 | x::rest -> x :: coalesce_positions rest
466
467 let strip env =
468 List.map
469 (function (v,vl) ->
470 let vl =
471 match vl with
472 Ast_c.MetaExprVal (a,c) ->
473 Ast_c.MetaExprVal(Lib_parsing_c.al_inh_expr a,c)
474 | Ast_c.MetaExprListVal a ->
475 Ast_c.MetaExprListVal(Lib_parsing_c.al_inh_arguments a)
476 | Ast_c.MetaStmtVal a ->
477 Ast_c.MetaStmtVal(Lib_parsing_c.al_inh_statement a)
478 | Ast_c.MetaInitVal a ->
479 Ast_c.MetaInitVal(Lib_parsing_c.al_inh_init a)
480 | Ast_c.MetaInitListVal a ->
481 Ast_c.MetaInitListVal(Lib_parsing_c.al_inh_inits a)
482 | x -> (*don't contain binding info*) x in
483 (v,vl))
484 env
485
486 let rec nub ls =
487 match ls with
488 [] -> []
489 | (x::xs) when (List.mem x xs) -> nub xs
490 | (x::xs) -> x::(nub xs)
491
492 (*****************************************************************************)
493 (* Call ctl engine *)
494 (*****************************************************************************)
495 let (mysat2:
496 Lib_engine.model ->
497 (Lib_engine.ctlcocci * (pred list list)) ->
498 (string (*rulename*) * Lib_engine.mvar list*Lib_engine.metavars_binding) ->
499 (Lib_engine.numbered_transformation_info * bool *
500 Lib_engine.metavars_binding * Lib_engine.metavars_binding list)) =
501 fun (flow, label, states) ctl (rulename, used_after, binding) ->
502 let binding2 = metavars_binding_to_binding2 binding in
503 let (triples,(trans_info2, returned_any_states, used_after_envs)) =
504 WRAPPED_ENGINE.satbis (flow, label, states) ctl
505 (used_after, binding2)
506 in
507 if not (!Flag_parsing_cocci.sgrep_mode || !Flag.sgrep_mode2 ||
508 !Flag_matcher.allow_inconsistent_paths)
509 then Check_reachability.check_reachability rulename triples flow;
510 let (trans_info2,used_after_fresh_envs) =
511 Postprocess_transinfo.process used_after binding2 trans_info2 in
512 let used_after_envs =
513 Common.uniq(List.map2 (@) used_after_fresh_envs used_after_envs) in
514 let trans_info = satbis_to_trans_info trans_info2 in
515 let newbindings = List.map metavars_binding2_to_binding used_after_envs in
516 let newbindings = List.map coalesce_positions newbindings in
517 let newbindings = List.map strip newbindings in
518 let newbindings = nub newbindings in
519 (trans_info, returned_any_states, binding, newbindings)
520
521 let mysat a b c =
522 Common.profile_code "mysat" (fun () -> mysat2 a b c)