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