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