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