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