Release coccinelle-0.2.5-rc2
[bpt/coccinelle.git] / parsing_cocci / context_neg.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 (* Detects subtrees that are all minus/plus and nodes that are "binding
26 context nodes". The latter is a node whose structure and immediate tokens
27 are the same in the minus and plus trees, and such that for every child,
28 the set of context nodes in the child subtree is the same in the minus and
29 plus subtrees. *)
30
31 module Ast = Ast_cocci
32 module Ast0 = Ast0_cocci
33 module V0 = Visitor_ast0
34 module VT0 = Visitor_ast0_types
35 module U = Unparse_ast0
36
37 (* --------------------------------------------------------------------- *)
38 (* Generic access to code *)
39
40 let set_mcodekind x mcodekind =
41 match x with
42 Ast0.DotsExprTag(d) -> Ast0.set_mcodekind d mcodekind
43 | Ast0.DotsInitTag(d) -> Ast0.set_mcodekind d mcodekind
44 | Ast0.DotsParamTag(d) -> Ast0.set_mcodekind d mcodekind
45 | Ast0.DotsStmtTag(d) -> Ast0.set_mcodekind d mcodekind
46 | Ast0.DotsDeclTag(d) -> Ast0.set_mcodekind d mcodekind
47 | Ast0.DotsCaseTag(d) -> Ast0.set_mcodekind d mcodekind
48 | Ast0.IdentTag(d) -> Ast0.set_mcodekind d mcodekind
49 | Ast0.ExprTag(d) -> Ast0.set_mcodekind d mcodekind
50 | Ast0.ArgExprTag(d) | Ast0.TestExprTag(d) ->
51 failwith "not possible - iso only"
52 | Ast0.TypeCTag(d) -> Ast0.set_mcodekind d mcodekind
53 | Ast0.ParamTag(d) -> Ast0.set_mcodekind d mcodekind
54 | Ast0.DeclTag(d) -> Ast0.set_mcodekind d mcodekind
55 | Ast0.InitTag(d) -> Ast0.set_mcodekind d mcodekind
56 | Ast0.StmtTag(d) -> Ast0.set_mcodekind d mcodekind
57 | Ast0.CaseLineTag(d) -> Ast0.set_mcodekind d mcodekind
58 | Ast0.TopTag(d) -> Ast0.set_mcodekind d mcodekind
59 | Ast0.IsoWhenTag(_) -> failwith "only within iso phase"
60 | Ast0.IsoWhenTTag(_) -> failwith "only within iso phase"
61 | Ast0.IsoWhenFTag(_) -> failwith "only within iso phase"
62 | Ast0.MetaPosTag(p) -> failwith "metapostag only within iso phase"
63
64 let set_index x index =
65 match x with
66 Ast0.DotsExprTag(d) -> Ast0.set_index d index
67 | Ast0.DotsInitTag(d) -> Ast0.set_index d index
68 | Ast0.DotsParamTag(d) -> Ast0.set_index d index
69 | Ast0.DotsStmtTag(d) -> Ast0.set_index d index
70 | Ast0.DotsDeclTag(d) -> Ast0.set_index d index
71 | Ast0.DotsCaseTag(d) -> Ast0.set_index d index
72 | Ast0.IdentTag(d) -> Ast0.set_index d index
73 | Ast0.ExprTag(d) -> Ast0.set_index d index
74 | Ast0.ArgExprTag(d) | Ast0.TestExprTag(d) ->
75 failwith "not possible - iso only"
76 | Ast0.TypeCTag(d) -> Ast0.set_index d index
77 | Ast0.ParamTag(d) -> Ast0.set_index d index
78 | Ast0.InitTag(d) -> Ast0.set_index d index
79 | Ast0.DeclTag(d) -> Ast0.set_index d index
80 | Ast0.StmtTag(d) -> Ast0.set_index d index
81 | Ast0.CaseLineTag(d) -> Ast0.set_index d index
82 | Ast0.TopTag(d) -> Ast0.set_index d index
83 | Ast0.IsoWhenTag(_) -> failwith "only within iso phase"
84 | Ast0.IsoWhenTTag(_) -> failwith "only within iso phase"
85 | Ast0.IsoWhenFTag(_) -> failwith "only within iso phase"
86 | Ast0.MetaPosTag(p) -> failwith "metapostag only within iso phase"
87
88 let get_index = function
89 Ast0.DotsExprTag(d) -> Index.expression_dots d
90 | Ast0.DotsInitTag(d) -> Index.initialiser_dots d
91 | Ast0.DotsParamTag(d) -> Index.parameter_dots d
92 | Ast0.DotsStmtTag(d) -> Index.statement_dots d
93 | Ast0.DotsDeclTag(d) -> Index.declaration_dots d
94 | Ast0.DotsCaseTag(d) -> Index.case_line_dots d
95 | Ast0.IdentTag(d) -> Index.ident d
96 | Ast0.ExprTag(d) -> Index.expression d
97 | Ast0.ArgExprTag(d) | Ast0.TestExprTag(d) ->
98 failwith "not possible - iso only"
99 | Ast0.TypeCTag(d) -> Index.typeC d
100 | Ast0.ParamTag(d) -> Index.parameterTypeDef d
101 | Ast0.InitTag(d) -> Index.initialiser d
102 | Ast0.DeclTag(d) -> Index.declaration d
103 | Ast0.StmtTag(d) -> Index.statement d
104 | Ast0.CaseLineTag(d) -> Index.case_line d
105 | Ast0.TopTag(d) -> Index.top_level d
106 | Ast0.IsoWhenTag(_) -> failwith "only within iso phase"
107 | Ast0.IsoWhenTTag(_) -> failwith "only within iso phase"
108 | Ast0.IsoWhenFTag(_) -> failwith "only within iso phase"
109 | Ast0.MetaPosTag(p) -> failwith "metapostag only within iso phase"
110
111 (* --------------------------------------------------------------------- *)
112 (* Collect the line numbers of the plus code. This is used for disjunctions.
113 It is not completely clear why this is necessary, but it seems like an easy
114 fix for whatever is the problem that is discussed in disj_cases *)
115
116 let plus_lines = ref ([] : int list)
117
118 let insert n =
119 let rec loop = function
120 [] -> [n]
121 | x::xs ->
122 match compare n x with
123 1 -> x::(loop xs)
124 | 0 -> x::xs
125 | -1 -> n::x::xs
126 | _ -> failwith "not possible" in
127 plus_lines := loop !plus_lines
128
129 let find n min max =
130 let rec loop = function
131 [] -> (min,max)
132 | [x] -> if n < x then (min,x) else (x,max)
133 | x1::x2::rest ->
134 if n < x1
135 then (min,x1)
136 else if n > x1 && n < x2 then (x1,x2) else loop (x2::rest) in
137 loop !plus_lines
138
139 let collect_plus_lines top =
140 plus_lines := [];
141 let bind x y = () in
142 let option_default = () in
143 let donothing r k e = k e in
144 let mcode (_,_,info,mcodekind,_,_) =
145 match mcodekind with
146 Ast0.PLUS _ -> insert info.Ast0.pos_info.Ast0.line_start
147 | _ -> () in
148 let fn =
149 V0.flat_combiner bind option_default
150 mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode
151 donothing donothing donothing donothing donothing donothing
152 donothing donothing donothing donothing donothing donothing donothing
153 donothing donothing in
154 fn.VT0.combiner_rec_top_level top
155
156 (* --------------------------------------------------------------------- *)
157
158 type kind =
159 Neutral | AllMarked of Ast.count | NotAllMarked (* marked means + or - *)
160
161 (* --------------------------------------------------------------------- *)
162 (* The first part analyzes each of the minus tree and the plus tree
163 separately *)
164
165 (* ints are unique token indices (offset field) *)
166 type node =
167 Token (* tokens *) of kind * int (* unique index *) * Ast0.mcodekind *
168 int list (* context tokens *)
169 | Recursor (* children *) of kind *
170 int list (* indices of all tokens at the level below *) *
171 Ast0.mcodekind list (* tokens at the level below *) *
172 int list
173 | Bind (* neighbors *) of kind *
174 int list (* indices of all tokens at current level *) *
175 Ast0.mcodekind list (* tokens at current level *) *
176 int list (* indices of all tokens at the level below *) *
177 Ast0.mcodekind list (* tokens at the level below *)
178 * int list list
179
180 let kind2c = function
181 Neutral -> "neutral"
182 | AllMarked _ -> "allmarked"
183 | NotAllMarked -> "notallmarked"
184
185 let node2c = function
186 Token(k,_,_,_) -> Printf.sprintf "token %s\n" (kind2c k)
187 | Recursor(k,_,_,_) -> Printf.sprintf "recursor %s\n" (kind2c k)
188 | Bind(k,_,_,_,_,_) -> Printf.sprintf "bind %s\n" (kind2c k)
189
190 (* goal: detect negative in both tokens and recursors, or context only in
191 tokens *)
192 let bind c1 c2 =
193 let lub = function
194 (k1,k2) when k1 = k2 -> k1
195 | (Neutral,AllMarked c) -> AllMarked c
196 | (AllMarked c,Neutral) -> AllMarked c
197 | _ -> NotAllMarked in
198 match (c1,c2) with
199 (* token/token *)
200 (* there are tokens at this level, so ignore the level below *)
201 (Token(k1,i1,t1,l1),Token(k2,i2,t2,l2)) ->
202 Bind(lub(k1,k2),[i1;i2],[t1;t2],[],[],[l1;l2])
203
204 (* token/recursor *)
205 (* there are tokens at this level, so ignore the level below *)
206 | (Token(k1,i1,t1,l1),Recursor(k2,_,_,l2)) ->
207 Bind(lub(k1,k2),[i1],[t1],[],[],[l1;l2])
208 | (Recursor(k1,_,_,l1),Token(k2,i2,t2,l2)) ->
209 Bind(lub(k1,k2),[i2],[t2],[],[],[l1;l2])
210
211 (* token/bind *)
212 (* there are tokens at this level, so ignore the level below *)
213 | (Token(k1,i1,t1,l1),Bind(k2,i2,t2,_,_,l2)) ->
214 Bind(lub(k1,k2),i1::i2,t1::t2,[],[],l1::l2)
215 | (Bind(k1,i1,t1,_,_,l1),Token(k2,i2,t2,l2)) ->
216 Bind(lub(k1,k2),i1@[i2],t1@[t2],[],[],l1@[l2])
217
218 (* recursor/bind *)
219 | (Recursor(k1,bi1,bt1,l1),Bind(k2,i2,t2,bi2,bt2,l2)) ->
220 Bind(lub(k1,k2),i2,t2,bi1@bi2,bt1@bt2,l1::l2)
221 | (Bind(k1,i1,t1,bi1,bt1,l1),Recursor(k2,bi2,bt2,l2)) ->
222 Bind(lub(k1,k2),i1,t1,bi1@bi2,bt1@bt2,l1@[l2])
223
224 (* recursor/recursor and bind/bind - not likely to ever occur *)
225 | (Recursor(k1,bi1,bt1,l1),Recursor(k2,bi2,bt2,l2)) ->
226 Bind(lub(k1,k2),[],[],bi1@bi2,bt1@bt2,[l1;l2])
227 | (Bind(k1,i1,t1,bi1,bt1,l1),Bind(k2,i2,t2,bi2,bt2,l2)) ->
228 Bind(lub(k1,k2),i1@i2,t1@t2,bi1@bi2,bt1@bt2,l1@l2)
229
230
231 let option_default = (*Bind(Neutral,[],[],[],[],[])*)
232 Recursor(Neutral,[],[],[])
233
234 let mcode (_,_,info,mcodekind,pos,_) =
235 let offset = info.Ast0.pos_info.Ast0.offset in
236 match mcodekind with
237 Ast0.MINUS(_) -> Token(AllMarked Ast.ONE,offset,mcodekind,[])
238 | Ast0.PLUS c -> Token(AllMarked c,offset,mcodekind,[])
239 | Ast0.CONTEXT(_) -> Token(NotAllMarked,offset,mcodekind,[offset])
240 | _ -> failwith "not possible"
241
242 let neutral_mcode (_,_,info,mcodekind,pos,_) =
243 let offset = info.Ast0.pos_info.Ast0.offset in
244 match mcodekind with
245 Ast0.MINUS(_) -> Token(Neutral,offset,mcodekind,[])
246 | Ast0.PLUS _ -> Token(Neutral,offset,mcodekind,[])
247 | Ast0.CONTEXT(_) -> Token(Neutral,offset,mcodekind,[offset])
248 | _ -> failwith "not possible"
249
250 (* neutral for context; used for mcode in bef aft nodes that don't represent
251 anything if they don't contain some information *)
252 let nc_mcode (_,_,info,mcodekind,pos,_) =
253 (* distinguish from the offset of some real token *)
254 let offset = (-1) * info.Ast0.pos_info.Ast0.offset in
255 match mcodekind with
256 Ast0.MINUS(_) -> Token(AllMarked Ast.ONE,offset,mcodekind,[])
257 | Ast0.PLUS c -> Token(AllMarked c,offset,mcodekind,[])
258 | Ast0.CONTEXT(_) ->
259 (* Unlike the other mcode cases, we drop the offset from the context
260 offsets. This is because we don't know whether the term this is
261 associated with is - or context. In any case, the context offsets are
262 used for identification, and this invisible node should not be needed
263 for this purpose. *)
264 Token(Neutral,offset,mcodekind,[])
265 | _ -> failwith "not possible"
266
267 let is_context = function Ast0.CONTEXT(_) -> true | _ -> false
268
269 let union_all l = List.fold_left Common.union_set [] l
270
271 (* is minus is true when we are processing minus code that might be
272 intermingled with plus code. it is used in disj_cases *)
273 let classify is_minus all_marked table code =
274 let mkres builder k il tl bil btl l e =
275 (match k with
276 AllMarked count ->
277 Ast0.set_mcodekind e (all_marked count) (* definitive *)
278 | _ ->
279 let check_index il tl =
280 if List.for_all is_context tl
281 then
282 (let e1 = builder e in
283 let index = (get_index e1)@il in
284 try
285 let _ = Hashtbl.find table index in
286 failwith
287 (Printf.sprintf "line %d: index %s already used\n"
288 (Ast0.get_info e).Ast0.pos_info.Ast0.line_start
289 (String.concat " " (List.map string_of_int index)))
290 with Not_found -> Hashtbl.add table index (e1,l)) in
291 if il = [] then check_index bil btl else check_index il tl);
292 if il = []
293 then Recursor(k, bil, btl, union_all l)
294 else Recursor(k, il, tl, union_all l) in
295
296 let compute_result builder e = function
297 Bind(k,il,tl,bil,btl,l) -> mkres builder k il tl bil btl l e
298 | Token(k,il,tl,l) -> mkres builder k [il] [tl] [] [] [l] e
299 | Recursor(k,bil,btl,l) -> mkres builder k [] [] bil btl [l] e in
300
301 let make_not_marked = function
302 Bind(k,il,tl,bil,btl,l) -> Bind(NotAllMarked,il,tl,bil,btl,l)
303 | Token(k,il,tl,l) -> Token(NotAllMarked,il,tl,l)
304 | Recursor(k,bil,btl,l) -> Recursor(NotAllMarked,bil,btl,l) in
305
306 let do_nothing builder r k e = compute_result builder e (k e) in
307
308 let disj_cases disj starter code fn ender =
309 (* neutral_mcode used so starter and ender don't have an affect on
310 whether the code is considered all plus/minus, but so that they are
311 consider in the index list, which is needed to make a disj with
312 something in one branch and nothing in the other different from code
313 that just has the something (starter/ender enough, mids not needed
314 for this). Cannot agglomerate + code over | boundaries, because two -
315 cases might have different + code, and don't want to put the + code
316 together into one unit. *)
317 let make_not_marked =
318 if is_minus
319 then
320 (let min = Ast0.get_line disj in
321 let max = Ast0.get_line_end disj in
322 let (plus_min,plus_max) = find min (min-1) (max+1) in
323 if max > plus_max then make_not_marked else (function x -> x))
324 else make_not_marked in
325 bind (neutral_mcode starter)
326 (bind (List.fold_right bind
327 (List.map make_not_marked (List.map fn code))
328 option_default)
329 (neutral_mcode ender)) in
330
331 (* no whencode in plus tree so have to drop it *)
332 (* need special cases for dots, nests, and disjs *)
333 let expression r k e =
334 compute_result Ast0.expr e
335 (match Ast0.unwrap e with
336 Ast0.NestExpr(starter,exp,ender,whencode,multi) ->
337 k (Ast0.rewrap e (Ast0.NestExpr(starter,exp,ender,None,multi)))
338 | Ast0.Edots(dots,whencode) ->
339 k (Ast0.rewrap e (Ast0.Edots(dots,None)))
340 | Ast0.Ecircles(dots,whencode) ->
341 k (Ast0.rewrap e (Ast0.Ecircles(dots,None)))
342 | Ast0.Estars(dots,whencode) ->
343 k (Ast0.rewrap e (Ast0.Estars(dots,None)))
344 | Ast0.DisjExpr(starter,expr_list,_,ender) ->
345 disj_cases e starter expr_list r.VT0.combiner_rec_expression ender
346 | _ -> k e) in
347
348 (* not clear why we have the next two cases, since DisjDecl and
349 DisjType shouldn't have been constructed yet, as they only come from isos *)
350 let declaration r k e =
351 compute_result Ast0.decl e
352 (match Ast0.unwrap e with
353 Ast0.DisjDecl(starter,decls,_,ender) ->
354 disj_cases e starter decls r.VT0.combiner_rec_declaration ender
355 | Ast0.Ddots(dots,whencode) ->
356 k (Ast0.rewrap e (Ast0.Ddots(dots,None)))
357 (* Need special cases for the following so that the type will be
358 considered as a unit, rather than distributed around the
359 declared variable. This needs to be done because of the call to
360 compute_result, ie the processing of each term should make a
361 side-effect on the complete term structure as well as collecting
362 some information about it. So we have to visit each complete
363 term structure. In (all?) other such cases, we visit the terms
364 using rebuilder, which just visits the subterms, rather than
365 reordering their components. *)
366 | Ast0.Init(stg,ty,id,eq,ini,sem) ->
367 bind (match stg with Some stg -> mcode stg | _ -> option_default)
368 (bind (r.VT0.combiner_rec_typeC ty)
369 (bind (r.VT0.combiner_rec_ident id)
370 (bind (mcode eq)
371 (bind (r.VT0.combiner_rec_initialiser ini) (mcode sem)))))
372 | Ast0.UnInit(stg,ty,id,sem) ->
373 bind (match stg with Some stg -> mcode stg | _ -> option_default)
374 (bind (r.VT0.combiner_rec_typeC ty)
375 (bind (r.VT0.combiner_rec_ident id) (mcode sem)))
376 | _ -> k e) in
377
378 let param r k e =
379 compute_result Ast0.param e
380 (match Ast0.unwrap e with
381 Ast0.Param(ty,Some id) ->
382 (* needed for the same reason as in the Init and UnInit cases *)
383 bind (r.VT0.combiner_rec_typeC ty) (r.VT0.combiner_rec_ident id)
384 | _ -> k e) in
385
386 let typeC r k e =
387 compute_result Ast0.typeC e
388 (match Ast0.unwrap e with
389 Ast0.DisjType(starter,types,_,ender) ->
390 disj_cases e starter types r.VT0.combiner_rec_typeC ender
391 | _ -> k e) in
392
393 let initialiser r k i =
394 compute_result Ast0.ini i
395 (match Ast0.unwrap i with
396 Ast0.Idots(dots,whencode) ->
397 k (Ast0.rewrap i (Ast0.Idots(dots,None)))
398 | _ -> k i) in
399
400 let case_line r k e =
401 compute_result Ast0.case_line e
402 (match Ast0.unwrap e with
403 Ast0.DisjCase(starter,case_list,_,ender) ->
404 disj_cases e starter case_list r.VT0.combiner_rec_case_line ender
405 | _ -> k e) in
406
407 let statement r k s =
408 compute_result Ast0.stmt s
409 (match Ast0.unwrap s with
410 Ast0.Nest(started,stm_dots,ender,whencode,multi) ->
411 k (Ast0.rewrap s (Ast0.Nest(started,stm_dots,ender,[],multi)))
412 | Ast0.Dots(dots,whencode) ->
413 k (Ast0.rewrap s (Ast0.Dots(dots,[])))
414 | Ast0.Circles(dots,whencode) ->
415 k (Ast0.rewrap s (Ast0.Circles(dots,[])))
416 | Ast0.Stars(dots,whencode) ->
417 k (Ast0.rewrap s (Ast0.Stars(dots,[])))
418 | Ast0.Disj(starter,statement_dots_list,_,ender) ->
419 disj_cases s starter statement_dots_list r.VT0.combiner_rec_statement_dots
420 ender
421 (* cases for everything with extra mcode *)
422 | Ast0.FunDecl((info,bef),_,_,_,_,_,_,_,_)
423 | Ast0.Decl((info,bef),_) ->
424 bind (nc_mcode ((),(),info,bef,(),-1)) (k s)
425 | Ast0.IfThen(_,_,_,_,_,(info,aft))
426 | Ast0.IfThenElse(_,_,_,_,_,_,_,(info,aft))
427 | Ast0.Iterator(_,_,_,_,_,(info,aft))
428 | Ast0.While(_,_,_,_,_,(info,aft))
429 | Ast0.For(_,_,_,_,_,_,_,_,_,(info,aft)) ->
430 bind (k s) (nc_mcode ((),(),info,aft,(),-1))
431 | _ -> k s
432
433 ) in
434
435 let do_top builder r k e = compute_result builder e (k e) in
436
437 let combiner =
438 V0.flat_combiner bind option_default
439 mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode
440 (do_nothing Ast0.dotsExpr) (do_nothing Ast0.dotsInit)
441 (do_nothing Ast0.dotsParam) (do_nothing Ast0.dotsStmt)
442 (do_nothing Ast0.dotsDecl) (do_nothing Ast0.dotsCase)
443 (do_nothing Ast0.ident) expression typeC initialiser param declaration
444 statement case_line (do_top Ast0.top) in
445 combiner.VT0.combiner_rec_top_level code
446
447 (* --------------------------------------------------------------------- *)
448 (* Traverse the hash tables and find corresponding context nodes that have
449 the same context children *)
450
451 (* this is just a sanity check - really only need to look at the top-level
452 structure *)
453 let equal_mcode (_,_,info1,_,_,_) (_,_,info2,_,_,_) =
454 info1.Ast0.pos_info.Ast0.offset = info2.Ast0.pos_info.Ast0.offset
455
456 let equal_option e1 e2 =
457 match (e1,e2) with
458 (Some x, Some y) -> equal_mcode x y
459 | (None, None) -> true
460 | _ -> false
461
462 let dots fn d1 d2 =
463 match (Ast0.unwrap d1,Ast0.unwrap d2) with
464 (Ast0.DOTS(l1),Ast0.DOTS(l2)) -> List.length l1 = List.length l2
465 | (Ast0.CIRCLES(l1),Ast0.CIRCLES(l2)) -> List.length l1 = List.length l2
466 | (Ast0.STARS(l1),Ast0.STARS(l2)) -> List.length l1 = List.length l2
467 | _ -> false
468
469 let rec equal_ident i1 i2 =
470 match (Ast0.unwrap i1,Ast0.unwrap i2) with
471 (Ast0.Id(name1),Ast0.Id(name2)) -> equal_mcode name1 name2
472 | (Ast0.MetaId(name1,_,_),Ast0.MetaId(name2,_,_)) ->
473 equal_mcode name1 name2
474 | (Ast0.MetaFunc(name1,_,_),Ast0.MetaFunc(name2,_,_)) ->
475 equal_mcode name1 name2
476 | (Ast0.MetaLocalFunc(name1,_,_),Ast0.MetaLocalFunc(name2,_,_)) ->
477 equal_mcode name1 name2
478 | (Ast0.OptIdent(_),Ast0.OptIdent(_)) -> true
479 | (Ast0.UniqueIdent(_),Ast0.UniqueIdent(_)) -> true
480 | _ -> false
481
482 let rec equal_expression e1 e2 =
483 match (Ast0.unwrap e1,Ast0.unwrap e2) with
484 (Ast0.Ident(_),Ast0.Ident(_)) -> true
485 | (Ast0.Constant(const1),Ast0.Constant(const2)) -> equal_mcode const1 const2
486 | (Ast0.FunCall(_,lp1,_,rp1),Ast0.FunCall(_,lp2,_,rp2)) ->
487 equal_mcode lp1 lp2 && equal_mcode rp1 rp2
488 | (Ast0.Assignment(_,op1,_,_),Ast0.Assignment(_,op2,_,_)) ->
489 equal_mcode op1 op2
490 | (Ast0.CondExpr(_,why1,_,colon1,_),Ast0.CondExpr(_,why2,_,colon2,_)) ->
491 equal_mcode why1 why2 && equal_mcode colon1 colon2
492 | (Ast0.Postfix(_,op1),Ast0.Postfix(_,op2)) -> equal_mcode op1 op2
493 | (Ast0.Infix(_,op1),Ast0.Infix(_,op2)) -> equal_mcode op1 op2
494 | (Ast0.Unary(_,op1),Ast0.Unary(_,op2)) -> equal_mcode op1 op2
495 | (Ast0.Binary(_,op1,_),Ast0.Binary(_,op2,_)) -> equal_mcode op1 op2
496 | (Ast0.Paren(lp1,_,rp1),Ast0.Paren(lp2,_,rp2)) ->
497 equal_mcode lp1 lp2 && equal_mcode rp1 rp2
498 | (Ast0.ArrayAccess(_,lb1,_,rb1),Ast0.ArrayAccess(_,lb2,_,rb2)) ->
499 equal_mcode lb1 lb2 && equal_mcode rb1 rb2
500 | (Ast0.RecordAccess(_,pt1,_),Ast0.RecordAccess(_,pt2,_)) ->
501 equal_mcode pt1 pt2
502 | (Ast0.RecordPtAccess(_,ar1,_),Ast0.RecordPtAccess(_,ar2,_)) ->
503 equal_mcode ar1 ar2
504 | (Ast0.Cast(lp1,_,rp1,_),Ast0.Cast(lp2,_,rp2,_)) ->
505 equal_mcode lp1 lp2 && equal_mcode rp1 rp2
506 | (Ast0.SizeOfExpr(szf1,_),Ast0.SizeOfExpr(szf2,_)) ->
507 equal_mcode szf1 szf2
508 | (Ast0.SizeOfType(szf1,lp1,_,rp1),Ast0.SizeOfType(szf2,lp2,_,rp2)) ->
509 equal_mcode szf1 szf2 && equal_mcode lp1 lp2 && equal_mcode rp1 rp2
510 | (Ast0.TypeExp(_),Ast0.TypeExp(_)) -> true
511 | (Ast0.MetaErr(name1,_,_),Ast0.MetaErr(name2,_,_))
512 | (Ast0.MetaExpr(name1,_,_,_,_),Ast0.MetaExpr(name2,_,_,_,_))
513 | (Ast0.MetaExprList(name1,_,_),Ast0.MetaExprList(name2,_,_)) ->
514 equal_mcode name1 name2
515 | (Ast0.EComma(cm1),Ast0.EComma(cm2)) -> equal_mcode cm1 cm2
516 | (Ast0.DisjExpr(starter1,_,mids1,ender1),
517 Ast0.DisjExpr(starter2,_,mids2,ender2)) ->
518 equal_mcode starter1 starter2 &&
519 List.for_all2 equal_mcode mids1 mids2 &&
520 equal_mcode ender1 ender2
521 | (Ast0.NestExpr(starter1,_,ender1,_,m1),
522 Ast0.NestExpr(starter2,_,ender2,_,m2)) ->
523 equal_mcode starter1 starter2 && equal_mcode ender1 ender2 && m1 = m2
524 | (Ast0.Edots(dots1,_),Ast0.Edots(dots2,_))
525 | (Ast0.Ecircles(dots1,_),Ast0.Ecircles(dots2,_))
526 | (Ast0.Estars(dots1,_),Ast0.Estars(dots2,_)) -> equal_mcode dots1 dots2
527 | (Ast0.OptExp(_),Ast0.OptExp(_)) -> true
528 | (Ast0.UniqueExp(_),Ast0.UniqueExp(_)) -> true
529 | _ -> false
530
531 let rec equal_typeC t1 t2 =
532 match (Ast0.unwrap t1,Ast0.unwrap t2) with
533 (Ast0.ConstVol(cv1,_),Ast0.ConstVol(cv2,_)) -> equal_mcode cv1 cv2
534 | (Ast0.BaseType(ty1,stringsa),Ast0.BaseType(ty2,stringsb)) ->
535 List.for_all2 equal_mcode stringsa stringsb
536 | (Ast0.Signed(sign1,_),Ast0.Signed(sign2,_)) ->
537 equal_mcode sign1 sign2
538 | (Ast0.Pointer(_,star1),Ast0.Pointer(_,star2)) ->
539 equal_mcode star1 star2
540 | (Ast0.Array(_,lb1,_,rb1),Ast0.Array(_,lb2,_,rb2)) ->
541 equal_mcode lb1 lb2 && equal_mcode rb1 rb2
542 | (Ast0.EnumName(kind1,_),Ast0.EnumName(kind2,_)) ->
543 equal_mcode kind1 kind2
544 | (Ast0.EnumDef(_,lb1,_,rb1),Ast0.EnumDef(_,lb2,_,rb2)) ->
545 equal_mcode lb1 lb2 && equal_mcode rb1 rb2
546 | (Ast0.StructUnionName(kind1,_),Ast0.StructUnionName(kind2,_)) ->
547 equal_mcode kind1 kind2
548 | (Ast0.FunctionType(ty1,lp1,p1,rp1),Ast0.FunctionType(ty2,lp2,p2,rp2)) ->
549 equal_mcode lp1 lp2 && equal_mcode rp1 rp2
550 | (Ast0.StructUnionDef(_,lb1,_,rb1),
551 Ast0.StructUnionDef(_,lb2,_,rb2)) ->
552 equal_mcode lb1 lb2 && equal_mcode rb1 rb2
553 | (Ast0.TypeName(name1),Ast0.TypeName(name2)) -> equal_mcode name1 name2
554 | (Ast0.MetaType(name1,_),Ast0.MetaType(name2,_)) ->
555 equal_mcode name1 name2
556 | (Ast0.DisjType(starter1,_,mids1,ender1),
557 Ast0.DisjType(starter2,_,mids2,ender2)) ->
558 equal_mcode starter1 starter2 &&
559 List.for_all2 equal_mcode mids1 mids2 &&
560 equal_mcode ender1 ender2
561 | (Ast0.OptType(_),Ast0.OptType(_)) -> true
562 | (Ast0.UniqueType(_),Ast0.UniqueType(_)) -> true
563 | _ -> false
564
565 let equal_declaration d1 d2 =
566 match (Ast0.unwrap d1,Ast0.unwrap d2) with
567 (Ast0.MetaDecl(name1,_),Ast0.MetaDecl(name2,_))
568 | (Ast0.MetaField(name1,_),Ast0.MetaField(name2,_)) ->
569 equal_mcode name1 name2
570 | (Ast0.Init(stg1,_,_,eq1,_,sem1),Ast0.Init(stg2,_,_,eq2,_,sem2)) ->
571 equal_option stg1 stg2 && equal_mcode eq1 eq2 && equal_mcode sem1 sem2
572 | (Ast0.UnInit(stg1,_,_,sem1),Ast0.UnInit(stg2,_,_,sem2)) ->
573 equal_option stg1 stg2 && equal_mcode sem1 sem2
574 | (Ast0.MacroDecl(nm1,lp1,_,rp1,sem1),Ast0.MacroDecl(nm2,lp2,_,rp2,sem2)) ->
575 equal_mcode lp1 lp2 && equal_mcode rp1 rp2 && equal_mcode sem1 sem2
576 | (Ast0.TyDecl(_,sem1),Ast0.TyDecl(_,sem2)) -> equal_mcode sem1 sem2
577 | (Ast0.Ddots(dots1,_),Ast0.Ddots(dots2,_)) -> equal_mcode dots1 dots2
578 | (Ast0.OptDecl(_),Ast0.OptDecl(_)) -> true
579 | (Ast0.UniqueDecl(_),Ast0.UniqueDecl(_)) -> true
580 | (Ast0.DisjDecl _,_) | (_,Ast0.DisjDecl _) ->
581 failwith "DisjDecl not expected here"
582 | _ -> false
583
584 let equal_designator d1 d2 =
585 match (d1,d2) with
586 (Ast0.DesignatorField(dot1,_),Ast0.DesignatorField(dot2,_)) ->
587 equal_mcode dot1 dot2
588 | (Ast0.DesignatorIndex(lb1,_,rb1),Ast0.DesignatorIndex(lb2,_,rb2)) ->
589 (equal_mcode lb1 lb2) && (equal_mcode rb1 rb2)
590 | (Ast0.DesignatorRange(lb1,_,dots1,_,rb1),
591 Ast0.DesignatorRange(lb2,_,dots2,_,rb2)) ->
592 (equal_mcode lb1 lb2) && (equal_mcode dots1 dots2) &&
593 (equal_mcode rb1 rb2)
594 | _ -> false
595
596 let equal_initialiser i1 i2 =
597 match (Ast0.unwrap i1,Ast0.unwrap i2) with
598 (Ast0.MetaInit(name1,_),Ast0.MetaInit(name2,_)) ->
599 equal_mcode name1 name2
600 | (Ast0.InitExpr(_),Ast0.InitExpr(_)) -> true
601 | (Ast0.InitList(lb1,_,rb1,o1),Ast0.InitList(lb2,_,rb2,o2)) ->
602 (* can't compare orderedness, because this can differ between -
603 and + code *)
604 (equal_mcode lb1 lb2) && (equal_mcode rb1 rb2)
605 | (Ast0.InitGccExt(designators1,eq1,_),
606 Ast0.InitGccExt(designators2,eq2,_)) ->
607 (List.for_all2 equal_designator designators1 designators2) &&
608 (equal_mcode eq1 eq2)
609 | (Ast0.InitGccName(_,eq1,_),Ast0.InitGccName(_,eq2,_)) ->
610 equal_mcode eq1 eq2
611 | (Ast0.IComma(cm1),Ast0.IComma(cm2)) -> equal_mcode cm1 cm2
612 | (Ast0.Idots(d1,_),Ast0.Idots(d2,_)) -> equal_mcode d1 d2
613 | (Ast0.OptIni(_),Ast0.OptIni(_)) -> true
614 | (Ast0.UniqueIni(_),Ast0.UniqueIni(_)) -> true
615 | _ -> false
616
617 let equal_parameterTypeDef p1 p2 =
618 match (Ast0.unwrap p1,Ast0.unwrap p2) with
619 (Ast0.VoidParam(_),Ast0.VoidParam(_)) -> true
620 | (Ast0.Param(_,_),Ast0.Param(_,_)) -> true
621 | (Ast0.MetaParam(name1,_),Ast0.MetaParam(name2,_))
622 | (Ast0.MetaParamList(name1,_,_),Ast0.MetaParamList(name2,_,_)) ->
623 equal_mcode name1 name2
624 | (Ast0.PComma(cm1),Ast0.PComma(cm2)) -> equal_mcode cm1 cm2
625 | (Ast0.Pdots(dots1),Ast0.Pdots(dots2))
626 | (Ast0.Pcircles(dots1),Ast0.Pcircles(dots2)) -> equal_mcode dots1 dots2
627 | (Ast0.OptParam(_),Ast0.OptParam(_)) -> true
628 | (Ast0.UniqueParam(_),Ast0.UniqueParam(_)) -> true
629 | _ -> false
630
631 let rec equal_statement s1 s2 =
632 match (Ast0.unwrap s1,Ast0.unwrap s2) with
633 (Ast0.FunDecl(_,fninfo1,_,lp1,_,rp1,lbrace1,_,rbrace1),
634 Ast0.FunDecl(_,fninfo2,_,lp2,_,rp2,lbrace2,_,rbrace2)) ->
635 (List.length fninfo1) = (List.length fninfo2) &&
636 List.for_all2 equal_fninfo fninfo1 fninfo2 &&
637 equal_mcode lp1 lp2 && equal_mcode rp1 rp2 &&
638 equal_mcode lbrace1 lbrace2 && equal_mcode rbrace1 rbrace2
639 | (Ast0.Decl(_,_),Ast0.Decl(_,_)) -> true
640 | (Ast0.Seq(lbrace1,_,rbrace1),Ast0.Seq(lbrace2,_,rbrace2)) ->
641 equal_mcode lbrace1 lbrace2 && equal_mcode rbrace1 rbrace2
642 | (Ast0.ExprStatement(_,sem1),Ast0.ExprStatement(_,sem2)) ->
643 equal_mcode sem1 sem2
644 | (Ast0.IfThen(iff1,lp1,_,rp1,_,_),Ast0.IfThen(iff2,lp2,_,rp2,_,_)) ->
645 equal_mcode iff1 iff2 && equal_mcode lp1 lp2 && equal_mcode rp1 rp2
646 | (Ast0.IfThenElse(iff1,lp1,_,rp1,_,els1,_,_),
647 Ast0.IfThenElse(iff2,lp2,_,rp2,_,els2,_,_)) ->
648 equal_mcode iff1 iff2 &&
649 equal_mcode lp1 lp2 && equal_mcode rp1 rp2 && equal_mcode els1 els2
650 | (Ast0.While(whl1,lp1,_,rp1,_,_),Ast0.While(whl2,lp2,_,rp2,_,_)) ->
651 equal_mcode whl1 whl2 && equal_mcode lp1 lp2 && equal_mcode rp1 rp2
652 | (Ast0.Do(d1,_,whl1,lp1,_,rp1,sem1),Ast0.Do(d2,_,whl2,lp2,_,rp2,sem2)) ->
653 equal_mcode whl1 whl2 && equal_mcode d1 d2 &&
654 equal_mcode lp1 lp2 && equal_mcode rp1 rp2 && equal_mcode sem1 sem2
655 | (Ast0.For(fr1,lp1,_,sem11,_,sem21,_,rp1,_,_),
656 Ast0.For(fr2,lp2,_,sem12,_,sem22,_,rp2,_,_)) ->
657 equal_mcode fr1 fr2 && equal_mcode lp1 lp2 &&
658 equal_mcode sem11 sem12 && equal_mcode sem21 sem22 &&
659 equal_mcode rp1 rp2
660 | (Ast0.Iterator(nm1,lp1,_,rp1,_,_),Ast0.Iterator(nm2,lp2,_,rp2,_,_)) ->
661 equal_mcode lp1 lp2 && equal_mcode rp1 rp2
662 | (Ast0.Switch(switch1,lp1,_,rp1,lb1,_,_,rb1),
663 Ast0.Switch(switch2,lp2,_,rp2,lb2,_,_,rb2)) ->
664 equal_mcode switch1 switch2 && equal_mcode lp1 lp2 &&
665 equal_mcode rp1 rp2 && equal_mcode lb1 lb2 &&
666 equal_mcode rb1 rb2
667 | (Ast0.Break(br1,sem1),Ast0.Break(br2,sem2)) ->
668 equal_mcode br1 br2 && equal_mcode sem1 sem2
669 | (Ast0.Continue(cont1,sem1),Ast0.Continue(cont2,sem2)) ->
670 equal_mcode cont1 cont2 && equal_mcode sem1 sem2
671 | (Ast0.Label(_,dd1),Ast0.Label(_,dd2)) ->
672 equal_mcode dd1 dd2
673 | (Ast0.Goto(g1,_,sem1),Ast0.Goto(g2,_,sem2)) ->
674 equal_mcode g1 g2 && equal_mcode sem1 sem2
675 | (Ast0.Return(ret1,sem1),Ast0.Return(ret2,sem2)) ->
676 equal_mcode ret1 ret2 && equal_mcode sem1 sem2
677 | (Ast0.ReturnExpr(ret1,_,sem1),Ast0.ReturnExpr(ret2,_,sem2)) ->
678 equal_mcode ret1 ret2 && equal_mcode sem1 sem2
679 | (Ast0.MetaStmt(name1,_),Ast0.MetaStmt(name2,_))
680 | (Ast0.MetaStmtList(name1,_),Ast0.MetaStmtList(name2,_)) ->
681 equal_mcode name1 name2
682 | (Ast0.Disj(starter1,_,mids1,ender1),Ast0.Disj(starter2,_,mids2,ender2)) ->
683 equal_mcode starter1 starter2 &&
684 List.for_all2 equal_mcode mids1 mids2 &&
685 equal_mcode ender1 ender2
686 | (Ast0.Nest(starter1,_,ender1,_,m1),Ast0.Nest(starter2,_,ender2,_,m2)) ->
687 equal_mcode starter1 starter2 && equal_mcode ender1 ender2 && m1 = m2
688 | (Ast0.Exp(_),Ast0.Exp(_)) -> true
689 | (Ast0.TopExp(_),Ast0.TopExp(_)) -> true
690 | (Ast0.Ty(_),Ast0.Ty(_)) -> true
691 | (Ast0.TopInit(_),Ast0.TopInit(_)) -> true
692 | (Ast0.Dots(d1,_),Ast0.Dots(d2,_))
693 | (Ast0.Circles(d1,_),Ast0.Circles(d2,_))
694 | (Ast0.Stars(d1,_),Ast0.Stars(d2,_)) -> equal_mcode d1 d2
695 | (Ast0.Include(inc1,name1),Ast0.Include(inc2,name2)) ->
696 equal_mcode inc1 inc2 && equal_mcode name1 name2
697 | (Ast0.Undef(def1,_),Ast0.Undef(def2,_)) ->
698 equal_mcode def1 def2
699 | (Ast0.Define(def1,_,_,_),Ast0.Define(def2,_,_,_)) ->
700 equal_mcode def1 def2
701 | (Ast0.OptStm(_),Ast0.OptStm(_)) -> true
702 | (Ast0.UniqueStm(_),Ast0.UniqueStm(_)) -> true
703 | _ -> false
704
705 and equal_fninfo x y =
706 match (x,y) with
707 (Ast0.FStorage(s1),Ast0.FStorage(s2)) -> equal_mcode s1 s2
708 | (Ast0.FType(_),Ast0.FType(_)) -> true
709 | (Ast0.FInline(i1),Ast0.FInline(i2)) -> equal_mcode i1 i2
710 | (Ast0.FAttr(i1),Ast0.FAttr(i2)) -> equal_mcode i1 i2
711 | _ -> false
712
713 let equal_case_line c1 c2 =
714 match (Ast0.unwrap c1,Ast0.unwrap c2) with
715 (Ast0.Default(def1,colon1,_),Ast0.Default(def2,colon2,_)) ->
716 equal_mcode def1 def2 && equal_mcode colon1 colon2
717 | (Ast0.Case(case1,_,colon1,_),Ast0.Case(case2,_,colon2,_)) ->
718 equal_mcode case1 case2 && equal_mcode colon1 colon2
719 | (Ast0.DisjCase(starter1,_,mids1,ender1),
720 Ast0.DisjCase(starter2,_,mids2,ender2)) ->
721 equal_mcode starter1 starter2 &&
722 List.for_all2 equal_mcode mids1 mids2 &&
723 equal_mcode ender1 ender2
724 | (Ast0.OptCase(_),Ast0.OptCase(_)) -> true
725 | _ -> false
726
727 let rec equal_top_level t1 t2 =
728 match (Ast0.unwrap t1,Ast0.unwrap t2) with
729 (Ast0.DECL(_),Ast0.DECL(_)) -> true
730 | (Ast0.FILEINFO(old_file1,new_file1),Ast0.FILEINFO(old_file2,new_file2)) ->
731 equal_mcode old_file1 old_file2 && equal_mcode new_file1 new_file2
732 | (Ast0.CODE(_),Ast0.CODE(_)) -> true
733 | (Ast0.ERRORWORDS(_),Ast0.ERRORWORDS(_)) -> true
734 | _ -> false
735
736 let root_equal e1 e2 =
737 match (e1,e2) with
738 (Ast0.DotsExprTag(d1),Ast0.DotsExprTag(d2)) -> dots equal_expression d1 d2
739 | (Ast0.DotsParamTag(d1),Ast0.DotsParamTag(d2)) ->
740 dots equal_parameterTypeDef d1 d2
741 | (Ast0.DotsStmtTag(d1),Ast0.DotsStmtTag(d2)) -> dots equal_statement d1 d2
742 | (Ast0.DotsDeclTag(d1),Ast0.DotsDeclTag(d2)) -> dots equal_declaration d1 d2
743 | (Ast0.DotsCaseTag(d1),Ast0.DotsCaseTag(d2)) -> dots equal_case_line d1 d2
744 | (Ast0.IdentTag(i1),Ast0.IdentTag(i2)) -> equal_ident i1 i2
745 | (Ast0.ExprTag(e1),Ast0.ExprTag(e2)) -> equal_expression e1 e2
746 | (Ast0.ArgExprTag(d),_) -> failwith "not possible - iso only"
747 | (Ast0.TypeCTag(t1),Ast0.TypeCTag(t2)) -> equal_typeC t1 t2
748 | (Ast0.ParamTag(p1),Ast0.ParamTag(p2)) -> equal_parameterTypeDef p1 p2
749 | (Ast0.InitTag(d1),Ast0.InitTag(d2)) -> equal_initialiser d1 d2
750 | (Ast0.DeclTag(d1),Ast0.DeclTag(d2)) -> equal_declaration d1 d2
751 | (Ast0.StmtTag(s1),Ast0.StmtTag(s2)) -> equal_statement s1 s2
752 | (Ast0.TopTag(t1),Ast0.TopTag(t2)) -> equal_top_level t1 t2
753 | (Ast0.IsoWhenTag(_),_) | (_,Ast0.IsoWhenTag(_))
754 | (Ast0.IsoWhenTTag(_),_) | (_,Ast0.IsoWhenTTag(_))
755 | (Ast0.IsoWhenFTag(_),_) | (_,Ast0.IsoWhenFTag(_)) ->
756 failwith "only within iso phase"
757 | _ -> false
758
759 let default_context _ =
760 Ast0.CONTEXT(ref(Ast.NOTHING,
761 Ast0.default_token_info,Ast0.default_token_info))
762
763 let traverse minus_table plus_table =
764 Hashtbl.iter
765 (function key ->
766 function (e,l) ->
767 try
768 let (plus_e,plus_l) = Hashtbl.find plus_table key in
769 if root_equal e plus_e &&
770 List.for_all (function x -> x)
771 (List.map2 Common.equal_set l plus_l)
772 then
773 let i = Ast0.fresh_index() in
774 (set_index e i; set_index plus_e i;
775 set_mcodekind e (default_context());
776 set_mcodekind plus_e (default_context()))
777 with Not_found -> ())
778 minus_table
779
780 (* --------------------------------------------------------------------- *)
781 (* contextify the whencode *)
782
783 let contextify_all =
784 let bind x y = () in
785 let option_default = () in
786 let mcode x = () in
787 let do_nothing r k e = Ast0.set_mcodekind e (default_context()); k e in
788
789 V0.flat_combiner bind option_default
790 mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode
791 do_nothing do_nothing do_nothing do_nothing do_nothing do_nothing
792 do_nothing do_nothing do_nothing do_nothing do_nothing do_nothing
793 do_nothing do_nothing do_nothing
794
795 let contextify_whencode =
796 let bind x y = () in
797 let option_default = () in
798
799 let expression r k e =
800 k e;
801 match Ast0.unwrap e with
802 Ast0.NestExpr(_,_,_,Some whencode,_)
803 | Ast0.Edots(_,Some whencode)
804 | Ast0.Ecircles(_,Some whencode)
805 | Ast0.Estars(_,Some whencode) ->
806 contextify_all.VT0.combiner_rec_expression whencode
807 | _ -> () in
808
809 let initialiser r k i =
810 match Ast0.unwrap i with
811 Ast0.Idots(dots,Some whencode) ->
812 contextify_all.VT0.combiner_rec_initialiser whencode
813 | _ -> k i in
814
815 let whencode = function
816 Ast0.WhenNot sd -> contextify_all.VT0.combiner_rec_statement_dots sd
817 | Ast0.WhenAlways s -> contextify_all.VT0.combiner_rec_statement s
818 | Ast0.WhenModifier(_) -> ()
819 | Ast0.WhenNotTrue(e) -> contextify_all.VT0.combiner_rec_expression e
820 | Ast0.WhenNotFalse(e) -> contextify_all.VT0.combiner_rec_expression e in
821
822 let statement r k (s : Ast0.statement) =
823 k s;
824 match Ast0.unwrap s with
825 Ast0.Nest(_,_,_,whn,_)
826 | Ast0.Dots(_,whn) | Ast0.Circles(_,whn) | Ast0.Stars(_,whn) ->
827 List.iter whencode whn
828 | _ -> () in
829
830 let combiner =
831 V0.combiner bind option_default
832 {V0.combiner_functions with
833 VT0.combiner_exprfn = expression;
834 VT0.combiner_initfn = initialiser;
835 VT0.combiner_stmtfn = statement} in
836 combiner.VT0.combiner_rec_top_level
837
838 (* --------------------------------------------------------------------- *)
839
840 (* the first int list is the tokens in the node, the second is the tokens
841 in the descendents *)
842 let minus_table =
843 (Hashtbl.create(50) : (int list, Ast0.anything * int list list) Hashtbl.t)
844 let plus_table =
845 (Hashtbl.create(50) : (int list, Ast0.anything * int list list) Hashtbl.t)
846
847 let iscode t =
848 match Ast0.unwrap t with
849 Ast0.DECL(_) -> true
850 | Ast0.FILEINFO(_) -> true
851 | Ast0.ERRORWORDS(_) -> false
852 | Ast0.CODE(_) -> true
853 | Ast0.OTHER(_) -> failwith "unexpected top level code"
854
855 (* ------------------------------------------------------------------- *)
856 (* alignment of minus and plus *)
857
858 let concat = function
859 [] -> []
860 | [s] -> [s]
861 | l ->
862 let rec loop = function
863 [] -> []
864 | x::rest ->
865 (match Ast0.unwrap x with
866 Ast0.DECL(s) -> let stms = loop rest in s::stms
867 | Ast0.CODE(ss) ->
868 let stms = loop rest in
869 (match Ast0.unwrap ss with
870 Ast0.DOTS(d) -> d@stms
871 | _ -> failwith "no dots allowed in pure plus code")
872 | _ -> failwith "plus code is being discarded") in
873 let res =
874 Compute_lines.compute_statement_dots_lines false
875 (Ast0.rewrap (List.hd l) (Ast0.DOTS (loop l))) in
876 [Ast0.rewrap res (Ast0.CODE res)]
877
878 let collect_up_to m plus =
879 let minfo = Ast0.get_info m in
880 let mend = minfo.Ast0.pos_info.Ast0.logical_end in
881 let rec loop = function
882 [] -> ([],[])
883 | p::plus ->
884 let pinfo = Ast0.get_info p in
885 let pstart = pinfo.Ast0.pos_info.Ast0.logical_start in
886 if pstart > mend
887 then ([],p::plus)
888 else let (plus,rest) = loop plus in (p::plus,rest) in
889 let (plus,rest) = loop plus in
890 (concat plus,rest)
891
892 let realign minus plus =
893 let rec loop = function
894 ([],_) -> failwith "not possible, some context required"
895 | ([m],p) -> ([m],concat p)
896 | (m::minus,plus) ->
897 let (p,plus) = collect_up_to m plus in
898 let (minus,plus) = loop (minus,plus) in
899 (m::minus,p@plus) in
900 loop (minus,plus)
901
902 (* ------------------------------------------------------------------- *)
903 (* check compatible: check that at the top level the minus and plus code is
904 of the same kind. Could go further and make the correspondence between the
905 code between ...s. *)
906
907 let isonly f l = match Ast0.undots l with [s] -> f s | _ -> false
908
909 let isall f l = List.for_all (isonly f) l
910
911 let rec is_exp s =
912 match Ast0.unwrap s with
913 Ast0.Exp(e) -> true
914 | Ast0.Disj(_,stmts,_,_) -> isall is_exp stmts
915 | _ -> false
916
917 let rec is_ty s =
918 match Ast0.unwrap s with
919 Ast0.Ty(e) -> true
920 | Ast0.Disj(_,stmts,_,_) -> isall is_ty stmts
921 | _ -> false
922
923 let rec is_init s =
924 match Ast0.unwrap s with
925 Ast0.TopInit(e) -> true
926 | Ast0.Disj(_,stmts,_,_) -> isall is_init stmts
927 | _ -> false
928
929 let rec is_decl s =
930 match Ast0.unwrap s with
931 Ast0.Decl(_,e) -> true
932 | Ast0.FunDecl(_,_,_,_,_,_,_,_,_) -> true
933 | Ast0.Disj(_,stmts,_,_) -> isall is_decl stmts
934 | _ -> false
935
936 let rec is_fndecl s =
937 match Ast0.unwrap s with
938 Ast0.FunDecl(_,_,_,_,_,_,_,_,_) -> true
939 | Ast0.Disj(_,stmts,_,_) -> isall is_fndecl stmts
940 | _ -> false
941
942 let rec is_toplevel s =
943 match Ast0.unwrap s with
944 Ast0.Decl(_,e) -> true
945 | Ast0.FunDecl(_,_,_,_,_,_,_,_,_) -> true
946 | Ast0.Disj(_,stmts,_,_) -> isall is_toplevel stmts
947 | Ast0.ExprStatement(fc,_) ->
948 (match Ast0.unwrap fc with
949 Ast0.FunCall(_,_,_,_) -> true
950 | _ -> false)
951 | Ast0.Include(_,_) -> true
952 | Ast0.Undef(_,_) -> true
953 | Ast0.Define(_,_,_,_) -> true
954 | _ -> false
955
956 let check_compatible m p =
957 let fail _ =
958 failwith
959 (Printf.sprintf
960 "incompatible minus and plus code starting on lines %d and %d"
961 (Ast0.get_line m) (Ast0.get_line p)) in
962 match (Ast0.unwrap m, Ast0.unwrap p) with
963 (Ast0.DECL(decl1),Ast0.DECL(decl2)) ->
964 if not (is_decl decl1 && is_decl decl2)
965 then fail()
966 | (Ast0.DECL(decl1),Ast0.CODE(code2)) ->
967 let v1 = is_decl decl1 in
968 let v2 = List.for_all is_toplevel (Ast0.undots code2) in
969 if !Flag.make_hrule = None && v1 && not v2 then fail()
970 | (Ast0.CODE(code1),Ast0.DECL(decl2)) ->
971 let v1 = List.for_all is_toplevel (Ast0.undots code1) in
972 let v2 = is_decl decl2 in
973 if v1 && not v2 then fail()
974 | (Ast0.CODE(code1),Ast0.CODE(code2)) ->
975 let v1 = isonly is_init code1 in
976 let v2a = isonly is_init code2 in
977 let v2b = isonly is_exp code2 in
978 if v1
979 then (if not (v2a || v2b) then fail())
980 else
981 let testers = [is_exp;is_ty] in
982 List.iter
983 (function tester ->
984 let v1 = isonly tester code1 in
985 let v2 = isonly tester code2 in
986 if (v1 && not v2) or (!Flag.make_hrule = None && v2 && not v1)
987 then fail())
988 testers;
989 let v1 = isonly is_fndecl code1 in
990 let v2 = List.for_all is_toplevel (Ast0.undots code2) in
991 if !Flag.make_hrule = None && v1 && not v2 then fail()
992 | (Ast0.FILEINFO(_,_),Ast0.FILEINFO(_,_)) -> ()
993 | (Ast0.OTHER(_),Ast0.OTHER(_)) -> ()
994 | _ -> fail()
995
996 (* ------------------------------------------------------------------- *)
997
998 (* returns a list of corresponding minus and plus trees *)
999 let context_neg minus plus =
1000 Hashtbl.clear minus_table;
1001 Hashtbl.clear plus_table;
1002 List.iter contextify_whencode minus;
1003 let (minus,plus) = realign minus plus in
1004 let rec loop = function
1005 ([],[]) -> []
1006 | ([],l) ->
1007 failwith (Printf.sprintf "%d plus things remaining" (List.length l))
1008 | (minus,[]) ->
1009 plus_lines := [];
1010 let _ =
1011 List.map
1012 (function m ->
1013 classify true
1014 (function _ -> Ast0.MINUS(ref([],Ast0.default_token_info)))
1015 minus_table m)
1016 minus in
1017 []
1018 | (((m::minus) as mall),((p::plus) as pall)) ->
1019 let minfo = Ast0.get_info m in
1020 let pinfo = Ast0.get_info p in
1021 let mstart = minfo.Ast0.pos_info.Ast0.logical_start in
1022 let mend = minfo.Ast0.pos_info.Ast0.logical_end in
1023 let pstart = pinfo.Ast0.pos_info.Ast0.logical_start in
1024 let pend = pinfo.Ast0.pos_info.Ast0.logical_end in
1025 if (iscode m or iscode p) &&
1026 (mend + 1 = pstart or pend + 1 = mstart or (* adjacent *)
1027 (mstart <= pstart && mend >= pstart) or
1028 (pstart <= mstart && pend >= mstart)) (* overlapping or nested *)
1029 then
1030 begin
1031 (* ensure that the root of each tree has a unique index,
1032 although it might get overwritten if the node is a context
1033 node *)
1034 let i = Ast0.fresh_index() in
1035 Ast0.set_index m i; Ast0.set_index p i;
1036 check_compatible m p;
1037 collect_plus_lines p;
1038 let _ =
1039 classify true
1040 (function _ -> Ast0.MINUS(ref([],Ast0.default_token_info)))
1041 minus_table m in
1042 let _ = classify false (function c -> Ast0.PLUS c) plus_table p in
1043 traverse minus_table plus_table;
1044 (m,p)::loop(minus,plus)
1045 end
1046 else
1047 if not(iscode m or iscode p)
1048 then loop(minus,plus)
1049 else
1050 if mstart < pstart
1051 then
1052 begin
1053 plus_lines := [];
1054 let _ =
1055 classify true
1056 (function _ -> Ast0.MINUS(ref([],Ast0.default_token_info)))
1057 minus_table m in
1058 loop(minus,pall)
1059 end
1060 else loop(mall,plus) in
1061 loop(minus,plus)