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