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