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