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