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