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