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