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