Release coccinelle-0.2.4
[bpt/coccinelle.git] / parsing_cocci / iso_pattern.ml
1 (*
2 * Copyright 2010, INRIA, University of Copenhagen
3 * Julia Lawall, Rene Rydhof Hansen, Gilles Muller, Nicolas Palix
4 * Copyright 2005-2009, Ecole des Mines de Nantes, University of Copenhagen
5 * Yoann Padioleau, Julia Lawall, Rene Rydhof Hansen, Henrik Stuart, Gilles Muller, Nicolas Palix
6 * This file is part of Coccinelle.
7 *
8 * Coccinelle is free software: you can redistribute it and/or modify
9 * it under the terms of the GNU General Public License as published by
10 * the Free Software Foundation, according to version 2 of the License.
11 *
12 * Coccinelle is distributed in the hope that it will be useful,
13 * but WITHOUT ANY WARRANTY; without even the implied warranty of
14 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
15 * GNU General Public License for more details.
16 *
17 * You should have received a copy of the GNU General Public License
18 * along with Coccinelle. If not, see <http://www.gnu.org/licenses/>.
19 *
20 * The authors reserve the right to distribute this or future versions of
21 * Coccinelle under other licenses.
22 *)
23
24
25 (*
26 * Copyright 2010, INRIA, University of Copenhagen
27 * Julia Lawall, Rene Rydhof Hansen, Gilles Muller, Nicolas Palix
28 * Copyright 2005-2009, Ecole des Mines de Nantes, University of Copenhagen
29 * Yoann Padioleau, Julia Lawall, Rene Rydhof Hansen, Henrik Stuart, Gilles Muller, Nicolas Palix
30 * This file is part of Coccinelle.
31 *
32 * Coccinelle is free software: you can redistribute it and/or modify
33 * it under the terms of the GNU General Public License as published by
34 * the Free Software Foundation, according to version 2 of the License.
35 *
36 * Coccinelle is distributed in the hope that it will be useful,
37 * but WITHOUT ANY WARRANTY; without even the implied warranty of
38 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
39 * GNU General Public License for more details.
40 *
41 * You should have received a copy of the GNU General Public License
42 * along with Coccinelle. If not, see <http://www.gnu.org/licenses/>.
43 *
44 * The authors reserve the right to distribute this or future versions of
45 * Coccinelle under other licenses.
46 *)
47
48
49 (* Potential problem: offset of mcode is not updated when an iso is
50 instantiated, implying that a term may end up with many mcodes with the
51 same offset. On the other hand, at the moment offset only seems to be used
52 before this phase. Furthermore add_dot_binding relies on the offset to
53 remain the same between matching an iso and instantiating it with bindings. *)
54
55 (* Consider whether ... in iso should match <... ...> in smpl? *)
56
57 (* --------------------------------------------------------------------- *)
58 (* match a SmPL expression against a SmPL abstract syntax tree,
59 either - or + *)
60
61 module Ast = Ast_cocci
62 module Ast0 = Ast0_cocci
63 module V0 = Visitor_ast0
64 module VT0 = Visitor_ast0_types
65
66 let current_rule = ref ""
67
68 (* --------------------------------------------------------------------- *)
69
70 type isomorphism =
71 Ast_cocci.metavar list * Ast0_cocci.anything list list * string (* name *)
72
73 let strip_info =
74 let mcode (term,_,_,_,_,_) =
75 (term,Ast0.NONE,Ast0.default_info(),Ast0.PLUS Ast.ONE,
76 ref Ast0.NoMetaPos,-1) in
77 let donothing r k e =
78 let x = k e in
79 {(Ast0.wrap (Ast0.unwrap x)) with
80 Ast0.mcodekind = ref (Ast0.PLUS Ast.ONE);
81 Ast0.true_if_test = x.Ast0.true_if_test} in
82 V0.flat_rebuilder
83 mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode
84 donothing donothing donothing donothing donothing donothing
85 donothing donothing donothing donothing donothing donothing donothing
86 donothing donothing
87
88 let anything_equal = function
89 (Ast0.DotsExprTag(d1),Ast0.DotsExprTag(d2)) ->
90 failwith "not a possible variable binding" (*not sure why these are pbs*)
91 | (Ast0.DotsInitTag(d1),Ast0.DotsInitTag(d2)) ->
92 failwith "not a possible variable binding"
93 | (Ast0.DotsParamTag(d1),Ast0.DotsParamTag(d2)) ->
94 failwith "not a possible variable binding"
95 | (Ast0.DotsStmtTag(d1),Ast0.DotsStmtTag(d2)) ->
96 (strip_info.VT0.rebuilder_rec_statement_dots d1) =
97 (strip_info.VT0.rebuilder_rec_statement_dots d2)
98 | (Ast0.DotsDeclTag(d1),Ast0.DotsDeclTag(d2)) ->
99 failwith "not a possible variable binding"
100 | (Ast0.DotsCaseTag(d1),Ast0.DotsCaseTag(d2)) ->
101 failwith "not a possible variable binding"
102 | (Ast0.IdentTag(d1),Ast0.IdentTag(d2)) ->
103 (strip_info.VT0.rebuilder_rec_ident d1) =
104 (strip_info.VT0.rebuilder_rec_ident d2)
105 | (Ast0.ExprTag(d1),Ast0.ExprTag(d2)) ->
106 (strip_info.VT0.rebuilder_rec_expression d1) =
107 (strip_info.VT0.rebuilder_rec_expression d2)
108 | (Ast0.ArgExprTag(_),_) | (_,Ast0.ArgExprTag(_)) ->
109 failwith "not possible - only in isos1"
110 | (Ast0.TestExprTag(_),_) | (_,Ast0.TestExprTag(_)) ->
111 failwith "not possible - only in isos1"
112 | (Ast0.TypeCTag(d1),Ast0.TypeCTag(d2)) ->
113 (strip_info.VT0.rebuilder_rec_typeC d1) =
114 (strip_info.VT0.rebuilder_rec_typeC d2)
115 | (Ast0.InitTag(d1),Ast0.InitTag(d2)) ->
116 (strip_info.VT0.rebuilder_rec_initialiser d1) =
117 (strip_info.VT0.rebuilder_rec_initialiser d2)
118 | (Ast0.ParamTag(d1),Ast0.ParamTag(d2)) ->
119 (strip_info.VT0.rebuilder_rec_parameter d1) =
120 (strip_info.VT0.rebuilder_rec_parameter d2)
121 | (Ast0.DeclTag(d1),Ast0.DeclTag(d2)) ->
122 (strip_info.VT0.rebuilder_rec_declaration d1) =
123 (strip_info.VT0.rebuilder_rec_declaration d2)
124 | (Ast0.StmtTag(d1),Ast0.StmtTag(d2)) ->
125 (strip_info.VT0.rebuilder_rec_statement d1) =
126 (strip_info.VT0.rebuilder_rec_statement d2)
127 | (Ast0.CaseLineTag(d1),Ast0.CaseLineTag(d2)) ->
128 (strip_info.VT0.rebuilder_rec_case_line d1) =
129 (strip_info.VT0.rebuilder_rec_case_line d2)
130 | (Ast0.TopTag(d1),Ast0.TopTag(d2)) ->
131 (strip_info.VT0.rebuilder_rec_top_level d1) =
132 (strip_info.VT0.rebuilder_rec_top_level d2)
133 | (Ast0.IsoWhenTTag(_),_) | (_,Ast0.IsoWhenTTag(_)) ->
134 failwith "only for isos within iso phase"
135 | (Ast0.IsoWhenFTag(_),_) | (_,Ast0.IsoWhenFTag(_)) ->
136 failwith "only for isos within iso phase"
137 | (Ast0.IsoWhenTag(_),_) | (_,Ast0.IsoWhenTag(_)) ->
138 failwith "only for isos within iso phase"
139 | _ -> false
140
141 let term (var1,_,_,_,_,_) = var1
142 let dot_term (var1,_,info,_,_,_) =
143 ("", var1 ^ (string_of_int info.Ast0.pos_info.Ast0.offset))
144
145
146 type reason =
147 NotPure of Ast0.pure * Ast.meta_name * Ast0.anything
148 | NotPureLength of Ast.meta_name
149 | ContextRequired of Ast0.anything
150 | NonMatch
151 | Braces of Ast0.statement
152 | Nest of Ast0.statement
153 | Position of Ast.meta_name
154 | TypeMatch of reason list
155
156 let rec interpret_reason name line reason printer =
157 Printf.printf
158 "warning: iso %s does not match the code below on line %d\n" name line;
159 printer(); Format.print_newline();
160 match reason with
161 NotPure(Ast0.Pure,(_,var),nonpure) ->
162 Printf.printf
163 "pure metavariable %s is matched against the following nonpure code:\n"
164 var;
165 Unparse_ast0.unparse_anything nonpure
166 | NotPure(Ast0.Context,(_,var),nonpure) ->
167 Printf.printf
168 "context metavariable %s is matched against the following\nnoncontext code:\n"
169 var;
170 Unparse_ast0.unparse_anything nonpure
171 | NotPure(Ast0.PureContext,(_,var),nonpure) ->
172 Printf.printf
173 "pure context metavariable %s is matched against the following\nnonpure or noncontext code:\n"
174 var;
175 Unparse_ast0.unparse_anything nonpure
176 | NotPureLength((_,var)) ->
177 Printf.printf
178 "pure metavariable %s is matched against too much or too little code\n"
179 var;
180 | ContextRequired(term) ->
181 Printf.printf
182 "the following code matched is not uniformly minus or context,\nor contains a disjunction:\n";
183 Unparse_ast0.unparse_anything term
184 | Braces(s) ->
185 Printf.printf "braces must be all minus (plus code allowed) or all\ncontext (plus code not allowed in the body) to match:\n";
186 Unparse_ast0.statement "" s;
187 Format.print_newline()
188 | Nest(s) ->
189 Printf.printf "iso with nest doesn't match whencode (TODO):\n";
190 Unparse_ast0.statement "" s;
191 Format.print_newline()
192 | Position(rule,name) ->
193 Printf.printf "position variable %s.%s conflicts with an isomorphism\n"
194 rule name;
195 | TypeMatch reason_list ->
196 List.iter (function r -> interpret_reason name line r printer)
197 reason_list
198 | _ -> failwith "not possible"
199
200 type 'a either = OK of 'a | Fail of reason
201
202 let add_binding var exp bindings =
203 let var = term var in
204 let attempt bindings =
205 try
206 let cur = List.assoc var bindings in
207 if anything_equal(exp,cur) then [bindings] else []
208 with Not_found -> [((var,exp)::bindings)] in
209 match List.concat(List.map attempt bindings) with
210 [] -> Fail NonMatch
211 | x -> OK x
212
213 let add_dot_binding var exp bindings =
214 let var = dot_term var in
215 let attempt bindings =
216 try
217 let cur = List.assoc var bindings in
218 if anything_equal(exp,cur) then [bindings] else []
219 with Not_found -> [((var,exp)::bindings)] in
220 match List.concat(List.map attempt bindings) with
221 [] -> Fail NonMatch
222 | x -> OK x
223
224 (* multi-valued *)
225 let add_multi_dot_binding var exp bindings =
226 let var = dot_term var in
227 let attempt bindings = [((var,exp)::bindings)] in
228 match List.concat(List.map attempt bindings) with
229 [] -> Fail NonMatch
230 | x -> OK x
231
232 let rec nub ls =
233 match ls with
234 [] -> []
235 | (x::xs) when (List.mem x xs) -> nub xs
236 | (x::xs) -> x::(nub xs)
237
238 (* --------------------------------------------------------------------- *)
239
240 let init_env = [[]]
241
242 let debug str m binding =
243 let res = m binding in
244 (match res with
245 None -> Printf.printf "%s: failed\n" str
246 | Some binding ->
247 List.iter
248 (function binding ->
249 Printf.printf "%s: %s\n" str
250 (String.concat " " (List.map (function (x,_) -> x) binding)))
251 binding);
252 res
253
254 let conjunct_bindings
255 (m1 : 'binding -> 'binding either)
256 (m2 : 'binding -> 'binding either)
257 (binding : 'binding) : 'binding either =
258 match m1 binding with Fail(reason) -> Fail(reason) | OK binding -> m2 binding
259
260 let rec conjunct_many_bindings = function
261 [] -> failwith "not possible"
262 | [x] -> x
263 | x::xs -> conjunct_bindings x (conjunct_many_bindings xs)
264
265 let mcode_equal (x,_,_,_,_,_) (y,_,_,_,_,_) = x = y
266
267 let return b binding = if b then OK binding else Fail NonMatch
268 let return_false reason binding = Fail reason
269
270 let match_option f t1 t2 =
271 match (t1,t2) with
272 (Some t1, Some t2) -> f t1 t2
273 | (None, None) -> return true
274 | _ -> return false
275
276 let bool_match_option f t1 t2 =
277 match (t1,t2) with
278 (Some t1, Some t2) -> f t1 t2
279 | (None, None) -> true
280 | _ -> false
281
282 (* context_required is for the example
283 if (
284 + (int * )
285 x == NULL)
286 where we can't change x == NULL to eg NULL == x. So there can either be
287 nothing attached to the root or the term has to be all removed.
288 if would be nice if we knew more about the relationship between the - and +
289 code, because in the case where the + code is a separate statement in a
290 sequence, this is not a problem. Perhaps something could be done in
291 insert_plus
292
293 The example seems strange. Why isn't the cast attached to x?
294 *)
295 let is_context e =
296 !Flag.sgrep_mode2 or (* everything is context for sgrep *)
297 (match Ast0.get_mcodekind e with
298 Ast0.CONTEXT(cell) -> true
299 | _ -> false)
300
301 (* needs a special case when there is a Disj or an empty DOTS
302 the following stops at the statement level, and gives true if one
303 statement is replaced by another *)
304 let rec is_pure_context s =
305 !Flag.sgrep_mode2 or (* everything is context for sgrep *)
306 (match Ast0.unwrap s with
307 Ast0.Disj(starter,statement_dots_list,mids,ender) ->
308 List.for_all
309 (function x ->
310 match Ast0.undots x with
311 [s] -> is_pure_context s
312 | _ -> false (* could we do better? *))
313 statement_dots_list
314 | _ ->
315 (match Ast0.get_mcodekind s with
316 Ast0.CONTEXT(mc) ->
317 (match !mc with
318 (Ast.NOTHING,_,_) -> true
319 | _ -> false)
320 | Ast0.MINUS(mc) ->
321 (match !mc with
322 (* do better for the common case of replacing a stmt by another one *)
323 ([[Ast.StatementTag(s)]],_) ->
324 (match Ast.unwrap s with
325 Ast.IfThen(_,_,_) -> false (* potentially dangerous *)
326 | _ -> true)
327 | (_,_) -> false)
328 | _ -> false))
329
330 let is_minus e =
331 match Ast0.get_mcodekind e with Ast0.MINUS(cell) -> true | _ -> false
332
333 let match_list matcher is_list_matcher do_list_match la lb =
334 let rec loop = function
335 ([],[]) -> return true
336 | ([x],lb) when is_list_matcher x -> do_list_match x lb
337 | (x::xs,y::ys) -> conjunct_bindings (matcher x y) (loop (xs,ys))
338 | _ -> return false in
339 loop (la,lb)
340
341 let all_caps = Str.regexp "^[A-Z_][A-Z_0-9]*$"
342
343 let match_maker checks_needed context_required whencode_allowed =
344
345 let check_mcode pmc cmc binding =
346 if checks_needed
347 then
348 match Ast0.get_pos cmc with
349 (Ast0.MetaPos (name,_,_)) as x ->
350 (match Ast0.get_pos pmc with
351 Ast0.MetaPos (name1,_,_) ->
352 add_binding name1 (Ast0.MetaPosTag x) binding
353 | Ast0.NoMetaPos ->
354 let (rule,name) = Ast0.unwrap_mcode name in
355 Fail (Position(rule,name)))
356 | Ast0.NoMetaPos -> OK binding
357 else OK binding in
358
359 let match_dots matcher is_list_matcher do_list_match d1 d2 =
360 match (Ast0.unwrap d1, Ast0.unwrap d2) with
361 (Ast0.DOTS(la),Ast0.DOTS(lb))
362 | (Ast0.CIRCLES(la),Ast0.CIRCLES(lb))
363 | (Ast0.STARS(la),Ast0.STARS(lb)) ->
364 match_list matcher is_list_matcher (do_list_match d2) la lb
365 | _ -> return false in
366
367 let is_elist_matcher el =
368 match Ast0.unwrap el with Ast0.MetaExprList(_,_,_) -> true | _ -> false in
369
370 let is_plist_matcher pl =
371 match Ast0.unwrap pl with Ast0.MetaParamList(_,_,_) -> true | _ -> false in
372
373 let is_slist_matcher pl =
374 match Ast0.unwrap pl with Ast0.MetaStmtList(_,_) -> true | _ -> false in
375
376 let no_list _ = false in
377
378 let build_dots pattern data =
379 match Ast0.unwrap pattern with
380 Ast0.DOTS(_) -> Ast0.rewrap pattern (Ast0.DOTS(data))
381 | Ast0.CIRCLES(_) -> Ast0.rewrap pattern (Ast0.CIRCLES(data))
382 | Ast0.STARS(_) -> Ast0.rewrap pattern (Ast0.STARS(data)) in
383
384 let pure_sp_code =
385 let bind = Ast0.lub_pure in
386 let option_default = Ast0.Context in
387 let pure_mcodekind mc =
388 if !Flag.sgrep_mode2
389 then Ast0.PureContext
390 else
391 match mc with
392 Ast0.CONTEXT(mc) ->
393 (match !mc with
394 (Ast.NOTHING,_,_) -> Ast0.PureContext
395 | _ -> Ast0.Context)
396 | Ast0.MINUS(mc) ->
397 (match !mc with ([],_) -> Ast0.Pure | _ -> Ast0.Impure)
398 | _ -> Ast0.Impure in
399 let donothing r k e =
400 bind (pure_mcodekind (Ast0.get_mcodekind e)) (k e) in
401
402 let mcode m = pure_mcodekind (Ast0.get_mcode_mcodekind m) in
403
404 (* a case for everything that has a metavariable *)
405 (* pure is supposed to match only unitary metavars, not anything that
406 contains only unitary metavars *)
407 let ident r k i =
408 bind (bind (pure_mcodekind (Ast0.get_mcodekind i)) (k i))
409 (match Ast0.unwrap i with
410 Ast0.MetaId(name,_,pure) | Ast0.MetaFunc(name,_,pure)
411 | Ast0.MetaLocalFunc(name,_,pure) -> pure
412 | _ -> Ast0.Impure) in
413
414 let expression r k e =
415 bind (bind (pure_mcodekind (Ast0.get_mcodekind e)) (k e))
416 (match Ast0.unwrap e with
417 Ast0.MetaErr(name,_,pure)
418 | Ast0.MetaExpr(name,_,_,_,pure) | Ast0.MetaExprList(name,_,pure) ->
419 pure
420 | _ -> Ast0.Impure) in
421
422 let typeC r k t =
423 bind (bind (pure_mcodekind (Ast0.get_mcodekind t)) (k t))
424 (match Ast0.unwrap t with
425 Ast0.MetaType(name,pure) -> pure
426 | _ -> Ast0.Impure) in
427
428 let init r k t =
429 bind (bind (pure_mcodekind (Ast0.get_mcodekind t)) (k t))
430 (match Ast0.unwrap t with
431 Ast0.MetaInit(name,pure) -> pure
432 | _ -> Ast0.Impure) in
433
434 let param r k p =
435 bind (bind (pure_mcodekind (Ast0.get_mcodekind p)) (k p))
436 (match Ast0.unwrap p with
437 Ast0.MetaParam(name,pure) | Ast0.MetaParamList(name,_,pure) -> pure
438 | _ -> Ast0.Impure) in
439
440 let decl r k d =
441 bind (bind (pure_mcodekind (Ast0.get_mcodekind d)) (k d))
442 (match Ast0.unwrap d with
443 Ast0.MetaDecl(name,pure) | Ast0.MetaField(name,pure) -> pure
444 | _ -> Ast0.Impure) in
445
446 let stmt r k s =
447 bind (bind (pure_mcodekind (Ast0.get_mcodekind s)) (k s))
448 (match Ast0.unwrap s with
449 Ast0.MetaStmt(name,pure) | Ast0.MetaStmtList(name,pure) -> pure
450 | _ -> Ast0.Impure) in
451
452 V0.flat_combiner bind option_default
453 mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode
454 donothing donothing donothing donothing donothing donothing
455 ident expression typeC init param decl stmt donothing
456 donothing in
457
458 let add_pure_list_binding name pure is_pure builder1 builder2 lst =
459 match (checks_needed,pure) with
460 (true,Ast0.Pure) | (true,Ast0.Context) | (true,Ast0.PureContext) ->
461 (match lst with
462 [x] ->
463 if (Ast0.lub_pure (is_pure x) pure) = pure
464 then add_binding name (builder1 lst)
465 else return_false (NotPure (pure,term name,builder1 lst))
466 | _ -> return_false (NotPureLength (term name)))
467 | (false,_) | (_,Ast0.Impure) -> add_binding name (builder2 lst) in
468
469 let add_pure_binding name pure is_pure builder x =
470 match (checks_needed,pure) with
471 (true,Ast0.Pure) | (true,Ast0.Context) | (true,Ast0.PureContext) ->
472 if (Ast0.lub_pure (is_pure x) pure) = pure
473 then add_binding name (builder x)
474 else return_false (NotPure (pure,term name, builder x))
475 | (false,_) | (_,Ast0.Impure) -> add_binding name (builder x) in
476
477 let do_elist_match builder el lst =
478 match Ast0.unwrap el with
479 Ast0.MetaExprList(name,lenname,pure) ->
480 (*how to handle lenname? should it be an option type and always None?*)
481 failwith "expr list pattern not supported in iso"
482 (*add_pure_list_binding name pure
483 pure_sp_code.V0.combiner_expression
484 (function lst -> Ast0.ExprTag(List.hd lst))
485 (function lst -> Ast0.DotsExprTag(build_dots builder lst))
486 lst*)
487 | _ -> failwith "not possible" in
488
489 let do_plist_match builder pl lst =
490 match Ast0.unwrap pl with
491 Ast0.MetaParamList(name,lename,pure) ->
492 failwith "param list pattern not supported in iso"
493 (*add_pure_list_binding name pure
494 pure_sp_code.V0.combiner_parameter
495 (function lst -> Ast0.ParamTag(List.hd lst))
496 (function lst -> Ast0.DotsParamTag(build_dots builder lst))
497 lst*)
498 | _ -> failwith "not possible" in
499
500 let do_slist_match builder sl lst =
501 match Ast0.unwrap sl with
502 Ast0.MetaStmtList(name,pure) ->
503 add_pure_list_binding name pure
504 pure_sp_code.VT0.combiner_rec_statement
505 (function lst -> Ast0.StmtTag(List.hd lst))
506 (function lst -> Ast0.DotsStmtTag(build_dots builder lst))
507 lst
508 | _ -> failwith "not possible" in
509
510 let do_nolist_match _ _ = failwith "not possible" in
511
512 let rec match_ident pattern id =
513 match Ast0.unwrap pattern with
514 Ast0.MetaId(name,_,pure) ->
515 (add_pure_binding name pure pure_sp_code.VT0.combiner_rec_ident
516 (function id -> Ast0.IdentTag id) id)
517 | Ast0.MetaFunc(name,_,pure) -> failwith "metafunc not supported"
518 | Ast0.MetaLocalFunc(name,_,pure) -> failwith "metalocalfunc not supported"
519 | up ->
520 if not(checks_needed) or not(context_required) or is_context id
521 then
522 match (up,Ast0.unwrap id) with
523 (Ast0.Id(namea),Ast0.Id(nameb)) ->
524 if mcode_equal namea nameb
525 then check_mcode namea nameb
526 else return false
527 | (Ast0.OptIdent(ida),Ast0.OptIdent(idb))
528 | (Ast0.UniqueIdent(ida),Ast0.UniqueIdent(idb)) ->
529 match_ident ida idb
530 | (_,Ast0.OptIdent(idb))
531 | (_,Ast0.UniqueIdent(idb)) -> match_ident pattern idb
532 | _ -> return false
533 else return_false (ContextRequired (Ast0.IdentTag id)) in
534
535 (* should we do something about matching metavars against ...? *)
536 let rec match_expr pattern expr =
537 match Ast0.unwrap pattern with
538 Ast0.MetaExpr(name,_,ty,form,pure) ->
539 let form_ok =
540 match (form,expr) with
541 (Ast.ANY,_) -> true
542 | (Ast.CONST,e) ->
543 let rec matches e =
544 match Ast0.unwrap e with
545 Ast0.Constant(c) -> true
546 | Ast0.Ident(c) ->
547 (match Ast0.unwrap c with
548 Ast0.Id(nm) ->
549 let nm = Ast0.unwrap_mcode nm in
550 (* all caps is a const *)
551 Str.string_match all_caps nm 0
552 | _ -> false)
553 | Ast0.Cast(lp,ty,rp,e) -> matches e
554 | Ast0.SizeOfExpr(se,exp) -> true
555 | Ast0.SizeOfType(se,lp,ty,rp) -> true
556 | Ast0.MetaExpr(nm,_,_,Ast.CONST,p) ->
557 (Ast0.lub_pure p pure) = pure
558 | _ -> false in
559 matches e
560 | (Ast.ID,e) | (Ast.LocalID,e) ->
561 let rec matches e =
562 match Ast0.unwrap e with
563 Ast0.Ident(c) -> true
564 | Ast0.Cast(lp,ty,rp,e) -> matches e
565 | Ast0.MetaExpr(nm,_,_,Ast.ID,p) ->
566 (Ast0.lub_pure p pure) = pure
567 | _ -> false in
568 matches e in
569 if form_ok
570 then
571 match ty with
572 Some ts ->
573 if List.exists
574 (function Type_cocci.MetaType(_,_,_) -> true | _ -> false)
575 ts
576 then
577 (match ts with
578 [Type_cocci.MetaType(tyname,_,_)] ->
579 let expty =
580 match (Ast0.unwrap expr,Ast0.get_type expr) with
581 (* easier than updating type inferencer to manage multiple
582 types *)
583 (Ast0.MetaExpr(_,_,Some tts,_,_),_) -> Some tts
584 | (_,Some ty) -> Some [ty]
585 | _ -> None in
586 (match expty with
587 Some expty ->
588 let tyname = Ast0.rewrap_mcode name tyname in
589 conjunct_bindings
590 (add_pure_binding name pure
591 pure_sp_code.VT0.combiner_rec_expression
592 (function expr -> Ast0.ExprTag expr)
593 expr)
594 (function bindings ->
595 let attempts =
596 List.map
597 (function expty ->
598 (try
599 add_pure_binding tyname Ast0.Impure
600 (function _ -> Ast0.Impure)
601 (function ty -> Ast0.TypeCTag ty)
602 (Ast0.rewrap expr
603 (Ast0.reverse_type expty))
604 bindings
605 with Ast0.TyConv ->
606 Printf.printf
607 "warning: unconvertible type";
608 return false bindings))
609 expty in
610 if List.exists
611 (function Fail _ -> false | OK x -> true)
612 attempts
613 then
614 (* not sure why this is ok. can there be more
615 than one OK? *)
616 OK (List.concat
617 (List.map
618 (function Fail _ -> [] | OK x -> x)
619 attempts))
620 else
621 Fail
622 (TypeMatch
623 (List.map
624 (function
625 Fail r -> r
626 | OK x -> failwith "not possible")
627 attempts)))
628 | _ ->
629 (*Printf.printf
630 "warning: type metavar can only match one type";*)
631 return false)
632 | _ ->
633 failwith
634 "mixture of metatype and other types not supported")
635 else
636 let expty = Ast0.get_type expr in
637 if List.exists (function t -> Type_cocci.compatible t expty) ts
638 then
639 add_pure_binding name pure
640 pure_sp_code.VT0.combiner_rec_expression
641 (function expr -> Ast0.ExprTag expr)
642 expr
643 else return false
644 | None ->
645 add_pure_binding name pure
646 pure_sp_code.VT0.combiner_rec_expression
647 (function expr -> Ast0.ExprTag expr)
648 expr
649 else return false
650 | Ast0.MetaErr(namea,_,pure) -> failwith "metaerr not supported"
651 | Ast0.MetaExprList(_,_,_) -> failwith "metaexprlist not supported"
652 | up ->
653 if not(checks_needed) or not(context_required) or is_context expr
654 then
655 match (up,Ast0.unwrap expr) with
656 (Ast0.Ident(ida),Ast0.Ident(idb)) ->
657 match_ident ida idb
658 | (Ast0.Constant(consta),Ast0.Constant(constb)) ->
659 if mcode_equal consta constb
660 then check_mcode consta constb
661 else return false
662 | (Ast0.FunCall(fna,lp1,argsa,rp1),Ast0.FunCall(fnb,lp,argsb,rp)) ->
663 conjunct_many_bindings
664 [check_mcode lp1 lp; check_mcode rp1 rp; match_expr fna fnb;
665 match_dots match_expr is_elist_matcher do_elist_match
666 argsa argsb]
667 | (Ast0.Assignment(lefta,opa,righta,_),
668 Ast0.Assignment(leftb,opb,rightb,_)) ->
669 if mcode_equal opa opb
670 then
671 conjunct_many_bindings
672 [check_mcode opa opb; match_expr lefta leftb;
673 match_expr righta rightb]
674 else return false
675 | (Ast0.CondExpr(exp1a,lp1,exp2a,rp1,exp3a),
676 Ast0.CondExpr(exp1b,lp,exp2b,rp,exp3b)) ->
677 conjunct_many_bindings
678 [check_mcode lp1 lp; check_mcode rp1 rp;
679 match_expr exp1a exp1b; match_option match_expr exp2a exp2b;
680 match_expr exp3a exp3b]
681 | (Ast0.Postfix(expa,opa),Ast0.Postfix(expb,opb)) ->
682 if mcode_equal opa opb
683 then
684 conjunct_bindings (check_mcode opa opb) (match_expr expa expb)
685 else return false
686 | (Ast0.Infix(expa,opa),Ast0.Infix(expb,opb)) ->
687 if mcode_equal opa opb
688 then
689 conjunct_bindings (check_mcode opa opb) (match_expr expa expb)
690 else return false
691 | (Ast0.Unary(expa,opa),Ast0.Unary(expb,opb)) ->
692 if mcode_equal opa opb
693 then
694 conjunct_bindings (check_mcode opa opb) (match_expr expa expb)
695 else return false
696 | (Ast0.Binary(lefta,opa,righta),Ast0.Binary(leftb,opb,rightb)) ->
697 if mcode_equal opa opb
698 then
699 conjunct_many_bindings
700 [check_mcode opa opb; match_expr lefta leftb;
701 match_expr righta rightb]
702 else return false
703 | (Ast0.Paren(lp1,expa,rp1),Ast0.Paren(lp,expb,rp)) ->
704 conjunct_many_bindings
705 [check_mcode lp1 lp; check_mcode rp1 rp; match_expr expa expb]
706 | (Ast0.ArrayAccess(exp1a,lb1,exp2a,rb1),
707 Ast0.ArrayAccess(exp1b,lb,exp2b,rb)) ->
708 conjunct_many_bindings
709 [check_mcode lb1 lb; check_mcode rb1 rb;
710 match_expr exp1a exp1b; match_expr exp2a exp2b]
711 | (Ast0.RecordAccess(expa,opa,fielda),
712 Ast0.RecordAccess(expb,op,fieldb))
713 | (Ast0.RecordPtAccess(expa,opa,fielda),
714 Ast0.RecordPtAccess(expb,op,fieldb)) ->
715 conjunct_many_bindings
716 [check_mcode opa op; match_expr expa expb;
717 match_ident fielda fieldb]
718 | (Ast0.Cast(lp1,tya,rp1,expa),Ast0.Cast(lp,tyb,rp,expb)) ->
719 conjunct_many_bindings
720 [check_mcode lp1 lp; check_mcode rp1 rp;
721 match_typeC tya tyb; match_expr expa expb]
722 | (Ast0.SizeOfExpr(szf1,expa),Ast0.SizeOfExpr(szf,expb)) ->
723 conjunct_bindings (check_mcode szf1 szf) (match_expr expa expb)
724 | (Ast0.SizeOfType(szf1,lp1,tya,rp1),
725 Ast0.SizeOfType(szf,lp,tyb,rp)) ->
726 conjunct_many_bindings
727 [check_mcode lp1 lp; check_mcode rp1 rp;
728 check_mcode szf1 szf; match_typeC tya tyb]
729 | (Ast0.TypeExp(tya),Ast0.TypeExp(tyb)) ->
730 match_typeC tya tyb
731 | (Ast0.EComma(cm1),Ast0.EComma(cm)) -> check_mcode cm1 cm
732 | (Ast0.DisjExpr(_,expsa,_,_),_) ->
733 failwith "not allowed in the pattern of an isomorphism"
734 | (Ast0.NestExpr(_,exp_dotsa,_,_,_),_) ->
735 failwith "not allowed in the pattern of an isomorphism"
736 | (Ast0.Edots(d,None),Ast0.Edots(d1,None))
737 | (Ast0.Ecircles(d,None),Ast0.Ecircles(d1,None))
738 | (Ast0.Estars(d,None),Ast0.Estars(d1,None)) -> check_mcode d d1
739 | (Ast0.Edots(ed,None),Ast0.Edots(ed1,Some wc))
740 | (Ast0.Ecircles(ed,None),Ast0.Ecircles(ed1,Some wc))
741 | (Ast0.Estars(ed,None),Ast0.Estars(ed1,Some wc)) ->
742 (* hope that mcode of edots is unique somehow *)
743 conjunct_bindings (check_mcode ed ed1)
744 (let (edots_whencode_allowed,_,_) = whencode_allowed in
745 if edots_whencode_allowed
746 then add_dot_binding ed (Ast0.ExprTag wc)
747 else
748 (Printf.printf
749 "warning: not applying iso because of whencode";
750 return false))
751 | (Ast0.Edots(_,Some _),_) | (Ast0.Ecircles(_,Some _),_)
752 | (Ast0.Estars(_,Some _),_) ->
753 failwith "whencode not allowed in a pattern1"
754 | (Ast0.OptExp(expa),Ast0.OptExp(expb))
755 | (Ast0.UniqueExp(expa),Ast0.UniqueExp(expb)) -> match_expr expa expb
756 | (_,Ast0.OptExp(expb))
757 | (_,Ast0.UniqueExp(expb)) -> match_expr pattern expb
758 | _ -> return false
759 else return_false (ContextRequired (Ast0.ExprTag expr))
760
761 (* the special case for function types prevents the eg T X; -> T X = E; iso
762 from applying, which doesn't seem very relevant, but it also avoids a
763 mysterious bug that is obtained with eg int attach(...); *)
764 and match_typeC pattern t =
765 match Ast0.unwrap pattern with
766 Ast0.MetaType(name,pure) ->
767 (match Ast0.unwrap t with
768 Ast0.FunctionType(tya,lp1a,paramsa,rp1a) -> return false
769 | _ ->
770 add_pure_binding name pure pure_sp_code.VT0.combiner_rec_typeC
771 (function ty -> Ast0.TypeCTag ty)
772 t)
773 | up ->
774 if not(checks_needed) or not(context_required) or is_context t
775 then
776 match (up,Ast0.unwrap t) with
777 (Ast0.ConstVol(cva,tya),Ast0.ConstVol(cvb,tyb)) ->
778 if mcode_equal cva cvb
779 then
780 conjunct_bindings (check_mcode cva cvb) (match_typeC tya tyb)
781 else return false
782 | (Ast0.BaseType(tya,stringsa),Ast0.BaseType(tyb,stringsb)) ->
783 if tya = tyb
784 then
785 match_list check_mcode
786 (function _ -> false) (function _ -> failwith "")
787 stringsa stringsb
788 else return false
789 | (Ast0.Signed(signa,tya),Ast0.Signed(signb,tyb)) ->
790 if mcode_equal signa signb
791 then
792 conjunct_bindings (check_mcode signa signb)
793 (match_option match_typeC tya tyb)
794 else return false
795 | (Ast0.Pointer(tya,star1),Ast0.Pointer(tyb,star)) ->
796 conjunct_bindings (check_mcode star1 star) (match_typeC tya tyb)
797 | (Ast0.FunctionPointer(tya,lp1a,stara,rp1a,lp2a,paramsa,rp2a),
798 Ast0.FunctionPointer(tyb,lp1b,starb,rp1b,lp2b,paramsb,rp2b)) ->
799 conjunct_many_bindings
800 [check_mcode stara starb; check_mcode lp1a lp1b;
801 check_mcode rp1a rp1b; check_mcode lp2a lp2b;
802 check_mcode rp2a rp2b; match_typeC tya tyb;
803 match_dots match_param is_plist_matcher
804 do_plist_match paramsa paramsb]
805 | (Ast0.FunctionType(tya,lp1a,paramsa,rp1a),
806 Ast0.FunctionType(tyb,lp1b,paramsb,rp1b)) ->
807 conjunct_many_bindings
808 [check_mcode lp1a lp1b; check_mcode rp1a rp1b;
809 match_option match_typeC tya tyb;
810 match_dots match_param is_plist_matcher do_plist_match
811 paramsa paramsb]
812 | (Ast0.Array(tya,lb1,sizea,rb1),Ast0.Array(tyb,lb,sizeb,rb)) ->
813 conjunct_many_bindings
814 [check_mcode lb1 lb; check_mcode rb1 rb;
815 match_typeC tya tyb; match_option match_expr sizea sizeb]
816 | (Ast0.EnumName(kinda,Some namea),
817 Ast0.EnumName(kindb,Some nameb)) ->
818 conjunct_bindings (check_mcode kinda kindb)
819 (match_ident namea nameb)
820 | (Ast0.EnumDef(tya,lb1,idsa,rb1),
821 Ast0.EnumDef(tyb,lb,idsb,rb)) ->
822 conjunct_many_bindings
823 [check_mcode lb1 lb; check_mcode rb1 rb;
824 match_typeC tya tyb;
825 match_dots match_expr no_list do_nolist_match idsa idsb]
826 | (Ast0.StructUnionName(kinda,Some namea),
827 Ast0.StructUnionName(kindb,Some nameb)) ->
828 if mcode_equal kinda kindb
829 then
830 conjunct_bindings (check_mcode kinda kindb)
831 (match_ident namea nameb)
832 else return false
833 | (Ast0.StructUnionDef(tya,lb1,declsa,rb1),
834 Ast0.StructUnionDef(tyb,lb,declsb,rb)) ->
835 conjunct_many_bindings
836 [check_mcode lb1 lb; check_mcode rb1 rb;
837 match_typeC tya tyb;
838 match_dots match_decl no_list do_nolist_match declsa declsb]
839 | (Ast0.TypeName(namea),Ast0.TypeName(nameb)) ->
840 if mcode_equal namea nameb
841 then check_mcode namea nameb
842 else return false
843 | (Ast0.DisjType(_,typesa,_,_),Ast0.DisjType(_,typesb,_,_)) ->
844 failwith "not allowed in the pattern of an isomorphism"
845 | (Ast0.OptType(tya),Ast0.OptType(tyb))
846 | (Ast0.UniqueType(tya),Ast0.UniqueType(tyb)) -> match_typeC tya tyb
847 | (_,Ast0.OptType(tyb))
848 | (_,Ast0.UniqueType(tyb)) -> match_typeC pattern tyb
849 | _ -> return false
850 else return_false (ContextRequired (Ast0.TypeCTag t))
851
852 and match_decl pattern d =
853 match Ast0.unwrap pattern with
854 Ast0.MetaDecl(name,pure) ->
855 add_pure_binding name pure pure_sp_code.VT0.combiner_rec_declaration
856 (function d -> Ast0.DeclTag d)
857 d
858 | Ast0.MetaField(name,pure) ->
859 add_pure_binding name pure pure_sp_code.VT0.combiner_rec_declaration
860 (function d -> Ast0.DeclTag d)
861 d
862 | up ->
863 if not(checks_needed) or not(context_required) or is_context d
864 then
865 match (up,Ast0.unwrap d) with
866 (Ast0.Init(stga,tya,ida,eq1,inia,sc1),
867 Ast0.Init(stgb,tyb,idb,eq,inib,sc)) ->
868 if bool_match_option mcode_equal stga stgb
869 then
870 conjunct_many_bindings
871 [check_mcode eq1 eq; check_mcode sc1 sc;
872 match_option check_mcode stga stgb;
873 match_typeC tya tyb; match_ident ida idb;
874 match_init inia inib]
875 else return false
876 | (Ast0.UnInit(stga,tya,ida,sc1),Ast0.UnInit(stgb,tyb,idb,sc)) ->
877 if bool_match_option mcode_equal stga stgb
878 then
879 conjunct_many_bindings
880 [check_mcode sc1 sc; match_option check_mcode stga stgb;
881 match_typeC tya tyb; match_ident ida idb]
882 else return false
883 | (Ast0.MacroDecl(namea,lp1,argsa,rp1,sc1),
884 Ast0.MacroDecl(nameb,lp,argsb,rp,sc)) ->
885 conjunct_many_bindings
886 [match_ident namea nameb;
887 check_mcode lp1 lp; check_mcode rp1 rp;
888 check_mcode sc1 sc;
889 match_dots match_expr is_elist_matcher do_elist_match
890 argsa argsb]
891 | (Ast0.TyDecl(tya,sc1),Ast0.TyDecl(tyb,sc)) ->
892 conjunct_bindings (check_mcode sc1 sc) (match_typeC tya tyb)
893 | (Ast0.Typedef(stga,tya,ida,sc1),Ast0.Typedef(stgb,tyb,idb,sc)) ->
894 conjunct_bindings (check_mcode sc1 sc)
895 (conjunct_bindings (match_typeC tya tyb) (match_typeC ida idb))
896 | (Ast0.DisjDecl(_,declsa,_,_),Ast0.DisjDecl(_,declsb,_,_)) ->
897 failwith "not allowed in the pattern of an isomorphism"
898 | (Ast0.Ddots(d1,None),Ast0.Ddots(d,None)) -> check_mcode d1 d
899 | (Ast0.Ddots(dd,None),Ast0.Ddots(d,Some wc)) ->
900 conjunct_bindings (check_mcode dd d)
901 (* hope that mcode of ddots is unique somehow *)
902 (let (ddots_whencode_allowed,_,_) = whencode_allowed in
903 if ddots_whencode_allowed
904 then add_dot_binding dd (Ast0.DeclTag wc)
905 else
906 (Printf.printf "warning: not applying iso because of whencode";
907 return false))
908 | (Ast0.Ddots(_,Some _),_) ->
909 failwith "whencode not allowed in a pattern1"
910
911 | (Ast0.OptDecl(decla),Ast0.OptDecl(declb))
912 | (Ast0.UniqueDecl(decla),Ast0.UniqueDecl(declb)) ->
913 match_decl decla declb
914 | (_,Ast0.OptDecl(declb))
915 | (_,Ast0.UniqueDecl(declb)) ->
916 match_decl pattern declb
917 | _ -> return false
918 else return_false (ContextRequired (Ast0.DeclTag d))
919
920 and match_init pattern i =
921 match Ast0.unwrap pattern with
922 Ast0.MetaInit(name,pure) ->
923 add_pure_binding name pure pure_sp_code.VT0.combiner_rec_initialiser
924 (function ini -> Ast0.InitTag ini)
925 i
926 | up ->
927 if not(checks_needed) or not(context_required) or is_context i
928 then
929 match (up,Ast0.unwrap i) with
930 (Ast0.InitExpr(expa),Ast0.InitExpr(expb)) ->
931 match_expr expa expb
932 | (Ast0.InitList(lb1,initlista,rb1,oa),
933 Ast0.InitList(lb,initlistb,rb,ob))
934 when oa = ob ->
935 conjunct_many_bindings
936 [check_mcode lb1 lb; check_mcode rb1 rb;
937 match_dots match_init no_list do_nolist_match
938 initlista initlistb]
939 | (Ast0.InitGccExt(designators1,e1,inia),
940 Ast0.InitGccExt(designators2,e2,inib)) ->
941 conjunct_many_bindings
942 [match_list match_designator
943 (function _ -> false) (function _ -> failwith "")
944 designators1 designators2;
945 check_mcode e1 e2;
946 match_init inia inib]
947 | (Ast0.InitGccName(namea,c1,inia),Ast0.InitGccName(nameb,c,inib)) ->
948 conjunct_many_bindings
949 [check_mcode c1 c; match_ident namea nameb;
950 match_init inia inib]
951 | (Ast0.IComma(c1),Ast0.IComma(c)) -> check_mcode c1 c
952 | (Ast0.Idots(d1,None),Ast0.Idots(d,None)) -> check_mcode d1 d
953 | (Ast0.Idots(id,None),Ast0.Idots(d,Some wc)) ->
954 conjunct_bindings (check_mcode id d)
955 (* hope that mcode of edots is unique somehow *)
956 (let (_,idots_whencode_allowed,_) = whencode_allowed in
957 if idots_whencode_allowed
958 then add_dot_binding id (Ast0.InitTag wc)
959 else
960 (Printf.printf
961 "warning: not applying iso because of whencode";
962 return false))
963 | (Ast0.Idots(_,Some _),_) ->
964 failwith "whencode not allowed in a pattern2"
965 | (Ast0.OptIni(ia),Ast0.OptIni(ib))
966 | (Ast0.UniqueIni(ia),Ast0.UniqueIni(ib)) -> match_init ia ib
967 | (_,Ast0.OptIni(ib))
968 | (_,Ast0.UniqueIni(ib)) -> match_init pattern ib
969 | _ -> return false
970 else return_false (ContextRequired (Ast0.InitTag i))
971
972 and match_designator pattern d =
973 match (pattern,d) with
974 (Ast0.DesignatorField(dota,ida),Ast0.DesignatorField(dotb,idb)) ->
975 conjunct_bindings (check_mcode dota dotb) (match_ident ida idb)
976 | (Ast0.DesignatorIndex(lba,expa,rba),
977 Ast0.DesignatorIndex(lbb,expb,rbb)) ->
978 conjunct_many_bindings
979 [check_mcode lba lbb; match_expr expa expb;
980 check_mcode rba rbb]
981 | (Ast0.DesignatorRange(lba,mina,dotsa,maxa,rba),
982 Ast0.DesignatorRange(lbb,minb,dotsb,maxb,rbb)) ->
983 conjunct_many_bindings
984 [check_mcode lba lbb; match_expr mina minb;
985 check_mcode dotsa dotsb; match_expr maxa maxb;
986 check_mcode rba rbb]
987 | _ -> return false
988
989 and match_param pattern p =
990 match Ast0.unwrap pattern with
991 Ast0.MetaParam(name,pure) ->
992 add_pure_binding name pure pure_sp_code.VT0.combiner_rec_parameter
993 (function p -> Ast0.ParamTag p)
994 p
995 | Ast0.MetaParamList(name,_,pure) -> failwith "metaparamlist not supported"
996 | up ->
997 if not(checks_needed) or not(context_required) or is_context p
998 then
999 match (up,Ast0.unwrap p) with
1000 (Ast0.VoidParam(tya),Ast0.VoidParam(tyb)) -> match_typeC tya tyb
1001 | (Ast0.Param(tya,ida),Ast0.Param(tyb,idb)) ->
1002 conjunct_bindings (match_typeC tya tyb)
1003 (match_option match_ident ida idb)
1004 | (Ast0.PComma(c1),Ast0.PComma(c)) -> check_mcode c1 c
1005 | (Ast0.Pdots(d1),Ast0.Pdots(d))
1006 | (Ast0.Pcircles(d1),Ast0.Pcircles(d)) -> check_mcode d1 d
1007 | (Ast0.OptParam(parama),Ast0.OptParam(paramb))
1008 | (Ast0.UniqueParam(parama),Ast0.UniqueParam(paramb)) ->
1009 match_param parama paramb
1010 | (_,Ast0.OptParam(paramb))
1011 | (_,Ast0.UniqueParam(paramb)) -> match_param pattern paramb
1012 | _ -> return false
1013 else return_false (ContextRequired (Ast0.ParamTag p))
1014
1015 and match_statement pattern s =
1016 match Ast0.unwrap pattern with
1017 Ast0.MetaStmt(name,pure) ->
1018 (match Ast0.unwrap s with
1019 Ast0.Dots(_,_) | Ast0.Circles(_,_) | Ast0.Stars(_,_) ->
1020 return false (* ... is not a single statement *)
1021 | _ ->
1022 add_pure_binding name pure pure_sp_code.VT0.combiner_rec_statement
1023 (function ty -> Ast0.StmtTag ty)
1024 s)
1025 | Ast0.MetaStmtList(name,pure) -> failwith "metastmtlist not supported"
1026 | up ->
1027 if not(checks_needed) or not(context_required) or is_context s
1028 then
1029 match (up,Ast0.unwrap s) with
1030 (Ast0.FunDecl(_,fninfoa,namea,lp1,paramsa,rp1,lb1,bodya,rb1),
1031 Ast0.FunDecl(_,fninfob,nameb,lp,paramsb,rp,lb,bodyb,rb)) ->
1032 conjunct_many_bindings
1033 [check_mcode lp1 lp; check_mcode rp1 rp;
1034 check_mcode lb1 lb; check_mcode rb1 rb;
1035 match_fninfo fninfoa fninfob; match_ident namea nameb;
1036 match_dots match_param is_plist_matcher do_plist_match
1037 paramsa paramsb;
1038 match_dots match_statement is_slist_matcher do_slist_match
1039 bodya bodyb]
1040 | (Ast0.Decl(_,decla),Ast0.Decl(_,declb)) ->
1041 match_decl decla declb
1042 | (Ast0.Seq(lb1,bodya,rb1),Ast0.Seq(lb,bodyb,rb)) ->
1043 (* seqs can only match if they are all minus (plus code
1044 allowed) or all context (plus code not allowed in the body).
1045 we could be more permissive if the expansions of the isos are
1046 also all seqs, but this would be hard to check except at top
1047 level, and perhaps not worth checking even in that case.
1048 Overall, the issue is that braces are used where single
1049 statements are required, and something not satisfying these
1050 conditions can cause a single statement to become a
1051 non-single statement after the transformation.
1052
1053 example: if { ... -foo(); ... }
1054 if we let the sequence convert to just -foo();
1055 then we produce invalid code. For some reason,
1056 single_statement can't deal with this case, perhaps because
1057 it starts introducing too many braces? don't remember the
1058 exact problem...
1059 *)
1060 conjunct_bindings (check_mcode lb1 lb)
1061 (conjunct_bindings (check_mcode rb1 rb)
1062 (if not(checks_needed) or is_minus s or
1063 (is_context s &&
1064 List.for_all is_pure_context (Ast0.undots bodyb))
1065 then
1066 match_dots match_statement is_slist_matcher do_slist_match
1067 bodya bodyb
1068 else return_false (Braces(s))))
1069 | (Ast0.ExprStatement(expa,sc1),Ast0.ExprStatement(expb,sc)) ->
1070 conjunct_bindings (check_mcode sc1 sc) (match_expr expa expb)
1071 | (Ast0.IfThen(if1,lp1,expa,rp1,branch1a,_),
1072 Ast0.IfThen(if2,lp2,expb,rp2,branch1b,_)) ->
1073 conjunct_many_bindings
1074 [check_mcode if1 if2; check_mcode lp1 lp2;
1075 check_mcode rp1 rp2;
1076 match_expr expa expb;
1077 match_statement branch1a branch1b]
1078 | (Ast0.IfThenElse(if1,lp1,expa,rp1,branch1a,e1,branch2a,_),
1079 Ast0.IfThenElse(if2,lp2,expb,rp2,branch1b,e2,branch2b,_)) ->
1080 conjunct_many_bindings
1081 [check_mcode if1 if2; check_mcode lp1 lp2;
1082 check_mcode rp1 rp2; check_mcode e1 e2;
1083 match_expr expa expb;
1084 match_statement branch1a branch1b;
1085 match_statement branch2a branch2b]
1086 | (Ast0.While(w1,lp1,expa,rp1,bodya,_),
1087 Ast0.While(w,lp,expb,rp,bodyb,_)) ->
1088 conjunct_many_bindings
1089 [check_mcode w1 w; check_mcode lp1 lp;
1090 check_mcode rp1 rp; match_expr expa expb;
1091 match_statement bodya bodyb]
1092 | (Ast0.Do(d1,bodya,w1,lp1,expa,rp1,_),
1093 Ast0.Do(d,bodyb,w,lp,expb,rp,_)) ->
1094 conjunct_many_bindings
1095 [check_mcode d1 d; check_mcode w1 w; check_mcode lp1 lp;
1096 check_mcode rp1 rp; match_statement bodya bodyb;
1097 match_expr expa expb]
1098 | (Ast0.For(f1,lp1,e1a,sc1a,e2a,sc2a,e3a,rp1,bodya,_),
1099 Ast0.For(f,lp,e1b,sc1b,e2b,sc2b,e3b,rp,bodyb,_)) ->
1100 conjunct_many_bindings
1101 [check_mcode f1 f; check_mcode lp1 lp; check_mcode sc1a sc1b;
1102 check_mcode sc2a sc2b; check_mcode rp1 rp;
1103 match_option match_expr e1a e1b;
1104 match_option match_expr e2a e2b;
1105 match_option match_expr e3a e3b;
1106 match_statement bodya bodyb]
1107 | (Ast0.Iterator(nma,lp1,argsa,rp1,bodya,_),
1108 Ast0.Iterator(nmb,lp,argsb,rp,bodyb,_)) ->
1109 conjunct_many_bindings
1110 [match_ident nma nmb;
1111 check_mcode lp1 lp; check_mcode rp1 rp;
1112 match_dots match_expr is_elist_matcher do_elist_match
1113 argsa argsb;
1114 match_statement bodya bodyb]
1115 | (Ast0.Switch(s1,lp1,expa,rp1,lb1,declsa,casesa,rb1),
1116 Ast0.Switch(s,lp,expb,rp,lb,declsb,casesb,rb)) ->
1117 conjunct_many_bindings
1118 [check_mcode s1 s; check_mcode lp1 lp; check_mcode rp1 rp;
1119 check_mcode lb1 lb; check_mcode rb1 rb;
1120 match_expr expa expb;
1121 match_dots match_statement is_slist_matcher do_slist_match
1122 declsa declsb;
1123 match_dots match_case_line no_list do_nolist_match
1124 casesa casesb]
1125 | (Ast0.Break(b1,sc1),Ast0.Break(b,sc))
1126 | (Ast0.Continue(b1,sc1),Ast0.Continue(b,sc)) ->
1127 conjunct_bindings (check_mcode b1 b) (check_mcode sc1 sc)
1128 | (Ast0.Label(l1,c1),Ast0.Label(l2,c)) ->
1129 conjunct_bindings (match_ident l1 l2) (check_mcode c1 c)
1130 | (Ast0.Goto(g1,l1,sc1),Ast0.Goto(g,l2,sc)) ->
1131 conjunct_many_bindings
1132 [check_mcode g1 g; check_mcode sc1 sc; match_ident l1 l2]
1133 | (Ast0.Return(r1,sc1),Ast0.Return(r,sc)) ->
1134 conjunct_bindings (check_mcode r1 r) (check_mcode sc1 sc)
1135 | (Ast0.ReturnExpr(r1,expa,sc1),Ast0.ReturnExpr(r,expb,sc)) ->
1136 conjunct_many_bindings
1137 [check_mcode r1 r; check_mcode sc1 sc; match_expr expa expb]
1138 | (Ast0.Disj(_,statement_dots_lista,_,_),_) ->
1139 failwith "disj not supported in patterns"
1140 | (Ast0.Nest(_,stmt_dotsa,_,[],multia),
1141 Ast0.Nest(_,stmt_dotsb,_,wc,multib)) ->
1142 if multia = multib
1143 then
1144 (match wc with
1145 [] ->
1146 (* not sure this is correct, perhaps too restrictive *)
1147 if not(checks_needed) or is_minus s or
1148 (is_context s &&
1149 List.for_all is_pure_context (Ast0.undots stmt_dotsb))
1150 then
1151 match_dots match_statement
1152 is_slist_matcher do_slist_match
1153 stmt_dotsa stmt_dotsb
1154 else return_false (Braces(s))
1155 | _ -> return_false (Nest(s)))
1156 else return false (* diff kind of nest *)
1157 | (Ast0.Nest(_,stmt_dotsa,_,_,_),_) ->
1158 failwith "nest with whencode not supported in patterns"
1159 | (Ast0.Exp(expa),Ast0.Exp(expb)) -> match_expr expa expb
1160 | (Ast0.TopExp(expa),Ast0.TopExp(expb)) -> match_expr expa expb
1161 | (Ast0.Exp(expa),Ast0.TopExp(expb)) -> match_expr expa expb
1162 | (Ast0.TopInit(inita),Ast0.TopInit(initb)) -> match_init inita initb
1163 | (Ast0.Ty(tya),Ast0.Ty(tyb)) -> match_typeC tya tyb
1164 | (Ast0.Dots(d,[]),Ast0.Dots(d1,wc))
1165 | (Ast0.Circles(d,[]),Ast0.Circles(d1,wc))
1166 | (Ast0.Stars(d,[]),Ast0.Stars(d1,wc)) ->
1167 (match wc with
1168 [] -> check_mcode d d1
1169 | _ ->
1170 let (_,_,dots_whencode_allowed) = whencode_allowed in
1171 if dots_whencode_allowed
1172 then
1173 conjunct_bindings (check_mcode d d1)
1174 (List.fold_left
1175 (function prev ->
1176 function
1177 | Ast0.WhenNot wc ->
1178 conjunct_bindings prev
1179 (add_multi_dot_binding d
1180 (Ast0.DotsStmtTag wc))
1181 | Ast0.WhenAlways wc ->
1182 conjunct_bindings prev
1183 (add_multi_dot_binding d (Ast0.StmtTag wc))
1184 | Ast0.WhenNotTrue wc ->
1185 conjunct_bindings prev
1186 (add_multi_dot_binding d
1187 (Ast0.IsoWhenTTag wc))
1188 | Ast0.WhenNotFalse wc ->
1189 conjunct_bindings prev
1190 (add_multi_dot_binding d
1191 (Ast0.IsoWhenFTag wc))
1192 | Ast0.WhenModifier(x) ->
1193 conjunct_bindings prev
1194 (add_multi_dot_binding d
1195 (Ast0.IsoWhenTag x)))
1196 (return true) wc)
1197 else
1198 (Printf.printf
1199 "warning: not applying iso because of whencode";
1200 return false))
1201 | (Ast0.Dots(_,_::_),_) | (Ast0.Circles(_,_::_),_)
1202 | (Ast0.Stars(_,_::_),_) ->
1203 failwith "whencode not allowed in a pattern3"
1204 | (Ast0.OptStm(rea),Ast0.OptStm(reb))
1205 | (Ast0.UniqueStm(rea),Ast0.UniqueStm(reb)) ->
1206 match_statement rea reb
1207 | (_,Ast0.OptStm(reb))
1208 | (_,Ast0.UniqueStm(reb)) -> match_statement pattern reb
1209 | _ -> return false
1210 else return_false (ContextRequired (Ast0.StmtTag s))
1211
1212 (* first should provide a subset of the information in the second *)
1213 and match_fninfo patterninfo cinfo =
1214 let patterninfo = List.sort compare patterninfo in
1215 let cinfo = List.sort compare cinfo in
1216 let rec loop = function
1217 (Ast0.FStorage(sta)::resta,Ast0.FStorage(stb)::restb) ->
1218 if mcode_equal sta stb
1219 then conjunct_bindings (check_mcode sta stb) (loop (resta,restb))
1220 else return false
1221 | (Ast0.FType(tya)::resta,Ast0.FType(tyb)::restb) ->
1222 conjunct_bindings (match_typeC tya tyb) (loop (resta,restb))
1223 | (Ast0.FInline(ia)::resta,Ast0.FInline(ib)::restb) ->
1224 if mcode_equal ia ib
1225 then conjunct_bindings (check_mcode ia ib) (loop (resta,restb))
1226 else return false
1227 | (Ast0.FAttr(ia)::resta,Ast0.FAttr(ib)::restb) ->
1228 if mcode_equal ia ib
1229 then conjunct_bindings (check_mcode ia ib) (loop (resta,restb))
1230 else return false
1231 | (x::resta,((y::_) as restb)) ->
1232 (match compare x y with
1233 -1 -> return false
1234 | 1 -> loop (resta,restb)
1235 | _ -> failwith "not possible")
1236 | _ -> return false in
1237 loop (patterninfo,cinfo)
1238
1239 and match_case_line pattern c =
1240 if not(checks_needed) or not(context_required) or is_context c
1241 then
1242 match (Ast0.unwrap pattern,Ast0.unwrap c) with
1243 (Ast0.Default(d1,c1,codea),Ast0.Default(d,c,codeb)) ->
1244 conjunct_many_bindings
1245 [check_mcode d1 d; check_mcode c1 c;
1246 match_dots match_statement is_slist_matcher do_slist_match
1247 codea codeb]
1248 | (Ast0.Case(ca1,expa,c1,codea),Ast0.Case(ca,expb,c,codeb)) ->
1249 conjunct_many_bindings
1250 [check_mcode ca1 ca; check_mcode c1 c; match_expr expa expb;
1251 match_dots match_statement is_slist_matcher do_slist_match
1252 codea codeb]
1253 | (Ast0.DisjCase(_,case_linesa,_,_),_) ->
1254 failwith "not allowed in the pattern of an isomorphism"
1255 | (Ast0.OptCase(ca),Ast0.OptCase(cb)) -> match_case_line ca cb
1256 | (_,Ast0.OptCase(cb)) -> match_case_line pattern cb
1257 | _ -> return false
1258 else return_false (ContextRequired (Ast0.CaseLineTag c)) in
1259
1260 let match_statement_dots x y =
1261 match_dots match_statement is_slist_matcher do_slist_match x y in
1262
1263 (match_expr, match_decl, match_statement, match_typeC,
1264 match_statement_dots)
1265
1266 let match_expr dochecks context_required whencode_allowed =
1267 let (fn,_,_,_,_) = match_maker dochecks context_required whencode_allowed in
1268 fn
1269
1270 let match_decl dochecks context_required whencode_allowed =
1271 let (_,fn,_,_,_) = match_maker dochecks context_required whencode_allowed in
1272 fn
1273
1274 let match_statement dochecks context_required whencode_allowed =
1275 let (_,_,fn,_,_) = match_maker dochecks context_required whencode_allowed in
1276 fn
1277
1278 let match_typeC dochecks context_required whencode_allowed =
1279 let (_,_,_,fn,_) = match_maker dochecks context_required whencode_allowed in
1280 fn
1281
1282 let match_statement_dots dochecks context_required whencode_allowed =
1283 let (_,_,_,_,fn) = match_maker dochecks context_required whencode_allowed in
1284 fn
1285
1286 (* --------------------------------------------------------------------- *)
1287 (* make an entire tree MINUS *)
1288
1289 let make_minus =
1290 let mcode (term,arity,info,mcodekind,pos,adj) =
1291 let new_mcodekind =
1292 match mcodekind with
1293 Ast0.CONTEXT(mc) ->
1294 (match !mc with
1295 (Ast.NOTHING,_,_) -> Ast0.MINUS(ref([],Ast0.default_token_info))
1296 | _ -> failwith "make_minus: unexpected befaft")
1297 | Ast0.MINUS(mc) -> mcodekind (* in the part copied from the src term *)
1298 | _ -> failwith "make_minus mcode: unexpected mcodekind" in
1299 (term,arity,info,new_mcodekind,pos,adj) in
1300
1301 let update_mc mcodekind e =
1302 match !mcodekind with
1303 Ast0.CONTEXT(mc) ->
1304 (match !mc with
1305 (Ast.NOTHING,_,_) ->
1306 mcodekind := Ast0.MINUS(ref([],Ast0.default_token_info))
1307 | _ -> failwith "make_minus: unexpected befaft")
1308 | Ast0.MINUS(_mc) -> () (* in the part copied from the src term *)
1309 | Ast0.PLUS _ -> failwith "make_minus donothing: unexpected plus mcodekind"
1310 | _ -> failwith "make_minus donothing: unexpected mcodekind" in
1311
1312 let donothing r k e =
1313 let mcodekind = Ast0.get_mcodekind_ref e in
1314 let e = k e in update_mc mcodekind e; e in
1315
1316 (* special case for whencode, because it isn't processed by contextneg,
1317 since it doesn't appear in the + code *)
1318 (* cases for dots and nests *)
1319 let expression r k e =
1320 let mcodekind = Ast0.get_mcodekind_ref e in
1321 match Ast0.unwrap e with
1322 Ast0.Edots(d,whencode) ->
1323 (*don't recurse because whencode hasn't been processed by context_neg*)
1324 update_mc mcodekind e; Ast0.rewrap e (Ast0.Edots(mcode d,whencode))
1325 | Ast0.Ecircles(d,whencode) ->
1326 (*don't recurse because whencode hasn't been processed by context_neg*)
1327 update_mc mcodekind e; Ast0.rewrap e (Ast0.Ecircles(mcode d,whencode))
1328 | Ast0.Estars(d,whencode) ->
1329 (*don't recurse because whencode hasn't been processed by context_neg*)
1330 update_mc mcodekind e; Ast0.rewrap e (Ast0.Estars(mcode d,whencode))
1331 | Ast0.NestExpr(starter,expr_dots,ender,whencode,multi) ->
1332 update_mc mcodekind e;
1333 Ast0.rewrap e
1334 (Ast0.NestExpr(mcode starter,
1335 r.VT0.rebuilder_rec_expression_dots expr_dots,
1336 mcode ender,whencode,multi))
1337 | _ -> donothing r k e in
1338
1339 let declaration r k e =
1340 let mcodekind = Ast0.get_mcodekind_ref e in
1341 match Ast0.unwrap e with
1342 Ast0.Ddots(d,whencode) ->
1343 (*don't recurse because whencode hasn't been processed by context_neg*)
1344 update_mc mcodekind e; Ast0.rewrap e (Ast0.Ddots(mcode d,whencode))
1345 | _ -> donothing r k e in
1346
1347 let statement r k e =
1348 let mcodekind = Ast0.get_mcodekind_ref e in
1349 match Ast0.unwrap e with
1350 Ast0.Dots(d,whencode) ->
1351 (*don't recurse because whencode hasn't been processed by context_neg*)
1352 update_mc mcodekind e; Ast0.rewrap e (Ast0.Dots(mcode d,whencode))
1353 | Ast0.Circles(d,whencode) ->
1354 update_mc mcodekind e; Ast0.rewrap e (Ast0.Circles(mcode d,whencode))
1355 | Ast0.Stars(d,whencode) ->
1356 update_mc mcodekind e; Ast0.rewrap e (Ast0.Stars(mcode d,whencode))
1357 | Ast0.Nest(starter,stmt_dots,ender,whencode,multi) ->
1358 update_mc mcodekind e;
1359 Ast0.rewrap e
1360 (Ast0.Nest
1361 (mcode starter,r.VT0.rebuilder_rec_statement_dots stmt_dots,
1362 mcode ender,whencode,multi))
1363 | _ -> donothing r k e in
1364
1365 let initialiser r k e =
1366 let mcodekind = Ast0.get_mcodekind_ref e in
1367 match Ast0.unwrap e with
1368 Ast0.Idots(d,whencode) ->
1369 (*don't recurse because whencode hasn't been processed by context_neg*)
1370 update_mc mcodekind e; Ast0.rewrap e (Ast0.Idots(mcode d,whencode))
1371 | _ -> donothing r k e in
1372
1373 let dots r k e =
1374 let info = Ast0.get_info e in
1375 let mcodekind = Ast0.get_mcodekind_ref e in
1376 match Ast0.unwrap e with
1377 Ast0.DOTS([]) ->
1378 (* if context is - this should be - as well. There are no tokens
1379 here though, so the bottom-up minusifier in context_neg leaves it
1380 as mixed (or context for sgrep2). It would be better to fix
1381 context_neg, but that would
1382 require a special case for each term with a dots subterm. *)
1383 (match !mcodekind with
1384 Ast0.MIXED(mc) | Ast0.CONTEXT(mc) ->
1385 (match !mc with
1386 (Ast.NOTHING,_,_) ->
1387 mcodekind := Ast0.MINUS(ref([],Ast0.default_token_info));
1388 e
1389 | _ -> failwith "make_minus: unexpected befaft")
1390 (* code already processed by an enclosing iso *)
1391 | Ast0.MINUS(mc) -> e
1392 | _ ->
1393 failwith
1394 (Printf.sprintf
1395 "%d: make_minus donothingxxx: unexpected mcodekind: %s"
1396 info.Ast0.pos_info.Ast0.line_start (Dumper.dump e)))
1397 | _ -> donothing r k e in
1398
1399 V0.flat_rebuilder
1400 mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode
1401 dots dots dots dots dots dots
1402 donothing expression donothing initialiser donothing declaration
1403 statement donothing donothing
1404
1405 (* --------------------------------------------------------------------- *)
1406 (* rebuild mcode cells in an instantiated alt *)
1407
1408 (* mcodes will be side effected later with plus code, so we have to copy
1409 them on instantiating an isomorphism. One could wonder whether it would
1410 be better not to use side-effects, but they are convenient for insert_plus
1411 where is it useful to manipulate a list of the mcodes but side-effect a
1412 tree *)
1413 (* hmm... Insert_plus is called before Iso_pattern... *)
1414 let rebuild_mcode start_line =
1415 let copy_mcodekind = function
1416 Ast0.CONTEXT(mc) -> Ast0.CONTEXT(ref (!mc))
1417 | Ast0.MINUS(mc) -> Ast0.MINUS(ref (!mc))
1418 | Ast0.MIXED(mc) -> Ast0.MIXED(ref (!mc))
1419 | Ast0.PLUS count ->
1420 (* this function is used elsewhere where we need to rebuild the
1421 indices, and so we allow PLUS code as well *)
1422 Ast0.PLUS count in
1423
1424 let mcode (term,arity,info,mcodekind,pos,adj) =
1425 let info =
1426 match start_line with
1427 Some x ->
1428 let new_pos_info =
1429 {info.Ast0.pos_info with
1430 Ast0.line_start = x;
1431 Ast0.line_end = x; } in
1432 {info with Ast0.pos_info = new_pos_info}
1433 | None -> info in
1434 (term,arity,info,copy_mcodekind mcodekind,pos,adj) in
1435
1436 let copy_one x =
1437 let old_info = Ast0.get_info x in
1438 let info =
1439 match start_line with
1440 Some x ->
1441 let new_pos_info =
1442 {old_info.Ast0.pos_info with
1443 Ast0.line_start = x;
1444 Ast0.line_end = x; } in
1445 {old_info with Ast0.pos_info = new_pos_info}
1446 | None -> old_info in
1447 {x with Ast0.info = info; Ast0.index = ref(Ast0.get_index x);
1448 Ast0.mcodekind = ref (copy_mcodekind (Ast0.get_mcodekind x))} in
1449
1450 let donothing r k e = copy_one (k e) in
1451
1452 (* case for control operators (if, etc) *)
1453 let statement r k e =
1454 let s = k e in
1455 let res =
1456 copy_one
1457 (Ast0.rewrap s
1458 (match Ast0.unwrap s with
1459 Ast0.Decl((info,mc),decl) ->
1460 Ast0.Decl((info,copy_mcodekind mc),decl)
1461 | Ast0.IfThen(iff,lp,tst,rp,branch,(info,mc)) ->
1462 Ast0.IfThen(iff,lp,tst,rp,branch,(info,copy_mcodekind mc))
1463 | Ast0.IfThenElse(iff,lp,tst,rp,branch1,els,branch2,(info,mc)) ->
1464 Ast0.IfThenElse(iff,lp,tst,rp,branch1,els,branch2,
1465 (info,copy_mcodekind mc))
1466 | Ast0.While(whl,lp,exp,rp,body,(info,mc)) ->
1467 Ast0.While(whl,lp,exp,rp,body,(info,copy_mcodekind mc))
1468 | Ast0.For(fr,lp,e1,sem1,e2,sem2,e3,rp,body,(info,mc)) ->
1469 Ast0.For(fr,lp,e1,sem1,e2,sem2,e3,rp,body,
1470 (info,copy_mcodekind mc))
1471 | Ast0.Iterator(nm,lp,args,rp,body,(info,mc)) ->
1472 Ast0.Iterator(nm,lp,args,rp,body,(info,copy_mcodekind mc))
1473 | Ast0.FunDecl
1474 ((info,mc),fninfo,name,lp,params,rp,lbrace,body,rbrace) ->
1475 Ast0.FunDecl
1476 ((info,copy_mcodekind mc),
1477 fninfo,name,lp,params,rp,lbrace,body,rbrace)
1478 | s -> s)) in
1479 Ast0.set_dots_bef_aft res
1480 (match Ast0.get_dots_bef_aft res with
1481 Ast0.NoDots -> Ast0.NoDots
1482 | Ast0.AddingBetweenDots s ->
1483 Ast0.AddingBetweenDots(r.VT0.rebuilder_rec_statement s)
1484 | Ast0.DroppingBetweenDots s ->
1485 Ast0.DroppingBetweenDots(r.VT0.rebuilder_rec_statement s)) in
1486
1487 V0.flat_rebuilder
1488 mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode
1489 donothing donothing donothing donothing donothing donothing
1490 donothing donothing donothing donothing donothing
1491 donothing statement donothing donothing
1492
1493 (* --------------------------------------------------------------------- *)
1494 (* The problem of whencode. If an isomorphism contains dots in multiple
1495 rules, then the code that is matched cannot contain whencode, because we
1496 won't know which dots it goes with. Should worry about nests, but they
1497 aren't allowed in isomorphisms for the moment. *)
1498
1499 let count_edots =
1500 let option_default = 0 in
1501 let bind x y = x + y in
1502 let exprfn r k e =
1503 match Ast0.unwrap e with
1504 Ast0.Edots(_,_) | Ast0.Ecircles(_,_) | Ast0.Estars(_,_) -> 1
1505 | _ -> 0 in
1506
1507 V0.combiner bind option_default
1508 {V0.combiner_functions with VT0.combiner_exprfn = exprfn}
1509
1510 let count_idots =
1511 let option_default = 0 in
1512 let bind x y = x + y in
1513 let initfn r k e =
1514 match Ast0.unwrap e with Ast0.Idots(_,_) -> 1 | _ -> 0 in
1515
1516 V0.combiner bind option_default
1517 {V0.combiner_functions with VT0.combiner_initfn = initfn}
1518
1519 let count_dots =
1520 let option_default = 0 in
1521 let bind x y = x + y in
1522 let stmtfn r k e =
1523 match Ast0.unwrap e with
1524 Ast0.Dots(_,_) | Ast0.Circles(_,_) | Ast0.Stars(_,_) -> 1
1525 | _ -> 0 in
1526
1527 V0.combiner bind option_default
1528 {V0.combiner_functions with VT0.combiner_stmtfn = stmtfn}
1529
1530 (* --------------------------------------------------------------------- *)
1531
1532 let lookup name bindings mv_bindings =
1533 try Common.Left (List.assoc (term name) bindings)
1534 with
1535 Not_found ->
1536 (* failure is not possible anymore *)
1537 Common.Right (List.assoc (term name) mv_bindings)
1538
1539 (* mv_bindings is for the fresh metavariables that are introduced by the
1540 isomorphism *)
1541 let instantiate bindings mv_bindings =
1542 let mcode x =
1543 match Ast0.get_pos x with
1544 Ast0.MetaPos(name,_,_) ->
1545 (try
1546 match lookup name bindings mv_bindings with
1547 Common.Left(Ast0.MetaPosTag(id)) -> Ast0.set_pos id x
1548 | _ -> failwith "not possible"
1549 with Not_found -> Ast0.set_pos Ast0.NoMetaPos x)
1550 | _ -> x in
1551 let donothing r k e = k e in
1552
1553 (* cases where metavariables can occur *)
1554 let identfn r k e =
1555 let e = k e in
1556 match Ast0.unwrap e with
1557 Ast0.MetaId(name,constraints,pure) ->
1558 (rebuild_mcode None).VT0.rebuilder_rec_ident
1559 (match lookup name bindings mv_bindings with
1560 Common.Left(Ast0.IdentTag(id)) -> id
1561 | Common.Left(_) -> failwith "not possible 1"
1562 | Common.Right(new_mv) ->
1563 Ast0.rewrap e
1564 (Ast0.MetaId
1565 (Ast0.set_mcode_data new_mv name,constraints,pure)))
1566 | Ast0.MetaFunc(name,_,pure) -> failwith "metafunc not supported"
1567 | Ast0.MetaLocalFunc(name,_,pure) -> failwith "metalocalfunc not supported"
1568 | _ -> e in
1569
1570 (* case for list metavariables *)
1571 let rec elist r same_dots = function
1572 [] -> []
1573 | [x] ->
1574 (match Ast0.unwrap x with
1575 Ast0.MetaExprList(name,lenname,pure) ->
1576 failwith "meta_expr_list in iso not supported"
1577 (*match lookup name bindings mv_bindings with
1578 Common.Left(Ast0.DotsExprTag(exp)) ->
1579 (match same_dots exp with
1580 Some l -> l
1581 | None -> failwith "dots put in incompatible context")
1582 | Common.Left(Ast0.ExprTag(exp)) -> [exp]
1583 | Common.Left(_) -> failwith "not possible 1"
1584 | Common.Right(new_mv) ->
1585 failwith "MetaExprList in SP not supported"*)
1586 | _ -> [r.VT0.rebuilder_rec_expression x])
1587 | x::xs -> (r.VT0.rebuilder_rec_expression x)::(elist r same_dots xs) in
1588
1589 let rec plist r same_dots = function
1590 [] -> []
1591 | [x] ->
1592 (match Ast0.unwrap x with
1593 Ast0.MetaParamList(name,lenname,pure) ->
1594 failwith "meta_param_list in iso not supported"
1595 (*match lookup name bindings mv_bindings with
1596 Common.Left(Ast0.DotsParamTag(param)) ->
1597 (match same_dots param with
1598 Some l -> l
1599 | None -> failwith "dots put in incompatible context")
1600 | Common.Left(Ast0.ParamTag(param)) -> [param]
1601 | Common.Left(_) -> failwith "not possible 1"
1602 | Common.Right(new_mv) ->
1603 failwith "MetaExprList in SP not supported"*)
1604 | _ -> [r.VT0.rebuilder_rec_parameter x])
1605 | x::xs -> (r.VT0.rebuilder_rec_parameter x)::(plist r same_dots xs) in
1606
1607 let rec slist r same_dots = function
1608 [] -> []
1609 | [x] ->
1610 (match Ast0.unwrap x with
1611 Ast0.MetaStmtList(name,pure) ->
1612 (match lookup name bindings mv_bindings with
1613 Common.Left(Ast0.DotsStmtTag(stm)) ->
1614 (match same_dots stm with
1615 Some l -> l
1616 | None -> failwith "dots put in incompatible context")
1617 | Common.Left(Ast0.StmtTag(stm)) -> [stm]
1618 | Common.Left(_) -> failwith "not possible 1"
1619 | Common.Right(new_mv) ->
1620 failwith "MetaExprList in SP not supported")
1621 | _ -> [r.VT0.rebuilder_rec_statement x])
1622 | x::xs -> (r.VT0.rebuilder_rec_statement x)::(slist r same_dots xs) in
1623
1624 let same_dots d =
1625 match Ast0.unwrap d with Ast0.DOTS(l) -> Some l |_ -> None in
1626 let same_circles d =
1627 match Ast0.unwrap d with Ast0.CIRCLES(l) -> Some l |_ -> None in
1628 let same_stars d =
1629 match Ast0.unwrap d with Ast0.STARS(l) -> Some l |_ -> None in
1630
1631 let dots list_fn r k d =
1632 Ast0.rewrap d
1633 (match Ast0.unwrap d with
1634 Ast0.DOTS(l) -> Ast0.DOTS(list_fn r same_dots l)
1635 | Ast0.CIRCLES(l) -> Ast0.CIRCLES(list_fn r same_circles l)
1636 | Ast0.STARS(l) -> Ast0.STARS(list_fn r same_stars l)) in
1637
1638 let exprfn r k old_e = (* need to keep the original code for ! optim *)
1639 let e = k old_e in
1640 let e1 =
1641 match Ast0.unwrap e with
1642 Ast0.MetaExpr(name,constraints,x,form,pure) ->
1643 (rebuild_mcode None).VT0.rebuilder_rec_expression
1644 (match lookup name bindings mv_bindings with
1645 Common.Left(Ast0.ExprTag(exp)) -> exp
1646 | Common.Left(_) -> failwith "not possible 1"
1647 | Common.Right(new_mv) ->
1648 let new_types =
1649 match x with
1650 None -> None
1651 | Some types ->
1652 let rec renamer = function
1653 Type_cocci.MetaType(name,keep,inherited) ->
1654 (match
1655 lookup (name,(),(),(),None,-1) bindings mv_bindings
1656 with
1657 Common.Left(Ast0.TypeCTag(t)) ->
1658 Ast0.ast0_type_to_type t
1659 | Common.Left(_) ->
1660 failwith "iso pattern: unexpected type"
1661 | Common.Right(new_mv) ->
1662 Type_cocci.MetaType(new_mv,keep,inherited))
1663 | Type_cocci.ConstVol(cv,ty) ->
1664 Type_cocci.ConstVol(cv,renamer ty)
1665 | Type_cocci.Pointer(ty) ->
1666 Type_cocci.Pointer(renamer ty)
1667 | Type_cocci.FunctionPointer(ty) ->
1668 Type_cocci.FunctionPointer(renamer ty)
1669 | Type_cocci.Array(ty) ->
1670 Type_cocci.Array(renamer ty)
1671 | t -> t in
1672 Some(List.map renamer types) in
1673 Ast0.rewrap e
1674 (Ast0.MetaExpr
1675 (Ast0.set_mcode_data new_mv name,constraints,
1676 new_types,form,pure)))
1677 | Ast0.MetaErr(namea,_,pure) -> failwith "metaerr not supported"
1678 | Ast0.MetaExprList(namea,lenname,pure) ->
1679 failwith "metaexprlist not supported"
1680 | Ast0.Unary(exp,unop) ->
1681 (match Ast0.unwrap_mcode unop with
1682 (* propagate negation only when the propagated and the encountered
1683 negation have the same transformation, when there is nothing
1684 added to the original one, and when there is nothing added to
1685 the expression into which we are doing the propagation. This
1686 may be too conservative. *)
1687 Ast.Not ->
1688 let was_meta =
1689 (* k e doesn't change the outer structure of the term,
1690 only the metavars *)
1691 match Ast0.unwrap old_e with
1692 Ast0.Unary(exp,_) ->
1693 (match Ast0.unwrap exp with
1694 Ast0.MetaExpr(name,constraints,x,form,pure) -> true
1695 | _ -> false)
1696 | _ -> failwith "not possible" in
1697 let nomodif = function
1698 Ast0.MINUS(x) ->
1699 (match !x with
1700 ([],_) -> true
1701 | _ -> false)
1702 | Ast0.CONTEXT(x) | Ast0.MIXED(x) ->
1703 (match !x with
1704 (Ast.NOTHING,_,_) -> true
1705 | _ -> false)
1706 | _ -> failwith "plus not possible" in
1707 let same_modif newop oldop =
1708 (* only propagate ! is they have the same modification
1709 and no + code on the old one (the new one from the iso
1710 surely has no + code) *)
1711 match (newop,oldop) with
1712 (Ast0.MINUS(x1),Ast0.MINUS(x2)) -> nomodif oldop
1713 | (Ast0.CONTEXT(x1),Ast0.CONTEXT(x2)) -> nomodif oldop
1714 | (Ast0.MIXED(x1),Ast0.MIXED(x2)) -> nomodif oldop
1715 | _ -> false in
1716 if was_meta
1717 then
1718 let idcont x = x in
1719 let rec negate e (*for rewrapping*) res (*code to process*) k =
1720 (* k accumulates parens, to keep negation outside if no
1721 propagation is possible *)
1722 if nomodif (Ast0.get_mcodekind e)
1723 then
1724 match Ast0.unwrap res with
1725 Ast0.Unary(e1,op) when Ast0.unwrap_mcode op = Ast.Not &&
1726 same_modif
1727 (Ast0.get_mcode_mcodekind unop)
1728 (Ast0.get_mcode_mcodekind op) ->
1729 k e1
1730 | Ast0.Edots(_,_) -> k (Ast0.rewrap e (Ast0.unwrap res))
1731 | Ast0.Paren(lp,e1,rp) ->
1732 negate e e1
1733 (function x ->
1734 k (Ast0.rewrap res (Ast0.Paren(lp,x,rp))))
1735 | Ast0.Binary(e1,op,e2) when
1736 same_modif
1737 (Ast0.get_mcode_mcodekind unop)
1738 (Ast0.get_mcode_mcodekind op) ->
1739 let reb nop =
1740 Ast0.rewrap_mcode op (Ast.Logical(nop)) in
1741 let k1 x = k (Ast0.rewrap e x) in
1742 (match Ast0.unwrap_mcode op with
1743 Ast.Logical(Ast.Inf) ->
1744 k1 (Ast0.Binary(e1,reb Ast.SupEq,e2))
1745 | Ast.Logical(Ast.Sup) ->
1746 k1 (Ast0.Binary(e1,reb Ast.InfEq,e2))
1747 | Ast.Logical(Ast.InfEq) ->
1748 k1 (Ast0.Binary(e1,reb Ast.Sup,e2))
1749 | Ast.Logical(Ast.SupEq) ->
1750 k1 (Ast0.Binary(e1,reb Ast.Inf,e2))
1751 | Ast.Logical(Ast.Eq) ->
1752 k1 (Ast0.Binary(e1,reb Ast.NotEq,e2))
1753 | Ast.Logical(Ast.NotEq) ->
1754 k1 (Ast0.Binary(e1,reb Ast.Eq,e2))
1755 | Ast.Logical(Ast.AndLog) ->
1756 k1 (Ast0.Binary(negate_reb e e1 idcont,
1757 reb Ast.OrLog,
1758 negate_reb e e2 idcont))
1759 | Ast.Logical(Ast.OrLog) ->
1760 k1 (Ast0.Binary(negate_reb e e1 idcont,
1761 reb Ast.AndLog,
1762 negate_reb e e2 idcont))
1763 | _ ->
1764 Ast0.rewrap e
1765 (Ast0.Unary(k res,
1766 Ast0.rewrap_mcode op Ast.Not)))
1767 | Ast0.DisjExpr(lp,exps,mids,rp) ->
1768 (* use res because it is the transformed argument *)
1769 let exps =
1770 List.map (function e1 -> negate_reb e e1 k) exps in
1771 Ast0.rewrap res (Ast0.DisjExpr(lp,exps,mids,rp))
1772 | _ ->
1773 (*use e, because this might be the toplevel expression*)
1774 Ast0.rewrap e
1775 (Ast0.Unary(k res,Ast0.rewrap_mcode unop Ast.Not))
1776 else
1777 Ast0.rewrap e
1778 (Ast0.Unary(k res,Ast0.rewrap_mcode unop Ast.Not))
1779 and negate_reb e e1 k =
1780 (* used when ! is propagated to multiple places, to avoid
1781 duplicating mcode cells *)
1782 let start_line =
1783 Some ((Ast0.get_info e).Ast0.pos_info.Ast0.line_start) in
1784 (rebuild_mcode start_line).VT0.rebuilder_rec_expression
1785 (negate e e1 k) in
1786 negate e exp idcont
1787 else e
1788 | _ -> e)
1789 | Ast0.Edots(d,_) ->
1790 (try
1791 (match List.assoc (dot_term d) bindings with
1792 Ast0.ExprTag(exp) -> Ast0.rewrap e (Ast0.Edots(d,Some exp))
1793 | _ -> failwith "unexpected binding")
1794 with Not_found -> e)
1795 | Ast0.Ecircles(d,_) ->
1796 (try
1797 (match List.assoc (dot_term d) bindings with
1798 Ast0.ExprTag(exp) -> Ast0.rewrap e (Ast0.Ecircles(d,Some exp))
1799 | _ -> failwith "unexpected binding")
1800 with Not_found -> e)
1801 | Ast0.Estars(d,_) ->
1802 (try
1803 (match List.assoc (dot_term d) bindings with
1804 Ast0.ExprTag(exp) -> Ast0.rewrap e (Ast0.Estars(d,Some exp))
1805 | _ -> failwith "unexpected binding")
1806 with Not_found -> e)
1807 | _ -> e in
1808 if Ast0.get_test_exp old_e then Ast0.set_test_exp e1 else e1 in
1809
1810 let tyfn r k e =
1811 let e = k e in
1812 match Ast0.unwrap e with
1813 Ast0.MetaType(name,pure) ->
1814 (rebuild_mcode None).VT0.rebuilder_rec_typeC
1815 (match lookup name bindings mv_bindings with
1816 Common.Left(Ast0.TypeCTag(ty)) -> ty
1817 | Common.Left(_) -> failwith "not possible 1"
1818 | Common.Right(new_mv) ->
1819 Ast0.rewrap e
1820 (Ast0.MetaType(Ast0.set_mcode_data new_mv name,pure)))
1821 | _ -> e in
1822
1823 let initfn r k e =
1824 let e = k e in
1825 match Ast0.unwrap e with
1826 Ast0.MetaInit(name,pure) ->
1827 (rebuild_mcode None).VT0.rebuilder_rec_initialiser
1828 (match lookup name bindings mv_bindings with
1829 Common.Left(Ast0.InitTag(ty)) -> ty
1830 | Common.Left(_) -> failwith "not possible 1"
1831 | Common.Right(new_mv) ->
1832 Ast0.rewrap e
1833 (Ast0.MetaInit(Ast0.set_mcode_data new_mv name,pure)))
1834 | _ -> e in
1835
1836 let declfn r k e =
1837 let e = k e in
1838 match Ast0.unwrap e with
1839 Ast0.MetaDecl(name,pure) ->
1840 (rebuild_mcode None).VT0.rebuilder_rec_declaration
1841 (match lookup name bindings mv_bindings with
1842 Common.Left(Ast0.DeclTag(d)) -> d
1843 | Common.Left(_) -> failwith "not possible 1"
1844 | Common.Right(new_mv) ->
1845 Ast0.rewrap e
1846 (Ast0.MetaDecl(Ast0.set_mcode_data new_mv name, pure)))
1847 | Ast0.MetaField(name,pure) ->
1848 (rebuild_mcode None).VT0.rebuilder_rec_declaration
1849 (match lookup name bindings mv_bindings with
1850 Common.Left(Ast0.DeclTag(d)) -> d
1851 | Common.Left(_) -> failwith "not possible 1"
1852 | Common.Right(new_mv) ->
1853 Ast0.rewrap e
1854 (Ast0.MetaField(Ast0.set_mcode_data new_mv name, pure)))
1855 | Ast0.Ddots(d,_) ->
1856 (try
1857 (match List.assoc (dot_term d) bindings with
1858 Ast0.DeclTag(exp) -> Ast0.rewrap e (Ast0.Ddots(d,Some exp))
1859 | _ -> failwith "unexpected binding")
1860 with Not_found -> e)
1861 | _ -> e in
1862
1863 let paramfn r k e =
1864 let e = k e in
1865 match Ast0.unwrap e with
1866 Ast0.MetaParam(name,pure) ->
1867 (rebuild_mcode None).VT0.rebuilder_rec_parameter
1868 (match lookup name bindings mv_bindings with
1869 Common.Left(Ast0.ParamTag(param)) -> param
1870 | Common.Left(_) -> failwith "not possible 1"
1871 | Common.Right(new_mv) ->
1872 Ast0.rewrap e
1873 (Ast0.MetaParam(Ast0.set_mcode_data new_mv name, pure)))
1874 | Ast0.MetaParamList(name,lenname,pure) ->
1875 failwith "metaparamlist not supported"
1876 | _ -> e in
1877
1878 let whenfn (_,v) =
1879 match v with
1880 Ast0.DotsStmtTag(stms) -> Ast0.WhenNot stms
1881 | Ast0.StmtTag(stm) -> Ast0.WhenAlways stm
1882 | Ast0.IsoWhenTTag(stm) -> Ast0.WhenNotTrue stm
1883 | Ast0.IsoWhenFTag(stm) -> Ast0.WhenNotFalse stm
1884 | Ast0.IsoWhenTag(x) -> Ast0.WhenModifier(x)
1885 | _ -> failwith "unexpected binding" in
1886
1887 let stmtfn r k e =
1888 let e = k e in
1889 match Ast0.unwrap e with
1890 Ast0.MetaStmt(name,pure) ->
1891 (rebuild_mcode None).VT0.rebuilder_rec_statement
1892 (match lookup name bindings mv_bindings with
1893 Common.Left(Ast0.StmtTag(stm)) -> stm
1894 | Common.Left(_) -> failwith "not possible 1"
1895 | Common.Right(new_mv) ->
1896 Ast0.rewrap e
1897 (Ast0.MetaStmt(Ast0.set_mcode_data new_mv name,pure)))
1898 | Ast0.MetaStmtList(name,pure) -> failwith "metastmtlist not supported"
1899 | Ast0.Dots(d,_) ->
1900 Ast0.rewrap e
1901 (Ast0.Dots
1902 (d,
1903 List.map whenfn
1904 (List.filter (function (x,v) -> x = (dot_term d)) bindings)))
1905 | Ast0.Circles(d,_) ->
1906 Ast0.rewrap e
1907 (Ast0.Circles
1908 (d,
1909 List.map whenfn
1910 (List.filter (function (x,v) -> x = (dot_term d)) bindings)))
1911 | Ast0.Stars(d,_) ->
1912 Ast0.rewrap e
1913 (Ast0.Stars
1914 (d,
1915 List.map whenfn
1916 (List.filter (function (x,v) -> x = (dot_term d)) bindings)))
1917 | _ -> e in
1918
1919 V0.flat_rebuilder
1920 mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode
1921 (dots elist) donothing (dots plist) (dots slist) donothing donothing
1922 identfn exprfn tyfn initfn paramfn declfn stmtfn donothing donothing
1923
1924 (* --------------------------------------------------------------------- *)
1925
1926 let is_minus e =
1927 match Ast0.get_mcodekind e with Ast0.MINUS(cell) -> true | _ -> false
1928
1929 let context_required e = not(is_minus e) && not !Flag.sgrep_mode2
1930
1931 let disj_fail bindings e =
1932 match bindings with
1933 Some x -> Printf.fprintf stderr "no disj available at this type"; e
1934 | None -> e
1935
1936 (* isomorphism code is by default CONTEXT *)
1937 let merge_plus model_mcode e_mcode =
1938 match model_mcode with
1939 Ast0.MINUS(mc) ->
1940 (* add the replacement information at the root *)
1941 (match e_mcode with
1942 Ast0.MINUS(emc) ->
1943 emc :=
1944 (match (!mc,!emc) with
1945 (([],_),(x,t)) | ((x,_),([],t)) -> (x,t)
1946 | _ -> failwith "how can we combine minuses?")
1947 | _ -> failwith "not possible 6")
1948 | Ast0.CONTEXT(mc) ->
1949 (match e_mcode with
1950 Ast0.CONTEXT(emc) ->
1951 (* keep the logical line info as in the model *)
1952 let (mba,tb,ta) = !mc in
1953 let (eba,_,_) = !emc in
1954 (* merging may be required when a term is replaced by a subterm *)
1955 let merged =
1956 match (mba,eba) with
1957 (x,Ast.NOTHING) | (Ast.NOTHING,x) -> x
1958 | (Ast.BEFORE(b1,it1),Ast.BEFORE(b2,it2)) ->
1959 Ast.BEFORE(b1@b2,Ast.lub_count it1 it2)
1960 | (Ast.BEFORE(b,it1),Ast.AFTER(a,it2)) ->
1961 Ast.BEFOREAFTER(b,a,Ast.lub_count it1 it2)
1962 | (Ast.BEFORE(b1,it1),Ast.BEFOREAFTER(b2,a,it2)) ->
1963 Ast.BEFOREAFTER(b1@b2,a,Ast.lub_count it1 it2)
1964 | (Ast.AFTER(a,it1),Ast.BEFORE(b,it2)) ->
1965 Ast.BEFOREAFTER(b,a,Ast.lub_count it1 it2)
1966 | (Ast.AFTER(a1,it1),Ast.AFTER(a2,it2)) ->
1967 Ast.AFTER(a2@a1,Ast.lub_count it1 it2)
1968 | (Ast.AFTER(a1,it1),Ast.BEFOREAFTER(b,a2,it2)) ->
1969 Ast.BEFOREAFTER(b,a2@a1,Ast.lub_count it1 it2)
1970 | (Ast.BEFOREAFTER(b1,a,it1),Ast.BEFORE(b2,it2)) ->
1971 Ast.BEFOREAFTER(b1@b2,a,Ast.lub_count it1 it2)
1972 | (Ast.BEFOREAFTER(b,a1,it1),Ast.AFTER(a2,it2)) ->
1973 Ast.BEFOREAFTER(b,a2@a1,Ast.lub_count it1 it2)
1974 | (Ast.BEFOREAFTER(b1,a1,it1),Ast.BEFOREAFTER(b2,a2,it2)) ->
1975 Ast.BEFOREAFTER(b1@b2,a2@a1,Ast.lub_count it1 it2) in
1976 emc := (merged,tb,ta)
1977 | Ast0.MINUS(emc) ->
1978 let (anything_bef_aft,_,_) = !mc in
1979 let (anythings,t) = !emc in
1980 emc :=
1981 (match anything_bef_aft with
1982 Ast.BEFORE(b,_) -> (b@anythings,t)
1983 | Ast.AFTER(a,_) -> (anythings@a,t)
1984 | Ast.BEFOREAFTER(b,a,_) -> (b@anythings@a,t)
1985 | Ast.NOTHING -> (anythings,t))
1986 | Ast0.MIXED(_) -> failwith "how did this become mixed?"
1987 | _ -> failwith "not possible 7")
1988 | Ast0.MIXED(_) -> failwith "not possible 8"
1989 | Ast0.PLUS _ -> failwith "not possible 9"
1990
1991 let copy_plus printer minusify model e =
1992 if !Flag.sgrep_mode2
1993 then e (* no plus code, can cause a "not possible" error, so just avoid it *)
1994 else
1995 begin
1996 let e =
1997 match Ast0.get_mcodekind model with
1998 Ast0.MINUS(mc) -> minusify e
1999 | Ast0.CONTEXT(mc) -> e
2000 | _ -> failwith "not possible: copy_plus\n" in
2001 merge_plus (Ast0.get_mcodekind model) (Ast0.get_mcodekind e);
2002 e
2003 end
2004
2005 let copy_minus printer minusify model e =
2006 match Ast0.get_mcodekind model with
2007 Ast0.MINUS(mc) -> minusify e
2008 | Ast0.CONTEXT(mc) -> e
2009 | Ast0.MIXED(_) ->
2010 if !Flag.sgrep_mode2
2011 then e
2012 else failwith "not possible 8"
2013 | Ast0.PLUS _ -> failwith "not possible 9"
2014
2015 let whencode_allowed prev_ecount prev_icount prev_dcount
2016 ecount icount dcount rest =
2017 (* actually, if ecount or dcount is 0, the flag doesn't matter, because it
2018 won't be tested *)
2019 let other_ecount = (* number of edots *)
2020 List.fold_left (function rest -> function (_,ec,ic,dc) -> ec + rest)
2021 prev_ecount rest in
2022 let other_icount = (* number of dots *)
2023 List.fold_left (function rest -> function (_,ec,ic,dc) -> ic + rest)
2024 prev_icount rest in
2025 let other_dcount = (* number of dots *)
2026 List.fold_left (function rest -> function (_,ec,ic,dc) -> dc + rest)
2027 prev_dcount rest in
2028 (ecount = 0 or other_ecount = 0, icount = 0 or other_icount = 0,
2029 dcount = 0 or other_dcount = 0)
2030
2031 (* copy the befores and afters to the instantiated code *)
2032 let extra_copy_stmt_plus model e =
2033 (if not !Flag.sgrep_mode2 (* sgrep has no plus code, so nothing to do *)
2034 then
2035 (match Ast0.unwrap model with
2036 Ast0.FunDecl((info,bef),_,_,_,_,_,_,_,_)
2037 | Ast0.Decl((info,bef),_) ->
2038 (match Ast0.unwrap e with
2039 Ast0.FunDecl((info,bef1),_,_,_,_,_,_,_,_)
2040 | Ast0.Decl((info,bef1),_) ->
2041 merge_plus bef bef1
2042 | _ -> merge_plus bef (Ast0.get_mcodekind e))
2043 | Ast0.IfThen(_,_,_,_,_,(info,aft))
2044 | Ast0.IfThenElse(_,_,_,_,_,_,_,(info,aft))
2045 | Ast0.While(_,_,_,_,_,(info,aft))
2046 | Ast0.For(_,_,_,_,_,_,_,_,_,(info,aft))
2047 | Ast0.Iterator(_,_,_,_,_,(info,aft)) ->
2048 (match Ast0.unwrap e with
2049 Ast0.IfThen(_,_,_,_,_,(info,aft1))
2050 | Ast0.IfThenElse(_,_,_,_,_,_,_,(info,aft1))
2051 | Ast0.While(_,_,_,_,_,(info,aft1))
2052 | Ast0.For(_,_,_,_,_,_,_,_,_,(info,aft1))
2053 | Ast0.Iterator(_,_,_,_,_,(info,aft1)) ->
2054 merge_plus aft aft1
2055 | _ -> merge_plus aft (Ast0.get_mcodekind e))
2056 | _ -> ()));
2057 e
2058
2059 let extra_copy_other_plus model e = e
2060
2061 (* --------------------------------------------------------------------- *)
2062
2063 let mv_count = ref 0
2064 let new_mv (_,s) =
2065 let ct = !mv_count in
2066 mv_count := !mv_count + 1;
2067 "_"^s^"_"^(string_of_int ct)
2068
2069 let get_name = function
2070 Ast.MetaIdDecl(ar,nm) ->
2071 (nm,function nm -> Ast.MetaIdDecl(ar,nm))
2072 | Ast.MetaFreshIdDecl(nm,seed) ->
2073 (nm,function nm -> Ast.MetaFreshIdDecl(nm,seed))
2074 | Ast.MetaTypeDecl(ar,nm) ->
2075 (nm,function nm -> Ast.MetaTypeDecl(ar,nm))
2076 | Ast.MetaInitDecl(ar,nm) ->
2077 (nm,function nm -> Ast.MetaInitDecl(ar,nm))
2078 | Ast.MetaListlenDecl(nm) ->
2079 failwith "should not be rebuilt"
2080 | Ast.MetaParamDecl(ar,nm) ->
2081 (nm,function nm -> Ast.MetaParamDecl(ar,nm))
2082 | Ast.MetaParamListDecl(ar,nm,nm1) ->
2083 (nm,function nm -> Ast.MetaParamListDecl(ar,nm,nm1))
2084 | Ast.MetaConstDecl(ar,nm,ty) ->
2085 (nm,function nm -> Ast.MetaConstDecl(ar,nm,ty))
2086 | Ast.MetaErrDecl(ar,nm) ->
2087 (nm,function nm -> Ast.MetaErrDecl(ar,nm))
2088 | Ast.MetaExpDecl(ar,nm,ty) ->
2089 (nm,function nm -> Ast.MetaExpDecl(ar,nm,ty))
2090 | Ast.MetaIdExpDecl(ar,nm,ty) ->
2091 (nm,function nm -> Ast.MetaIdExpDecl(ar,nm,ty))
2092 | Ast.MetaLocalIdExpDecl(ar,nm,ty) ->
2093 (nm,function nm -> Ast.MetaLocalIdExpDecl(ar,nm,ty))
2094 | Ast.MetaExpListDecl(ar,nm,nm1) ->
2095 (nm,function nm -> Ast.MetaExpListDecl(ar,nm,nm1))
2096 | Ast.MetaDeclDecl(ar,nm) ->
2097 (nm,function nm -> Ast.MetaDeclDecl(ar,nm))
2098 | Ast.MetaFieldDecl(ar,nm) ->
2099 (nm,function nm -> Ast.MetaFieldDecl(ar,nm))
2100 | Ast.MetaStmDecl(ar,nm) ->
2101 (nm,function nm -> Ast.MetaStmDecl(ar,nm))
2102 | Ast.MetaStmListDecl(ar,nm) ->
2103 (nm,function nm -> Ast.MetaStmListDecl(ar,nm))
2104 | Ast.MetaFuncDecl(ar,nm) ->
2105 (nm,function nm -> Ast.MetaFuncDecl(ar,nm))
2106 | Ast.MetaLocalFuncDecl(ar,nm) ->
2107 (nm,function nm -> Ast.MetaLocalFuncDecl(ar,nm))
2108 | Ast.MetaPosDecl(ar,nm) ->
2109 (nm,function nm -> Ast.MetaPosDecl(ar,nm))
2110 | Ast.MetaDeclarerDecl(ar,nm) ->
2111 (nm,function nm -> Ast.MetaDeclarerDecl(ar,nm))
2112 | Ast.MetaIteratorDecl(ar,nm) ->
2113 (nm,function nm -> Ast.MetaIteratorDecl(ar,nm))
2114
2115 let make_new_metavars metavars bindings =
2116 let new_metavars =
2117 List.filter
2118 (function mv ->
2119 let (s,_) = get_name mv in
2120 try let _ = List.assoc s bindings in false with Not_found -> true)
2121 metavars in
2122 List.split
2123 (List.map
2124 (function mv ->
2125 let (s,rebuild) = get_name mv in
2126 let new_s = (!current_rule,new_mv s) in
2127 (rebuild new_s, (s,new_s)))
2128 new_metavars)
2129
2130 (* --------------------------------------------------------------------- *)
2131
2132 let do_nothing x = x
2133
2134 let mkdisj matcher metavars alts e instantiater mkiso disj_maker minusify
2135 rebuild_mcodes name printer extra_plus update_others has_context =
2136 let call_instantiate bindings mv_bindings alts pattern has_context =
2137 List.concat
2138 (List.map
2139 (function (a,_,_,_) ->
2140 nub
2141 (* no need to create duplicates when the bindings have no effect *)
2142 (List.map
2143 (function bindings ->
2144 let instantiated =
2145 instantiater bindings mv_bindings (rebuild_mcodes a) in
2146 let plus_added =
2147 if has_context (* ie if pat is not just a metavara *)
2148 then
2149 copy_plus printer minusify e (extra_plus e instantiated)
2150 else instantiated in
2151 if pattern = a
2152 then plus_added
2153 else (* iso tracking *)
2154 Ast0.set_iso plus_added
2155 ((name,mkiso a)::(Ast0.get_iso e))) (* keep count, not U *)
2156 bindings))
2157 alts) in
2158 let rec inner_loop all_alts prev_ecount prev_icount prev_dcount = function
2159 [] -> Common.Left (prev_ecount, prev_icount, prev_dcount)
2160 | ((pattern,ecount,icount,dcount)::rest) ->
2161 let wc =
2162 whencode_allowed prev_ecount prev_icount prev_dcount
2163 ecount dcount icount rest in
2164 (match matcher true (context_required e) wc pattern e init_env with
2165 Fail(reason) ->
2166 if reason = NonMatch || not !Flag_parsing_cocci.show_iso_failures
2167 then ()
2168 else
2169 (match matcher false false wc pattern e init_env with
2170 OK _ ->
2171 interpret_reason name (Ast0.get_line e) reason
2172 (function () -> printer e)
2173 | _ -> ());
2174 inner_loop all_alts (prev_ecount + ecount) (prev_icount + icount)
2175 (prev_dcount + dcount) rest
2176 | OK (bindings : ((Ast.meta_name * 'a) list list)) ->
2177 let all_alts =
2178 (* apply update_others to all patterns other than the matched
2179 one. This is used to desigate the others as test
2180 expressions in the TestExpression case *)
2181 (List.map
2182 (function (x,e,i,d) as all ->
2183 if x = pattern
2184 then all
2185 else (update_others x,e,i,d))
2186 (List.hd all_alts)) ::
2187 (List.map
2188 (List.map (function (x,e,i,d) -> (update_others x,e,i,d)))
2189 (List.tl all_alts)) in
2190 (match List.concat all_alts with
2191 [x] -> Common.Left (prev_ecount, prev_icount, prev_dcount)
2192 | all_alts ->
2193 let (new_metavars,mv_bindings) =
2194 make_new_metavars metavars (nub(List.concat bindings)) in
2195 Common.Right
2196 (new_metavars,
2197 call_instantiate bindings mv_bindings all_alts pattern
2198 (has_context pattern)))) in
2199 let rec outer_loop prev_ecount prev_icount prev_dcount = function
2200 [] | [[_]] (*only one alternative*) -> (0,[],e) (* nothing matched *)
2201 | (alts::rest) as all_alts ->
2202 match inner_loop all_alts prev_ecount prev_icount prev_dcount alts with
2203 Common.Left(prev_ecount, prev_icount, prev_dcount) ->
2204 outer_loop prev_ecount prev_icount prev_dcount rest
2205 | Common.Right (new_metavars,res) ->
2206 (1,new_metavars,
2207 copy_minus printer minusify e (disj_maker res)) in
2208 let (count,metavars,e) = outer_loop 0 0 0 alts in
2209 (count, metavars, e)
2210
2211 (* no one should ever look at the information stored in these mcodes *)
2212 let disj_starter lst =
2213 let old_info = Ast0.get_info(List.hd lst) in
2214 let new_pos_info =
2215 { old_info.Ast0.pos_info with
2216 Ast0.line_end = old_info.Ast0.pos_info.Ast0.line_start;
2217 Ast0.logical_end = old_info.Ast0.pos_info.Ast0.logical_start; } in
2218 let info =
2219 { Ast0.pos_info = new_pos_info;
2220 Ast0.attachable_start = false; Ast0.attachable_end = false;
2221 Ast0.mcode_start = []; Ast0.mcode_end = [];
2222 Ast0.strings_before = []; Ast0.strings_after = [] } in
2223 Ast0.make_mcode_info "(" info
2224
2225 let disj_ender lst =
2226 let old_info = Ast0.get_info(List.hd lst) in
2227 let new_pos_info =
2228 { old_info.Ast0.pos_info with
2229 Ast0.line_start = old_info.Ast0.pos_info.Ast0.line_end;
2230 Ast0.logical_start = old_info.Ast0.pos_info.Ast0.logical_end; } in
2231 let info =
2232 { Ast0.pos_info = new_pos_info;
2233 Ast0.attachable_start = false; Ast0.attachable_end = false;
2234 Ast0.mcode_start = []; Ast0.mcode_end = [];
2235 Ast0.strings_before = []; Ast0.strings_after = [] } in
2236 Ast0.make_mcode_info ")" info
2237
2238 let disj_mid _ = Ast0.make_mcode "|"
2239
2240 let make_disj_type tl =
2241 let mids =
2242 match tl with
2243 [] -> failwith "bad disjunction"
2244 | x::xs -> List.map disj_mid xs in
2245 Ast0.context_wrap (Ast0.DisjType(disj_starter tl,tl,mids,disj_ender tl))
2246 let make_disj_stmt_list tl =
2247 let mids =
2248 match tl with
2249 [] -> failwith "bad disjunction"
2250 | x::xs -> List.map disj_mid xs in
2251 Ast0.context_wrap (Ast0.Disj(disj_starter tl,tl,mids,disj_ender tl))
2252 let make_disj_expr model el =
2253 let mids =
2254 match el with
2255 [] -> failwith "bad disjunction"
2256 | x::xs -> List.map disj_mid xs in
2257 let update_arg x =
2258 if Ast0.get_arg_exp model then Ast0.set_arg_exp x else x in
2259 let update_test x =
2260 let x = if Ast0.get_test_pos model then Ast0.set_test_pos x else x in
2261 if Ast0.get_test_exp model then Ast0.set_test_exp x else x in
2262 let el = List.map update_arg (List.map update_test el) in
2263 Ast0.context_wrap (Ast0.DisjExpr(disj_starter el,el,mids,disj_ender el))
2264 let make_disj_decl dl =
2265 let mids =
2266 match dl with
2267 [] -> failwith "bad disjunction"
2268 | x::xs -> List.map disj_mid xs in
2269 Ast0.context_wrap (Ast0.DisjDecl(disj_starter dl,dl,mids,disj_ender dl))
2270 let make_disj_stmt sl =
2271 let dotify x = Ast0.context_wrap (Ast0.DOTS[x]) in
2272 let mids =
2273 match sl with
2274 [] -> failwith "bad disjunction"
2275 | x::xs -> List.map disj_mid xs in
2276 Ast0.context_wrap
2277 (Ast0.Disj(disj_starter sl,List.map dotify sl,mids,disj_ender sl))
2278
2279 let transform_type (metavars,alts,name) e =
2280 match alts with
2281 (Ast0.TypeCTag(_)::_)::_ ->
2282 (* start line is given to any leaves in the iso code *)
2283 let start_line =
2284 Some ((Ast0.get_info e).Ast0.pos_info.Ast0.line_start) in
2285 let alts =
2286 List.map
2287 (List.map
2288 (function
2289 Ast0.TypeCTag(p) ->
2290 (p,count_edots.VT0.combiner_rec_typeC p,
2291 count_idots.VT0.combiner_rec_typeC p,
2292 count_dots.VT0.combiner_rec_typeC p)
2293 | _ -> failwith "invalid alt"))
2294 alts in
2295 mkdisj match_typeC metavars alts e
2296 (function b -> function mv_b ->
2297 (instantiate b mv_b).VT0.rebuilder_rec_typeC)
2298 (function t -> Ast0.TypeCTag t)
2299 make_disj_type make_minus.VT0.rebuilder_rec_typeC
2300 (rebuild_mcode start_line).VT0.rebuilder_rec_typeC
2301 name Unparse_ast0.typeC extra_copy_other_plus do_nothing
2302 (function x ->
2303 match Ast0.unwrap x with Ast0.MetaType _ -> false | _ -> true)
2304 | _ -> (0,[],e)
2305
2306
2307 let transform_expr (metavars,alts,name) e =
2308 let process update_others =
2309 (* start line is given to any leaves in the iso code *)
2310 let start_line =
2311 Some ((Ast0.get_info e).Ast0.pos_info.Ast0.line_start) in
2312 let alts =
2313 List.map
2314 (List.map
2315 (function
2316 Ast0.ExprTag(p) | Ast0.ArgExprTag(p) | Ast0.TestExprTag(p) ->
2317 (p,count_edots.VT0.combiner_rec_expression p,
2318 count_idots.VT0.combiner_rec_expression p,
2319 count_dots.VT0.combiner_rec_expression p)
2320 | _ -> failwith "invalid alt"))
2321 alts in
2322 mkdisj match_expr metavars alts e
2323 (function b -> function mv_b ->
2324 (instantiate b mv_b).VT0.rebuilder_rec_expression)
2325 (function e -> Ast0.ExprTag e)
2326 (make_disj_expr e)
2327 make_minus.VT0.rebuilder_rec_expression
2328 (rebuild_mcode start_line).VT0.rebuilder_rec_expression
2329 name Unparse_ast0.expression extra_copy_other_plus update_others
2330 (function x ->
2331 match Ast0.unwrap x with
2332 Ast0.MetaExpr _ | Ast0.MetaExprList _ | Ast0.MetaErr _ -> false
2333 | _ -> true)
2334 in
2335 match alts with
2336 (Ast0.ExprTag(_)::r)::rs ->
2337 (* hack to accomodate ToTestExpression case, where the first pattern is
2338 a normal expression, but the others are test expressions *)
2339 let others = r @ (List.concat rs) in
2340 let is_test = function Ast0.TestExprTag(_) -> true | _ -> false in
2341 if List.for_all is_test others then process Ast0.set_test_exp
2342 else if List.exists is_test others then failwith "inconsistent iso"
2343 else process do_nothing
2344 | (Ast0.ArgExprTag(_)::_)::_ when Ast0.get_arg_exp e -> process do_nothing
2345 | (Ast0.TestExprTag(_)::_)::_ when Ast0.get_test_pos e ->
2346 process Ast0.set_test_exp
2347 | _ -> (0,[],e)
2348
2349 let transform_decl (metavars,alts,name) e =
2350 match alts with
2351 (Ast0.DeclTag(_)::_)::_ ->
2352 (* start line is given to any leaves in the iso code *)
2353 let start_line =
2354 Some (Ast0.get_info e).Ast0.pos_info.Ast0.line_start in
2355 let alts =
2356 List.map
2357 (List.map
2358 (function
2359 Ast0.DeclTag(p) ->
2360 (p,count_edots.VT0.combiner_rec_declaration p,
2361 count_idots.VT0.combiner_rec_declaration p,
2362 count_dots.VT0.combiner_rec_declaration p)
2363 | _ -> failwith "invalid alt"))
2364 alts in
2365 mkdisj match_decl metavars alts e
2366 (function b -> function mv_b ->
2367 (instantiate b mv_b).VT0.rebuilder_rec_declaration)
2368 (function d -> Ast0.DeclTag d)
2369 make_disj_decl
2370 make_minus.VT0.rebuilder_rec_declaration
2371 (rebuild_mcode start_line).VT0.rebuilder_rec_declaration
2372 name Unparse_ast0.declaration extra_copy_other_plus do_nothing
2373 (function _ -> true (* no metavars *))
2374 | _ -> (0,[],e)
2375
2376 let transform_stmt (metavars,alts,name) e =
2377 match alts with
2378 (Ast0.StmtTag(_)::_)::_ ->
2379 (* start line is given to any leaves in the iso code *)
2380 let start_line =
2381 Some (Ast0.get_info e).Ast0.pos_info.Ast0.line_start in
2382 let alts =
2383 List.map
2384 (List.map
2385 (function
2386 Ast0.StmtTag(p) ->
2387 (p,count_edots.VT0.combiner_rec_statement p,
2388 count_idots.VT0.combiner_rec_statement p,
2389 count_dots.VT0.combiner_rec_statement p)
2390 | _ -> failwith "invalid alt"))
2391 alts in
2392 mkdisj match_statement metavars alts e
2393 (function b -> function mv_b ->
2394 (instantiate b mv_b).VT0.rebuilder_rec_statement)
2395 (function s -> Ast0.StmtTag s)
2396 make_disj_stmt make_minus.VT0.rebuilder_rec_statement
2397 (rebuild_mcode start_line).VT0.rebuilder_rec_statement
2398 name (Unparse_ast0.statement "") extra_copy_stmt_plus do_nothing
2399 (function x ->
2400 match Ast0.unwrap x with
2401 Ast0.MetaStmt _ | Ast0.MetaStmtList _ -> false
2402 | _ -> true)
2403 | _ -> (0,[],e)
2404
2405 (* sort of a hack, because there is no disj at top level *)
2406 let transform_top (metavars,alts,name) e =
2407 match Ast0.unwrap e with
2408 Ast0.DECL(declstm) ->
2409 (try
2410 let strip alts =
2411 List.map
2412 (List.map
2413 (function
2414 Ast0.DotsStmtTag(d) ->
2415 (match Ast0.unwrap d with
2416 Ast0.DOTS([s]) -> Ast0.StmtTag(s)
2417 | _ -> raise (Failure ""))
2418 | _ -> raise (Failure "")))
2419 alts in
2420 let (count,mv,s) = transform_stmt (metavars,strip alts,name) declstm in
2421 (count,mv,Ast0.rewrap e (Ast0.DECL(s)))
2422 with Failure _ -> (0,[],e))
2423 | Ast0.CODE(stmts) ->
2424 let (count,mv,res) =
2425 match alts with
2426 (Ast0.DotsStmtTag(_)::_)::_ ->
2427 (* start line is given to any leaves in the iso code *)
2428 let start_line =
2429 Some ((Ast0.get_info e).Ast0.pos_info.Ast0.line_start) in
2430 let alts =
2431 List.map
2432 (List.map
2433 (function
2434 Ast0.DotsStmtTag(p) ->
2435 (p,count_edots.VT0.combiner_rec_statement_dots p,
2436 count_idots.VT0.combiner_rec_statement_dots p,
2437 count_dots.VT0.combiner_rec_statement_dots p)
2438 | _ -> failwith "invalid alt"))
2439 alts in
2440 mkdisj match_statement_dots metavars alts stmts
2441 (function b -> function mv_b ->
2442 (instantiate b mv_b).VT0.rebuilder_rec_statement_dots)
2443 (function s -> Ast0.DotsStmtTag s)
2444 (function x ->
2445 Ast0.rewrap e (Ast0.DOTS([make_disj_stmt_list x])))
2446 (function x ->
2447 make_minus.VT0.rebuilder_rec_statement_dots x)
2448 (rebuild_mcode start_line).VT0.rebuilder_rec_statement_dots
2449 name Unparse_ast0.statement_dots extra_copy_other_plus do_nothing
2450 (function _ -> true)
2451 | _ -> (0,[],stmts) in
2452 (count,mv,Ast0.rewrap e (Ast0.CODE res))
2453 | _ -> (0,[],e)
2454
2455 (* --------------------------------------------------------------------- *)
2456
2457 let transform (alts : isomorphism) t =
2458 (* the following ugliness is because rebuilder only returns a new term *)
2459 let extra_meta_decls = ref ([] : Ast_cocci.metavar list) in
2460 let in_limit n = function
2461 None -> true
2462 | Some n1 ->
2463 n < n1 or
2464 ((if !Flag_parsing_cocci.show_iso_failures
2465 then Common.pr2_once "execeeded iso threshold, see -iso_limit option");
2466 false) in
2467 let bind x y = x + y in
2468 let option_default = 0 in
2469 let exprfn r k e =
2470 let (e_count,e) = k e in
2471 if in_limit e_count !Flag_parsing_cocci.iso_limit
2472 then
2473 let (count,extra_meta,exp) = transform_expr alts e in
2474 extra_meta_decls := extra_meta @ !extra_meta_decls;
2475 (bind count e_count,exp)
2476 else (e_count,e) in
2477
2478 let declfn r k e =
2479 let (e_count,e) = k e in
2480 if in_limit e_count !Flag_parsing_cocci.iso_limit
2481 then
2482 let (count,extra_meta,dec) = transform_decl alts e in
2483 extra_meta_decls := extra_meta @ !extra_meta_decls;
2484 (bind count e_count,dec)
2485 else (e_count,e) in
2486
2487 let stmtfn r k e =
2488 let (e_count,e) = k e in
2489 if in_limit e_count !Flag_parsing_cocci.iso_limit
2490 then
2491 let (count,extra_meta,stm) = transform_stmt alts e in
2492 extra_meta_decls := extra_meta @ !extra_meta_decls;
2493 (bind count e_count,stm)
2494 else (e_count,e) in
2495
2496 let typefn r k e =
2497 let (continue,e_count,e) =
2498 match Ast0.unwrap e with
2499 Ast0.Signed(signb,tyb) ->
2500 (* Hack! How else to prevent iso from applying under an
2501 unsigned??? *)
2502 (true,0,e)
2503 | _ ->
2504 let (e_count,e) = k e in
2505 if in_limit e_count !Flag_parsing_cocci.iso_limit
2506 then (true,e_count,e)
2507 else (false,e_count,e) in
2508 if continue
2509 then
2510 let (count,extra_meta,ty) = transform_type alts e in
2511 extra_meta_decls := extra_meta @ !extra_meta_decls;
2512 (bind count e_count,ty)
2513 else (e_count,e) in
2514
2515 let topfn r k e =
2516 let (e_count,e) = k e in
2517 if in_limit e_count !Flag_parsing_cocci.iso_limit
2518 then
2519 let (count,extra_meta,ty) = transform_top alts e in
2520 extra_meta_decls := extra_meta @ !extra_meta_decls;
2521 (bind count e_count,ty)
2522 else (e_count,e) in
2523
2524 let res =
2525 V0.combiner_rebuilder bind option_default
2526 {V0.combiner_rebuilder_functions with
2527 VT0.combiner_rebuilder_exprfn = exprfn;
2528 VT0.combiner_rebuilder_tyfn = typefn;
2529 VT0.combiner_rebuilder_declfn = declfn;
2530 VT0.combiner_rebuilder_stmtfn = stmtfn;
2531 VT0.combiner_rebuilder_topfn = topfn} in
2532 let (_,res) = res.VT0.top_level t in
2533 (!extra_meta_decls,res)
2534
2535 (* --------------------------------------------------------------------- *)
2536
2537 (* should be done by functorizing the parser to use wrap or context_wrap *)
2538 let rewrap =
2539 let mcode (x,a,i,mc,pos,adj) = (x,a,i,Ast0.context_befaft(),pos,adj) in
2540 let donothing r k e = Ast0.context_wrap(Ast0.unwrap(k e)) in
2541 V0.flat_rebuilder
2542 mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode
2543 donothing donothing donothing donothing donothing donothing
2544 donothing donothing donothing donothing donothing donothing donothing
2545 donothing donothing
2546
2547 let rewrap_anything = function
2548 Ast0.DotsExprTag(d) ->
2549 Ast0.DotsExprTag(rewrap.VT0.rebuilder_rec_expression_dots d)
2550 | Ast0.DotsInitTag(d) ->
2551 Ast0.DotsInitTag(rewrap.VT0.rebuilder_rec_initialiser_list d)
2552 | Ast0.DotsParamTag(d) ->
2553 Ast0.DotsParamTag(rewrap.VT0.rebuilder_rec_parameter_list d)
2554 | Ast0.DotsStmtTag(d) ->
2555 Ast0.DotsStmtTag(rewrap.VT0.rebuilder_rec_statement_dots d)
2556 | Ast0.DotsDeclTag(d) ->
2557 Ast0.DotsDeclTag(rewrap.VT0.rebuilder_rec_declaration_dots d)
2558 | Ast0.DotsCaseTag(d) ->
2559 Ast0.DotsCaseTag(rewrap.VT0.rebuilder_rec_case_line_dots d)
2560 | Ast0.IdentTag(d) -> Ast0.IdentTag(rewrap.VT0.rebuilder_rec_ident d)
2561 | Ast0.ExprTag(d) -> Ast0.ExprTag(rewrap.VT0.rebuilder_rec_expression d)
2562 | Ast0.ArgExprTag(d) ->
2563 Ast0.ArgExprTag(rewrap.VT0.rebuilder_rec_expression d)
2564 | Ast0.TestExprTag(d) ->
2565 Ast0.TestExprTag(rewrap.VT0.rebuilder_rec_expression d)
2566 | Ast0.TypeCTag(d) -> Ast0.TypeCTag(rewrap.VT0.rebuilder_rec_typeC d)
2567 | Ast0.InitTag(d) -> Ast0.InitTag(rewrap.VT0.rebuilder_rec_initialiser d)
2568 | Ast0.ParamTag(d) -> Ast0.ParamTag(rewrap.VT0.rebuilder_rec_parameter d)
2569 | Ast0.DeclTag(d) -> Ast0.DeclTag(rewrap.VT0.rebuilder_rec_declaration d)
2570 | Ast0.StmtTag(d) -> Ast0.StmtTag(rewrap.VT0.rebuilder_rec_statement d)
2571 | Ast0.CaseLineTag(d) ->
2572 Ast0.CaseLineTag(rewrap.VT0.rebuilder_rec_case_line d)
2573 | Ast0.TopTag(d) -> Ast0.TopTag(rewrap.VT0.rebuilder_rec_top_level d)
2574 | Ast0.IsoWhenTag(_) | Ast0.IsoWhenTTag(_) | Ast0.IsoWhenFTag(_) ->
2575 failwith "only for isos within iso phase"
2576 | Ast0.MetaPosTag(p) -> Ast0.MetaPosTag(p)
2577
2578 (* --------------------------------------------------------------------- *)
2579
2580 let apply_isos isos rule rule_name =
2581 if isos = []
2582 then ([],rule)
2583 else
2584 begin
2585 current_rule := rule_name;
2586 let isos =
2587 List.map
2588 (function (metavars,iso,name) ->
2589 (metavars,List.map (List.map rewrap_anything) iso,name))
2590 isos in
2591 let (extra_meta,rule) =
2592 List.split
2593 (List.map
2594 (function t ->
2595 List.fold_left
2596 (function (extra_meta,t) -> function iso ->
2597 let (new_extra_meta,t) = transform iso t in
2598 (new_extra_meta@extra_meta,t))
2599 ([],t) isos)
2600 rule) in
2601 (List.concat extra_meta, (Compute_lines.compute_lines true) rule)
2602 end