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