Coccinelle release 1.0.0-rc13
[bpt/coccinelle.git] / parsing_cocci / ast0_cocci.mli
CommitLineData
f537ebc4 1(*
17ba0788
C
2 * Copyright 2012, INRIA
3 * Julia Lawall, Gilles Muller
4 * Copyright 2010-2011, INRIA, University of Copenhagen
f537ebc4
C
5 * Julia Lawall, Rene Rydhof Hansen, Gilles Muller, Nicolas Palix
6 * Copyright 2005-2009, Ecole des Mines de Nantes, University of Copenhagen
7 * Yoann Padioleau, Julia Lawall, Rene Rydhof Hansen, Henrik Stuart, Gilles Muller, Nicolas Palix
8 * This file is part of Coccinelle.
9 *
10 * Coccinelle is free software: you can redistribute it and/or modify
11 * it under the terms of the GNU General Public License as published by
12 * the Free Software Foundation, according to version 2 of the License.
13 *
14 * Coccinelle is distributed in the hope that it will be useful,
15 * but WITHOUT ANY WARRANTY; without even the implied warranty of
16 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
17 * GNU General Public License for more details.
18 *
19 * You should have received a copy of the GNU General Public License
20 * along with Coccinelle. If not, see <http://www.gnu.org/licenses/>.
21 *
22 * The authors reserve the right to distribute this or future versions of
23 * Coccinelle under other licenses.
24 *)
25
26
d6ce1786
C
27# 0 "./ast0_cocci.mli"
28(*
29 * Copyright 2012, INRIA
30 * Julia Lawall, Gilles Muller
31 * Copyright 2010-2011, INRIA, University of Copenhagen
32 * Julia Lawall, Rene Rydhof Hansen, Gilles Muller, Nicolas Palix
33 * Copyright 2005-2009, Ecole des Mines de Nantes, University of Copenhagen
34 * Yoann Padioleau, Julia Lawall, Rene Rydhof Hansen, Henrik Stuart, Gilles Muller, Nicolas Palix
35 * This file is part of Coccinelle.
36 *
37 * Coccinelle is free software: you can redistribute it and/or modify
38 * it under the terms of the GNU General Public License as published by
39 * the Free Software Foundation, according to version 2 of the License.
40 *
41 * Coccinelle is distributed in the hope that it will be useful,
42 * but WITHOUT ANY WARRANTY; without even the implied warranty of
43 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
44 * GNU General Public License for more details.
45 *
46 * You should have received a copy of the GNU General Public License
47 * along with Coccinelle. If not, see <http://www.gnu.org/licenses/>.
48 *
49 * The authors reserve the right to distribute this or future versions of
50 * Coccinelle under other licenses.
51 *)
52
53
feec80c3 54# 0 "./ast0_cocci.mli"
34e49164
C
55(* --------------------------------------------------------------------- *)
56(* Modified code *)
57
58type arity = OPT | UNIQUE | NONE
59
60type token_info =
61 { tline_start : int; tline_end : int;
62 left_offset : int; right_offset : int }
63val default_token_info : token_info
64
65type mcodekind =
8babbc8f 66 MINUS of (Ast_cocci.anything Ast_cocci.replacement * token_info) ref
951c7801 67 | PLUS of Ast_cocci.count
34e49164
C
68 | CONTEXT of (Ast_cocci.anything Ast_cocci.befaft *
69 token_info * token_info) ref
70 | MIXED of (Ast_cocci.anything Ast_cocci.befaft *
71 token_info * token_info) ref
72
0708f913
C
73type position_info = { line_start : int; line_end : int;
74 logical_start : int; logical_end : int;
75 column : int; offset : int; }
76
77type info = { pos_info : position_info;
34e49164
C
78 attachable_start : bool; attachable_end : bool;
79 mcode_start : mcodekind list; mcode_end : mcodekind list;
34e49164 80 (* the following are only for + code *)
c3e37e97 81 strings_before : (Ast_cocci.added_string * position_info) list;
97111a47
C
82 strings_after : (Ast_cocci.added_string * position_info) list;
83 isSymbolIdent : bool; (* is the token a symbol identifier or not *) }
34e49164 84
708f4980 85type 'a mcode =
17ba0788 86 'a * arity * info * mcodekind * anything list ref (* pos, - only *) *
708f4980
C
87 int (* adjacency_index *)
88
34e49164
C
89and 'a wrap =
90 { node : 'a;
91 info : info;
92 index : int ref;
93 mcodekind : mcodekind ref;
94 exp_ty : Type_cocci.typeC option ref; (* only for expressions *)
95 bef_aft : dots_bef_aft; (* only for statements *)
96 true_if_arg : bool; (* true if "arg_exp", only for exprs *)
97 true_if_test : bool; (* true if "test position", only for exprs *)
98 true_if_test_exp : bool;(* true if "test_exp from iso", only for exprs *)
99 (*nonempty if this represents the use of an iso*)
100 iso_info : (string*anything) list }
101
102and dots_bef_aft =
103 NoDots | AddingBetweenDots of statement | DroppingBetweenDots of statement
104
105(* for iso metavariables, true if they can only match nonmodified, unitary
106 metavariables
107 for SP metavariables, true if the metavariable is unitary (valid up to
108 isomorphism phase only) *)
109and pure = Impure | Pure | Context | PureContext (* pure and only context *)
110
111(* --------------------------------------------------------------------- *)
112(* --------------------------------------------------------------------- *)
113(* Dots *)
114
115and 'a base_dots =
116 DOTS of 'a list
117 | CIRCLES of 'a list
118 | STARS of 'a list
119
120and 'a dots = 'a base_dots wrap
121
122(* --------------------------------------------------------------------- *)
123(* Identifier *)
124
125and base_ident =
951c7801 126 Id of string mcode
8babbc8f
C
127 | MetaId of Ast_cocci.meta_name mcode * Ast_cocci.idconstraint *
128 Ast_cocci.seed * pure
951c7801
C
129 | MetaFunc of Ast_cocci.meta_name mcode * Ast_cocci.idconstraint * pure
130 | MetaLocalFunc of Ast_cocci.meta_name mcode * Ast_cocci.idconstraint * pure
d6ce1786 131 | AsIdent of ident * ident (* as ident, always metavar *)
d3f655c6
C
132 | DisjId of string mcode * ident list *
133 string mcode list (* the |s *) * string mcode
34e49164
C
134 | OptIdent of ident
135 | UniqueIdent of ident
136
137and ident = base_ident wrap
138
139(* --------------------------------------------------------------------- *)
140(* Expression *)
141
faf9a90c 142and base_expression =
34e49164
C
143 Ident of ident
144 | Constant of Ast_cocci.constant mcode
145 | FunCall of expression * string mcode (* ( *) *
146 expression dots * string mcode (* ) *)
147 | Assignment of expression * Ast_cocci.assignOp mcode * expression *
148 bool (* true if it can match an initialization *)
17ba0788 149 | Sequence of expression * string mcode (* , *) * expression
34e49164
C
150 | CondExpr of expression * string mcode (* ? *) * expression option *
151 string mcode (* : *) * expression
152 | Postfix of expression * Ast_cocci.fixOp mcode
153 | Infix of expression * Ast_cocci.fixOp mcode
154 | Unary of expression * Ast_cocci.unaryOp mcode
155 | Binary of expression * Ast_cocci.binaryOp mcode * expression
156 | Nested of expression * Ast_cocci.binaryOp mcode * expression
157 | Paren of string mcode (* ( *) * expression *
158 string mcode (* ) *)
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 (* ( *) * typeC * string mcode (* ) *) *
164 expression
165 | SizeOfExpr of string mcode (* sizeof *) * expression
166 | SizeOfType of string mcode (* sizeof *) * string mcode (* ( *) *
167 typeC * string mcode (* ) *)
168 | TypeExp of typeC
7fe62b65
C
169 | Constructor of string mcode (* ( *) * typeC * string mcode (* ) *) *
170 initialiser
951c7801
C
171 | MetaErr of Ast_cocci.meta_name mcode * constraints * pure
172 | MetaExpr of Ast_cocci.meta_name mcode * constraints *
34e49164
C
173 Type_cocci.typeC list option * Ast_cocci.form * pure
174 | MetaExprList of Ast_cocci.meta_name mcode (* only in arglists *) *
175 listlen * pure
17ba0788 176 | AsExpr of expression * expression (* as expr, always metavar *)
34e49164
C
177 | EComma of string mcode (* only in arglists *)
178 | DisjExpr of string mcode * expression list * string mcode list *
179 string mcode
180 | NestExpr of string mcode * expression dots * string mcode *
181 expression option * Ast_cocci.multi
182 | Edots of string mcode (* ... *) * expression option
183 | Ecircles of string mcode (* ooo *) * expression option
184 | Estars of string mcode (* *** *) * expression option
185 | OptExp of expression
186 | UniqueExp of expression
187
188and expression = base_expression wrap
189
951c7801
C
190and constraints =
191 NoConstraint
5636bb2c 192 | NotIdCstrt of Ast_cocci.reconstraint
951c7801 193 | NotExpCstrt of expression list
5636bb2c 194 | SubExpCstrt of Ast_cocci.meta_name list
951c7801 195
88e71198
C
196and listlen =
197 MetaListLen of Ast_cocci.meta_name mcode
198 | CstListLen of int
199 | AnyListLen
34e49164
C
200
201(* --------------------------------------------------------------------- *)
202(* Types *)
203
faf9a90c 204and base_typeC =
34e49164 205 ConstVol of Ast_cocci.const_vol mcode * typeC
faf9a90c
C
206 | BaseType of Ast_cocci.baseType * string mcode list
207 | Signed of Ast_cocci.sign mcode * typeC option
34e49164
C
208 | Pointer of typeC * string mcode (* * *)
209 | FunctionPointer of typeC *
210 string mcode(* ( *)*string mcode(* * *)*string mcode(* ) *)*
211 string mcode (* ( *)*parameter_list*string mcode(* ) *)
212 | FunctionType of typeC option *
213 string mcode (* ( *) * parameter_list *
214 string mcode (* ) *)
215 | Array of typeC * string mcode (* [ *) *
216 expression option * string mcode (* ] *)
c491d8ee
C
217 | EnumName of string mcode (*enum*) * ident option (* name *)
218 | EnumDef of typeC (* either StructUnionName or metavar *) *
219 string mcode (* { *) * expression dots * string mcode (* } *)
34e49164
C
220 | StructUnionName of Ast_cocci.structUnion mcode * ident option (* name *)
221 | StructUnionDef of typeC (* either StructUnionName or metavar *) *
222 string mcode (* { *) * declaration dots * string mcode (* } *)
223 | TypeName of string mcode
224 | MetaType of Ast_cocci.meta_name mcode * pure
17ba0788 225 | AsType of typeC * typeC (* as type, always metavar *)
34e49164
C
226 | DisjType of string mcode * typeC list * (* only after iso *)
227 string mcode list (* the |s *) * string mcode
228 | OptType of typeC
229 | UniqueType of typeC
230
231and typeC = base_typeC wrap
232
233(* --------------------------------------------------------------------- *)
234(* Variable declaration *)
235(* Even if the Cocci program specifies a list of declarations, they are
236 split out into multiple declarations of a single variable each. *)
237
238and base_declaration =
190f1acf 239 MetaDecl of Ast_cocci.meta_name mcode * pure (* variables *)
413ffc02 240 | MetaField of Ast_cocci.meta_name mcode * pure (* structure fields *)
190f1acf 241 | MetaFieldList of Ast_cocci.meta_name mcode * listlen * pure
17ba0788 242 | AsDecl of declaration * declaration
413ffc02 243 | Init of Ast_cocci.storage mcode option * typeC * ident *
34e49164
C
244 string mcode (*=*) * initialiser * string mcode (*;*)
245 | UnInit of Ast_cocci.storage mcode option * typeC * ident *
246 string mcode (* ; *)
247 | TyDecl of typeC * string mcode (* ; *)
248 | MacroDecl of ident (* name *) * string mcode (* ( *) *
249 expression dots * string mcode (* ) *) * string mcode (* ; *)
17ba0788
C
250 | MacroDeclInit of ident (* name *) * string mcode (* ( *) *
251 expression dots * string mcode (* ) *) * string mcode (*=*) *
252 initialiser * string mcode (* ; *)
34e49164
C
253 | Typedef of string mcode (* typedef *) * typeC * typeC * string mcode (*;*)
254 | DisjDecl of string mcode * declaration list * string mcode list *
255 string mcode
256 | Ddots of string mcode (* ... *) * declaration option (* whencode *)
257 | OptDecl of declaration
258 | UniqueDecl of declaration
259
260and declaration = base_declaration wrap
261
262(* --------------------------------------------------------------------- *)
263(* Initializers *)
264
265and base_initialiser =
113803cf 266 MetaInit of Ast_cocci.meta_name mcode * pure
8f657093 267 | MetaInitList of Ast_cocci.meta_name mcode * listlen * pure
17ba0788 268 | AsInit of initialiser * initialiser (* as init, always metavar *)
113803cf 269 | InitExpr of expression
c491d8ee
C
270 | InitList of string mcode (*{*) * initialiser_list * string mcode (*}*) *
271 bool (* true if ordered, false if unordered *)
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 | Idots of string mcode (* ... *) * initialiser option (* whencode *)
279 | OptIni of initialiser
280 | UniqueIni of initialiser
281
113803cf
C
282and designator =
283 DesignatorField of string mcode (* . *) * ident
284 | DesignatorIndex of string mcode (* [ *) * expression * string mcode (* ] *)
285 | DesignatorRange of
286 string mcode (* [ *) * expression * string mcode (* ... *) *
287 expression * string mcode (* ] *)
288
34e49164
C
289and initialiser = base_initialiser wrap
290
291and initialiser_list = initialiser dots
292
293(* --------------------------------------------------------------------- *)
294(* Parameter *)
295
296and base_parameterTypeDef =
297 VoidParam of typeC
298 | Param of typeC * ident option
299 | MetaParam of Ast_cocci.meta_name mcode * pure
300 | MetaParamList of Ast_cocci.meta_name mcode * listlen * pure
301 | PComma of string mcode
302 | Pdots of string mcode (* ... *)
303 | Pcircles of string mcode (* ooo *)
304 | OptParam of parameterTypeDef
305 | UniqueParam of parameterTypeDef
306
307and parameterTypeDef = base_parameterTypeDef wrap
308
309and parameter_list = parameterTypeDef dots
310
311(* --------------------------------------------------------------------- *)
312(* #define Parameters *)
313
314and base_define_param =
315 DParam of ident
316 | DPComma of string mcode
317 | DPdots of string mcode (* ... *)
318 | DPcircles of string mcode (* ooo *)
319 | OptDParam of define_param
320 | UniqueDParam of define_param
321
322and define_param = base_define_param wrap
323
324and base_define_parameters =
325 NoParams
326 | DParams of string mcode(*( *) * define_param dots * string mcode(* )*)
327
328and define_parameters = base_define_parameters wrap
329
330(* --------------------------------------------------------------------- *)
331(* Statement*)
332
333and base_statement =
334 Decl of (info * mcodekind) (* before the decl *) * declaration
335 | Seq of string mcode (* { *) * statement dots *
336 string mcode (* } *)
8babbc8f 337 | ExprStatement of expression option * string mcode (*;*)
34e49164
C
338 | IfThen of string mcode (* if *) * string mcode (* ( *) *
339 expression * string mcode (* ) *) *
340 statement * (info * mcodekind)
341 | IfThenElse of string mcode (* if *) * string mcode (* ( *) *
342 expression * string mcode (* ) *) *
343 statement * string mcode (* else *) * statement *
344 (info * mcodekind)
345 | While of string mcode (* while *) * string mcode (* ( *) *
346 expression * string mcode (* ) *) *
347 statement * (info * mcodekind) (* after info *)
348 | Do of string mcode (* do *) * statement *
349 string mcode (* while *) * string mcode (* ( *) *
350 expression * string mcode (* ) *) *
351 string mcode (* ; *)
352 | For of string mcode (* for *) * string mcode (* ( *) *
353 expression option * string mcode (*;*) *
354 expression option * string mcode (*;*) *
355 expression option * string mcode (* ) *) * statement *
356 (info * mcodekind) (* after info *)
357 | Iterator of ident (* name *) * string mcode (* ( *) *
358 expression dots * string mcode (* ) *) *
359 statement * (info * mcodekind) (* after info *)
360 | Switch of string mcode (* switch *) * string mcode (* ( *) *
361 expression * string mcode (* ) *) * string mcode (* { *) *
fc1ad971 362 statement (*decl*) dots *
34e49164
C
363 case_line dots * string mcode (* } *)
364 | Break of string mcode (* break *) * string mcode (* ; *)
365 | Continue of string mcode (* continue *) * string mcode (* ; *)
366 | Label of ident * string mcode (* : *)
367 | Goto of string mcode (* goto *) * ident * string mcode (* ; *)
368 | Return of string mcode (* return *) * string mcode (* ; *)
369 | ReturnExpr of string mcode (* return *) * expression *
370 string mcode (* ; *)
371 | MetaStmt of Ast_cocci.meta_name mcode * pure
372 | MetaStmtList of Ast_cocci.meta_name mcode (*only in statement lists*) *
373 pure
17ba0788 374 | AsStmt of statement * statement (* as statement, always metavar *)
34e49164
C
375 | Exp of expression (* only in dotted statement lists *)
376 | TopExp of expression (* for macros body *)
377 | Ty of typeC (* only at top level *)
1be43e12 378 | TopInit of initialiser (* only at top level *)
34e49164
C
379 | Disj of string mcode * statement dots list * string mcode list *
380 string mcode
381 | Nest of string mcode * statement dots * string mcode *
382 (statement dots,statement) whencode list * Ast_cocci.multi
383 | Dots of string mcode (* ... *) *
384 (statement dots,statement) whencode list
385 | Circles of string mcode (* ooo *) *
386 (statement dots,statement) whencode list
387 | Stars of string mcode (* *** *) *
388 (statement dots,statement) whencode list
389 | FunDecl of (info * mcodekind) (* before the function decl *) *
390 fninfo list * ident (* name *) *
391 string mcode (* ( *) * parameter_list * string mcode (* ) *) *
392 string mcode (* { *) * statement dots *
393 string mcode (* } *)
394 | Include of string mcode (* #include *) * Ast_cocci.inc_file mcode(* file *)
3a314143 395 | Undef of string mcode (* #define *) * ident (* name *)
34e49164
C
396 | Define of string mcode (* #define *) * ident (* name *) *
397 define_parameters (*params*) * statement dots
398 | OptStm of statement
399 | UniqueStm of statement
400
401and fninfo =
402 FStorage of Ast_cocci.storage mcode
403 | FType of typeC
404 | FInline of string mcode
405 | FAttr of string mcode
406
407and ('a,'b) whencode =
408 WhenNot of 'a
409 | WhenAlways of 'b
410 | WhenModifier of Ast_cocci.when_modifier
1be43e12
C
411 | WhenNotTrue of expression
412 | WhenNotFalse of expression
34e49164
C
413
414and statement = base_statement wrap
415
416and base_case_line =
417 Default of string mcode (* default *) * string mcode (*:*) * statement dots
418 | Case of string mcode (* case *) * expression * string mcode (*:*) *
419 statement dots
fc1ad971
C
420 | DisjCase of string mcode * case_line list *
421 string mcode list (* the |s *) * string mcode
34e49164
C
422 | OptCase of case_line
423
424and case_line = base_case_line wrap
425
426(* --------------------------------------------------------------------- *)
427(* Positions *)
428
429and meta_pos =
430 MetaPos of Ast_cocci.meta_name mcode * Ast_cocci.meta_name list *
431 Ast_cocci.meta_collect
34e49164
C
432
433(* --------------------------------------------------------------------- *)
434(* Top-level code *)
435
436and base_top_level =
65038c61
C
437 NONDECL of statement (* cannot match all of a top-level declaration *)
438 | TOPCODE of statement dots
34e49164
C
439 | CODE of statement dots
440 | FILEINFO of string mcode (* old file *) * string mcode (* new file *)
441 | ERRORWORDS of expression list
442 | OTHER of statement (* temporary, disappears after top_level.ml *)
443
444and top_level = base_top_level wrap
445and rule = top_level list
446
447and parsed_rule =
448 CocciRule of
449 (rule * Ast_cocci.metavar list *
450 (string list * string list * Ast_cocci.dependency * string *
451 Ast_cocci.exists)) *
faf9a90c 452 (rule * Ast_cocci.metavar list) * Ast_cocci.ruletype
174d1640
C
453 | ScriptRule of string (* name *) *
454 string * Ast_cocci.dependency *
aba5c457 455 (Ast_cocci.script_meta_name *
413ffc02
C
456 Ast_cocci.meta_name * Ast_cocci.metavar) list (*inherited vars*) *
457 Ast_cocci.meta_name list (*script vars*) *
34e49164 458 string
174d1640 459 | InitialScriptRule of string (* name *) *
c3e37e97 460 string (*language*) * Ast_cocci.dependency * string (*code*)
174d1640 461 | FinalScriptRule of string (* name *) *
c3e37e97 462 string (*language*) * Ast_cocci.dependency * string (*code*)
34e49164
C
463
464(* --------------------------------------------------------------------- *)
465
97111a47
C
466and dependency =
467 Dep of string (* rule applies for the current binding *)
468 | AntiDep of dependency (* rule doesn't apply for the current binding *)
469 | EverDep of string (* rule applies for some binding *)
470 | NeverDep of string (* rule never applies for any binding *)
471 | AndDep of dependency * dependency
472 | OrDep of dependency * dependency
473 | NoDep | FailDep
474
475(* --------------------------------------------------------------------- *)
476
34e49164
C
477and anything =
478 DotsExprTag of expression dots
479 | DotsInitTag of initialiser dots
480 | DotsParamTag of parameterTypeDef dots
481 | DotsStmtTag of statement dots
482 | DotsDeclTag of declaration dots
483 | DotsCaseTag of case_line dots
484 | IdentTag of ident
485 | ExprTag of expression
486 | ArgExprTag of expression (* for isos *)
487 | TestExprTag of expression (* for isos *)
488 | TypeCTag of typeC
489 | ParamTag of parameterTypeDef
490 | InitTag of initialiser
491 | DeclTag of declaration
492 | StmtTag of statement
493 | CaseLineTag of case_line
494 | TopTag of top_level
495 | IsoWhenTag of Ast_cocci.when_modifier (*only for when code, in iso phase*)
1be43e12
C
496 | IsoWhenTTag of expression(*only for when code, in iso phase*)
497 | IsoWhenFTag of expression(*only for when code, in iso phase*)
17ba0788
C
498 | MetaPosTag of meta_pos
499 | HiddenVarTag of anything list (* in iso_compile/pattern only *)
34e49164
C
500
501val dotsExpr : expression dots -> anything
502val dotsInit : initialiser dots -> anything
503val dotsParam : parameterTypeDef dots -> anything
504val dotsStmt : statement dots -> anything
505val dotsDecl : declaration dots -> anything
506val dotsCase : case_line dots -> anything
507val ident : ident -> anything
508val expr : expression -> anything
509val typeC : typeC -> anything
510val param : parameterTypeDef -> anything
511val ini : initialiser -> anything
512val decl : declaration -> anything
513val stmt : statement -> anything
514val case_line : case_line -> anything
515val top : top_level -> anything
516
517(* --------------------------------------------------------------------- *)
518
519val undots : 'a dots -> 'a list
520
521(* --------------------------------------------------------------------- *)
522(* Avoid cluttering the parser. Calculated in compute_lines.ml. *)
523
524val default_info : unit -> info
525val default_befaft : unit -> mcodekind
526val context_befaft : unit -> mcodekind
527val wrap : 'a -> 'a wrap
528val context_wrap : 'a -> 'a wrap
529val unwrap : 'a wrap -> 'a
530val unwrap_mcode : 'a mcode -> 'a
531val rewrap : 'a wrap -> 'b -> 'b wrap
532val rewrap_mcode : 'a mcode -> 'b -> 'b mcode
533val copywrap : 'a wrap -> 'b -> 'b wrap
17ba0788
C
534val get_pos : 'a mcode -> anything list
535val get_pos_ref : 'a mcode -> anything list ref
536val set_pos : anything list -> 'a mcode -> 'a mcode
34e49164
C
537val get_info : 'a wrap -> info
538val set_info : 'a wrap -> info -> 'a wrap
539val get_index : 'a wrap -> int
540val set_index : 'a wrap -> int -> unit
541val get_line : 'a wrap -> int
542val get_line_end : 'a wrap -> int
543val get_mcodekind : 'a wrap -> mcodekind
544val get_mcode_mcodekind : 'a mcode -> mcodekind
545val get_mcodekind_ref : 'a wrap -> mcodekind ref
546val set_mcodekind : 'a wrap -> mcodekind -> unit
547val set_type : 'a wrap -> Type_cocci.typeC option -> unit
548val get_type : 'a wrap -> Type_cocci.typeC option
549val set_dots_bef_aft : statement -> dots_bef_aft -> statement
550val get_dots_bef_aft : 'a wrap -> dots_bef_aft
551val set_arg_exp : expression -> expression
552val get_arg_exp : expression -> bool
553val set_test_pos : expression -> expression
554val get_test_pos : 'a wrap -> bool
555val set_test_exp : expression -> expression
556val get_test_exp : 'a wrap -> bool
557val set_iso : 'a wrap -> (string*anything) list -> 'a wrap
558val get_iso : 'a wrap -> (string*anything) list
559val fresh_index : unit -> int
560val set_mcode_data : 'a -> 'a mcode -> 'a mcode
561val make_mcode : 'a -> 'a mcode
562val make_mcode_info : 'a -> info -> 'a mcode
c491d8ee 563val make_minus_mcode : 'a -> 'a mcode
34e49164 564
17ba0788
C
565val meta_pos_name : anything -> Ast_cocci.meta_name mcode
566
34e49164
C
567val ast0_type_to_type : typeC -> Type_cocci.typeC
568val reverse_type : Type_cocci.typeC -> base_typeC
569exception TyConv
570
571val lub_pure : pure -> pure -> pure
572
573(* --------------------------------------------------------------------- *)
574
575val rule_name : string ref (* for the convenience of the parser *)