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