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