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