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