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