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