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