Version 1.0.0-rc17 has been released. Some changes are:
[bpt/coccinelle.git] / parsing_cocci / parser_cocci_menhir.mly
1 /*
2 * Copyright 2012, INRIA
3 * Julia Lawall, Gilles Muller
4 * Copyright 2010-2011, INRIA, University of Copenhagen
5 * Julia Lawall, Rene Rydhof Hansen, Gilles Muller, Nicolas Palix
6 * Copyright 2005-2009, Ecole des Mines de Nantes, University of Copenhagen
7 * Yoann Padioleau, Julia Lawall, Rene Rydhof Hansen, Henrik Stuart, Gilles Muller, Nicolas Palix
8 * This file is part of Coccinelle.
9 *
10 * Coccinelle is free software: you can redistribute it and/or modify
11 * it under the terms of the GNU General Public License as published by
12 * the Free Software Foundation, according to version 2 of the License.
13 *
14 * Coccinelle is distributed in the hope that it will be useful,
15 * but WITHOUT ANY WARRANTY; without even the implied warranty of
16 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
17 * GNU General Public License for more details.
18 *
19 * You should have received a copy of the GNU General Public License
20 * along with Coccinelle. If not, see <http://www.gnu.org/licenses/>.
21 *
22 * The authors reserve the right to distribute this or future versions of
23 * Coccinelle under other licenses.
24 */
25
26
27 %{
28
29 (* Not clear how to allow function declarations to specify a return type
30 and how to allow both to be specified as static, because they are in
31 different rules. The rules seem to have to be combined, which would allow
32 functions to be declared as local variables *)
33
34 (* Not clear how to let a function have a parameter of type void. At the
35 moment, void is allowed to be the type of a variable, which is wrong, and a
36 parameter needs both a type and an identifier *)
37 module Ast0 = Ast0_cocci
38 module Ast = Ast_cocci
39 module P = Parse_aux
40
41 (* ---------------------------------------------------------------------- *)
42 (* support for TMeta *)
43
44 let print_meta (r,n) = r^"."^n
45
46 let meta_metatable = Hashtbl.create(101)
47
48 let coerce_tmeta newty name builder matcher =
49 try
50 let x = Hashtbl.find meta_metatable name in
51 if not (matcher x)
52 then
53 failwith
54 (Printf.sprintf "Metavariable %s is used as %s"
55 (print_meta name) newty)
56 with Not_found ->
57 (if !Flag_parsing_cocci.show_SP
58 then
59 Common.pr2
60 (Printf.sprintf
61 "Metavariable %s is assumed to be %s metavariable"
62 (print_meta name) newty));
63 Hashtbl.add meta_metatable name builder
64
65 let tmeta_to_type (name,pure,clt) =
66 (coerce_tmeta "a type" name (TMetaType(name,pure,clt))
67 (function TMetaType(_,_,_) -> true | _ -> false));
68 Ast0.wrap(Ast0.MetaType(P.clt2mcode name clt,pure))
69
70 let tmeta_to_field (name,pure,clt) =
71 (coerce_tmeta "a field" name (TMetaField(name,pure,clt))
72 (function TMetaField(_,_,_) -> true | _ -> false));
73 P.meta_field (name,pure,clt)
74
75 let tmeta_to_exp (name,pure,clt) =
76 (coerce_tmeta "an expression" name
77 (TMetaExp(name,Ast0.NoConstraint,pure,None,clt))
78 (function TMetaExp(_,_,_,_,_) -> true | _ -> false));
79 Ast0.wrap
80 (Ast0.MetaExpr(P.clt2mcode name clt,Ast0.NoConstraint,None,Ast.ANY,pure))
81
82 let tmeta_to_param (name,pure,clt) =
83 (coerce_tmeta "a parameter" name (TMetaParam(name,pure,clt))
84 (function TMetaParam(_,_,_) -> true | _ -> false));
85 Ast0.wrap(Ast0.MetaParam(P.clt2mcode name clt,pure))
86
87 let tmeta_to_statement (name,pure,clt) =
88 (coerce_tmeta "a statement" name (TMetaType(name,pure,clt))
89 (function TMetaType(_,_,_) -> true | _ -> false));
90 P.meta_stm (name,pure,clt)
91
92 let tmeta_to_seed_id (name,pure,clt) =
93 (coerce_tmeta "an identifier" name
94 (TMetaId(name,Ast.IdNoConstraint,Ast.NoVal,pure,clt))
95 (function TMetaId(_,_,_,_,_) -> true | _ -> false));
96 Ast.SeedId name
97
98 let tmeta_to_ident (name,pure,clt) =
99 (coerce_tmeta "an identifier" name
100 (TMetaId(name,Ast.IdNoConstraint,Ast.NoVal,pure,clt))
101 (function TMetaId(_,_,_,_,_) -> true | _ -> false));
102 Ast0.wrap(Ast0.MetaId(P.clt2mcode name clt,Ast.IdNoConstraint,Ast.NoVal,pure))
103 %}
104
105 %token EOF
106
107 %token TIdentifier TExpression TStatement TFunction TLocal TType TParameter
108 %token TIdExpression TInitialiser TDeclaration TField TMetavariable TSymbol
109 %token Tlist TFresh TConstant TError TWords TWhy0 TPlus0 TBang0
110 %token TPure TContext TGenerated
111 %token TTypedef TDeclarer TIterator TName TPosition TAnalysis TPosAny
112 %token TUsing TDisable TExtends TDepends TOn TEver TNever TExists TForall
113 %token TScript TInitialize TFinalize TNothing TVirtual
114 %token<string> TRuleName
115
116 %token<Data.clt> Tchar Tshort Tint Tdouble Tfloat Tlong
117 %token<Data.clt> Tsize_t Tssize_t Tptrdiff_t
118 %token<Data.clt> Tvoid Tstruct Tunion Tenum
119 %token<Data.clt> Tunsigned Tsigned
120
121 %token<Data.clt> Tstatic Tauto Tregister Textern Tinline Ttypedef
122 %token<Data.clt> Tconst Tvolatile
123 %token<string * Data.clt> Tattr
124
125 %token <Data.clt> TIf TElse TWhile TFor TDo TSwitch TCase TDefault TReturn
126 %token <Data.clt> TBreak TContinue TGoto TSizeof TFunDecl
127 %token <string * Data.clt> TIdent TTypeId TDeclarerId TIteratorId TSymId
128 %token <Ast_cocci.added_string * Data.clt> TPragma
129
130 %token <Parse_aux.midinfo> TMetaId
131 %token <Parse_aux.idinfo> TMetaFunc TMetaLocalFunc
132 %token <Parse_aux.idinfo> TMetaIterator TMetaDeclarer
133 %token <Parse_aux.expinfo> TMetaErr
134 %token <Parse_aux.info> TMetaParam TMetaStm TMetaStmList TMetaType
135 %token <Parse_aux.info> TMetaInit TMetaDecl TMetaField TMeta
136 %token <Parse_aux.list_info> TMetaParamList TMetaExpList TMetaInitList
137 %token <Parse_aux.list_info> TMetaFieldList
138 %token <Parse_aux.typed_expinfo> TMetaExp TMetaIdExp TMetaLocalIdExp TMetaConst
139 %token <Parse_aux.pos_info> TMetaPos
140
141 %token TArob TArobArob
142 %token <Data.clt> TPArob
143 %token <string> TScriptData
144
145 %token <Data.clt> TEllipsis TOEllipsis TCEllipsis TPOEllipsis TPCEllipsis
146 %token <Data.clt> TWhen TWhenTrue TWhenFalse TAny TStrict TLineEnd
147
148 %token <Data.clt> TWhy TDotDot TBang TOPar TOPar0
149 %token <Data.clt> TMid0 TCPar TCPar0
150
151 %token <string> TPathIsoFile
152 %token <string * Data.clt> TIncludeL TIncludeNL
153 %token <Data.clt * token> TDefine TUndef
154 %token <Data.clt * token * int * int> TDefineParam
155 %token <string * Data.clt> TMinusFile TPlusFile
156
157 %token <Data.clt> TInc TDec
158
159 %token <string * Data.clt> TString TChar TFloat TInt
160
161 %token <Data.clt> TOrLog
162 %token <Data.clt> TAndLog
163 %token <Data.clt> TOr
164 %token <Data.clt> TXor
165 %token <Data.clt> TAnd
166 %token <Data.clt> TEqEq TNotEq TTildeEq TTildeExclEq TSub
167 %token <Ast_cocci.logicalOp * Data.clt> TLogOp /* TInf TSup TInfEq TSupEq */
168 %token <Ast_cocci.arithOp * Data.clt> TShLOp TShROp /* TShl TShr */
169 %token <Ast_cocci.arithOp * Data.clt> TDmOp /* TDiv TMod TMin TMax */
170 %token <Data.clt> TPlus TMinus
171 %token <Data.clt> TMul TTilde
172
173 %token <Data.clt> TOBrace TCBrace TOInit
174 %token <Data.clt> TOCro TCCro
175
176 %token <Data.clt> TPtrOp
177
178 %token TMPtVirg TCppConcatOp
179 %token <Data.clt> TEq TDot TComma TPtVirg
180 %token <Ast_cocci.assignOp * Data.clt> TAssign
181
182 %token TIso TRightIso TIsoExpression TIsoStatement TIsoDeclaration TIsoType
183 %token TIsoTopLevel TIsoArgExpression TIsoTestExpression TIsoToTestExpression
184
185 %token TUnderscore
186
187 %token TInvalid
188
189 /* operator precedence */
190 %nonassoc TIf
191 %nonassoc TElse
192
193 %left TOrLog
194 %left TAndLog
195 %left TOr
196 %left TXor
197 %left TAnd
198 %left TEqEq TNotEq
199 %left TLogOp /* TInf TSup TInfEq TSupEq */
200 %left TShLOp TShROp /* TShl TShr */
201 %left TPlus TMinus
202 %left TMul TDmOp /* TDiv TMod TMin TMax */
203
204 %start reinit
205 %type <unit> reinit
206
207 %start minus_main
208 %type <Ast0_cocci.rule> minus_main
209
210 %start minus_exp_main
211 %type <Ast0_cocci.rule> minus_exp_main
212
213 %start plus_main
214 %type <Ast0_cocci.rule> plus_main
215
216 %start plus_exp_main
217 %type <Ast0_cocci.rule> plus_exp_main
218
219 %start include_main
220 %type <Data.incl_iso list> include_main
221
222 %start iso_rule_name
223 %type <Ast_cocci.rulename>
224 iso_rule_name
225
226 %start rule_name
227 %type <Ast_cocci.rulename>
228 rule_name
229
230 %start meta_main
231 %type <(Ast_cocci.metavar,Ast_cocci.metavar) Common.either list> meta_main
232
233 %start <(string option (*string*) * string option (*ast*)) * (Ast_cocci.meta_name * Ast_cocci.metavar) option> script_meta_main
234
235 %start iso_main
236 %type <Ast0_cocci.anything list list> iso_main
237
238 %start iso_meta_main
239 %type <(Ast_cocci.metavar,Ast_cocci.metavar) Common.either list> iso_meta_main
240
241 %start never_used
242 %type <unit> never_used
243
244 %%
245
246 reinit: { }
247 minus_main: minus_body EOF { $1 } | m=minus_body TArobArob { m }
248 | m=minus_body TArob { m }
249 plus_main: plus_body EOF { $1 } | p=plus_body TArobArob { p }
250 | p=plus_body TArob { p }
251 minus_exp_main: minus_exp_body EOF { $1 } | m=minus_exp_body TArobArob { m }
252 | m=minus_exp_body TArob { m }
253 plus_exp_main: plus_exp_body EOF { $1 } | p=plus_exp_body TArobArob { p }
254 | p=plus_exp_body TArob { p }
255 meta_main: m=metadec { m (!Ast0.rule_name) }
256 iso_meta_main: m=metadec { m "" }
257
258 /*****************************************************************************
259 *
260 *
261 *****************************************************************************/
262
263 pure:
264 TPure { Ast0.Pure }
265 | TContext { Ast0.Context }
266 | TPure TContext { Ast0.PureContext }
267 | TContext TPure { Ast0.PureContext }
268 | /* empty */ { Ast0.Impure }
269
270 iso_rule_name:
271 nm=pure_ident TArob { P.make_iso_rule_name_result (P.id2name nm) }
272
273 rule_name:
274 nm=ioption(pure_ident) extends d=depends i=loption(choose_iso)
275 a=loption(disable) e=exists ee=is_expression TArob
276 { P.make_cocci_rule_name_result nm d i a e ee }
277 | TGenerated extends d=depends i=loption(choose_iso)
278 a=loption(disable) e=exists ee=is_expression TArob
279 /* these rules have no name as a cheap way to ensure that no normal
280 rule inherits their metavariables or depends on them */
281 { P.make_generated_rule_name_result None d i a e ee }
282 | TScript TDotDot lang=pure_ident nm=ioption(pure_ident) d=depends TArob
283 { P.make_script_rule_name_result lang nm d }
284 | TInitialize TDotDot lang=pure_ident d=depends TArob
285 { P.make_initial_script_rule_name_result lang d }
286 | TFinalize TDotDot lang=pure_ident d=depends TArob
287 { P.make_final_script_rule_name_result lang d }
288
289 extends:
290 /* empty */ { () }
291 | TExtends parent=TRuleName
292 { !Data.install_bindings (parent) }
293
294 depends:
295 /* empty */ { Ast0.NoDep }
296 | TDepends TOn parents=dep { parents }
297
298 dep:
299 TRuleName { Ast0.Dep $1 }
300 | TBang TRuleName { Ast0.AntiDep (Ast0.Dep $2) }
301 | TBang TOPar dep TCPar
302 { Ast0.AntiDep $3 }
303 | TEver TRuleName { Ast0.EverDep $2 }
304 | TNever TRuleName { Ast0.NeverDep $2 }
305 | dep TAndLog dep { Ast0.AndDep($1, $3) }
306 | dep TOrLog dep { Ast0.OrDep ($1, $3) }
307 | TOPar dep TCPar { $2 }
308
309 choose_iso:
310 TUsing separated_nonempty_list(TComma,TString) { List.map P.id2name $2 }
311
312 disable:
313 TDisable separated_nonempty_list(TComma,pure_ident) { List.map P.id2name $2 }
314
315 exists:
316 TExists { Ast.Exists }
317 | TForall { Ast.Forall }
318 | { Ast.Undetermined }
319
320 is_expression: // for more flexible parsing of top level expressions
321 { false }
322 | TExpression { true }
323
324 include_main:
325 list(incl) TArob { $1 }
326 | list(incl) TArobArob { $1 }
327
328 incl:
329 TIncludeL { let (x,_) = $1 in Data.Include(x) }
330 | TUsing TString { Data.Iso(Common.Left(P.id2name $2)) }
331 | TUsing TPathIsoFile { Data.Iso(Common.Right $2) }
332 | TVirtual comma_list(pure_ident)
333 { let names = List.map P.id2name $2 in
334 Iteration.parsed_virtual_rules :=
335 Common.union_set names !Iteration.parsed_virtual_rules;
336 (* ensure that the names of virtual and real rules don't overlap *)
337 List.iter
338 (function name -> Hashtbl.add Data.all_metadecls name [])
339 names;
340 Data.Virt(names) }
341
342 metadec:
343 ar=arity ispure=pure
344 kindfn=metakind ids=comma_list(pure_ident_or_meta_ident) TMPtVirg
345 { P.create_metadec ar ispure kindfn ids }
346 | kindfn=metakind_fresh ids=comma_list(pure_ident_or_meta_ident_with_seed)
347 TMPtVirg
348 { P.create_fresh_metadec kindfn ids }
349 | ar=arity ispure=pure
350 kindfn=metakind_atomic_maybe_virt
351 ids=
352 comma_list(pure_ident_or_meta_ident_with_idconstraint_virt(re_or_not_eqid))
353 TMPtVirg
354 { let (normal,virt) = Common.partition_either (fun x -> x) ids in
355 let (idfn,virtfn) = kindfn in
356 function cr ->
357 (P.create_metadec_with_constraints ar ispure idfn normal cr) @
358 (P.create_metadec_virt ar ispure virtfn virt cr) }
359 | ar=arity ispure=pure
360 kindfn=metakind_atomic
361 ids=comma_list(pure_ident_or_meta_ident_with_idconstraint(re_or_not_eqid))
362 TMPtVirg
363 { P.create_metadec_with_constraints ar ispure kindfn ids }
364 | ar=arity ispure=pure
365 kindfn=metakind_atomic_expi
366 ids=comma_list(pure_ident_or_meta_ident_with_econstraint(re_or_not_eqe_or_sub))
367 TMPtVirg
368 { P.create_metadec_with_constraints ar ispure kindfn ids }
369 | ar=arity ispure=pure
370 kindfn=metakind_atomic_expe
371 ids=comma_list(pure_ident_or_meta_ident_with_econstraint(not_ceq_or_sub))
372 TMPtVirg
373 { P.create_metadec_with_constraints ar ispure kindfn ids }
374 | ar=arity TPosition a=option(TPosAny)
375 ids=comma_list(pure_ident_or_meta_ident_with_x_eq(not_pos)) TMPtVirg
376 (* pb: position variables can't be inherited from normal rules, and then
377 there is no way to inherit from a generated rule, so there is no point
378 to have a position variable *)
379 { (if !Data.in_generating
380 then failwith "position variables not allowed in a generated rule file");
381 let kindfn arity name pure check_meta constraints =
382 let tok = check_meta(Ast.MetaPosDecl(arity,name)) in
383 let any = match a with None -> Ast.PER | Some _ -> Ast.ALL in
384 !Data.add_pos_meta name constraints any; tok in
385 P.create_metadec_with_constraints ar false kindfn ids }
386 | ar=arity ispure=pure
387 TParameter Tlist TOCro len=list_len TCCro
388 ids=comma_list(pure_ident_or_meta_ident) TMPtVirg
389 { P.create_len_metadec ar ispure
390 (fun lenname arity name pure check_meta ->
391 let tok = check_meta(Ast.MetaParamListDecl(arity,name,lenname)) in
392 !Data.add_paramlist_meta name lenname pure; tok)
393 len ids }
394 | ar=arity ispure=pure
395 TExpression Tlist TOCro len=list_len TCCro
396 ids=comma_list(pure_ident_or_meta_ident) TMPtVirg
397 { P.create_len_metadec ar ispure
398 (fun lenname arity name pure check_meta ->
399 let tok = check_meta(Ast.MetaExpListDecl(arity,name,lenname)) in
400 !Data.add_explist_meta name lenname pure; tok)
401 len ids }
402 | ar=arity ispure=pure
403 TField Tlist TOCro len=list_len TCCro
404 ids=comma_list(pure_ident_or_meta_ident) TMPtVirg
405 { P.create_len_metadec ar ispure
406 (fun lenname arity name pure check_meta ->
407 let tok = check_meta(Ast.MetaFieldListDecl(arity,name,lenname)) in
408 !Data.add_field_list_meta name lenname pure; tok)
409 len ids }
410 | ar=arity ispure=pure
411 TInitialiser Tlist TOCro len=list_len TCCro
412 ids=comma_list(pure_ident_or_meta_ident) TMPtVirg
413 { P.create_len_metadec ar ispure
414 (fun lenname arity name pure check_meta ->
415 let tok = check_meta(Ast.MetaInitListDecl(arity,name,lenname)) in
416 !Data.add_initlist_meta name lenname pure; tok)
417 len ids }
418 | TSymbol ids=comma_list(pure_ident) TMPtVirg
419 { (fun _ ->
420 let add_sym = fun (nm,_) -> !Data.add_symbol_meta nm in
421 List.iter add_sym ids; [])
422 }
423
424 list_len:
425 pure_ident_or_meta_ident { Common.Left $1 }
426 | TInt { let (x,clt) = $1 in Common.Right (int_of_string x) }
427 | TVirtual TDot pure_ident
428 { let nm = ("virtual",P.id2name $3) in
429 Iteration.parsed_virtual_identifiers :=
430 Common.union_set [snd nm]
431 !Iteration.parsed_virtual_identifiers;
432 try
433 Common.Right (int_of_string
434 (List.assoc (snd nm) !Flag.defined_virtual_env))
435 with Not_found | Failure "int_of_string" ->
436 begin
437 Common.Left (Some "virtual",P.id2name $3)
438 end
439 }
440
441
442 %inline metakind_fresh:
443 TFresh TIdentifier
444 { (fun name check_meta seed ->
445 let tok = check_meta(Ast.MetaFreshIdDecl(name,seed)) in
446 !Data.add_fresh_id_meta name seed; tok) }
447
448 /* metavariable kinds with no constraints, etc */
449 %inline metakind:
450 TMetavariable
451 { (fun arity name pure check_meta ->
452 let tok = check_meta(Ast.MetaMetaDecl(arity,name)) in
453 !Data.add_meta_meta name pure; tok) }
454 | TParameter
455 { (fun arity name pure check_meta ->
456 let tok = check_meta(Ast.MetaParamDecl(arity,name)) in
457 !Data.add_param_meta name pure; tok) }
458 | TParameter Tlist
459 { (fun arity name pure check_meta ->
460 let len = Ast.AnyLen in
461 let tok = check_meta(Ast.MetaParamListDecl(arity,name,len)) in
462 !Data.add_paramlist_meta name len pure; tok) }
463 | TExpression Tlist
464 { (fun arity name pure check_meta ->
465 let len = Ast.AnyLen in
466 let tok = check_meta(Ast.MetaExpListDecl(arity,name,len)) in
467 !Data.add_explist_meta name len pure; tok) }
468 | TType
469 { (fun arity name pure check_meta ->
470 let tok = check_meta(Ast.MetaTypeDecl(arity,name)) in
471 !Data.add_type_meta name pure; tok) }
472 | TInitialiser
473 { (fun arity name pure check_meta ->
474 let tok = check_meta(Ast.MetaInitDecl(arity,name)) in
475 !Data.add_init_meta name pure; tok) }
476 | TInitialiser Tlist
477 { (fun arity name pure check_meta ->
478 let len = Ast.AnyLen in
479 let tok = check_meta(Ast.MetaInitListDecl(arity,name,len)) in
480 !Data.add_initlist_meta name len pure; tok) }
481 | TStatement
482 { (fun arity name pure check_meta ->
483 let tok = check_meta(Ast.MetaStmDecl(arity,name)) in
484 !Data.add_stm_meta name pure; tok) }
485 | TDeclaration
486 { (fun arity name pure check_meta ->
487 let tok = check_meta(Ast.MetaDeclDecl(arity,name)) in
488 !Data.add_decl_meta name pure; tok) }
489 | TField
490 { (fun arity name pure check_meta ->
491 let tok = check_meta(Ast.MetaFieldDecl(arity,name)) in
492 !Data.add_field_meta name pure; tok) }
493 | TField Tlist
494 { (fun arity name pure check_meta ->
495 let len = Ast.AnyLen in
496 let tok = check_meta(Ast.MetaFieldListDecl(arity,name,len)) in
497 !Data.add_field_list_meta name len pure; tok) }
498 | TStatement Tlist
499 { (fun arity name pure check_meta ->
500 let tok = check_meta(Ast.MetaStmListDecl(arity,name)) in
501 !Data.add_stmlist_meta name pure; tok) }
502 | TTypedef
503 { (fun arity (_,name) pure check_meta ->
504 if arity = Ast.NONE && pure = Ast0.Impure
505 then (!Data.add_type_name name; [])
506 else raise (Semantic_cocci.Semantic "bad typedef")) }
507 | TDeclarer TName
508 { (fun arity (_,name) pure check_meta ->
509 if arity = Ast.NONE && pure = Ast0.Impure
510 then (!Data.add_declarer_name name; [])
511 else raise (Semantic_cocci.Semantic "bad declarer")) }
512 | TIterator TName
513 { (fun arity (_,name) pure check_meta ->
514 if arity = Ast.NONE && pure = Ast0.Impure
515 then (!Data.add_iterator_name name; [])
516 else raise (Semantic_cocci.Semantic "bad iterator")) }
517
518 %inline metakind_atomic_maybe_virt:
519 TIdentifier
520 {
521 let idfn arity name pure check_meta constraints =
522 let tok = check_meta(Ast.MetaIdDecl(arity,name)) in
523 !Data.add_id_meta name constraints pure; tok in
524 let virtfn arity name pure check_meta virtual_env =
525 try
526 let vl = List.assoc name virtual_env in
527 !Data.add_virt_id_meta_found name vl; []
528 with Not_found ->
529 Iteration.parsed_virtual_identifiers :=
530 Common.union_set [name]
531 !Iteration.parsed_virtual_identifiers;
532 let name = ("virtual",name) in
533 let tok = check_meta(Ast.MetaIdDecl(arity,name)) in
534 !Data.add_virt_id_meta_not_found name pure; tok in
535 (idfn,virtfn) }
536
537 %inline metakind_atomic:
538 TFunction
539 { (fun arity name pure check_meta constraints ->
540 let tok = check_meta(Ast.MetaFuncDecl(arity,name)) in
541 !Data.add_func_meta name constraints pure; tok) }
542 | TLocal TFunction
543 { (fun arity name pure check_meta constraints ->
544 let tok = check_meta(Ast.MetaLocalFuncDecl(arity,name)) in
545 !Data.add_local_func_meta name constraints pure;
546 tok) }
547 | TDeclarer
548 { (fun arity name pure check_meta constraints ->
549 let tok = check_meta(Ast.MetaDeclarerDecl(arity,name)) in
550 !Data.add_declarer_meta name constraints pure; tok) }
551 | TIterator
552 { (fun arity name pure check_meta constraints ->
553 let tok = check_meta(Ast.MetaIteratorDecl(arity,name)) in
554 !Data.add_iterator_meta name constraints pure; tok) }
555
556 %inline metakind_atomic_expi:
557 TError
558 { (fun arity name pure check_meta constraints ->
559 let tok = check_meta(Ast.MetaErrDecl(arity,name)) in
560 !Data.add_err_meta name constraints pure; tok) }
561 | l=option(TLocal) TIdExpression ty=ioption(meta_exp_type)
562 { (fun arity name pure check_meta constraints ->
563 match l with
564 None ->
565 !Data.add_idexp_meta ty name constraints pure;
566 check_meta(Ast.MetaIdExpDecl(arity,name,ty))
567 | Some _ ->
568 !Data.add_local_idexp_meta ty name constraints pure;
569 check_meta(Ast.MetaLocalIdExpDecl(arity,name,ty))) }
570 | l=option(TLocal) TIdExpression m=nonempty_list(TMul)
571 { (fun arity name pure check_meta constraints ->
572 let ty = Some [P.ty_pointerify Type_cocci.Unknown m] in
573 match l with
574 None ->
575 !Data.add_idexp_meta ty name constraints pure;
576 check_meta(Ast.MetaIdExpDecl(arity,name,ty))
577 | Some _ ->
578 !Data.add_local_idexp_meta ty name constraints pure;
579 check_meta(Ast.MetaLocalIdExpDecl(arity,name,ty))) }
580 | TExpression ty=expression_type
581 { (fun arity name pure check_meta constraints ->
582 let ty = Some [ty] in
583 let tok = check_meta(Ast.MetaExpDecl(arity,name,ty)) in
584 !Data.add_exp_meta ty name constraints pure; tok) }
585 | TConstant ty=ioption(meta_exp_type)
586 { (fun arity name pure check_meta constraints ->
587 let tok = check_meta(Ast.MetaConstDecl(arity,name,ty)) in
588 !Data.add_const_meta ty name constraints pure; tok) }
589
590 expression_type:
591 m=nonempty_list(TMul) { P.ty_pointerify Type_cocci.Unknown m }
592 | Tenum m=list(TMul)
593 { P.ty_pointerify (Type_cocci.EnumName Type_cocci.NoName) m }
594 | Tstruct m=list(TMul)
595 { P.ty_pointerify
596 (Type_cocci.StructUnionName (Type_cocci.Struct,Type_cocci.NoName)) m }
597 | Tunion m=list(TMul)
598 { P.ty_pointerify
599 (Type_cocci.StructUnionName (Type_cocci.Union,Type_cocci.NoName)) m }
600
601 %inline
602 metakind_atomic_expe:
603 TExpression
604 { (fun arity name pure check_meta constraints ->
605 let tok = check_meta(Ast.MetaExpDecl(arity,name,None)) in
606 !Data.add_exp_meta None name constraints pure; tok) }
607 | vl=meta_exp_type // no error if use $1 but doesn't type check
608 { (fun arity name pure check_meta constraints ->
609 let ty = Some vl in
610 (match constraints with
611 Ast0.NotExpCstrt constraints ->
612 List.iter
613 (function c ->
614 match Ast0.unwrap c with
615 Ast0.Constant(_) ->
616 if not
617 (List.exists
618 (function
619 Type_cocci.BaseType(Type_cocci.IntType) -> true
620 | Type_cocci.BaseType(Type_cocci.ShortType) -> true
621 | Type_cocci.BaseType(Type_cocci.LongType) -> true
622 | _ -> false)
623 vl)
624 then
625 failwith "metavariable with int constraint must be an int"
626 | _ -> ())
627 constraints
628 | _ -> ());
629 let tok = check_meta(Ast.MetaExpDecl(arity,name,ty)) in
630 !Data.add_exp_meta ty name constraints pure; tok)
631 }
632
633 meta_exp_type:
634 t=typedef_ctype
635 { [Ast0_cocci.ast0_type_to_type t] }
636 | t=typedef_ctype TOCro TCCro
637 { [Type_cocci.Array (Ast0_cocci.ast0_type_to_type t)] }
638 | TOBrace t=comma_list(ctype) TCBrace m=list(TMul)
639 { List.map
640 (function x -> P.ty_pointerify (Ast0_cocci.ast0_type_to_type x) m)
641 t }
642
643 arity: TBang0 { Ast.UNIQUE }
644 | TWhy0 { Ast.OPT }
645 | TPlus0 { Ast.MULTI }
646 | /* empty */ { Ast.NONE }
647
648 /* ---------------------------------------------------------------------- */
649
650 signable_types:
651 ty=Tchar
652 { Ast0.wrap(Ast0.BaseType(Ast.CharType,[P.clt2mcode "char" ty])) }
653 | ty=Tshort
654 { Ast0.wrap(Ast0.BaseType(Ast.ShortType,[P.clt2mcode "short" ty])) }
655 | ty1=Tshort ty2=Tint
656 { Ast0.wrap
657 (Ast0.BaseType
658 (Ast.ShortIntType,[P.clt2mcode "short" ty1;P.clt2mcode "int" ty2])) }
659 | ty=Tint
660 { Ast0.wrap(Ast0.BaseType(Ast.IntType,[P.clt2mcode "int" ty])) }
661 | p=TMetaType
662 { let (nm,pure,clt) = p in
663 Ast0.wrap(Ast0.MetaType(P.clt2mcode nm clt,pure)) }
664 | r=TRuleName TDot p=TIdent
665 { let nm = (r,P.id2name p) in
666 (* this is only possible when we are in a metavar decl. Otherwise,
667 it will be represented already as a MetaType *)
668 let _ = P.check_meta(Ast.MetaTypeDecl(Ast.NONE,nm)) in
669 Ast0.wrap(Ast0.MetaType(P.clt2mcode nm (P.id2clt p),
670 Ast0.Impure (*will be ignored*))) }
671 | ty1=Tlong
672 { Ast0.wrap(Ast0.BaseType(Ast.LongType,[P.clt2mcode "long" ty1])) }
673 | ty1=Tlong ty2=Tint
674 { Ast0.wrap
675 (Ast0.BaseType
676 (Ast.LongIntType,[P.clt2mcode "long" ty1;P.clt2mcode "int" ty2])) }
677 | ty1=Tlong ty2=Tlong
678 { Ast0.wrap
679 (Ast0.BaseType
680 (Ast.LongLongType,
681 [P.clt2mcode "long" ty1;P.clt2mcode "long" ty2])) }
682 | ty1=Tlong ty2=Tlong ty3=Tint
683 { Ast0.wrap
684 (Ast0.BaseType
685 (Ast.LongLongIntType,
686 [P.clt2mcode "long" ty1;P.clt2mcode "long" ty2;
687 P.clt2mcode "int" ty3])) }
688
689 non_signable_types:
690 ty=Tvoid
691 { Ast0.wrap(Ast0.BaseType(Ast.VoidType,[P.clt2mcode "void" ty])) }
692 | ty1=Tlong ty2=Tdouble
693 { Ast0.wrap
694 (Ast0.BaseType
695 (Ast.LongDoubleType,
696 [P.clt2mcode "long" ty1;P.clt2mcode "double" ty2])) }
697 | ty=Tdouble
698 { Ast0.wrap(Ast0.BaseType(Ast.DoubleType,[P.clt2mcode "double" ty])) }
699 | ty=Tfloat
700 { Ast0.wrap(Ast0.BaseType(Ast.FloatType,[P.clt2mcode "float" ty])) }
701 | ty=Tsize_t
702 { Ast0.wrap(Ast0.BaseType(Ast.SizeType,[P.clt2mcode "size_t" ty])) }
703 | ty=Tssize_t
704 { Ast0.wrap(Ast0.BaseType(Ast.SSizeType,[P.clt2mcode "ssize_t" ty])) }
705 | ty=Tptrdiff_t
706 { Ast0.wrap(Ast0.BaseType(Ast.PtrDiffType,[P.clt2mcode "ptrdiff_t" ty])) }
707 | s=Tenum i=ident
708 { Ast0.wrap(Ast0.EnumName(P.clt2mcode "enum" s, Some i)) }
709 | s=Tenum i=ioption(ident) l=TOBrace ids=enum_decl_list r=TCBrace
710 { (if i = None && !Data.in_iso
711 then failwith "enums must be named in the iso file");
712 Ast0.wrap(Ast0.EnumDef(Ast0.wrap(Ast0.EnumName(P.clt2mcode "enum" s, i)),
713 P.clt2mcode "{" l, ids, P.clt2mcode "}" r)) }
714 | s=struct_or_union i=type_ident // allow typedef name
715 { Ast0.wrap(Ast0.StructUnionName(s, Some i)) }
716 | s=struct_or_union i=ioption(type_ident)
717 l=TOBrace d=struct_decl_list r=TCBrace
718 { (if i = None && !Data.in_iso
719 then failwith "structures must be named in the iso file");
720 Ast0.wrap(Ast0.StructUnionDef(Ast0.wrap(Ast0.StructUnionName(s, i)),
721 P.clt2mcode "{" l,
722 d, P.clt2mcode "}" r)) }
723 | s=TMetaType l=TOBrace d=struct_decl_list r=TCBrace
724 { let (nm,pure,clt) = s in
725 let ty = Ast0.wrap(Ast0.MetaType(P.clt2mcode nm clt,pure)) in
726 Ast0.wrap(Ast0.StructUnionDef(ty,P.clt2mcode "{" l,d,P.clt2mcode "}" r)) }
727 | p=TTypeId
728 { Ast0.wrap(Ast0.TypeName(P.id2mcode p)) }
729
730 all_basic_types:
731 r=Tsigned ty=signable_types
732 { Ast0.wrap(Ast0.Signed(P.clt2mcode Ast.Signed r,Some ty)) }
733 | r=Tunsigned ty=signable_types
734 { Ast0.wrap(Ast0.Signed(P.clt2mcode Ast.Unsigned r,Some ty)) }
735 | ty=signable_types { ty }
736 | ty=non_signable_types { ty }
737
738 ctype:
739 cv=ioption(const_vol) ty=all_basic_types m=list(mul)
740 { List.fold_left
741 (function prev ->
742 function (star,cv) ->
743 P.make_cv cv (P.pointerify prev [star]))
744 (P.make_cv cv ty) m }
745 | r=Tsigned
746 { Ast0.wrap(Ast0.Signed(P.clt2mcode Ast.Signed r,None)) }
747 | r=Tunsigned
748 { Ast0.wrap(Ast0.Signed(P.clt2mcode Ast.Unsigned r,None)) }
749 | lp=TOPar0 t=midzero_list(ctype,ctype) rp=TCPar0
750 { let (mids,code) = t in
751 Ast0.wrap
752 (Ast0.DisjType(P.clt2mcode "(" lp,code,mids, P.clt2mcode ")" rp)) }
753
754 mul: a=TMul b=ioption(const_vol) { (a,b) }
755
756 mctype:
757 | TMeta { tmeta_to_type $1 }
758 | ctype {$1}
759
760 /* signed, unsigned alone not allowed */
761 typedef_ctype:
762 cv=ioption(const_vol) ty=all_basic_types m=list(TMul)
763 { P.pointerify (P.make_cv cv ty) m }
764 | lp=TOPar0 t=midzero_list(mctype,mctype) rp=TCPar0
765 { let (mids,code) = t in
766 Ast0.wrap
767 (Ast0.DisjType(P.clt2mcode "(" lp,code,mids, P.clt2mcode ")" rp)) }
768 | TMeta { tmeta_to_type $1 }
769
770 /* ---------------------------------------------------------------------- */
771
772 struct_or_union:
773 s=Tstruct { P.clt2mcode Ast.Struct s }
774 | u=Tunion { P.clt2mcode Ast.Union u }
775
776 struct_decl:
777 TNothing { [] }
778 | struct_decl_one { [$1] }
779
780 struct_decl_one:
781 | TMetaField { P.meta_field $1 }
782 | TMetaFieldList { P.meta_field_list $1 }
783 | TMeta { tmeta_to_field $1 }
784 | lp=TOPar0 t=midzero_list(struct_decl_one,struct_decl_one) rp=TCPar0
785 { let (mids,code) = t in
786 Ast0.wrap
787 (Ast0.DisjDecl(P.clt2mcode "(" lp,code,mids, P.clt2mcode ")" rp)) }
788 | t=ctype d=d_ident pv=TPtVirg
789 { let (id,fn) = d in
790 Ast0.wrap(Ast0.UnInit(None,fn t,id,P.clt2mcode ";" pv)) }
791 | t=ctype lp1=TOPar st=TMul d=d_ident rp1=TCPar
792 lp2=TOPar p=decl_list(name_opt_decl) rp2=TCPar pv=TPtVirg
793 { let (id,fn) = d in
794 let t =
795 Ast0.wrap
796 (Ast0.FunctionPointer
797 (t,P.clt2mcode "(" lp1,P.clt2mcode "*" st,P.clt2mcode ")" rp1,
798 P.clt2mcode "(" lp2,p,P.clt2mcode ")" rp2)) in
799 Ast0.wrap(Ast0.UnInit(None,fn t,id,P.clt2mcode ";" pv)) }
800 | cv=ioption(const_vol) i=pure_ident_or_symbol d=d_ident pv=TPtVirg
801 { let (id,fn) = d in
802 let idtype = P.make_cv cv (Ast0.wrap (Ast0.TypeName(P.id2mcode i))) in
803 Ast0.wrap(Ast0.UnInit(None,fn idtype,id,P.clt2mcode ";" pv)) }
804
805 struct_decl_list:
806 struct_decl_list_start { Ast0.wrap(Ast0.DOTS($1)) }
807
808 struct_decl_list_start:
809 struct_decl { $1 }
810 | struct_decl struct_decl_list_start { $1@$2 }
811 | d=edots_when(TEllipsis,struct_decl_one) r=continue_struct_decl_list
812 { (P.mkddots_one "..." d)::r }
813
814 continue_struct_decl_list:
815 /* empty */ { [] }
816 | struct_decl struct_decl_list_start { $1@$2 }
817 | struct_decl { $1 }
818
819
820 /* ---------------------------------------------------------------------- */
821 /* very restricted what kinds of expressions can appear in an enum decl */
822
823 enum_decl_one:
824 | disj_ident { Ast0.wrap(Ast0.Ident($1)) }
825 | disj_ident TEq enum_val
826 { let id = Ast0.wrap(Ast0.Ident($1)) in
827 Ast0.wrap
828 (Ast0.Assignment
829 (id,P.clt2mcode Ast.SimpleAssign $2,Ast0.set_arg_exp $3,
830 false)) }
831
832 enum_val:
833 ident { Ast0.wrap(Ast0.Ident($1)) }
834 | TInt
835 { let (x,clt) = $1 in
836 Ast0.wrap(Ast0.Constant (P.clt2mcode (Ast.Int x) clt)) }
837 | TMeta { tmeta_to_exp $1 }
838 | TMetaConst
839 { let (nm,constraints,pure,ty,clt) = $1 in
840 Ast0.wrap
841 (Ast0.MetaExpr(P.clt2mcode nm clt,constraints,ty,Ast.CONST,pure)) }
842 | TMetaExp
843 { let (nm,constraints,pure,ty,clt) = $1 in
844 Ast0.wrap
845 (Ast0.MetaExpr(P.clt2mcode nm clt,constraints,ty,Ast.ANY,pure)) }
846 | TMetaIdExp
847 { let (nm,constraints,pure,ty,clt) = $1 in
848 Ast0.wrap
849 (Ast0.MetaExpr(P.clt2mcode nm clt,constraints,ty,Ast.ID,pure)) }
850
851 enum_decl_list:
852 nonempty_list_start(enum_decl_one,edots_when(TEllipsis,enum_decl_one))
853 { Ast0.wrap(Ast0.DOTS($1 P.mkedots (fun c -> Ast0.EComma c))) }
854
855 /*****************************************************************************/
856
857 /* have to inline everything to avoid conflicts? switch to proper
858 declarations, statements, and expressions for the subterms */
859
860 minus_body:
861 f=loption(filespec)
862 b=loption(minus_start)
863 /*ew=loption(error_words)*/
864 { match f@b(*@ew*) with
865 [] -> raise (Semantic_cocci.Semantic "minus slice can't be empty")
866 | code -> code }
867
868 plus_body:
869 f=loption(filespec)
870 b=loption(plus_start)
871 /*ew=loption(error_words)*/
872 { f@b(*@ew*) }
873
874 minus_exp_body:
875 f=loption(filespec)
876 b=top_eexpr
877 /*ew=loption(error_words)*/
878 { match f@[b](*@ew*) with
879 [] -> raise (Semantic_cocci.Semantic "minus slice can't be empty")
880 | code -> code }
881
882 plus_exp_body:
883 f=loption(filespec)
884 b=top_eexpr
885 /*ew=loption(error_words)*/
886 { f@[b](*@ew*) }
887
888 filespec:
889 TMinusFile TPlusFile
890 { [Ast0.wrap
891 (Ast0.FILEINFO(P.id2mcode $1,
892 P.id2mcode $2))] }
893
894 includes:
895 TIncludeL
896 { Ast0.wrap
897 (Ast0.Include(P.clt2mcode "#include"
898 (P.drop_pos (P.drop_aft (P.id2clt $1))),
899 let (arity,ln,lln,offset,col,strbef,straft,pos) =
900 P.id2clt $1 in
901 let clt =
902 (arity,ln,lln,offset,0,strbef,straft,pos) in
903 P.clt2mcode
904 (Ast.Local (Parse_aux.str2inc (P.id2name $1)))
905 (P.drop_bef clt))) }
906 | TIncludeNL
907 { Ast0.wrap
908 (Ast0.Include(P.clt2mcode "#include"
909 (P.drop_pos (P.drop_aft (P.id2clt $1))),
910 let (arity,ln,lln,offset,col,strbef,straft,pos) =
911 P.id2clt $1 in
912 let clt =
913 (arity,ln,lln,offset,0,strbef,straft,pos) in
914 P.clt2mcode
915 (Ast.NonLocal (Parse_aux.str2inc (P.id2name $1)))
916 (P.drop_bef clt))) }
917 | TUndef TLineEnd
918 { let (clt,ident) = $1 in
919 let aft = P.get_aft clt in (* move stuff after the define to the ident *)
920 Ast0.wrap
921 (Ast0.Undef
922 (P.clt2mcode "#undef" (P.drop_aft clt),
923 (match ident with
924 TMetaId((nm,constraints,seed,pure,clt)) ->
925 let clt = P.set_aft aft clt in
926 Ast0.wrap(Ast0.MetaId(P.clt2mcode nm clt,constraints,seed,pure))
927 | TIdent((nm,clt)) ->
928 let clt = P.set_aft aft clt in
929 Ast0.wrap(Ast0.Id(P.clt2mcode nm clt))
930 | TSymId(nm,clt) ->
931 let clt = P.set_aft aft clt in
932 Ast0.wrap(Ast0.Id(P.clt2mcode nm clt))
933 | _ ->
934 raise
935 (Semantic_cocci.Semantic
936 "unexpected name for a #define")))) }
937 | d=defineop TLineEnd
938 { d (Ast0.wrap(Ast0.DOTS([]))) }
939 | d=defineop t=ctype TLineEnd
940 { let ty = Ast0.wrap(Ast0.TopExp(Ast0.wrap(Ast0.TypeExp(t)))) in
941 d (Ast0.wrap(Ast0.DOTS([ty]))) }
942 | defineop b=toplevel_seq_start(toplevel_after_dots) TLineEnd
943 { let body =
944 match b with
945 [e] ->
946 (match Ast0.unwrap e with
947 Ast0.Exp(e1) ->
948 [Ast0.rewrap e (Ast0.TopExp(Ast0.set_arg_exp (e1)))]
949 | _ -> b)
950 | _ -> b in
951 $1 (Ast0.wrap(Ast0.DOTS(body))) }
952
953 defineop:
954 TDefine
955 { let (clt,ident) = $1 in
956 let aft = P.get_aft clt in (* move stuff after the define to the ident *)
957 function body ->
958 Ast0.wrap
959 (Ast0.Define
960 (P.clt2mcode "#define" (P.drop_aft clt),
961 (match ident with
962 TMetaId((nm,constraints,seed,pure,clt)) ->
963 let clt = P.set_aft aft clt in
964 Ast0.wrap
965 (Ast0.MetaId(P.clt2mcode nm clt,constraints,seed,pure))
966 | TIdent((nm,clt)) ->
967 let clt = P.set_aft aft clt in
968 Ast0.wrap(Ast0.Id(P.clt2mcode nm clt))
969 | TSymId(nm,clt) ->
970 let clt = P.set_aft aft clt in
971 Ast0.wrap(Ast0.Id(P.clt2mcode nm clt))
972 | _ ->
973 raise
974 (Semantic_cocci.Semantic
975 "unexpected name for a #define")),
976 Ast0.wrap Ast0.NoParams,
977 body)) }
978 | TDefineParam define_param_list_option TCPar
979 { let (clt,ident,parenoff,parencol) = $1 in
980 let aft = P.get_aft clt in (* move stuff after the define to the ( *)
981 (* clt is the start of the #define itself *)
982 let (arity,line,lline,offset,col,strbef,straft,pos) = clt in
983 let lp =
984 P.clt2mcode "("
985 (arity,line,lline,parenoff,parencol,[],[],[]) in
986 function body ->
987 Ast0.wrap
988 (Ast0.Define
989 (P.clt2mcode "#define" (P.drop_aft clt),
990 (match ident with
991 TMetaId((nm,constraints,seed,pure,clt)) ->
992 Ast0.wrap
993 (Ast0.MetaId(P.clt2mcode nm clt,constraints,seed,pure))
994 | TIdent((nm,clt)) ->
995 Ast0.wrap(Ast0.Id(P.clt2mcode nm clt))
996 | TSymId(nm,clt) ->
997 Ast0.wrap(Ast0.Id(P.clt2mcode nm clt))
998 | _ ->
999 raise
1000 (Semantic_cocci.Semantic
1001 "unexpected name for a #define")),
1002 (let clt = P.set_aft aft $3 in
1003 Ast0.wrap (Ast0.DParams (lp,$2,P.clt2mcode ")" clt))),body)) }
1004
1005 /* ---------------------------------------------------------------------- */
1006
1007 dparam: mident { Ast0.wrap(Ast0.DParam $1) }
1008
1009 define_param_list_option:
1010 empty_list_start(dparam,TEllipsis)
1011 { Ast0.wrap
1012 (Ast0.DOTS
1013 ($1
1014 (fun _ d -> Ast0.wrap(Ast0.DPdots(P.clt2mcode "," d)))
1015 (fun c -> Ast0.DPComma c))) }
1016
1017 /*****************************************************************************/
1018
1019 funproto:
1020 s=ioption(storage) t=ctype
1021 id=fn_ident lp=TOPar d=decl_list(name_opt_decl) rp=TCPar pt=TPtVirg
1022 { Ast0.wrap
1023 (Ast0.UnInit
1024 (s,
1025 Ast0.wrap
1026 (Ast0.FunctionType(Some t,
1027 P.clt2mcode "(" lp, d, P.clt2mcode ")" rp)),
1028 id, P.clt2mcode ";" pt)) }
1029
1030 fundecl:
1031 f=fninfo
1032 TFunDecl i=fn_ident lp=TOPar d=decl_list(decl) rp=TCPar
1033 lb=TOBrace b=fun_start rb=TCBrace
1034 { P.verify_parameter_declarations (Ast0.undots d);
1035 Ast0.wrap(Ast0.FunDecl((Ast0.default_info(),Ast0.context_befaft()),
1036 f, i,
1037 P.clt2mcode "(" lp, d,
1038 P.clt2mcode ")" rp,
1039 P.clt2mcode "{" lb, b,
1040 P.clt2mcode "}" rb)) }
1041
1042 fninfo:
1043 /* empty */ { [] }
1044 | storage fninfo
1045 { try
1046 let _ =
1047 List.find (function Ast0.FStorage(_) -> true | _ -> false) $2 in
1048 raise (Semantic_cocci.Semantic "duplicate storage")
1049 with Not_found -> (Ast0.FStorage($1))::$2 }
1050 | t=ctype r=fninfo_nt { (Ast0.FType(t))::r }
1051 | Tinline fninfo
1052 { try
1053 let _ = List.find (function Ast0.FInline(_) -> true | _ -> false) $2 in
1054 raise (Semantic_cocci.Semantic "duplicate inline")
1055 with Not_found -> (Ast0.FInline(P.clt2mcode "inline" $1))::$2 }
1056 | Tattr fninfo
1057 { try
1058 let _ = List.find (function Ast0.FAttr(_) -> true | _ -> false) $2 in
1059 raise (Semantic_cocci.Semantic "multiple attributes")
1060 with Not_found -> (Ast0.FAttr(P.id2mcode $1))::$2 }
1061
1062 fninfo_nt:
1063 /* empty */ { [] }
1064 | storage fninfo_nt
1065 { try
1066 let _ =
1067 List.find (function Ast0.FStorage(_) -> true | _ -> false) $2 in
1068 raise (Semantic_cocci.Semantic "duplicate storage")
1069 with Not_found -> (Ast0.FStorage($1))::$2 }
1070 | Tinline fninfo_nt
1071 { try
1072 let _ = List.find (function Ast0.FInline(_) -> true | _ -> false) $2 in
1073 raise (Semantic_cocci.Semantic "duplicate inline")
1074 with Not_found -> (Ast0.FInline(P.clt2mcode "inline" $1))::$2 }
1075 | Tattr fninfo_nt
1076 { try
1077 let _ = List.find (function Ast0.FAttr(_) -> true | _ -> false) $2 in
1078 raise (Semantic_cocci.Semantic "duplicate init")
1079 with Not_found -> (Ast0.FAttr(P.id2mcode $1))::$2 }
1080
1081 storage:
1082 s=Tstatic { P.clt2mcode Ast.Static s }
1083 | s=Tauto { P.clt2mcode Ast.Auto s }
1084 | s=Tregister { P.clt2mcode Ast.Register s }
1085 | s=Textern { P.clt2mcode Ast.Extern s }
1086
1087 decl: t=ctype i=disj_ident a=list(array_dec)
1088 { let t = P.arrayify t a in Ast0.wrap(Ast0.Param(t, Some i)) }
1089 | t=ctype { (*verify in FunDecl*) Ast0.wrap(Ast0.Param(t, None)) }
1090 | t=ctype lp=TOPar s=TMul i=disj_ident rp=TCPar
1091 lp1=TOPar d=decl_list(name_opt_decl) rp1=TCPar
1092 { let fnptr =
1093 Ast0.wrap
1094 (Ast0.FunctionPointer
1095 (t,P.clt2mcode "(" lp,P.clt2mcode "*" s,P.clt2mcode ")" rp,
1096 P.clt2mcode "(" lp1,d,P.clt2mcode ")" rp1)) in
1097 Ast0.wrap(Ast0.Param(fnptr, Some i)) }
1098 | TMetaParam
1099 { let (nm,pure,clt) = $1 in
1100 Ast0.wrap(Ast0.MetaParam(P.clt2mcode nm clt,pure)) }
1101 | TMeta { tmeta_to_param $1 }
1102
1103 name_opt_decl:
1104 decl { $1 }
1105 | t=ctype lp=TOPar s=TMul rp=TCPar
1106 lp1=TOPar d=decl_list(name_opt_decl) rp1=TCPar
1107 { let fnptr =
1108 Ast0.wrap
1109 (Ast0.FunctionPointer
1110 (t,P.clt2mcode "(" lp,P.clt2mcode "*" s,P.clt2mcode ")" rp,
1111 P.clt2mcode "(" lp1,d,P.clt2mcode ")" rp1)) in
1112 Ast0.wrap(Ast0.Param(fnptr, None)) }
1113
1114 const_vol:
1115 Tconst { P.clt2mcode Ast.Const $1 }
1116 | Tvolatile { P.clt2mcode Ast.Volatile $1 }
1117
1118 /*****************************************************************************/
1119
1120 statement:
1121 includes { $1 } /* shouldn't be allowed to be a single_statement... */
1122 | TMeta { tmeta_to_statement $1}
1123 | TMetaStm
1124 { P.meta_stm $1 }
1125 | option(expr) TPtVirg
1126 { P.exp_stm $1 $2 }
1127 | TIf TOPar eexpr TCPar single_statement %prec TIf
1128 { P.ifthen $1 $2 $3 $4 $5 }
1129 | TIf TOPar eexpr TCPar single_statement TElse single_statement
1130 { P.ifthenelse $1 $2 $3 $4 $5 $6 $7 }
1131 | TFor TOPar option(eexpr) TPtVirg option(eexpr) TPtVirg
1132 option(eexpr) TCPar single_statement
1133 { P.forloop $1 $2 $3 $4 $5 $6 $7 $8 $9 }
1134 | TFor TOPar one_decl_var option(eexpr) TPtVirg
1135 option(eexpr) TCPar single_statement
1136 { P.forloop2 $1 $2 $3 $4 $5 $6 $7 $8 }
1137 | TWhile TOPar eexpr TCPar single_statement
1138 { P.whileloop $1 $2 $3 $4 $5 }
1139 | TDo single_statement TWhile TOPar eexpr TCPar TPtVirg
1140 { P.doloop $1 $2 $3 $4 $5 $6 $7 }
1141 | iter_ident TOPar eexpr_list_option TCPar single_statement
1142 { P.iterator $1 $2 $3 $4 $5 }
1143 | TSwitch TOPar eexpr TCPar TOBrace list(decl_var) list(case_line) TCBrace
1144 { P.switch $1 $2 $3 $4 $5 (List.concat $6) $7 $8 }
1145 | TReturn eexpr TPtVirg { P.ret_exp $1 $2 $3 }
1146 | TReturn TPtVirg { P.ret $1 $2 }
1147 | TBreak TPtVirg { P.break $1 $2 }
1148 | TContinue TPtVirg { P.cont $1 $2 }
1149 | mident TDotDot { P.label $1 $2 }
1150 | TGoto disj_ident TPtVirg { P.goto $1 $2 $3 }
1151 | TOBrace fun_start TCBrace
1152 { P.seq $1 $2 $3 }
1153
1154 stm_dots:
1155 TEllipsis w=list(whenppdecs)
1156 { Ast0.wrap(Ast0.Dots(P.clt2mcode "..." $1, List.concat w)) }
1157 | TOEllipsis w=list(whenppdecs) b=nest_start c=TCEllipsis
1158 { Ast0.wrap(Ast0.Nest(P.clt2mcode "<..." $1, b,
1159 P.clt2mcode "...>" c, List.concat w, false)) }
1160 | TPOEllipsis w=list(whenppdecs) b=nest_start c=TPCEllipsis
1161 { Ast0.wrap(Ast0.Nest(P.clt2mcode "<+..." $1, b,
1162 P.clt2mcode "...+>" c, List.concat w, true)) }
1163
1164 %inline stm_dots_ell:
1165 a=TEllipsis w=list(whenppdecs)
1166 { Ast0.wrap(Ast0.Dots(P.clt2mcode "..." a, List.concat w)) }
1167
1168 %inline stm_dots_nest:
1169 a=TOEllipsis w=list(whenppdecs) b=nest_start c=TCEllipsis
1170 { Ast0.wrap(Ast0.Nest(P.clt2mcode "<..." a, b,
1171 P.clt2mcode "...>" c, List.concat w, false)) }
1172 | a=TPOEllipsis w=list(whenppdecs) b=nest_start c=TPCEllipsis
1173 { Ast0.wrap(Ast0.Nest(P.clt2mcode "<+..." a, b,
1174 P.clt2mcode "...+>" c, List.concat w, true)) }
1175
1176 whenppdecs: w=whens(when_start,rule_elem_statement,any_strict)
1177 { w }
1178
1179 /* a statement that fits into a single rule_elem. should nests be included?
1180 what about statement metavariables? */
1181 rule_elem_statement:
1182 one_decl_var
1183 { Ast0.wrap(Ast0.Decl((Ast0.default_info(),Ast0.context_befaft()),$1)) }
1184 | option(expr) TPtVirg { P.exp_stm $1 $2 }
1185 | TReturn eexpr TPtVirg { P.ret_exp $1 $2 $3 }
1186 | TReturn TPtVirg { P.ret $1 $2 }
1187 | TBreak TPtVirg { P.break $1 $2 }
1188 | TContinue TPtVirg { P.cont $1 $2 }
1189 | TOPar0 midzero_list(rule_elem_statement,rule_elem_statement) TCPar0
1190 { let (mids,code) = $2 in
1191 Ast0.wrap
1192 (Ast0.Disj(P.clt2mcode "(" $1,
1193 List.map (function x -> Ast0.wrap(Ast0.DOTS([x]))) code,
1194 mids, P.clt2mcode ")" $3)) }
1195
1196 /* a statement on its own */
1197 single_statement:
1198 statement { $1 }
1199 | TOPar0 midzero_list(statement,statement) TCPar0
1200 /* degenerate case, elements are single statements and thus don't
1201 contain dots */
1202 { let (mids,code) = $2 in
1203 Ast0.wrap
1204 (Ast0.Disj(P.clt2mcode "(" $1,
1205 List.map (function x -> Ast0.wrap(Ast0.DOTS([x]))) code,
1206 mids, P.clt2mcode ")" $3)) }
1207
1208 iso_statement: /* statement or declaration used in statement context */
1209 statement { $1 }
1210 | decl_var
1211 { match $1 with
1212 [decl] ->
1213 Ast0.wrap
1214 (Ast0.Decl((Ast0.default_info(),Ast0.context_befaft()),decl))
1215 | _ -> failwith "exactly one decl allowed in statement iso" }
1216
1217 case_line:
1218 TDefault TDotDot fun_start
1219 { Ast0.wrap
1220 (Ast0.Default(P.clt2mcode "default" $1,P.clt2mcode ":" $2,$3)) }
1221 | TCase eexpr TDotDot fun_start
1222 { Ast0.wrap(Ast0.Case(P.clt2mcode "case" $1,$2,P.clt2mcode ":" $3,$4)) }
1223 /* | lp=TOPar0 t=midzero_list(case_line,case_line) rp=TCPar0
1224 { let (mids,code) = ([],[t]) in
1225 Ast0.wrap
1226 (Ast0.DisjCase(P.clt2mcode "(" lp,code,mids, P.clt2mcode ")" rp)) } */
1227
1228 /* In the following, an identifier as a type is not fully supported. Indeed,
1229 the language is ambiguous: what is foo * bar; */
1230 /* The AST DisjDecl cannot be generated because it would be ambiguous with
1231 a disjunction on a statement with a declaration in each branch */
1232 decl_var:
1233 t=ctype pv=TPtVirg
1234 { [Ast0.wrap(Ast0.TyDecl(t,P.clt2mcode ";" pv))] }
1235 | TMetaDecl { [P.meta_decl $1] }
1236 | s=ioption(storage) t=ctype d=comma_list(d_ident) pv=TPtVirg
1237 { List.map
1238 (function (id,fn) ->
1239 Ast0.wrap(Ast0.UnInit(s,fn t,id,P.clt2mcode ";" pv)))
1240 d }
1241 | f=funproto { [f] }
1242 | s=ioption(storage) t=ctype d=d_ident q=TEq e=initialize pv=TPtVirg
1243 {let (id,fn) = d in
1244 [Ast0.wrap(Ast0.Init(s,fn t,id,P.clt2mcode "=" q,e,P.clt2mcode ";" pv))]}
1245 /* type is a typedef name */
1246 | s=ioption(storage) cv=ioption(const_vol) i=pure_ident_or_symbol
1247 d=comma_list(d_ident) pv=TPtVirg
1248 { List.map
1249 (function (id,fn) ->
1250 let idtype =
1251 P.make_cv cv (Ast0.wrap (Ast0.TypeName(P.id2mcode i))) in
1252 Ast0.wrap(Ast0.UnInit(s,fn idtype,id,P.clt2mcode ";" pv)))
1253 d }
1254 | s=ioption(storage) cv=ioption(const_vol) i=pure_ident_or_symbol
1255 d=d_ident q=TEq e=initialize pv=TPtVirg
1256 { let (id,fn) = d in
1257 !Data.add_type_name (P.id2name i);
1258 let idtype = P.make_cv cv (Ast0.wrap (Ast0.TypeName(P.id2mcode i))) in
1259 [Ast0.wrap(Ast0.Init(s,fn idtype,id,P.clt2mcode "=" q,e,
1260 P.clt2mcode ";" pv))] }
1261 /* function pointer type */
1262 | s=ioption(storage)
1263 t=ctype lp1=TOPar st=TMul d=d_ident rp1=TCPar
1264 lp2=TOPar p=decl_list(name_opt_decl) rp2=TCPar
1265 pv=TPtVirg
1266 { let (id,fn) = d in
1267 let t =
1268 Ast0.wrap
1269 (Ast0.FunctionPointer
1270 (t,P.clt2mcode "(" lp1,P.clt2mcode "*" st,P.clt2mcode ")" rp1,
1271 P.clt2mcode "(" lp2,p,P.clt2mcode ")" rp2)) in
1272 [Ast0.wrap(Ast0.UnInit(s,fn t,id,P.clt2mcode ";" pv))] }
1273 | decl_ident TOPar eexpr_list_option TCPar TPtVirg
1274 { [Ast0.wrap(Ast0.MacroDecl($1,P.clt2mcode "(" $2,$3,
1275 P.clt2mcode ")" $4,P.clt2mcode ";" $5))] }
1276 | decl_ident TOPar eexpr_list_option TCPar q=TEq e=initialize TPtVirg
1277 { [Ast0.wrap
1278 (Ast0.MacroDeclInit
1279 ($1,P.clt2mcode "(" $2,$3,
1280 P.clt2mcode ")" $4,P.clt2mcode "=" q,e,
1281 P.clt2mcode ";" $7))] }
1282 | s=ioption(storage)
1283 t=ctype lp1=TOPar st=TMul d=d_ident rp1=TCPar
1284 lp2=TOPar p=decl_list(name_opt_decl) rp2=TCPar
1285 q=TEq e=initialize pv=TPtVirg
1286 { let (id,fn) = d in
1287 let t =
1288 Ast0.wrap
1289 (Ast0.FunctionPointer
1290 (t,P.clt2mcode "(" lp1,P.clt2mcode "*" st,P.clt2mcode ")" rp1,
1291 P.clt2mcode "(" lp2,p,P.clt2mcode ")" rp2)) in
1292 [Ast0.wrap(Ast0.Init(s,fn t,id,P.clt2mcode "=" q,e,P.clt2mcode ";" pv))]}
1293 | s=Ttypedef t=typedef_ctype id=comma_list(typedef_ident) pv=TPtVirg
1294 { let s = P.clt2mcode "typedef" s in
1295 List.map
1296 (function id ->
1297 Ast0.wrap(Ast0.Typedef(s,t,id,P.clt2mcode ";" pv)))
1298 id }
1299
1300 one_decl_var:
1301 t=ctype pv=TPtVirg
1302 { Ast0.wrap(Ast0.TyDecl(t,P.clt2mcode ";" pv)) }
1303 | TMetaDecl { P.meta_decl $1 }
1304 | s=ioption(storage) t=ctype d=d_ident pv=TPtVirg
1305 { let (id,fn) = d in
1306 Ast0.wrap(Ast0.UnInit(s,fn t,id,P.clt2mcode ";" pv)) }
1307 | f=funproto { f }
1308 | s=ioption(storage) t=ctype d=d_ident q=TEq e=initialize pv=TPtVirg
1309 { let (id,fn) = d in
1310 Ast0.wrap(Ast0.Init(s,fn t,id,P.clt2mcode "=" q,e,P.clt2mcode ";" pv)) }
1311 /* type is a typedef name */
1312 | s=ioption(storage) cv=ioption(const_vol) i=pure_ident_or_symbol
1313 d=d_ident pv=TPtVirg
1314 { let (id,fn) = d in
1315 let idtype = P.make_cv cv (Ast0.wrap (Ast0.TypeName(P.id2mcode i))) in
1316 Ast0.wrap(Ast0.UnInit(s,fn idtype,id,P.clt2mcode ";" pv)) }
1317 | s=ioption(storage) cv=ioption(const_vol) i=pure_ident_or_symbol
1318 d=d_ident q=TEq e=initialize pv=TPtVirg
1319 { let (id,fn) = d in
1320 !Data.add_type_name (P.id2name i);
1321 let idtype = P.make_cv cv (Ast0.wrap (Ast0.TypeName(P.id2mcode i))) in
1322 Ast0.wrap(Ast0.Init(s,fn idtype,id,P.clt2mcode "=" q,e,
1323 P.clt2mcode ";" pv)) }
1324 /* function pointer type */
1325 | s=ioption(storage)
1326 t=ctype lp1=TOPar st=TMul d=d_ident rp1=TCPar
1327 lp2=TOPar p=decl_list(name_opt_decl) rp2=TCPar
1328 pv=TPtVirg
1329 { let (id,fn) = d in
1330 let t =
1331 Ast0.wrap
1332 (Ast0.FunctionPointer
1333 (t,P.clt2mcode "(" lp1,P.clt2mcode "*" st,P.clt2mcode ")" rp1,
1334 P.clt2mcode "(" lp2,p,P.clt2mcode ")" rp2)) in
1335 Ast0.wrap(Ast0.UnInit(s,fn t,id,P.clt2mcode ";" pv)) }
1336 | decl_ident TOPar eexpr_list_option TCPar TPtVirg
1337 { Ast0.wrap(Ast0.MacroDecl($1,P.clt2mcode "(" $2,$3,
1338 P.clt2mcode ")" $4,P.clt2mcode ";" $5)) }
1339 | decl_ident TOPar eexpr_list_option TCPar q=TEq e=initialize TPtVirg
1340 { Ast0.wrap
1341 (Ast0.MacroDeclInit
1342 ($1,P.clt2mcode "(" $2,$3,
1343 P.clt2mcode ")" $4,P.clt2mcode "=" q,e,
1344 P.clt2mcode ";" $7)) }
1345 | s=ioption(storage)
1346 t=ctype lp1=TOPar st=TMul d=d_ident rp1=TCPar
1347 lp2=TOPar p=decl_list(name_opt_decl) rp2=TCPar
1348 q=TEq e=initialize pv=TPtVirg
1349 { let (id,fn) = d in
1350 let t =
1351 Ast0.wrap
1352 (Ast0.FunctionPointer
1353 (t,P.clt2mcode "(" lp1,P.clt2mcode "*" st,P.clt2mcode ")" rp1,
1354 P.clt2mcode "(" lp2,p,P.clt2mcode ")" rp2)) in
1355 Ast0.wrap(Ast0.Init(s,fn t,id,P.clt2mcode "=" q,e,P.clt2mcode ";" pv))}
1356
1357
1358 d_ident:
1359 disj_ident list(array_dec)
1360 { ($1, function t -> P.arrayify t $2) }
1361
1362 array_dec: l=TOCro i=option(eexpr) r=TCCro { (l,i,r) }
1363
1364 initialize:
1365 eexpr
1366 { Ast0.wrap(Ast0.InitExpr($1)) }
1367 | TOBrace initialize_list TCBrace
1368 { if P.struct_initializer $2
1369 then
1370 let il = P.drop_dot_commas $2 in
1371 Ast0.wrap(Ast0.InitList(P.clt2mcode "{" $1,il,P.clt2mcode "}" $3,false))
1372 else
1373 Ast0.wrap(Ast0.InitList(P.clt2mcode "{" $1,$2,P.clt2mcode "}" $3,true)) }
1374 | TMetaInit
1375 {let (nm,pure,clt) = $1 in
1376 Ast0.wrap(Ast0.MetaInit(P.clt2mcode nm clt,pure)) }
1377
1378 initialize2:
1379 /*arithexpr and not eexpr because can have ambiguity with comma*/
1380 /*dots and nests probably not allowed at top level, haven't looked into why*/
1381 arith_expr(eexpr,invalid) { Ast0.wrap(Ast0.InitExpr($1)) }
1382 | nest_expressions_only { Ast0.wrap(Ast0.InitExpr($1)) }
1383 | TOBrace initialize_list TCBrace
1384 { if P.struct_initializer $2
1385 then
1386 let il = P.drop_dot_commas $2 in
1387 Ast0.wrap(Ast0.InitList(P.clt2mcode "{" $1,il,P.clt2mcode "}" $3,false))
1388 else
1389 Ast0.wrap(Ast0.InitList(P.clt2mcode "{" $1,$2,P.clt2mcode "}" $3,true)) }
1390 /* gccext:, labeled elements */
1391 | list(designator) TEq initialize2 /*can we have another of these on the rhs?*/
1392 { Ast0.wrap(Ast0.InitGccExt($1,P.clt2mcode "=" $2,$3)) }
1393 | mident TDotDot initialize2
1394 { Ast0.wrap(Ast0.InitGccName($1,P.clt2mcode ":" $2,$3)) } /* in old kernel */
1395 | TMetaInit
1396 {let (nm,pure,clt) = $1 in
1397 Ast0.wrap(Ast0.MetaInit(P.clt2mcode nm clt,pure)) }
1398 | TMetaInitList
1399 {let (nm,lenname,pure,clt) = $1 in
1400 let nm = P.clt2mcode nm clt in
1401 let lenname =
1402 match lenname with
1403 Ast.AnyLen -> Ast0.AnyListLen
1404 | Ast.MetaLen nm -> Ast0.MetaListLen(P.clt2mcode nm clt)
1405 | Ast.CstLen n -> Ast0.CstListLen n in
1406 Ast0.wrap(Ast0.MetaInitList(nm,lenname,pure)) }
1407
1408 designator:
1409 | TDot disj_ident
1410 { Ast0.DesignatorField (P.clt2mcode "." $1,$2) }
1411 | TOCro eexpr TCCro
1412 { Ast0.DesignatorIndex (P.clt2mcode "[" $1,$2,P.clt2mcode "]" $3) }
1413 | TOCro eexpr TEllipsis eexpr TCCro
1414 { Ast0.DesignatorRange (P.clt2mcode "[" $1,$2,P.clt2mcode "..." $3,
1415 $4,P.clt2mcode "]" $5) }
1416
1417 initialize_list:
1418 empty_list_start(initialize2,edots_when(TEllipsis,initialize))
1419 { Ast0.wrap(Ast0.DOTS($1 P.mkidots (fun c -> Ast0.IComma c))) }
1420
1421 /* a statement that is part of a list */
1422 decl_statement:
1423 TMetaStmList
1424 { let (nm,pure,clt) = $1 in
1425 [Ast0.wrap(Ast0.MetaStmt(P.clt2mcode nm clt,pure))] }
1426 | decl_var
1427 { List.map
1428 (function x ->
1429 Ast0.wrap
1430 (Ast0.Decl((Ast0.default_info(),Ast0.context_befaft()),x)))
1431 $1 }
1432 | statement { [$1] }
1433 /* this doesn't allow expressions at top level, because the parser doesn't
1434 know whether there is one. If there is one, this is not sequencible.
1435 If there is not one, then it is. It seems complicated to get around
1436 this at the parser level. We would have to have a check afterwards to
1437 allow this. One case where this would be useful is for a when. Now
1438 we allow a sequence of whens, so one can be on only statements and
1439 one can be on only expressions. */
1440 | TOPar0 t=midzero_list(fun_start,fun_start) TCPar0
1441 { let (mids,code) = t in
1442 if List.for_all
1443 (function x ->
1444 match Ast0.unwrap x with Ast0.DOTS([]) -> true | _ -> false)
1445 code
1446 then []
1447 else
1448 [Ast0.wrap(Ast0.Disj(P.clt2mcode "(" $1, code, mids,
1449 P.clt2mcode ")" $3))] }
1450
1451 /* a statement that is part of a list */
1452 decl_statement_expr:
1453 TMetaStmList
1454 { let (nm,pure,clt) = $1 in
1455 [Ast0.wrap(Ast0.MetaStmt(P.clt2mcode nm clt,pure))] }
1456 | decl_var
1457 { List.map
1458 (function x ->
1459 Ast0.wrap
1460 (Ast0.Decl((Ast0.default_info(),Ast0.context_befaft()),x)))
1461 $1 }
1462 | statement { [$1] }
1463 /* this doesn't allow expressions at top level, because the parser doesn't
1464 know whether there is one. If there is one, this is not sequencible.
1465 If there is not one, then it is. It seems complicated to get around
1466 this at the parser level. We would have to have a check afterwards to
1467 allow this. One case where this would be useful is for a when. Now
1468 we allow a sequence of whens, so one can be on only statements and
1469 one can be on only expressions. */
1470 | TOPar0 t=midzero_list(fun_after_stm,fun_after_dots_or) TCPar0
1471 { let (mids,code) = t in
1472 if List.for_all (function [] -> true | _ -> false) code
1473 then []
1474 else
1475 let dot_code =
1476 List.map (function x -> Ast0.wrap(Ast0.DOTS x)) code in
1477 [Ast0.wrap(Ast0.Disj(P.clt2mcode "(" $1, dot_code, mids,
1478 P.clt2mcode ")" $3))] }
1479
1480 /*****************************************************************************/
1481
1482 /* expr cannot contain <... ...> at the top level. This can only
1483 be allowed as an expression when the expression is delimited on the left
1484 by an expression-specific marker. In that case, the rule eexpr is used, which
1485 allows <... ...> anywhere. Hopefully, this will not be too much of a problem
1486 in practice.
1487 dot_expressions is the most permissive. all three kinds of expressions use
1488 this once an expression_specific token has been seen
1489 The arg versions don't allow sequences, to avoid conflicting with commas in
1490 argument lists.
1491 */
1492 expr: basic_expr(expr,invalid) { $1 }
1493 /* allows ... and nests */
1494 eexpr: pre_basic_expr(eexpr,dot_expressions) { $1 }
1495 eargexpr: basic_expr(eexpr,dot_expressions) { $1 } /* no sequences */
1496 /* allows nests but not .... */
1497 dexpr: pre_basic_expr(eexpr,nest_expressions) { $1 }
1498 dargexpr: basic_expr(eexpr,nest_expressions) { $1 } /* no sequences */
1499
1500 top_eexpr:
1501 eexpr { Ast0.wrap(Ast0.OTHER(Ast0.wrap(Ast0.Exp($1)))) }
1502
1503 invalid:
1504 TInvalid { raise (Semantic_cocci.Semantic "not matchable") }
1505
1506 dot_expressions:
1507 TEllipsis { Ast0.wrap(Ast0.Edots(P.clt2mcode "..." $1,None)) }
1508 | nest_expressions { $1 }
1509
1510 /* not clear what whencode would mean, so just drop it */
1511 nest_expressions:
1512 TOEllipsis e=expr_dots(TEllipsis) c=TCEllipsis
1513 { Ast0.wrap(Ast0.NestExpr(P.clt2mcode "<..." $1,
1514 Ast0.wrap(Ast0.DOTS(e (P.mkedots "..."))),
1515 P.clt2mcode "...>" c, None, false)) }
1516 | TPOEllipsis e=expr_dots(TEllipsis) c=TPCEllipsis
1517 { Ast0.wrap(Ast0.NestExpr(P.clt2mcode "<+..." $1,
1518 Ast0.wrap(Ast0.DOTS(e (P.mkedots "..."))),
1519 P.clt2mcode "...+>" c, None, true)) }
1520 | TMeta { tmeta_to_exp $1 }
1521
1522 nest_expressions_only:
1523 TOEllipsis e=expr_dots(TEllipsis) c=TCEllipsis
1524 { Ast0.wrap(Ast0.NestExpr(P.clt2mcode "<..." $1,
1525 Ast0.wrap(Ast0.DOTS(e (P.mkedots "..."))),
1526 P.clt2mcode "...>" c, None, false)) }
1527 | TPOEllipsis e=expr_dots(TEllipsis) c=TPCEllipsis
1528 { Ast0.wrap(Ast0.NestExpr(P.clt2mcode "<+..." $1,
1529 Ast0.wrap(Ast0.DOTS(e (P.mkedots "..."))),
1530 P.clt2mcode "...+>" c, None, true)) }
1531
1532 //whenexp: TWhen TNotEq w=eexpr TLineEnd { w }
1533
1534 pre_basic_expr(recurser,primary_extra):
1535 basic_expr(recurser,primary_extra) { $1 }
1536 | pre_basic_expr(recurser,primary_extra) TComma
1537 basic_expr(recurser,primary_extra)
1538 { Ast0.wrap(Ast0.Sequence($1,P.clt2mcode "," $2,$3)) }
1539
1540 basic_expr(recurser,primary_extra):
1541 assign_expr(recurser,primary_extra) { $1 }
1542
1543 assign_expr(r,pe):
1544 cond_expr(r,pe) { $1 }
1545 | unary_expr(r,pe) TAssign assign_expr_bis
1546 { let (op,clt) = $2 in
1547 Ast0.wrap(Ast0.Assignment($1,P.clt2mcode op clt,
1548 Ast0.set_arg_exp $3,false)) }
1549 | unary_expr(r,pe) TEq assign_expr_bis
1550 { Ast0.wrap
1551 (Ast0.Assignment
1552 ($1,P.clt2mcode Ast.SimpleAssign $2,Ast0.set_arg_exp $3,false)) }
1553
1554 assign_expr_bis:
1555 cond_expr(eexpr,dot_expressions) { $1 }
1556 | unary_expr(eexpr,dot_expressions) TAssign assign_expr_bis
1557 { let (op,clt) = $2 in
1558 Ast0.wrap(Ast0.Assignment($1,P.clt2mcode op clt,
1559 Ast0.set_arg_exp $3,false)) }
1560 | unary_expr(eexpr,dot_expressions) TEq assign_expr_bis
1561 { Ast0.wrap
1562 (Ast0.Assignment
1563 ($1,P.clt2mcode Ast.SimpleAssign $2,Ast0.set_arg_exp $3,false)) }
1564
1565 cond_expr(r,pe):
1566 arith_expr(r,pe) { $1 }
1567 | l=arith_expr(r,pe) w=TWhy t=option(eexpr)
1568 dd=TDotDot r=eargexpr/*see parser_c*/
1569 { Ast0.wrap(Ast0.CondExpr (l, P.clt2mcode "?" w, t,
1570 P.clt2mcode ":" dd, r)) }
1571
1572 arith_expr(r,pe):
1573 cast_expr(r,pe) { $1 }
1574 | arith_expr(r,pe) TMul arith_expr_bis
1575 { P.arith_op Ast.Mul $1 $2 $3 }
1576 | arith_expr(r,pe) TDmOp arith_expr_bis
1577 { let (op,clt) = $2 in P.arith_op op $1 clt $3 }
1578 | arith_expr(r,pe) TPlus arith_expr_bis
1579 { P.arith_op Ast.Plus $1 $2 $3 }
1580 | arith_expr(r,pe) TMinus arith_expr_bis
1581 { P.arith_op Ast.Minus $1 $2 $3 }
1582 | arith_expr(r,pe) TShLOp arith_expr_bis
1583 { let (op,clt) = $2 in P.arith_op op $1 clt $3 }
1584 | arith_expr(r,pe) TShROp arith_expr_bis
1585 { let (op,clt) = $2 in P.arith_op op $1 clt $3 }
1586 | arith_expr(r,pe) TLogOp arith_expr_bis
1587 { let (op,clt) = $2 in P.logic_op op $1 clt $3 }
1588 | arith_expr(r,pe) TEqEq arith_expr_bis
1589 { P.logic_op Ast.Eq $1 $2 $3 }
1590 | arith_expr(r,pe) TNotEq arith_expr_bis
1591 { P.logic_op Ast.NotEq $1 $2 $3 }
1592 | arith_expr(r,pe) TAnd arith_expr_bis
1593 { P.arith_op Ast.And $1 $2 $3 }
1594 | arith_expr(r,pe) TOr arith_expr_bis
1595 { P.arith_op Ast.Or $1 $2 $3 }
1596 | arith_expr(r,pe) TXor arith_expr_bis
1597 { P.arith_op Ast.Xor $1 $2 $3 }
1598 | arith_expr(r,pe) TAndLog arith_expr_bis
1599 { P.logic_op Ast.AndLog $1 $2 $3 }
1600 | arith_expr(r,pe) TOrLog arith_expr_bis
1601 { P.logic_op Ast.OrLog $1 $2 $3 }
1602
1603 // allows dots now that an expression-specific token has been seen
1604 // need an extra rule because of recursion restrictions
1605 arith_expr_bis:
1606 cast_expr(eexpr,dot_expressions) { $1 }
1607 | arith_expr_bis TMul arith_expr_bis
1608 { P.arith_op Ast.Mul $1 $2 $3 }
1609 | arith_expr_bis TDmOp arith_expr_bis
1610 { let (op,clt) = $2 in P.arith_op op $1 clt $3 }
1611 | arith_expr_bis TPlus arith_expr_bis
1612 { P.arith_op Ast.Plus $1 $2 $3 }
1613 | arith_expr_bis TMinus arith_expr_bis
1614 { P.arith_op Ast.Minus $1 $2 $3 }
1615 | arith_expr_bis TShLOp arith_expr_bis
1616 { let (op,clt) = $2 in P.arith_op op $1 clt $3 }
1617 | arith_expr_bis TShROp arith_expr_bis
1618 { let (op,clt) = $2 in P.arith_op op $1 clt $3 }
1619 | arith_expr_bis TLogOp arith_expr_bis
1620 { let (op,clt) = $2 in P.logic_op op $1 clt $3 }
1621 | arith_expr_bis TEqEq arith_expr_bis
1622 { P.logic_op Ast.Eq $1 $2 $3 }
1623 | arith_expr_bis TNotEq arith_expr_bis
1624 { P.logic_op Ast.NotEq $1 $2 $3 }
1625 | arith_expr_bis TAnd arith_expr_bis
1626 { P.arith_op Ast.And $1 $2 $3 }
1627 | arith_expr_bis TOr arith_expr_bis
1628 { P.arith_op Ast.Or $1 $2 $3 }
1629 | arith_expr_bis TXor arith_expr_bis
1630 { P.arith_op Ast.Xor $1 $2 $3 }
1631 | arith_expr_bis TAndLog arith_expr_bis
1632 { P.logic_op Ast.AndLog $1 $2 $3 }
1633 // no OrLog because it is left associative and this is for
1634 // a right argument, not sure why not the same problem for AndLog
1635
1636 cast_expr(r,pe):
1637 unary_expr(r,pe) { $1 }
1638 | lp=TOPar t=ctype rp=TCPar e=cast_expr(r,pe)
1639 { Ast0.wrap(Ast0.Cast (P.clt2mcode "(" lp, t,
1640 P.clt2mcode ")" rp, e)) }
1641
1642 unary_expr(r,pe):
1643 postfix_expr(r,pe) { $1 }
1644 | TInc unary_expr_bis
1645 { Ast0.wrap(Ast0.Infix ($2, P.clt2mcode Ast.Inc $1)) }
1646 | TDec unary_expr_bis
1647 { Ast0.wrap(Ast0.Infix ($2, P.clt2mcode Ast.Dec $1)) }
1648 | unary_op cast_expr(r,pe)
1649 { let mcode = $1 in Ast0.wrap(Ast0.Unary($2, mcode)) }
1650 | TBang unary_expr_bis
1651 { let mcode = P.clt2mcode Ast.Not $1 in
1652 Ast0.wrap(Ast0.Unary($2, mcode)) }
1653 | TSizeof unary_expr_bis
1654 { Ast0.wrap(Ast0.SizeOfExpr (P.clt2mcode "sizeof" $1, $2)) }
1655 | s=TSizeof lp=TOPar t=ctype rp=TCPar
1656 { Ast0.wrap(Ast0.SizeOfType (P.clt2mcode "sizeof" s,
1657 P.clt2mcode "(" lp,t,
1658 P.clt2mcode ")" rp)) }
1659
1660 // version that allows dots
1661 unary_expr_bis:
1662 postfix_expr(eexpr,dot_expressions) { $1 }
1663 | TInc unary_expr_bis
1664 { Ast0.wrap(Ast0.Infix ($2, P.clt2mcode Ast.Inc $1)) }
1665 | TDec unary_expr_bis
1666 { Ast0.wrap(Ast0.Infix ($2, P.clt2mcode Ast.Dec $1)) }
1667 | unary_op cast_expr(eexpr,dot_expressions)
1668 { let mcode = $1 in Ast0.wrap(Ast0.Unary($2, mcode)) }
1669 | TBang unary_expr_bis
1670 { let mcode = P.clt2mcode Ast.Not $1 in
1671 Ast0.wrap(Ast0.Unary($2, mcode)) }
1672 | TSizeof unary_expr_bis
1673 { Ast0.wrap(Ast0.SizeOfExpr (P.clt2mcode "sizeof" $1, $2)) }
1674 | s=TSizeof lp=TOPar t=ctype rp=TCPar
1675 { Ast0.wrap(Ast0.SizeOfType (P.clt2mcode "sizeof" s,
1676 P.clt2mcode "(" lp,t,
1677 P.clt2mcode ")" rp)) }
1678
1679 unary_op: TAnd { P.clt2mcode Ast.GetRef $1 }
1680 | TMul { P.clt2mcode Ast.DeRef $1 }
1681 | TPlus { P.clt2mcode Ast.UnPlus $1 }
1682 | TMinus { P.clt2mcode Ast.UnMinus $1 }
1683 | TTilde { P.clt2mcode Ast.Tilde $1 }
1684
1685 postfix_expr(r,pe):
1686 primary_expr(r,pe) { $1 }
1687 | postfix_expr(r,pe) TOCro eexpr TCCro
1688 { Ast0.wrap(Ast0.ArrayAccess ($1,P.clt2mcode "[" $2,$3,
1689 P.clt2mcode "]" $4)) }
1690 | postfix_expr(r,pe) TDot disj_ident
1691 { Ast0.wrap(Ast0.RecordAccess($1, P.clt2mcode "." $2, $3)) }
1692 | postfix_expr(r,pe) TPtrOp disj_ident
1693 { Ast0.wrap(Ast0.RecordPtAccess($1, P.clt2mcode "->" $2,
1694 $3)) }
1695 | postfix_expr(r,pe) TInc
1696 { Ast0.wrap(Ast0.Postfix ($1, P.clt2mcode Ast.Inc $2)) }
1697 | postfix_expr(r,pe) TDec
1698 { Ast0.wrap(Ast0.Postfix ($1, P.clt2mcode Ast.Dec $2)) }
1699 | postfix_expr(r,pe) TOPar eexpr_list_option TCPar
1700 { Ast0.wrap(Ast0.FunCall($1,P.clt2mcode "(" $2,
1701 $3,
1702 P.clt2mcode ")" $4)) }
1703 /*(* gccext: also called compound literals *)
1704 empty case causes conflicts */
1705 | TOPar ctype TCPar TOBrace initialize_list TCBrace
1706 { let init =
1707 if P.struct_initializer $5
1708 then
1709 let il = P.drop_dot_commas $5 in
1710 Ast0.wrap
1711 (Ast0.InitList(P.clt2mcode "{" $4,il,P.clt2mcode "}" $6,false))
1712 else
1713 Ast0.wrap
1714 (Ast0.InitList(P.clt2mcode "{" $4,$5,P.clt2mcode "}" $6,true)) in
1715 Ast0.wrap
1716 (Ast0.Constructor(P.clt2mcode "(" $1, $2, P.clt2mcode ")" $3, init)) }
1717
1718 primary_expr(recurser,primary_extra):
1719 func_ident { Ast0.wrap(Ast0.Ident($1)) }
1720 | TAndLog ident
1721 { let op = P.clt2mcode Ast.GetRefLabel $1 in
1722 Ast0.wrap(Ast0.Unary(Ast0.wrap(Ast0.Ident($2)), op)) }
1723 | TInt
1724 { let (x,clt) = $1 in
1725 Ast0.wrap(Ast0.Constant (P.clt2mcode (Ast.Int x) clt)) }
1726 | TFloat
1727 { let (x,clt) = $1 in
1728 Ast0.wrap(Ast0.Constant (P.clt2mcode (Ast.Float x) clt)) }
1729 | TString
1730 { let (x,clt) = $1 in
1731 Ast0.wrap(Ast0.Constant (P.clt2mcode (Ast.String x) clt)) }
1732 | TChar
1733 { let (x,clt) = $1 in
1734 Ast0.wrap(Ast0.Constant (P.clt2mcode (Ast.Char x) clt)) }
1735 | TMetaConst
1736 { let (nm,constraints,pure,ty,clt) = $1 in
1737 Ast0.wrap
1738 (Ast0.MetaExpr(P.clt2mcode nm clt,constraints,ty,Ast.CONST,pure)) }
1739 | TMetaErr
1740 { let (nm,constraints,pure,clt) = $1 in
1741 Ast0.wrap(Ast0.MetaErr(P.clt2mcode nm clt,constraints,pure)) }
1742 | TMetaExp
1743 { let (nm,constraints,pure,ty,clt) = $1 in
1744 Ast0.wrap
1745 (Ast0.MetaExpr(P.clt2mcode nm clt,constraints,ty,Ast.ANY,pure)) }
1746 | TMetaIdExp
1747 { let (nm,constraints,pure,ty,clt) = $1 in
1748 Ast0.wrap
1749 (Ast0.MetaExpr(P.clt2mcode nm clt,constraints,ty,Ast.ID,pure)) }
1750 | TMetaLocalIdExp
1751 { let (nm,constraints,pure,ty,clt) = $1 in
1752 Ast0.wrap
1753 (Ast0.MetaExpr(P.clt2mcode nm clt,constraints,ty,Ast.LocalID,pure)) }
1754 | TOPar eexpr TCPar
1755 { Ast0.wrap(Ast0.Paren(P.clt2mcode "(" $1,$2,
1756 P.clt2mcode ")" $3)) }
1757 | TOPar0 midzero_list(recurser,eexpr) TCPar0
1758 { let (mids,code) = $2 in
1759 Ast0.wrap(Ast0.DisjExpr(P.clt2mcode "(" $1,
1760 code, mids,
1761 P.clt2mcode ")" $3)) }
1762 | primary_extra { $1 }
1763
1764 expr_dots(dotter):
1765 r=no_dot_start_end(dexpr,edots_when(dotter,eexpr)) { r }
1766
1767 // used in NEST
1768 no_dot_start_end(grammar,dotter):
1769 g=grammar dg=list(pair(dotter,grammar))
1770 { function dot_builder ->
1771 g :: (List.concat(List.map (function (d,g) -> [dot_builder d;g]) dg)) }
1772
1773 /*****************************************************************************/
1774
1775 pure_ident:
1776 TIdent { $1 }
1777
1778 pure_ident_or_symbol:
1779 pure_ident { $1 }
1780 | TSymId { $1 }
1781
1782 pure_ident_kwd:
1783 | TIdentifier { "identifier" }
1784 | TExpression { "expression" }
1785 | TStatement { "statement" }
1786 | TFunction { "function" }
1787 | TLocal { "local" }
1788 | TType { "type" }
1789 | TParameter { "parameter" }
1790 | TIdExpression { "idexpression" }
1791 | TInitialiser { "initialiser" }
1792 | Tlist { "list" }
1793 | TFresh { "fresh" }
1794 | TConstant { "constant" }
1795 | TError { "error" }
1796 | TWords { "words" }
1797 | TPure { "pure" }
1798 | TContext { "context" }
1799 | TGenerated { "generated" }
1800 | TTypedef { "typedef" }
1801 | TDeclarer { "declarer" }
1802 | TIterator { "iterator" }
1803 | TName { "name" }
1804 | TPosition { "position" }
1805 | TSymbol { "symbol" }
1806
1807 meta_ident:
1808 TRuleName TDot pure_ident { (Some $1,P.id2name $3) }
1809 | TRuleName TDot pure_ident_kwd { (Some $1,$3) }
1810
1811 pure_ident_or_meta_ident:
1812 pure_ident { (None,P.id2name $1) }
1813 | pure_ident_kwd { (None,$1) }
1814 | meta_ident { $1 }
1815
1816 wrapped_sym_ident:
1817 TSymId { Ast0.wrap(Ast0.Id(P.sym2mcode $1)) }
1818
1819 pure_ident_or_meta_ident_with_seed:
1820 pure_ident_or_meta_ident { ($1,Ast.NoVal) }
1821 | pure_ident_or_meta_ident TEq
1822 separated_nonempty_list(TCppConcatOp,seed_elem)
1823 { match $3 with
1824 [Ast.SeedString s] -> ($1,Ast.StringSeed s)
1825 | _ -> ($1,Ast.ListSeed $3) }
1826
1827 seed_elem:
1828 TString { let (x,_) = $1 in Ast.SeedString x }
1829 | TMetaId { let (x,_,_,_,_) = $1 in Ast.SeedId x }
1830 | TMeta {failwith "tmeta"}
1831 | TVirtual TDot pure_ident
1832 { let nm = ("virtual",P.id2name $3) in
1833 Iteration.parsed_virtual_identifiers :=
1834 Common.union_set [snd nm]
1835 !Iteration.parsed_virtual_identifiers;
1836 try Ast.SeedString (List.assoc (snd nm) !Flag.defined_virtual_env)
1837 with Not_found -> Ast.SeedId nm }
1838 | TRuleName TDot pure_ident
1839 { let nm = ($1,P.id2name $3) in
1840 P.check_meta(Ast.MetaIdDecl(Ast.NONE,nm));
1841 Ast.SeedId nm }
1842
1843 pure_ident_or_meta_ident_with_x_eq(x_eq):
1844 i=pure_ident_or_meta_ident l=loption(x_eq)
1845 {
1846 (i, l)
1847 }
1848
1849 pure_ident_or_meta_ident_with_econstraint(x_eq):
1850 i=pure_ident_or_meta_ident optc=option(x_eq)
1851 {
1852 match optc with
1853 None -> (i, Ast0.NoConstraint)
1854 | Some c -> (i, c)
1855 }
1856
1857 pure_ident_or_meta_ident_with_idconstraint_virt(constraint_type):
1858 i=pure_ident_or_meta_ident c=option(constraint_type)
1859 {
1860 Common.Left
1861 (match c with
1862 None -> (i, Ast.IdNoConstraint)
1863 | Some constraint_ -> (i,constraint_))
1864 }
1865 | TVirtual TDot pure_ident
1866 {
1867 let nm = P.id2name $3 in
1868 Iteration.parsed_virtual_identifiers :=
1869 Common.union_set [nm]
1870 !Iteration.parsed_virtual_identifiers;
1871 Common.Right nm
1872 }
1873
1874 pure_ident_or_meta_ident_with_idconstraint(constraint_type):
1875 i=pure_ident_or_meta_ident c=option(constraint_type)
1876 {
1877 match c with
1878 None -> (i, Ast.IdNoConstraint)
1879 | Some constraint_ -> (i,constraint_)
1880 }
1881
1882 re_or_not_eqid:
1883 re=regexp_eqid {Ast.IdRegExpConstraint re}
1884 | ne=not_eqid {ne}
1885
1886 regexp_eqid:
1887 TTildeEq re=TString
1888 { (if !Data.in_iso
1889 then failwith "constraints not allowed in iso file");
1890 (if !Data.in_generating
1891 then failwith "constraints not allowed in a generated rule file");
1892 let (s,_) = re in Ast.IdRegExp (s,Regexp.regexp s)
1893 }
1894 | TTildeExclEq re=TString
1895 { (if !Data.in_iso
1896 then failwith "constraints not allowed in iso file");
1897 (if !Data.in_generating
1898 then failwith "constraints not allowed in a generated rule file");
1899 let (s,_) = re in Ast.IdNotRegExp (s,Regexp.regexp s)
1900 }
1901
1902 not_eqid:
1903 TNotEq i=pure_ident_or_meta_ident
1904 { (if !Data.in_iso
1905 then failwith "constraints not allowed in iso file");
1906 (if !Data.in_generating
1907 (* pb: constraints not stored with metavars; too lazy to search for
1908 them in the pattern *)
1909 then failwith "constraints not allowed in a generated rule file");
1910 (match i with
1911 (Some rn,id) ->
1912 let i =
1913 P.check_inherited_constraint i
1914 (function mv -> Ast.MetaIdDecl(Ast.NONE,mv)) in
1915 Ast.IdNegIdSet([],[i])
1916 | (None,i) -> Ast.IdNegIdSet([i],[])) }
1917 | TNotEq TOBrace l=comma_list(pure_ident_or_meta_ident) TCBrace
1918 { (if !Data.in_iso
1919 then failwith "constraints not allowed in iso file");
1920 (if !Data.in_generating
1921 then failwith "constraints not allowed in a generated rule file");
1922 let (str,meta) =
1923 List.fold_left
1924 (function (str,meta) ->
1925 function
1926 (Some rn,id) as i ->
1927 let i =
1928 P.check_inherited_constraint i
1929 (function mv -> Ast.MetaIdDecl(Ast.NONE,mv)) in
1930 (str,i::meta)
1931 | (None,i) -> (i::str,meta))
1932 ([],[]) l in
1933 Ast.IdNegIdSet(str,meta)
1934 }
1935
1936 re_or_not_eqe_or_sub:
1937 re=regexp_eqid {Ast0.NotIdCstrt re}
1938 | ne=not_eqe {Ast0.NotExpCstrt ne}
1939 | s=sub {Ast0.SubExpCstrt s}
1940
1941 not_ceq_or_sub:
1942 ceq=not_ceq {Ast0.NotExpCstrt ceq}
1943 | s=sub {Ast0.SubExpCstrt s}
1944
1945 not_eqe:
1946 TNotEq i=pure_ident
1947 { (if !Data.in_iso
1948 then failwith "constraints not allowed in iso file");
1949 (if !Data.in_generating
1950 then failwith "constraints not allowed in a generated rule file");
1951 [Ast0.wrap(Ast0.Ident(Ast0.wrap(Ast0.Id(P.id2mcode i))))]
1952 }
1953 | TNotEq TOBrace l=comma_list(pure_ident) TCBrace
1954 { (if !Data.in_iso
1955 then failwith "constraints not allowed in iso file");
1956 (if !Data.in_generating
1957 then failwith "constraints not allowed in a generated rule file");
1958 List.map
1959 (function i ->
1960 Ast0.wrap(Ast0.Ident(Ast0.wrap(Ast0.Id(P.id2mcode i)))))
1961 l
1962 }
1963
1964 not_ceq:
1965 TNotEq i=ident_or_const
1966 { (if !Data.in_iso
1967 then failwith "constraints not allowed in iso file");
1968 (if !Data.in_generating
1969 then failwith "constraints not allowed in a generated rule file");
1970 [i] }
1971 | TNotEq TOBrace l=comma_list(ident_or_const) TCBrace
1972 { (if !Data.in_iso
1973 then failwith "constraints not allowed in iso file");
1974 (if !Data.in_generating
1975 then failwith "constraints not allowed in a generated rule file");
1976 l }
1977
1978 sub:
1979 (* has to be inherited because not clear how to check subterm constraints
1980 in the functorized CTL engine, so need the variable to be bound
1981 already when bind the subterm constrained metavariable *)
1982 TSub i=meta_ident
1983 { (if !Data.in_iso
1984 then failwith "constraints not allowed in iso file");
1985 (if !Data.in_generating
1986 then failwith "constraints not allowed in a generated rule file");
1987 let i =
1988 P.check_inherited_constraint i
1989 (function mv -> Ast.MetaExpDecl(Ast.NONE,mv,None)) in
1990 [i] }
1991 | TSub TOBrace l=comma_list(meta_ident) TCBrace
1992 { (if !Data.in_iso
1993 then failwith "constraints not allowed in iso file");
1994 (if !Data.in_generating
1995 then failwith "constraints not allowed in a generated rule file");
1996 List.map
1997 (function i ->
1998 P.check_inherited_constraint i
1999 (function mv -> Ast.MetaExpDecl(Ast.NONE,mv,None)))
2000 l}
2001
2002 ident_or_const:
2003 i=pure_ident { Ast0.wrap(Ast0.Ident(Ast0.wrap(Ast0.Id(P.id2mcode i)))) }
2004 | wrapped_sym_ident { Ast0.wrap(Ast0.Ident($1)) }
2005 | TInt
2006 { let (x,clt) = $1 in
2007 Ast0.wrap(Ast0.Constant (P.clt2mcode (Ast.Int x) clt)) }
2008
2009 not_pos:
2010 TNotEq i=meta_ident
2011 { (if !Data.in_iso
2012 then failwith "constraints not allowed in iso file");
2013 (if !Data.in_generating
2014 then failwith "constraints not allowed in a generated rule file");
2015 let i =
2016 P.check_inherited_constraint i
2017 (function mv -> Ast.MetaPosDecl(Ast.NONE,mv)) in
2018 [i] }
2019 | TNotEq TOBrace l=comma_list(meta_ident) TCBrace
2020 { (if !Data.in_iso
2021 then failwith "constraints not allowed in iso file");
2022 (if !Data.in_generating
2023 then failwith "constraints not allowed in a generated rule file");
2024 List.map
2025 (function i ->
2026 P.check_inherited_constraint i
2027 (function mv -> Ast.MetaPosDecl(Ast.NONE,mv)))
2028 l }
2029
2030 func_ident:
2031 ident { $1 }
2032 | TMetaFunc
2033 { let (nm,constraints,pure,clt) = $1 in
2034 Ast0.wrap(Ast0.MetaFunc(P.clt2mcode nm clt,constraints,pure)) }
2035 | TMetaLocalFunc
2036 { let (nm,constraints,pure,clt) = $1 in
2037 Ast0.wrap
2038 (Ast0.MetaLocalFunc(P.clt2mcode nm clt,constraints,pure)) }
2039
2040 fn_ident: disj_ident { $1 }
2041 | TMetaFunc
2042 { let (nm,constraints,pure,clt) = $1 in
2043 Ast0.wrap(Ast0.MetaFunc(P.clt2mcode nm clt,constraints,pure)) }
2044 | TMetaLocalFunc
2045 { let (nm,constraints,pure,clt) = $1 in
2046 Ast0.wrap
2047 (Ast0.MetaLocalFunc(P.clt2mcode nm clt,constraints,pure)) }
2048
2049 ident: pure_ident
2050 { Ast0.wrap(Ast0.Id(P.id2mcode $1)) }
2051 | wrapped_sym_ident { $1 }
2052 | TMetaId
2053 { let (nm,constraints,seed,pure,clt) = $1 in
2054 Ast0.wrap(Ast0.MetaId(P.clt2mcode nm clt,constraints,seed,pure)) }
2055
2056 mident: pure_ident
2057 { Ast0.wrap(Ast0.Id(P.id2mcode $1)) }
2058 | wrapped_sym_ident { $1 }
2059 | TMeta { tmeta_to_ident $1 }
2060 | TMetaId
2061 { let (nm,constraints,seed,pure,clt) = $1 in
2062 Ast0.wrap(Ast0.MetaId(P.clt2mcode nm clt,constraints,seed,pure)) }
2063
2064 disj_ident:
2065 mident { $1 }
2066 | lp=TOPar0 t=midzero_list(disj_ident,disj_ident) rp=TCPar0
2067 { let (mids,code) = t in
2068 Ast0.wrap
2069 (Ast0.DisjId(P.clt2mcode "(" lp,code,mids, P.clt2mcode ")" rp)) }
2070
2071 type_ident: disj_ident { $1 }
2072 | TTypeId
2073 { Ast0.wrap(Ast0.Id(P.id2mcode $1)) }
2074
2075 decl_ident:
2076 TDeclarerId
2077 { Ast0.wrap(Ast0.Id(P.id2mcode $1)) }
2078 | TMetaDeclarer
2079 { let (nm,constraints,pure,clt) = $1 in
2080 Ast0.wrap(Ast0.MetaId(P.clt2mcode nm clt,constraints,Ast.NoVal,pure)) }
2081
2082 iter_ident:
2083 TIteratorId
2084 { Ast0.wrap(Ast0.Id(P.id2mcode $1)) }
2085 | TMetaIterator
2086 { let (nm,constraints,pure,clt) = $1 in
2087 Ast0.wrap(Ast0.MetaId(P.clt2mcode nm clt,constraints,Ast.NoVal,pure)) }
2088
2089 typedef_ident:
2090 pure_ident_or_symbol
2091 { Ast0.wrap(Ast0.TypeName(P.id2mcode $1)) }
2092 | TMeta { tmeta_to_type $1 }
2093 | TMetaType
2094 { let (nm,pure,clt) = $1 in
2095 Ast0.wrap(Ast0.MetaType(P.clt2mcode nm clt,pure)) }
2096
2097 /*****************************************************************************/
2098
2099 decl_list(decl):
2100 empty_list_start(one_dec(decl),TEllipsis)
2101 { Ast0.wrap
2102 (Ast0.DOTS
2103 ($1
2104 (fun _ d -> Ast0.wrap(Ast0.Pdots(P.clt2mcode "..." d)))
2105 (fun c -> Ast0.PComma c))) }
2106
2107 one_dec(decl):
2108 decl { $1 }
2109 | TMetaParamList
2110 { let (nm,lenname,pure,clt) = $1 in
2111 let nm = P.clt2mcode nm clt in
2112 let lenname =
2113 match lenname with
2114 Ast.AnyLen -> Ast0.AnyListLen
2115 | Ast.MetaLen nm -> Ast0.MetaListLen(P.clt2mcode nm clt)
2116 | Ast.CstLen n -> Ast0.CstListLen n in
2117 Ast0.wrap(Ast0.MetaParamList(nm,lenname,pure)) }
2118
2119 /* ---------------------------------------------------------------------- */
2120 /* comma list parser, used for fn params, fn args, enums, initlists,
2121 #define params */
2122
2123 /* enums: enum_decl, edots_when(TEllipsis,enum_decl_one)
2124 fun s d -> P.mkedots "..." d
2125 fun c -> Ast0.EComma c
2126 */
2127
2128 empty_list_start(elem,dotter):
2129 /* empty */ { fun build_dots build_comma -> [] }
2130 | nonempty_list_start(elem,dotter) { $1 }
2131
2132 nonempty_list_start(elem,dotter): /* dots allowed */
2133 elem { fun build_dots build_comma -> [$1] }
2134 | elem TComma
2135 { fun build_dots build_comma ->
2136 $1::[Ast0.wrap(build_comma(P.clt2mcode "," $2))] }
2137 | elem TComma nonempty_list_start(elem,dotter)
2138 { fun build_dots build_comma ->
2139 $1::(Ast0.wrap(build_comma(P.clt2mcode "," $2)))::
2140 ($3 build_dots build_comma) }
2141 | TNothing nonempty_list_start(elem,dotter) { $2 }
2142 | d=dotter { fun build_dots build_comma -> [(build_dots "..." d)] }
2143 | d=dotter TComma
2144 { fun build_dots build_comma ->
2145 [(build_dots "..." d);Ast0.wrap(build_comma(P.clt2mcode "," $2))] }
2146 | d=dotter TComma r=continue_list(elem,dotter)
2147 { fun build_dots build_comma ->
2148 (build_dots "..." d)::
2149 (Ast0.wrap(build_comma(P.clt2mcode "," $2)))::
2150 (r build_dots build_comma) }
2151
2152 continue_list(elem,dotter): /* dots not allowed */
2153 elem { fun build_dots build_comma -> [$1] }
2154 | elem TComma
2155 { fun build_dots build_comma ->
2156 $1::[Ast0.wrap(build_comma(P.clt2mcode "," $2))] }
2157 | elem TComma nonempty_list_start(elem,dotter)
2158 { fun build_dots build_comma ->
2159 $1::(Ast0.wrap(build_comma(P.clt2mcode "," $2)))::
2160 ($3 build_dots build_comma) }
2161 | TNothing nonempty_list_start(elem,dotter) { $2 }
2162
2163 /* ---------------------------------------------------------------------- */
2164
2165 /* error words make it complicated to be able to use error as a metavariable
2166 name or a type in a metavariable list; for that we would like to allow TError
2167 as an ident, but that makes conflicts with this rule. To add back error words,
2168 need to find some appropriate delimiter for it, but it has not been used much
2169 so just drop it */
2170 /*error_words:
2171 TError TWords TEq TOCro cl=comma_list(dexpr) TCCro
2172 { [Ast0.wrap(Ast0.ERRORWORDS(cl))] }
2173 */
2174
2175 /* ---------------------------------------------------------------------- */
2176 /* sequences of statements and expressions */
2177
2178 /* There are number of cases that must be considered:
2179
2180 1. Top level:
2181 Dots and nests allowed at the beginning or end
2182 Expressions allowed at the beginning or end
2183 One function allowed, by itself
2184 2. A function body:
2185 Dots and nests allowed at the beginning or end
2186 Expressions not allowed at the beginning or end
2187 Functions not allowed
2188 3. The body of a nest:
2189 Dots and nests not allowed at the beginning or end
2190 Expressions allowed at the beginning or end
2191 Functions not allowed
2192 4. Whencode:
2193 Dots and nests not allowed at the beginning but allowed at the end
2194 Expressions allowed at the beginning or end
2195 Functions not allowed
2196
2197 These are implemented by the rules minus_toplevel_sequence,
2198 plus_toplevel_sequence, function_body_sequence, nest_body_sequence, and
2199 when_body_sequence.
2200 */
2201 /* ------------------------------------------------------------------------ */
2202 /* Minus top level */
2203
2204 /* doesn't allow only ... */
2205 minus_start:
2206 fundecl { [Ast0.wrap(Ast0.OTHER($1))] }
2207 | ctype { [Ast0.wrap(Ast0.OTHER(Ast0.wrap(Ast0.Ty($1))))] }
2208 | top_init { [Ast0.wrap(Ast0.OTHER(Ast0.wrap(Ast0.TopInit($1))))] }
2209 | toplevel_seq_startne(toplevel_after_dots_init)
2210 { List.map (function x -> Ast0.wrap(Ast0.OTHER(x))) $1 }
2211
2212 toplevel_seq_startne(after_dots_init):
2213 a=stm_dots_ell b=after_dots_init { a::b }
2214 | a=stm_dots_nest b=after_dots_init { a::b }
2215 | a=stm_dots_nest { [a] }
2216 | expr toplevel_after_exp { (Ast0.wrap(Ast0.Exp($1)))::$2 }
2217 | decl_statement_expr toplevel_after_stm { $1@$2 }
2218
2219 toplevel_seq_start(after_dots_init):
2220 stm_dots after_dots_init { $1::$2 }
2221 | expr toplevel_after_exp { (Ast0.wrap(Ast0.Exp($1)))::$2 }
2222 | decl_statement_expr toplevel_after_stm { $1@$2 }
2223
2224 toplevel_after_dots_init:
2225 TNothing toplevel_after_exp {$2}
2226 | expr toplevel_after_exp {(Ast0.wrap(Ast0.Exp($1)))::$2}
2227 | decl_statement_expr toplevel_after_stm {$1@$2}
2228
2229 toplevel_after_exp:
2230 /* empty */ {[]}
2231 | stm_dots toplevel_after_dots {$1::$2}
2232
2233 toplevel_after_dots:
2234 /* empty */ {[]}
2235 | TNothing toplevel_after_exp {$2}
2236 | expr toplevel_after_exp {(Ast0.wrap(Ast0.Exp($1)))::$2}
2237 | decl_statement_expr toplevel_after_stm {$1@$2}
2238
2239 toplevel_after_stm:
2240 /* empty */ {[]}
2241 | stm_dots toplevel_after_dots {$1::$2}
2242 | decl_statement toplevel_after_stm {$1@$2}
2243
2244 top_init:
2245 TOInit initialize_list TCBrace
2246 { if P.struct_initializer $2
2247 then
2248 let il = P.drop_dot_commas $2 in
2249 Ast0.wrap(Ast0.InitList(P.clt2mcode "{" $1,il,P.clt2mcode "}" $3,false))
2250 else
2251 Ast0.wrap(Ast0.InitList(P.clt2mcode "{" $1,$2,P.clt2mcode "}" $3,true)) }
2252
2253 /* ------------------------------------------------------------------------ */
2254 /* Plus top level */
2255
2256 /* does allow only ... also allows multiple top-level functions */
2257 plus_start:
2258 ctype { [Ast0.wrap(Ast0.OTHER(Ast0.wrap(Ast0.Ty($1))))] }
2259 | top_init { [Ast0.wrap(Ast0.OTHER(Ast0.wrap(Ast0.TopInit($1))))] }
2260 | stm_dots plus_after_dots
2261 { (Ast0.wrap(Ast0.OTHER($1)))::$2 }
2262 | expr plus_after_exp
2263 { (Ast0.wrap(Ast0.OTHER(Ast0.wrap(Ast0.Exp($1)))))::$2 }
2264 | fundecl plus_after_stm { Ast0.wrap(Ast0.OTHER($1))::$2 }
2265 | decl_statement_expr plus_after_stm
2266 { (List.map (function x -> Ast0.wrap(Ast0.OTHER(x))) $1)@$2 }
2267
2268 plus_after_exp:
2269 /* empty */ {[]}
2270 | stm_dots plus_after_dots { (Ast0.wrap(Ast0.OTHER($1)))::$2 }
2271
2272 plus_after_dots:
2273 /* empty */ {[]}
2274 | TNothing plus_after_exp {$2}
2275 | expr plus_after_exp
2276 { (Ast0.wrap(Ast0.OTHER(Ast0.wrap(Ast0.Exp($1)))))::$2 }
2277 | fundecl plus_after_stm { Ast0.wrap(Ast0.OTHER($1))::$2 }
2278 | decl_statement_expr plus_after_stm
2279 { (List.map (function x -> Ast0.wrap(Ast0.OTHER(x))) $1)@$2 }
2280
2281 plus_after_stm:
2282 /* empty */ {[]}
2283 | stm_dots plus_after_dots { (Ast0.wrap(Ast0.OTHER($1)))::$2 }
2284 | fundecl plus_after_stm { Ast0.wrap(Ast0.OTHER($1))::$2 }
2285 | decl_statement plus_after_stm
2286 { (List.map (function x -> Ast0.wrap(Ast0.OTHER(x))) $1)@$2 }
2287
2288 /* ------------------------------------------------------------------------ */
2289 /* Function body */
2290
2291 fun_start:
2292 fun_after_stm { Ast0.wrap(Ast0.DOTS($1)) }
2293
2294 fun_after_stm:
2295 /* empty */ {[]}
2296 | stm_dots fun_after_dots {$1::$2}
2297 | decl_statement fun_after_stm {$1@$2}
2298
2299 fun_after_dots:
2300 /* empty */ {[]}
2301 | TNothing fun_after_exp {$2}
2302 | expr fun_after_exp {Ast0.wrap(Ast0.Exp($1))::$2}
2303 | decl_statement_expr fun_after_stm {$1@$2}
2304
2305 fun_after_exp:
2306 stm_dots fun_after_dots {$1::$2}
2307
2308 /* hack to allow mixing statements and expressions in an or */
2309 fun_after_dots_or:
2310 /* empty */ {[]}
2311 | TNothing fun_after_exp_or {$2}
2312 | expr fun_after_exp_or {Ast0.wrap(Ast0.Exp($1))::$2}
2313 | decl_statement_expr fun_after_stm {$1@$2}
2314
2315 fun_after_exp_or:
2316 /* empty */ {[]}
2317 | stm_dots fun_after_dots {$1::$2}
2318
2319 /* ------------------------------------------------------------------------ */
2320 /* Nest body */
2321
2322 nest_start:
2323 nest_after_dots { Ast0.wrap(Ast0.DOTS($1)) }
2324
2325 nest_after_dots:
2326 decl_statement_expr nest_after_stm {$1@$2}
2327 | TNothing nest_after_exp {$2}
2328 | expr nest_after_exp {(Ast0.wrap(Ast0.Exp($1)))::$2}
2329
2330 nest_after_stm:
2331 /* empty */ {[]}
2332 | stm_dots nest_after_dots {$1::$2}
2333 | decl_statement nest_after_stm {$1@$2}
2334
2335 nest_after_exp:
2336 /* empty */ {[]}
2337 | stm_dots nest_after_dots {$1::$2}
2338
2339 /* ------------------------------------------------------------------------ */
2340 /*Whencode*/
2341
2342 when_start:
2343 expr toplevel_after_exp
2344 { Ast0.wrap(Ast0.DOTS((Ast0.wrap(Ast0.Exp($1)))::$2)) }
2345 | decl_statement toplevel_after_stm
2346 { Ast0.wrap(Ast0.DOTS($1@$2)) }
2347
2348 /* ---------------------------------------------------------------------- */
2349
2350 /* arg expr. may contain a type or a explist metavariable */
2351 aexpr:
2352 dargexpr { Ast0.set_arg_exp $1 }
2353 | TMetaExpList
2354 { let (nm,lenname,pure,clt) = $1 in
2355 let nm = P.clt2mcode nm clt in
2356 let lenname =
2357 match lenname with
2358 Ast.AnyLen -> Ast0.AnyListLen
2359 | Ast.MetaLen nm -> Ast0.MetaListLen(P.clt2mcode nm clt)
2360 | Ast.CstLen n -> Ast0.CstListLen n in
2361 Ast0.wrap(Ast0.MetaExprList(nm,lenname,pure)) }
2362 | ctype
2363 { Ast0.set_arg_exp(Ast0.wrap(Ast0.TypeExp($1))) }
2364
2365 eexpr_list_option:
2366 empty_list_start(aexpr,TEllipsis)
2367 { Ast0.wrap
2368 (Ast0.DOTS
2369 ($1
2370 (fun _ d -> Ast0.wrap(Ast0.Edots(P.clt2mcode "..." d,None)))
2371 (fun c -> Ast0.EComma c))) }
2372
2373 /****************************************************************************/
2374
2375 // non-empty lists - drop separator
2376 comma_list(elem):
2377 separated_nonempty_list(TComma,elem) { $1 }
2378
2379 midzero_list(elem,aft):
2380 a=elem b=list(mzl(aft))
2381 { let (mids,code) = List.split b in (mids,(a::code)) }
2382
2383 mzl(elem):
2384 a=TMid0 b=elem { (P.clt2mcode "|" a, b) }
2385
2386 edots_when(dotter,when_grammar):
2387 d=dotter { (d,None) }
2388 | d=dotter TWhen TNotEq w=when_grammar TLineEnd { (d,Some w) }
2389
2390 whens(when_grammar,simple_when_grammar,any_strict):
2391 TWhen TNotEq w=when_grammar TLineEnd { [Ast0.WhenNot w] }
2392 | TWhen TEq w=simple_when_grammar TLineEnd { [Ast0.WhenAlways w] }
2393 | TWhen comma_list(any_strict) TLineEnd
2394 { List.map (function x -> Ast0.WhenModifier(x)) $2 }
2395 | TWhenTrue TNotEq e = eexpr TLineEnd { [Ast0.WhenNotTrue e] }
2396 | TWhenFalse TNotEq e = eexpr TLineEnd { [Ast0.WhenNotFalse e] }
2397
2398 any_strict:
2399 TAny { Ast.WhenAny }
2400 | TStrict { Ast.WhenStrict }
2401 | TForall { Ast.WhenForall }
2402 | TExists { Ast.WhenExists }
2403
2404 /*****************************************************************************
2405 *
2406 *
2407 *****************************************************************************/
2408
2409 iso_main:
2410 TIsoExpression e1=eexpr el=list(iso(eexpr)) EOF
2411 { let fn x = Ast0.ExprTag x in P.iso_adjust fn fn e1 el }
2412 | TIsoArgExpression e1=eexpr el=list(iso(eexpr)) EOF
2413 { let fn x = Ast0.ArgExprTag x in P.iso_adjust fn fn e1 el }
2414 | TIsoTestExpression e1=eexpr el=list(iso(eexpr)) EOF
2415 { let fn x = Ast0.TestExprTag x in P.iso_adjust fn fn e1 el }
2416 | TIsoToTestExpression e1=eexpr el=list(iso(eexpr)) EOF
2417 { let ffn x = Ast0.ExprTag x in
2418 let fn x = Ast0.TestExprTag x in
2419 P.iso_adjust ffn fn e1 el }
2420 | TIsoStatement s1=iso_statement sl=list(iso(iso_statement)) EOF
2421 { let fn x = Ast0.StmtTag x in P.iso_adjust fn fn s1 sl }
2422 | TIsoType t1=ctype tl=list(iso(ctype)) EOF
2423 { let fn x = Ast0.TypeCTag x in P.iso_adjust fn fn t1 tl }
2424 | TIsoTopLevel e1=nest_start el=list(iso(nest_start)) EOF
2425 { let fn x = Ast0.DotsStmtTag x in P.iso_adjust fn fn e1 el }
2426 | TIsoDeclaration d1=decl_var dl=list(iso(decl_var)) EOF
2427 { let check_one = function
2428 [x] -> x
2429 | _ ->
2430 raise
2431 (Semantic_cocci.Semantic
2432 "only one variable per declaration in an isomorphism rule") in
2433 let d1 = check_one d1 in
2434 let dl =
2435 List.map
2436 (function
2437 Common.Left x -> Common.Left(check_one x)
2438 | Common.Right x -> Common.Right(check_one x))
2439 dl in
2440 let fn x = Ast0.DeclTag x in P.iso_adjust fn fn d1 dl }
2441
2442 iso(term):
2443 TIso t=term { Common.Left t }
2444 | TRightIso t=term { Common.Right t }
2445
2446 /*****************************************************************************
2447 *
2448 *
2449 *****************************************************************************/
2450
2451 never_used: TPragma { () }
2452 | TPArob TMetaPos { () }
2453 | TScriptData { () }
2454 | TAnalysis { () }
2455
2456 script_meta_main:
2457 py=pure_ident TMPtVirg
2458 { ((Some (P.id2name py), None), None) }
2459 | py=pure_ident script_name_decl TMPtVirg
2460 { ((Some (P.id2name py), None), Some $2) }
2461 | TOPar TUnderscore TComma ast=pure_ident TCPar script_name_decl TMPtVirg
2462 { ((None, Some (P.id2name ast)), Some $6) }
2463 | TOPar str=pure_ident TComma TUnderscore TCPar script_name_decl TMPtVirg
2464 { ((Some (P.id2name str), None), Some $6) }
2465 | TOPar str=pure_ident TComma ast=pure_ident TCPar script_name_decl TMPtVirg
2466 { ((Some (P.id2name str), Some (P.id2name ast)), Some $6) }
2467
2468 script_name_decl:
2469 TShLOp TRuleName TDot cocci=pure_ident
2470 { let nm = P.id2name cocci in
2471 let mv = Parse_aux.lookup $2 nm in
2472 (($2, nm), mv) }
2473 | TShLOp TVirtual TDot cocci=pure_ident
2474 { let nm = P.id2name cocci in
2475 Iteration.parsed_virtual_identifiers :=
2476 Common.union_set [nm]
2477 !Iteration.parsed_virtual_identifiers;
2478 let name = ("virtual", nm) in
2479 let mv = Ast.MetaIdDecl(Ast.NONE,name) in
2480 (name,mv) }