Coccinelle release-1.0.0-rc11
[bpt/coccinelle.git] / engine / c_vs_c.ml
1 (*
2 * Copyright 2012, INRIA
3 * Julia Lawall, Gilles Muller
4 * Copyright 2010-2011, INRIA, University of Copenhagen
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
27 open Common
28
29 open Ast_c
30
31 (* For the moment I do only eq_type and not eq_expr, etc. The reason
32 * for eq_type is related to the typedef and struct isomorphism. Sometimes
33 * one use the typedef and sometimes the structname.
34 *
35 * TODO: should use the isomorphisms engine of julia.
36 * Maybe I can transform my ast_c in ast_cocci, and use julia's code ?
37 * Maybe I can add some Disj in my ast_c ?
38 *)
39
40
41 module type PARAM =
42 sig
43 type tin
44 type 'x tout
45
46 type 'a matcher = 'a -> 'a -> tin -> 'a tout
47
48 val (>>=):
49 (tin -> 'a tout) ->
50 ('a -> (tin -> 'b tout)) ->
51 (tin -> 'b tout)
52
53 val (>&&>) : bool -> (tin -> 'x tout) -> (tin -> 'x tout)
54
55 val return : 'a -> tin -> 'a tout
56 val fail : tin -> 'a tout
57 end
58
59
60 module C_VS_C =
61 functor (X : PARAM) ->
62 struct
63
64 type 'a matcher = 'a -> 'a -> X.tin -> 'a X.tout
65
66 let (>>=) = X.(>>=)
67 let (>&&>) = X.(>&&>)
68 let return = X.return
69 let fail = X.fail
70
71 let (option: 'a matcher -> ('a option matcher)) = fun f t1 t2 ->
72 match (t1,t2) with
73 | (Some t1, Some t2) ->
74 f t1 t2 >>= (fun t ->
75 return (Some t)
76 )
77 | (None, None) -> return None
78 | _ -> fail
79
80
81 let same_s saopt sbopt =
82 match saopt, sbopt with
83 | None, None -> true
84 | Some namea, Some nameb ->
85 let sa = Ast_c.str_of_name namea in
86 let sb = Ast_c.str_of_name nameb in
87 sa =$= sb
88 | _ -> false
89
90
91 let rec fullType a b =
92 let ((qua,iiqa), tya) = a in
93 let ((qub,iiqb), tyb) = b in
94 (qua.const =:= qub.const && qua.volatile =:= qub.volatile) >&&>
95
96 let (qu,iiq) = (qua, iiqa) in
97 typeC tya tyb >>= (fun ty ->
98 return ((qu,iiq), ty)
99 )
100
101 and typeC tya tyb =
102 let (a, iia) = tya in
103 let (b, iib) = tyb in
104
105 let iix = iia in
106
107 match a, b with
108 | BaseType a, BaseType b ->
109 a =*= b >&&> return (BaseType a, iix)
110 | Pointer a, Pointer b ->
111 fullType a b >>= (fun x -> return (Pointer x, iix))
112
113 | StructUnionName (sua, sa), StructUnionName (sub, sb) ->
114 (sua =*= sub && sa =$= sb) >&&>
115 return (StructUnionName (sua, sa), iix)
116
117 | TypeName (namea, opta), TypeName (nameb, optb) ->
118 let sa = Ast_c.str_of_name namea in
119 let sb = Ast_c.str_of_name nameb in
120
121 (* assert compatible opta optb ? *)
122 (*option fullType opta optb*)
123 sa =$= sb >&&>
124 let opt =
125 (match opta, optb with
126 | None, None -> None
127
128 | Some x, _
129 | _, Some x
130
131 -> Some x
132 )
133 in
134 return (TypeName (namea, opt), iix)
135
136
137 | Array (ea, a), Array (eb,b) ->
138 let get_option f = function Some x -> Some (f x) | None -> None in
139 let ea = get_option Lib_parsing_c.al_expr ea in
140 let eb = get_option Lib_parsing_c.al_expr eb in
141 ea =*= eb >&&> fullType a b >>= (fun x -> return (Array (ea, x), iix))
142
143 | FunctionType (returna, paramsa), FunctionType (returnb, paramsb) ->
144 let (tsa, (ba,iihas3dotsa)) = paramsa in
145 let (tsb, (bb,iihas3dotsb)) = paramsb in
146
147 let bx = ba in
148 let iihas3dotsx = iihas3dotsa in
149
150 (ba =:= bb && List.length tsa =|= List.length tsb) >&&>
151 fullType returna returnb >>= (fun returnx ->
152
153 Common.zip tsa tsb +> List.fold_left
154 (fun acc ((parama,iia),(paramb,iib))->
155 let iix = iia in
156 acc >>= (fun xs ->
157
158 let {p_register = (ba,iiba); p_namei = saopt; p_type = ta} =
159 parama in
160 let {p_register = (bb,iibb); p_namei = sbopt; p_type = tb} =
161 paramb in
162
163 let bx = ba in
164 let iibx = iiba in
165
166 let sxopt = saopt in
167
168
169 (* todo? iso on name or argument ? *)
170 (ba =:= bb && same_s saopt sbopt) >&&>
171 fullType ta tb >>= (fun tx ->
172 let paramx = { p_register = (bx, iibx);
173 p_namei = sxopt;
174 p_type = tx; } in
175 return ((paramx,iix)::xs)
176 )
177 )
178 ) (return [])
179 >>= (fun tsx ->
180 let paramsx = (List.rev tsx, (bx, iihas3dotsx)) in
181 return (FunctionType (returnx, paramsx), iix)
182 ))
183
184 | Enum (saopt, enuma), Enum (sbopt, enumb) ->
185 (saopt =*= sbopt &&
186 List.length enuma =|= List.length enumb &&
187 Common.zip enuma enumb +> List.for_all (fun
188 (((namesa,eopta), iicommaa), ((namesb,eoptb),iicommab))
189 ->
190 let sa = str_of_name namesa in
191 let sb = str_of_name namesb in
192 sa =$= sb &&
193 (* todo ? eopta and b can have some info so ok to use =*= ? *)
194 eopta =*= eoptb
195 )
196 ) >&&>
197 return (Enum (saopt, enuma), iix)
198
199 | EnumName sa, EnumName sb -> sa =$= sb >&&> return (EnumName sa, iix)
200
201 | ParenType a, ParenType b ->
202 (* iso here ? *)
203 fullType a b >>= (fun x ->
204 return (ParenType x, iix)
205 )
206
207 | TypeOfExpr ea, TypeOfExpr eb ->
208 let ea = Lib_parsing_c.al_expr ea in
209 let eb = Lib_parsing_c.al_expr eb in
210 ea =*= eb >&&> return (TypeOfExpr ea, iix)
211
212 | TypeOfType a, TypeOfType b ->
213 fullType a b >>= (fun x -> return (TypeOfType x, iix))
214
215 (* | TypeOfType a, b ->
216 | a, TypeOfType b ->
217 *)
218
219
220 | StructUnion (sua, saopt, sta), StructUnion (sub, sbopt, stb) ->
221 (sua =*= sub && saopt =*= sbopt && List.length sta =|= List.length stb)
222 >&&>
223 (function tin ->
224 (* zip is only safe if the above succeeds *)
225 (Common.zip sta stb +> List.fold_left
226 (fun acc ((fielda), (fieldb)) ->
227 acc >>= (fun xs ->
228 match fielda, fieldb with
229 | EmptyField iia, EmptyField iib ->
230 let iix = iia in
231 return ((EmptyField iix)::xs)
232
233 | DeclarationField (FieldDeclList (fa, iipta)),
234 DeclarationField (FieldDeclList (fb, iiptb)) ->
235 let iipt = iipta in (* TODO ?*)
236 (List.length fa =|= List.length fb) >&&>
237 (function tin ->
238 (* only executable if the length is correct *)
239 (Common.zip fa fb +> List.fold_left
240 (fun acc2 ((fielda,iia),(fieldb,iib))->
241 let iix = iia in
242 acc2 >>= (fun xs ->
243 match fielda, fieldb with
244 | Simple (nameaopt, ta), Simple (namebopt, tb) ->
245
246
247 same_s nameaopt namebopt >&&>
248 fullType ta tb >>= (fun tx ->
249 return (((Simple (nameaopt, tx)), iix)::xs)
250 )
251
252 | BitField (nameopta, ta, infoa, ea),
253 BitField (nameoptb, tb, infob, eb) ->
254 let infox = infoa in
255 (same_s nameopta nameoptb && ea =*= eb) >&&>
256 fullType ta tb >>= (fun tx ->
257 return (((BitField (nameopta,tx,infox,ea)), iix)::xs)
258 )
259 | _,_ -> fail
260 )
261 ) (return [])) tin)
262 >>= (fun fx ->
263 return (((DeclarationField
264 (FieldDeclList (List.rev fx,iipt))))::xs)
265 )
266 | _ -> fail
267 )
268
269
270 ) (return [])
271 >>= (fun stx ->
272 return (StructUnion (sua, saopt, List.rev stx), iix)
273 )) tin)
274
275
276
277 (* choose the lub.
278 * subtil: in the return must put iia, not iix, and in following case
279 * must put iib and not iix, because we want the token corresponding
280 * to the typedef.
281 *)
282 | TypeName (name, Some a), _ ->
283 fullType a (Ast_c.nQ, tyb) >>= (fun x ->
284 return (TypeName (name, Some x), iia)
285 )
286
287 | _, TypeName (name, Some b) ->
288 fullType b (Ast_c.nQ, tya) >>= (fun x ->
289 return (TypeName (name, Some x), iib) (* subtil: *)
290 )
291
292 | _, _ -> fail
293
294
295
296 end
297
298 module XEQ = struct
299 type tin = unit
300 type 'a tout = 'a option
301
302 type 'a matcher = 'a -> 'a -> tin -> 'a tout
303
304 let return x = fun tin -> Some x
305 let fail = fun tin -> None
306
307 let (>>=) m f = fun tin ->
308 match m tin with
309 | None -> None
310 | Some x -> f x tin
311
312 let (>&&>) b m = fun tin ->
313 if b then m tin
314 else fail tin
315
316 end
317
318 module EQ = C_VS_C (XEQ)
319
320
321 let eq_type2 a b = EQ.fullType a b () <> None
322 let merge_type2 a b = Common.some (EQ.fullType a b ())
323
324 let eq_type a b =
325 Common.profile_code "C_vs_c" (fun () -> eq_type2 a b)
326
327 let merge_type a b =
328 Common.profile_code "C_vs_c" (fun () -> merge_type2 a b)
329
330
331 (* ------------------------------------------------------------------------- *)
332
333 (* This seemed like a reasonable place to put this, given the file name,
334 but not sure that it is the case... This has to be compatible with the
335 function equal_inh_metavarval. It is indeed not so clear why that is
336 defined in cocci_vs_c.ml, and not here, since it is comparing C code to C
337 code. *)
338
339 let subexpression_of_expression small_exp big_exp =
340 let res = ref false in (* because no appropriate functional visitor... *)
341 let expr (k,bigf) big_exp =
342 (* comparison used in Cocci_vs_c.equal_inh_metavarval *)
343 (* have to strip each subexp, because stripping puts some offsets in the
344 term rather than setting everything to 0. No idea why... *)
345 if small_exp =*= Lib_parsing_c.al_inh_expr big_exp
346 then res := true
347 else k big_exp in
348 let bigf = { Visitor_c.default_visitor_c with Visitor_c.kexpr = expr } in
349 Visitor_c.vk_expr bigf big_exp;
350 (*Printf.printf "comparison gives %b\n" !res;
351 Pretty_print_c.pp_expression_simple small_exp;
352 Format.print_newline();
353 Pretty_print_c.pp_expression_simple big_exp;
354 Format.print_newline();
355 Printf.printf "--------------------------------\n";*)
356 !res