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