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