Coccinelle release 1.0.0-rc13
[bpt/coccinelle.git] / parsing_cocci / function_prototypes.ml
CommitLineData
f537ebc4 1(*
17ba0788
C
2 * Copyright 2012, INRIA
3 * Julia Lawall, Gilles Muller
4 * Copyright 2010-2011, INRIA, University of Copenhagen
f537ebc4
C
5 * Julia Lawall, Rene Rydhof Hansen, Gilles Muller, Nicolas Palix
6 * Copyright 2005-2009, Ecole des Mines de Nantes, University of Copenhagen
7 * Yoann Padioleau, Julia Lawall, Rene Rydhof Hansen, Henrik Stuart, Gilles Muller, Nicolas Palix
8 * This file is part of Coccinelle.
9 *
10 * Coccinelle is free software: you can redistribute it and/or modify
11 * it under the terms of the GNU General Public License as published by
12 * the Free Software Foundation, according to version 2 of the License.
13 *
14 * Coccinelle is distributed in the hope that it will be useful,
15 * but WITHOUT ANY WARRANTY; without even the implied warranty of
16 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
17 * GNU General Public License for more details.
18 *
19 * You should have received a copy of the GNU General Public License
20 * along with Coccinelle. If not, see <http://www.gnu.org/licenses/>.
21 *
22 * The authors reserve the right to distribute this or future versions of
23 * Coccinelle under other licenses.
24 *)
25
26
d6ce1786
C
27# 0 "./function_prototypes.ml"
28(*
29 * Copyright 2012, INRIA
30 * Julia Lawall, Gilles Muller
31 * Copyright 2010-2011, INRIA, University of Copenhagen
32 * Julia Lawall, Rene Rydhof Hansen, Gilles Muller, Nicolas Palix
33 * Copyright 2005-2009, Ecole des Mines de Nantes, University of Copenhagen
34 * Yoann Padioleau, Julia Lawall, Rene Rydhof Hansen, Henrik Stuart, Gilles Muller, Nicolas Palix
35 * This file is part of Coccinelle.
36 *
37 * Coccinelle is free software: you can redistribute it and/or modify
38 * it under the terms of the GNU General Public License as published by
39 * the Free Software Foundation, according to version 2 of the License.
40 *
41 * Coccinelle is distributed in the hope that it will be useful,
42 * but WITHOUT ANY WARRANTY; without even the implied warranty of
43 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
44 * GNU General Public License for more details.
45 *
46 * You should have received a copy of the GNU General Public License
47 * along with Coccinelle. If not, see <http://www.gnu.org/licenses/>.
48 *
49 * The authors reserve the right to distribute this or future versions of
50 * Coccinelle under other licenses.
51 *)
52
53
feec80c3 54# 0 "./function_prototypes.ml"
34e49164
C
55module Ast0 = Ast0_cocci
56module Ast = Ast_cocci
57module V0 = Visitor_ast0
b1b2de81 58module VT0 = Visitor_ast0_types
34e49164 59
ae4735db 60type id = Id of string | Meta of Ast.meta_name
34e49164
C
61
62let rec get_name name =
63 match Ast0.unwrap name with
d3f655c6 64 Ast0.Id(nm) -> [Id(Ast0.unwrap_mcode nm)]
8babbc8f 65 | Ast0.MetaId(nm,_,_,_) | Ast0.MetaFunc(nm,_,_)
d3f655c6 66 | Ast0.MetaLocalFunc(nm,_,_) -> [Meta(Ast0.unwrap_mcode nm)]
d6ce1786 67 | Ast0.AsIdent(id1,id2) -> failwith "not supported"
d3f655c6
C
68 | Ast0.DisjId(_,id_list,_,_) -> List.concat (List.map get_name id_list)
69 | Ast0.OptIdent(id) | Ast0.UniqueIdent(id) ->
70 get_name id
34e49164
C
71
72(* --------------------------------------------------------------------- *)
73(* collect all of the functions *)
74
708f4980
C
75let brace_to_semi (_,arity,info,mcodekind,pos,adj) =
76 let info =
77 (* drop column information, so that with -smpl_spacing the semicolon
78 will come out right after the close parenthesis *)
79 {info with Ast0.pos_info = {info.Ast0.pos_info with Ast0.column = -1}} in
80 (";",Ast0.NONE,info,mcodekind,pos,adj)
34e49164
C
81
82let collect_function (stm : Ast0.statement) =
83 match Ast0.unwrap stm with
84 Ast0.FunDecl(_,fninfo,name,lp,params,rp,lbrace,body,rbrace) ->
85 let stg =
86 match
87 List.filter (function Ast0.FStorage(_) -> true | _ -> false)
88 fninfo with [Ast0.FStorage(s)] -> Some s | _ -> None in
89 let ty =
90 match
91 List.filter (function Ast0.FType(_) -> true | _ -> false)
92 fninfo with [Ast0.FType(t)] -> Some t | _ -> None in
d3f655c6
C
93 List.map
94 (function nm ->
95 (nm,stm,
96 Ast0.copywrap stm
97 (Ast0.Decl((Ast0.default_info(),Ast0.context_befaft()),
98 Ast0.copywrap stm
99 (Ast0.UnInit
100 (stg,
101 Ast0.copywrap stm
102 (Ast0.FunctionType(ty,lp,params,rp)),
103 name,brace_to_semi lbrace))))))
104 (get_name name)
34e49164
C
105 | _ -> []
106
107let collect_functions stmt_dots =
108 List.concat (List.map collect_function (Ast0.undots stmt_dots))
109
65038c61
C
110let drop_positions =
111 let mcode (term,arity,info,mc,_,adj) =
112 (term,arity,info,mc,ref [],adj) in
113 let donothing r k e = k e in
114 let res =
115 V0.flat_rebuilder
116 mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode
117 donothing donothing donothing donothing donothing donothing
118 donothing donothing donothing donothing donothing donothing donothing
119 donothing donothing in
120 res.VT0.rebuilder_rec_statement
121
34e49164
C
122let get_all_functions rule =
123 let res =
124 match Ast0.unwrap rule with
65038c61 125 Ast0.NONDECL(stmt) -> collect_function stmt
34e49164
C
126 | Ast0.CODE(rule_elem_dots) -> collect_functions rule_elem_dots
127 | _ -> [] in
128 List.map
129 (function (nm,def,vl) ->
b1b2de81 130 (nm,
65038c61
C
131 (def,
132 drop_positions
133 ((Iso_pattern.rebuild_mcode None).VT0.rebuilder_rec_statement vl))))
34e49164
C
134 res
135
136(* --------------------------------------------------------------------- *)
137(* try to match up the functions *)
138
139(* pass through the - and + functions in lockstep, until one runs out.
140Then process the remaining minuses, if any. If we can find another
141function of the same name for either the current - or + function, take that
142one. Otherwise, align the two current ones. *)
143
144let rec align all_minus all_plus =
145 let rec loop = function
146 ([],_) -> []
147 | ((mname,(mdef,mproto))::minus,[]) ->
148 (try
149 let (_,pproto) = List.assoc mname all_plus in
150 (mname,mdef,mproto,Some pproto)::(loop (minus,[]))
151 with Not_found -> (mname,mdef,mproto,None)::(loop (minus, [])))
152 | ((mname,(mdef,mproto))::minus,(pname,(pdef,pproto))::plus) ->
153 if mname = pname
154 then (mname,mdef,mproto,Some pproto)::(loop (minus, []))
155 else
156 (try
157 let (_,pproto_for_minus) = List.assoc mname all_plus in
158 (try
159 let _ = List.assoc mname all_plus in
160 (* protos that match both *)
161 (mname,mdef,mproto,Some pproto_for_minus)::(loop (minus, plus))
162 with Not_found ->
163 (* proto that matches only minus *)
164 (mname,mdef,mproto,Some pproto_for_minus)::
165 (loop (minus, ((pname,(pdef,pproto))::plus))))
166 with Not_found ->
167 (try
168 let _ = List.assoc mname all_plus in
169 (* proto only for plus *)
170 (mname,mdef,mproto,None)::(loop (minus, plus))
171 with Not_found ->
172 (* protos for no one *)
173 (mname,mdef,mproto,Some pproto)::(loop (minus, plus)))) in
174 List.filter changed_proto (loop (all_minus, all_plus))
175
176(* --------------------------------------------------------------------- *)
177
178and strip =
179 let donothing r k e =
951c7801
C
180 {(Ast0.wrap (Ast0.unwrap (k e))) with
181 Ast0.mcodekind = ref (Ast0.PLUS Ast.ONE)} in
708f4980 182 let mcode (mc,_,_,_,_,_) =
951c7801 183 (mc,Ast0.NONE,Ast0.default_info(),Ast0.PLUS Ast.ONE,
8f657093 184 ref [],-1) in
34e49164
C
185
186 (* need a case for everything that has an unvisited component and can be in
97111a47
C
187 a function prototype. Also get rid of constraints because pcre
188 constraints cannot be compared. *)
34e49164
C
189
190 let ident r k e =
191 donothing r k
192 (Ast0.rewrap e
193 (match Ast0.unwrap e with
8babbc8f 194 Ast0.MetaId(nm,constraints,seed,pure) ->
97111a47 195 Ast0.MetaId(nm,Ast.IdNoConstraint,seed,Ast0.Pure)
34e49164 196 | Ast0.MetaFunc(nm,constraints,pure) ->
97111a47 197 Ast0.MetaFunc(nm,Ast.IdNoConstraint,Ast0.Pure)
34e49164 198 | Ast0.MetaLocalFunc(nm,constraints,pure) ->
97111a47 199 Ast0.MetaLocalFunc(nm,Ast.IdNoConstraint,Ast0.Pure)
34e49164
C
200 | e -> e)) in
201
202 let typeC r k e =
203 donothing r k
204 (Ast0.rewrap e
205 (match Ast0.unwrap e with
206 Ast0.MetaType(nm,pure) -> Ast0.MetaType(nm,Ast0.Pure)
207 | e -> e)) in
208
209 let param r k e =
210 donothing r k
211 (Ast0.rewrap e
212 (match Ast0.unwrap e with
213 Ast0.MetaParam(nm,pure) ->
214 Ast0.MetaParam(nm,Ast0.Pure)
215 | Ast0.MetaParamList(nm,lenname,pure) ->
216 Ast0.MetaParamList(nm,lenname,Ast0.Pure)
217 | e -> e)) in
218
b1b2de81 219 V0.flat_rebuilder
34e49164 220 mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode mcode
34e49164
C
221 donothing donothing donothing donothing donothing donothing
222 ident donothing typeC donothing param donothing donothing
223 donothing donothing
224
225and changed_proto = function
226 (mname,mdef,mproto,None) -> true
227 | (mname,mdef,mproto,Some pproto) ->
b1b2de81
C
228 not ((strip.VT0.rebuilder_rec_statement mproto) =
229 (strip.VT0.rebuilder_rec_statement pproto))
34e49164
C
230
231(* --------------------------------------------------------------------- *)
232(* make rules *)
233
234let rec drop_param_name p =
235 Ast0.rewrap p
236 (match Ast0.unwrap p with
237 Ast0.Param(p,_) -> Ast0.Param(p,None)
238 | Ast0.OptParam(p) -> Ast0.OptParam(drop_param_name p)
239 | Ast0.UniqueParam(p) -> Ast0.UniqueParam(p)
240 | p -> p)
241
242let drop_names dec =
b1b2de81 243 let dec = (Iso_pattern.rebuild_mcode None).VT0.rebuilder_rec_statement dec in
34e49164
C
244 match Ast0.unwrap dec with
245 Ast0.Decl(info,uninit) ->
246 (match Ast0.unwrap uninit with
247 Ast0.UnInit(stg,typ,name,sem) ->
248 (match Ast0.unwrap typ with
249 Ast0.FunctionType(ty,lp,params,rp) ->
250 let params =
251 match Ast0.unwrap params with
252 Ast0.DOTS(l) ->
253 Ast0.rewrap params (Ast0.DOTS(List.map drop_param_name l))
254 | Ast0.CIRCLES(l) ->
255 Ast0.rewrap params
256 (Ast0.CIRCLES(List.map drop_param_name l))
257 | Ast0.STARS(l) -> failwith "unexpected stars" in
258 Ast0.rewrap dec
259 (Ast0.Decl
260 (info,
261 Ast0.rewrap uninit
262 (Ast0.UnInit
263 (stg,
264 Ast0.rewrap typ
265 (Ast0.FunctionType(ty,lp,params,rp)),
266 name,sem))))
267 | _ -> failwith "function prototypes: unexpected type")
268 | _ -> failwith "unexpected declaration")
269 | _ -> failwith "unexpected term"
270
271let ct = ref 0
272
faf9a90c 273let new_name name =
34e49164
C
274 let n = !ct in
275 ct := !ct + 1;
276 name^"__"^(string_of_int n)
277
278let rec rename_param old_name all param =
279 match Ast0.unwrap param with
280 Ast0.Param(ty,Some id) when all ->
281 (match Ast0.unwrap id with
708f4980 282 Ast0.MetaId
8babbc8f 283 (((_,name),arity,info,mcodekind,pos,adj),constraints,seed,pure) ->
34e49164
C
284 let nm = ("__no_name__",new_name name) in
285 let new_id =
286 Ast0.rewrap id
287 (Ast0.MetaId
8babbc8f 288 ((nm,arity,info,mcodekind,pos,adj),constraints,seed,
ae4735db 289 Ast0.Pure)) in
34e49164
C
290 ([Ast.MetaIdDecl(Ast.NONE,nm)],
291 Ast0.rewrap param (Ast0.Param(ty,Some new_id)))
292 | _ -> ([],param))
293 | Ast0.Pdots(d) ->
294 let nm = (old_name,new_name "__P") in
295 let nml = (old_name,new_name "__n") in
296 let new_id =
297 Ast0.rewrap param
298 (Ast0.MetaParamList(Ast0.rewrap_mcode d nm,
88e71198 299 Ast0.MetaListLen (Ast0.rewrap_mcode d nml),
34e49164 300 Ast0.Pure)) in
88e71198
C
301 ([Ast.MetaParamListDecl(Ast.NONE,nm,Ast.MetaLen nml);
302 Ast.MetaListlenDecl(nml)],
34e49164
C
303 new_id)
304 | Ast0.OptParam(p) ->
305 let (metavars,p) = rename_param old_name all p in
306 (metavars,Ast0.rewrap param (Ast0.OptParam(p)))
307 | Ast0.UniqueParam(p) ->
308 let (metavars,p) = rename_param old_name all p in
309 (metavars,Ast0.rewrap param (Ast0.UniqueParam(p)))
310 | _ -> ([],param)
311
312(* try to convert names in the - parameter list to new metavariables, to
313account for spelling mistakes on the part of the programmer *)
314let fresh_names old_name mdef dec =
315 let res = ([],[],dec,mdef) in
316 match Ast0.unwrap dec with
317 Ast0.Decl(info,uninit) ->
318 (match Ast0.unwrap uninit with
319 Ast0.UnInit(stg,typ,name,sem) ->
320 (match Ast0.unwrap typ with
321 Ast0.FunctionType(ty,lp,params,rp) ->
322 let (metavars,newdec) =
323 let (metavars,l) =
324 List.split
325 (List.map (rename_param old_name true)
326 (Ast0.undots params)) in
327 (List.concat metavars,
328 Ast0.rewrap dec
329 (Ast0.Decl
330 (info,
331 Ast0.rewrap uninit
332 (Ast0.UnInit
333 (stg,
334 Ast0.rewrap typ
335 (Ast0.FunctionType
336 (ty,lp,Ast0.rewrap params (Ast0.DOTS(l)),
337 rp)),
338 name,sem))))) in
339 let (def_metavars,newdef) =
340 match Ast0.unwrap mdef with
341 Ast0.FunDecl(x,fninfo,name,lp,params,rp,lb,body,rb) ->
342 let (def_metavars,def_l) =
343 List.split
344 (List.map (rename_param old_name false)
345 (Ast0.undots params)) in
346 (List.concat def_metavars,
347 Ast0.rewrap mdef
348 (Ast0.FunDecl(x,fninfo,name,lp,
349 Ast0.rewrap params (Ast0.DOTS(def_l)),
350 rp,lb,body,rb)))
351 | _ -> failwith "unexpected function definition" in
352 (metavars,def_metavars,newdec,newdef)
353 | _ -> res)
354 | _ -> res)
355 | _ -> res
356
357(* since there is no + counterpart, the function must be completely deleted *)
358let no_names dec =
359 match Ast0.unwrap dec with
360 Ast0.Decl(info,uninit) ->
361 (match Ast0.unwrap uninit with
362 Ast0.UnInit(stg,typ,name,sem) ->
363 (match Ast0.unwrap typ with
364 Ast0.FunctionType(ty,lp,params,rp) ->
365 Ast0.rewrap dec
366 (Ast0.Decl
367 (info,
368 Ast0.rewrap uninit
369 (Ast0.UnInit
370 (stg,
371 Ast0.rewrap typ
372 (Ast0.FunctionType
373 (ty,lp,
374 Ast0.rewrap params
375 (let info = Ast0.get_info params in
376 let mcodekind =
377 (* use the mcodekind of an atomic minused
378 thing *)
379 Ast0.get_mcode_mcodekind lp in
380 let pdots =
381 ("...",Ast0.NONE,info,mcodekind,
8f657093 382 ref [],-1) in
34e49164
C
383 Ast0.DOTS
384 ([Ast0.rewrap params
385 (Ast0.Pdots(pdots))])),
386 rp)),
387 name,sem))))
388 | _ -> dec)
389 | _ -> dec)
390 | _ -> dec
391
65038c61
C
392let mkcode proto =
393 Ast0.copywrap proto (Ast0.CODE(Ast0.copywrap proto (Ast0.DOTS [proto])))
394
34e49164 395let merge mproto pproto =
65038c61
C
396 let mproto = Compute_lines.compute_lines true [mkcode mproto] in
397 let pproto = Compute_lines.compute_lines true [mkcode pproto] in
34e49164 398 let (m,p) = List.split(Context_neg.context_neg mproto pproto) in
faf9a90c 399 Insert_plus.insert_plus m p true (* no isos for protos *);
34e49164 400 (* convert to ast so that the + code will fall down to the tokens
65038c61 401 and off the artificially added Ast0.CODE *)
34e49164
C
402 let mproto = Ast0toast.ast0toast_toplevel (List.hd mproto) in
403 (* clean up the wrapping added above *)
404 match Ast.unwrap mproto with
65038c61 405 Ast.CODE mproto -> List.hd (Ast.undots mproto)
34e49164
C
406 | _ -> failwith "not possible"
407
408let make_rule rule_name = function
409 (mname,mdef,mproto,Some pproto) ->
410 let (metavars,mdef_metavars,mproto,mdef) =
411 fresh_names rule_name mdef mproto in
412 let no_name_mproto = drop_names mproto in
413 let no_name_pproto = drop_names pproto in
414 (metavars,mdef_metavars,
415 [merge mproto pproto; merge no_name_mproto no_name_pproto],mdef)
416 | (mname,mdef,mproto,None) ->
417 ([],[],[Ast0toast.statement(no_names mproto)],mdef)
418
419(* --------------------------------------------------------------------- *)
420
421let reinsert mdefs minus =
422 let table =
423 List.map
424 (function x ->
425 match Ast0.unwrap x with
426 Ast0.FunDecl(_,fninfo,name,lp,params,rp,lbrace,body,rbrace) ->
427 (name,x)
428 | _ -> failwith "bad mdef")
429 mdefs in
430 List.map
431 (function x ->
432 match Ast0.unwrap x with
65038c61 433 Ast0.NONDECL(stmt) ->
34e49164
C
434 (match Ast0.unwrap stmt with
435 Ast0.FunDecl(_,fninfo,name,lp,params,rp,lbrace,body,rbrace) ->
65038c61 436 (try Ast0.rewrap x (Ast0.NONDECL(List.assoc name table))
34e49164
C
437 with Not_found -> x)
438 | _ -> x)
439 | Ast0.CODE(rule_elem_dots) ->
440 (* let's hope there are no functions in here... *)
441 x
442 | _ -> x)
443 minus
444
445(* --------------------------------------------------------------------- *)
446(* entry point *)
447
448let rec split4 = function
449 [] -> ([],[],[],[])
450 | (a,b,c,d)::rest ->
451 let (ax,bx,cx,dx) = split4 rest in (a::ax,b::bx,c::cx,d::dx)
452
65038c61
C
453let mk_ast_code proto =
454 Ast.rewrap proto (Ast.CODE(Ast.rewrap proto (Ast.DOTS [proto])))
455
faf9a90c 456let process rule_name rule_metavars dropped_isos minus plus ruletype =
34e49164
C
457 let minus_functions = List.concat (List.map get_all_functions minus) in
458 match minus_functions with
459 [] -> ((rule_metavars,minus),None)
460 | _ ->
461 let plus_functions =
462 List.concat (List.map get_all_functions plus) in
463 let protos = align minus_functions plus_functions in
464 let (metavars,mdef_metavars,rules,mdefs) =
465 split4(List.map (make_rule rule_name) protos) in
466 let metavars = List.concat metavars in
467 let mdef_metavars = (List.concat mdef_metavars) @ rule_metavars in
468 let rules = List.concat rules in
469 let minus = reinsert mdefs minus in
470 match rules with
471 [] -> ((rule_metavars,minus),None)
472 | [x] ->
473 (* probably not possible, since there is always the version with
474 variables and the version without *)
475 ((mdef_metavars,minus),
faf9a90c 476 Some
34e49164
C
477 (metavars,
478 Ast.CocciRule
479 ("proto for "^rule_name,
480 (Ast.Dep rule_name,dropped_isos,Ast.Forall),
65038c61 481 [mk_ast_code x],
faf9a90c 482 [false],ruletype)))
34e49164
C
483 | x::_ ->
484 let drules =
485 List.map (function x -> Ast.rewrap x (Ast.DOTS [x])) rules in
486 let res =
487 Ast.CocciRule
488 ("proto for "^rule_name,
489 (Ast.Dep rule_name,dropped_isos,Ast.Forall),
65038c61 490 [mk_ast_code (Ast.rewrap x (Ast.Disj drules))],
faf9a90c 491 [false],ruletype) in
34e49164 492 ((mdef_metavars,minus),Some(metavars,res))