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