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