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