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