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