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