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