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