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