Coccinelle release 1.0.0-rc3
[bpt/coccinelle.git] / parsing_cocci / insert_plus.ml
1 (*
2 * Copyright 2010, INRIA, University of Copenhagen
3 * Julia Lawall, Rene Rydhof Hansen, Gilles Muller, Nicolas Palix
4 * Copyright 2005-2009, Ecole des Mines de Nantes, University of Copenhagen
5 * Yoann Padioleau, Julia Lawall, Rene Rydhof Hansen, Henrik Stuart, Gilles Muller, Nicolas Palix
6 * This file is part of Coccinelle.
7 *
8 * Coccinelle is free software: you can redistribute it and/or modify
9 * it under the terms of the GNU General Public License as published by
10 * the Free Software Foundation, according to version 2 of the License.
11 *
12 * Coccinelle is distributed in the hope that it will be useful,
13 * but WITHOUT ANY WARRANTY; without even the implied warranty of
14 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
15 * GNU General Public License for more details.
16 *
17 * You should have received a copy of the GNU General Public License
18 * along with Coccinelle. If not, see <http://www.gnu.org/licenses/>.
19 *
20 * The authors reserve the right to distribute this or future versions of
21 * Coccinelle under other licenses.
22 *)
23
24
25 (* The error message "no available token to attach to" often comes in an
26 argument list of unbounded length. In this case, one should move a comma so
27 that there is a comma after the + code. *)
28
29 (* Start at all of the corresponding BindContext nodes in the minus and
30 plus trees, and traverse their children. We take the same strategy as
31 before: collect the list of minus/context nodes/tokens and the list of plus
32 tokens, and then merge them. *)
33
34 module Ast = Ast_cocci
35 module Ast0 = Ast0_cocci
36 module V0 = Visitor_ast0
37 module VT0 = Visitor_ast0_types
38 module CN = Context_neg
39
40 let empty_isos = ref false
41
42 let get_option f = function
43 None -> []
44 | Some x -> f x
45
46 (* --------------------------------------------------------------------- *)
47 (* Collect root and all context nodes in a tree *)
48
49 let collect_context e =
50 let bind x y = x @ y in
51 let option_default = [] in
52
53 let mcode _ = [] in
54
55 let donothing builder r k e =
56 match Ast0.get_mcodekind e with
57 Ast0.CONTEXT(_) -> (builder e) :: (k e)
58 | _ -> k e in
59
60 (* special case for everything that contains whencode, so that we skip over
61 it *)
62 let expression r k e =
63 donothing Ast0.expr r k
64 (Ast0.rewrap e
65 (match Ast0.unwrap e with
66 Ast0.NestExpr(starter,exp,ender,whencode,multi) ->
67 Ast0.NestExpr(starter,exp,ender,None,multi)
68 | Ast0.Edots(dots,whencode) -> Ast0.Edots(dots,None)
69 | Ast0.Ecircles(dots,whencode) -> Ast0.Ecircles(dots,None)
70 | Ast0.Estars(dots,whencode) -> Ast0.Estars(dots,None)
71 | e -> e)) in
72
73 let initialiser r k i =
74 donothing Ast0.ini r k
75 (Ast0.rewrap i
76 (match Ast0.unwrap i with
77 Ast0.Idots(dots,whencode) -> Ast0.Idots(dots,None)
78 | i -> i)) in
79
80 let statement r k s =
81 donothing Ast0.stmt r k
82 (Ast0.rewrap s
83 (match Ast0.unwrap s with
84 Ast0.Nest(started,stm_dots,ender,whencode,multi) ->
85 Ast0.Nest(started,stm_dots,ender,[],multi)
86 | Ast0.Dots(dots,whencode) -> Ast0.Dots(dots,[])
87 | Ast0.Circles(dots,whencode) -> Ast0.Circles(dots,[])
88 | Ast0.Stars(dots,whencode) -> Ast0.Stars(dots,[])
89 | s -> s)) in
90
91 let topfn r k e = Ast0.TopTag(e) :: (k e) in
92
93 let res =
94 V0.flat_combiner bind option_default
95 mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode
96 (donothing Ast0.dotsExpr) (donothing Ast0.dotsInit)
97 (donothing Ast0.dotsParam) (donothing Ast0.dotsStmt)
98 (donothing Ast0.dotsDecl) (donothing Ast0.dotsCase)
99 (donothing Ast0.ident) expression (donothing Ast0.typeC) initialiser
100 (donothing Ast0.param) (donothing Ast0.decl) statement
101 (donothing Ast0.case_line) topfn in
102 res.VT0.combiner_rec_top_level e
103
104 (* --------------------------------------------------------------------- *)
105 (* --------------------------------------------------------------------- *)
106 (* collect the possible join points, in order, among the children of a
107 BindContext. Dots are not allowed. Nests and disjunctions are no problem,
108 because their delimiters take up a line by themselves *)
109
110 (* An Unfavored token is one that is in a BindContext node; using this causes
111 the node to become Neither, meaning that isomorphisms can't be applied *)
112 (* Toplevel is for the bef token of a function declaration and is for
113 attaching top-level definitions that should come before the complete
114 declaration *)
115 type minus_join_point = Favored | Unfavored | Toplevel | Decl
116
117 (* Maps the index of a node to the indices of the mcodes it contains *)
118 let root_token_table = (Hashtbl.create(50) : (int, int list) Hashtbl.t)
119
120 let create_root_token_table minus =
121 Hashtbl.iter
122 (function tokens ->
123 function (node,_) ->
124 let key =
125 match node with
126 Ast0.DotsExprTag(d) -> Ast0.get_index d
127 | Ast0.DotsInitTag(d) -> Ast0.get_index d
128 | Ast0.DotsParamTag(d) -> Ast0.get_index d
129 | Ast0.DotsStmtTag(d) -> Ast0.get_index d
130 | Ast0.DotsDeclTag(d) -> Ast0.get_index d
131 | Ast0.DotsCaseTag(d) -> Ast0.get_index d
132 | Ast0.IdentTag(d) -> Ast0.get_index d
133 | Ast0.ExprTag(d) -> Ast0.get_index d
134 | Ast0.ArgExprTag(d) | Ast0.TestExprTag(d) ->
135 failwith "not possible - iso only"
136 | Ast0.TypeCTag(d) -> Ast0.get_index d
137 | Ast0.ParamTag(d) -> Ast0.get_index d
138 | Ast0.InitTag(d) -> Ast0.get_index d
139 | Ast0.DeclTag(d) -> Ast0.get_index d
140 | Ast0.StmtTag(d) -> Ast0.get_index d
141 | Ast0.CaseLineTag(d) -> Ast0.get_index d
142 | Ast0.TopTag(d) -> Ast0.get_index d
143 | Ast0.IsoWhenTag(_) -> failwith "only within iso phase"
144 | Ast0.IsoWhenTTag(_) -> failwith "only within iso phase"
145 | Ast0.IsoWhenFTag(_) -> failwith "only within iso phase"
146 | Ast0.MetaPosTag(p) -> failwith "metapostag only within iso phase"
147 in
148 Hashtbl.add root_token_table key tokens)
149 CN.minus_table;
150 List.iter
151 (function r ->
152 let index = Ast0.get_index r in
153 try let _ = Hashtbl.find root_token_table index in ()
154 with Not_found -> Hashtbl.add root_token_table index [])
155 minus
156
157 let collect_minus_join_points root =
158 let root_index = Ast0.get_index root in
159 let unfavored_tokens = Hashtbl.find root_token_table root_index in
160 let bind x y = x @ y in
161 let option_default = [] in
162
163 let mcode (x,_,info,mcodekind,_,_) =
164 if List.mem (info.Ast0.pos_info.Ast0.offset) unfavored_tokens
165 then [(Unfavored,info,mcodekind)]
166 else [(Favored,info,mcodekind)] in
167
168 let do_nothing r k e =
169 let info = Ast0.get_info e in
170 let index = Ast0.get_index e in
171 match Ast0.get_mcodekind e with
172 (Ast0.MINUS(_)) as mc -> [(Favored,info,mc)]
173 | (Ast0.CONTEXT(_)) as mc when not(index = root_index) ->
174 (* This was unfavored at one point, but I don't remember why *)
175 [(Favored,info,mc)]
176 | _ -> k e in
177
178 (* don't want to attach to the outside of DOTS, because metavariables can't
179 bind to that; not good for isomorphisms *)
180
181 let dots f k d =
182 let multibind l =
183 let rec loop = function
184 [] -> option_default
185 | [x] -> x
186 | x::xs -> bind x (loop xs) in
187 loop l in
188
189 match Ast0.unwrap d with
190 Ast0.DOTS(l) -> multibind (List.map f l)
191 | Ast0.CIRCLES(l) -> multibind (List.map f l)
192 | Ast0.STARS(l) -> multibind (List.map f l) in
193
194 let edots r k d = dots r.VT0.combiner_rec_expression k d in
195 let idots r k d = dots r.VT0.combiner_rec_initialiser k d in
196 let pdots r k d = dots r.VT0.combiner_rec_parameter k d in
197 let sdots r k d = dots r.VT0.combiner_rec_statement k d in
198 let ddots r k d = dots r.VT0.combiner_rec_declaration k d in
199 let cdots r k d = dots r.VT0.combiner_rec_case_line k d in
200
201 (* a case for everything that has a Opt *)
202
203 let statement r k s =
204 (*
205 let redo_branched res (ifinfo,aftmc) =
206 let redo fv info mc rest =
207 let new_info = {info with Ast0.attachable_end = false} in
208 List.rev ((Favored,ifinfo,aftmc)::(fv,new_info,mc)::rest) in
209 match List.rev res with
210 [(fv,info,mc)] ->
211 (match mc with
212 Ast0.MINUS(_) | Ast0.CONTEXT(_) ->
213 (* even for -, better for isos not to integrate code after an
214 if into the if body.
215 but the problem is that this can extend the region in
216 which a variable is bound, because a variable bound in the
217 aft node would seem to have to be live in the whole if,
218 whereas we might like it to be live in only one branch.
219 ie ideally, if we can keep the minus code in the right
220 order, we would like to drop it as close to the bindings
221 of its free variables. This could be anywhere in the minus
222 code. Perhaps we would like to do this after the
223 application of isomorphisms, though.
224 *)
225 redo fv info mc []
226 | _ -> res)
227 | (fv,info,mc)::rest ->
228 (match mc with
229 Ast0.CONTEXT(_) -> redo fv info mc rest
230 | _ -> res)
231 | _ -> failwith "unexpected empty code" in *)
232 match Ast0.unwrap s with
233 (* Ast0.IfThen(_,_,_,_,_,aft)
234 | Ast0.IfThenElse(_,_,_,_,_,_,_,aft)
235 | Ast0.While(_,_,_,_,_,aft)
236 | Ast0.For(_,_,_,_,_,_,_,_,_,aft)
237 | Ast0.Iterator(_,_,_,_,_,aft) ->
238 redo_branched (do_nothing r k s) aft*)
239 | Ast0.FunDecl((info,bef),fninfo,name,lp,params,rp,lbrace,body,rbrace) ->
240 (Toplevel,info,bef)::(k s)
241 | Ast0.Decl((info,bef),decl) -> (Decl,info,bef)::(k s)
242 | Ast0.Nest(starter,stmt_dots,ender,whencode,multi) ->
243 mcode starter @ r.VT0.combiner_rec_statement_dots stmt_dots @
244 mcode ender
245 | Ast0.Dots(d,whencode) | Ast0.Circles(d,whencode)
246 | Ast0.Stars(d,whencode) -> mcode d (* ignore whencode *)
247 | Ast0.OptStm s | Ast0.UniqueStm s ->
248 (* put the + code on the thing, not on the opt *)
249 r.VT0.combiner_rec_statement s
250 | _ -> do_nothing r k s in
251
252 let expression r k e =
253 match Ast0.unwrap e with
254 Ast0.NestExpr(starter,expr_dots,ender,whencode,multi) ->
255 mcode starter @
256 r.VT0.combiner_rec_expression_dots expr_dots @ mcode ender
257 | Ast0.Edots(d,whencode) | Ast0.Ecircles(d,whencode)
258 | Ast0.Estars(d,whencode) -> mcode d (* ignore whencode *)
259 | Ast0.OptExp e | Ast0.UniqueExp e ->
260 (* put the + code on the thing, not on the opt *)
261 r.VT0.combiner_rec_expression e
262 | _ -> do_nothing r k e in
263
264 let ident r k e =
265 match Ast0.unwrap e with
266 Ast0.OptIdent i | Ast0.UniqueIdent i ->
267 (* put the + code on the thing, not on the opt *)
268 r.VT0.combiner_rec_ident i
269 | _ -> do_nothing r k e in
270
271 let typeC r k e =
272 match Ast0.unwrap e with
273 Ast0.OptType t | Ast0.UniqueType t ->
274 (* put the + code on the thing, not on the opt *)
275 r.VT0.combiner_rec_typeC t
276 | _ -> do_nothing r k e in
277
278 let decl r k e =
279 match Ast0.unwrap e with
280 Ast0.OptDecl d | Ast0.UniqueDecl d ->
281 (* put the + code on the thing, not on the opt *)
282 r.VT0.combiner_rec_declaration d
283 | _ -> do_nothing r k e in
284
285 let initialiser r k e =
286 match Ast0.unwrap e with
287 Ast0.Idots(d,whencode) -> mcode d (* ignore whencode *)
288 | Ast0.OptIni i | Ast0.UniqueIni i ->
289 (* put the + code on the thing, not on the opt *)
290 r.VT0.combiner_rec_initialiser i
291 | _ -> do_nothing r k e in
292
293 let param r k e =
294 match Ast0.unwrap e with
295 Ast0.OptParam p | Ast0.UniqueParam p ->
296 (* put the + code on the thing, not on the opt *)
297 r.VT0.combiner_rec_parameter p
298 | _ -> do_nothing r k e in
299
300 let case_line r k e =
301 match Ast0.unwrap e with
302 Ast0.OptCase c ->
303 (* put the + code on the thing, not on the opt *)
304 r.VT0.combiner_rec_case_line c
305 | _ -> do_nothing r k e in
306
307 let do_top r k (e: Ast0.top_level) = k e in
308
309 V0.flat_combiner bind option_default
310 mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode
311 edots idots pdots sdots ddots cdots
312 ident expression typeC initialiser param decl statement case_line do_top
313
314
315 let call_collect_minus context_nodes :
316 (int * (minus_join_point * Ast0.info * Ast0.mcodekind) list) list =
317 List.map
318 (function e ->
319 match e with
320 Ast0.DotsExprTag(e) ->
321 (Ast0.get_index e,
322 (collect_minus_join_points e).VT0.combiner_rec_expression_dots e)
323 | Ast0.DotsInitTag(e) ->
324 (Ast0.get_index e,
325 (collect_minus_join_points e).VT0.combiner_rec_initialiser_list e)
326 | Ast0.DotsParamTag(e) ->
327 (Ast0.get_index e,
328 (collect_minus_join_points e).VT0.combiner_rec_parameter_list e)
329 | Ast0.DotsStmtTag(e) ->
330 (Ast0.get_index e,
331 (collect_minus_join_points e).VT0.combiner_rec_statement_dots e)
332 | Ast0.DotsDeclTag(e) ->
333 (Ast0.get_index e,
334 (collect_minus_join_points e).VT0.combiner_rec_declaration_dots e)
335 | Ast0.DotsCaseTag(e) ->
336 (Ast0.get_index e,
337 (collect_minus_join_points e).VT0.combiner_rec_case_line_dots e)
338 | Ast0.IdentTag(e) ->
339 (Ast0.get_index e,
340 (collect_minus_join_points e).VT0.combiner_rec_ident e)
341 | Ast0.ExprTag(e) ->
342 (Ast0.get_index e,
343 (collect_minus_join_points e).VT0.combiner_rec_expression e)
344 | Ast0.ArgExprTag(e) | Ast0.TestExprTag(e) ->
345 failwith "not possible - iso only"
346 | Ast0.TypeCTag(e) ->
347 (Ast0.get_index e,
348 (collect_minus_join_points e).VT0.combiner_rec_typeC e)
349 | Ast0.ParamTag(e) ->
350 (Ast0.get_index e,
351 (collect_minus_join_points e).VT0.combiner_rec_parameter e)
352 | Ast0.InitTag(e) ->
353 (Ast0.get_index e,
354 (collect_minus_join_points e).VT0.combiner_rec_initialiser e)
355 | Ast0.DeclTag(e) ->
356 (Ast0.get_index e,
357 (collect_minus_join_points e).VT0.combiner_rec_declaration e)
358 | Ast0.StmtTag(e) ->
359 (Ast0.get_index e,
360 (collect_minus_join_points e).VT0.combiner_rec_statement e)
361 | Ast0.CaseLineTag(e) ->
362 (Ast0.get_index e,
363 (collect_minus_join_points e).VT0.combiner_rec_case_line e)
364 | Ast0.TopTag(e) ->
365 (Ast0.get_index e,
366 (collect_minus_join_points e).VT0.combiner_rec_top_level e)
367 | Ast0.IsoWhenTag(_) -> failwith "only within iso phase"
368 | Ast0.IsoWhenTTag(_) -> failwith "only within iso phase"
369 | Ast0.IsoWhenFTag(_) -> failwith "only within iso phase"
370 | Ast0.MetaPosTag(p) -> failwith "metapostag only within iso phase")
371 context_nodes
372
373 (* result of collecting the join points should be sorted in nondecreasing
374 order by line *)
375 let verify l =
376 let get_info = function
377 (Favored,info,_) | (Unfavored,info,_) | (Toplevel,info,_)
378 | (Decl,info,_) -> info in
379 let token_start_line x = (get_info x).Ast0.pos_info.Ast0.logical_start in
380 let token_end_line x = (get_info x).Ast0.pos_info.Ast0.logical_end in
381 let token_real_start_line x = (get_info x).Ast0.pos_info.Ast0.line_start in
382 let token_real_end_line x = (get_info x).Ast0.pos_info.Ast0.line_end in
383 List.iter
384 (function
385 (index,((_::_) as l1)) ->
386 let _ =
387 List.fold_left
388 (function (prev,real_prev) ->
389 function cur ->
390 let ln = token_start_line cur in
391 if ln < prev
392 then
393 failwith
394 (Printf.sprintf
395 "error in collection of - tokens: line %d less than line %d"
396 (token_real_start_line cur) real_prev);
397 (token_end_line cur,token_real_end_line cur))
398 (token_end_line (List.hd l1), token_real_end_line (List.hd l1))
399 (List.tl l1) in
400 ()
401 | _ -> ()) (* dots, in eg f() has no join points *)
402 l
403
404 let process_minus minus =
405 Hashtbl.clear root_token_table;
406 create_root_token_table minus;
407 List.concat
408 (List.map
409 (function x ->
410 let res = call_collect_minus (collect_context x) in
411 verify res;
412 res)
413 minus)
414
415 (* --------------------------------------------------------------------- *)
416 (* --------------------------------------------------------------------- *)
417 (* collect the plus tokens *)
418
419 let mk_structUnion x = Ast.StructUnionTag x
420 let mk_sign x = Ast.SignTag x
421 let mk_ident x = Ast.IdentTag (Ast0toast.ident x)
422 let mk_expression x = Ast.ExpressionTag (Ast0toast.expression x)
423 let mk_constant x = Ast.ConstantTag x
424 let mk_unaryOp x = Ast.UnaryOpTag x
425 let mk_assignOp x = Ast.AssignOpTag x
426 let mk_fixOp x = Ast.FixOpTag x
427 let mk_binaryOp x = Ast.BinaryOpTag x
428 let mk_arithOp x = Ast.ArithOpTag x
429 let mk_logicalOp x = Ast.LogicalOpTag x
430 let mk_declaration x = Ast.DeclarationTag (Ast0toast.declaration x)
431 let mk_topdeclaration x = Ast.DeclarationTag (Ast0toast.declaration x)
432 let mk_storage x = Ast.StorageTag x
433 let mk_inc_file x = Ast.IncFileTag x
434 let mk_statement x = Ast.StatementTag (Ast0toast.statement x)
435 let mk_case_line x = Ast.CaseLineTag (Ast0toast.case_line x)
436 let mk_const_vol x = Ast.ConstVolTag x
437 let mk_token x info = Ast.Token (x,Some info)
438 let mk_meta (_,x) info = Ast.Token (x,Some info)
439 let mk_code x = Ast.Code (Ast0toast.top_level x)
440
441 let mk_exprdots x = Ast.ExprDotsTag (Ast0toast.expression_dots x)
442 let mk_paramdots x = Ast.ParamDotsTag (Ast0toast.parameter_list x)
443 let mk_stmtdots x = Ast.StmtDotsTag (Ast0toast.statement_dots x)
444 let mk_decldots x = Ast.DeclDotsTag (Ast0toast.declaration_dots x)
445 let mk_casedots x = failwith "+ case lines not supported"
446 let mk_typeC x = Ast.FullTypeTag (Ast0toast.typeC x)
447 let mk_init x = Ast.InitTag (Ast0toast.initialiser x)
448 let mk_param x = Ast.ParamTag (Ast0toast.parameterTypeDef x)
449
450 let collect_plus_nodes root =
451 let root_index = Ast0.get_index root in
452
453 let bind x y = x @ y in
454 let option_default = [] in
455
456 let extract_strings info =
457 let adjust_info =
458 {info with Ast0.strings_before = []; Ast0.strings_after = []} in
459 let extract = function
460 [] -> []
461 | strings_before ->
462 let (_,first) = List.hd strings_before in
463 let (_,last) = List.hd (List.rev strings_before) in
464 let new_pos_info =
465 {Ast0.line_start = first.Ast0.line_start;
466 Ast0.line_end = last.Ast0.line_start;
467 Ast0.logical_start = first.Ast0.logical_start;
468 Ast0.logical_end = last.Ast0.logical_start;
469 Ast0.column = first.Ast0.column;
470 Ast0.offset = first.Ast0.offset} in
471 let new_info = {adjust_info with Ast0.pos_info = new_pos_info} in
472 let string = List.map (function (s,_) -> s) strings_before in
473 [(new_info,Ast.ONE(*?*),Ast.Pragma (string))] in
474 let bef = extract info.Ast0.strings_before in
475 let aft = extract info.Ast0.strings_after in
476 (bef,aft) in
477
478 let mcode fn (term,_,info,mcodekind,_,_) =
479 match mcodekind with
480 Ast0.PLUS c -> [(info,c,fn term)]
481 | Ast0.CONTEXT _ -> let (bef,aft) = extract_strings info in bef@aft
482 | _ -> [] in
483
484 let imcode fn (term,_,info,mcodekind,_,_) =
485 match mcodekind with
486 Ast0.PLUS c -> [(info,c,fn term (Ast0toast.convert_info info))]
487 | Ast0.CONTEXT _ -> let (bef,aft) = extract_strings info in bef@aft
488 | _ -> [] in
489
490 let info (i,_) = let (bef,aft) = extract_strings i in bef@aft in
491
492 let do_nothing fn r k e =
493 match Ast0.get_mcodekind e with
494 (Ast0.CONTEXT(_)) when not(Ast0.get_index e = root_index) -> []
495 | Ast0.PLUS c -> [(Ast0.get_info e,c,fn e)]
496 | _ -> k e in
497
498 (* case for everything that is just a wrapper for a simpler thing *)
499 (* case for things with bef aft *)
500 let stmt r k e =
501 match Ast0.unwrap e with
502 Ast0.Exp(exp) -> r.VT0.combiner_rec_expression exp
503 | Ast0.TopExp(exp) -> r.VT0.combiner_rec_expression exp
504 | Ast0.Ty(ty) -> r.VT0.combiner_rec_typeC ty
505 | Ast0.TopInit(init) -> r.VT0.combiner_rec_initialiser init
506 | Ast0.Decl(bef,decl) ->
507 (info bef) @ (do_nothing mk_statement r k e)
508 | Ast0.FunDecl(bef,fi,name,lp,params,rp,lbrace,body,rbrace) ->
509 (info bef) @ (do_nothing mk_statement r k e)
510 | Ast0.IfThen(iff,lp,exp,rp,branch1,aft) ->
511 (do_nothing mk_statement r k e) @ (info aft)
512 | Ast0.IfThenElse(iff,lp,exp,rp,branch1,els,branch2,aft) ->
513 (do_nothing mk_statement r k e) @ (info aft)
514 | Ast0.While(whl,lp,exp,rp,body,aft) ->
515 (do_nothing mk_statement r k e) @ (info aft)
516 | Ast0.For(fr,lp,e1,sem1,e2,sem2,e3,rp,body,aft) ->
517 (do_nothing mk_statement r k e) @ (info aft)
518 | Ast0.Iterator(nm,lp,args,rp,body,aft) ->
519 (do_nothing mk_statement r k e) @ (info aft)
520 | _ -> do_nothing mk_statement r k e in
521
522 (* statementTag is preferred, because it indicates that one statement is
523 replaced by one statement, in single_statement *)
524 let stmt_dots r k e =
525 match Ast0.unwrap e with
526 Ast0.DOTS([s]) | Ast0.CIRCLES([s]) | Ast0.STARS([s]) ->
527 r.VT0.combiner_rec_statement s
528 | _ -> do_nothing mk_stmtdots r k e in
529
530 let toplevel r k e =
531 match Ast0.unwrap e with
532 Ast0.NONDECL(s) -> r.VT0.combiner_rec_statement s
533 | Ast0.CODE(sdots) -> r.VT0.combiner_rec_statement_dots sdots
534 | _ -> do_nothing mk_code r k e in
535
536 let initdots r k e = k e in
537
538 V0.flat_combiner bind option_default
539 (imcode mk_meta) (imcode mk_token) (mcode mk_constant) (mcode mk_assignOp)
540 (mcode mk_fixOp)
541 (mcode mk_unaryOp) (mcode mk_binaryOp) (mcode mk_const_vol)
542 (mcode mk_sign) (mcode mk_structUnion)
543 (mcode mk_storage) (mcode mk_inc_file)
544 (do_nothing mk_exprdots) initdots
545 (do_nothing mk_paramdots) stmt_dots (do_nothing mk_decldots)
546 (do_nothing mk_casedots)
547 (do_nothing mk_ident) (do_nothing mk_expression)
548 (do_nothing mk_typeC) (do_nothing mk_init) (do_nothing mk_param)
549 (do_nothing mk_declaration)
550 stmt (do_nothing mk_case_line) toplevel
551
552 let call_collect_plus context_nodes :
553 (int * (Ast0.info * Ast.count * Ast.anything) list) list =
554 List.map
555 (function e ->
556 match e with
557 Ast0.DotsExprTag(e) ->
558 (Ast0.get_index e,
559 (collect_plus_nodes e).VT0.combiner_rec_expression_dots e)
560 | Ast0.DotsInitTag(e) ->
561 (Ast0.get_index e,
562 (collect_plus_nodes e).VT0.combiner_rec_initialiser_list e)
563 | Ast0.DotsParamTag(e) ->
564 (Ast0.get_index e,
565 (collect_plus_nodes e).VT0.combiner_rec_parameter_list e)
566 | Ast0.DotsStmtTag(e) ->
567 (Ast0.get_index e,
568 (collect_plus_nodes e).VT0.combiner_rec_statement_dots e)
569 | Ast0.DotsDeclTag(e) ->
570 (Ast0.get_index e,
571 (collect_plus_nodes e).VT0.combiner_rec_declaration_dots e)
572 | Ast0.DotsCaseTag(e) ->
573 (Ast0.get_index e,
574 (collect_plus_nodes e).VT0.combiner_rec_case_line_dots e)
575 | Ast0.IdentTag(e) ->
576 (Ast0.get_index e,
577 (collect_plus_nodes e).VT0.combiner_rec_ident e)
578 | Ast0.ExprTag(e) ->
579 (Ast0.get_index e,
580 (collect_plus_nodes e).VT0.combiner_rec_expression e)
581 | Ast0.ArgExprTag(_) | Ast0.TestExprTag(_) ->
582 failwith "not possible - iso only"
583 | Ast0.TypeCTag(e) ->
584 (Ast0.get_index e,
585 (collect_plus_nodes e).VT0.combiner_rec_typeC e)
586 | Ast0.InitTag(e) ->
587 (Ast0.get_index e,
588 (collect_plus_nodes e).VT0.combiner_rec_initialiser e)
589 | Ast0.ParamTag(e) ->
590 (Ast0.get_index e,
591 (collect_plus_nodes e).VT0.combiner_rec_parameter e)
592 | Ast0.DeclTag(e) ->
593 (Ast0.get_index e,
594 (collect_plus_nodes e).VT0.combiner_rec_declaration e)
595 | Ast0.StmtTag(e) ->
596 (Ast0.get_index e,
597 (collect_plus_nodes e).VT0.combiner_rec_statement e)
598 | Ast0.CaseLineTag(e) ->
599 (Ast0.get_index e,
600 (collect_plus_nodes e).VT0.combiner_rec_case_line e)
601 | Ast0.TopTag(e) ->
602 (Ast0.get_index e,
603 (collect_plus_nodes e).VT0.combiner_rec_top_level e)
604 | Ast0.IsoWhenTag(_) -> failwith "only within iso phase"
605 | Ast0.IsoWhenTTag(_) -> failwith "only within iso phase"
606 | Ast0.IsoWhenFTag(_) -> failwith "only within iso phase"
607 | Ast0.MetaPosTag(p) -> failwith "metapostag only within iso phase")
608 context_nodes
609
610 (* The plus fragments are converted to a list of lists of lists.
611 Innermost list: Elements have type anything. For any pair of successive
612 elements, n and n+1, the ending line of n is the same as the starting line
613 of n+1.
614 Middle lists: For any pair of successive elements, n and n+1, the ending
615 line of n is one less than the starting line of n+1.
616 Outer list: For any pair of successive elements, n and n+1, the ending
617 line of n is more than one less than the starting line of n+1. *)
618
619 let logstart info = info.Ast0.pos_info.Ast0.logical_start
620 let logend info = info.Ast0.pos_info.Ast0.logical_end
621
622 let redo info start finish =
623 let new_pos_info =
624 {info.Ast0.pos_info with
625 Ast0.logical_start = start;
626 Ast0.logical_end = finish} in
627 {info with Ast0.pos_info = new_pos_info}
628
629 let rec find_neighbors (index,l) :
630 int * (Ast0.info * Ast.count * (Ast.anything list list)) list =
631 let rec loop = function
632 [] -> []
633 | (i,c,x)::rest ->
634 (match loop rest with
635 ((i1,c1,(x1::rest_inner))::rest_middle)::rest_outer ->
636 let finish1 = logend i in
637 let start2 = logstart i1 in
638 if finish1 = start2
639 then
640 ((if not (c = c1) then failwith "inconsistent + code");
641 ((redo i (logstart i) (logend i1),c,(x::x1::rest_inner))
642 ::rest_middle)
643 ::rest_outer)
644 else if finish1 + 1 = start2
645 then ((i,c,[x])::(i1,c1,(x1::rest_inner))::rest_middle)::rest_outer
646 else
647 [(i,c,[x])]::((i1,c1,(x1::rest_inner))::rest_middle)::rest_outer
648 | _ -> [[(i,c,[x])]]) (* rest must be [] *) in
649 let res =
650 List.map
651 (function l ->
652 let (start_info,start_count,_) = List.hd l in
653 let (end_info,end_count,_) = List.hd (List.rev l) in
654 (if not (start_count = end_count) then failwith "inconsistent + code");
655 (redo start_info (logstart start_info) (logend end_info),
656 start_count,
657 List.map (function (_,_,x) -> x) l))
658 (loop l) in
659 (index,res)
660
661 let process_plus plus :
662 (int * (Ast0.info * Ast.count * Ast.anything list list) list) list =
663 List.concat
664 (List.map
665 (function x ->
666 List.map find_neighbors (call_collect_plus (collect_context x)))
667 plus)
668
669 (* --------------------------------------------------------------------- *)
670 (* --------------------------------------------------------------------- *)
671 (* merge *)
672 (*
673 let merge_one = function
674 (m1::m2::minus_info,p::plus_info) ->
675 if p < m1, then
676 attach p to the beginning of m1.bef if m1 is Good, fail if it is bad
677 if p > m1 && p < m2, then consider the following possibilities, in order
678 m1 is Good and favored: attach to the beginning of m1.aft
679 m2 is Good and favored: attach to the beginning of m2.bef; drop m1
680 m1 is Good and unfavored: attach to the beginning of m1.aft
681 m2 is Good and unfavored: attach to the beginning of m2.bef; drop m1
682 also flip m1.bef if the first where > m1
683 if we drop m1, then flip m1.aft first
684 if p > m2
685 m2 is Good and favored: attach to the beginning of m2.aft; drop m1
686 *)
687
688 (* end of first argument < start/end of second argument *)
689 let less_than_start info1 info2 =
690 info1.Ast0.pos_info.Ast0.logical_end < info2.Ast0.pos_info.Ast0.logical_start
691 let less_than_end info1 info2 =
692 info1.Ast0.pos_info.Ast0.logical_end < info2.Ast0.pos_info.Ast0.logical_end
693 let greater_than_end info1 info2 =
694 info1.Ast0.pos_info.Ast0.logical_start > info2.Ast0.pos_info.Ast0.logical_end
695 let good_start info = info.Ast0.attachable_start
696 let good_end info = info.Ast0.attachable_end
697
698 let toplevel = function Toplevel -> true | Favored | Unfavored | Decl -> false
699 let decl = function Decl -> true | Favored | Unfavored | Toplevel -> false
700 let favored = function Favored -> true | Unfavored | Toplevel | Decl -> false
701
702 let top_code =
703 List.for_all
704 (List.for_all (function Ast.Code _ | Ast.Pragma _ -> true | _ -> false))
705
706 let storage_code =
707 List.for_all
708 (List.for_all (function Ast.StorageTag _ -> true | _ -> false))
709
710 (* The following is probably not correct. The idea is to detect what
711 should be placed completely before the declaration. So type/storage
712 related things do not fall into this category, and complete statements do
713 fall into this category. But perhaps other things should be in this
714 category as well, such as { or ;? *)
715 let predecl_code =
716 let tester = function
717 (* the following should definitely be true *)
718 Ast.DeclarationTag _
719 | Ast.StatementTag _
720 | Ast.Rule_elemTag _
721 | Ast.StmtDotsTag _
722 | Ast.Code _
723 | Ast.Pragma _ -> true
724 (* the following should definitely be false *)
725 | Ast.FullTypeTag _ | Ast.BaseTypeTag _ | Ast.StructUnionTag _
726 | Ast.SignTag _
727 | Ast.StorageTag _ | Ast.ConstVolTag _ | Ast.TypeCTag _ -> false
728 (* not sure about the rest *)
729 | _ -> false in
730 List.for_all (List.for_all tester)
731
732 let pr = Printf.sprintf
733
734 let insert thing thinginfo into intoinfo =
735 let get_last l = let l = List.rev l in (List.rev(List.tl l),List.hd l) in
736 let get_first l = (List.hd l,List.tl l) in
737 let thing_start = thinginfo.Ast0.pos_info.Ast0.logical_start in
738 let thing_end = thinginfo.Ast0.pos_info.Ast0.logical_end in
739 let thing_offset = thinginfo.Ast0.pos_info.Ast0.offset in
740 let into_start = intoinfo.Ast0.tline_start in
741 let into_end = intoinfo.Ast0.tline_end in
742 let into_left_offset = intoinfo.Ast0.left_offset in
743 let into_right_offset = intoinfo.Ast0.right_offset in
744 if thing_end < into_start && thing_start < into_start
745 then (thing@into,
746 {{intoinfo with Ast0.tline_start = thing_start}
747 with Ast0.left_offset = thing_offset})
748 else if thing_end = into_start && thing_offset < into_left_offset
749 then
750 let (prev,last) = get_last thing in
751 let (first,rest) = get_first into in
752 (prev@[last@first]@rest,
753 {{intoinfo with Ast0.tline_start = thing_start}
754 with Ast0.left_offset = thing_offset})
755 else if thing_start > into_end && thing_end > into_end
756 then (into@thing,
757 {{intoinfo with Ast0.tline_end = thing_end}
758 with Ast0.right_offset = thing_offset})
759 else if thing_start = into_end && thing_offset > into_right_offset
760 then
761 let (first,rest) = get_first thing in
762 let (prev,last) = get_last into in
763 (prev@[last@first]@rest,
764 {{intoinfo with Ast0.tline_end = thing_end}
765 with Ast0.right_offset = thing_offset})
766 else
767 begin
768 Printf.printf "thing start %d thing end %d into start %d into end %d\n"
769 thing_start thing_end into_start into_end;
770 Printf.printf "thing offset %d left offset %d right offset %d\n"
771 thing_offset into_left_offset into_right_offset;
772 Pretty_print_cocci.print_anything "" thing;
773 Pretty_print_cocci.print_anything "" into;
774 failwith "can't figure out where to put the + code"
775 end
776
777 let init thing info =
778 (thing,
779 {Ast0.tline_start = info.Ast0.pos_info.Ast0.logical_start;
780 Ast0.tline_end = info.Ast0.pos_info.Ast0.logical_end;
781 Ast0.left_offset = info.Ast0.pos_info.Ast0.offset;
782 Ast0.right_offset = info.Ast0.pos_info.Ast0.offset})
783
784 let it2c = function Ast.ONE -> "one" | Ast.MANY -> "many"
785
786 let attachbefore (infop,c,p) = function
787 Ast0.MINUS(replacements) ->
788 let (repl,ti) = !replacements in
789 (match repl with
790 Ast.NOREPLACEMENT ->
791 let (bef,ti) = init p infop in
792 replacements := (Ast.REPLACEMENT(bef,c),ti)
793 | Ast.REPLACEMENT(repl,it) ->
794 let it = Ast.lub_count it c in
795 let (bef,ti) = insert p infop repl ti in
796 replacements := (Ast.REPLACEMENT(bef,it),ti))
797 | Ast0.CONTEXT(neighbors) ->
798 let (repl,ti1,ti2) = !neighbors in
799 (match repl with
800 Ast.BEFORE(bef,it) ->
801 let (bef,ti1) = insert p infop bef ti1 in
802 let it = Ast.lub_count it c in
803 neighbors := (Ast.BEFORE(bef,it),ti1,ti2)
804 | Ast.AFTER(aft,it) ->
805 let (bef,ti1) = init p infop in
806 let it = Ast.lub_count it c in
807 neighbors := (Ast.BEFOREAFTER(bef,aft,it),ti1,ti2)
808 | Ast.BEFOREAFTER(bef,aft,it) ->
809 let (bef,ti1) = insert p infop bef ti1 in
810 let it = Ast.lub_count it c in
811 neighbors := (Ast.BEFOREAFTER(bef,aft,it),ti1,ti2)
812 | Ast.NOTHING ->
813 let (bef,ti1) = init p infop in
814 neighbors := (Ast.BEFORE(bef,c),ti1,ti2))
815 | _ -> failwith "not possible for attachbefore"
816
817 let attachafter (infop,c,p) = function
818 Ast0.MINUS(replacements) ->
819 let (repl,ti) = !replacements in
820 (match repl with
821 Ast.NOREPLACEMENT ->
822 let (aft,ti) = init p infop in
823 replacements := (Ast.REPLACEMENT(aft,c),ti)
824 | Ast.REPLACEMENT(repl,it) ->
825 let it = Ast.lub_count it c in
826 let (aft,ti) = insert p infop repl ti in
827 replacements := (Ast.REPLACEMENT(aft,it),ti))
828 | Ast0.CONTEXT(neighbors) ->
829 let (repl,ti1,ti2) = !neighbors in
830 (match repl with
831 Ast.BEFORE(bef,it) ->
832 let (aft,ti2) = init p infop in
833 let it = Ast.lub_count it c in
834 neighbors := (Ast.BEFOREAFTER(bef,aft,it),ti1,ti2)
835 | Ast.AFTER(aft,it) ->
836 let (aft,ti2) = insert p infop aft ti2 in
837 let it = Ast.lub_count it c in
838 neighbors := (Ast.AFTER(aft,it),ti1,ti2)
839 | Ast.BEFOREAFTER(bef,aft,it) ->
840 let (aft,ti2) = insert p infop aft ti2 in
841 let it = Ast.lub_count it c in
842 neighbors := (Ast.BEFOREAFTER(bef,aft,it),ti1,ti2)
843 | Ast.NOTHING ->
844 let (aft,ti2) = init p infop in
845 neighbors := (Ast.AFTER(aft,c),ti1,ti2))
846 | _ -> failwith "not possible for attachbefore"
847
848 let attach_all_before ps m =
849 List.iter (function x -> attachbefore x m) ps
850
851 let attach_all_after ps m =
852 List.iter (function x -> attachafter x m) ps
853
854 let split_at_end info ps =
855 let split_point = info.Ast0.pos_info.Ast0.logical_end in
856 List.partition
857 (function (info,_,_) -> info.Ast0.pos_info.Ast0.logical_end < split_point)
858 ps
859
860 let allminus = function
861 Ast0.MINUS(_) -> true
862 | _ -> false
863
864 let rec before_m1 ((f1,infom1,m1) as x1) ((f2,infom2,m2) as x2) rest = function
865 [] -> ()
866 | (((infop,_,pcode) as p) :: ps) as all ->
867 if less_than_start infop infom1 or
868 (allminus m1 && less_than_end infop infom1) (* account for trees *)
869 then
870 if toplevel f1
871 then
872 if storage_code pcode
873 then before_m2 x2 rest all (* skip fake token for storage *)
874 else (attachbefore p m1; before_m1 x1 x2 rest ps)
875 else
876 if good_start infom1
877 then (attachbefore p m1; before_m1 x1 x2 rest ps)
878 else
879 failwith
880 (pr "%d: no available token to attach to"
881 infop.Ast0.pos_info.Ast0.line_start)
882 else after_m1 x1 x2 rest all
883
884 and after_m1 ((f1,infom1,m1) as x1) ((f2,infom2,m2) as x2) rest = function
885 [] -> ()
886 | (((infop,count,pcode) as p) :: ps) as all ->
887 (* if the following is false, then some + code is stuck in the middle
888 of some context code (m1). could drop down to the token level.
889 this might require adjustments in ast0toast as well, when + code on
890 expressions is dropped down to + code on expressions. it might
891 also break some invariants on which iso depends, particularly on
892 what it can infer from something being CONTEXT with no top-level
893 modifications. for the moment, we thus give an error, asking the
894 user to rewrite the semantic patch. *)
895 if greater_than_end infop infom1 or is_minus m1 or !empty_isos
896 then
897 if less_than_start infop infom2
898 then
899 if predecl_code pcode && good_end infom1 && decl f1
900 then (attachafter p m1; after_m1 x1 x2 rest ps)
901 else if predecl_code pcode && good_start infom2 && decl f2
902 then before_m2 x2 rest all
903 else if top_code pcode && good_end infom1 && toplevel f1
904 then (attachafter p m1; after_m1 x1 x2 rest ps)
905 else if top_code pcode && good_start infom2 && toplevel f2
906 then before_m2 x2 rest all
907 else if good_end infom1 && favored f1
908 then (attachafter p m1; after_m1 x1 x2 rest ps)
909 else if good_start infom2 && favored f2
910 then before_m2 x2 rest all
911 else if good_end infom1
912 then (attachafter p m1; after_m1 x1 x2 rest ps)
913 else if good_start infom2
914 then before_m2 x2 rest all
915 else
916 failwith
917 (pr "%d: no available token to attach to"
918 infop.Ast0.pos_info.Ast0.line_start)
919 else after_m2 x2 rest all
920 else
921 begin
922 Printf.printf "between: p start %d p end %d m1 start %d m1 end %d m2 start %d m2 end %d\n"
923 infop.Ast0.pos_info.Ast0.line_start
924 infop.Ast0.pos_info.Ast0.line_end
925 infom1.Ast0.pos_info.Ast0.line_start
926 infom1.Ast0.pos_info.Ast0.line_end
927 infom2.Ast0.pos_info.Ast0.line_start
928 infom2.Ast0.pos_info.Ast0.line_end;
929 Pretty_print_cocci.print_anything "" pcode;
930 failwith
931 "The semantic patch is structured in a way that may give bad results with isomorphisms. Please try to rewrite it by moving + code out from -/context terms."
932 end
933
934 (* not sure this is safe. if have iso problems, consider changing this
935 to always return false *)
936 and is_minus = function
937 Ast0.MINUS _ -> true
938 | _ -> false
939
940 and before_m2 ((f2,infom2,m2) as x2) rest
941 (p : (Ast0.info * Ast.count * Ast.anything list list) list) =
942 match (rest,p) with
943 (_,[]) -> ()
944 | ([],((infop,_,_)::_)) ->
945 let (bef_m2,aft_m2) = split_at_end infom2 p in (* bef_m2 isn't empty *)
946 if good_start infom2
947 then (attach_all_before bef_m2 m2; after_m2 x2 rest aft_m2)
948 else
949 failwith
950 (pr "%d: no available token to attach to"
951 infop.Ast0.pos_info.Ast0.line_start)
952 | (m::ms,_) -> before_m1 x2 m ms p
953
954 and after_m2 ((f2,infom2,m2) as x2) rest
955 (p : (Ast0.info * Ast.count * Ast.anything list list) list) =
956 match (rest,p) with
957 (_,[]) -> ()
958 | ([],((infop,_,_)::_)) ->
959 if good_end infom2
960 then attach_all_after p m2
961 else
962 failwith
963 (pr "%d: no available token to attach to"
964 infop.Ast0.pos_info.Ast0.line_start)
965 | (m::ms,_) -> after_m1 x2 m ms p
966
967 let merge_one : (minus_join_point * Ast0.info * 'a) list *
968 (Ast0.info * Ast.count * Ast.anything list list) list -> unit =
969 function (m,p) ->
970 (*
971 Printf.printf "minus code\n";
972 List.iter
973 (function (_,info,_) ->
974 Printf.printf
975 "start %d end %d real_start %d real_end %d attachable start %b attachable end %b\n"
976 info.Ast0.pos_info.Ast0.logical_start
977 info.Ast0.pos_info.Ast0.logical_end
978 info.Ast0.pos_info.Ast0.line_start
979 info.Ast0.pos_info.Ast0.line_end
980 info.Ast0.attachable_start
981 info.Ast0.attachable_end)
982 m;
983 Printf.printf "plus code\n";
984 List.iter
985 (function (info,_,p) ->
986 Printf.printf "start %d end %d real_start %d real_end %d\n"
987 info.Ast0.pos_info.Ast0.logical_start
988 info.Ast0.pos_info.Ast0.logical_end
989 info.Ast0.pos_info.Ast0.line_end
990 info.Ast0.pos_info.Ast0.line_end;
991 Pretty_print_cocci.print_anything "" p;
992 Format.print_newline())
993 p;
994 *)
995 match (m,p) with
996 (_,[]) -> ()
997 | (m1::m2::restm,p) -> before_m1 m1 m2 restm p
998 | ([m],p) -> before_m2 m [] p
999 | ([],_) -> failwith "minus tree ran out before the plus tree"
1000
1001 let merge minus_list plus_list =
1002 (*
1003 Printf.printf "minus list %s\n"
1004 (String.concat " "
1005 (List.map (function (x,_) -> string_of_int x) minus_list));
1006 Printf.printf "plus list %s\n"
1007 (String.concat " "
1008 (List.map (function (x,_) -> string_of_int x) plus_list));
1009 *)
1010 List.iter
1011 (function (index,minus_info) ->
1012 let plus_info = List.assoc index plus_list in
1013 merge_one (minus_info,plus_info))
1014 minus_list
1015
1016 (* --------------------------------------------------------------------- *)
1017 (* --------------------------------------------------------------------- *)
1018 (* Need to check that CONTEXT nodes have nothing attached to their tokens.
1019 If they do, they become MIXED *)
1020
1021 let reevaluate_contextness =
1022 let bind = (@) in
1023 let option_default = [] in
1024
1025 let mcode (_,_,_,mc,_,_) =
1026 match mc with
1027 Ast0.CONTEXT(mc) -> let (ba,_,_) = !mc in [ba]
1028 | _ -> [] in
1029
1030 let info (_,mc) =
1031 match mc with
1032 Ast0.CONTEXT(mc) -> let (ba,_,_) = !mc in [ba]
1033 | _ -> [] in
1034
1035 let donothing r k e =
1036 match Ast0.get_mcodekind e with
1037 Ast0.CONTEXT(mc) ->
1038 if List.exists (function Ast.NOTHING -> false | _ -> true) (k e)
1039 then Ast0.set_mcodekind e (Ast0.MIXED(mc));
1040 []
1041 | _ -> let _ = k e in [] in
1042
1043 (* a case for everything with bef or aft *)
1044 let stmt r k e =
1045 match Ast0.unwrap e with
1046 Ast0.Decl(bef,decl) ->
1047 (info bef) @ (donothing r k e)
1048 | Ast0.FunDecl(bef,fi,name,lp,params,rp,lbrace,body,rbrace) ->
1049 (info bef) @ (donothing r k e)
1050 | Ast0.IfThen(iff,lp,exp,rp,branch1,aft) ->
1051 (donothing r k e) @ (info aft)
1052 | Ast0.IfThenElse(iff,lp,exp,rp,branch1,els,branch2,aft) ->
1053 (donothing r k e) @ (info aft)
1054 | Ast0.While(whl,lp,exp,rp,body,aft) ->
1055 (donothing r k e) @ (info aft)
1056 | Ast0.For(fr,lp,e1,sem1,e2,sem2,e3,rp,body,aft) ->
1057 (donothing r k e) @ (info aft)
1058 | Ast0.Iterator(nm,lp,args,rp,body,aft) ->
1059 (donothing r k e) @ (info aft)
1060 | _ -> donothing r k e in
1061
1062 let res =
1063 V0.flat_combiner bind option_default
1064 mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode
1065 donothing donothing donothing donothing donothing donothing donothing
1066 donothing
1067 donothing donothing donothing donothing stmt donothing donothing in
1068 res.VT0.combiner_rec_top_level
1069
1070 (* --------------------------------------------------------------------- *)
1071 (* --------------------------------------------------------------------- *)
1072
1073 let insert_plus minus plus ei =
1074 empty_isos := ei;
1075 let minus_stream = process_minus minus in
1076 let plus_stream = process_plus plus in
1077 merge minus_stream plus_stream;
1078 List.iter (function x -> let _ = reevaluate_contextness x in ()) minus