Release coccinelle-0.2.4
[bpt/coccinelle.git] / parsing_cocci / type_infer.ml
CommitLineData
9bc82bae
C
1(*
2 * Copyright 2010, INRIA, University of Copenhagen
3 * Julia Lawall, Rene Rydhof Hansen, Gilles Muller, Nicolas Palix
4 * Copyright 2005-2009, Ecole des Mines de Nantes, University of Copenhagen
5 * Yoann Padioleau, Julia Lawall, Rene Rydhof Hansen, Henrik Stuart, Gilles Muller, Nicolas Palix
6 * This file is part of Coccinelle.
7 *
8 * Coccinelle is free software: you can redistribute it and/or modify
9 * it under the terms of the GNU General Public License as published by
10 * the Free Software Foundation, according to version 2 of the License.
11 *
12 * Coccinelle is distributed in the hope that it will be useful,
13 * but WITHOUT ANY WARRANTY; without even the implied warranty of
14 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
15 * GNU General Public License for more details.
16 *
17 * You should have received a copy of the GNU General Public License
18 * along with Coccinelle. If not, see <http://www.gnu.org/licenses/>.
19 *
20 * The authors reserve the right to distribute this or future versions of
21 * Coccinelle under other licenses.
22 *)
23
24
c491d8ee
C
25(*
26 * Copyright 2010, INRIA, University of Copenhagen
27 * Julia Lawall, Rene Rydhof Hansen, Gilles Muller, Nicolas Palix
28 * Copyright 2005-2009, Ecole des Mines de Nantes, University of Copenhagen
29 * Yoann Padioleau, Julia Lawall, Rene Rydhof Hansen, Henrik Stuart, Gilles Muller, Nicolas Palix
30 * This file is part of Coccinelle.
31 *
32 * Coccinelle is free software: you can redistribute it and/or modify
33 * it under the terms of the GNU General Public License as published by
34 * the Free Software Foundation, according to version 2 of the License.
35 *
36 * Coccinelle is distributed in the hope that it will be useful,
37 * but WITHOUT ANY WARRANTY; without even the implied warranty of
38 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
39 * GNU General Public License for more details.
40 *
41 * You should have received a copy of the GNU General Public License
42 * along with Coccinelle. If not, see <http://www.gnu.org/licenses/>.
43 *
44 * The authors reserve the right to distribute this or future versions of
45 * Coccinelle under other licenses.
46 *)
47
48
34e49164
C
49module T = Type_cocci
50module Ast = Ast_cocci
51module Ast0 = Ast0_cocci
52module V0 = Visitor_ast0
b1b2de81 53module VT0 = Visitor_ast0_types
34e49164
C
54
55(* Type inference:
56Just propagates information based on declarations. Could try to infer
57more precise information about expression metavariables, but not sure it is
58worth it. The most obvious goal is to distinguish between test expressions
59that have pointer, integer, and boolean type when matching isomorphisms,
60but perhaps other needs will become apparent. *)
61
62(* "functions" that return a boolean value *)
63let bool_functions = ["likely";"unlikely"]
64
65let err wrapped ty s =
66 T.typeC ty; Format.print_newline();
67 failwith (Printf.sprintf "line %d: %s" (Ast0.get_line wrapped) s)
68
ae4735db 69type id = Id of string | Meta of Ast.meta_name
34e49164 70
faf9a90c
C
71let int_type = T.BaseType(T.IntType)
72let bool_type = T.BaseType(T.BoolType)
73let char_type = T.BaseType(T.CharType)
74let float_type = T.BaseType(T.FloatType)
1eddfd50
C
75let size_type = T.BaseType(T.SizeType)
76let ssize_type = T.BaseType(T.SSizeType)
77let ptrdiff_type = T.BaseType(T.PtrDiffType)
faf9a90c 78
34e49164
C
79let rec lub_type t1 t2 =
80 match (t1,t2) with
81 (None,None) -> None
82 | (None,Some t) -> t2
83 | (Some t,None) -> t1
84 | (Some t1,Some t2) ->
85 let rec loop = function
86 (T.Unknown,t2) -> t2
87 | (t1,T.Unknown) -> t1
88 | (T.ConstVol(cv1,ty1),T.ConstVol(cv2,ty2)) when cv1 = cv2 ->
89 T.ConstVol(cv1,loop(ty1,ty2))
91eba41f
C
90
91 (* pad: in pointer arithmetic, as in ptr+1, the lub must be ptr *)
34e49164
C
92 | (T.Pointer(ty1),T.Pointer(ty2)) ->
93 T.Pointer(loop(ty1,ty2))
94 | (ty1,T.Pointer(ty2)) -> T.Pointer(ty2)
95 | (T.Pointer(ty1),ty2) -> T.Pointer(ty1)
91eba41f 96
34e49164
C
97 | (T.Array(ty1),T.Array(ty2)) -> T.Array(loop(ty1,ty2))
98 | (T.TypeName(s1),t2) -> t2
99 | (t1,T.TypeName(s1)) -> t1
100 | (t1,_) -> t1 in (* arbitrarily pick the first, assume type correct *)
101 Some (loop (t1,t2))
102
103let lub_envs envs =
104 List.fold_left
105 (function acc ->
106 function env ->
107 List.fold_left
108 (function acc ->
109 function (var,ty) ->
110 let (relevant,irrelevant) =
111 List.partition (function (x,_) -> x = var) acc in
112 match relevant with
113 [] -> (var,ty)::acc
114 | [(x,ty1)] ->
115 (match lub_type (Some ty) (Some ty1) with
116 Some new_ty -> (var,new_ty)::irrelevant
117 | None -> irrelevant)
118 | _ -> failwith "bad type environment")
119 acc env)
120 [] envs
121
122let rec propagate_types env =
123 let option_default = None in
124 let bind x y = option_default in (* no generic way of combining types *)
125
34e49164
C
126 let ident r k i =
127 match Ast0.unwrap i with
128 Ast0.Id(id) ->
129 (try Some(List.assoc (Id(Ast0.unwrap_mcode id)) env)
130 with Not_found -> None)
131 | Ast0.MetaId(id,_,_) ->
132 (try Some(List.assoc (Meta(Ast0.unwrap_mcode id)) env)
133 with Not_found -> None)
134 | _ -> k i in
135
136 let strip_cv = function
137 Some (T.ConstVol(_,t)) -> Some t
138 | t -> t in
139
faf9a90c
C
140 (* types that might be integer types. should char be allowed? *)
141 let rec is_int_type = function
142 T.BaseType(T.IntType)
143 | T.BaseType(T.LongType)
144 | T.BaseType(T.ShortType)
145 | T.MetaType(_,_,_)
146 | T.TypeName _
0708f913 147 | T.EnumName _
faf9a90c
C
148 | T.SignedT(_,None) -> true
149 | T.SignedT(_,Some ty) -> is_int_type ty
150 | _ -> false in
151
34e49164
C
152 let expression r k e =
153 let res = k e in
154 let ty =
155 match Ast0.unwrap e with
951c7801
C
156 (* pad: the type of id is set in the ident visitor *)
157 Ast0.Ident(id) -> Ast0.set_type e res; res
158 | Ast0.Constant(const) ->
159 (match Ast0.unwrap_mcode const with
160 Ast.String(_) -> Some (T.Pointer(char_type))
161 | Ast.Char(_) -> Some (char_type)
162 | Ast.Int(_) -> Some (int_type)
163 | Ast.Float(_) -> Some (float_type))
164 (* pad: note that in C can do either ptr(...) or ( *ptr)(...)
165 * so I am not sure this code is enough.
166 *)
167 | Ast0.FunCall(fn,lp,args,rp) ->
168 (match Ast0.get_type fn with
169 Some (T.FunctionPointer(ty)) -> Some ty
170 | _ ->
171 (match Ast0.unwrap fn with
172 Ast0.Ident(id) ->
173 (match Ast0.unwrap id with
174 Ast0.Id(id) ->
175 if List.mem (Ast0.unwrap_mcode id) bool_functions
176 then Some(bool_type)
177 else None
178 | _ -> None)
179 | _ -> None))
180 | Ast0.Assignment(exp1,op,exp2,_) ->
181 let ty = lub_type (Ast0.get_type exp1) (Ast0.get_type exp2) in
182 Ast0.set_type exp1 ty; Ast0.set_type exp2 ty; ty
183 | Ast0.CondExpr(exp1,why,Some exp2,colon,exp3) ->
184 let ty = lub_type (Ast0.get_type exp2) (Ast0.get_type exp3) in
185 Ast0.set_type exp2 ty; Ast0.set_type exp3 ty; ty
186 | Ast0.CondExpr(exp1,why,None,colon,exp3) -> Ast0.get_type exp3
187 | Ast0.Postfix(exp,op) | Ast0.Infix(exp,op) -> (* op is dec or inc *)
188 Ast0.get_type exp
189 | Ast0.Unary(exp,op) ->
190 (match Ast0.unwrap_mcode op with
191 Ast.GetRef ->
192 (match Ast0.get_type exp with
193 None -> Some (T.Pointer(T.Unknown))
194 | Some t -> Some (T.Pointer(t)))
195 | Ast.DeRef ->
196 (match Ast0.get_type exp with
197 Some (T.Pointer(t)) -> Some t
198 | _ -> None)
199 | Ast.UnPlus -> Ast0.get_type exp
200 | Ast.UnMinus -> Ast0.get_type exp
201 | Ast.Tilde -> Ast0.get_type exp
202 | Ast.Not -> Some(bool_type))
203 | Ast0.Nested(exp1,op,exp2) -> failwith "nested in type inf not possible"
204 | Ast0.Binary(exp1,op,exp2) ->
205 let ty1 = Ast0.get_type exp1 in
206 let ty2 = Ast0.get_type exp2 in
207 let same_type = function
208 (None,None) -> Some (int_type)
91eba41f 209
951c7801
C
210 (* pad: pointer arithmetic handling as in ptr+1 *)
211 | (Some (T.Pointer ty1),Some ty2) when is_int_type ty2 ->
212 Some (T.Pointer ty1)
213 | (Some ty1,Some (T.Pointer ty2)) when is_int_type ty1 ->
214 Some (T.Pointer ty2)
91eba41f 215
951c7801
C
216 | (t1,t2) ->
217 let ty = lub_type t1 t2 in
218 Ast0.set_type exp1 ty; Ast0.set_type exp2 ty; ty in
219 (match Ast0.unwrap_mcode op with
220 Ast.Arith(op) -> same_type (ty1, ty2)
aa721442
C
221 | Ast.Logical(Ast.AndLog) | Ast.Logical(Ast.OrLog) ->
222 Some(bool_type)
951c7801
C
223 | Ast.Logical(op) ->
224 let ty = lub_type ty1 ty2 in
aa721442
C
225 Ast0.set_type exp1 ty; Ast0.set_type exp2 ty;
226 Some(bool_type))
951c7801
C
227 | Ast0.Paren(lp,exp,rp) -> Ast0.get_type exp
228 | Ast0.ArrayAccess(exp1,lb,exp2,rb) ->
229 (match strip_cv (Ast0.get_type exp2) with
230 None -> Ast0.set_type exp2 (Some(int_type))
231 | Some(ty) when is_int_type ty -> ()
aa721442
C
232 | Some(Type_cocci.Unknown) ->
233 (* unknown comes from param types, not sure why this
234 is not just None... *)
235 Ast0.set_type exp2 (Some(int_type))
951c7801
C
236 | Some ty -> err exp2 ty "bad type for an array index");
237 (match strip_cv (Ast0.get_type exp1) with
238 None -> None
239 | Some (T.Array(ty)) -> Some ty
240 | Some (T.Pointer(ty)) -> Some ty
241 | Some (T.MetaType(_,_,_)) -> None
242 | Some x -> err exp1 x "ill-typed array reference")
243 (* pad: should handle structure one day and look 'field' in environment *)
244 | Ast0.RecordAccess(exp,pt,field) ->
245 (match strip_cv (Ast0.get_type exp) with
246 None -> None
e6509c05 247 | Some (T.StructUnionName(_,_)) -> None
951c7801
C
248 | Some (T.TypeName(_)) -> None
249 | Some (T.MetaType(_,_,_)) -> None
250 | Some x -> err exp x "non-structure type in field ref")
251 | Ast0.RecordPtAccess(exp,ar,field) ->
252 (match strip_cv (Ast0.get_type exp) with
253 None -> None
254 | Some (T.Pointer(t)) ->
255 (match strip_cv (Some t) with
256 | Some (T.Unknown) -> None
257 | Some (T.MetaType(_,_,_)) -> None
258 | Some (T.TypeName(_)) -> None
e6509c05 259 | Some (T.StructUnionName(_,_)) -> None
951c7801
C
260 | Some x ->
261 err exp (T.Pointer(t))
262 "non-structure pointer type in field ref"
263 | _ -> failwith "not possible")
264 | Some (T.MetaType(_,_,_)) -> None
265 | Some (T.TypeName(_)) -> None
266 | Some x -> err exp x "non-structure pointer type in field ref")
267 | Ast0.Cast(lp,ty,rp,exp) -> Some(Ast0.ast0_type_to_type ty)
268 | Ast0.SizeOfExpr(szf,exp) -> Some(int_type)
269 | Ast0.SizeOfType(szf,lp,ty,rp) -> Some(int_type)
270 | Ast0.TypeExp(ty) -> None
271 | Ast0.MetaErr(name,_,_) -> None
272 | Ast0.MetaExpr(name,_,Some [ty],_,_) -> Some ty
273 | Ast0.MetaExpr(name,_,ty,_,_) -> None
274 | Ast0.MetaExprList(name,_,_) -> None
275 | Ast0.EComma(cm) -> None
276 | Ast0.DisjExpr(_,exp_list,_,_) ->
277 let types = List.map Ast0.get_type exp_list in
278 let combined = List.fold_left lub_type None types in
279 (match combined with
280 None -> None
281 | Some t ->
282 List.iter (function e -> Ast0.set_type e (Some t)) exp_list;
283 Some t)
284 | Ast0.NestExpr(starter,expr_dots,ender,None,multi) ->
285 let _ = r.VT0.combiner_rec_expression_dots expr_dots in None
286 | Ast0.NestExpr(starter,expr_dots,ender,Some e,multi) ->
287 let _ = r.VT0.combiner_rec_expression_dots expr_dots in
288 let _ = r.VT0.combiner_rec_expression e in None
289 | Ast0.Edots(_,None) | Ast0.Ecircles(_,None) | Ast0.Estars(_,None) ->
290 None
291 | Ast0.Edots(_,Some e) | Ast0.Ecircles(_,Some e)
292 | Ast0.Estars(_,Some e) ->
293 let _ = r.VT0.combiner_rec_expression e in None
294 | Ast0.OptExp(exp) -> Ast0.get_type exp
295 | Ast0.UniqueExp(exp) -> Ast0.get_type exp in
296 Ast0.set_type e ty;
297 ty in
34e49164 298
34e49164
C
299 let rec strip id =
300 match Ast0.unwrap id with
951c7801 301 Ast0.Id(name) -> Id(Ast0.unwrap_mcode name)
34e49164
C
302 | Ast0.MetaId(name,_,_) -> Meta(Ast0.unwrap_mcode name)
303 | Ast0.MetaFunc(name,_,_) -> Meta(Ast0.unwrap_mcode name)
304 | Ast0.MetaLocalFunc(name,_,_) -> Meta(Ast0.unwrap_mcode name)
951c7801
C
305 | Ast0.OptIdent(id) -> strip id
306 | Ast0.UniqueIdent(id) -> strip id in
34e49164 307
1be43e12 308 let process_whencode notfn allfn exp = function
34e49164
C
309 Ast0.WhenNot(x) -> let _ = notfn x in ()
310 | Ast0.WhenAlways(x) -> let _ = allfn x in ()
1be43e12
C
311 | Ast0.WhenModifier(_) -> ()
312 | Ast0.WhenNotTrue(x) -> let _ = exp x in ()
313 | Ast0.WhenNotFalse(x) -> let _ = exp x in () in
34e49164
C
314
315 (* assume that all of the declarations are at the beginning of a statement
316 list, which is required by C, but not actually required by the cocci
317 parser *)
318 let rec process_statement_list r acc = function
319 [] -> acc
320 | (s::ss) ->
321 (match Ast0.unwrap s with
322 Ast0.Decl(_,decl) ->
fc1ad971 323 let new_acc = (process_decl acc decl)@acc in
34e49164
C
324 process_statement_list r new_acc ss
325 | Ast0.Dots(_,wc) ->
1be43e12 326 (* why is this case here? why is there none for nests? *)
34e49164 327 List.iter
b1b2de81
C
328 (process_whencode r.VT0.combiner_rec_statement_dots
329 r.VT0.combiner_rec_statement r.VT0.combiner_rec_expression)
34e49164
C
330 wc;
331 process_statement_list r acc ss
332 | Ast0.Disj(_,statement_dots_list,_,_) ->
333 let new_acc =
334 lub_envs
335 (List.map
336 (function x -> process_statement_list r acc (Ast0.undots x))
337 statement_dots_list) in
338 process_statement_list r new_acc ss
339 | _ ->
b1b2de81 340 let _ = (propagate_types acc).VT0.combiner_rec_statement s in
fc1ad971
C
341 process_statement_list r acc ss)
342
343 and process_decl env decl =
344 match Ast0.unwrap decl with
413ffc02
C
345 Ast0.MetaDecl(_,_) | Ast0.MetaField(_,_) -> []
346 | Ast0.Init(_,ty,id,_,exp,_) ->
fc1ad971
C
347 let _ =
348 (propagate_types env).VT0.combiner_rec_initialiser exp in
349 [(strip id,Ast0.ast0_type_to_type ty)]
350 | Ast0.UnInit(_,ty,id,_) ->
351 [(strip id,Ast0.ast0_type_to_type ty)]
352 | Ast0.MacroDecl(_,_,_,_,_) -> []
353 | Ast0.TyDecl(ty,_) -> []
354 (* pad: should handle typedef one day and add a binding *)
355 | Ast0.Typedef(_,_,_,_) -> []
356 | Ast0.DisjDecl(_,disjs,_,_) ->
357 List.concat(List.map (process_decl env) disjs)
358 | Ast0.Ddots(_,_) -> [] (* not in a statement list anyway *)
359 | Ast0.OptDecl(decl) -> process_decl env decl
360 | Ast0.UniqueDecl(decl) -> process_decl env decl in
34e49164
C
361
362 let statement_dots r k d =
363 match Ast0.unwrap d with
364 Ast0.DOTS(l) | Ast0.CIRCLES(l) | Ast0.STARS(l) ->
365 let _ = process_statement_list r env l in option_default in
fc1ad971
C
366
367 let post_bool exp =
368 let rec process_test exp =
369 match (Ast0.unwrap exp,Ast0.get_type exp) with
370 (Ast0.Edots(_,_),_) -> None
371 | (Ast0.NestExpr(_,_,_,_,_),_) -> None
372 | (Ast0.MetaExpr(_,_,_,_,_),_) ->
373 (* if a type is known, it is specified in the decl *)
374 None
375 | (Ast0.Paren(lp,exp,rp),None) -> process_test exp
c3e37e97
C
376 (* the following doesn't seem like a good idea - triggers int isos
377 on all test expressions *)
378 (*| (_,None) -> Some (int_type) *)
fc1ad971
C
379 | _ -> None in
380 let new_expty = process_test exp in
381 (match new_expty with
382 None -> () (* leave things as they are *)
383 | Some ty -> Ast0.set_type exp new_expty) in
384
34e49164
C
385 let statement r k s =
386 match Ast0.unwrap s with
387 Ast0.FunDecl(_,fninfo,name,lp,params,rp,lbrace,body,rbrace) ->
388 let rec get_binding p =
389 match Ast0.unwrap p with
390 Ast0.Param(ty,Some id) ->
391 [(strip id,Ast0.ast0_type_to_type ty)]
392 | Ast0.OptParam(param) -> get_binding param
393 | _ -> [] in
394 let fenv = List.concat (List.map get_binding (Ast0.undots params)) in
b1b2de81 395 (propagate_types (fenv@env)).VT0.combiner_rec_statement_dots body
34e49164
C
396 | Ast0.IfThen(_,_,exp,_,_,_) | Ast0.IfThenElse(_,_,exp,_,_,_,_,_)
397 | Ast0.While(_,_,exp,_,_,_) | Ast0.Do(_,_,_,_,exp,_,_)
fc1ad971 398 | Ast0.For(_,_,_,_,Some exp,_,_,_,_,_) ->
34e49164 399 let _ = k s in
fc1ad971 400 post_bool exp;
34e49164 401 None
fc1ad971
C
402 | Ast0.Switch(_,_,exp,_,_,decls,cases,_) ->
403 let senv = process_statement_list r env (Ast0.undots decls) in
404 let res =
405 (propagate_types (senv@env)).VT0.combiner_rec_case_line_dots cases in
406 post_bool exp;
407 res
34e49164
C
408 | _ -> k s
409
410 and case_line r k c =
411 match Ast0.unwrap c with
fc1ad971 412 Ast0.Case(case,exp,colon,code) ->
34e49164
C
413 let _ = k c in
414 (match Ast0.get_type exp with
faf9a90c 415 None -> Ast0.set_type exp (Some (int_type))
34e49164
C
416 | _ -> ());
417 None
fc1ad971 418 | _ -> k c in
34e49164
C
419
420 V0.combiner bind option_default
b1b2de81
C
421 {V0.combiner_functions with
422 VT0.combiner_dotsstmtfn = statement_dots;
423 VT0.combiner_identfn = ident;
424 VT0.combiner_exprfn = expression;
425 VT0.combiner_stmtfn = statement;
426 VT0.combiner_casefn = case_line}
34e49164
C
427
428let type_infer code =
429 let prop = propagate_types [(Id("NULL"),T.Pointer(T.Unknown))] in
b1b2de81 430 let fn = prop.VT0.combiner_rec_top_level in
34e49164
C
431 let _ = List.map fn code in
432 ()