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