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