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