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