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