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