Release coccinelle-0.1
[bpt/coccinelle.git] / parsing_cocci / ast_cocci.mli
1 (* --------------------------------------------------------------------- *)
2 (* Modified code *)
3
4 type info = { line : int; column : int;
5 strbef : string list; straft : string list }
6 type line = int
7 type meta_name = string * string
8 type 'a wrap =
9 {node : 'a;
10 node_line : line;
11 free_vars : meta_name list; (*free vars*)
12 minus_free_vars : meta_name list; (*minus free vars*)
13 fresh_vars : meta_name list; (*fresh vars*)
14 inherited : meta_name list; (*inherited vars*)
15 saved_witness : meta_name list; (*witness vars*)
16 bef_aft : dots_bef_aft;
17 pos_info : meta_name mcode option; (* pos info, try not to duplicate *)
18 true_if_test_exp : bool;(* true if "test_exp from iso", only for exprs *)
19 (* isos relevant to the term; ultimately only used for rule_elems *)
20 iso_info : (string*anything) list }
21
22 and 'a befaft =
23 BEFORE of 'a list list
24 | AFTER of 'a list list
25 | BEFOREAFTER of 'a list list * 'a list list
26 | NOTHING
27
28 and 'a mcode = 'a * info * mcodekind * meta_pos (* pos variable *)
29 (* pos is an offset indicating where in the C code the mcodekind has an
30 effect *)
31 and mcodekind =
32 MINUS of pos * anything list list
33 | CONTEXT of pos * anything befaft
34 | PLUS
35 and fixpos =
36 Real of int (* charpos *) | Virt of int * int (* charpos + offset *)
37 and pos = NoPos | DontCarePos | FixPos of (fixpos * fixpos)
38
39 and dots_bef_aft =
40 NoDots
41 | AddingBetweenDots of statement * int (*index of let var*)
42 | DroppingBetweenDots of statement * int (*index of let var*)
43
44 and inherited = Type_cocci.inherited
45 and keep_binding = Type_cocci.keep_binding
46 and multi = bool (*true if a nest is one or more, false if it is zero or more*)
47
48 and end_info =
49 meta_name list (*free vars*) * meta_name list (*inherited vars*) *
50 meta_name list (*witness vars*) * mcodekind
51
52 (* --------------------------------------------------------------------- *)
53 (* Metavariables *)
54
55 and arity = UNIQUE | OPT | MULTI | NONE
56
57 and metavar =
58 MetaIdDecl of arity * meta_name (* name *)
59 | MetaFreshIdDecl of arity * meta_name (* name *)
60 | MetaTypeDecl of arity * meta_name (* name *)
61 | MetaListlenDecl of meta_name (* name *)
62 | MetaParamDecl of arity * meta_name (* name *)
63 | MetaParamListDecl of arity * meta_name (*name*) * meta_name option (*len*)
64 | MetaConstDecl of
65 arity * meta_name (* name *) * Type_cocci.typeC list option
66 | MetaErrDecl of arity * meta_name (* name *)
67 | MetaExpDecl of
68 arity * meta_name (* name *) * Type_cocci.typeC list option
69 | MetaIdExpDecl of
70 arity * meta_name (* name *) * Type_cocci.typeC list option
71 | MetaLocalIdExpDecl of
72 arity * meta_name (* name *) * Type_cocci.typeC list option
73 | MetaExpListDecl of arity * meta_name (*name*) * meta_name option (*len*)
74 | MetaStmDecl of arity * meta_name (* name *)
75 | MetaStmListDecl of arity * meta_name (* name *)
76 | MetaFuncDecl of arity * meta_name (* name *)
77 | MetaLocalFuncDecl of arity * meta_name (* name *)
78 | MetaPosDecl of arity * meta_name (* name *)
79 | MetaDeclarerDecl of arity * meta_name (* name *)
80 | MetaIteratorDecl of arity * meta_name (* name *)
81
82 (* --------------------------------------------------------------------- *)
83 (* --------------------------------------------------------------------- *)
84 (* Dots *)
85
86 and 'a base_dots =
87 DOTS of 'a list
88 | CIRCLES of 'a list
89 | STARS of 'a list
90
91 and 'a dots = 'a base_dots wrap
92
93 (* --------------------------------------------------------------------- *)
94 (* Identifier *)
95
96 and base_ident =
97 Id of string mcode
98
99 | MetaId of meta_name mcode * ident list * keep_binding * inherited
100 | MetaFunc of meta_name mcode * ident list * keep_binding * inherited
101 | MetaLocalFunc of meta_name mcode * ident list * keep_binding * inherited
102
103 | OptIdent of ident
104 | UniqueIdent of ident
105
106 and ident = base_ident wrap
107
108 (* --------------------------------------------------------------------- *)
109 (* Expression *)
110
111 and base_expression =
112 Ident of ident
113 | Constant of constant mcode
114 | FunCall of expression * string mcode (* ( *) *
115 expression dots * string mcode (* ) *)
116 | Assignment of expression * assignOp mcode * expression * bool
117 | CondExpr of expression * string mcode (* ? *) * expression option *
118 string mcode (* : *) * expression
119 | Postfix of expression * fixOp mcode
120 | Infix of expression * fixOp mcode
121 | Unary of expression * unaryOp mcode
122 | Binary of expression * binaryOp mcode * expression
123 | Nested of expression * binaryOp mcode * expression
124 | ArrayAccess of expression * string mcode (* [ *) * expression *
125 string mcode (* ] *)
126 | RecordAccess of expression * string mcode (* . *) * ident
127 | RecordPtAccess of expression * string mcode (* -> *) * ident
128 | Cast of string mcode (* ( *) * fullType * string mcode (* ) *) *
129 expression
130
131 | SizeOfExpr of string mcode (* sizeof *) * expression
132 | SizeOfType of string mcode (* sizeof *) * string mcode (* ( *) *
133 fullType * string mcode (* ) *)
134 | TypeExp of fullType
135
136 | Paren of string mcode (* ( *) * expression *
137 string mcode (* ) *)
138
139 | MetaErr of meta_name mcode * expression list * keep_binding *
140 inherited
141 | MetaExpr of meta_name mcode * expression list * keep_binding *
142 Type_cocci.typeC list option * form * inherited
143 | MetaExprList of meta_name mcode * listlen option *
144 keep_binding * inherited (* only in arg lists *)
145
146 | EComma of string mcode (* only in arg lists *)
147
148 | DisjExpr of expression list
149 | NestExpr of expression dots * expression option * multi
150
151 (* can appear in arg lists, and also inside Nest, as in:
152 if(< ... X ... Y ...>)
153 In the following, the expression option is the WHEN *)
154 | Edots of string mcode (* ... *) * expression option
155 | Ecircles of string mcode (* ooo *) * expression option
156 | Estars of string mcode (* *** *) * expression option
157
158 | OptExp of expression
159 | UniqueExp of expression
160
161 and form = ANY | ID | LocalID | CONST (* form for MetaExp *)
162
163 and expression = base_expression wrap
164
165 and listlen = meta_name mcode * keep_binding * inherited
166
167 and unaryOp = GetRef | DeRef | UnPlus | UnMinus | Tilde | Not
168 and assignOp = SimpleAssign | OpAssign of arithOp
169 and fixOp = Dec | Inc
170
171 and binaryOp = Arith of arithOp | Logical of logicalOp
172 and arithOp =
173 Plus | Minus | Mul | Div | Mod | DecLeft | DecRight | And | Or | Xor
174 and logicalOp = Inf | Sup | InfEq | SupEq | Eq | NotEq | AndLog | OrLog
175
176 and constant =
177 String of string
178 | Char of string
179 | Int of string
180 | Float of string
181
182 (* --------------------------------------------------------------------- *)
183 (* Types *)
184
185 and base_fullType =
186 Type of const_vol mcode option * typeC
187 | DisjType of fullType list (* only after iso *)
188 | OptType of fullType
189 | UniqueType of fullType
190
191 and base_typeC =
192 BaseType of baseType mcode * sign mcode option
193 | ImplicitInt of sign mcode
194 | Pointer of fullType * string mcode (* * *)
195 | FunctionPointer of fullType *
196 string mcode(* ( *)*string mcode(* * *)*string mcode(* ) *)*
197 string mcode (* ( *)*parameter_list*string mcode(* ) *)
198 | FunctionType of bool (* true if all minus for dropping return type *) *
199 fullType option *
200 string mcode (* ( *) * parameter_list *
201 string mcode (* ) *)
202 | Array of fullType * string mcode (* [ *) *
203 expression option * string mcode (* ] *)
204 | StructUnionName of structUnion mcode * ident option (* name *)
205 | StructUnionDef of fullType (* either StructUnionName or metavar *) *
206 string mcode (* { *) * declaration dots * string mcode (* } *)
207 | TypeName of string mcode
208
209 | MetaType of meta_name mcode * keep_binding * inherited
210
211 and fullType = base_fullType wrap
212 and typeC = base_typeC wrap
213
214 and baseType = VoidType | CharType | ShortType | IntType | DoubleType
215 | FloatType | LongType
216
217 and structUnion = Struct | Union
218
219 and sign = Signed | Unsigned
220
221 and const_vol = Const | Volatile
222
223 (* --------------------------------------------------------------------- *)
224 (* Variable declaration *)
225 (* Even if the Cocci program specifies a list of declarations, they are
226 split out into multiple declarations of a single variable each. *)
227
228 and base_declaration =
229 Init of storage mcode option * fullType * ident * string mcode (*=*) *
230 initialiser * string mcode (*;*)
231 | UnInit of storage mcode option * fullType * ident * string mcode (* ; *)
232 | TyDecl of fullType * string mcode (* ; *)
233 | MacroDecl of ident (* name *) * string mcode (* ( *) *
234 expression dots * string mcode (* ) *) * string mcode (* ; *)
235 | Typedef of string mcode (*typedef*) * fullType * typeC * string mcode (*;*)
236 | DisjDecl of declaration list
237 | Ddots of string mcode (* ... *) * declaration option (* whencode *)
238
239 | MetaDecl of meta_name mcode * keep_binding * inherited
240
241 | OptDecl of declaration
242 | UniqueDecl of declaration
243
244 and declaration = base_declaration wrap
245
246 (* --------------------------------------------------------------------- *)
247 (* Initializers *)
248
249 and base_initialiser =
250 InitExpr of expression
251 | InitList of string mcode (*{*) * initialiser list * string mcode (*}*) *
252 initialiser list (* whencode: elements that shouldn't appear in init *)
253 | InitGccDotName of
254 string mcode (*.*) * ident (* name *) * string mcode (*=*) *
255 initialiser (* gccext: *)
256 | InitGccName of ident (* name *) * string mcode (*:*) *
257 initialiser
258 | InitGccIndex of
259 string mcode (*[*) * expression * string mcode (*]*) *
260 string mcode (*=*) * initialiser
261 | InitGccRange of
262 string mcode (*[*) * expression * string mcode (*...*) *
263 expression * string mcode (*]*) * string mcode (*=*) * initialiser
264 | IComma of string mcode (* , *)
265 | OptIni of initialiser
266 | UniqueIni of initialiser
267
268 and initialiser = base_initialiser wrap
269
270 (* --------------------------------------------------------------------- *)
271 (* Parameter *)
272
273 and base_parameterTypeDef =
274 VoidParam of fullType
275 | Param of fullType * ident option
276
277 | MetaParam of meta_name mcode * keep_binding * inherited
278 | MetaParamList of meta_name mcode * listlen option * keep_binding *
279 inherited
280
281 | PComma of string mcode
282
283 | Pdots of string mcode (* ... *)
284 | Pcircles of string mcode (* ooo *)
285
286 | OptParam of parameterTypeDef
287 | UniqueParam of parameterTypeDef
288
289 and parameterTypeDef = base_parameterTypeDef wrap
290
291 and parameter_list = parameterTypeDef dots
292
293 (* --------------------------------------------------------------------- *)
294 (* #define Parameters *)
295
296 and base_define_param =
297 DParam of ident
298 | DPComma of string mcode
299 | DPdots of string mcode (* ... *)
300 | DPcircles of string mcode (* ooo *)
301 | OptDParam of define_param
302 | UniqueDParam of define_param
303
304 and define_param = base_define_param wrap
305
306 and base_define_parameters =
307 NoParams
308 | DParams of string mcode(*( *) * define_param dots * string mcode(* )*)
309
310 and define_parameters = base_define_parameters wrap
311
312 (* --------------------------------------------------------------------- *)
313 (* positions *)
314
315 (* PER = keep bindings separate, ANY = collect them *)
316 and meta_collect = PER | ALL
317
318 and meta_pos =
319 MetaPos of meta_name mcode * meta_name list *
320 meta_collect * keep_binding * inherited
321 | NoMetaPos
322
323 (* --------------------------------------------------------------------- *)
324 (* Function declaration *)
325
326 and storage = Static | Auto | Register | Extern
327
328 (* --------------------------------------------------------------------- *)
329 (* Top-level code *)
330
331 and base_rule_elem =
332 FunHeader of mcodekind (* before the function header *) *
333 bool (* true if all minus, for dropping static, etc *) *
334 fninfo list * ident (* name *) *
335 string mcode (* ( *) * parameter_list *
336 string mcode (* ) *)
337 | Decl of mcodekind (* before the decl *) *
338 bool (* true if all minus *) * declaration
339
340 | SeqStart of string mcode (* { *)
341 | SeqEnd of string mcode (* } *)
342
343 | ExprStatement of expression * string mcode (*;*)
344 | IfHeader of string mcode (* if *) * string mcode (* ( *) *
345 expression * string mcode (* ) *)
346 | Else of string mcode (* else *)
347 | WhileHeader of string mcode (* while *) * string mcode (* ( *) *
348 expression * string mcode (* ) *)
349 | DoHeader of string mcode (* do *)
350 | WhileTail of string mcode (* while *) * string mcode (* ( *) *
351 expression * string mcode (* ) *) *
352 string mcode (* ; *)
353 | ForHeader of string mcode (* for *) * string mcode (* ( *) *
354 expression option * string mcode (*;*) *
355 expression option * string mcode (*;*) *
356 expression option * string mcode (* ) *)
357 | IteratorHeader of ident (* name *) * string mcode (* ( *) *
358 expression dots * string mcode (* ) *)
359 | SwitchHeader of string mcode (* switch *) * string mcode (* ( *) *
360 expression * string mcode (* ) *)
361 | Break of string mcode (* break *) * string mcode (* ; *)
362 | Continue of string mcode (* continue *) * string mcode (* ; *)
363 | Label of ident * string mcode (* : *)
364 | Goto of string mcode (* goto *) * ident * string mcode (* ; *)
365 | Return of string mcode (* return *) * string mcode (* ; *)
366 | ReturnExpr of string mcode (* return *) * expression *
367 string mcode (* ; *)
368
369 | MetaRuleElem of meta_name mcode * keep_binding * inherited
370 | MetaStmt of meta_name mcode * keep_binding * metaStmtInfo *
371 inherited
372 | MetaStmtList of meta_name mcode * keep_binding * inherited
373
374 | Exp of expression
375 | TopExp of expression (* for macros body *)
376 | Ty of fullType (* only at top level *)
377 | Include of string mcode (*#include*) * inc_file mcode (*file *)
378 | DefineHeader of string mcode (* #define *) * ident (* name *) *
379 define_parameters (*params*)
380 | Case of string mcode (* case *) * expression * string mcode (*:*)
381 | Default of string mcode (* default *) * string mcode (*:*)
382 | DisjRuleElem of rule_elem list
383
384 and fninfo =
385 FStorage of storage mcode
386 | FType of fullType
387 | FInline of string mcode
388 | FAttr of string mcode
389
390 and metaStmtInfo =
391 NotSequencible | SequencibleAfterDots of dots_whencode list | Sequencible
392
393 and rule_elem = base_rule_elem wrap
394
395 and base_statement =
396 Seq of rule_elem (* { *) * statement dots *
397 statement dots * rule_elem (* } *)
398 | IfThen of rule_elem (* header *) * statement * end_info
399 | IfThenElse of rule_elem (* header *) * statement *
400 rule_elem (* else *) * statement * end_info
401 | While of rule_elem (* header *) * statement * end_info
402 | Do of rule_elem (* do *) * statement * rule_elem (* tail *)
403 | For of rule_elem (* header *) * statement * end_info
404 | Iterator of rule_elem (* header *) * statement * end_info (*enditer*)
405 | Switch of rule_elem (* header *) * rule_elem (* { *) *
406 case_line list * rule_elem (* } *)
407 | Atomic of rule_elem
408 | Disj of statement dots list
409 | Nest of statement dots *
410 (statement dots,statement) whencode list * multi *
411 dots_whencode list * dots_whencode list
412 | FunDecl of rule_elem (* header *) * rule_elem (* { *) *
413 statement dots * statement dots * rule_elem (* } *)
414 | Define of rule_elem (* header *) * statement dots
415 | Dots of string mcode (* ... *) *
416 (statement dots,statement) whencode list *
417 dots_whencode list * dots_whencode list
418 | Circles of string mcode (* ooo *) *
419 (statement dots,statement) whencode list *
420 dots_whencode list * dots_whencode list
421 | Stars of string mcode (* *** *) *
422 (statement dots,statement) whencode list *
423 dots_whencode list * dots_whencode list
424 | OptStm of statement
425 | UniqueStm of statement
426
427 and ('a,'b) whencode =
428 WhenNot of 'a
429 | WhenAlways of 'b
430 | WhenModifier of when_modifier
431
432 and when_modifier =
433 WhenAny
434 | WhenStrict
435 | WhenForall
436 | WhenExists
437
438 and dots_whencode =
439 WParen of rule_elem * meta_name (*pren_var*)
440 | Other of statement
441 | Other_dots of statement dots
442
443 and statement = base_statement wrap
444
445 and base_case_line =
446 CaseLine of rule_elem (* case/default header *) * statement dots
447 | OptCase of case_line
448
449 and case_line = base_case_line wrap
450
451 and inc_file =
452 Local of inc_elem list
453 | NonLocal of inc_elem list
454
455 and inc_elem =
456 IncPath of string
457 | IncDots
458
459 and base_top_level =
460 DECL of statement
461 | CODE of statement dots
462 | FILEINFO of string mcode (* old file *) * string mcode (* new file *)
463 | ERRORWORDS of expression list
464
465 and top_level = base_top_level wrap
466
467 and rulename =
468 CocciRulename of string option * dependency * string list * string list *
469 exists * bool
470 (* true if the whole thing is an expression *)
471 | ScriptRulename of string * dependency
472
473 and rule =
474 CocciRule of string (* name *) *
475 (dependency * string list (* dropped isos *) * exists) *
476 top_level list * bool list (* true if generates an exp *)
477 | ScriptRule of string * dependency * (string * meta_name) list * string
478
479 and dependency =
480 Dep of string (* rule applies for the current binding *)
481 | AntiDep of string (* rule doesn't apply for the current binding *)
482 | EverDep of string (* rule applies for some binding *)
483 | NeverDep of string (* rule never applies for any binding *)
484 | AndDep of dependency * dependency
485 | OrDep of dependency * dependency
486 | NoDep
487
488 and rule_with_metavars = metavar list * rule
489
490 and anything =
491 FullTypeTag of fullType
492 | BaseTypeTag of baseType
493 | StructUnionTag of structUnion
494 | SignTag of sign
495 | IdentTag of ident
496 | ExpressionTag of expression
497 | ConstantTag of constant
498 | UnaryOpTag of unaryOp
499 | AssignOpTag of assignOp
500 | FixOpTag of fixOp
501 | BinaryOpTag of binaryOp
502 | ArithOpTag of arithOp
503 | LogicalOpTag of logicalOp
504 | DeclarationTag of declaration
505 | InitTag of initialiser
506 | StorageTag of storage
507 | IncFileTag of inc_file
508 | Rule_elemTag of rule_elem
509 | StatementTag of statement
510 | CaseLineTag of case_line
511 | ConstVolTag of const_vol
512 | Token of string * info option
513 | Code of top_level
514 | ExprDotsTag of expression dots
515 | ParamDotsTag of parameterTypeDef dots
516 | StmtDotsTag of statement dots
517 | DeclDotsTag of declaration dots
518 | TypeCTag of typeC
519 | ParamTag of parameterTypeDef
520 | SgrepStartTag of string
521 | SgrepEndTag of string
522
523 (* --------------------------------------------------------------------- *)
524
525 and exists = Exists | Forall | ReverseForall | Undetermined
526
527 (* --------------------------------------------------------------------- *)
528
529 val mkToken : string -> anything
530
531 val undots : 'a dots -> 'a list
532
533 (* --------------------------------------------------------------------- *)
534
535 val rewrap : 'a wrap -> 'b -> 'b wrap
536 val rewrap_mcode : 'a mcode -> 'a -> 'a mcode
537 val unwrap : 'a wrap -> 'a
538 val unwrap_mcode : 'a mcode -> 'a
539 val get_mcodekind : 'a mcode -> mcodekind
540 val get_line : 'a wrap -> line
541 val get_mcode_line : 'a mcode -> line
542 val get_fvs : 'a wrap -> meta_name list
543 val get_wcfvs : ('a wrap,'b wrap) whencode list -> meta_name list
544 val set_fvs : meta_name list -> 'a wrap -> 'a wrap
545 val get_mfvs : 'a wrap -> meta_name list
546 val set_mfvs : meta_name list -> 'a wrap -> 'a wrap
547 val get_fresh : 'a wrap -> meta_name list
548 val get_inherited : 'a wrap -> meta_name list
549 val get_saved : 'a wrap -> meta_name list
550 val get_dots_bef_aft : statement -> dots_bef_aft
551 val set_dots_bef_aft : dots_bef_aft -> statement -> statement
552 val get_pos : 'a wrap -> meta_name mcode option
553 val set_pos : 'a wrap -> meta_name mcode option -> 'a wrap
554 val get_test_exp : 'a wrap -> bool
555 val set_test_exp : expression -> expression
556 val get_isos : 'a wrap -> (string*anything) list
557 val set_isos : 'a wrap -> (string*anything) list -> 'a wrap
558 val get_pos_var : 'a mcode -> meta_pos
559 val set_pos_var : meta_pos -> 'a mcode -> 'a mcode
560 val drop_pos : 'a mcode -> 'a mcode
561
562 val get_meta_name : metavar -> meta_name
563
564 val no_info : info
565
566 val make_meta_rule_elem :
567 string -> mcodekind ->
568 (meta_name list * meta_name list * meta_name list) ->
569 rule_elem
570
571 val make_meta_decl :
572 string -> mcodekind ->
573 (meta_name list * meta_name list * meta_name list) ->
574 declaration
575
576 val make_term : 'a -> 'a wrap
577 val make_mcode : 'a -> 'a mcode
578
579 val equal_pos : fixpos -> fixpos -> bool