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