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