Release coccinelle-0.2.0
[bpt/coccinelle.git] / engine / pattern_c.ml
1 (*
2 * Copyright 2005-2009, Ecole des Mines de Nantes, University of Copenhagen
3 * Yoann Padioleau, Julia Lawall, Rene Rydhof Hansen, Henrik Stuart, Gilles Muller, Nicolas Palix
4 * This file is part of Coccinelle.
5 *
6 * Coccinelle is free software: you can redistribute it and/or modify
7 * it under the terms of the GNU General Public License as published by
8 * the Free Software Foundation, according to version 2 of the License.
9 *
10 * Coccinelle is distributed in the hope that it will be useful,
11 * but WITHOUT ANY WARRANTY; without even the implied warranty of
12 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
13 * GNU General Public License for more details.
14 *
15 * You should have received a copy of the GNU General Public License
16 * along with Coccinelle. If not, see <http://www.gnu.org/licenses/>.
17 *
18 * The authors reserve the right to distribute this or future versions of
19 * Coccinelle under other licenses.
20 *)
21
22
23 (* Yoann Padioleau
24 *
25 * Copyright (C) 2006, 2007 Ecole des Mines de Nantes
26 *
27 * This program is free software; you can redistribute it and/or
28 * modify it under the terms of the GNU General Public License (GPL)
29 * version 2 as published by the Free Software Foundation.
30 *
31 * This program is distributed in the hope that it will be useful,
32 * but WITHOUT ANY WARRANTY; without even the implied warranty of
33 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
34 * file license.txt for more details.
35 *
36 * This file was part of Coccinelle.
37 *)
38 open Common
39
40 module Flag_engine = Flag_matcher
41 (*****************************************************************************)
42 (* The functor argument *)
43 (*****************************************************************************)
44
45 (* info passed recursively in monad in addition to binding *)
46 type xinfo = {
47 optional_storage_iso : bool;
48 optional_qualifier_iso : bool;
49 value_format_iso : bool;
50 }
51
52 module XMATCH = struct
53
54 (* ------------------------------------------------------------------------*)
55 (* Combinators history *)
56 (* ------------------------------------------------------------------------*)
57 (*
58 * version0:
59 * type ('a, 'b) matcher = 'a -> 'b -> bool
60 *
61 * version1: same but with a global variable holding the current binding
62 * BUT bug
63 * - can have multiple possibilities
64 * - globals sux
65 * - sometimes have to undo, cos if start match, then it binds,
66 * and if later it does not match, then must undo the first binds.
67 * ex: when match parameters, can try to match, but then we found far
68 * later that the last argument of a function does not match
69 * => have to uando the binding !!!
70 * (can handle that too with a global, by saving the
71 * global, ... but sux)
72 * => better not use global
73 *
74 * version2:
75 * type ('a, 'b) matcher = binding -> 'a -> 'b -> binding list
76 *
77 * Empty list mean failure (let matchfailure = []).
78 * To be able to have pretty code, have to use partial application
79 * powa, and so the type is in fact
80 *
81 * version3:
82 * type ('a, 'b) matcher = 'a -> 'b -> binding -> binding list
83 *
84 * Then by defining the correct combinators, can have quite pretty code (that
85 * looks like the clean code of version0).
86 *
87 * opti: return a lazy list of possible matchs ?
88 *
89 * version4: type tin = Lib_engine.metavars_binding
90 *)
91
92 (* ------------------------------------------------------------------------*)
93 (* Standard type and operators *)
94 (* ------------------------------------------------------------------------*)
95
96 type tin = {
97 extra: xinfo;
98 binding: Lib_engine.metavars_binding;
99 binding0: Lib_engine.metavars_binding; (* inherited bindings *)
100 }
101 (* 'x is a ('a * 'b) but in fact dont care about 'b, we just tag the SP *)
102 (* opti? use set instead of list *)
103 type 'x tout = ('x * Lib_engine.metavars_binding) list
104
105 type ('a, 'b) matcher = 'a -> 'b -> tin -> ('a * 'b) tout
106
107 (* was >&&> *)
108 let (>>=) m1 m2 = fun tin ->
109 let xs = m1 tin in
110 let xxs = xs +> List.map (fun ((a,b), binding) ->
111 m2 a b {tin with binding = binding}
112 ) in
113 List.flatten xxs
114
115 (* Je compare les bindings retournés par les differentes branches.
116 * Si la deuxieme branche amene a des bindings qui sont deja presents
117 * dans la premiere branche, alors je ne les accepte pas.
118 *
119 * update: still useful now that julia better handle Exp directly via
120 * ctl tricks using positions ?
121 *)
122 let (>|+|>) m1 m2 = fun tin ->
123 (* CHOICE
124 let xs = m1 tin in
125 if null xs
126 then m2 tin
127 else xs
128 *)
129 let res1 = m1 tin in
130 let res2 = m2 tin in
131 let list_bindings_already = List.map snd res1 in
132 res1 ++
133 (res2 +> List.filter (fun (x, binding) ->
134 not
135 (list_bindings_already +> List.exists (fun already ->
136 Lib_engine.equal_binding binding already))
137 ))
138
139
140
141
142 let (>||>) m1 m2 = fun tin ->
143 (* CHOICE
144 let xs = m1 tin in
145 if null xs
146 then m2 tin
147 else xs
148 *)
149 (* opti? use set instead of list *)
150 let l1 = m1 tin in
151 let l2 = m2 tin in
152 if l2 = [] then l1 else l1 ++ l2 (*a small benefit; avoid a trivial @*)
153
154
155 let return res = fun tin ->
156 [res, tin.binding]
157
158 let fail = fun tin ->
159 []
160
161 let (>&&>) f m = fun tin ->
162 if f tin
163 then m tin
164 else fail tin
165
166
167 let mode = Cocci_vs_c.PatternMode
168
169 (* ------------------------------------------------------------------------*)
170 (* Exp *)
171 (* ------------------------------------------------------------------------*)
172 let cocciExp = fun expf expa node -> fun tin ->
173
174 let globals = ref [] in
175 let bigf = {
176 (* julia's style *)
177 Visitor_c.default_visitor_c with
178 Visitor_c.kexpr = (fun (k, bigf) expb ->
179 match expf expa expb tin with
180 | [] -> (* failed *) k expb
181 | xs ->
182 globals := xs @ !globals;
183 if not !Flag_engine.disallow_nested_exps then k expb (* CHOICE *)
184 );
185 (* pad's style.
186 * push2 expr globals; k expr
187 * ...
188 * !globals +> List.fold_left (fun acc e -> acc >||> match_e_e expr e)
189 * (return false)
190 *
191 *)
192 }
193 in
194 Visitor_c.vk_node bigf node;
195 !globals +> List.map (fun ((a, _exp), binding) ->
196 (a, node), binding
197 )
198
199 (* same as cocciExp, but for expressions in an expression, not expressions
200 in a node *)
201 let cocciExpExp = fun expf expa expb -> fun tin ->
202
203 let globals = ref [] in
204 let bigf = {
205 (* julia's style *)
206 Visitor_c.default_visitor_c with
207 Visitor_c.kexpr = (fun (k, bigf) expb ->
208 match expf expa expb tin with
209 | [] -> (* failed *) k expb
210 | xs ->
211 globals := xs @ !globals;
212 if not !Flag_engine.disallow_nested_exps then k expb (* CHOICE *)
213 );
214 (* pad's style.
215 * push2 expr globals; k expr
216 * ...
217 * !globals +> List.fold_left (fun acc e -> acc >||> match_e_e expr e)
218 * (return false)
219 *
220 *)
221 }
222 in
223 Visitor_c.vk_expr bigf expb;
224 !globals +> List.map (fun ((a, _exp), binding) ->
225 (a, expb), binding
226 )
227
228 let cocciTy = fun expf expa node -> fun tin ->
229
230 let globals = ref [] in
231 let bigf = {
232 Visitor_c.default_visitor_c with
233 Visitor_c.ktype = (fun (k, bigf) expb ->
234 match expf expa expb tin with
235 | [] -> (* failed *) k expb
236 | xs -> globals := xs @ !globals);
237
238 }
239 in
240 Visitor_c.vk_node bigf node;
241 !globals +> List.map (fun ((a, _exp), binding) ->
242 (a, node), binding
243 )
244
245 let cocciInit = fun expf expa node -> fun tin ->
246
247 let globals = ref [] in
248 let bigf = {
249 Visitor_c.default_visitor_c with
250 Visitor_c.kini = (fun (k, bigf) expb ->
251 match expf expa expb tin with
252 | [] -> (* failed *) k expb
253 | xs -> globals := xs @ !globals);
254
255 }
256 in
257 Visitor_c.vk_node bigf node;
258 !globals +> List.map (fun ((a, _exp), binding) ->
259 (a, node), binding
260 )
261
262
263 (* ------------------------------------------------------------------------*)
264 (* Distribute mcode *)
265 (* ------------------------------------------------------------------------*)
266 let tag_mck_pos mck posmck =
267 match mck with
268 | Ast_cocci.PLUS c -> Ast_cocci.PLUS c
269 | Ast_cocci.CONTEXT (pos, xs) ->
270 assert (pos =*= Ast_cocci.NoPos || pos =*= Ast_cocci.DontCarePos);
271 Ast_cocci.CONTEXT (posmck, xs)
272 | Ast_cocci.MINUS (pos, inst, adj, xs) ->
273 assert (pos =*= Ast_cocci.NoPos || pos =*= Ast_cocci.DontCarePos);
274 Ast_cocci.MINUS (posmck, inst, adj, xs)
275
276
277 let tag_mck_pos_mcode (x,info,mck,pos) posmck stuff = fun tin ->
278 [((x, info, tag_mck_pos mck posmck, pos),stuff), tin.binding]
279
280
281 let distrf (ii_of_x_f) =
282 fun mcode x -> fun tin ->
283 let (max, min) = Lib_parsing_c.max_min_by_pos (ii_of_x_f x)
284 in
285 let posmck = Ast_cocci.FixPos (min, max) (* subtil: and not max, min !!*)
286 in
287 tag_mck_pos_mcode mcode posmck x tin
288
289 let distrf_e = distrf (Lib_parsing_c.ii_of_expr)
290 let distrf_args = distrf (Lib_parsing_c.ii_of_args)
291 let distrf_type = distrf (Lib_parsing_c.ii_of_type)
292 let distrf_param = distrf (Lib_parsing_c.ii_of_param)
293 let distrf_params = distrf (Lib_parsing_c.ii_of_params)
294 let distrf_ini = distrf (Lib_parsing_c.ii_of_ini)
295 let distrf_node = distrf (Lib_parsing_c.ii_of_node)
296 let distrf_struct_fields = distrf (Lib_parsing_c.ii_of_struct_fields)
297 let distrf_cst = distrf (Lib_parsing_c.ii_of_cst)
298 let distrf_define_params = distrf (Lib_parsing_c.ii_of_define_params)
299
300
301 (* ------------------------------------------------------------------------*)
302 (* Constraints on metavariable values *)
303 (* ------------------------------------------------------------------------*)
304 let check_idconstraint matcher c id = fun f tin ->
305 if matcher c id then
306 (* success *)
307 f () tin
308 else
309 (* failure *)
310 fail tin
311
312 let check_constraints_ne matcher constraints exp = fun f tin ->
313 let rec loop = function
314 [] -> f () tin (* success *)
315 | c::cs ->
316 match matcher c exp tin with
317 [] (* failure *) -> loop cs
318 | _ (* success *) -> fail tin in
319 loop constraints
320
321 let check_pos_constraints constraints pvalu f tin =
322 check_constraints_ne
323 (fun c exp tin ->
324 let success = [[]] in
325 let failure = [] in
326 (* relies on the fact that constraints on pos variables must refer to
327 inherited variables *)
328 (match Common.optionise (fun () -> tin.binding0 +> List.assoc c) with
329 Some valu' ->
330 if Cocci_vs_c.equal_inh_metavarval exp valu'
331 then success else failure
332 | None ->
333 (* if the variable is not there, it puts no constraints *)
334 (* not sure this is still useful *)
335 failure))
336 constraints pvalu f tin
337
338 (* ------------------------------------------------------------------------*)
339 (* Environment *)
340 (* ------------------------------------------------------------------------*)
341 (* pre: if have declared a new metavar that hide another one, then
342 * must be passed with a binding that deleted this metavar
343 *
344 * Here we dont use the keep argument of julia. cf f(X,X), J'ai
345 * besoin de garder le X en interne, meme si julia s'en fout elle du
346 * X et qu'elle a mis X a DontSaved.
347 *)
348 let check_add_metavars_binding strip _keep inherited = fun (k, valu) tin ->
349 if inherited
350 then
351 match Common.optionise (fun () -> tin.binding0 +> List.assoc k) with
352 | Some (valu') ->
353 if Cocci_vs_c.equal_inh_metavarval valu valu'
354 then Some tin.binding
355 else None
356 | None -> None
357 else
358 match Common.optionise (fun () -> tin.binding +> List.assoc k) with
359 | Some (valu') ->
360 if Cocci_vs_c.equal_metavarval valu valu'
361 then Some tin.binding
362 else None
363
364 | None ->
365 let valu' =
366 match valu with
367 Ast_c.MetaIdVal a -> Ast_c.MetaIdVal a
368 | Ast_c.MetaFuncVal a -> Ast_c.MetaFuncVal a
369 | Ast_c.MetaLocalFuncVal a -> Ast_c.MetaLocalFuncVal a (*more?*)
370 | Ast_c.MetaExprVal a ->
371 Ast_c.MetaExprVal
372 (if strip
373 then Lib_parsing_c.al_expr a
374 else Lib_parsing_c.semi_al_expr a)
375 | Ast_c.MetaExprListVal a ->
376 Ast_c.MetaExprListVal
377 (if strip
378 then Lib_parsing_c.al_arguments a
379 else Lib_parsing_c.semi_al_arguments a)
380
381 | Ast_c.MetaStmtVal a ->
382 Ast_c.MetaStmtVal
383 (if strip
384 then Lib_parsing_c.al_statement a
385 else Lib_parsing_c.semi_al_statement a)
386 | Ast_c.MetaTypeVal a ->
387 Ast_c.MetaTypeVal
388 (if strip
389 then Lib_parsing_c.al_type a
390 else Lib_parsing_c.semi_al_type a)
391
392 | Ast_c.MetaInitVal a ->
393 Ast_c.MetaInitVal
394 (if strip
395 then Lib_parsing_c.al_init a
396 else Lib_parsing_c.semi_al_init a)
397
398 | Ast_c.MetaListlenVal a -> Ast_c.MetaListlenVal a
399
400 | Ast_c.MetaParamVal a -> failwith "not handling MetaParamVal"
401 | Ast_c.MetaParamListVal a ->
402 Ast_c.MetaParamListVal
403 (if strip
404 then Lib_parsing_c.al_params a
405 else Lib_parsing_c.semi_al_params a)
406
407 | Ast_c.MetaPosVal (pos1,pos2) -> Ast_c.MetaPosVal (pos1,pos2)
408 | Ast_c.MetaPosValList l -> Ast_c.MetaPosValList l
409 in Some (tin.binding +> Common.insert_assoc (k, valu'))
410
411 let envf keep inherited = fun (k, valu, get_max_min) f tin ->
412 let x = Ast_cocci.unwrap_mcode k in
413 match check_add_metavars_binding true keep inherited (x, valu) tin with
414 | Some binding ->
415 let new_tin = {tin with binding = binding} in
416 (match Ast_cocci.get_pos_var k with
417 Ast_cocci.MetaPos(name,constraints,per,keep,inherited) ->
418 let pvalu =
419 let (file,current_element,min,max) = get_max_min() in
420 Ast_c.MetaPosValList[(file,current_element,min,max)] in
421 (* check constraints. success means that there is a match with
422 one of the constraints, which will ultimately result in
423 failure. *)
424 check_pos_constraints constraints pvalu
425 (function () ->
426 (* constraints are satisfied, now see if we are compatible
427 with existing bindings *)
428 function new_tin ->
429 let x = Ast_cocci.unwrap_mcode name in
430 (match
431 check_add_metavars_binding false keep inherited (x, pvalu)
432 new_tin with
433 | Some binding ->
434 f () {new_tin with binding = binding}
435 | None -> fail tin))
436 new_tin
437 | Ast_cocci.NoMetaPos -> f () new_tin)
438 | None -> fail tin
439
440 (* ------------------------------------------------------------------------*)
441 (* Environment, allbounds *)
442 (* ------------------------------------------------------------------------*)
443 (* all referenced inherited variables have to be bound. This would
444 * be naturally checked for the minus or context ones in the
445 * matching process, but have to check the plus ones as well. The
446 * result of get_inherited contains all of these, but the potential
447 * redundant checking for the minus and context ones is probably not
448 * a big deal. If it's a problem, could fix free_vars to distinguish
449 * between + variables and the other ones. *)
450
451 let (all_bound : Ast_cocci.meta_name list -> tin -> bool) = fun l tin ->
452 l +> List.for_all (fun inhvar ->
453 match Common.optionise (fun () -> tin.binding0 +> List.assoc inhvar) with
454 | Some _ -> true
455 | None -> false
456 )
457
458 let optional_storage_flag f = fun tin ->
459 f (tin.extra.optional_storage_iso) tin
460
461 let optional_qualifier_flag f = fun tin ->
462 f (tin.extra.optional_qualifier_iso) tin
463
464 let value_format_flag f = fun tin ->
465 f (tin.extra.value_format_iso) tin
466
467
468 (* ------------------------------------------------------------------------*)
469 (* Tokens *)
470 (* ------------------------------------------------------------------------*)
471 let tokenf ia ib = fun tin ->
472 let pos = Ast_c.info_to_fixpos ib in
473 let posmck = Ast_cocci.FixPos (pos, pos) in
474 let finish tin = tag_mck_pos_mcode ia posmck ib tin in
475 match Ast_cocci.get_pos_var ia with
476 Ast_cocci.MetaPos(name,constraints,per,keep,inherited) ->
477 let mpos = Lib_parsing_c.lin_col_by_pos [ib] in
478 let pvalu = Ast_c.MetaPosValList [mpos] in
479 check_pos_constraints constraints pvalu
480 (function () ->
481 (* constraints are satisfied, now see if we are compatible
482 with existing bindings *)
483 function new_tin ->
484 let x = Ast_cocci.unwrap_mcode name in
485 (match
486 check_add_metavars_binding false keep inherited (x, pvalu) tin
487 with
488 Some binding -> finish {tin with binding = binding}
489 | None -> fail tin))
490 tin
491 | _ -> finish tin
492
493 let tokenf_mck mck ib = fun tin ->
494 let pos = Ast_c.info_to_fixpos ib in
495 let posmck = Ast_cocci.FixPos (pos, pos) in
496 [(tag_mck_pos mck posmck, ib), tin.binding]
497
498 end
499
500 (*****************************************************************************)
501 (* Entry point *)
502 (*****************************************************************************)
503 module MATCH = Cocci_vs_c.COCCI_VS_C (XMATCH)
504
505
506 let match_re_node2 dropped_isos a b binding0 =
507
508 let tin = {
509 XMATCH.extra = {
510 optional_storage_iso = not(List.mem "optional_storage" dropped_isos);
511 optional_qualifier_iso = not(List.mem "optional_qualifier" dropped_isos);
512 value_format_iso = not(List.mem "value_format" dropped_isos);
513 };
514 XMATCH.binding = [];
515 XMATCH.binding0 = binding0;
516 } in
517
518 MATCH.rule_elem_node a b tin
519 (* take only the tagged-SP, the 'a' *)
520 +> List.map (fun ((a,_b), binding) -> a, binding)
521
522
523 let match_re_node a b c d =
524 Common.profile_code "Pattern3.match_re_node"
525 (fun () -> match_re_node2 a b c d)