Release coccinelle-0.2.0
[bpt/coccinelle.git] / engine / cocci_vs_c.ml
CommitLineData
9f8e26f4
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, Nicolas Palix
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
951c7801
C
23(* Yoann Padioleau, Julia Lawall
24 *
25 * Copyright (C) 2006, 2007, 2008 Ecole des Mines de Nantes
26 *
27 * This program is free software; you can redistribute it and/or
28 * modify it under the terms of the GNU General Public License (GPL)
29 * version 2 as published by the Free Software Foundation.
30 *
31 * This program is distributed in the hope that it will be useful,
32 * but WITHOUT ANY WARRANTY; without even the implied warranty of
33 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
34 * file license.txt for more details.
35 *
36 * This file was part of Coccinelle.
37 *)
38
34e49164
C
39open Common
40
41module A = Ast_cocci
42module B = Ast_c
43
44module F = Control_flow_c
45
485bce71
C
46module Flag = Flag_matcher
47
34e49164
C
48(*****************************************************************************)
49(* Wrappers *)
50(*****************************************************************************)
708f4980 51let pr2, pr2_once = Common.mk_pr2_wrappers Flag_matcher.verbose_matcher
34e49164
C
52
53(*****************************************************************************)
54(* Helpers *)
55(*****************************************************************************)
56
57type sequence = Ordered | Unordered
58
951c7801
C
59let seqstyle eas =
60 match A.unwrap eas with
61 | A.DOTS _ -> Ordered
62 | A.CIRCLES _ -> Unordered
34e49164
C
63 | A.STARS _ -> failwith "not handling stars"
64
65let (redots : 'a A.dots -> 'a list -> 'a A.dots)=fun eas easundots ->
66 A.rewrap eas (
67 match A.unwrap eas with
68 | A.DOTS _ -> A.DOTS easundots
69 | A.CIRCLES _ -> A.CIRCLES easundots
70 | A.STARS _ -> A.STARS easundots
71 )
72
73
74let (need_unordered_initialisers : B.initialiser B.wrap2 list -> bool) =
75 fun ibs ->
76 ibs +> List.exists (fun (ib, icomma) ->
77 match B.unwrap ib with
78 | B.InitDesignators _
79 | B.InitFieldOld _
80 | B.InitIndexOld _
81 -> true
82 | B.InitExpr _
83 | B.InitList _
84 -> false
85 )
86
87(* For the #include <linux/...> in the .cocci, need to find where is
88 * the '+' attached to this element, to later find the first concrete
89 * #include <linux/xxx.h> or last one in the serie of #includes in the
90 * .c.
91 *)
92type include_requirement =
93 | IncludeMcodeBefore
94 | IncludeMcodeAfter
95 | IncludeNothing
96
97
98
99(* todo? put in semantic_c.ml *)
100type info_ident =
101 | Function
102 | LocalFunction (* entails Function *)
103 | DontKnow
104
105
106let term mc = A.unwrap_mcode mc
107let mcodekind mc = A.get_mcodekind mc
108
109
110let mcode_contain_plus = function
111 | A.CONTEXT (_,A.NOTHING) -> false
112 | A.CONTEXT _ -> true
708f4980
C
113 | A.MINUS (_,_,_,[]) -> false
114 | A.MINUS (_,_,_,x::xs) -> true
951c7801 115 | A.PLUS _ -> raise Impossible
34e49164
C
116
117let mcode_simple_minus = function
708f4980 118 | A.MINUS (_,_,_,[]) -> true
34e49164
C
119 | _ -> false
120
121
122(* In transformation.ml sometime I build some mcodekind myself and
123 * julia has put None for the pos. But there is no possible raise
124 * NoMatch in those cases because it is for the minusall trick or for
125 * the distribute, so either have to build those pos, in fact a range,
126 * because for the distribute have to erase a fullType with one
127 * mcodekind, or add an argument to tag_with_mck such as "safe" that
128 * don't do the check_pos. Hence this DontCarePos constructor. *)
129
130let minusizer =
131 ("fake","fake"),
708f4980
C
132 {A.line = 0; A.column =0; A.strbef=[]; A.straft=[];},
133 (A.MINUS(A.DontCarePos,[],-1,[])),
34e49164
C
134 A.NoMetaPos
135
136let generalize_mcode ia =
137 let (s1, i, mck, pos) = ia in
138 let new_mck =
139 match mck with
951c7801 140 | A.PLUS _ -> raise Impossible
34e49164
C
141 | A.CONTEXT (A.NoPos,x) ->
142 A.CONTEXT (A.DontCarePos,x)
708f4980
C
143 | A.MINUS (A.NoPos,inst,adj,x) ->
144 A.MINUS (A.DontCarePos,inst,adj,x)
485bce71
C
145
146 | A.CONTEXT ((A.FixPos _|A.DontCarePos), _)
708f4980 147 | A.MINUS ((A.FixPos _|A.DontCarePos), _, _, _)
485bce71
C
148 ->
149 raise Impossible
150 in
34e49164
C
151 (s1, i, new_mck, pos)
152
153
154
155(*---------------------------------------------------------------------------*)
156
157(* 0x0 is equivalent to 0, value format isomorphism *)
158let equal_c_int s1 s2 =
159 try
b1b2de81 160 int_of_string s1 =|= int_of_string s2
34e49164
C
161 with Failure("int_of_string") ->
162 s1 =$= s2
163
164
165
166(*---------------------------------------------------------------------------*)
167(* Normally A should reuse some types of Ast_c, so those
168 * functions should not exist.
169 *
170 * update: but now Ast_c depends on A, so can't make too
171 * A depends on Ast_c, so have to stay with those equal_xxx
172 * functions.
173 *)
174
175let equal_unaryOp a b =
176 match a, b with
177 | A.GetRef , B.GetRef -> true
178 | A.DeRef , B.DeRef -> true
179 | A.UnPlus , B.UnPlus -> true
180 | A.UnMinus , B.UnMinus -> true
181 | A.Tilde , B.Tilde -> true
182 | A.Not , B.Not -> true
485bce71
C
183 | _, B.GetRefLabel -> false (* todo cocci? *)
184 | _, (B.Not|B.Tilde|B.UnMinus|B.UnPlus|B.DeRef|B.GetRef) -> false
185
186
34e49164
C
187
188let equal_arithOp a b =
189 match a, b with
190 | A.Plus , B.Plus -> true
191 | A.Minus , B.Minus -> true
192 | A.Mul , B.Mul -> true
193 | A.Div , B.Div -> true
194 | A.Mod , B.Mod -> true
195 | A.DecLeft , B.DecLeft -> true
196 | A.DecRight , B.DecRight -> true
197 | A.And , B.And -> true
198 | A.Or , B.Or -> true
199 | A.Xor , B.Xor -> true
485bce71
C
200 | _, (B.Xor|B.Or|B.And|B.DecRight|B.DecLeft|B.Mod|B.Div|B.Mul|B.Minus|B.Plus)
201 -> false
34e49164
C
202
203let equal_logicalOp a b =
204 match a, b with
205 | A.Inf , B.Inf -> true
206 | A.Sup , B.Sup -> true
207 | A.InfEq , B.InfEq -> true
208 | A.SupEq , B.SupEq -> true
209 | A.Eq , B.Eq -> true
210 | A.NotEq , B.NotEq -> true
211 | A.AndLog , B.AndLog -> true
212 | A.OrLog , B.OrLog -> true
485bce71
C
213 | _, (B.OrLog|B.AndLog|B.NotEq|B.Eq|B.SupEq|B.InfEq|B.Sup|B.Inf)
214 -> false
34e49164
C
215
216let equal_assignOp a b =
217 match a, b with
218 | A.SimpleAssign, B.SimpleAssign -> true
219 | A.OpAssign a, B.OpAssign b -> equal_arithOp a b
485bce71 220 | _, (B.OpAssign _|B.SimpleAssign) -> false
34e49164
C
221
222let equal_fixOp a b =
223 match a, b with
224 | A.Dec, B.Dec -> true
225 | A.Inc, B.Inc -> true
485bce71 226 | _, (B.Inc|B.Dec) -> false
34e49164
C
227
228let equal_binaryOp a b =
229 match a, b with
230 | A.Arith a, B.Arith b -> equal_arithOp a b
231 | A.Logical a, B.Logical b -> equal_logicalOp a b
485bce71 232 | _, (B.Logical _ | B.Arith _) -> false
34e49164
C
233
234let equal_structUnion a b =
235 match a, b with
236 | A.Struct, B.Struct -> true
237 | A.Union, B.Union -> true
485bce71 238 | _, (B.Struct|B.Union) -> false
34e49164
C
239
240let equal_sign a b =
241 match a, b with
242 | A.Signed, B.Signed -> true
243 | A.Unsigned, B.UnSigned -> true
485bce71 244 | _, (B.UnSigned|B.Signed) -> false
34e49164
C
245
246let equal_storage a b =
247 match a, b with
248 | A.Static , B.Sto B.Static
249 | A.Auto , B.Sto B.Auto
250 | A.Register , B.Sto B.Register
251 | A.Extern , B.Sto B.Extern
252 -> true
485bce71
C
253 | _, (B.NoSto | B.StoTypedef) -> false
254 | _, (B.Sto (B.Register|B.Static|B.Auto|B.Extern)) -> false
255
34e49164
C
256
257(*---------------------------------------------------------------------------*)
258
259let equal_metavarval valu valu' =
260 match valu, valu' with
261 | Ast_c.MetaIdVal a, Ast_c.MetaIdVal b -> a =$= b
262 | Ast_c.MetaFuncVal a, Ast_c.MetaFuncVal b -> a =$= b
263 | Ast_c.MetaLocalFuncVal a, Ast_c.MetaLocalFuncVal b ->
264 (* do something more ? *)
265 a =$= b
266
267 (* al_expr before comparing !!! and accept when they match.
268 * Note that here we have Astc._expression, so it is a match
269 * modulo isomorphism (there is no metavariable involved here,
270 * just isomorphisms). => TODO call isomorphism_c_c instead of
271 * =*=. Maybe would be easier to transform ast_c in ast_cocci
272 * and call the iso engine of julia. *)
273 | Ast_c.MetaExprVal a, Ast_c.MetaExprVal b ->
274 Lib_parsing_c.al_expr a =*= Lib_parsing_c.al_expr b
275 | Ast_c.MetaExprListVal a, Ast_c.MetaExprListVal b ->
276 Lib_parsing_c.al_arguments a =*= Lib_parsing_c.al_arguments b
277
278 | Ast_c.MetaStmtVal a, Ast_c.MetaStmtVal b ->
279 Lib_parsing_c.al_statement a =*= Lib_parsing_c.al_statement b
113803cf
C
280 | Ast_c.MetaInitVal a, Ast_c.MetaInitVal b ->
281 Lib_parsing_c.al_init a =*= Lib_parsing_c.al_init b
34e49164
C
282 | Ast_c.MetaTypeVal a, Ast_c.MetaTypeVal b ->
283 (* old: Lib_parsing_c.al_type a =*= Lib_parsing_c.al_type b *)
284 C_vs_c.eq_type a b
285
286 | Ast_c.MetaListlenVal a, Ast_c.MetaListlenVal b -> a =|= b
287
288 | Ast_c.MetaParamVal a, Ast_c.MetaParamVal b ->
289 Lib_parsing_c.al_param a =*= Lib_parsing_c.al_param b
290 | Ast_c.MetaParamListVal a, Ast_c.MetaParamListVal b ->
291 Lib_parsing_c.al_params a =*= Lib_parsing_c.al_params b
292
293 | Ast_c.MetaPosVal (posa1,posa2), Ast_c.MetaPosVal (posb1,posb2) ->
294 Ast_cocci.equal_pos posa1 posb1 && Ast_cocci.equal_pos posa2 posb2
951c7801 295
34e49164
C
296 | Ast_c.MetaPosValList l1, Ast_c.MetaPosValList l2 ->
297 List.exists
485bce71 298 (function (fla,cea,posa1,posa2) ->
34e49164 299 List.exists
485bce71 300 (function (flb,ceb,posb1,posb2) ->
b1b2de81 301 fla =$= flb && cea =$= ceb &&
34e49164
C
302 Ast_c.equal_posl posa1 posb1 && Ast_c.equal_posl posa2 posb2)
303 l2)
304 l1
34e49164 305
485bce71 306 | (B.MetaPosValList _|B.MetaListlenVal _|B.MetaPosVal _|B.MetaStmtVal _
113803cf 307 |B.MetaTypeVal _ |B.MetaInitVal _
485bce71
C
308 |B.MetaParamListVal _|B.MetaParamVal _|B.MetaExprListVal _
309 |B.MetaExprVal _|B.MetaLocalFuncVal _|B.MetaFuncVal _|B.MetaIdVal _
310 ), _
311 -> raise Impossible
34e49164 312
002099fc
C
313(* probably only one argument needs to be stripped, because inherited
314metavariables containing expressions are stripped in advance. But don't
315know which one is which... *)
316let equal_inh_metavarval valu valu'=
978fd7e5
C
317 match valu, valu' with
318 | Ast_c.MetaIdVal a, Ast_c.MetaIdVal b -> a =$= b
319 | Ast_c.MetaFuncVal a, Ast_c.MetaFuncVal b -> a =$= b
320 | Ast_c.MetaLocalFuncVal a, Ast_c.MetaLocalFuncVal b ->
321 (* do something more ? *)
322 a =$= b
323
324 (* al_expr before comparing !!! and accept when they match.
325 * Note that here we have Astc._expression, so it is a match
326 * modulo isomorphism (there is no metavariable involved here,
327 * just isomorphisms). => TODO call isomorphism_c_c instead of
328 * =*=. Maybe would be easier to transform ast_c in ast_cocci
329 * and call the iso engine of julia. *)
330 | Ast_c.MetaExprVal a, Ast_c.MetaExprVal b ->
331 Lib_parsing_c.al_inh_expr a =*= Lib_parsing_c.al_inh_expr b
332 | Ast_c.MetaExprListVal a, Ast_c.MetaExprListVal b ->
333 Lib_parsing_c.al_inh_arguments a =*= Lib_parsing_c.al_inh_arguments b
334
335 | Ast_c.MetaStmtVal a, Ast_c.MetaStmtVal b ->
336 Lib_parsing_c.al_inh_statement a =*= Lib_parsing_c.al_inh_statement b
337 | Ast_c.MetaInitVal a, Ast_c.MetaInitVal b ->
338 Lib_parsing_c.al_inh_init a =*= Lib_parsing_c.al_inh_init b
339 | Ast_c.MetaTypeVal a, Ast_c.MetaTypeVal b ->
340 (* old: Lib_parsing_c.al_inh_type a =*= Lib_parsing_c.al_inh_type b *)
341 C_vs_c.eq_type a b
342
343 | Ast_c.MetaListlenVal a, Ast_c.MetaListlenVal b -> a =|= b
344
345 | Ast_c.MetaParamVal a, Ast_c.MetaParamVal b ->
346 Lib_parsing_c.al_param a =*= Lib_parsing_c.al_param b
347 | Ast_c.MetaParamListVal a, Ast_c.MetaParamListVal b ->
348 Lib_parsing_c.al_params a =*= Lib_parsing_c.al_params b
349
350 | Ast_c.MetaPosVal (posa1,posa2), Ast_c.MetaPosVal (posb1,posb2) ->
351 Ast_cocci.equal_pos posa1 posb1 && Ast_cocci.equal_pos posa2 posb2
352
353 | Ast_c.MetaPosValList l1, Ast_c.MetaPosValList l2 ->
354 List.exists
355 (function (fla,cea,posa1,posa2) ->
356 List.exists
357 (function (flb,ceb,posb1,posb2) ->
358 fla =$= flb && cea =$= ceb &&
359 Ast_c.equal_posl posa1 posb1 && Ast_c.equal_posl posa2 posb2)
360 l2)
361 l1
362
363 | (B.MetaPosValList _|B.MetaListlenVal _|B.MetaPosVal _|B.MetaStmtVal _
364 |B.MetaTypeVal _ |B.MetaInitVal _
365 |B.MetaParamListVal _|B.MetaParamVal _|B.MetaExprListVal _
366 |B.MetaExprVal _|B.MetaLocalFuncVal _|B.MetaFuncVal _|B.MetaIdVal _
367 ), _
368 -> raise Impossible
369
34e49164
C
370
371(*---------------------------------------------------------------------------*)
372(* could put in ast_c.ml, next to the split/unsplit_comma *)
373let split_signb_baseb_ii (baseb, ii) =
374 let iis = ii +> List.map (fun info -> (B.str_of_info info), info) in
375 match baseb, iis with
376
377 | B.Void, ["void",i1] -> None, [i1]
378
379 | B.FloatType (B.CFloat),["float",i1] -> None, [i1]
380 | B.FloatType (B.CDouble),["double",i1] -> None, [i1]
381 | B.FloatType (B.CLongDouble),["long",i1;"double",i2] -> None,[i1;i2]
382
383 | B.IntType (B.CChar), ["char",i1] -> None, [i1]
384
385
b1b2de81
C
386 | B.IntType (B.Si (sign, base)), xs ->
387 let (signed,rest) =
388 match (sign,xs) with
389 (_,[]) -> None,[]
390 | (B.Signed,(("signed",i1)::rest)) -> (Some (B.Signed,i1),rest)
391 | (B.Signed,rest) -> (None,rest)
392 | (B.UnSigned,(("unsigned",i1)::rest)) -> (Some (B.UnSigned,i1),rest)
393 | (B.UnSigned,rest) -> (* is this case possible? *) (None,rest) in
394 (* The original code only allowed explicit signed and unsigned for char,
395 while this code allows char by itself. Not sure that needs to be
396 checked for here. If it does, then add a special case. *)
397 let base_res =
398 match (base,rest) with
399 B.CInt, ["int",i1] -> [i1]
400 | B.CInt, [] -> []
401
402 | B.CInt, ["",i1] -> (* no type is specified at all *)
403 (match i1.B.pinfo with
404 B.FakeTok(_,_) -> []
405 | _ -> failwith ("unrecognized signed int: "^
406 (String.concat " "(List.map fst iis))))
407
408 | B.CChar2, ["char",i2] -> [i2]
409
410 | B.CShort, ["short",i1] -> [i1]
411 | B.CShort, ["short",i1;"int",i2] -> [i1;i2]
412
413 | B.CLong, ["long",i1] -> [i1]
414 | B.CLong, ["long",i1;"int",i2] -> [i1;i2]
415
416 | B.CLongLong, ["long",i1;"long",i2] -> [i1;i2]
417 | B.CLongLong, ["long",i1;"long",i2;"int",i3] -> [i1;i2;i3]
418
419 | _ ->
420 failwith ("strange type1, maybe because of weird order: "^
421 (String.concat " " (List.map fst iis))) in
422 (signed,base_res)
423 | _ -> failwith ("strange type2, maybe because of weird order: "^
424 (String.concat " " (List.map fst iis)))
34e49164
C
425
426(*---------------------------------------------------------------------------*)
427
428let rec unsplit_icomma xs =
429 match xs with
430 | [] -> []
431 | x::y::xs ->
432 (match A.unwrap y with
433 | A.IComma mcode ->
434 (x, y)::unsplit_icomma xs
435 | _ -> failwith "wrong ast_cocci in initializer"
436 )
437 | _ ->
438 failwith ("wrong ast_cocci in initializer, should have pair " ^
439 "number of Icomma")
440
441
442
443let resplit_initialiser ibs iicomma =
444 match iicomma, ibs with
445 | [], [] -> []
446 | [], _ ->
447 failwith "should have a iicomma, do you generate fakeInfo in parser?"
448 | _, [] ->
449 failwith "shouldn't have a iicomma"
450 | [iicomma], x::xs ->
451 let elems = List.map fst (x::xs) in
452 let commas = List.map snd (x::xs) +> List.flatten in
453 let commas = commas @ [iicomma] in
454 zip elems commas
455 | _ -> raise Impossible
456
457
458
459let rec split_icomma xs =
460 match xs with
461 | [] -> []
462 | (x,y)::xs -> x::y::split_icomma xs
463
464let rec unsplit_initialiser ibs_unsplit =
465 match ibs_unsplit with
466 | [] -> [], [] (* empty iicomma *)
467 | (x, commax)::xs ->
468 let (xs, lastcomma) = unsplit_initialiser_bis commax xs in
469 (x, [])::xs, lastcomma
470
471and unsplit_initialiser_bis comma_before = function
472 | [] -> [], [comma_before]
473 | (x, commax)::xs ->
474 let (xs, lastcomma) = unsplit_initialiser_bis commax xs in
475 (x, [comma_before])::xs, lastcomma
476
477
478
479
480(*---------------------------------------------------------------------------*)
481(* coupling: same in type_annotater_c.ml *)
482let structdef_to_struct_name ty =
483 match ty with
484 | qu, (B.StructUnion (su, sopt, fields), iis) ->
485 (match sopt,iis with
486 | Some s , [i1;i2;i3;i4] ->
487 qu, (B.StructUnionName (su, s), [i1;i2])
488 | None, _ ->
489 ty
490
491 | x -> raise Impossible
492 )
493 | _ -> raise Impossible
494
495(*---------------------------------------------------------------------------*)
496let initialisation_to_affectation decl =
497 match decl with
498 | B.MacroDecl _ -> F.Decl decl
499 | B.DeclList (xs, iis) ->
500
501 (* todo?: should not do that if the variable is an array cos
502 * will have x[] = , mais de toute facon ca sera pas un InitExp
503 *)
504 (match xs with
505 | [] -> raise Impossible
506 | [x] ->
485bce71
C
507 let ({B.v_namei = var;
508 B.v_type = returnType;
978fd7e5 509 B.v_type_bis = tybis;
485bce71
C
510 B.v_storage = storage;
511 B.v_local = local},
512 iisep) = x in
34e49164 513
978fd7e5
C
514
515
34e49164 516 (match var with
b1b2de81
C
517 | Some (name, iniopt) ->
518 (match iniopt with
519 | Some (iini, (B.InitExpr e, ii_empty2)) ->
978fd7e5 520
34e49164
C
521 let local =
522 match local with
523 Ast_c.NotLocalDecl -> Ast_c.NotLocalVar
978fd7e5
C
524 | Ast_c.LocalDecl ->
525 Ast_c.LocalVar (Ast_c.info_of_type returnType) in
526
527 let typexp =
528 (* old: Lib_parsing_c.al_type returnType
529 * but this type has not the typename completed so
530 * instead try to use tybis
531 *)
532 match !tybis with
533 | Some ty_with_typename_completed ->
534 ty_with_typename_completed
535 | None -> raise Impossible
536 in
537
34e49164 538 let typ =
978fd7e5 539 ref (Some (typexp,local),
34e49164 540 Ast_c.NotTest) in
b1b2de81 541 let ident = name in
708f4980
C
542 let idexpr =
543 Ast_c.mk_e_bis (B.Ident (ident)) typ Ast_c.noii
544 in
545 let assign =
546 Ast_c.mk_e
547 (B.Assignment (idexpr,B.SimpleAssign, e)) [iini] in
548 F.DefineExpr assign
549
34e49164
C
550 | _ -> F.Decl decl
551 )
552 | _ -> F.Decl decl
553 )
554 | x::xs ->
555 pr2_once "TODO: initialisation_to_affectation for multi vars";
556 (* todo? do a fold_left and generate 'x = a, y = b' etc, use
557 * the Sequence expression operator of C and make an
558 * ExprStatement from that.
559 *)
560 F.Decl decl
561 )
562
563
564
565
566
567(*****************************************************************************)
568(* Functor parameter combinators *)
569(*****************************************************************************)
570(* monad like stuff
571 * src: papers on parser combinators in haskell (cf a pearl by meijer in ICFP)
572 *
573 * version0: was not tagging the SP, so just tag the C
574 * val (>>=):
575 * (tin -> 'c tout) -> ('c -> (tin -> 'b tout)) -> (tin -> 'b tout)
576 * val return : 'b -> tin -> 'b tout
577 * val fail : tin -> 'b tout
578 *
579 * version1: now also tag the SP so return a ('a * 'b)
580 *)
581
582type mode = PatternMode | TransformMode
583
584module type PARAM =
585 sig
586 type tin
587 type 'x tout
588
589
590 type ('a, 'b) matcher = 'a -> 'b -> tin -> ('a * 'b) tout
591
592 val mode : mode
593
594 val (>>=):
595 (tin -> ('a * 'b) tout) ->
596 ('a -> 'b -> (tin -> ('c * 'd) tout)) ->
597 (tin -> ('c * 'd) tout)
598
599 val return : ('a * 'b) -> tin -> ('a *'b) tout
600 val fail : tin -> ('a * 'b) tout
601
602 val (>||>) :
603 (tin -> 'x tout) ->
604 (tin -> 'x tout) ->
605 (tin -> 'x tout)
606
607 val (>|+|>) :
608 (tin -> 'x tout) ->
609 (tin -> 'x tout) ->
610 (tin -> 'x tout)
611
612 val (>&&>) : (tin -> bool) -> (tin -> 'x tout) -> (tin -> 'x tout)
613
614 val tokenf : ('a A.mcode, B.info) matcher
615 val tokenf_mck : (A.mcodekind, B.info) matcher
616
617 val distrf_e :
618 (A.meta_name A.mcode, B.expression) matcher
619 val distrf_args :
620 (A.meta_name A.mcode, (Ast_c.argument, Ast_c.il) either list) matcher
621 val distrf_type :
622 (A.meta_name A.mcode, Ast_c.fullType) matcher
623 val distrf_params :
624 (A.meta_name A.mcode,
625 (Ast_c.parameterType, Ast_c.il) either list) matcher
626 val distrf_param :
627 (A.meta_name A.mcode, Ast_c.parameterType) matcher
628 val distrf_ini :
629 (A.meta_name A.mcode, Ast_c.initialiser) matcher
630 val distrf_node :
631 (A.meta_name A.mcode, Control_flow_c.node) matcher
632
633 val distrf_define_params :
634 (A.meta_name A.mcode, (string Ast_c.wrap, Ast_c.il) either list)
635 matcher
636
637 val distrf_struct_fields :
485bce71 638 (A.meta_name A.mcode, B.field list) matcher
34e49164
C
639
640 val distrf_cst :
641 (A.meta_name A.mcode, (B.constant, string) either B.wrap) matcher
642
643 val cocciExp :
644 (A.expression, B.expression) matcher -> (A.expression, F.node) matcher
645
646 val cocciExpExp :
647 (A.expression, B.expression) matcher ->
648 (A.expression, B.expression) matcher
649
650 val cocciTy :
651 (A.fullType, B.fullType) matcher -> (A.fullType, F.node) matcher
652
1be43e12
C
653 val cocciInit :
654 (A.initialiser, B.initialiser) matcher -> (A.initialiser, F.node) matcher
655
34e49164
C
656 val envf :
657 A.keep_binding -> A.inherited ->
658 A.meta_name A.mcode * Ast_c.metavar_binding_kind *
485bce71 659 (unit -> Common.filename * string * Ast_c.posl * Ast_c.posl) ->
34e49164
C
660 (unit -> tin -> 'x tout) -> (tin -> 'x tout)
661
951c7801
C
662 val check_idconstraint :
663 ('a -> 'b -> bool) -> 'a -> 'b ->
664 (unit -> tin -> 'x tout) -> (tin -> 'x tout)
665
666 val check_constraints_ne :
34e49164
C
667 ('a, 'b) matcher -> 'a list -> 'b ->
668 (unit -> tin -> 'x tout) -> (tin -> 'x tout)
669
670 val all_bound : A.meta_name list -> (tin -> bool)
671
672 val optional_storage_flag : (bool -> tin -> 'x tout) -> (tin -> 'x tout)
673 val optional_qualifier_flag : (bool -> tin -> 'x tout) -> (tin -> 'x tout)
674 val value_format_flag: (bool -> tin -> 'x tout) -> (tin -> 'x tout)
675
676
677 end
678
679(*****************************************************************************)
680(* Functor code, "Cocci vs C" *)
681(*****************************************************************************)
682
683module COCCI_VS_C =
951c7801 684 functor (X : PARAM) ->
34e49164
C
685struct
686
687type ('a, 'b) matcher = 'a -> 'b -> X.tin -> ('a * 'b) X.tout
688
689let (>>=) = X.(>>=)
690let return = X.return
691let fail = X.fail
692
693let (>||>) = X.(>||>)
694let (>|+|>) = X.(>|+|>)
695let (>&&>) = X.(>&&>)
696
697let tokenf = X.tokenf
698
699(* should be raise Impossible when called from transformation.ml *)
700let fail2 () =
701 match X.mode with
702 | PatternMode -> fail
703 | TransformMode -> raise Impossible
704
705
706let (option: ('a,'b) matcher -> ('a option,'b option) matcher)= fun f t1 t2 ->
707 match (t1,t2) with
708 | (Some t1, Some t2) ->
709 f t1 t2 >>= (fun t1 t2 ->
710 return (Some t1, Some t2)
711 )
712 | (None, None) -> return (None, None)
713 | _ -> fail
714
715(* Dots are sometimes used as metavariables, since like metavariables they
716can match other things. But they no longer have the same type. Perhaps these
717functions could be avoided by introducing an appropriate level of polymorphism,
718but I don't know how to declare polymorphism across functors *)
719let dots2metavar (_,info,mcodekind,pos) = (("","..."),info,mcodekind,pos)
720let metavar2dots (_,info,mcodekind,pos) = ("...",info,mcodekind,pos)
721
951c7801
C
722let satisfies_iconstraint c id : bool =
723 match c with
724 A.IdNoConstraint -> true
725 | A.IdNegIdSet l -> not (List.mem id l)
726 | A.IdRegExp (_,recompiled) ->
727 if Str.string_match recompiled id 0 then
728 true
729 else
730 false
731 | A.IdNotRegExp (_,recompiled) ->
732 if Str.string_match recompiled id 0 then
733 false
734 else
735 true
736
737let satisfies_econstraint c exp : bool =
738 match Ast_c.unwrap_expr exp with
739 Ast_c.Ident (name) ->
740 (
741 match name with
742 Ast_c.RegularName rname -> satisfies_iconstraint c (Ast_c.unwrap_st rname)
743 | Ast_c.CppConcatenatedName _ ->
744 pr2_once ("WARNING: Unable to apply a constraint on a CppConcatenatedName identifier !"); true
745 | Ast_c.CppVariadicName _ ->
746 pr2_once ("WARNING: Unable to apply a constraint on a CppVariadicName identifier !"); true
747 | Ast_c.CppIdentBuilder _ ->
748 pr2_once ("WARNING: Unable to apply a constraint on a CppIdentBuilder identifier !"); true
749 )
750 | Ast_c.Constant cst ->
751 (match cst with
752 | Ast_c.String (str, _) -> satisfies_iconstraint c str
753 | Ast_c.MultiString strlist ->
754 pr2_once ("WARNING: Unable to apply a constraint on an multistring constant !"); true
755 | Ast_c.Char (char , _) -> satisfies_iconstraint c char
756 | Ast_c.Int (int , _) -> satisfies_iconstraint c int
757 | Ast_c.Float (float, _) -> satisfies_iconstraint c float
758 )
759 | _ -> pr2_once ("WARNING: Unable to apply a constraint on an expression !"); true
760
34e49164
C
761(*---------------------------------------------------------------------------*)
762(* toc:
763 * - expression
764 * - ident
765 * - arguments
766 * - parameters
767 * - declaration
768 * - initialisers
769 * - type
770 * - node
771 *)
772
773(*---------------------------------------------------------------------------*)
774let rec (expression: (A.expression, Ast_c.expression) matcher) =
775 fun ea eb ->
776 X.all_bound (A.get_inherited ea) >&&>
777 let wa x = A.rewrap ea x in
778 match A.unwrap ea, eb with
779
780 (* general case: a MetaExpr can match everything *)
781 | A.MetaExpr (ida,constraints,keep,opttypa,form,inherited),
782 (((expr, opttypb), ii) as expb) ->
783
784 (* old: before have a MetaConst. Now we factorize and use 'form' to
785 * differentiate between different cases *)
786 let rec matches_id = function
b1b2de81 787 B.Ident(name) -> true
34e49164
C
788 | B.Cast(ty,e) -> matches_id (B.unwrap_expr e)
789 | _ -> false in
790 let form_ok =
791 match (form,expr) with
792 (A.ANY,_) -> true
793 | (A.CONST,e) ->
794 let rec matches = function
795 B.Constant(c) -> true
b1b2de81
C
796 | B.Ident (nameidb) ->
797 let s = Ast_c.str_of_name nameidb in
798 if s =~ "^[A-Z_][A-Z_0-9]*$"
799 then begin
002099fc 800 pr2_once ("warning: " ^ s ^ " treated as a constant");
b1b2de81
C
801 true
802 end
803 else false
34e49164
C
804 | B.Cast(ty,e) -> matches (B.unwrap_expr e)
805 | B.Unary(e,B.UnMinus) -> matches (B.unwrap_expr e)
806 | B.SizeOfExpr(exp) -> true
807 | B.SizeOfType(ty) -> true
808 | _ -> false in
809 matches e
810 | (A.LocalID,e) ->
811 (matches_id e) &&
812 (match !opttypb with
813 (Some (_,Ast_c.LocalVar _),_) -> true
814 | _ -> false)
815 | (A.ID,e) -> matches_id e in
816
817 if form_ok
818 then
819 (let (opttypb,_testb) = !opttypb in
820 match opttypa, opttypb with
821 | None, _ -> return ((),())
822 | Some _, None ->
823 pr2_once ("Missing type information. Certainly a pb in " ^
824 "annotate_typer.ml");
825 fail
951c7801 826
fc1ad971 827 | Some tas, Some tb ->
951c7801 828 tas +> List.fold_left (fun acc ta ->
34e49164
C
829 acc >|+|> compatible_type ta tb) fail
830 ) >>=
831 (fun () () ->
951c7801
C
832 match constraints with
833 Ast_cocci.NoConstraint ->
834 let max_min _ =
835 Lib_parsing_c.lin_col_by_pos (Lib_parsing_c.ii_of_expr expb) in
836 X.envf keep inherited (ida, Ast_c.MetaExprVal expb, max_min)
837 (fun () ->
838 X.distrf_e ida expb >>=
839 (fun ida expb ->
840 return (
841 A.MetaExpr (ida,constraints,keep,opttypa,form,inherited)+>
842 A.rewrap ea,
843 expb
844 ))
845 )
846
847 | Ast_cocci.NotIdCstrt cstrt ->
848 X.check_idconstraint satisfies_econstraint cstrt eb
849 (fun () ->
850 let max_min _ =
851 Lib_parsing_c.lin_col_by_pos (Lib_parsing_c.ii_of_expr expb) in
852 X.envf keep inherited (ida, Ast_c.MetaExprVal expb, max_min)
853 (fun () ->
854 X.distrf_e ida expb >>=
855 (fun ida expb ->
856 return (
857 A.MetaExpr (ida,constraints,keep,opttypa,form,inherited)+>
858 A.rewrap ea,
859 expb
860 ))
861 ))
862
863 | Ast_cocci.NotExpCstrt cstrts ->
864 X.check_constraints_ne expression cstrts eb
865 (fun () ->
866 let max_min _ =
867 Lib_parsing_c.lin_col_by_pos (Lib_parsing_c.ii_of_expr expb) in
868 X.envf keep inherited (ida, Ast_c.MetaExprVal expb, max_min)
869 (fun () ->
870 X.distrf_e ida expb >>=
871 (fun ida expb ->
872 return (
873 A.MetaExpr (ida,constraints,keep,opttypa,form,inherited)+>
874 A.rewrap ea,
875 expb
876 ))
877 )))
34e49164 878 else fail
951c7801 879
34e49164
C
880 (* old:
881 * | A.MetaExpr(ida,false,opttypa,_inherited), expb ->
882 * D.distribute_mck (mcodekind ida) D.distribute_mck_e expb binding
883 *
884 * but bug! because if have not tagged SP, then transform without doing
885 * any checks. Hopefully now have tagged SP technique.
886 *)
887
888
889 (* old:
890 * | A.Edots _, _ -> raise Impossible.
891 *
892 * In fact now can also have the Edots inside normal expression, not
893 * just in arg lists. in 'x[...];' less: in if(<... x ... y ...>)
894 *)
895 | A.Edots (mcode, None), expb ->
896 X.distrf_e (dots2metavar mcode) expb >>= (fun mcode expb ->
897 return (
898 A.Edots (metavar2dots mcode, None) +> A.rewrap ea ,
899 expb
900 ))
901
902
903 | A.Edots (_, Some expr), _ -> failwith "not handling when on Edots"
904
905
b1b2de81
C
906 | A.Ident ida, ((B.Ident (nameidb), typ),noii) ->
907 assert (null noii);
908 ident_cpp DontKnow ida nameidb >>= (fun ida nameidb ->
34e49164
C
909 return (
910 ((A.Ident ida)) +> wa,
b1b2de81 911 ((B.Ident (nameidb), typ),Ast_c.noii)
34e49164
C
912 ))
913
914
915
916
485bce71 917 | A.MetaErr _, _ -> failwith "not handling MetaErr"
34e49164
C
918
919 (* todo?: handle some isomorphisms in int/float ? can have different
920 * format : 1l can match a 1.
921 *
922 * todo: normally string can contain some metavar too, so should
923 * recurse on the string
924 *)
925 | A.Constant (ia1), ((B.Constant (ib) , typ),ii) ->
926 (* for everything except the String case where can have multi elems *)
927 let do1 () =
928 let ib1 = tuple_of_list1 ii in
929 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
930 return (
931 ((A.Constant ia1)) +> wa,
932 ((B.Constant (ib), typ),[ib1])
933 ))
934 in
935 (match term ia1, ib with
708f4980 936 | A.Int x, B.Int (y,_) ->
34e49164
C
937 X.value_format_flag (fun use_value_equivalence ->
938 if use_value_equivalence
939 then
940 if equal_c_int x y
941 then do1()
942 else fail
943 else
944 if x =$= y
945 then do1()
946 else fail
947 )
948 | A.Char x, B.Char (y,_) when x =$= y (* todo: use kind ? *)
949 -> do1()
950 | A.Float x, B.Float (y,_) when x =$= y (* todo: use floatType ? *)
951 -> do1()
952
953 | A.String sa, B.String (sb,_kind) when sa =$= sb ->
954 (match ii with
955 | [ib1] ->
956 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
957 return (
958 ((A.Constant ia1)) +> wa,
959 ((B.Constant (ib), typ),[ib1])
960 ))
961 | _ -> fail (* multi string, not handled *)
962 )
485bce71 963
0708f913 964 | _, B.MultiString _ -> (* todo cocci? *) fail
485bce71 965 | _, (B.String _ | B.Float _ | B.Char _ | B.Int _) -> fail
34e49164
C
966 )
967
968
969 | A.FunCall (ea, ia1, eas, ia2), ((B.FunCall (eb, ebs), typ),ii) ->
970 (* todo: do special case to allow IdMetaFunc, cos doing the
971 * recursive call will be too late, match_ident will not have the
972 * info whether it was a function. todo: but how detect when do
973 * x.field = f; how know that f is a Func ? By having computed
974 * some information before the matching!
975 *
976 * Allow match with FunCall containing types. Now ast_cocci allow
977 * type in parameter, and morover ast_cocci allow f(...) and those
978 * ... could match type.
979 *)
980 let (ib1, ib2) = tuple_of_list2 ii in
113803cf
C
981 expression ea eb >>= (fun ea eb ->
982 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
983 tokenf ia2 ib2 >>= (fun ia2 ib2 ->
984 arguments (seqstyle eas) (A.undots eas) ebs >>= (fun easundots ebs ->
34e49164
C
985 let eas = redots eas easundots in
986 return (
987 ((A.FunCall (ea, ia1, eas, ia2)) +> wa,
988 ((B.FunCall (eb, ebs),typ), [ib1;ib2])
989 ))))))
990
991
992
993
994 | A.Assignment (ea1, opa, ea2, simple),
995 ((B.Assignment (eb1, opb, eb2), typ),ii) ->
996 let (opbi) = tuple_of_list1 ii in
997 if equal_assignOp (term opa) opb
998 then
999 expression ea1 eb1 >>= (fun ea1 eb1 ->
1000 expression ea2 eb2 >>= (fun ea2 eb2 ->
1001 tokenf opa opbi >>= (fun opa opbi ->
1002 return (
1003 ((A.Assignment (ea1, opa, ea2, simple))) +> wa,
1004 ((B.Assignment (eb1, opb, eb2), typ), [opbi])
1005 ))))
1006 else fail
1007
1008 | A.CondExpr(ea1,ia1,ea2opt,ia2,ea3),((B.CondExpr(eb1,eb2opt,eb3),typ),ii) ->
1009 let (ib1, ib2) = tuple_of_list2 ii in
1010 expression ea1 eb1 >>= (fun ea1 eb1 ->
1011 option expression ea2opt eb2opt >>= (fun ea2opt eb2opt ->
1012 expression ea3 eb3 >>= (fun ea3 eb3 ->
1013 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
1014 tokenf ia2 ib2 >>= (fun ia2 ib2 ->
1015 return (
1016 ((A.CondExpr(ea1,ia1,ea2opt,ia2,ea3))) +> wa,
1017 ((B.CondExpr (eb1, eb2opt, eb3),typ), [ib1;ib2])
1018 ))))))
1019
1020 (* todo?: handle some isomorphisms here ? *)
1021 | A.Postfix (ea, opa), ((B.Postfix (eb, opb), typ),ii) ->
1022 let opbi = tuple_of_list1 ii in
1023 if equal_fixOp (term opa) opb
1024 then
1025 expression ea eb >>= (fun ea eb ->
1026 tokenf opa opbi >>= (fun opa opbi ->
1027 return (
1028 ((A.Postfix (ea, opa))) +> wa,
1029 ((B.Postfix (eb, opb), typ),[opbi])
1030 )))
1031 else fail
1032
1033
1034 | A.Infix (ea, opa), ((B.Infix (eb, opb), typ),ii) ->
1035 let opbi = tuple_of_list1 ii in
1036 if equal_fixOp (term opa) opb
1037 then
1038 expression ea eb >>= (fun ea eb ->
1039 tokenf opa opbi >>= (fun opa opbi ->
1040 return (
1041 ((A.Infix (ea, opa))) +> wa,
1042 ((B.Infix (eb, opb), typ),[opbi])
1043 )))
1044 else fail
1045
1046 | A.Unary (ea, opa), ((B.Unary (eb, opb), typ),ii) ->
1047 let opbi = tuple_of_list1 ii in
1048 if equal_unaryOp (term opa) opb
1049 then
1050 expression ea eb >>= (fun ea eb ->
1051 tokenf opa opbi >>= (fun opa opbi ->
1052 return (
1053 ((A.Unary (ea, opa))) +> wa,
1054 ((B.Unary (eb, opb), typ),[opbi])
1055 )))
1056 else fail
1057
1058 | A.Binary (ea1, opa, ea2), ((B.Binary (eb1, opb, eb2), typ),ii) ->
1059 let opbi = tuple_of_list1 ii in
1060 if equal_binaryOp (term opa) opb
1061 then
1062 expression ea1 eb1 >>= (fun ea1 eb1 ->
1063 expression ea2 eb2 >>= (fun ea2 eb2 ->
1064 tokenf opa opbi >>= (fun opa opbi ->
1065 return (
1066 ((A.Binary (ea1, opa, ea2))) +> wa,
1067 ((B.Binary (eb1, opb, eb2), typ),[opbi]
1068 )))))
1069 else fail
1070
1071 | A.Nested (ea1, opa, ea2), eb ->
1072 let rec loop eb =
1073 (if A.get_test_exp ea1 && not (Ast_c.is_test eb) then fail
1074 else expression ea1 eb) >|+|>
1075 (match eb with
1076 ((B.Binary (eb1, opb, eb2), typ),ii)
1077 when equal_binaryOp (term opa) opb ->
1078 let opbi = tuple_of_list1 ii in
1079 let left_to_right =
1080 (expression ea1 eb1 >>= (fun ea1 eb1 ->
1081 expression ea2 eb2 >>= (fun ea2 eb2 ->
1082 tokenf opa opbi >>= (fun opa opbi ->
1083 return (
1084 ((A.Nested (ea1, opa, ea2))) +> wa,
1085 ((B.Binary (eb1, opb, eb2), typ),[opbi]
1086 )))))) in
1087 let right_to_left =
1088 (expression ea2 eb1 >>= (fun ea2 eb1 ->
1089 expression ea1 eb2 >>= (fun ea1 eb2 ->
1090 tokenf opa opbi >>= (fun opa opbi ->
1091 return (
1092 ((A.Nested (ea1, opa, ea2))) +> wa,
1093 ((B.Binary (eb1, opb, eb2), typ),[opbi]
1094 )))))) in
1095 let in_left =
1096 (loop eb1 >>= (fun ea1 eb1 ->
1097 expression ea2 eb2 >>= (fun ea2 eb2 ->
1098 tokenf opa opbi >>= (fun opa opbi ->
1099 return (
1100 ((A.Nested (ea1, opa, ea2))) +> wa,
1101 ((B.Binary (eb1, opb, eb2), typ),[opbi]
1102 )))))) in
1103 let in_right =
1104 (expression ea2 eb1 >>= (fun ea2 eb1 ->
1105 loop eb2 >>= (fun ea1 eb2 ->
1106 tokenf opa opbi >>= (fun opa opbi ->
1107 return (
1108 ((A.Nested (ea1, opa, ea2))) +> wa,
1109 ((B.Binary (eb1, opb, eb2), typ),[opbi]
1110 )))))) in
1111 left_to_right >|+|> right_to_left >|+|> in_left >|+|> in_right
1112 | _ -> fail) in
1113 loop eb
1114
1115 (* todo?: handle some isomorphisms here ? (with pointers = Unary Deref) *)
1116 | A.ArrayAccess (ea1, ia1, ea2, ia2),((B.ArrayAccess (eb1, eb2), typ),ii) ->
1117 let (ib1, ib2) = tuple_of_list2 ii in
1118 expression ea1 eb1 >>= (fun ea1 eb1 ->
1119 expression ea2 eb2 >>= (fun ea2 eb2 ->
1120 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
1121 tokenf ia2 ib2 >>= (fun ia2 ib2 ->
1122 return (
1123 ((A.ArrayAccess (ea1, ia1, ea2, ia2))) +> wa,
1124 ((B.ArrayAccess (eb1, eb2),typ), [ib1;ib2])
1125 )))))
1126
1127 (* todo?: handle some isomorphisms here ? *)
1128 | A.RecordAccess (ea, ia1, ida), ((B.RecordAccess (eb, idb), typ),ii) ->
b1b2de81
C
1129 let (ib1) = tuple_of_list1 ii in
1130 ident_cpp DontKnow ida idb >>= (fun ida idb ->
34e49164
C
1131 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
1132 expression ea eb >>= (fun ea eb ->
1133 return (
1134 ((A.RecordAccess (ea, ia1, ida))) +> wa,
b1b2de81 1135 ((B.RecordAccess (eb, idb), typ), [ib1])
34e49164
C
1136 ))))
1137
1138
1139
1140 | A.RecordPtAccess (ea,ia1,ida),((B.RecordPtAccess (eb, idb), typ), ii) ->
b1b2de81
C
1141 let (ib1) = tuple_of_list1 ii in
1142 ident_cpp DontKnow ida idb >>= (fun ida idb ->
34e49164
C
1143 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
1144 expression ea eb >>= (fun ea eb ->
1145 return (
1146 ((A.RecordPtAccess (ea, ia1, ida))) +> wa,
b1b2de81 1147 ((B.RecordPtAccess (eb, idb), typ), [ib1])
34e49164
C
1148 ))))
1149
1150
1151 (* todo?: handle some isomorphisms here ?
1152 * todo?: do some iso-by-absence on cast ?
1153 * by trying | ea, B.Case (typb, eb) -> match_e_e ea eb ?
1154 *)
1155
1156 | A.Cast (ia1, typa, ia2, ea), ((B.Cast (typb, eb), typ),ii) ->
1157 let (ib1, ib2) = tuple_of_list2 ii in
1158 fullType typa typb >>= (fun typa typb ->
1159 expression ea eb >>= (fun ea eb ->
1160 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
1161 tokenf ia2 ib2 >>= (fun ia2 ib2 ->
1162 return (
1163 ((A.Cast (ia1, typa, ia2, ea))) +> wa,
1164 ((B.Cast (typb, eb),typ),[ib1;ib2])
1165 )))))
1166
1167 | A.SizeOfExpr (ia1, ea), ((B.SizeOfExpr (eb), typ),ii) ->
1168 let ib1 = tuple_of_list1 ii in
1169 expression ea eb >>= (fun ea eb ->
1170 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
1171 return (
1172 ((A.SizeOfExpr (ia1, ea))) +> wa,
1173 ((B.SizeOfExpr (eb), typ),[ib1])
1174 )))
1175
1176 | A.SizeOfType (ia1, ia2, typa, ia3), ((B.SizeOfType typb, typ),ii) ->
1177 let (ib1,ib2,ib3) = tuple_of_list3 ii in
1178 fullType typa typb >>= (fun typa typb ->
1179 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
1180 tokenf ia2 ib2 >>= (fun ia2 ib2 ->
1181 tokenf ia3 ib3 >>= (fun ia3 ib3 ->
1182 return (
1183 ((A.SizeOfType (ia1, ia2, typa, ia3))) +> wa,
1184 ((B.SizeOfType (typb),typ),[ib1;ib2;ib3])
1185 )))))
1186
1187
1188 (* todo? iso ? allow all the combinations ? *)
1189 | A.Paren (ia1, ea, ia2), ((B.ParenExpr (eb), typ),ii) ->
1190 let (ib1, ib2) = tuple_of_list2 ii in
1191 expression ea eb >>= (fun ea eb ->
1192 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
1193 tokenf ia2 ib2 >>= (fun ia2 ib2 ->
1194 return (
1195 ((A.Paren (ia1, ea, ia2))) +> wa,
1196 ((B.ParenExpr (eb), typ), [ib1;ib2])
1197 ))))
1198
1199 | A.NestExpr(exps,None,true), eb ->
1200 (match A.unwrap exps with
1201 A.DOTS [exp] ->
1202 X.cocciExpExp expression exp eb >>= (fun exp eb ->
1203 return (
1204 (A.NestExpr(A.rewrap exps (A.DOTS [exp]),None,true)) +> wa,
1205 eb
1206 )
1207 )
1208 | _ ->
1209 failwith
1210 "for nestexpr, only handling the case with dots and only one exp")
1211
485bce71 1212 | A.NestExpr _, _ ->
34e49164
C
1213 failwith "only handling multi and no when code in a nest expr"
1214
1215 (* only in arg lists or in define body *)
485bce71 1216 | A.TypeExp _, _ -> fail
34e49164
C
1217
1218 (* only in arg lists *)
485bce71
C
1219 | A.MetaExprList _, _
1220 | A.EComma _, _
1221 | A.Ecircles _, _
1222 | A.Estars _, _
34e49164
C
1223 ->
1224 raise Impossible
1225
1226 | A.DisjExpr eas, eb ->
1227 eas +> List.fold_left (fun acc ea -> acc >|+|> (expression ea eb)) fail
1228
1229 | A.UniqueExp _,_ | A.OptExp _,_ ->
1230 failwith "not handling Opt/Unique/Multi on expr"
1231
1232 (* Because of Exp cant put a raise Impossible; have to put a fail *)
1233
1234 (* have not a counter part in coccinelle, for the moment *)
1235 | _, ((B.Sequence _,_),_)
1236 | _, ((B.StatementExpr _,_),_)
1237 | _, ((B.Constructor _,_),_)
1238 -> fail
1239
485bce71
C
1240
1241 | _,
1242 (((B.Cast (_, _)|B.ParenExpr _|B.SizeOfType _|B.SizeOfExpr _|
1243 B.RecordPtAccess (_, _)|
1244 B.RecordAccess (_, _)|B.ArrayAccess (_, _)|
1245 B.Binary (_, _, _)|B.Unary (_, _)|
1246 B.Infix (_, _)|B.Postfix (_, _)|
1247 B.Assignment (_, _, _)|B.CondExpr (_, _, _)|
1248 B.FunCall (_, _)|B.Constant _|B.Ident _),
1249 _),_)
1250 -> fail
1251
1252
1253
34e49164
C
1254
1255
34e49164 1256(* ------------------------------------------------------------------------- *)
b1b2de81 1257and (ident_cpp: info_ident -> (A.ident, B.name) matcher) =
708f4980 1258 fun infoidb ida idb ->
b1b2de81
C
1259 match idb with
1260 | B.RegularName (s, iis) ->
1261 let iis = tuple_of_list1 iis in
1262 ident infoidb ida (s, iis) >>= (fun ida (s,iis) ->
1263 return (
1264 ida,
1265 (B.RegularName (s, [iis]))
1266 ))
1267 | B.CppConcatenatedName _ | B.CppVariadicName _ |B.CppIdentBuilder _
708f4980
C
1268 ->
1269 (* This should be moved to the Id case of ident. Metavariables
1270 should be allowed to be bound to such variables. But doing so
1271 would require implementing an appropriate distr function *)
1272 fail
b1b2de81 1273
34e49164 1274and (ident: info_ident -> (A.ident, string * Ast_c.info) matcher) =
951c7801 1275 fun infoidb ida ((idb, iib)) -> (* (idb, iib) as ib *)
34e49164
C
1276 X.all_bound (A.get_inherited ida) >&&>
1277 match A.unwrap ida with
1278 | A.Id sa ->
1279 if (term sa) =$= idb then
1280 tokenf sa iib >>= (fun sa iib ->
1281 return (
1282 ((A.Id sa)) +> A.rewrap ida,
1283 (idb, iib)
1284 ))
1285 else fail
1286
34e49164 1287 | A.MetaId(mida,constraints,keep,inherited) ->
951c7801 1288 X.check_idconstraint satisfies_iconstraint constraints idb
34e49164
C
1289 (fun () ->
1290 let max_min _ = Lib_parsing_c.lin_col_by_pos [iib] in
1291 (* use drop_pos for ids so that the pos is not added a second time in
1292 the call to tokenf *)
1293 X.envf keep inherited (A.drop_pos mida, Ast_c.MetaIdVal (idb), max_min)
1294 (fun () ->
1295 tokenf mida iib >>= (fun mida iib ->
1296 return (
1297 ((A.MetaId (mida, constraints, keep, inherited)) +> A.rewrap ida,
1298 (idb, iib)
1299 )))
1300 ))
1301
1302 | A.MetaFunc(mida,constraints,keep,inherited) ->
1303 let is_function _ =
951c7801 1304 X.check_idconstraint satisfies_iconstraint constraints idb
34e49164
C
1305 (fun () ->
1306 let max_min _ = Lib_parsing_c.lin_col_by_pos [iib] in
1307 X.envf keep inherited (A.drop_pos mida,Ast_c.MetaFuncVal idb,max_min)
1308 (fun () ->
1309 tokenf mida iib >>= (fun mida iib ->
1310 return (
1311 ((A.MetaFunc(mida,constraints,keep,inherited)))+>A.rewrap ida,
1312 (idb, iib)
1313 ))
1314 )) in
1315 (match infoidb with
1316 | LocalFunction | Function -> is_function()
1317 | DontKnow ->
1318 failwith "MetaFunc, need more semantic info about id"
1319 (* the following implementation could possibly be useful, if one
1320 follows the convention that a macro is always in capital letters
1321 and that a macro is not a function.
1322 (if idb =~ "^[A-Z_][A-Z_0-9]*$" then fail else is_function())*)
1323 )
1324
1325 | A.MetaLocalFunc(mida,constraints,keep,inherited) ->
1326 (match infoidb with
1327 | LocalFunction ->
951c7801 1328 X.check_idconstraint satisfies_iconstraint constraints idb
34e49164
C
1329 (fun () ->
1330 let max_min _ = Lib_parsing_c.lin_col_by_pos [iib] in
1331 X.envf keep inherited
1332 (A.drop_pos mida,Ast_c.MetaLocalFuncVal idb, max_min)
1333 (fun () ->
1334 tokenf mida iib >>= (fun mida iib ->
1335 return (
1336 ((A.MetaLocalFunc(mida,constraints,keep,inherited)))
1337 +> A.rewrap ida,
1338 (idb, iib)
1339 ))
1340 ))
1341 | Function -> fail
1342 | DontKnow -> failwith "MetaLocalFunc, need more semantic info about id"
1343 )
1344
1345 | A.OptIdent _ | A.UniqueIdent _ ->
1346 failwith "not handling Opt/Unique for ident"
1347
1348
1349
1350(* ------------------------------------------------------------------------- *)
1351and (arguments: sequence ->
1352 (A.expression list, Ast_c.argument Ast_c.wrap2 list) matcher) =
1353 fun seqstyle eas ebs ->
1354 match seqstyle with
1355 | Unordered -> failwith "not handling ooo"
1356 | Ordered ->
1357 arguments_bis eas (Ast_c.split_comma ebs) >>= (fun eas ebs_splitted ->
1358 return (eas, (Ast_c.unsplit_comma ebs_splitted))
1359 )
1360(* because '...' can match nothing, need to take care when have
1361 * ', ...' or '...,' as in f(..., X, Y, ...). It must match
1362 * f(1,2) for instance.
1363 * So I have added special cases such as (if startxs = []) and code
1364 * in the Ecomma matching rule.
1365 *
1366 * old: Must do some try, for instance when f(...,X,Y,...) have to
1367 * test the transfo for all the combinaitions and if multiple transfo
1368 * possible ? pb ? => the type is to return a expression option ? use
1369 * some combinators to help ?
1370 * update: with the tag-SP approach, no more a problem.
1371 *)
1372
1373and arguments_bis = fun eas ebs ->
1374 match eas, ebs with
1375 | [], [] -> return ([], [])
1376 | [], eb::ebs -> fail
1377 | ea::eas, ebs ->
1378 X.all_bound (A.get_inherited ea) >&&>
1379 (match A.unwrap ea, ebs with
1380 | A.Edots (mcode, optexpr), ys ->
1381 (* todo: if optexpr, then a WHEN and so may have to filter yys *)
1382 if optexpr <> None then failwith "not handling when in argument";
1383
1384 (* '...' can take more or less the beginnings of the arguments *)
1385 let startendxs = Common.zip (Common.inits ys) (Common.tails ys) in
1386 startendxs +> List.fold_left (fun acc (startxs, endxs) ->
1387 acc >||> (
1388
1389 (* allow '...', and maybe its associated ',' to match nothing.
1390 * for the associated ',' see below how we handle the EComma
1391 * to match nothing.
1392 *)
b1b2de81 1393 (if null startxs
34e49164
C
1394 then
1395 if mcode_contain_plus (mcodekind mcode)
1396 then fail
1397 (* failwith "I have no token that I could accroche myself on" *)
1398 else return (dots2metavar mcode, [])
1399 else
1400 (* subtil: we dont want the '...' to match until the
1401 * comma. cf -test pb_params_iso. We would get at
1402 * "already tagged" error.
1403 * this is because both f (... x, ...) and f (..., x, ...)
1404 * would match a f(x,3) with our "optional-comma" strategy.
1405 *)
1406 (match Common.last startxs with
1407 | Right _ -> fail
1408 | Left _ ->
1409 X.distrf_args (dots2metavar mcode) startxs
1410 )
1411 )
1412 >>= (fun mcode startxs ->
1413 let mcode = metavar2dots mcode in
1414 arguments_bis eas endxs >>= (fun eas endxs ->
1415 return (
1416 (A.Edots (mcode, optexpr) +> A.rewrap ea) ::eas,
1417 startxs ++ endxs
1418 )))
1419 )
1420 ) fail
1421
1422 | A.EComma ia1, Right ii::ebs ->
1423 let ib1 = tuple_of_list1 ii in
1424 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
1425 arguments_bis eas ebs >>= (fun eas ebs ->
1426 return (
1427 (A.EComma ia1 +> A.rewrap ea)::eas,
1428 (Right [ib1])::ebs
1429 )
1430 ))
1431 | A.EComma ia1, ebs ->
1432 (* allow ',' to maching nothing. optional comma trick *)
1433 if mcode_contain_plus (mcodekind ia1)
1434 then fail
1435 else arguments_bis eas ebs
1436
1437 | A.MetaExprList(ida,leninfo,keep,inherited),ys ->
1438 let startendxs = Common.zip (Common.inits ys) (Common.tails ys) in
1439 startendxs +> List.fold_left (fun acc (startxs, endxs) ->
1440 acc >||> (
1441 let ok =
b1b2de81 1442 if null startxs
34e49164
C
1443 then
1444 if mcode_contain_plus (mcodekind ida)
1445 then false
1446 (* failwith "no token that I could accroche myself on" *)
1447 else true
1448 else
1449 (match Common.last startxs with
1450 | Right _ -> false
1451 | Left _ -> true
1452 )
1453 in
1454 if not ok
1455 then fail
1456 else
1457 let startxs' = Ast_c.unsplit_comma startxs in
1458 let len = List.length startxs' in
1459
1460 (match leninfo with
1461 | Some (lenname,lenkeep,leninherited) ->
1462 let max_min _ = failwith "no pos" in
1463 X.envf lenkeep leninherited
1464 (lenname, Ast_c.MetaListlenVal (len), max_min)
1465 | None -> function f -> f()
1466 )
1467 (fun () ->
1468 let max_min _ =
1469 Lib_parsing_c.lin_col_by_pos
1470 (Lib_parsing_c.ii_of_args startxs) in
1471 X.envf keep inherited
1472 (ida, Ast_c.MetaExprListVal startxs', max_min)
1473 (fun () ->
b1b2de81 1474 if null startxs
34e49164
C
1475 then return (ida, [])
1476 else X.distrf_args ida (Ast_c.split_comma startxs')
1477 )
1478 >>= (fun ida startxs ->
1479 arguments_bis eas endxs >>= (fun eas endxs ->
1480 return (
1481 (A.MetaExprList(ida,leninfo,keep,inherited))
1482 +> A.rewrap ea::eas,
1483 startxs ++ endxs
1484 ))
1485 )
1486 )
1487 )) fail
1488
1489
1490 | _unwrapx, (Left eb)::ebs ->
1491 argument ea eb >>= (fun ea eb ->
1492 arguments_bis eas ebs >>= (fun eas ebs ->
1493 return (ea::eas, Left eb::ebs)
1494 ))
1495 | _unwrapx, (Right y)::ys -> raise Impossible
1496 | _unwrapx, [] -> fail
1497 )
1498
1499
113803cf 1500and argument arga argb =
34e49164
C
1501 X.all_bound (A.get_inherited arga) >&&>
1502 match A.unwrap arga, argb with
b1b2de81
C
1503 | A.TypeExp tya,
1504 Right (B.ArgType {B.p_register=b,iib; p_namei=sopt;p_type=tyb}) ->
34e49164
C
1505
1506 if b || sopt <> None
1507 then
1508 (* failwith "the argument have a storage and ast_cocci does not have"*)
1509 fail
1510 else
b1b2de81 1511 (* b = false and sopt = None *)
34e49164
C
1512 fullType tya tyb >>= (fun tya tyb ->
1513 return (
1514 (A.TypeExp tya) +> A.rewrap arga,
b1b2de81
C
1515 (Right (B.ArgType {B.p_register=(b,iib);
1516 p_namei=sopt;
1517 p_type=tyb;}))
34e49164
C
1518 ))
1519
1520 | A.TypeExp tya, _ -> fail
b1b2de81 1521 | _, Right (B.ArgType _) -> fail
113803cf
C
1522 | _, Left argb ->
1523 expression arga argb >>= (fun arga argb ->
34e49164
C
1524 return (arga, Left argb)
1525 )
1526 | _, Right (B.ArgAction y) -> fail
1527
1528
1529(* ------------------------------------------------------------------------- *)
1530(* todo? facto code with argument ? *)
1531and (parameters: sequence ->
1532 (A.parameterTypeDef list, Ast_c.parameterType Ast_c.wrap2 list)
1533 matcher) =
1534 fun seqstyle eas ebs ->
1535 match seqstyle with
1536 | Unordered -> failwith "not handling ooo"
1537 | Ordered ->
1538 parameters_bis eas (Ast_c.split_comma ebs) >>= (fun eas ebs_splitted ->
1539 return (eas, (Ast_c.unsplit_comma ebs_splitted))
1540 )
1541
1542
1543and parameters_bis eas ebs =
1544 match eas, ebs with
1545 | [], [] -> return ([], [])
1546 | [], eb::ebs -> fail
1547 | ea::eas, ebs ->
1548 (* the management of positions is inlined into each case, because
1549 sometimes there is a Param and sometimes a ParamList *)
1550 X.all_bound (A.get_inherited ea) >&&>
1551 (match A.unwrap ea, ebs with
1552 | A.Pdots (mcode), ys ->
1553
1554 (* '...' can take more or less the beginnings of the arguments *)
1555 let startendxs = Common.zip (Common.inits ys) (Common.tails ys) in
1556 startendxs +> List.fold_left (fun acc (startxs, endxs) ->
1557 acc >||> (
1558
b1b2de81 1559 (if null startxs
34e49164
C
1560 then
1561 if mcode_contain_plus (mcodekind mcode)
1562 then fail
1563 (* failwith "I have no token that I could accroche myself on"*)
1564 else return (dots2metavar mcode, [])
1565 else
1566 (match Common.last startxs with
1567 | Right _ -> fail
1568 | Left _ ->
1569 X.distrf_params (dots2metavar mcode) startxs
1570 )
1571 ) >>= (fun mcode startxs ->
1572 let mcode = metavar2dots mcode in
1573 parameters_bis eas endxs >>= (fun eas endxs ->
1574 return (
1575 (A.Pdots (mcode) +> A.rewrap ea) ::eas,
1576 startxs ++ endxs
1577 )))
1578 )
1579 ) fail
1580
1581 | A.PComma ia1, Right ii::ebs ->
1582 let ib1 = tuple_of_list1 ii in
1583 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
1584 parameters_bis eas ebs >>= (fun eas ebs ->
1585 return (
1586 (A.PComma ia1 +> A.rewrap ea)::eas,
1587 (Right [ib1])::ebs
1588 )
1589 ))
1590
1591 | A.PComma ia1, ebs ->
1592 (* try optional comma trick *)
1593 if mcode_contain_plus (mcodekind ia1)
1594 then fail
1595 else parameters_bis eas ebs
1596
1597
1598 | A.MetaParamList(ida,leninfo,keep,inherited),ys->
1599 let startendxs = Common.zip (Common.inits ys) (Common.tails ys) in
1600 startendxs +> List.fold_left (fun acc (startxs, endxs) ->
1601 acc >||> (
1602 let ok =
b1b2de81 1603 if null startxs
34e49164
C
1604 then
1605 if mcode_contain_plus (mcodekind ida)
1606 then false
1607 (* failwith "I have no token that I could accroche myself on" *)
1608 else true
1609 else
1610 (match Common.last startxs with
1611 | Right _ -> false
1612 | Left _ -> true
1613 )
1614 in
1615 if not ok
1616 then fail
1617 else
1618 let startxs' = Ast_c.unsplit_comma startxs in
1619 let len = List.length startxs' in
1620
1621 (match leninfo with
1622 Some (lenname,lenkeep,leninherited) ->
1623 let max_min _ = failwith "no pos" in
1624 X.envf lenkeep leninherited
1625 (lenname, Ast_c.MetaListlenVal (len), max_min)
1626 | None -> function f -> f()
1627 )
1628 (fun () ->
1629 let max_min _ =
1630 Lib_parsing_c.lin_col_by_pos
1631 (Lib_parsing_c.ii_of_params startxs) in
1632 X.envf keep inherited
1633 (ida, Ast_c.MetaParamListVal startxs', max_min)
1634 (fun () ->
b1b2de81 1635 if null startxs
34e49164
C
1636 then return (ida, [])
1637 else X.distrf_params ida (Ast_c.split_comma startxs')
1638 ) >>= (fun ida startxs ->
1639 parameters_bis eas endxs >>= (fun eas endxs ->
1640 return (
1641 (A.MetaParamList(ida,leninfo,keep,inherited))
1642 +> A.rewrap ea::eas,
1643 startxs ++ endxs
1644 ))
1645 )
1646 ))
1647 ) fail
1648
1649
1650 | A.VoidParam ta, ys ->
1651 (match eas, ebs with
1652 | [], [Left eb] ->
b1b2de81
C
1653 let {B.p_register=(hasreg,iihasreg);
1654 p_namei = idbopt;
1655 p_type=tb; } = eb in
1656
1657 if idbopt =*= None && not hasreg
34e49164
C
1658 then
1659 match tb with
1660 | (qub, (B.BaseType B.Void,_)) ->
1661 fullType ta tb >>= (fun ta tb ->
1662 return (
1663 [(A.VoidParam ta) +> A.rewrap ea],
b1b2de81
C
1664 [Left {B.p_register=(hasreg, iihasreg);
1665 p_namei = idbopt;
1666 p_type = tb;}]
34e49164
C
1667 ))
1668 | _ -> fail
1669 else fail
1670 | _ -> fail
1671 )
1672
1673 | (A.OptParam _ | A.UniqueParam _), _ ->
1674 failwith "handling Opt/Unique for Param"
1675
1676 | A.Pcircles (_), ys -> raise Impossible (* in Ordered mode *)
1677
1678
1679 | A.MetaParam (ida,keep,inherited), (Left eb)::ebs ->
1680 (* todo: use quaopt, hasreg ? *)
1681 let max_min _ =
1682 Lib_parsing_c.lin_col_by_pos (Lib_parsing_c.ii_of_param eb) in
1683 X.envf keep inherited (ida,Ast_c.MetaParamVal eb,max_min) (fun () ->
1684 X.distrf_param ida eb
1685 ) >>= (fun ida eb ->
1686 parameters_bis eas ebs >>= (fun eas ebs ->
1687 return (
1688 (A.MetaParam(ida,keep,inherited))+> A.rewrap ea::eas,
1689 (Left eb)::ebs
1690 )))
1691
1692
1693 | A.Param (typa, idaopt), (Left eb)::ebs ->
1694 (*this should succeed if the C code has a name, and fail otherwise*)
1695 parameter (idaopt, typa) eb >>= (fun (idaopt, typa) eb ->
1696 parameters_bis eas ebs >>= (fun eas ebs ->
1697 return (
1698 (A.Param (typa, idaopt))+> A.rewrap ea :: eas,
1699 (Left eb)::ebs
1700 )))
1701
1702 | _unwrapx, (Right y)::ys -> raise Impossible
1703 | _unwrapx, [] -> fail
1704 )
1705
1706
1707
b1b2de81
C
1708(*
1709let split_register_param = fun (hasreg, idb, ii_b_s) ->
1710 match hasreg, idb, ii_b_s with
1711 | false, Some s, [i1] -> Left (s, [], i1)
1712 | true, Some s, [i1;i2] -> Left (s, [i1], i2)
1713 | _, None, ii -> Right ii
1714 | _ -> raise Impossible
1715*)
1716
1717
1718and parameter = fun (idaopt, typa) paramb ->
34e49164 1719
b1b2de81
C
1720 let {B.p_register = (hasreg,iihasreg);
1721 p_namei = nameidbopt;
1722 p_type = typb;} = paramb in
34e49164 1723
34e49164 1724 fullType typa typb >>= (fun typa typb ->
b1b2de81
C
1725 match idaopt, nameidbopt with
1726 | Some ida, Some nameidb ->
34e49164 1727 (* todo: if minus on ida, should also minus the iihasreg ? *)
b1b2de81 1728 ident_cpp DontKnow ida nameidb >>= (fun ida nameidb ->
34e49164
C
1729 return (
1730 (Some ida, typa),
b1b2de81
C
1731 {B.p_register = (hasreg, iihasreg);
1732 p_namei = Some (nameidb);
1733 p_type = typb}
34e49164
C
1734 ))
1735
b1b2de81 1736 | None, None ->
34e49164
C
1737 return (
1738 (None, typa),
b1b2de81
C
1739 {B.p_register=(hasreg,iihasreg);
1740 p_namei = None;
1741 p_type = typb;}
34e49164
C
1742 )
1743
1744
1745 (* why handle this case ? because of transform_proto ? we may not
1746 * have an ident in the proto.
1747 * If have some plus on ida ? do nothing about ida ?
1748 *)
1749 (* not anymore !!! now that julia is handling the proto.
1750 | _, Right iihasreg ->
1751 return (
1752 (idaopt, typa),
1753 ((hasreg, None, typb), iihasreg)
1754 )
1755 *)
1756
b1b2de81
C
1757 | Some _, None -> fail
1758 | None, Some _ -> fail
34e49164
C
1759 )
1760
1761
1762
1763
1764(* ------------------------------------------------------------------------- *)
1765and (declaration: (A.mcodekind * bool * A.declaration,B.declaration) matcher) =
1766 fun (mckstart, allminus, decla) declb ->
1767 X.all_bound (A.get_inherited decla) >&&>
1768 match A.unwrap decla, declb with
1769
1770 (* Un MetaDecl est introduit dans l'asttoctl pour sauter au dessus
1771 * de toutes les declarations qui sont au debut d'un fonction et
1772 * commencer le reste du match au premier statement. Alors, ca matche
1773 * n'importe quelle declaration. On n'a pas besoin d'ajouter
1774 * quoi que ce soit dans l'environnement. C'est une sorte de DDots.
1775 *
1776 * When the SP want to remove the whole function, the minus is not
1777 * on the MetaDecl but on the MetaRuleElem. So there should
1778 * be no transform of MetaDecl, just matching are allowed.
1779 *)
1780
1781 | A.MetaDecl(ida,_keep,_inherited), _ -> (* keep ? inherited ? *)
1782 (* todo: should not happen in transform mode *)
1783 return ((mckstart, allminus, decla), declb)
1784
1785
1786
1787 | _, (B.DeclList ([var], iiptvirgb::iifakestart::iisto)) ->
1788 onedecl allminus decla (var,iiptvirgb,iisto) >>=
1789 (fun decla (var,iiptvirgb,iisto)->
1790 X.tokenf_mck mckstart iifakestart >>= (fun mckstart iifakestart ->
1791 return (
1792 (mckstart, allminus, decla),
1793 (B.DeclList ([var], iiptvirgb::iifakestart::iisto))
1794 )))
1795
1796 | _, (B.DeclList (xs, iiptvirgb::iifakestart::iisto)) ->
b1b2de81 1797 if X.mode =*= PatternMode
34e49164
C
1798 then
1799 xs +> List.fold_left (fun acc var ->
1800 acc >||> (
1801 X.tokenf_mck mckstart iifakestart >>= (fun mckstart iifakestart ->
1802 onedecl allminus decla (var, iiptvirgb, iisto) >>=
1803 (fun decla (var, iiptvirgb, iisto) ->
1804 return (
1805 (mckstart, allminus, decla),
1806 (B.DeclList ([var], iiptvirgb::iifakestart::iisto))
1807 )))))
1808 fail
1809 else
1810 failwith "More that one variable in decl. Have to split to transform."
1811
1812 | A.MacroDecl (sa,lpa,eas,rpa,enda), B.MacroDecl ((sb,ebs),ii) ->
1813 let (iisb, lpb, rpb, iiendb, iifakestart, iistob) =
1814 (match ii with
1815 | iisb::lpb::rpb::iiendb::iifakestart::iisto ->
1816 (iisb,lpb,rpb,iiendb, iifakestart,iisto)
1817 | _ -> raise Impossible
1818 ) in
1819 (if allminus
1820 then minusize_list iistob
1821 else return ((), iistob)
1822 ) >>= (fun () iistob ->
1823
1824 X.tokenf_mck mckstart iifakestart >>= (fun mckstart iifakestart ->
1825 ident DontKnow sa (sb, iisb) >>= (fun sa (sb, iisb) ->
1826 tokenf lpa lpb >>= (fun lpa lpb ->
1827 tokenf rpa rpb >>= (fun rpa rpb ->
1828 tokenf enda iiendb >>= (fun enda iiendb ->
1829 arguments (seqstyle eas) (A.undots eas) ebs >>= (fun easundots ebs ->
1830 let eas = redots eas easundots in
1831
1832 return (
1833 (mckstart, allminus,
1834 (A.MacroDecl (sa,lpa,eas,rpa,enda)) +> A.rewrap decla),
1835 (B.MacroDecl ((sb,ebs),
1836 [iisb;lpb;rpb;iiendb;iifakestart] ++ iistob))
1837 ))))))))
485bce71 1838
708f4980 1839 | _, (B.MacroDecl _ |B.DeclList _) -> fail
34e49164
C
1840
1841
1842
1843and onedecl = fun allminus decla (declb, iiptvirgb, iistob) ->
1844 X.all_bound (A.get_inherited decla) >&&>
1845 match A.unwrap decla, declb with
1846
1847 (* kind of typedef iso, we must unfold, it's for the case
1848 * T { }; that we want to match against typedef struct { } xx_t;
1849 *)
1850 | A.TyDecl (tya0, ptvirga),
b1b2de81 1851 ({B.v_namei = Some (nameidb, None);
485bce71
C
1852 B.v_type = typb0;
1853 B.v_storage = (B.StoTypedef, inl);
1854 B.v_local = local;
1855 B.v_attr = attrs;
978fd7e5 1856 B.v_type_bis = typb0bis;
485bce71 1857 }, iivirg) ->
34e49164
C
1858
1859 (match A.unwrap tya0, typb0 with
1860 | A.Type(cv1,tya1), ((qu,il),typb1) ->
1861
1862 (match A.unwrap tya1, typb1 with
1863 | A.StructUnionDef(tya2, lba, declsa, rba),
1864 (B.StructUnion (sub, sbopt, declsb), ii) ->
1865
1866 let (iisub, iisbopt, lbb, rbb) =
1867 match sbopt with
1868 | None ->
1869 let (iisub, lbb, rbb) = tuple_of_list3 ii in
1870 (iisub, [], lbb, rbb)
1871 | Some s ->
1872 pr2 (sprintf
1873 "warning: both a typedef (%s) and struct name introduction (%s)"
b1b2de81 1874 (Ast_c.str_of_name nameidb) s
34e49164
C
1875 );
1876 pr2 "warning: I will consider only the typedef";
1877 let (iisub, iisb, lbb, rbb) = tuple_of_list4 ii in
1878 (iisub, [iisb], lbb, rbb)
1879 in
1880 let structnameb =
1881 structdef_to_struct_name
1882 (Ast_c.nQ, (B.StructUnion (sub, sbopt, declsb), ii))
1883 in
1884 let fake_typeb =
b1b2de81
C
1885 Ast_c.nQ,((B.TypeName (nameidb, Some
1886 (Lib_parsing_c.al_type structnameb))), [])
34e49164
C
1887 in
1888
1889 tokenf ptvirga iiptvirgb >>= (fun ptvirga iiptvirgb ->
1890 tokenf lba lbb >>= (fun lba lbb ->
1891 tokenf rba rbb >>= (fun rba rbb ->
1892 struct_fields (A.undots declsa) declsb >>=(fun undeclsa declsb ->
1893 let declsa = redots declsa undeclsa in
1894
1895 (match A.unwrap tya2 with
1896 | A.Type(cv3, tya3) ->
1897 (match A.unwrap tya3 with
1898 | A.MetaType(ida,keep, inherited) ->
1899
1900 fullType tya2 fake_typeb >>= (fun tya2 fake_typeb ->
1901 let tya1 =
1902 A.StructUnionDef(tya2,lba,declsa,rba)+> A.rewrap tya1 in
1903 let tya0 = A.Type(cv1, tya1) +> A.rewrap tya0 in
1904
1905
1906 let typb1 = B.StructUnion (sub,sbopt, declsb),
1907 [iisub] @ iisbopt @ [lbb;rbb] in
1908 let typb0 = ((qu, il), typb1) in
1909
1910 match fake_typeb with
b1b2de81 1911 | _nQ, ((B.TypeName (nameidb, _typ)),[]) ->
34e49164
C
1912
1913 return (
1914 (A.TyDecl (tya0, ptvirga)) +> A.rewrap decla,
b1b2de81 1915 (({B.v_namei = Some (nameidb, None);
485bce71
C
1916 B.v_type = typb0;
1917 B.v_storage = (B.StoTypedef, inl);
1918 B.v_local = local;
1919 B.v_attr = attrs;
978fd7e5 1920 B.v_type_bis = typb0bis;
485bce71 1921 },
34e49164
C
1922 iivirg),iiptvirgb,iistob)
1923 )
1924 | _ -> raise Impossible
1925 )
1926
1927 | A.StructUnionName(sua, sa) ->
1928
1929 fullType tya2 structnameb >>= (fun tya2 structnameb ->
1930
1931 let tya1 = A.StructUnionDef(tya2,lba,declsa,rba)+> A.rewrap tya1
1932 in
1933 let tya0 = A.Type(cv1, tya1) +> A.rewrap tya0 in
1934
1935 match structnameb with
1936 | _nQ, (B.StructUnionName (sub, s), [iisub;iisbopt]) ->
1937
1938 let typb1 = B.StructUnion (sub,sbopt, declsb),
1939 [iisub;iisbopt;lbb;rbb] in
1940 let typb0 = ((qu, il), typb1) in
1941
1942 return (
1943 (A.TyDecl (tya0, ptvirga)) +> A.rewrap decla,
b1b2de81 1944 (({B.v_namei = Some (nameidb, None);
485bce71
C
1945 B.v_type = typb0;
1946 B.v_storage = (B.StoTypedef, inl);
1947 B.v_local = local;
1948 B.v_attr = attrs;
978fd7e5 1949 B.v_type_bis = typb0bis;
485bce71 1950 },
34e49164
C
1951 iivirg),iiptvirgb,iistob)
1952 )
1953 | _ -> raise Impossible
1954 )
1955 | _ -> raise Impossible
1956 )
1957 | _ -> fail
1958 )))))
1959 | _ -> fail
1960 )
1961 | _ -> fail
1962 )
1963
1964 | A.UnInit (stoa, typa, ida, ptvirga),
b1b2de81
C
1965 ({B.v_namei= Some (nameidb, _);B.v_storage= (B.StoTypedef,_);}, iivirg)
1966 -> fail
34e49164
C
1967
1968 | A.Init (stoa, typa, ida, eqa, inia, ptvirga),
b1b2de81
C
1969 ({B.v_namei=Some(nameidb, _);B.v_storage=(B.StoTypedef,_);}, iivirg)
1970 -> fail
34e49164
C
1971
1972
1973
1974 (* could handle iso here but handled in standard.iso *)
1975 | A.UnInit (stoa, typa, ida, ptvirga),
b1b2de81 1976 ({B.v_namei = Some (nameidb, None);
485bce71
C
1977 B.v_type = typb;
1978 B.v_storage = stob;
1979 B.v_local = local;
1980 B.v_attr = attrs;
978fd7e5 1981 B.v_type_bis = typbbis;
485bce71
C
1982 }, iivirg) ->
1983
34e49164
C
1984 tokenf ptvirga iiptvirgb >>= (fun ptvirga iiptvirgb ->
1985 fullType typa typb >>= (fun typa typb ->
b1b2de81 1986 ident_cpp DontKnow ida nameidb >>= (fun ida nameidb ->
34e49164
C
1987 storage_optional_allminus allminus stoa (stob, iistob) >>=
1988 (fun stoa (stob, iistob) ->
1989 return (
1990 (A.UnInit (stoa, typa, ida, ptvirga)) +> A.rewrap decla,
b1b2de81 1991 (({B.v_namei = Some (nameidb, None);
485bce71
C
1992 B.v_type = typb;
1993 B.v_storage = stob;
1994 B.v_local = local;
1995 B.v_attr = attrs;
978fd7e5 1996 B.v_type_bis = typbbis;
485bce71 1997 },iivirg),
34e49164
C
1998 iiptvirgb,iistob)
1999 )))))
2000
2001 | A.Init (stoa, typa, ida, eqa, inia, ptvirga),
b1b2de81 2002 ({B.v_namei = Some(nameidb, Some (iieqb, inib));
485bce71
C
2003 B.v_type = typb;
2004 B.v_storage = stob;
2005 B.v_local = local;
2006 B.v_attr = attrs;
978fd7e5 2007 B.v_type_bis = typbbis;
485bce71 2008 },iivirg)
34e49164
C
2009 ->
2010 tokenf ptvirga iiptvirgb >>= (fun ptvirga iiptvirgb ->
2011 tokenf eqa iieqb >>= (fun eqa iieqb ->
2012 fullType typa typb >>= (fun typa typb ->
b1b2de81 2013 ident_cpp DontKnow ida nameidb >>= (fun ida nameidb ->
34e49164
C
2014 storage_optional_allminus allminus stoa (stob, iistob) >>=
2015 (fun stoa (stob, iistob) ->
2016 initialiser inia inib >>= (fun inia inib ->
2017 return (
2018 (A.Init (stoa, typa, ida, eqa, inia, ptvirga)) +> A.rewrap decla,
b1b2de81 2019 (({B.v_namei = Some(nameidb, Some (iieqb, inib));
485bce71
C
2020 B.v_type = typb;
2021 B.v_storage = stob;
2022 B.v_local = local;
2023 B.v_attr = attrs;
978fd7e5 2024 B.v_type_bis = typbbis;
485bce71 2025 },iivirg),
34e49164
C
2026 iiptvirgb,iistob)
2027 )))))))
2028
2029 (* do iso-by-absence here ? allow typedecl and var ? *)
485bce71
C
2030 | A.TyDecl (typa, ptvirga),
2031 ({B.v_namei = None; B.v_type = typb;
2032 B.v_storage = stob;
2033 B.v_local = local;
2034 B.v_attr = attrs;
978fd7e5 2035 B.v_type_bis = typbbis;
485bce71
C
2036 }, iivirg) ->
2037
b1b2de81 2038 if stob =*= (B.NoSto, false)
34e49164
C
2039 then
2040 tokenf ptvirga iiptvirgb >>= (fun ptvirga iiptvirgb ->
2041 fullType typa typb >>= (fun typa typb ->
2042 return (
2043 (A.TyDecl (typa, ptvirga)) +> A.rewrap decla,
485bce71
C
2044 (({B.v_namei = None;
2045 B.v_type = typb;
2046 B.v_storage = stob;
2047 B.v_local = local;
2048 B.v_attr = attrs;
978fd7e5 2049 B.v_type_bis = typbbis;
485bce71 2050 }, iivirg), iiptvirgb, iistob)
34e49164
C
2051 )))
2052 else fail
2053
2054
2055 | A.Typedef (stoa, typa, ida, ptvirga),
b1b2de81 2056 ({B.v_namei = Some (nameidb, None);
485bce71
C
2057 B.v_type = typb;
2058 B.v_storage = (B.StoTypedef,inline);
2059 B.v_local = local;
2060 B.v_attr = attrs;
978fd7e5 2061 B.v_type_bis = typbbis;
485bce71 2062 },iivirg) ->
34e49164
C
2063
2064 tokenf ptvirga iiptvirgb >>= (fun ptvirga iiptvirgb ->
2065 fullType typa typb >>= (fun typa typb ->
2066 (match iistob with
2067 | [iitypedef] ->
2068 tokenf stoa iitypedef >>= (fun stoa iitypedef ->
2069 return (stoa, [iitypedef])
2070 )
0708f913 2071 | _ -> failwith "weird, have both typedef and inline or nothing";
34e49164
C
2072 ) >>= (fun stoa iistob ->
2073 (match A.unwrap ida with
2074 | A.MetaType(_,_,_) ->
2075
2076 let fake_typeb =
b1b2de81 2077 Ast_c.nQ, ((B.TypeName (nameidb, Ast_c.noTypedefDef())), [])
34e49164
C
2078 in
2079 fullTypebis ida fake_typeb >>= (fun ida fake_typeb ->
2080 match fake_typeb with
b1b2de81
C
2081 | _nQ, ((B.TypeName (nameidb, _typ)), []) ->
2082 return (ida, nameidb)
34e49164
C
2083 | _ -> raise Impossible
2084 )
2085
2086 | A.TypeName sa ->
b1b2de81
C
2087 (match nameidb with
2088 | B.RegularName (sb, iidb) ->
2089 let iidb1 = tuple_of_list1 iidb in
2090
2091 if (term sa) =$= sb
2092 then
2093 tokenf sa iidb1 >>= (fun sa iidb1 ->
2094 return (
2095 (A.TypeName sa) +> A.rewrap ida,
2096 B.RegularName (sb, [iidb1])
2097 ))
2098 else fail
2099
2100 | B.CppConcatenatedName _ | B.CppVariadicName _ |B.CppIdentBuilder _
2101 -> raise Todo
2102 )
2103
34e49164
C
2104 | _ -> raise Impossible
2105
b1b2de81 2106 ) >>= (fun ida nameidb ->
34e49164
C
2107 return (
2108 (A.Typedef (stoa, typa, ida, ptvirga)) +> A.rewrap decla,
b1b2de81 2109 (({B.v_namei = Some (nameidb, None);
485bce71
C
2110 B.v_type = typb;
2111 B.v_storage = (B.StoTypedef,inline);
2112 B.v_local = local;
2113 B.v_attr = attrs;
978fd7e5 2114 B.v_type_bis = typbbis;
485bce71 2115 },
34e49164
C
2116 iivirg),
2117 iiptvirgb, iistob)
2118 )
2119 ))))
2120
2121
485bce71 2122 | _, ({B.v_namei = None;}, _) ->
0708f913 2123 (* old: failwith "no variable in this declaration, weird" *)
34e49164
C
2124 fail
2125
2126
2127
2128 | A.DisjDecl declas, declb ->
2129 declas +> List.fold_left (fun acc decla ->
2130 acc >|+|>
2131 (* (declaration (mckstart, allminus, decla) declb) *)
2132 (onedecl allminus decla (declb,iiptvirgb, iistob))
2133 ) fail
2134
2135
2136
2137 (* only in struct type decls *)
2138 | A.Ddots(dots,whencode), _ ->
2139 raise Impossible
2140
485bce71 2141 | A.OptDecl _, _ | A.UniqueDecl _, _ ->
34e49164
C
2142 failwith "not handling Opt/Unique Decl"
2143
b1b2de81
C
2144 | _, ({B.v_namei=Some _}, _) ->
2145 fail
34e49164 2146
34e49164
C
2147
2148
2149
2150(* ------------------------------------------------------------------------- *)
2151
2152and (initialiser: (A.initialiser, Ast_c.initialiser) matcher) = fun ia ib ->
2153 X.all_bound (A.get_inherited ia) >&&>
2154 match (A.unwrap ia,ib) with
2155
113803cf
C
2156 | (A.MetaInit(ida,keep,inherited), ib) ->
2157 let max_min _ =
2158 Lib_parsing_c.lin_col_by_pos (Lib_parsing_c.ii_of_ini ib) in
2159 X.envf keep inherited (ida, Ast_c.MetaInitVal ib, max_min)
2160 (fun () ->
2161 X.distrf_ini ida ib >>= (fun ida ib ->
2162 return (
2163 A.MetaInit (ida,keep,inherited) +> A.rewrap ia,
2164 ib
2165 ))
2166 )
2167
34e49164
C
2168 | (A.InitExpr expa, ib) ->
2169 (match A.unwrap expa, ib with
2170 | A.Edots (mcode, None), ib ->
2171 X.distrf_ini (dots2metavar mcode) ib >>= (fun mcode ib ->
2172 return (
2173 A.InitExpr
2174 (A.Edots (metavar2dots mcode, None) +> A.rewrap expa)
2175 +> A.rewrap ia,
2176 ib
2177 ))
2178
2179 | A.Edots (_, Some expr), _ -> failwith "not handling when on Edots"
2180
2181 | _, (B.InitExpr expb, ii) ->
2182 assert (null ii);
2183 expression expa expb >>= (fun expa expb ->
2184 return (
2185 (A.InitExpr expa) +> A.rewrap ia,
2186 (B.InitExpr expb, ii)
2187 ))
2188 | _ -> fail
2189 )
2190
2191 | (A.InitList (ia1, ias, ia2, []), (B.InitList ibs, ii)) ->
2192 (match ii with
2193 | ib1::ib2::iicommaopt ->
2194 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
2195 tokenf ia2 ib2 >>= (fun ia2 ib2 ->
2196 initialisers ias (ibs, iicommaopt) >>= (fun ias (ibs,iicommaopt) ->
2197 return (
2198 (A.InitList (ia1, ias, ia2, [])) +> A.rewrap ia,
2199 (B.InitList ibs, ib1::ib2::iicommaopt)
2200 ))))
2201
2202 | _ -> raise Impossible
2203 )
2204
2205 | (A.InitList (i1, ias, i2, whencode),(B.InitList ibs, _ii)) ->
2206 failwith "TODO: not handling whencode in initialisers"
2207
2208
113803cf
C
2209 | (A.InitGccExt (designatorsa, ia2, inia),
2210 (B.InitDesignators (designatorsb, inib), ii2))->
34e49164 2211
34e49164
C
2212 let iieq = tuple_of_list1 ii2 in
2213
34e49164 2214 tokenf ia2 iieq >>= (fun ia2 iieq ->
113803cf
C
2215 designators designatorsa designatorsb >>=
2216 (fun designatorsa designatorsb ->
34e49164
C
2217 initialiser inia inib >>= (fun inia inib ->
2218 return (
113803cf
C
2219 (A.InitGccExt (designatorsa, ia2, inia)) +> A.rewrap ia,
2220 (B.InitDesignators (designatorsb, inib), [iieq])
2221 ))))
34e49164
C
2222
2223
2224
2225
2226 | (A.InitGccName (ida, ia1, inia), (B.InitFieldOld (idb, inib), ii)) ->
2227 (match ii with
2228 | [iidb;iicolon] ->
2229 ident DontKnow ida (idb, iidb) >>= (fun ida (idb, iidb) ->
2230 initialiser inia inib >>= (fun inia inib ->
2231 tokenf ia1 iicolon >>= (fun ia1 iicolon ->
2232 return (
2233 (A.InitGccName (ida, ia1, inia)) +> A.rewrap ia,
2234 (B.InitFieldOld (idb, inib), [iidb;iicolon])
2235 ))))
2236 | _ -> fail
2237 )
2238
2239
2240
2241 | A.IComma(comma), _ ->
2242 raise Impossible
2243
2244 | A.UniqueIni _,_ | A.OptIni _,_ ->
2245 failwith "not handling Opt/Unique on initialisers"
485bce71
C
2246
2247 | _, (B.InitIndexOld (_, _), _) -> fail
2248 | _, (B.InitFieldOld (_, _), _) -> fail
2249
2250 | _, ((B.InitDesignators (_, _)|B.InitList _|B.InitExpr _), _)
2251 -> fail
2252
113803cf
C
2253and designators dla dlb =
2254 match (dla,dlb) with
2255 ([],[]) -> return ([], [])
2256 | ([],_) | (_,[]) -> fail
2257 | (da::dla,db::dlb) ->
2258 designator da db >>= (fun da db ->
2259 designators dla dlb >>= (fun dla dlb ->
2260 return (da::dla, db::dlb)))
2261
2262and designator da db =
2263 match (da,db) with
2264 (A.DesignatorField (ia1, ida), (B.DesignatorField idb,ii1)) ->
34e49164 2265
113803cf
C
2266 let (iidot, iidb) = tuple_of_list2 ii1 in
2267 tokenf ia1 iidot >>= (fun ia1 iidot ->
2268 ident DontKnow ida (idb, iidb) >>= (fun ida (idb, iidb) ->
2269 return (
2270 A.DesignatorField (ia1, ida),
2271 (B.DesignatorField idb, [iidot;iidb])
2272 )))
2273
2274 | (A.DesignatorIndex (ia1,ea,ia2), (B.DesignatorIndex eb, ii1)) ->
2275
2276 let (ib1, ib2) = tuple_of_list2 ii1 in
2277 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
2278 tokenf ia2 ib2 >>= (fun ia2 ib2 ->
2279 expression ea eb >>= (fun ea eb ->
2280 return (
2281 A.DesignatorIndex (ia1,ea,ia2),
2282 (B.DesignatorIndex eb, [ib1;ib2])
2283 ))))
34e49164 2284
113803cf
C
2285 | (A.DesignatorRange (ia1,e1a,ia2,e2a,ia3),
2286 (B.DesignatorRange (e1b, e2b), ii1)) ->
34e49164 2287
113803cf
C
2288 let (ib1, ib2, ib3) = tuple_of_list3 ii1 in
2289 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
2290 tokenf ia2 ib2 >>= (fun ia2 ib2 ->
2291 tokenf ia3 ib3 >>= (fun ia3 ib3 ->
2292 expression e1a e1b >>= (fun e1a e1b ->
2293 expression e2a e2b >>= (fun e2a e2b ->
2294 return (
2295 A.DesignatorRange (ia1,e1a,ia2,e2a,ia3),
2296 (B.DesignatorRange (e1b, e2b), [ib1;ib2;ib3])
2297 ))))))
2298 | (_, ((B.DesignatorField _|B.DesignatorIndex _|B.DesignatorRange _), _)) ->
2299 fail
34e49164
C
2300
2301
2302and initialisers = fun ias (ibs, iicomma) ->
2303 let ias_unsplit = unsplit_icomma ias in
2304 let ibs_split = resplit_initialiser ibs iicomma in
2305
2306 let f =
2307 if need_unordered_initialisers ibs
2308 then initialisers_unordered2
2309 else initialisers_ordered2
2310 in
2311 f ias_unsplit ibs_split >>=
2312 (fun ias_unsplit ibs_split ->
2313 return (
2314 split_icomma ias_unsplit,
2315 unsplit_initialiser ibs_split
2316 )
2317 )
2318
2319(* todo: one day julia will reput a IDots *)
2320and initialisers_ordered2 = fun ias ibs ->
2321 match ias, ibs with
2322 | [], [] -> return ([], [])
2323 | (x, xcomma)::xs, (y, commay)::ys ->
2324 (match A.unwrap xcomma with
2325 | A.IComma commax ->
2326 tokenf commax commay >>= (fun commax commay ->
2327 initialiser x y >>= (fun x y ->
2328 initialisers_ordered2 xs ys >>= (fun xs ys ->
2329 return (
2330 (x, (A.IComma commax) +> A.rewrap xcomma)::xs,
2331 (y, commay)::ys
2332 )
2333 )))
2334 | _ -> raise Impossible (* unsplit_iicomma wrong *)
2335 )
2336 | _ -> fail
2337
2338
2339
2340and initialisers_unordered2 = fun ias ibs ->
2341
2342 match ias, ibs with
2343 | [], ys -> return ([], ys)
2344 | (x,xcomma)::xs, ys ->
2345
2346 let permut = Common.uncons_permut_lazy ys in
2347 permut +> List.fold_left (fun acc ((e, pos), rest) ->
2348 acc >||>
2349 (
2350 (match A.unwrap xcomma, e with
2351 | A.IComma commax, (y, commay) ->
2352 tokenf commax commay >>= (fun commax commay ->
2353 initialiser x y >>= (fun x y ->
2354 return (
2355 (x, (A.IComma commax) +> A.rewrap xcomma),
2356 (y, commay))
2357 )
2358 )
2359 | _ -> raise Impossible (* unsplit_iicomma wrong *)
2360 )
2361 >>= (fun x e ->
2362 let rest = Lazy.force rest in
2363 initialisers_unordered2 xs rest >>= (fun xs rest ->
2364 return (
2365 x::xs,
2366 Common.insert_elem_pos (e, pos) rest
2367 ))))
2368 ) fail
2369
2370
2371(* ------------------------------------------------------------------------- *)
485bce71 2372and (struct_fields: (A.declaration list, B.field list) matcher) =
34e49164
C
2373 fun eas ebs ->
2374 match eas, ebs with
2375 | [], [] -> return ([], [])
2376 | [], eb::ebs -> fail
2377 | ea::eas, ebs ->
2378 X.all_bound (A.get_inherited ea) >&&>
2379 (match A.unwrap ea, ebs with
2380 | A.Ddots (mcode, optwhen), ys ->
2381 if optwhen <> None then failwith "not handling when in argument";
2382
2383 (* '...' can take more or less the beginnings of the arguments *)
9f8e26f4
C
2384 let startendxs =
2385 if eas = []
2386 then [(ys,[])] (* hack! the only one that can work *)
2387 else Common.zip (Common.inits ys) (Common.tails ys) in
34e49164
C
2388 startendxs +> List.fold_left (fun acc (startxs, endxs) ->
2389 acc >||> (
2390
b1b2de81 2391 (if null startxs
34e49164
C
2392 then
2393 if mcode_contain_plus (mcodekind mcode)
2394 then fail
2395 (* failwith "I have no token that I could accroche myself on" *)
2396 else return (dots2metavar mcode, [])
2397 else
2398
2399 X.distrf_struct_fields (dots2metavar mcode) startxs
2400 ) >>= (fun mcode startxs ->
2401 let mcode = metavar2dots mcode in
2402 struct_fields eas endxs >>= (fun eas endxs ->
2403 return (
2404 (A.Ddots (mcode, optwhen) +> A.rewrap ea) ::eas,
2405 startxs ++ endxs
2406 )))
2407 )
2408 ) fail
2409 | _unwrapx, eb::ebs ->
2410 struct_field ea eb >>= (fun ea eb ->
2411 struct_fields eas ebs >>= (fun eas ebs ->
2412 return (ea::eas, eb::ebs)
2413 ))
2414
2415 | _unwrapx, [] -> fail
2416 )
2417
485bce71 2418and (struct_field: (A.declaration, B.field) matcher) = fun fa fb ->
34e49164 2419
708f4980 2420 match fb with
485bce71
C
2421 | B.DeclarationField (B.FieldDeclList (onefield_multivars,iiptvirg)) ->
2422
2423 let iiptvirgb = tuple_of_list1 iiptvirg in
34e49164
C
2424
2425 (match onefield_multivars with
2426 | [] -> raise Impossible
2427 | [onevar,iivirg] ->
2428 assert (null iivirg);
2429 (match onevar with
b1b2de81 2430 | B.BitField (sopt, typb, _, expr) ->
34e49164
C
2431 pr2_once "warning: bitfield not handled by ast_cocci";
2432 fail
b1b2de81 2433 | B.Simple (None, typb) ->
34e49164
C
2434 pr2_once "warning: unamed struct field not handled by ast_cocci";
2435 fail
b1b2de81 2436 | B.Simple (Some nameidb, typb) ->
34e49164
C
2437
2438 (* build a declaration from a struct field *)
2439 let allminus = false in
2440 let iisto = [] in
2441 let stob = B.NoSto, false in
2442 let fake_var =
b1b2de81 2443 ({B.v_namei = Some (nameidb, None);
485bce71
C
2444 B.v_type = typb;
2445 B.v_storage = stob;
2446 B.v_local = Ast_c.NotLocalDecl;
2447 B.v_attr = Ast_c.noattr;
978fd7e5
C
2448 B.v_type_bis = ref None;
2449 (* the struct field should also get expanded ? no it's not
2450 * important here, we will rematch very soon *)
485bce71 2451 },
34e49164
C
2452 iivirg)
2453 in
2454 onedecl allminus fa (fake_var,iiptvirgb,iisto) >>=
2455 (fun fa (var,iiptvirgb,iisto) ->
2456
2457 match fake_var with
b1b2de81 2458 | ({B.v_namei = Some (nameidb, None);
485bce71
C
2459 B.v_type = typb;
2460 B.v_storage = stob;
2461 }, iivirg) ->
b1b2de81
C
2462
2463 let onevar = B.Simple (Some nameidb, typb) in
34e49164
C
2464
2465 return (
2466 (fa),
485bce71 2467 ((B.DeclarationField
708f4980
C
2468 (B.FieldDeclList ([onevar, iivirg], [iiptvirgb])))
2469 )
34e49164
C
2470 )
2471 | _ -> raise Impossible
2472 )
2473 )
2474
2475 | x::y::xs ->
2476 pr2_once "PB: More that one variable in decl. Have to split";
2477 fail
2478 )
708f4980 2479 | B.EmptyField _iifield ->
485bce71
C
2480 fail
2481
708f4980
C
2482 | B.MacroDeclField _ ->
2483 raise Todo
2484
485bce71
C
2485 | B.CppDirectiveStruct directive -> fail
2486 | B.IfdefStruct directive -> fail
34e49164
C
2487
2488
2489
2490(* ------------------------------------------------------------------------- *)
2491and (fullType: (A.fullType, Ast_c.fullType) matcher) =
2492 fun typa typb ->
2493 X.optional_qualifier_flag (fun optional_qualifier ->
2494 X.all_bound (A.get_inherited typa) >&&>
2495 match A.unwrap typa, typb with
2496 | A.Type(cv,ty1), ((qu,il),ty2) ->
2497
2498 if qu.B.const && qu.B.volatile
2499 then
2500 pr2_once
2501 ("warning: the type is both const & volatile but cocci " ^
2502 "does not handle that");
2503
2504 (* Drop out the const/volatile part that has been matched.
2505 * This is because a SP can contain const T v; in which case
2506 * later in match_t_t when we encounter a T, we must not add in
2507 * the environment the whole type.
2508 *)
2509
2510
2511 (match cv with
2512 (* "iso-by-absence" *)
2513 | None ->
2514 let do_stuff () =
2515 fullTypebis ty1 ((qu,il), ty2) >>= (fun ty1 fullty2 ->
2516 return (
2517 (A.Type(None, ty1)) +> A.rewrap typa,
2518 fullty2
2519 ))
2520 in
2521 (match optional_qualifier, qu.B.const || qu.B.volatile with
2522 | false, false -> do_stuff ()
2523 | false, true -> fail
2524 | true, false -> do_stuff ()
2525 | true, true ->
2526 if !Flag.show_misc
2527 then pr2_once "USING optional_qualifier builtin isomorphism";
2528 do_stuff()
2529 )
2530
2531
2532 | Some x ->
2533 (* todo: can be __const__ ? can be const & volatile so
2534 * should filter instead ?
2535 *)
2536 (match term x, il with
2537 | A.Const, [i1] when qu.B.const ->
2538
2539 tokenf x i1 >>= (fun x i1 ->
2540 fullTypebis ty1 (Ast_c.nQ,ty2) >>= (fun ty1 (_, ty2) ->
2541 return (
2542 (A.Type(Some x, ty1)) +> A.rewrap typa,
2543 ((qu, [i1]), ty2)
2544 )))
2545
2546 | A.Volatile, [i1] when qu.B.volatile ->
2547 tokenf x i1 >>= (fun x i1 ->
2548 fullTypebis ty1 (Ast_c.nQ,ty2) >>= (fun ty1 (_, ty2) ->
2549 return (
2550 (A.Type(Some x, ty1)) +> A.rewrap typa,
2551 ((qu, [i1]), ty2)
2552 )))
2553
2554 | _ -> fail
2555 )
2556 )
2557
2558 | A.DisjType typas, typb ->
2559 typas +>
2560 List.fold_left (fun acc typa -> acc >|+|> (fullType typa typb)) fail
2561
2562 | A.OptType(_), _ | A.UniqueType(_), _
2563 -> failwith "not handling Opt/Unique on type"
2564 )
2565
2566
2567(*
2568 * Why not (A.typeC, Ast_c.typeC) matcher ?
2569 * because when there is MetaType, we want that T record the whole type,
2570 * including the qualifier, and so this type (and the new_il function in
2571 * preceding function).
2572*)
2573
2574and (fullTypebis: (A.typeC, Ast_c.fullType) matcher) =
2575 fun ta tb ->
2576 X.all_bound (A.get_inherited ta) >&&>
2577 match A.unwrap ta, tb with
2578
2579 (* cas general *)
2580 | A.MetaType(ida,keep, inherited), typb ->
2581 let max_min _ =
2582 Lib_parsing_c.lin_col_by_pos (Lib_parsing_c.ii_of_type typb) in
2583 X.envf keep inherited (ida, B.MetaTypeVal typb, max_min) (fun () ->
2584 X.distrf_type ida typb >>= (fun ida typb ->
2585 return (
2586 A.MetaType(ida,keep, inherited) +> A.rewrap ta,
2587 typb
2588 ))
2589 )
2590 | unwrap, (qub, typb) ->
2591 typeC ta typb >>= (fun ta typb ->
2592 return (ta, (qub, typb))
2593 )
2594
faf9a90c 2595and simulate_signed ta basea stringsa signaopt tb baseb ii rebuilda =
34e49164
C
2596 (* In ii there is a list, sometimes of length 1 or 2 or 3.
2597 * And even if in baseb we have a Signed Int, that does not mean
2598 * that ii is of length 2, cos Signed is the default, so if in signa
2599 * we have Signed explicitely ? we cant "accrocher" this mcode to
2600 * something :( So for the moment when there is signed in cocci,
2601 * we force that there is a signed in c too (done in pattern.ml).
2602 *)
2603 let signbopt, iibaseb = split_signb_baseb_ii (baseb, ii) in
2604
2605
2606 (* handle some iso on type ? (cf complex C rule for possible implicit
2607 casting) *)
faf9a90c 2608 match basea, baseb with
34e49164
C
2609 | A.VoidType, B.Void
2610 | A.FloatType, B.FloatType (B.CFloat)
2611 | A.DoubleType, B.FloatType (B.CDouble) ->
b1b2de81 2612 assert (signaopt =*= None);
faf9a90c 2613 let stringa = tuple_of_list1 stringsa in
34e49164 2614 let (ibaseb) = tuple_of_list1 ii in
faf9a90c 2615 tokenf stringa ibaseb >>= (fun stringa ibaseb ->
34e49164 2616 return (
faf9a90c 2617 (rebuilda ([stringa], signaopt)) +> A.rewrap ta,
34e49164
C
2618 (B.BaseType baseb, [ibaseb])
2619 ))
2620
b1b2de81 2621 | A.CharType, B.IntType B.CChar when signaopt =*= None ->
faf9a90c 2622 let stringa = tuple_of_list1 stringsa in
34e49164 2623 let ibaseb = tuple_of_list1 ii in
faf9a90c 2624 tokenf stringa ibaseb >>= (fun stringa ibaseb ->
34e49164 2625 return (
faf9a90c 2626 (rebuilda ([stringa], signaopt)) +> A.rewrap ta,
34e49164
C
2627 (B.BaseType (B.IntType B.CChar), [ibaseb])
2628 ))
2629
2630 | A.CharType,B.IntType (B.Si (_sign, B.CChar2)) when signaopt <> None ->
faf9a90c 2631 let stringa = tuple_of_list1 stringsa in
34e49164
C
2632 let ibaseb = tuple_of_list1 iibaseb in
2633 sign signaopt signbopt >>= (fun signaopt iisignbopt ->
faf9a90c 2634 tokenf stringa ibaseb >>= (fun stringa ibaseb ->
34e49164 2635 return (
faf9a90c 2636 (rebuilda ([stringa], signaopt)) +> A.rewrap ta,
34e49164
C
2637 (B.BaseType (baseb), iisignbopt ++ [ibaseb])
2638 )))
2639
2640 | A.ShortType, B.IntType (B.Si (_, B.CShort))
2641 | A.IntType, B.IntType (B.Si (_, B.CInt))
2642 | A.LongType, B.IntType (B.Si (_, B.CLong)) ->
faf9a90c 2643 let stringa = tuple_of_list1 stringsa in
34e49164
C
2644 (match iibaseb with
2645 | [] ->
2646 (* iso-by-presence ? *)
2647 (* when unsigned int in SP, allow have just unsigned in C ? *)
faf9a90c 2648 if mcode_contain_plus (mcodekind stringa)
34e49164
C
2649 then fail
2650 else
2651
2652 sign signaopt signbopt >>= (fun signaopt iisignbopt ->
2653 return (
faf9a90c 2654 (rebuilda ([stringa], signaopt)) +> A.rewrap ta,
34e49164
C
2655 (B.BaseType (baseb), iisignbopt ++ [])
2656 ))
2657
2658
2659 | [x;y] ->
2660 pr2_once
2661 "warning: long int or short int not handled by ast_cocci";
2662 fail
2663
2664 | [ibaseb] ->
2665 sign signaopt signbopt >>= (fun signaopt iisignbopt ->
faf9a90c 2666 tokenf stringa ibaseb >>= (fun stringa ibaseb ->
34e49164 2667 return (
faf9a90c 2668 (rebuilda ([stringa], signaopt)) +> A.rewrap ta,
34e49164
C
2669 (B.BaseType (baseb), iisignbopt ++ [ibaseb])
2670 )))
2671 | _ -> raise Impossible
2672
2673 )
2674
2675
faf9a90c
C
2676 | A.LongLongType, B.IntType (B.Si (_, B.CLongLong)) ->
2677 let (string1a,string2a) = tuple_of_list2 stringsa in
2678 (match iibaseb with
2679 [ibase1b;ibase2b] ->
2680 sign signaopt signbopt >>= (fun signaopt iisignbopt ->
2681 tokenf string1a ibase1b >>= (fun base1a ibase1b ->
2682 tokenf string2a ibase2b >>= (fun base2a ibase2b ->
2683 return (
2684 (rebuilda ([base1a;base2a], signaopt)) +> A.rewrap ta,
2685 (B.BaseType (baseb), iisignbopt ++ [ibase1b;ibase2b])
2686 ))))
2687 | [] -> fail (* should something be done in this case? *)
2688 | _ -> raise Impossible)
2689
2690
34e49164
C
2691 | _, B.FloatType B.CLongDouble
2692 ->
2693 pr2_once
faf9a90c 2694 "warning: long double not handled by ast_cocci";
34e49164 2695 fail
485bce71
C
2696
2697 | _, (B.Void|B.FloatType _|B.IntType _) -> fail
2698
faf9a90c
C
2699and simulate_signed_meta ta basea signaopt tb baseb ii rebuilda =
2700 (* In ii there is a list, sometimes of length 1 or 2 or 3.
2701 * And even if in baseb we have a Signed Int, that does not mean
2702 * that ii is of length 2, cos Signed is the default, so if in signa
2703 * we have Signed explicitely ? we cant "accrocher" this mcode to
2704 * something :( So for the moment when there is signed in cocci,
2705 * we force that there is a signed in c too (done in pattern.ml).
2706 *)
2707 let signbopt, iibaseb = split_signb_baseb_ii (baseb, ii) in
2708
2709 let match_to_type rebaseb =
2710 sign signaopt signbopt >>= (fun signaopt iisignbopt ->
faf9a90c 2711 let fta = A.rewrap basea (A.Type(None,basea)) in
b1b2de81 2712 let ftb = Ast_c.nQ,(B.BaseType (rebaseb), iibaseb) in
faf9a90c
C
2713 fullType fta ftb >>= (fun fta (_,tb) ->
2714 (match A.unwrap fta,tb with
2715 A.Type(_,basea), (B.BaseType baseb, ii) ->
faf9a90c
C
2716 return (
2717 (rebuilda (basea, signaopt)) +> A.rewrap ta,
b1b2de81 2718 (B.BaseType (baseb), iisignbopt ++ ii)
faf9a90c
C
2719 )
2720 | _ -> failwith "not possible"))) in
2721
2722 (* handle some iso on type ? (cf complex C rule for possible implicit
2723 casting) *)
2724 match baseb with
2725 | B.IntType (B.Si (_sign, B.CChar2)) ->
2726 match_to_type (B.IntType B.CChar)
34e49164 2727
faf9a90c
C
2728 | B.IntType (B.Si (_, ty)) ->
2729 (match iibaseb with
2730 | [] -> fail (* metavariable has to match something *)
2731
b1b2de81 2732 | _ -> match_to_type (B.IntType (B.Si (B.Signed, ty)))
34e49164 2733
faf9a90c
C
2734 )
2735
2736 | (B.Void|B.FloatType _|B.IntType _) -> fail
2737
2738and (typeC: (A.typeC, Ast_c.typeC) matcher) =
2739 fun ta tb ->
2740 match A.unwrap ta, tb with
2741 | A.BaseType (basea,stringsa), (B.BaseType baseb, ii) ->
2742 simulate_signed ta basea stringsa None tb baseb ii
2743 (function (stringsa, signaopt) -> A.BaseType (basea,stringsa))
2744 | A.SignedT (signaopt, Some basea), (B.BaseType baseb, ii) ->
2745 (match A.unwrap basea with
2746 A.BaseType (basea1,strings1) ->
2747 simulate_signed ta basea1 strings1 (Some signaopt) tb baseb ii
2748 (function (strings1, Some signaopt) ->
2749 A.SignedT
2750 (signaopt,
2751 Some (A.rewrap basea (A.BaseType (basea1,strings1))))
2752 | _ -> failwith "not possible")
2753 | A.MetaType(ida,keep,inherited) ->
2754 simulate_signed_meta ta basea (Some signaopt) tb baseb ii
2755 (function (basea, Some signaopt) ->
2756 A.SignedT(signaopt,Some basea)
2757 | _ -> failwith "not possible")
2758 | _ -> failwith "not possible")
2759 | A.SignedT (signa,None), (B.BaseType baseb, ii) ->
34e49164
C
2760 let signbopt, iibaseb = split_signb_baseb_ii (baseb, ii) in
2761 (match iibaseb, baseb with
2762 | [], B.IntType (B.Si (_sign, B.CInt)) ->
2763 sign (Some signa) signbopt >>= (fun signaopt iisignbopt ->
2764 match signaopt with
2765 | None -> raise Impossible
2766 | Some signa ->
2767 return (
faf9a90c 2768 (A.SignedT (signa,None)) +> A.rewrap ta,
34e49164
C
2769 (B.BaseType baseb, iisignbopt)
2770 )
2771 )
2772 | _ -> fail
2773 )
2774
2775
2776
2777 (* todo? iso with array *)
2778 | A.Pointer (typa, iamult), (B.Pointer typb, ii) ->
2779 let (ibmult) = tuple_of_list1 ii in
2780 fullType typa typb >>= (fun typa typb ->
2781 tokenf iamult ibmult >>= (fun iamult ibmult ->
2782 return (
2783 (A.Pointer (typa, iamult)) +> A.rewrap ta,
2784 (B.Pointer typb, [ibmult])
2785 )))
2786
2787 | A.FunctionType(allminus,tyaopt,lpa,paramsa,rpa),
2788 (B.FunctionType(tyb, (paramsb, (isvaargs, iidotsb))), ii) ->
2789
2790 let (lpb, rpb) = tuple_of_list2 ii in
2791 if isvaargs
2792 then
2793 pr2_once
2794 ("Not handling well variable length arguments func. "^
2795 "You have been warned");
2796 tokenf lpa lpb >>= (fun lpa lpb ->
2797 tokenf rpa rpb >>= (fun rpa rpb ->
2798 fullType_optional_allminus allminus tyaopt tyb >>= (fun tyaopt tyb ->
2799 parameters (seqstyle paramsa) (A.undots paramsa) paramsb >>=
2800 (fun paramsaundots paramsb ->
2801 let paramsa = redots paramsa paramsaundots in
2802 return (
2803 (A.FunctionType(allminus,tyaopt,lpa,paramsa,rpa) +> A.rewrap ta,
2804 (B.FunctionType(tyb, (paramsb, (isvaargs, iidotsb))), [lpb;rpb])
2805 )
2806 )))))
2807
2808
2809
2810
2811
2812 | A.FunctionPointer(tya,lp1a,stara,rp1a,lp2a,paramsa,rp2a),
2813 (B.ParenType t1, ii) ->
2814 let (lp1b, rp1b) = tuple_of_list2 ii in
2815 let (qu1b, t1b) = t1 in
2816 (match t1b with
2817 | B.Pointer t2, ii ->
2818 let (starb) = tuple_of_list1 ii in
2819 let (qu2b, t2b) = t2 in
2820 (match t2b with
2821 | B.FunctionType (tyb, (paramsb, (isvaargs, iidotsb))), ii ->
2822 let (lp2b, rp2b) = tuple_of_list2 ii in
2823
2824 if isvaargs
2825 then
2826 pr2_once
2827 ("Not handling well variable length arguments func. "^
2828 "You have been warned");
2829
2830 fullType tya tyb >>= (fun tya tyb ->
2831 tokenf lp1a lp1b >>= (fun lp1a lp1b ->
2832 tokenf rp1a rp1b >>= (fun rp1a rp1b ->
2833 tokenf lp2a lp2b >>= (fun lp2a lp2b ->
2834 tokenf rp2a rp2b >>= (fun rp2a rp2b ->
2835 tokenf stara starb >>= (fun stara starb ->
2836 parameters (seqstyle paramsa) (A.undots paramsa) paramsb >>=
2837 (fun paramsaundots paramsb ->
2838 let paramsa = redots paramsa paramsaundots in
2839
2840 let t2 =
2841 (qu2b,
2842 (B.FunctionType (tyb, (paramsb, (isvaargs, iidotsb))),
2843 [lp2b;rp2b]))
2844 in
2845 let t1 =
2846 (qu1b,
2847 (B.Pointer t2, [starb]))
2848 in
2849
2850 return (
2851 (A.FunctionPointer(tya,lp1a,stara,rp1a,lp2a,paramsa,rp2a))
2852 +> A.rewrap ta,
2853 (B.ParenType t1, [lp1b;rp1b])
2854 )
2855 )))))))
2856
2857
2858
2859 | _ -> fail
2860 )
2861 | _ -> fail
2862 )
2863
2864
2865
2866 (* todo: handle the iso on optionnal size specifification ? *)
2867 | A.Array (typa, ia1, eaopt, ia2), (B.Array (ebopt, typb), ii) ->
2868 let (ib1, ib2) = tuple_of_list2 ii in
2869 fullType typa typb >>= (fun typa typb ->
2870 option expression eaopt ebopt >>= (fun eaopt ebopt ->
2871 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
2872 tokenf ia2 ib2 >>= (fun ia2 ib2 ->
2873 return (
2874 (A.Array (typa, ia1, eaopt, ia2)) +> A.rewrap ta,
2875 (B.Array (ebopt, typb), [ib1;ib2])
2876 )))))
2877
2878
2879 (* todo: could also match a Struct that has provided a name *)
2880 (* This is for the case where the SmPL code contains "struct x", without
2881 a definition. In this case, the name field is always present.
2882 This case is also called from the case for A.StructUnionDef when
2883 a name is present in the C code. *)
2884 | A.StructUnionName(sua, Some sa), (B.StructUnionName (sub, sb), ii) ->
2885 (* sa is now an ident, not an mcode, old: ... && (term sa) =$= sb *)
2886 let (ib1, ib2) = tuple_of_list2 ii in
2887 if equal_structUnion (term sua) sub
2888 then
2889 ident DontKnow sa (sb, ib2) >>= (fun sa (sb, ib2) ->
2890 tokenf sua ib1 >>= (fun sua ib1 ->
2891 return (
2892 (A.StructUnionName (sua, Some sa)) +> A.rewrap ta,
2893 (B.StructUnionName (sub, sb), [ib1;ib2])
2894 )))
2895 else fail
2896
2897
2898 | A.StructUnionDef(ty, lba, declsa, rba),
2899 (B.StructUnion (sub, sbopt, declsb), ii) ->
2900
2901 let (ii_sub_sb, lbb, rbb) =
2902 match ii with
2903 [iisub; lbb; rbb] -> (Common.Left iisub,lbb,rbb)
2904 | [iisub; iisb; lbb; rbb] -> (Common.Right (iisub,iisb),lbb,rbb)
2905 | _ -> failwith "list of length 3 or 4 expected" in
2906
2907 let process_type =
2908 match (sbopt,ii_sub_sb) with
2909 (None,Common.Left iisub) ->
2910 (* the following doesn't reconstruct the complete SP code, just
2911 the part that matched *)
2912 let rec loop s =
2913 match A.unwrap s with
2914 A.Type(None,ty) ->
2915 (match A.unwrap ty with
2916 A.StructUnionName(sua, None) ->
2917 tokenf sua iisub >>= (fun sua iisub ->
2918 let ty =
2919 A.Type(None,
2920 A.StructUnionName(sua, None) +> A.rewrap ty)
2921 +> A.rewrap s in
2922 return (ty,[iisub]))
2923 | _ -> fail)
2924 | A.DisjType(disjs) ->
2925 disjs +>
2926 List.fold_left (fun acc disj -> acc >|+|> (loop disj)) fail
2927 | _ -> fail in
2928 loop ty
2929
2930 | (Some sb,Common.Right (iisub,iisb)) ->
2931
2932 (* build a StructUnionName from a StructUnion *)
2933 let fake_su = B.nQ, (B.StructUnionName (sub, sb), [iisub;iisb]) in
2934
2935 fullType ty fake_su >>= (fun ty fake_su ->
2936 match fake_su with
2937 | _nQ, (B.StructUnionName (sub, sb), [iisub;iisb]) ->
2938 return (ty, [iisub; iisb])
2939 | _ -> raise Impossible)
2940 | _ -> fail in
2941
2942 process_type
9f8e26f4 2943 >>= (fun ty ii_sub_sb ->
34e49164
C
2944
2945 tokenf lba lbb >>= (fun lba lbb ->
2946 tokenf rba rbb >>= (fun rba rbb ->
2947 struct_fields (A.undots declsa) declsb >>=(fun undeclsa declsb ->
2948 let declsa = redots declsa undeclsa in
2949
2950 return (
2951 (A.StructUnionDef(ty, lba, declsa, rba)) +> A.rewrap ta,
2952 (B.StructUnion (sub, sbopt, declsb),ii_sub_sb@[lbb;rbb])
2953 )))))
2954
2955
2956 (* todo? handle isomorphisms ? because Unsigned Int can be match on a
2957 * uint in the C code. But some CEs consists in renaming some types,
2958 * so we don't want apply isomorphisms every time.
2959 *)
b1b2de81
C
2960 | A.TypeName sa, (B.TypeName (nameb, typb), noii) ->
2961 assert (null noii);
2962
2963 (match nameb with
2964 | B.RegularName (sb, iidb) ->
2965 let iidb1 = tuple_of_list1 iidb in
2966
2967 if (term sa) =$= sb
2968 then
2969 tokenf sa iidb1 >>= (fun sa iidb1 ->
2970 return (
2971 (A.TypeName sa) +> A.rewrap ta,
2972 (B.TypeName (B.RegularName (sb, [iidb1]), typb), noii)
2973 ))
2974 else fail
2975
2976 | B.CppConcatenatedName _ | B.CppVariadicName _ |B.CppIdentBuilder _
2977 -> raise Todo
2978 )
2979
34e49164
C
2980
2981 | _, (B.TypeOfExpr e, ii) -> fail
2982 | _, (B.TypeOfType e, ii) -> fail
485bce71
C
2983
2984 | _, (B.ParenType e, ii) -> fail (* todo ?*)
faf9a90c
C
2985 | A.EnumName(en,namea), (B.EnumName nameb, ii) ->
2986 let (ib1,ib2) = tuple_of_list2 ii in
2987 ident DontKnow namea (nameb, ib2) >>= (fun namea (nameb, ib2) ->
2988 tokenf en ib1 >>= (fun en ib1 ->
2989 return (
2990 (A.EnumName (en, namea)) +> A.rewrap ta,
2991 (B.EnumName nameb, [ib1;ib2])
2992 )))
2993
485bce71
C
2994 | _, (B.Enum _, _) -> fail (* todo cocci ?*)
2995
2996 | _,
b1b2de81 2997 ((B.TypeName _ | B.StructUnionName (_, _) | B.EnumName _ |
faf9a90c
C
2998 B.StructUnion (_, _, _) |
2999 B.FunctionType _ | B.Array (_, _) | B.Pointer _ |
485bce71
C
3000 B.BaseType _),
3001 _)
3002 -> fail
3003
34e49164
C
3004
3005(* todo: iso on sign, if not mentioned then free. tochange?
3006 * but that require to know if signed int because explicit
3007 * signed int, or because implicit signed int.
3008 *)
3009
3010and sign signa signb =
3011 match signa, signb with
3012 | None, None -> return (None, [])
3013 | Some signa, Some (signb, ib) ->
3014 if equal_sign (term signa) signb
3015 then tokenf signa ib >>= (fun signa ib ->
3016 return (Some signa, [ib])
3017 )
3018 else fail
3019 | _, _ -> fail
3020
3021
3022and minusize_list iixs =
3023 iixs +> List.fold_left (fun acc ii ->
3024 acc >>= (fun xs ys ->
3025 tokenf minusizer ii >>= (fun minus ii ->
3026 return (minus::xs, ii::ys)
3027 ))) (return ([],[]))
3028 >>= (fun _xsminys ys ->
3029 return ((), List.rev ys)
3030 )
3031
3032and storage_optional_allminus allminus stoa (stob, iistob) =
3033 (* "iso-by-absence" for storage, and return type. *)
3034 X.optional_storage_flag (fun optional_storage ->
3035 match stoa, stob with
3036 | None, (stobis, inline) ->
3037 let do_minus () =
3038 if allminus
3039 then
3040 minusize_list iistob >>= (fun () iistob ->
3041 return (None, (stob, iistob))
3042 )
3043 else return (None, (stob, iistob))
3044 in
3045
3046 (match optional_storage, stobis with
3047 | false, B.NoSto -> do_minus ()
3048 | false, _ -> fail
3049 | true, B.NoSto -> do_minus ()
3050 | true, _ ->
3051 if !Flag.show_misc
3052 then pr2_once "USING optional_storage builtin isomorphism";
3053 do_minus()
3054 )
3055
3056 | Some x, ((stobis, inline)) ->
3057 if equal_storage (term x) stobis
3058 then
3059 match iistob with
3060 | [i1] ->
3061 tokenf x i1 >>= (fun x i1 ->
3062 return (Some x, ((stobis, inline), [i1]))
3063 )
3064 (* or if have inline ? have to do a split_storage_inline a la
3065 * split_signb_baseb_ii *)
3066 | _ -> raise Impossible
3067 else fail
3068 )
3069
3070
3071
3072
3073
3074and fullType_optional_allminus allminus tya retb =
3075 match tya with
3076 | None ->
3077 if allminus
3078 then
3079 X.distrf_type minusizer retb >>= (fun _x retb ->
3080 return (None, retb)
3081 )
3082
3083 else return (None, retb)
3084 | Some tya ->
3085 fullType tya retb >>= (fun tya retb ->
3086 return (Some tya, retb)
3087 )
3088
3089
3090
3091(*---------------------------------------------------------------------------*)
faf9a90c
C
3092
3093and compatible_base_type a signa b =
34e49164
C
3094 let ok = return ((),()) in
3095
faf9a90c
C
3096 match a, b with
3097 | Type_cocci.VoidType, B.Void ->
b1b2de81 3098 assert (signa =*= None);
faf9a90c 3099 ok
b1b2de81 3100 | Type_cocci.CharType, B.IntType B.CChar when signa =*= None ->
faf9a90c
C
3101 ok
3102 | Type_cocci.CharType, B.IntType (B.Si (signb, B.CChar2)) ->
3103 compatible_sign signa signb
3104 | Type_cocci.ShortType, B.IntType (B.Si (signb, B.CShort)) ->
3105 compatible_sign signa signb
3106 | Type_cocci.IntType, B.IntType (B.Si (signb, B.CInt)) ->
3107 compatible_sign signa signb
3108 | Type_cocci.LongType, B.IntType (B.Si (signb, B.CLong)) ->
3109 compatible_sign signa signb
3110 | _, B.IntType (B.Si (signb, B.CLongLong)) ->
3111 pr2_once "no longlong in cocci";
3112 fail
3113 | Type_cocci.FloatType, B.FloatType B.CFloat ->
b1b2de81 3114 assert (signa =*= None);
faf9a90c
C
3115 ok
3116 | Type_cocci.DoubleType, B.FloatType B.CDouble ->
b1b2de81 3117 assert (signa =*= None);
faf9a90c
C
3118 ok
3119 | _, B.FloatType B.CLongDouble ->
3120 pr2_once "no longdouble in cocci";
3121 fail
3122 | Type_cocci.BoolType, _ -> failwith "no booltype in C"
3123
3124 | _, (B.Void|B.FloatType _|B.IntType _) -> fail
3125
3126and compatible_base_type_meta a signa qua b ii local =
3127 match a, b with
3128 | Type_cocci.MetaType(ida,keep,inherited),
3129 B.IntType (B.Si (signb, B.CChar2)) ->
3130 compatible_sign signa signb >>= fun _ _ ->
3131 let newb = ((qua, (B.BaseType (B.IntType B.CChar),ii)),local) in
3132 compatible_type a newb
3133 | Type_cocci.MetaType(ida,keep,inherited), B.IntType (B.Si (signb, ty)) ->
3134 compatible_sign signa signb >>= fun _ _ ->
3135 let newb =
3136 ((qua, (B.BaseType (B.IntType (B.Si (B.Signed, ty))),ii)),local) in
3137 compatible_type a newb
3138 | _, B.FloatType B.CLongDouble ->
3139 pr2_once "no longdouble in cocci";
3140 fail
3141
3142 | _, (B.Void|B.FloatType _|B.IntType _) -> fail
485bce71
C
3143
3144
faf9a90c
C
3145and compatible_type a (b,local) =
3146 let ok = return ((),()) in
3147
3148 let rec loop = function
3149 | Type_cocci.BaseType a, (qua, (B.BaseType b,ii)) ->
3150 compatible_base_type a None b
485bce71 3151
faf9a90c
C
3152 | Type_cocci.SignedT (signa,None), (qua, (B.BaseType b,ii)) ->
3153 compatible_base_type Type_cocci.IntType (Some signa) b
485bce71 3154
faf9a90c
C
3155 | Type_cocci.SignedT (signa,Some ty), (qua, (B.BaseType b,ii)) ->
3156 (match ty with
3157 Type_cocci.BaseType ty ->
3158 compatible_base_type ty (Some signa) b
3159 | Type_cocci.MetaType(ida,keep,inherited) ->
3160 compatible_base_type_meta ty (Some signa) qua b ii local
3161 | _ -> failwith "not possible")
485bce71 3162
34e49164
C
3163 | Type_cocci.Pointer a, (qub, (B.Pointer b, ii)) ->
3164 loop (a,b)
3165 | Type_cocci.FunctionPointer a, _ ->
3166 failwith
3167 "TODO: function pointer type doesn't store enough information to determine compatability"
3168 | Type_cocci.Array a, (qub, (B.Array (eopt, b),ii)) ->
3169 (* no size info for cocci *)
3170 loop (a,b)
3171 | Type_cocci.StructUnionName (sua, _, sa),
3172 (qub, (B.StructUnionName (sub, sb),ii)) ->
b1b2de81 3173 if equal_structUnion_type_cocci sua sub && sa =$= sb
34e49164
C
3174 then ok
3175 else fail
faf9a90c
C
3176 | Type_cocci.EnumName (_, sa),
3177 (qub, (B.EnumName (sb),ii)) ->
b1b2de81 3178 if sa =$= sb
faf9a90c
C
3179 then ok
3180 else fail
b1b2de81
C
3181 | Type_cocci.TypeName sa, (qub, (B.TypeName (namesb, _typb),noii)) ->
3182 let sb = Ast_c.str_of_name namesb in
3183 if sa =$= sb
34e49164
C
3184 then ok
3185 else fail
3186
3187 | Type_cocci.ConstVol (qua, a), (qub, b) ->
3188 if (fst qub).B.const && (fst qub).B.volatile
3189 then
3190 begin
3191 pr2_once ("warning: the type is both const & volatile but cocci " ^
3192 "does not handle that");
3193 fail
3194 end
3195 else
3196 if
3197 (match qua with
3198 | Type_cocci.Const -> (fst qub).B.const
3199 | Type_cocci.Volatile -> (fst qub).B.volatile
3200 )
3201 then loop (a,(Ast_c.nQ, b))
3202 else fail
3203
3204 | Type_cocci.MetaType (ida,keep,inherited), typb ->
3205 let max_min _ =
3206 Lib_parsing_c.lin_col_by_pos (Lib_parsing_c.ii_of_type typb) in
3207 X.envf keep inherited (A.make_mcode ida, B.MetaTypeVal typb, max_min)
3208 (fun () -> ok
3209 )
3210
3211 (* subtil: must be after the MetaType case *)
b1b2de81 3212 | a, (qub, (B.TypeName (_namesb, Some b), noii)) ->
34e49164
C
3213 (* kind of typedef iso *)
3214 loop (a,b)
3215
3216
3217
3218
3219
3220 (* for metavariables of type expression *^* *)
3221 | Type_cocci.Unknown , _ -> ok
3222
485bce71
C
3223 | (_,
3224 (_,
3225 ((
3226 B.TypeOfType _|B.TypeOfExpr _|B.ParenType _|
3227 B.EnumName _|B.StructUnion (_, _, _)|B.Enum (_, _)
3228 ),
3229 _))) -> fail
3230
3231 | (_,
3232 (_,
3233 ((
3234 B.StructUnionName (_, _)|
3235 B.FunctionType _|
3236 B.Array (_, _)|B.Pointer _|B.TypeName _|
3237 B.BaseType _
3238 ),
3239 _))) -> fail
3240
3241
3242 in
34e49164
C
3243 loop (a,b)
3244
3245and compatible_sign signa signb =
3246 let ok = return ((),()) in
3247 match signa, signb with
3248 | None, B.Signed
3249 | Some Type_cocci.Signed, B.Signed
3250 | Some Type_cocci.Unsigned, B.UnSigned
3251 -> ok
3252 | _ -> fail
3253
3254
3255and equal_structUnion_type_cocci a b =
3256 match a, b with
3257 | Type_cocci.Struct, B.Struct -> true
3258 | Type_cocci.Union, B.Union -> true
485bce71 3259 | _, (B.Struct | B.Union) -> false
34e49164
C
3260
3261
3262
3263(*---------------------------------------------------------------------------*)
3264and inc_file (a, before_after) (b, h_rel_pos) =
3265
3266 let rec aux_inc (ass, bss) passed =
3267 match ass, bss with
3268 | [], [] -> true
3269 | [A.IncDots], _ ->
3270 let passed = List.rev passed in
3271
3272 (match before_after, !h_rel_pos with
3273 | IncludeNothing, _ -> true
3274 | IncludeMcodeBefore, Some x ->
3275 List.mem passed (x.Ast_c.first_of)
3276
3277 | IncludeMcodeAfter, Some x ->
3278 List.mem passed (x.Ast_c.last_of)
3279
3280 (* no info, maybe cos of a #include <xx.h> that was already in a .h *)
3281 | _, None -> false
3282 )
3283
b1b2de81 3284 | (A.IncPath x)::xs, y::ys -> x =$= y && aux_inc (xs, ys) (x::passed)
34e49164
C
3285 | _ -> failwith "IncDots not in last place or other pb"
3286
3287 in
3288
3289 match a, b with
3290 | A.Local ass, B.Local bss ->
3291 aux_inc (ass, bss) []
3292 | A.NonLocal ass, B.NonLocal bss ->
3293 aux_inc (ass, bss) []
3294 | _ -> false
3295
3296
3297
3298(*---------------------------------------------------------------------------*)
3299
3300and (define_params: sequence ->
3301 (A.define_param list, (string B.wrap) B.wrap2 list) matcher) =
3302 fun seqstyle eas ebs ->
3303 match seqstyle with
3304 | Unordered -> failwith "not handling ooo"
3305 | Ordered ->
3306 define_paramsbis eas (Ast_c.split_comma ebs) >>= (fun eas ebs_splitted ->
3307 return (eas, (Ast_c.unsplit_comma ebs_splitted))
3308 )
3309
3310(* todo? facto code with argument and parameters ? *)
3311and define_paramsbis = fun eas ebs ->
3312 match eas, ebs with
3313 | [], [] -> return ([], [])
3314 | [], eb::ebs -> fail
3315 | ea::eas, ebs ->
3316 X.all_bound (A.get_inherited ea) >&&>
3317 (match A.unwrap ea, ebs with
3318 | A.DPdots (mcode), ys ->
3319
3320 (* '...' can take more or less the beginnings of the arguments *)
3321 let startendxs = Common.zip (Common.inits ys) (Common.tails ys) in
3322 startendxs +> List.fold_left (fun acc (startxs, endxs) ->
3323 acc >||> (
3324
b1b2de81 3325 (if null startxs
34e49164
C
3326 then
3327 if mcode_contain_plus (mcodekind mcode)
3328 then fail
3329 (* failwith "I have no token that I could accroche myself on" *)
3330 else return (dots2metavar mcode, [])
3331 else
3332 (match Common.last startxs with
3333 | Right _ -> fail
3334 | Left _ ->
3335 X.distrf_define_params (dots2metavar mcode) startxs
3336 )
3337 ) >>= (fun mcode startxs ->
3338 let mcode = metavar2dots mcode in
3339 define_paramsbis eas endxs >>= (fun eas endxs ->
3340 return (
3341 (A.DPdots (mcode) +> A.rewrap ea) ::eas,
3342 startxs ++ endxs
3343 )))
3344 )
3345 ) fail
3346
3347 | A.DPComma ia1, Right ii::ebs ->
3348 let ib1 = tuple_of_list1 ii in
3349 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
3350 define_paramsbis eas ebs >>= (fun eas ebs ->
3351 return (
3352 (A.DPComma ia1 +> A.rewrap ea)::eas,
3353 (Right [ib1])::ebs
3354 )
3355 ))
3356
3357 | A.DPComma ia1, ebs ->
3358 if mcode_contain_plus (mcodekind ia1)
3359 then fail
3360 else
3361 (define_paramsbis eas ebs) (* try optional comma trick *)
3362
3363 | (A.OptDParam _ | A.UniqueDParam _), _ ->
3364 failwith "handling Opt/Unique for define parameters"
3365
3366 | A.DPcircles (_), ys -> raise Impossible (* in Ordered mode *)
3367
3368 | A.DParam ida, (Left (idb, ii))::ebs ->
3369 let ib1 = tuple_of_list1 ii in
3370 ident DontKnow ida (idb, ib1) >>= (fun ida (idb, ib1) ->
3371 define_paramsbis eas ebs >>= (fun eas ebs ->
3372 return (
3373 (A.DParam ida)+> A.rewrap ea :: eas,
3374 (Left (idb, [ib1]))::ebs
3375 )))
3376
3377 | _unwrapx, (Right y)::ys -> raise Impossible
3378 | _unwrapx, [] -> fail
3379 )
3380
3381
3382
3383(*****************************************************************************)
3384(* Entry points *)
3385(*****************************************************************************)
3386
3387(* no global solution for positions here, because for a statement metavariable
3388we want a MetaStmtVal, and for the others, it's not clear what we want *)
3389
3390let rec (rule_elem_node: (A.rule_elem, Control_flow_c.node) matcher) =
3391 fun re node ->
3392 let rewrap x =
3393 x >>= (fun a b -> return (A.rewrap re a, F.rewrap node b))
3394 in
3395 X.all_bound (A.get_inherited re) >&&>
3396
3397 rewrap (
3398 match A.unwrap re, F.unwrap node with
3399
3400 (* note: the order of the clauses is important. *)
3401
3402 | _, F.Enter | _, F.Exit | _, F.ErrorExit -> fail2()
3403
3404 (* the metaRuleElem contains just '-' information. We dont need to add
3405 * stuff in the environment. If we need stuff in environment, because
3406 * there is a + S somewhere, then this will be done via MetaStmt, not
3407 * via MetaRuleElem.
3408 * Can match TrueNode/FalseNode/... so must be placed before those cases.
3409 *)
3410
3411 | A.MetaRuleElem(mcode,keep,inherited), unwrap_node ->
3412 let default = A.MetaRuleElem(mcode,keep,inherited), unwrap_node in
3413 (match unwrap_node with
3414 | F.CaseNode _
951c7801
C
3415 | F.TrueNode | F.FalseNode | F.AfterNode
3416 | F.LoopFallThroughNode | F.FallThroughNode
34e49164 3417 | F.InLoopNode ->
b1b2de81 3418 if X.mode =*= PatternMode
34e49164
C
3419 then return default
3420 else
3421 if mcode_contain_plus (mcodekind mcode)
3422 then failwith "try add stuff on fake node"
3423 (* minusize or contextize a fake node is ok *)
3424 else return default
3425
3426 | F.EndStatement None ->
b1b2de81 3427 if X.mode =*= PatternMode then return default
34e49164
C
3428 else
3429 (* DEAD CODE NOW ? only useful in -no_cocci_vs_c_3 ?
3430 if mcode_contain_plus (mcodekind mcode)
3431 then
3432 let fake_info = Ast_c.fakeInfo() in
3433 distrf distrf_node (mcodekind mcode)
3434 (F.EndStatement (Some fake_info))
3435 else return unwrap_node
3436 *)
3437 raise Todo
3438
3439 | F.EndStatement (Some i1) ->
3440 tokenf mcode i1 >>= (fun mcode i1 ->
3441 return (
3442 A.MetaRuleElem (mcode,keep, inherited),
3443 F.EndStatement (Some i1)
3444 ))
3445
3446 | F.FunHeader _ ->
b1b2de81 3447 if X.mode =*= PatternMode then return default
34e49164
C
3448 else failwith "a MetaRuleElem can't transform a headfunc"
3449 | _n ->
b1b2de81 3450 if X.mode =*= PatternMode then return default
34e49164
C
3451 else
3452 X.distrf_node (generalize_mcode mcode) node >>= (fun mcode node ->
3453 return (
3454 A.MetaRuleElem(mcode,keep, inherited),
3455 F.unwrap node
3456 ))
3457 )
3458
3459
3460 (* rene cant have found that a state containing a fake/exit/... should be
3461 * transformed
3462 * TODO: and F.Fake ?
3463 *)
3464 | _, F.EndStatement _ | _, F.CaseNode _
951c7801
C
3465 | _, F.TrueNode | _, F.FalseNode | _, F.AfterNode
3466 | _, F.FallThroughNode | _, F.LoopFallThroughNode
34e49164
C
3467 | _, F.InLoopNode
3468 -> fail2()
3469
3470 (* really ? diff between pattern.ml and transformation.ml *)
3471 | _, F.Fake -> fail2()
3472
3473
3474 (* cas general: a Meta can match everything. It matches only
3475 * "header"-statement. We transform only MetaRuleElem, not MetaStmt.
3476 * So can't have been called in transform.
3477 *)
3478 | A.MetaStmt (ida,keep,metainfoMaybeTodo,inherited), F.Decl(_) -> fail
3479
3480 | A.MetaStmt (ida,keep,metainfoMaybeTodo,inherited), unwrap_node ->
3481 (* todo: should not happen in transform mode *)
3482
3483 (match Control_flow_c.extract_fullstatement node with
3484 | Some stb ->
3485 let max_min _ =
3486 Lib_parsing_c.lin_col_by_pos (Lib_parsing_c.ii_of_stmt stb) in
3487 X.envf keep inherited (ida, Ast_c.MetaStmtVal stb, max_min)
3488 (fun () ->
3489 (* no need tag ida, we can't be called in transform-mode *)
3490 return (
3491 A.MetaStmt (ida, keep, metainfoMaybeTodo, inherited),
3492 unwrap_node
3493 )
3494 )
3495 | None -> fail
3496 )
3497
3498 (* not me?: *)
3499 | A.MetaStmtList _, _ ->
3500 failwith "not handling MetaStmtList"
3501
3502 | A.TopExp ea, F.DefineExpr eb ->
3503 expression ea eb >>= (fun ea eb ->
3504 return (
3505 A.TopExp ea,
3506 F.DefineExpr eb
3507 ))
3508
3509 | A.TopExp ea, F.DefineType eb ->
3510 (match A.unwrap ea with
3511 A.TypeExp(ft) ->
3512 fullType ft eb >>= (fun ft eb ->
3513 return (
3514 A.TopExp (A.rewrap ea (A.TypeExp(ft))),
3515 F.DefineType eb
3516 ))
3517 | _ -> fail)
3518
3519
3520
3521 (* It is important to put this case before the one that fails because
3522 * of the lack of the counter part of a C construct in SmPL (for instance
3523 * there is not yet a CaseRange in SmPL). Even if SmPL don't handle
3524 * yet certain constructs, those constructs may contain expression
3525 * that we still want and can transform.
3526 *)
3527
3528 | A.Exp exp, nodeb ->
3529
3530 (* kind of iso, initialisation vs affectation *)
3531 let node =
3532 match A.unwrap exp, nodeb with
3533 | A.Assignment (ea, op, eb, true), F.Decl decl ->
3534 initialisation_to_affectation decl +> F.rewrap node
3535 | _ -> node
3536 in
3537
3538
3539 (* Now keep fullstatement inside the control flow node,
3540 * so that can then get in a MetaStmtVar the fullstatement to later
3541 * pp back when the S is in a +. But that means that
3542 * Exp will match an Ifnode even if there is no such exp
3543 * inside the condition of the Ifnode (because the exp may
3544 * be deeper, in the then branch). So have to not visit
3545 * all inside a node anymore.
3546 *
3547 * update: j'ai choisi d'accrocher au noeud du CFG à la
3548 * fois le fullstatement et le partialstatement et appeler le
3549 * visiteur que sur le partialstatement.
3550 *)
3551 let expfn =
3552 match Ast_cocci.get_pos re with
3553 | None -> expression
3554 | Some pos ->
3555 (fun ea eb ->
3556 let (max,min) =
3557 Lib_parsing_c.max_min_by_pos (Lib_parsing_c.ii_of_expr eb) in
3558 let keep = Type_cocci.Unitary in
3559 let inherited = false in
3560 let max_min _ = failwith "no pos" in
3561 X.envf keep inherited (pos, B.MetaPosVal (min,max), max_min)
3562 (fun () ->
3563 expression ea eb
3564 )
3565 )
3566 in
3567 X.cocciExp expfn exp node >>= (fun exp node ->
3568 return (
3569 A.Exp exp,
3570 F.unwrap node
3571 )
3572 )
3573
34e49164
C
3574 | A.Ty ty, nodeb ->
3575 X.cocciTy fullType ty node >>= (fun ty node ->
3576 return (
3577 A.Ty ty,
3578 F.unwrap node
3579 )
3580 )
1be43e12
C
3581
3582 | A.TopInit init, nodeb ->
3583 X.cocciInit initialiser init node >>= (fun init node ->
3584 return (
3585 A.TopInit init,
3586 F.unwrap node
3587 )
3588 )
34e49164
C
3589
3590
3591 | A.FunHeader (mckstart, allminus, fninfoa, ida, oparen, paramsa, cparen),
b1b2de81 3592 F.FunHeader ({B.f_name = nameidb;
485bce71
C
3593 f_type = (retb, (paramsb, (isvaargs, iidotsb)));
3594 f_storage = stob;
3595 f_attr = attrs;
3596 f_body = body;
91eba41f 3597 f_old_c_style = oldstyle;
485bce71
C
3598 }, ii) ->
3599 assert (null body);
34e49164 3600
91eba41f
C
3601 if oldstyle <> None
3602 then pr2 "OLD STYLE DECL NOT WELL SUPPORTED";
3603
3604
34e49164
C
3605 (* fninfoa records the order in which the SP specified the various
3606 information, but this isn't taken into account in the matching.
3607 Could this be a problem for transformation? *)
3608 let stoa =
3609 match
3610 List.filter (function A.FStorage(s) -> true | _ -> false) fninfoa
3611 with [A.FStorage(s)] -> Some s | _ -> None in
3612 let tya =
3613 match List.filter (function A.FType(s) -> true | _ -> false) fninfoa
3614 with [A.FType(t)] -> Some t | _ -> None in
3615
3616 (match List.filter (function A.FInline(i) -> true | _ -> false) fninfoa
3617 with [A.FInline(i)] -> failwith "not checking inline" | _ -> ());
3618
3619 (match List.filter (function A.FAttr(a) -> true | _ -> false) fninfoa
3620 with [A.FAttr(a)] -> failwith "not checking attributes" | _ -> ());
3621
3622 (match ii with
b1b2de81 3623 | ioparenb::icparenb::iifakestart::iistob ->
34e49164
C
3624
3625 (* maybe important to put ident as the first tokens to transform.
3626 * It's related to transform_proto. So don't change order
3627 * between the >>=.
3628 *)
b1b2de81 3629 ident_cpp LocalFunction ida nameidb >>= (fun ida nameidb ->
34e49164
C
3630 X.tokenf_mck mckstart iifakestart >>= (fun mckstart iifakestart ->
3631 tokenf oparen ioparenb >>= (fun oparen ioparenb ->
3632 tokenf cparen icparenb >>= (fun cparen icparenb ->
3633 parameters (seqstyle paramsa)
3634 (A.undots paramsa) paramsb >>=
3635 (fun paramsaundots paramsb ->
3636 let paramsa = redots paramsa paramsaundots in
3637 storage_optional_allminus allminus
3638 stoa (stob, iistob) >>= (fun stoa (stob, iistob) ->
3639 (
3640 if isvaargs
3641 then
3642 pr2_once
3643 ("Not handling well variable length arguments func. "^
3644 "You have been warned");
3645 if allminus
3646 then minusize_list iidotsb
3647 else return ((),iidotsb)
3648 ) >>= (fun () iidotsb ->
3649
3650 fullType_optional_allminus allminus tya retb >>= (fun tya retb ->
3651
3652 let fninfoa =
3653 (match stoa with Some st -> [A.FStorage st] | None -> []) ++
3654 (match tya with Some t -> [A.FType t] | None -> [])
3655
3656 in
3657
3658 return (
3659 A.FunHeader(mckstart,allminus,fninfoa,ida,oparen,
3660 paramsa,cparen),
b1b2de81 3661 F.FunHeader ({B.f_name = nameidb;
485bce71
C
3662 f_type = (retb, (paramsb, (isvaargs, iidotsb)));
3663 f_storage = stob;
3664 f_attr = attrs;
3665 f_body = body;
91eba41f 3666 f_old_c_style = oldstyle; (* TODO *)
485bce71 3667 },
b1b2de81 3668 ioparenb::icparenb::iifakestart::iistob)
34e49164
C
3669 )
3670 ))))))))
3671 | _ -> raise Impossible
3672 )
3673
3674
3675
3676
3677
3678
3679 | A.Decl (mckstart,allminus,decla), F.Decl declb ->
3680 declaration (mckstart,allminus,decla) declb >>=
3681 (fun (mckstart,allminus,decla) declb ->
3682 return (
3683 A.Decl (mckstart,allminus,decla),
3684 F.Decl declb
3685 ))
3686
3687
3688 | A.SeqStart mcode, F.SeqStart (st, level, i1) ->
3689 tokenf mcode i1 >>= (fun mcode i1 ->
3690 return (
3691 A.SeqStart mcode,
3692 F.SeqStart (st, level, i1)
3693 ))
3694
3695 | A.SeqEnd mcode, F.SeqEnd (level, i1) ->
3696 tokenf mcode i1 >>= (fun mcode i1 ->
3697 return (
3698 A.SeqEnd mcode,
3699 F.SeqEnd (level, i1)
3700 ))
3701
3702 | A.ExprStatement (ea, ia1), F.ExprStatement (st, (Some eb, ii)) ->
3703 let ib1 = tuple_of_list1 ii in
3704 expression ea eb >>= (fun ea eb ->
3705 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
3706 return (
3707 A.ExprStatement (ea, ia1),
3708 F.ExprStatement (st, (Some eb, [ib1]))
3709 )
3710 ))
3711
3712
3713 | A.IfHeader (ia1,ia2, ea, ia3), F.IfHeader (st, (eb,ii)) ->
3714 let (ib1, ib2, ib3) = tuple_of_list3 ii in
3715 expression ea eb >>= (fun ea eb ->
3716 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
3717 tokenf ia2 ib2 >>= (fun ia2 ib2 ->
3718 tokenf ia3 ib3 >>= (fun ia3 ib3 ->
3719 return (
3720 A.IfHeader (ia1, ia2, ea, ia3),
3721 F.IfHeader (st, (eb,[ib1;ib2;ib3]))
3722 )))))
3723
3724 | A.Else ia, F.Else ib ->
3725 tokenf ia ib >>= (fun ia ib ->
3726 return (A.Else ia, F.Else ib)
3727 )
3728
3729 | A.WhileHeader (ia1, ia2, ea, ia3), F.WhileHeader (st, (eb, ii)) ->
3730 let (ib1, ib2, ib3) = tuple_of_list3 ii in
3731 expression ea eb >>= (fun ea eb ->
3732 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
3733 tokenf ia2 ib2 >>= (fun ia2 ib2 ->
3734 tokenf ia3 ib3 >>= (fun ia3 ib3 ->
3735 return (
3736 A.WhileHeader (ia1, ia2, ea, ia3),
3737 F.WhileHeader (st, (eb, [ib1;ib2;ib3]))
3738 )))))
3739
3740 | A.DoHeader ia, F.DoHeader (st, ib) ->
3741 tokenf ia ib >>= (fun ia ib ->
3742 return (
3743 A.DoHeader ia,
3744 F.DoHeader (st, ib)
3745 ))
3746 | A.WhileTail (ia1,ia2,ea,ia3,ia4), F.DoWhileTail (eb, ii) ->
3747 let (ib1, ib2, ib3, ib4) = tuple_of_list4 ii in
3748 expression ea eb >>= (fun ea eb ->
3749 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
3750 tokenf ia2 ib2 >>= (fun ia2 ib2 ->
3751 tokenf ia3 ib3 >>= (fun ia3 ib3 ->
3752 tokenf ia4 ib4 >>= (fun ia4 ib4 ->
3753 return (
3754 A.WhileTail (ia1,ia2,ea,ia3,ia4),
3755 F.DoWhileTail (eb, [ib1;ib2;ib3;ib4])
3756 ))))))
3757 | A.IteratorHeader (ia1, ia2, eas, ia3), F.MacroIterHeader (st, ((s,ebs),ii))
3758 ->
3759 let (ib1, ib2, ib3) = tuple_of_list3 ii in
3760
3761 ident DontKnow ia1 (s, ib1) >>= (fun ia1 (s, ib1) ->
3762 tokenf ia2 ib2 >>= (fun ia2 ib2 ->
3763 tokenf ia3 ib3 >>= (fun ia3 ib3 ->
3764 arguments (seqstyle eas) (A.undots eas) ebs >>= (fun easundots ebs ->
3765 let eas = redots eas easundots in
3766 return (
3767 A.IteratorHeader (ia1, ia2, eas, ia3),
3768 F.MacroIterHeader (st, ((s,ebs), [ib1;ib2;ib3]))
3769 )))))
3770
3771
3772
3773 | A.ForHeader (ia1, ia2, ea1opt, ia3, ea2opt, ia4, ea3opt, ia5),
3774 F.ForHeader (st, (((eb1opt,ib3s), (eb2opt,ib4s), (eb3opt,ib4vide)), ii))
3775 ->
3776 assert (null ib4vide);
3777 let (ib1, ib2, ib5) = tuple_of_list3 ii in
3778 let ib3 = tuple_of_list1 ib3s in
3779 let ib4 = tuple_of_list1 ib4s in
3780
3781 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
3782 tokenf ia2 ib2 >>= (fun ia2 ib2 ->
3783 tokenf ia3 ib3 >>= (fun ia3 ib3 ->
3784 tokenf ia4 ib4 >>= (fun ia4 ib4 ->
3785 tokenf ia5 ib5 >>= (fun ia5 ib5 ->
3786 option expression ea1opt eb1opt >>= (fun ea1opt eb1opt ->
3787 option expression ea2opt eb2opt >>= (fun ea2opt eb2opt ->
3788 option expression ea3opt eb3opt >>= (fun ea3opt eb3opt ->
3789 return (
3790 A.ForHeader (ia1, ia2, ea1opt, ia3, ea2opt, ia4, ea3opt, ia5),
3791 F.ForHeader (st, (((eb1opt,[ib3]), (eb2opt,[ib4]), (eb3opt,[])),
3792 [ib1;ib2;ib5]))
3793
3794 )))))))))
3795
3796
3797 | A.SwitchHeader(ia1,ia2,ea,ia3), F.SwitchHeader (st, (eb,ii)) ->
3798 let (ib1, ib2, ib3) = tuple_of_list3 ii in
3799 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
3800 tokenf ia2 ib2 >>= (fun ia2 ib2 ->
3801 tokenf ia3 ib3 >>= (fun ia3 ib3 ->
3802 expression ea eb >>= (fun ea eb ->
3803 return (
3804 A.SwitchHeader(ia1,ia2,ea,ia3),
3805 F.SwitchHeader (st, (eb,[ib1;ib2;ib3]))
3806 )))))
3807
3808 | A.Break (ia1, ia2), F.Break (st, ((),ii)) ->
3809 let (ib1, ib2) = tuple_of_list2 ii in
3810 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
3811 tokenf ia2 ib2 >>= (fun ia2 ib2 ->
3812 return (
3813 A.Break (ia1, ia2),
3814 F.Break (st, ((),[ib1;ib2]))
3815 )))
3816
3817 | A.Continue (ia1, ia2), F.Continue (st, ((),ii)) ->
3818 let (ib1, ib2) = tuple_of_list2 ii in
3819 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
3820 tokenf ia2 ib2 >>= (fun ia2 ib2 ->
3821 return (
3822 A.Continue (ia1, ia2),
3823 F.Continue (st, ((),[ib1;ib2]))
3824 )))
3825
3826 | A.Return (ia1, ia2), F.Return (st, ((),ii)) ->
3827 let (ib1, ib2) = tuple_of_list2 ii in
3828 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
3829 tokenf ia2 ib2 >>= (fun ia2 ib2 ->
3830 return (
3831 A.Return (ia1, ia2),
3832 F.Return (st, ((),[ib1;ib2]))
3833 )))
3834
3835 | A.ReturnExpr (ia1, ea, ia2), F.ReturnExpr (st, (eb, ii)) ->
3836 let (ib1, ib2) = tuple_of_list2 ii in
3837 tokenf ia1 ib1 >>= (fun ia1 ib1 ->
3838 tokenf ia2 ib2 >>= (fun ia2 ib2 ->
3839 expression ea eb >>= (fun ea eb ->
3840 return (
3841 A.ReturnExpr (ia1, ea, ia2),
3842 F.ReturnExpr (st, (eb, [ib1;ib2]))
3843 ))))
3844
3845
3846
485bce71
C
3847 | A.Include(incla,filea),
3848 F.Include {B.i_include = (fileb, ii);
3849 B.i_rel_pos = h_rel_pos;
3850 B.i_is_in_ifdef = inifdef;
3851 B.i_content = copt;
3852 } ->
b1b2de81 3853 assert (copt =*= None);
485bce71 3854
34e49164
C
3855 let include_requirment =
3856 match mcodekind incla, mcodekind filea with
3857 | A.CONTEXT (_, A.BEFORE _), _ ->
3858 IncludeMcodeBefore
3859 | _, A.CONTEXT (_, A.AFTER _) ->
3860 IncludeMcodeAfter
3861 | _ ->
3862 IncludeNothing
3863 in
3864
3865 let (inclb, iifileb) = tuple_of_list2 ii in
3866 if inc_file (term filea, include_requirment) (fileb, h_rel_pos)
3867 then
3868 tokenf incla inclb >>= (fun incla inclb ->
3869 tokenf filea iifileb >>= (fun filea iifileb ->
3870 return (
3871 A.Include(incla, filea),
485bce71
C
3872 F.Include {B.i_include = (fileb, [inclb;iifileb]);
3873 B.i_rel_pos = h_rel_pos;
3874 B.i_is_in_ifdef = inifdef;
3875 B.i_content = copt;
3876 }
34e49164
C
3877 )))
3878 else fail
3879
3880
3881
3882 | A.DefineHeader(definea,ida,params), F.DefineHeader ((idb, ii), defkind) ->
3883 let (defineb, iidb, ieol) = tuple_of_list3 ii in
3884 ident DontKnow ida (idb, iidb) >>= (fun ida (idb, iidb) ->
3885 tokenf definea defineb >>= (fun definea defineb ->
3886 (match A.unwrap params, defkind with
3887 | A.NoParams, B.DefineVar ->
3888 return (
3889 A.NoParams +> A.rewrap params,
3890 B.DefineVar
3891 )
3892 | A.DParams(lpa,eas,rpa), (B.DefineFunc (ebs, ii)) ->
3893 let (lpb, rpb) = tuple_of_list2 ii in
3894 tokenf lpa lpb >>= (fun lpa lpb ->
3895 tokenf rpa rpb >>= (fun rpa rpb ->
3896
3897 define_params (seqstyle eas) (A.undots eas) ebs >>=
3898 (fun easundots ebs ->
3899 let eas = redots eas easundots in
3900 return (
3901 A.DParams (lpa,eas,rpa) +> A.rewrap params,
3902 B.DefineFunc (ebs,[lpb;rpb])
3903 )
3904 )))
3905 | _ -> fail
3906 ) >>= (fun params defkind ->
3907 return (
3908 A.DefineHeader (definea, ida, params),
3909 F.DefineHeader ((idb,[defineb;iidb;ieol]),defkind)
3910 ))
3911 ))
3912
3913
3914 | A.Default(def,colon), F.Default (st, ((),ii)) ->
3915 let (ib1, ib2) = tuple_of_list2 ii in
3916 tokenf def ib1 >>= (fun def ib1 ->
3917 tokenf colon ib2 >>= (fun colon ib2 ->
3918 return (
3919 A.Default(def,colon),
3920 F.Default (st, ((),[ib1;ib2]))
3921 )))
3922
3923
3924
3925 | A.Case(case,ea,colon), F.Case (st, (eb,ii)) ->
3926 let (ib1, ib2) = tuple_of_list2 ii in
3927 tokenf case ib1 >>= (fun case ib1 ->
3928 expression ea eb >>= (fun ea eb ->
3929 tokenf colon ib2 >>= (fun colon ib2 ->
3930 return (
3931 A.Case(case,ea,colon),
3932 F.Case (st, (eb,[ib1;ib2]))
3933 ))))
3934
3935 (* only occurs in the predicates generated by asttomember *)
3936 | A.DisjRuleElem eas, _ ->
3937 (eas +>
3938 List.fold_left (fun acc ea -> acc >|+|> (rule_elem_node ea node)) fail)
3939 >>= (fun ea eb -> return (A.unwrap ea,F.unwrap eb))
3940
3941 | _, F.ExprStatement (_, (None, ii)) -> fail (* happen ? *)
3942
b1b2de81
C
3943 | A.Label(id,dd), F.Label (st, nameb, ((),ii)) ->
3944 let (ib2) = tuple_of_list1 ii in
978fd7e5
C
3945 ident_cpp DontKnow id nameb >>= (fun ida nameb ->
3946 tokenf dd ib2 >>= (fun dd ib2 ->
3947 return (
3948 A.Label (ida,dd),
3949 F.Label (st,nameb, ((),[ib2]))
3950 )))
34e49164 3951
b1b2de81
C
3952 | A.Goto(goto,id,sem), F.Goto (st,nameb, ((),ii)) ->
3953 let (ib1,ib3) = tuple_of_list2 ii in
34e49164 3954 tokenf goto ib1 >>= (fun goto ib1 ->
b1b2de81 3955 ident_cpp DontKnow id nameb >>= (fun id nameb ->
34e49164
C
3956 tokenf sem ib3 >>= (fun sem ib3 ->
3957 return(
3958 A.Goto(goto,id,sem),
b1b2de81 3959 F.Goto (st,nameb, ((),[ib1;ib3]))
34e49164
C
3960 ))))
3961
3962 (* have not a counter part in coccinelle, for the moment *)
3963 (* todo?: print a warning at least ? *)
3964 | _, F.CaseRange _
3965 | _, F.Asm _
34e49164
C
3966 | _, F.MacroTop _
3967 -> fail2()
3968
485bce71
C
3969 | _, (F.IfdefEndif _|F.IfdefElse _|F.IfdefHeader _)
3970 -> fail2 ()
3971
3972 | _,
3973 (F.MacroStmt (_, _)| F.DefineDoWhileZeroHeader _| F.EndNode|F.TopNode)
3974 -> fail
3975 | _,
b1b2de81 3976 (F.Label (_, _, _)|F.Break (_, _)|F.Continue (_, _)|F.Default (_, _)|
485bce71
C
3977 F.Case (_, _)|F.Include _|F.Goto _|F.ExprStatement _|
3978 F.DefineType _|F.DefineExpr _|F.DefineTodo|
3979 F.DefineHeader (_, _)|F.ReturnExpr (_, _)|F.Return (_, _)|F.MacroIterHeader (_, _)|
3980 F.SwitchHeader (_, _)|F.ForHeader (_, _)|F.DoWhileTail _|F.DoHeader (_, _)|
3981 F.WhileHeader (_, _)|F.Else _|F.IfHeader (_, _)|
3982 F.SeqEnd (_, _)|F.SeqStart (_, _, _)|
3983 F.Decl _|F.FunHeader _)
3984 -> fail
3985
34e49164 3986
34e49164
C
3987 )
3988end
3989