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