Coccinelle release 1.0.0-rc13
[bpt/coccinelle.git] / parsing_cocci / ast_cocci.mli
CommitLineData
f537ebc4 1(*
17ba0788
C
2 * Copyright 2012, INRIA
3 * Julia Lawall, Gilles Muller
4 * Copyright 2010-2011, INRIA, University of Copenhagen
f537ebc4
C
5 * Julia Lawall, Rene Rydhof Hansen, Gilles Muller, Nicolas Palix
6 * Copyright 2005-2009, Ecole des Mines de Nantes, University of Copenhagen
7 * Yoann Padioleau, Julia Lawall, Rene Rydhof Hansen, Henrik Stuart, Gilles Muller, Nicolas Palix
8 * This file is part of Coccinelle.
9 *
10 * Coccinelle is free software: you can redistribute it and/or modify
11 * it under the terms of the GNU General Public License as published by
12 * the Free Software Foundation, according to version 2 of the License.
13 *
14 * Coccinelle is distributed in the hope that it will be useful,
15 * but WITHOUT ANY WARRANTY; without even the implied warranty of
16 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
17 * GNU General Public License for more details.
18 *
19 * You should have received a copy of the GNU General Public License
20 * along with Coccinelle. If not, see <http://www.gnu.org/licenses/>.
21 *
22 * The authors reserve the right to distribute this or future versions of
23 * Coccinelle under other licenses.
24 *)
25
26
d6ce1786
C
27# 0 "./ast_cocci.mli"
28(*
29 * Copyright 2012, INRIA
30 * Julia Lawall, Gilles Muller
31 * Copyright 2010-2011, INRIA, University of Copenhagen
32 * Julia Lawall, Rene Rydhof Hansen, Gilles Muller, Nicolas Palix
33 * Copyright 2005-2009, Ecole des Mines de Nantes, University of Copenhagen
34 * Yoann Padioleau, Julia Lawall, Rene Rydhof Hansen, Henrik Stuart, Gilles Muller, Nicolas Palix
35 * This file is part of Coccinelle.
36 *
37 * Coccinelle is free software: you can redistribute it and/or modify
38 * it under the terms of the GNU General Public License as published by
39 * the Free Software Foundation, according to version 2 of the License.
40 *
41 * Coccinelle is distributed in the hope that it will be useful,
42 * but WITHOUT ANY WARRANTY; without even the implied warranty of
43 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
44 * GNU General Public License for more details.
45 *
46 * You should have received a copy of the GNU General Public License
47 * along with Coccinelle. If not, see <http://www.gnu.org/licenses/>.
48 *
49 * The authors reserve the right to distribute this or future versions of
50 * Coccinelle under other licenses.
51 *)
52
53
feec80c3 54# 0 "./ast_cocci.mli"
34e49164
C
55(* --------------------------------------------------------------------- *)
56(* Modified code *)
57
190f1acf 58type added_string = Noindent of string | Indent of string | Space of string
c3e37e97 59
34e49164 60type info = { line : int; column : int;
c3e37e97
C
61 strbef : (added_string * int (* line *) * int (* col *)) list;
62 straft : (added_string * int (* line *) * int (* col *)) list }
34e49164
C
63type line = int
64type meta_name = string * string
65type 'a wrap =
66 {node : 'a;
67 node_line : line;
68 free_vars : meta_name list; (*free vars*)
69 minus_free_vars : meta_name list; (*minus free vars*)
978fd7e5 70 fresh_vars : (meta_name * seed) list; (*fresh vars*)
34e49164
C
71 inherited : meta_name list; (*inherited vars*)
72 saved_witness : meta_name list; (*witness vars*)
73 bef_aft : dots_bef_aft;
74 pos_info : meta_name mcode option; (* pos info, try not to duplicate *)
75 true_if_test_exp : bool;(* true if "test_exp from iso", only for exprs *)
690d68d1
C
76 (* the following is only for declarations *)
77 safe_for_multi_decls : bool;
34e49164
C
78 (* isos relevant to the term; ultimately only used for rule_elems *)
79 iso_info : (string*anything) list }
80
81and 'a befaft =
951c7801
C
82 BEFORE of 'a list list * count
83 | AFTER of 'a list list * count
84 | BEFOREAFTER of 'a list list * 'a list list * count
34e49164
C
85 | NOTHING
86
8babbc8f
C
87and 'a replacement = REPLACEMENT of 'a list list * count | NOREPLACEMENT
88
8f657093 89and 'a mcode = 'a * info * mcodekind * meta_pos list (* pos variables *)
34e49164
C
90 (* pos is an offset indicating where in the C code the mcodekind has an
91 effect *)
8babbc8f 92and adjacency = ALLMINUS | ADJ of int
34e49164 93 and mcodekind =
8babbc8f 94 MINUS of pos * int list * adjacency * anything replacement
34e49164 95 | CONTEXT of pos * anything befaft
951c7801
C
96 | PLUS of count
97 and count = ONE (* + *) | MANY (* ++ *)
34e49164
C
98 and fixpos =
99 Real of int (* charpos *) | Virt of int * int (* charpos + offset *)
100 and pos = NoPos | DontCarePos | FixPos of (fixpos * fixpos)
101
102and dots_bef_aft =
103 NoDots
104 | AddingBetweenDots of statement * int (*index of let var*)
105 | DroppingBetweenDots of statement * int (*index of let var*)
106
107and inherited = Type_cocci.inherited
108and keep_binding = Type_cocci.keep_binding
109and multi = bool (*true if a nest is one or more, false if it is zero or more*)
110
111and end_info =
978fd7e5 112 meta_name list (*free vars*) * (meta_name * seed) list (*fresh*) *
b1b2de81 113 meta_name list (*inherited vars*) * mcodekind
34e49164
C
114
115(* --------------------------------------------------------------------- *)
116(* Metavariables *)
117
118and arity = UNIQUE | OPT | MULTI | NONE
119
120and metavar =
b23ff9c7
C
121 MetaMetaDecl of arity * meta_name (* name *)
122 | MetaIdDecl of arity * meta_name (* name *)
978fd7e5 123 | MetaFreshIdDecl of meta_name (* name *) * seed (* seed *)
34e49164 124 | MetaTypeDecl of arity * meta_name (* name *)
113803cf 125 | MetaInitDecl of arity * meta_name (* name *)
8f657093 126 | MetaInitListDecl of arity * meta_name (* name *) * list_len (*len*)
34e49164
C
127 | MetaListlenDecl of meta_name (* name *)
128 | MetaParamDecl of arity * meta_name (* name *)
88e71198 129 | MetaParamListDecl of arity * meta_name (*name*) * list_len (*len*)
34e49164
C
130 | MetaConstDecl of
131 arity * meta_name (* name *) * Type_cocci.typeC list option
132 | MetaErrDecl of arity * meta_name (* name *)
133 | MetaExpDecl of
134 arity * meta_name (* name *) * Type_cocci.typeC list option
135 | MetaIdExpDecl of
136 arity * meta_name (* name *) * Type_cocci.typeC list option
137 | MetaLocalIdExpDecl of
138 arity * meta_name (* name *) * Type_cocci.typeC list option
88e71198 139 | MetaExpListDecl of arity * meta_name (*name*) * list_len (*len*)
413ffc02
C
140 | MetaDeclDecl of arity * meta_name (* name *)
141 | MetaFieldDecl of arity * meta_name (* name *)
190f1acf 142 | MetaFieldListDecl of arity * meta_name (* name *) * list_len (*len*)
34e49164
C
143 | MetaStmDecl of arity * meta_name (* name *)
144 | MetaStmListDecl of arity * meta_name (* name *)
145 | MetaFuncDecl of arity * meta_name (* name *)
146 | MetaLocalFuncDecl of arity * meta_name (* name *)
147 | MetaPosDecl of arity * meta_name (* name *)
148 | MetaDeclarerDecl of arity * meta_name (* name *)
149 | MetaIteratorDecl of arity * meta_name (* name *)
150
88e71198
C
151and list_len = AnyLen | MetaLen of meta_name | CstLen of int
152
978fd7e5
C
153and seed = NoVal | StringSeed of string | ListSeed of seed_elem list
154and seed_elem = SeedString of string | SeedId of meta_name
155
34e49164
C
156(* --------------------------------------------------------------------- *)
157(* --------------------------------------------------------------------- *)
158(* Dots *)
159
160and 'a base_dots =
161 DOTS of 'a list
162 | CIRCLES of 'a list
163 | STARS of 'a list
164
165and 'a dots = 'a base_dots wrap
166
167(* --------------------------------------------------------------------- *)
168(* Identifier *)
169
170and base_ident =
951c7801
C
171 Id of string mcode
172 | MetaId of meta_name mcode * idconstraint * keep_binding * inherited
173 | MetaFunc of meta_name mcode * idconstraint * keep_binding * inherited
174 | MetaLocalFunc of meta_name mcode * idconstraint * keep_binding * inherited
d6ce1786 175 | AsIdent of ident * ident (* as ident, always metavar *)
34e49164 176
d3f655c6 177 | DisjId of ident list
34e49164
C
178 | OptIdent of ident
179 | UniqueIdent of ident
180
181and ident = base_ident wrap
182
183(* --------------------------------------------------------------------- *)
184(* Expression *)
185
faf9a90c 186and base_expression =
34e49164
C
187 Ident of ident
188 | Constant of constant mcode
189 | FunCall of expression * string mcode (* ( *) *
190 expression dots * string mcode (* ) *)
191 | Assignment of expression * assignOp mcode * expression * bool
17ba0788 192 | Sequence of expression * string mcode (* , *) * expression
34e49164
C
193 | CondExpr of expression * string mcode (* ? *) * expression option *
194 string mcode (* : *) * expression
195 | Postfix of expression * fixOp mcode
196 | Infix of expression * fixOp mcode
197 | Unary of expression * unaryOp mcode
198 | Binary of expression * binaryOp mcode * expression
199 | Nested of expression * binaryOp mcode * expression
200 | ArrayAccess of expression * string mcode (* [ *) * expression *
201 string mcode (* ] *)
202 | RecordAccess of expression * string mcode (* . *) * ident
203 | RecordPtAccess of expression * string mcode (* -> *) * ident
204 | Cast of string mcode (* ( *) * fullType * string mcode (* ) *) *
205 expression
206
207 | SizeOfExpr of string mcode (* sizeof *) * expression
208 | SizeOfType of string mcode (* sizeof *) * string mcode (* ( *) *
209 fullType * string mcode (* ) *)
210 | TypeExp of fullType
211
212 | Paren of string mcode (* ( *) * expression *
213 string mcode (* ) *)
214
7fe62b65
C
215 | Constructor of string mcode (* ( *) * fullType * string mcode (* ) *) *
216 initialiser
951c7801 217 | MetaErr of meta_name mcode * constraints * keep_binding *
34e49164 218 inherited
951c7801 219 | MetaExpr of meta_name mcode * constraints * keep_binding *
34e49164 220 Type_cocci.typeC list option * form * inherited
88e71198 221 | MetaExprList of meta_name mcode * listlen *
34e49164 222 keep_binding * inherited (* only in arg lists *)
17ba0788 223 | AsExpr of expression * expression (* as expr, always metavar *)
34e49164
C
224
225 | EComma of string mcode (* only in arg lists *)
226
227 | DisjExpr of expression list
5636bb2c
C
228 | NestExpr of string mcode (* <.../<+... *) *
229 expression dots *
97111a47 230 string mcode (* ...>/...+> *) *
5636bb2c 231 expression option * multi
34e49164
C
232
233 (* can appear in arg lists, and also inside Nest, as in:
234 if(< ... X ... Y ...>)
235 In the following, the expression option is the WHEN *)
236 | Edots of string mcode (* ... *) * expression option
237 | Ecircles of string mcode (* ooo *) * expression option
238 | Estars of string mcode (* *** *) * expression option
239
240 | OptExp of expression
241 | UniqueExp of expression
242
951c7801
C
243and constraints =
244 NoConstraint
5636bb2c 245 | NotIdCstrt of reconstraint
951c7801 246 | NotExpCstrt of expression list
5636bb2c
C
247 | SubExpCstrt of meta_name list
248
249(* Constraints on Meta-* Identifiers, Functions *)
250and idconstraint =
251 IdNoConstraint
252 | IdNegIdSet of string list * meta_name list
253 | IdRegExpConstraint of reconstraint
254
255and reconstraint =
993936c0
C
256 | IdRegExp of string * Regexp.regexp
257 | IdNotRegExp of string * Regexp.regexp
951c7801 258
34e49164
C
259and form = ANY | ID | LocalID | CONST (* form for MetaExp *)
260
261and expression = base_expression wrap
262
88e71198
C
263and listlen =
264 MetaListLen of meta_name mcode * keep_binding * inherited
265 | CstListLen of int
266 | AnyListLen
34e49164 267
8babbc8f 268and unaryOp = GetRef | GetRefLabel | DeRef | UnPlus | UnMinus | Tilde | Not
34e49164
C
269and assignOp = SimpleAssign | OpAssign of arithOp
270and fixOp = Dec | Inc
271
272and binaryOp = Arith of arithOp | Logical of logicalOp
273and arithOp =
274 Plus | Minus | Mul | Div | Mod | DecLeft | DecRight | And | Or | Xor
275and logicalOp = Inf | Sup | InfEq | SupEq | Eq | NotEq | AndLog | OrLog
276
277and constant =
278 String of string
279 | Char of string
280 | Int of string
281 | Float of string
282
283(* --------------------------------------------------------------------- *)
284(* Types *)
285
286and base_fullType =
17ba0788
C
287 Type of bool (* true if all minus *) *
288 const_vol mcode option * typeC
289 | AsType of fullType * fullType (* as type, always metavar *)
34e49164
C
290 | DisjType of fullType list (* only after iso *)
291 | OptType of fullType
292 | UniqueType of fullType
293
faf9a90c
C
294and base_typeC =
295 BaseType of baseType * string mcode list (* Yoann style *)
296 | SignedT of sign mcode * typeC option
34e49164
C
297 | Pointer of fullType * string mcode (* * *)
298 | FunctionPointer of fullType *
299 string mcode(* ( *)*string mcode(* * *)*string mcode(* ) *)*
300 string mcode (* ( *)*parameter_list*string mcode(* ) *)
301 | FunctionType of bool (* true if all minus for dropping return type *) *
302 fullType option *
303 string mcode (* ( *) * parameter_list *
304 string mcode (* ) *)
305 | Array of fullType * string mcode (* [ *) *
306 expression option * string mcode (* ] *)
c491d8ee
C
307 | EnumName of string mcode (*enum*) * ident option (* name *)
308 | EnumDef of fullType (* either EnumName or metavar *) *
309 string mcode (* { *) * expression dots * string mcode (* } *)
34e49164
C
310 | StructUnionName of structUnion mcode * ident option (* name *)
311 | StructUnionDef of fullType (* either StructUnionName or metavar *) *
312 string mcode (* { *) * declaration dots * string mcode (* } *)
313 | TypeName of string mcode
314
315 | MetaType of meta_name mcode * keep_binding * inherited
316
317and fullType = base_fullType wrap
318and typeC = base_typeC wrap
faf9a90c 319
f3c4ece6
C
320and baseType = VoidType | CharType | ShortType | ShortIntType | IntType
321| DoubleType | LongDoubleType | FloatType
322| LongType | LongIntType | LongLongType | LongLongIntType
323| SizeType | SSizeType | PtrDiffType
34e49164
C
324
325and structUnion = Struct | Union
326
327and sign = Signed | Unsigned
328
329and const_vol = Const | Volatile
330
331(* --------------------------------------------------------------------- *)
332(* Variable declaration *)
333(* Even if the Cocci program specifies a list of declarations, they are
334 split out into multiple declarations of a single variable each. *)
335
336and base_declaration =
337 Init of storage mcode option * fullType * ident * string mcode (*=*) *
338 initialiser * string mcode (*;*)
339 | UnInit of storage mcode option * fullType * ident * string mcode (* ; *)
340 | TyDecl of fullType * string mcode (* ; *)
341 | MacroDecl of ident (* name *) * string mcode (* ( *) *
342 expression dots * string mcode (* ) *) * string mcode (* ; *)
17ba0788
C
343 | MacroDeclInit of ident (* name *) * string mcode (* ( *) *
344 expression dots * string mcode (* ) *) * string mcode (*=*) *
345 initialiser * string mcode (* ; *)
34e49164
C
346 | Typedef of string mcode (*typedef*) * fullType * typeC * string mcode (*;*)
347 | DisjDecl of declaration list
348 | Ddots of string mcode (* ... *) * declaration option (* whencode *)
349
350 | MetaDecl of meta_name mcode * keep_binding * inherited
413ffc02 351 | MetaField of meta_name mcode * keep_binding * inherited
190f1acf 352 | MetaFieldList of meta_name mcode * listlen * keep_binding * inherited
17ba0788 353 | AsDecl of declaration * declaration
34e49164
C
354
355 | OptDecl of declaration
356 | UniqueDecl of declaration
357
358and declaration = base_declaration wrap
359
360(* --------------------------------------------------------------------- *)
361(* Initializers *)
362
363and base_initialiser =
113803cf 364 MetaInit of meta_name mcode * keep_binding * inherited
8f657093 365 | MetaInitList of meta_name mcode * listlen * keep_binding * inherited
17ba0788 366 | AsInit of initialiser * initialiser (* as init, always metavar *)
113803cf 367 | InitExpr of expression
c491d8ee
C
368 | ArInitList of string mcode (*{*) * initialiser dots * string mcode (*}*)
369 | StrInitList of bool (* true if all are - *) *
90aeb998 370 string mcode (*{*) * initialiser list * string mcode (*}*) *
34e49164 371 initialiser list (* whencode: elements that shouldn't appear in init *)
113803cf
C
372 | InitGccExt of
373 designator list (* name *) * string mcode (*=*) *
34e49164
C
374 initialiser (* gccext: *)
375 | InitGccName of ident (* name *) * string mcode (*:*) *
376 initialiser
34e49164 377 | IComma of string mcode (* , *)
c491d8ee 378 | Idots of string mcode (* ... *) * initialiser option (* whencode *)
34e49164
C
379 | OptIni of initialiser
380 | UniqueIni of initialiser
381
113803cf
C
382and designator =
383 DesignatorField of string mcode (* . *) * ident
384 | DesignatorIndex of string mcode (* [ *) * expression * string mcode (* ] *)
385 | DesignatorRange of
386 string mcode (* [ *) * expression * string mcode (* ... *) *
387 expression * string mcode (* ] *)
388
34e49164
C
389and initialiser = base_initialiser wrap
390
391(* --------------------------------------------------------------------- *)
392(* Parameter *)
393
394and base_parameterTypeDef =
395 VoidParam of fullType
396 | Param of fullType * ident option
397
398 | MetaParam of meta_name mcode * keep_binding * inherited
88e71198 399 | MetaParamList of meta_name mcode * listlen * keep_binding * inherited
34e49164
C
400
401 | PComma of string mcode
402
403 | Pdots of string mcode (* ... *)
404 | Pcircles of string mcode (* ooo *)
405
406 | OptParam of parameterTypeDef
407 | UniqueParam of parameterTypeDef
408
409and parameterTypeDef = base_parameterTypeDef wrap
410
411and parameter_list = parameterTypeDef dots
412
413(* --------------------------------------------------------------------- *)
414(* #define Parameters *)
415
416and base_define_param =
417 DParam of ident
418 | DPComma of string mcode
419 | DPdots of string mcode (* ... *)
420 | DPcircles of string mcode (* ooo *)
421 | OptDParam of define_param
422 | UniqueDParam of define_param
423
424and define_param = base_define_param wrap
425
426and base_define_parameters =
427 NoParams
428 | DParams of string mcode(*( *) * define_param dots * string mcode(* )*)
429
430and define_parameters = base_define_parameters wrap
431
432(* --------------------------------------------------------------------- *)
433(* positions *)
434
435(* PER = keep bindings separate, ANY = collect them *)
436and meta_collect = PER | ALL
437
438and meta_pos =
439 MetaPos of meta_name mcode * meta_name list *
440 meta_collect * keep_binding * inherited
34e49164
C
441
442(* --------------------------------------------------------------------- *)
443(* Function declaration *)
444
445and storage = Static | Auto | Register | Extern
446
447(* --------------------------------------------------------------------- *)
448(* Top-level code *)
449
450and base_rule_elem =
451 FunHeader of mcodekind (* before the function header *) *
452 bool (* true if all minus, for dropping static, etc *) *
453 fninfo list * ident (* name *) *
454 string mcode (* ( *) * parameter_list *
455 string mcode (* ) *)
faf9a90c 456 | Decl of mcodekind (* before the decl *) *
34e49164
C
457 bool (* true if all minus *) * declaration
458
459 | SeqStart of string mcode (* { *)
460 | SeqEnd of string mcode (* } *)
461
8babbc8f 462 | ExprStatement of expression option * string mcode (*;*)
34e49164
C
463 | IfHeader of string mcode (* if *) * string mcode (* ( *) *
464 expression * string mcode (* ) *)
465 | Else of string mcode (* else *)
466 | WhileHeader of string mcode (* while *) * string mcode (* ( *) *
467 expression * string mcode (* ) *)
468 | DoHeader of string mcode (* do *)
469 | WhileTail of string mcode (* while *) * string mcode (* ( *) *
470 expression * string mcode (* ) *) *
471 string mcode (* ; *)
472 | ForHeader of string mcode (* for *) * string mcode (* ( *) *
473 expression option * string mcode (*;*) *
474 expression option * string mcode (*;*) *
475 expression option * string mcode (* ) *)
476 | IteratorHeader of ident (* name *) * string mcode (* ( *) *
477 expression dots * string mcode (* ) *)
478 | SwitchHeader of string mcode (* switch *) * string mcode (* ( *) *
479 expression * string mcode (* ) *)
480 | Break of string mcode (* break *) * string mcode (* ; *)
481 | Continue of string mcode (* continue *) * string mcode (* ; *)
482 | Label of ident * string mcode (* : *)
483 | Goto of string mcode (* goto *) * ident * string mcode (* ; *)
484 | Return of string mcode (* return *) * string mcode (* ; *)
485 | ReturnExpr of string mcode (* return *) * expression *
486 string mcode (* ; *)
487
488 | MetaRuleElem of meta_name mcode * keep_binding * inherited
489 | MetaStmt of meta_name mcode * keep_binding * metaStmtInfo *
490 inherited
491 | MetaStmtList of meta_name mcode * keep_binding * inherited
492
493 | Exp of expression
494 | TopExp of expression (* for macros body *)
495 | Ty of fullType (* only at top level *)
1be43e12 496 | TopInit of initialiser (* only at top level *)
34e49164 497 | Include of string mcode (*#include*) * inc_file mcode (*file *)
3a314143 498 | Undef of string mcode (* #define *) * ident (* name *)
34e49164
C
499 | DefineHeader of string mcode (* #define *) * ident (* name *) *
500 define_parameters (*params*)
501 | Case of string mcode (* case *) * expression * string mcode (*:*)
502 | Default of string mcode (* default *) * string mcode (*:*)
503 | DisjRuleElem of rule_elem list
504
505and fninfo =
506 FStorage of storage mcode
507 | FType of fullType
508 | FInline of string mcode
509 | FAttr of string mcode
510
511and metaStmtInfo =
512 NotSequencible | SequencibleAfterDots of dots_whencode list | Sequencible
513
514and rule_elem = base_rule_elem wrap
515
516and base_statement =
708f4980 517 Seq of rule_elem (* { *) *
34e49164
C
518 statement dots * rule_elem (* } *)
519 | IfThen of rule_elem (* header *) * statement * end_info
520 | IfThenElse of rule_elem (* header *) * statement *
521 rule_elem (* else *) * statement * end_info
522 | While of rule_elem (* header *) * statement * end_info
523 | Do of rule_elem (* do *) * statement * rule_elem (* tail *)
524 | For of rule_elem (* header *) * statement * end_info
525 | Iterator of rule_elem (* header *) * statement * end_info (*enditer*)
526 | Switch of rule_elem (* header *) * rule_elem (* { *) *
fc1ad971 527 statement (*decl*) dots * case_line list * rule_elem(*}*)
34e49164
C
528 | Atomic of rule_elem
529 | Disj of statement dots list
5636bb2c 530 | Nest of string mcode (* <.../<+... *) * statement dots *
97111a47 531 string mcode (* ...>/...+> *) *
34e49164
C
532 (statement dots,statement) whencode list * multi *
533 dots_whencode list * dots_whencode list
534 | FunDecl of rule_elem (* header *) * rule_elem (* { *) *
708f4980 535 statement dots * rule_elem (* } *)
34e49164 536 | Define of rule_elem (* header *) * statement dots
17ba0788 537 | AsStmt of statement * statement (* as statement, always metavar *)
34e49164
C
538 | Dots of string mcode (* ... *) *
539 (statement dots,statement) whencode list *
540 dots_whencode list * dots_whencode list
541 | Circles of string mcode (* ooo *) *
542 (statement dots,statement) whencode list *
543 dots_whencode list * dots_whencode list
544 | Stars of string mcode (* *** *) *
545 (statement dots,statement) whencode list *
546 dots_whencode list * dots_whencode list
547 | OptStm of statement
548 | UniqueStm of statement
549
550and ('a,'b) whencode =
551 WhenNot of 'a
552 | WhenAlways of 'b
553 | WhenModifier of when_modifier
1be43e12
C
554 | WhenNotTrue of rule_elem
555 | WhenNotFalse of rule_elem
34e49164
C
556
557and when_modifier =
558 WhenAny
559 | WhenStrict
560 | WhenForall
561 | WhenExists
562
563and dots_whencode =
564 WParen of rule_elem * meta_name (*pren_var*)
565 | Other of statement
566 | Other_dots of statement dots
567
568and statement = base_statement wrap
569
570and base_case_line =
571 CaseLine of rule_elem (* case/default header *) * statement dots
572 | OptCase of case_line
573
574and case_line = base_case_line wrap
575
576and inc_file =
577 Local of inc_elem list
578 | NonLocal of inc_elem list
579
580and inc_elem =
581 IncPath of string
582 | IncDots
583
584and base_top_level =
65038c61 585 NONDECL of statement (* cannot match all of a top-level declaration *)
34e49164
C
586 | CODE of statement dots
587 | FILEINFO of string mcode (* old file *) * string mcode (* new file *)
588 | ERRORWORDS of expression list
589
590and top_level = base_top_level wrap
591
592and rulename =
593 CocciRulename of string option * dependency * string list * string list *
594 exists * bool
595 (* true if the whole thing is an expression *)
faf9a90c
C
596 | GeneratedRulename of string option * dependency *
597 string list * string list * exists * bool
598 (* true if the whole thing is an expression *)
174d1640
C
599 | ScriptRulename of string option (* name *) * string (* language *) *
600 dependency
601 | InitialScriptRulename of string option (* name *) * string (* language *) *
602 dependency
603 | FinalScriptRulename of string option (* name *) * string (* language *) *
604 dependency
34e49164 605
faf9a90c
C
606and ruletype = Normal | Generated
607
34e49164
C
608and rule =
609 CocciRule of string (* name *) *
610 (dependency * string list (* dropped isos *) * exists) *
faf9a90c 611 top_level list * bool list (* true if generates an exp *) * ruletype
174d1640 612 | ScriptRule of string (* name *) *
aba5c457 613 string * dependency *
413ffc02
C
614 (script_meta_name * meta_name * metavar) list *
615 meta_name list (*script vars*) * string
174d1640
C
616 | InitialScriptRule of string (* name *) *
617 string * dependency * string
618 | FinalScriptRule of string (* name *) *
619 string * dependency * string
34e49164 620
aba5c457
C
621and script_meta_name = string option (*string*) * string option (*ast*)
622
34e49164
C
623and dependency =
624 Dep of string (* rule applies for the current binding *)
625 | AntiDep of string (* rule doesn't apply for the current binding *)
626 | EverDep of string (* rule applies for some binding *)
627 | NeverDep of string (* rule never applies for any binding *)
628 | AndDep of dependency * dependency
629 | OrDep of dependency * dependency
7f004419 630 | NoDep | FailDep
34e49164
C
631
632and rule_with_metavars = metavar list * rule
633
634and anything =
635 FullTypeTag of fullType
636 | BaseTypeTag of baseType
637 | StructUnionTag of structUnion
638 | SignTag of sign
639 | IdentTag of ident
640 | ExpressionTag of expression
641 | ConstantTag of constant
642 | UnaryOpTag of unaryOp
643 | AssignOpTag of assignOp
644 | FixOpTag of fixOp
645 | BinaryOpTag of binaryOp
646 | ArithOpTag of arithOp
647 | LogicalOpTag of logicalOp
648 | DeclarationTag of declaration
649 | InitTag of initialiser
650 | StorageTag of storage
651 | IncFileTag of inc_file
652 | Rule_elemTag of rule_elem
653 | StatementTag of statement
654 | CaseLineTag of case_line
655 | ConstVolTag of const_vol
656 | Token of string * info option
c3e37e97 657 | Pragma of added_string list
34e49164
C
658 | Code of top_level
659 | ExprDotsTag of expression dots
660 | ParamDotsTag of parameterTypeDef dots
661 | StmtDotsTag of statement dots
662 | DeclDotsTag of declaration dots
663 | TypeCTag of typeC
664 | ParamTag of parameterTypeDef
665 | SgrepStartTag of string
666 | SgrepEndTag of string
667
668(* --------------------------------------------------------------------- *)
669
978fd7e5 670and exists = Exists | Forall | Undetermined
34e49164
C
671
672(* --------------------------------------------------------------------- *)
673
674val mkToken : string -> anything
675
676val undots : 'a dots -> 'a list
677
951c7801
C
678val lub_count : count -> count -> count
679
34e49164
C
680(* --------------------------------------------------------------------- *)
681
682val rewrap : 'a wrap -> 'b -> 'b wrap
683val rewrap_mcode : 'a mcode -> 'a -> 'a mcode
684val unwrap : 'a wrap -> 'a
685val unwrap_mcode : 'a mcode -> 'a
686val get_mcodekind : 'a mcode -> mcodekind
687val get_line : 'a wrap -> line
688val get_mcode_line : 'a mcode -> line
708f4980 689val get_mcode_col : 'a mcode -> int
34e49164
C
690val get_fvs : 'a wrap -> meta_name list
691val get_wcfvs : ('a wrap,'b wrap) whencode list -> meta_name list
692val set_fvs : meta_name list -> 'a wrap -> 'a wrap
693val get_mfvs : 'a wrap -> meta_name list
694val set_mfvs : meta_name list -> 'a wrap -> 'a wrap
978fd7e5 695val get_fresh : 'a wrap -> (meta_name * seed) list
34e49164
C
696val get_inherited : 'a wrap -> meta_name list
697val get_saved : 'a wrap -> meta_name list
698val get_dots_bef_aft : statement -> dots_bef_aft
699val set_dots_bef_aft : dots_bef_aft -> statement -> statement
700val get_pos : 'a wrap -> meta_name mcode option
701val set_pos : 'a wrap -> meta_name mcode option -> 'a wrap
702val get_test_exp : 'a wrap -> bool
703val set_test_exp : expression -> expression
690d68d1 704val get_safe_decl : 'a wrap -> bool
34e49164
C
705val get_isos : 'a wrap -> (string*anything) list
706val set_isos : 'a wrap -> (string*anything) list -> 'a wrap
8f657093
C
707val get_pos_var : 'a mcode -> meta_pos list
708val set_pos_var : meta_pos list -> 'a mcode -> 'a mcode
34e49164
C
709val drop_pos : 'a mcode -> 'a mcode
710
711val get_meta_name : metavar -> meta_name
712
0708f913
C
713val tag2c : anything -> string
714
34e49164
C
715val no_info : info
716
717val make_meta_rule_elem :
718 string -> mcodekind ->
978fd7e5 719 (meta_name list * (meta_name * seed) list * meta_name list) ->
34e49164
C
720 rule_elem
721
722val make_meta_decl :
723 string -> mcodekind ->
978fd7e5 724 (meta_name list * (meta_name * seed) list * meta_name list) ->
34e49164
C
725 declaration
726
727val make_term : 'a -> 'a wrap
17ba0788 728val make_inherited_term : 'a -> meta_name list (* inherited vars *) -> 'a wrap
34e49164
C
729val make_mcode : 'a -> 'a mcode
730
731val equal_pos : fixpos -> fixpos -> bool