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