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