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