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