Coccinelle release 1.0.0-rc3
[bpt/coccinelle.git] / parsing_cocci / ast_cocci.ml
CommitLineData
f537ebc4
C
1(*
2 * Copyright 2010, INRIA, University of Copenhagen
3 * Julia Lawall, Rene Rydhof Hansen, Gilles Muller, Nicolas Palix
4 * Copyright 2005-2009, Ecole des Mines de Nantes, University of Copenhagen
5 * Yoann Padioleau, Julia Lawall, Rene Rydhof Hansen, Henrik Stuart, Gilles Muller, Nicolas Palix
6 * This file is part of Coccinelle.
7 *
8 * Coccinelle is free software: you can redistribute it and/or modify
9 * it under the terms of the GNU General Public License as published by
10 * the Free Software Foundation, according to version 2 of the License.
11 *
12 * Coccinelle is distributed in the hope that it will be useful,
13 * but WITHOUT ANY WARRANTY; without even the implied warranty of
14 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
15 * GNU General Public License for more details.
16 *
17 * You should have received a copy of the GNU General Public License
18 * along with Coccinelle. If not, see <http://www.gnu.org/licenses/>.
19 *
20 * The authors reserve the right to distribute this or future versions of
21 * Coccinelle under other licenses.
22 *)
23
24
34e49164
C
25(* --------------------------------------------------------------------- *)
26(* Modified code *)
27
190f1acf 28type added_string = Noindent of string | Indent of string | Space of string
c3e37e97 29
34e49164 30type info = { line : int; column : int;
c3e37e97
C
31 strbef : (added_string * int (* line *) * int (* col *)) list;
32 straft : (added_string * int (* line *) * int (* col *)) list }
34e49164
C
33type line = int
34type meta_name = string * string
35(* need to be careful about rewrapping, to avoid duplicating pos info
36currently, the pos info is always None until asttoctl2. *)
37type 'a wrap =
38 {node : 'a;
39 node_line : line;
40 free_vars : meta_name list; (*free vars*)
41 minus_free_vars : meta_name list; (*minus free vars*)
978fd7e5 42 fresh_vars : (meta_name * seed) list; (*fresh vars*)
34e49164
C
43 inherited : meta_name list; (*inherited vars*)
44 saved_witness : meta_name list; (*witness vars*)
45 bef_aft : dots_bef_aft;
46 (* the following is for or expressions *)
47 pos_info : meta_name mcode option; (* pos info, try not to duplicate *)
48 true_if_test_exp : bool;(* true if "test_exp from iso", only for exprs *)
690d68d1
C
49 (* the following is only for declarations *)
50 safe_for_multi_decls : bool;
34e49164
C
51 (* isos relevant to the term; ultimately only used for rule_elems *)
52 iso_info : (string*anything) list }
53
54and 'a befaft =
951c7801
C
55 BEFORE of 'a list list * count
56 | AFTER of 'a list list * count
57 | BEFOREAFTER of 'a list list * 'a list list * count
34e49164
C
58 | NOTHING
59
8babbc8f
C
60and 'a replacement = REPLACEMENT of 'a list list * count | NOREPLACEMENT
61
8f657093 62and 'a mcode = 'a * info * mcodekind * meta_pos list (* pos variables *)
951c7801
C
63 (* pos is an offset indicating where in the C code the mcodekind
64 has an effect *)
65 (* int list is the match instances, which are only meaningful in annotated
66 C code *)
8babbc8f 67 (* adjacency is the adjacency index, which is incremented on context dots *)
5626f154 68(* iteration is only allowed on context code, the intuition vaguely being
951c7801
C
69that there is no way to replace something more than once. Actually,
70allowing iterated additions on minus code would cause problems with some
71heuristics for adding braces, because one couldn't identify simple
72replacements with certainty. Anyway, iteration doesn't seem to be needed
73on - code for the moment. Although it may be confusing that there can be
74iterated addition of code before context code where the context code is
75immediately followed by removed code. *)
8babbc8f 76and adjacency = ALLMINUS | ADJ of int
951c7801 77and mcodekind =
8babbc8f 78 MINUS of pos * int list * adjacency * anything replacement
34e49164 79 | CONTEXT of pos * anything befaft
951c7801
C
80 | PLUS of count
81and count = ONE (* + *) | MANY (* ++ *)
82and fixpos =
34e49164 83 Real of int (* charpos *) | Virt of int * int (* charpos + offset *)
951c7801 84and pos = NoPos | DontCarePos | FixPos of (fixpos * fixpos)
34e49164
C
85
86and dots_bef_aft =
87 NoDots
88 | AddingBetweenDots of statement * int (*index of let var*)
89 | DroppingBetweenDots of statement * int (*index of let var*)
90
91and inherited = Type_cocci.inherited
92and keep_binding = Type_cocci.keep_binding
93and multi = bool (*true if a nest is one or more, false if it is zero or more*)
94
95and end_info =
978fd7e5 96 meta_name list (*free vars*) * (meta_name * seed) list (*fresh*) *
b1b2de81 97 meta_name list (*inherited vars*) * mcodekind
34e49164
C
98
99(* --------------------------------------------------------------------- *)
100(* Metavariables *)
101
102and arity = UNIQUE | OPT | MULTI | NONE
103
104and metavar =
b23ff9c7
C
105 MetaMetaDecl of arity * meta_name (* name *)
106 | MetaIdDecl of arity * meta_name (* name *)
978fd7e5 107 | MetaFreshIdDecl of meta_name (* name *) * seed (* seed *)
34e49164 108 | MetaTypeDecl of arity * meta_name (* name *)
113803cf 109 | MetaInitDecl of arity * meta_name (* name *)
8f657093 110 | MetaInitListDecl of arity * meta_name (* name *) * list_len (*len*)
34e49164
C
111 | MetaListlenDecl of meta_name (* name *)
112 | MetaParamDecl of arity * meta_name (* name *)
88e71198 113 | MetaParamListDecl of arity * meta_name (*name*) * list_len (*len*)
34e49164
C
114 | MetaConstDecl of
115 arity * meta_name (* name *) * Type_cocci.typeC list option
116 | MetaErrDecl of arity * meta_name (* name *)
117 | MetaExpDecl of
118 arity * meta_name (* name *) * Type_cocci.typeC list option
119 | MetaIdExpDecl of
120 arity * meta_name (* name *) * Type_cocci.typeC list option
121 | MetaLocalIdExpDecl of
122 arity * meta_name (* name *) * Type_cocci.typeC list option
88e71198 123 | MetaExpListDecl of arity * meta_name (*name*) * list_len (*len*)
413ffc02
C
124 | MetaDeclDecl of arity * meta_name (* name *)
125 | MetaFieldDecl of arity * meta_name (* name *)
190f1acf 126 | MetaFieldListDecl of arity * meta_name (* name *) * list_len (*len*)
34e49164
C
127 | MetaStmDecl of arity * meta_name (* name *)
128 | MetaStmListDecl of arity * meta_name (* name *)
129 | MetaFuncDecl of arity * meta_name (* name *)
130 | MetaLocalFuncDecl of arity * meta_name (* name *)
131 | MetaPosDecl of arity * meta_name (* name *)
132 | MetaDeclarerDecl of arity * meta_name (* name *)
133 | MetaIteratorDecl of arity * meta_name (* name *)
134
88e71198
C
135and list_len = AnyLen | MetaLen of meta_name | CstLen of int
136
978fd7e5
C
137and seed = NoVal | StringSeed of string | ListSeed of seed_elem list
138and seed_elem = SeedString of string | SeedId of meta_name
139
34e49164
C
140(* --------------------------------------------------------------------- *)
141(* --------------------------------------------------------------------- *)
142(* Dots *)
143
144and 'a base_dots =
145 DOTS of 'a list
146 | CIRCLES of 'a list
147 | STARS of 'a list
148
149and 'a dots = 'a base_dots wrap
150
151(* --------------------------------------------------------------------- *)
152(* Identifier *)
153
154and base_ident =
951c7801
C
155 Id of string mcode
156 | MetaId of meta_name mcode * idconstraint * keep_binding * inherited
157 | MetaFunc of meta_name mcode * idconstraint * keep_binding * inherited
158 | MetaLocalFunc of meta_name mcode * idconstraint * keep_binding * inherited
34e49164 159
d3f655c6 160 | DisjId of ident list
34e49164
C
161 | OptIdent of ident
162 | UniqueIdent of ident
163
164and ident = base_ident wrap
165
166(* --------------------------------------------------------------------- *)
167(* Expression *)
168
faf9a90c 169and base_expression =
34e49164
C
170 Ident of ident
171 | Constant of constant mcode
172 | FunCall of expression * string mcode (* ( *) *
173 expression dots * string mcode (* ) *)
174 | Assignment of expression * assignOp mcode * expression *
175 bool (* true if it can match an initialization *)
176 | CondExpr of expression * string mcode (* ? *) * expression option *
177 string mcode (* : *) * expression
178 | Postfix of expression * fixOp mcode
179 | Infix of expression * fixOp mcode
180 | Unary of expression * unaryOp mcode
181 | Binary of expression * binaryOp mcode * expression
182 | Nested of expression * binaryOp mcode * expression
183 | ArrayAccess of expression * string mcode (* [ *) * expression *
184 string mcode (* ] *)
185 | RecordAccess of expression * string mcode (* . *) * ident
186 | RecordPtAccess of expression * string mcode (* -> *) * ident
187 | Cast of string mcode (* ( *) * fullType * string mcode (* ) *) *
188 expression
189 | SizeOfExpr of string mcode (* sizeof *) * expression
190 | SizeOfType of string mcode (* sizeof *) * string mcode (* ( *) *
191 fullType * string mcode (* ) *)
192 | TypeExp of fullType (*type name used as an expression, only in
193 arg or #define*)
194
195 | Paren of string mcode (* ( *) * expression *
196 string mcode (* ) *)
197
951c7801 198 | MetaErr of meta_name mcode * constraints * keep_binding *
34e49164 199 inherited
951c7801 200 | MetaExpr of meta_name mcode * constraints * keep_binding *
34e49164 201 Type_cocci.typeC list option * form * inherited
88e71198 202 | MetaExprList of meta_name mcode * listlen * keep_binding *
34e49164
C
203 inherited (* only in arg lists *)
204
205 | EComma of string mcode (* only in arg lists *)
206
207 | DisjExpr of expression list
5636bb2c
C
208 | NestExpr of string mcode (* <.../<+... *) *
209 expression dots *
210 string mcode (* ...>/...+> *) *
211 expression option * multi
34e49164
C
212
213 (* can appear in arg lists, and also inside Nest, as in:
214 if(< ... X ... Y ...>)
215 In the following, the expression option is the WHEN *)
216 | Edots of string mcode (* ... *) * expression option
217 | Ecircles of string mcode (* ooo *) * expression option
218 | Estars of string mcode (* *** *) * expression option
219
220 | OptExp of expression
221 | UniqueExp of expression
222
951c7801
C
223and constraints =
224 NoConstraint
5636bb2c 225 | NotIdCstrt of reconstraint
951c7801 226 | NotExpCstrt of expression list
5636bb2c
C
227 | SubExpCstrt of meta_name list
228
229(* Constraints on Meta-* Identifiers, Functions *)
230and idconstraint =
231 IdNoConstraint
232 | IdNegIdSet of string list * meta_name list
233 | IdRegExpConstraint of reconstraint
234
235and reconstraint =
236 | IdRegExp of string * Str.regexp
237 | IdNotRegExp of string * Str.regexp
951c7801 238
34e49164
C
239(* ANY = int E; ID = idexpression int X; CONST = constant int X; *)
240and form = ANY | ID | LocalID | CONST (* form for MetaExp *)
241
242and expression = base_expression wrap
243
88e71198
C
244and listlen =
245 MetaListLen of meta_name mcode * keep_binding * inherited
246 | CstListLen of int
247 | AnyListLen
34e49164 248
8babbc8f 249and unaryOp = GetRef | GetRefLabel | DeRef | UnPlus | UnMinus | Tilde | Not
34e49164
C
250and assignOp = SimpleAssign | OpAssign of arithOp
251and fixOp = Dec | Inc
252
253and binaryOp = Arith of arithOp | Logical of logicalOp
254and arithOp =
255 Plus | Minus | Mul | Div | Mod | DecLeft | DecRight | And | Or | Xor
256and logicalOp = Inf | Sup | InfEq | SupEq | Eq | NotEq | AndLog | OrLog
257
258and constant =
259 String of string
260 | Char of string
261 | Int of string
262 | Float of string
263
264(* --------------------------------------------------------------------- *)
265(* Types *)
266
267and base_fullType =
268 Type of const_vol mcode option * typeC
269 | DisjType of fullType list (* only after iso *)
270 | OptType of fullType
271 | UniqueType of fullType
272
faf9a90c
C
273and base_typeC =
274 BaseType of baseType * string mcode list (* Yoann style *)
275 | SignedT of sign mcode * typeC option
34e49164
C
276 | Pointer of fullType * string mcode (* * *)
277 | FunctionPointer of fullType *
278 string mcode(* ( *)*string mcode(* * *)*string mcode(* ) *)*
279 string mcode (* ( *)*parameter_list*string mcode(* ) *)
280
281 (* used for the automatic managment of prototypes *)
282 | FunctionType of bool (* true if all minus for dropping return type *) *
283 fullType option *
284 string mcode (* ( *) * parameter_list *
285 string mcode (* ) *)
286
287 | Array of fullType * string mcode (* [ *) *
288 expression option * string mcode (* ] *)
c491d8ee
C
289 | EnumName of string mcode (*enum*) * ident option (* name *)
290 | EnumDef of fullType (* either EnumName or metavar *) *
291 string mcode (* { *) * expression dots * string mcode (* } *)
34e49164
C
292 | StructUnionName of structUnion mcode * ident option (* name *)
293 | StructUnionDef of fullType (* either StructUnionName or metavar *) *
294 string mcode (* { *) * declaration dots * string mcode (* } *)
b1b2de81 295 | TypeName of string mcode (* pad: should be 'of ident' ? *)
34e49164
C
296
297 | MetaType of meta_name mcode * keep_binding * inherited
298
299and fullType = base_fullType wrap
300and typeC = base_typeC wrap
faf9a90c 301
34e49164 302and baseType = VoidType | CharType | ShortType | IntType | DoubleType
1eddfd50 303 | FloatType | LongType | LongLongType | SizeType | SSizeType | PtrDiffType
34e49164
C
304
305and structUnion = Struct | Union
306
307and sign = Signed | Unsigned
308
309and const_vol = Const | Volatile
310
311(* --------------------------------------------------------------------- *)
312(* Variable declaration *)
313(* Even if the Cocci program specifies a list of declarations, they are
314 split out into multiple declarations of a single variable each. *)
315
316and base_declaration =
317 Init of storage mcode option * fullType * ident * string mcode (*=*) *
318 initialiser * string mcode (*;*)
319 | UnInit of storage mcode option * fullType * ident * string mcode (* ; *)
320 | TyDecl of fullType * string mcode (* ; *)
321 | MacroDecl of ident (* name *) * string mcode (* ( *) *
322 expression dots * string mcode (* ) *) * string mcode (* ; *)
faf9a90c 323 | Typedef of string mcode (*typedef*) * fullType *
34e49164
C
324 typeC (* either TypeName or metavar *) * string mcode (*;*)
325 | DisjDecl of declaration list
326 (* Ddots is for a structure declaration *)
327 | Ddots of string mcode (* ... *) * declaration option (* whencode *)
328
329 | MetaDecl of meta_name mcode * keep_binding * inherited
413ffc02 330 | MetaField of meta_name mcode * keep_binding * inherited
190f1acf 331 | MetaFieldList of meta_name mcode * listlen * keep_binding * inherited
34e49164
C
332
333 | OptDecl of declaration
334 | UniqueDecl of declaration
335
336and declaration = base_declaration wrap
337
338(* --------------------------------------------------------------------- *)
339(* Initializers *)
340
341and base_initialiser =
113803cf 342 MetaInit of meta_name mcode * keep_binding * inherited
8f657093 343 | MetaInitList of meta_name mcode * listlen * keep_binding * inherited
113803cf 344 | InitExpr of expression
c491d8ee
C
345 | ArInitList of string mcode (*{*) * initialiser dots * string mcode (*}*)
346 | StrInitList of bool (* true if all are - *) *
90aeb998 347 string mcode (*{*) * initialiser list * string mcode (*}*) *
34e49164 348 initialiser list (* whencode: elements that shouldn't appear in init *)
113803cf
C
349 | InitGccExt of
350 designator list (* name *) * string mcode (*=*) *
34e49164
C
351 initialiser (* gccext: *)
352 | InitGccName of ident (* name *) * string mcode (*:*) *
353 initialiser
34e49164 354 | IComma of string mcode (* , *)
c491d8ee 355 | Idots of string mcode (* ... *) * initialiser option (* whencode *)
34e49164
C
356
357 | OptIni of initialiser
358 | UniqueIni of initialiser
359
113803cf
C
360and designator =
361 DesignatorField of string mcode (* . *) * ident
362 | DesignatorIndex of string mcode (* [ *) * expression * string mcode (* ] *)
363 | DesignatorRange of
364 string mcode (* [ *) * expression * string mcode (* ... *) *
365 expression * string mcode (* ] *)
366
34e49164
C
367and initialiser = base_initialiser wrap
368
369(* --------------------------------------------------------------------- *)
370(* Parameter *)
371
372and base_parameterTypeDef =
373 VoidParam of fullType
374 | Param of fullType * ident option
375
376 | MetaParam of meta_name mcode * keep_binding * inherited
88e71198 377 | MetaParamList of meta_name mcode * listlen * keep_binding * inherited
34e49164
C
378
379 | PComma of string mcode
380
381 | Pdots of string mcode (* ... *)
382 | Pcircles of string mcode (* ooo *)
383
384 | OptParam of parameterTypeDef
385 | UniqueParam of parameterTypeDef
386
387and parameterTypeDef = base_parameterTypeDef wrap
388
389and parameter_list = parameterTypeDef dots
390
391(* --------------------------------------------------------------------- *)
392(* #define Parameters *)
393
394and base_define_param =
395 DParam of ident
396 | DPComma of string mcode
397 | DPdots of string mcode (* ... *)
398 | DPcircles of string mcode (* ooo *)
399 | OptDParam of define_param
400 | UniqueDParam of define_param
401
402and define_param = base_define_param wrap
403
404and base_define_parameters =
405 NoParams (* not parameter list, not an empty one *)
406 | DParams of string mcode(*( *) * define_param dots * string mcode(* )*)
407
408and define_parameters = base_define_parameters wrap
409
410(* --------------------------------------------------------------------- *)
411(* positions *)
412
413(* PER = keep bindings separate, ALL = collect them *)
414and meta_collect = PER | ALL
415
416and meta_pos =
417 MetaPos of meta_name mcode * meta_name list *
8f657093 418 meta_collect * keep_binding * inherited
34e49164
C
419
420(* --------------------------------------------------------------------- *)
421(* Function declaration *)
422
423and storage = Static | Auto | Register | Extern
424
425(* --------------------------------------------------------------------- *)
426(* Top-level code *)
427
428and base_rule_elem =
429 FunHeader of mcodekind (* before the function header *) *
430 bool (* true if all minus, for dropping static, etc *) *
431 fninfo list * ident (* name *) *
432 string mcode (* ( *) * parameter_list *
433 string mcode (* ) *)
434 | Decl of mcodekind (* before the decl *) *
435 bool (* true if all minus *) * declaration
436
437 | SeqStart of string mcode (* { *)
438 | SeqEnd of string mcode (* } *)
439
8babbc8f 440 | ExprStatement of expression option * string mcode (*;*)
34e49164
C
441 | IfHeader of string mcode (* if *) * string mcode (* ( *) *
442 expression * string mcode (* ) *)
443 | Else of string mcode (* else *)
444 | WhileHeader of string mcode (* while *) * string mcode (* ( *) *
445 expression * string mcode (* ) *)
446 | DoHeader of string mcode (* do *)
447 | WhileTail of string mcode (* while *) * string mcode (* ( *) *
448 expression * string mcode (* ) *) *
449 string mcode (* ; *)
450 | ForHeader of string mcode (* for *) * string mcode (* ( *) *
451 expression option * string mcode (*;*) *
452 expression option * string mcode (*;*) *
453 expression option * string mcode (* ) *)
454 | IteratorHeader of ident (* name *) * string mcode (* ( *) *
455 expression dots * string mcode (* ) *)
456 | SwitchHeader of string mcode (* switch *) * string mcode (* ( *) *
457 expression * string mcode (* ) *)
458 | Break of string mcode (* break *) * string mcode (* ; *)
459 | Continue of string mcode (* continue *) * string mcode (* ; *)
460 | Label of ident * string mcode (* : *)
461 | Goto of string mcode (* goto *) * ident * string mcode (* ; *)
462 | Return of string mcode (* return *) * string mcode (* ; *)
463 | ReturnExpr of string mcode (* return *) * expression *
464 string mcode (* ; *)
465
466 | MetaRuleElem of meta_name mcode * keep_binding * inherited
467 | MetaStmt of meta_name mcode * keep_binding * metaStmtInfo *
468 inherited
469 | MetaStmtList of meta_name mcode * keep_binding * inherited
470
471 | Exp of expression (* matches a subterm *)
472 | TopExp of expression (* for macros body, exp at top level,
473 not subexp *)
474 | Ty of fullType (* only at SP top level, matches a subterm *)
1be43e12 475 | TopInit of initialiser (* only at top level *)
34e49164 476 | Include of string mcode (*#include*) * inc_file mcode (*file *)
3a314143 477 | Undef of string mcode (* #define *) * ident (* name *)
34e49164
C
478 | DefineHeader of string mcode (* #define *) * ident (* name *) *
479 define_parameters (*params*)
480 | Case of string mcode (* case *) * expression * string mcode (*:*)
481 | Default of string mcode (* default *) * string mcode (*:*)
482 | DisjRuleElem of rule_elem list
483
484and fninfo =
485 FStorage of storage mcode
486 | FType of fullType
487 | FInline of string mcode
488 | FAttr of string mcode
489
490and metaStmtInfo =
491 NotSequencible | SequencibleAfterDots of dots_whencode list | Sequencible
492
493and rule_elem = base_rule_elem wrap
494
495and base_statement =
708f4980 496 Seq of rule_elem (* { *) *
34e49164
C
497 statement dots * rule_elem (* } *)
498 | IfThen of rule_elem (* header *) * statement * end_info (* endif *)
499 | IfThenElse of rule_elem (* header *) * statement *
500 rule_elem (* else *) * statement * end_info (* endif *)
501 | While of rule_elem (* header *) * statement * end_info (*endwhile*)
502 | Do of rule_elem (* do *) * statement * rule_elem (* tail *)
503 | For of rule_elem (* header *) * statement * end_info (*endfor*)
504 | Iterator of rule_elem (* header *) * statement * end_info (*enditer*)
505 | Switch of rule_elem (* header *) * rule_elem (* { *) *
fc1ad971 506 statement (*decl*) dots * case_line list * rule_elem(*}*)
34e49164
C
507 | Atomic of rule_elem
508 | Disj of statement dots list
5636bb2c
C
509 | Nest of string mcode (* <.../<+... *) * statement dots *
510 string mcode (* ...>/...+> *) *
34e49164
C
511 (statement dots,statement) whencode list * multi *
512 dots_whencode list * dots_whencode list
513 | FunDecl of rule_elem (* header *) * rule_elem (* { *) *
708f4980 514 statement dots * rule_elem (* } *)
34e49164
C
515 | Define of rule_elem (* header *) * statement dots
516 | Dots of string mcode (* ... *) *
517 (statement dots,statement) whencode list *
518 dots_whencode list * dots_whencode list
519 | Circles of string mcode (* ooo *) *
520 (statement dots,statement) whencode list *
521 dots_whencode list * dots_whencode list
522 | Stars of string mcode (* *** *) *
523 (statement dots,statement) whencode list *
524 dots_whencode list * dots_whencode list
525 | OptStm of statement
526 | UniqueStm of statement
527
528and ('a,'b) whencode =
529 WhenNot of 'a
530 | WhenAlways of 'b
531 | WhenModifier of when_modifier
1be43e12
C
532 | WhenNotTrue of rule_elem (* useful for fvs *)
533 | WhenNotFalse of rule_elem
34e49164
C
534
535and when_modifier =
536 (* The following removes the shortest path constraint. It can be used
537 with other when modifiers *)
538 WhenAny
539 (* The following removes the special consideration of error paths. It
540 can be used with other when modifiers *)
541 | WhenStrict
542 | WhenForall
543 | WhenExists
544
545(* only used with asttoctl *)
546and dots_whencode =
547 WParen of rule_elem * meta_name (*pren_var*)
548 | Other of statement
549 | Other_dots of statement dots
550
551and statement = base_statement wrap
552
553and base_case_line =
554 CaseLine of rule_elem (* case/default header *) * statement dots
555 | OptCase of case_line
556
557and case_line = base_case_line wrap
558
559and inc_file =
560 Local of inc_elem list
561 | NonLocal of inc_elem list
562
563and inc_elem =
564 IncPath of string
565 | IncDots
566
567and base_top_level =
65038c61 568 NONDECL of statement
34e49164
C
569 | CODE of statement dots
570 | FILEINFO of string mcode (* old file *) * string mcode (* new file *)
571 | ERRORWORDS of expression list
572
573and top_level = base_top_level wrap
574
575and rulename =
576 CocciRulename of string option * dependency *
577 string list * string list * exists * bool
faf9a90c
C
578 | GeneratedRulename of string option * dependency *
579 string list * string list * exists * bool
174d1640
C
580 | ScriptRulename of string option (* name *) * string (* language *) *
581 dependency
582 | InitialScriptRulename of string option (* name *) * string (* language *) *
583 dependency
584 | FinalScriptRulename of string option (* name *) * string (* language *) *
585 dependency
34e49164 586
faf9a90c
C
587and ruletype = Normal | Generated
588
34e49164 589and rule =
faf9a90c 590 CocciRule of string (* name *) *
34e49164 591 (dependency * string list (* dropped isos *) * exists) * top_level list
faf9a90c 592 * bool list * ruletype
174d1640
C
593 | ScriptRule of string (* name *) *
594 (* metaname for python (untyped), metavar for ocaml (typed) *)
aba5c457 595 string * dependency *
413ffc02
C
596 (script_meta_name * meta_name * metavar) list (*inherited vars*) *
597 meta_name list (*script vars*) * string
174d1640
C
598 | InitialScriptRule of string (* name *) *
599 string (*language*) * dependency * string (*code*)
600 | FinalScriptRule of string (* name *) *
601 string (*language*) * dependency * string (*code*)
34e49164 602
aba5c457
C
603and script_meta_name = string option (*string*) * string option (*ast*)
604
34e49164
C
605and dependency =
606 Dep of string (* rule applies for the current binding *)
607 | AntiDep of string (* rule doesn't apply for the current binding *)
608 | EverDep of string (* rule applies for some binding *)
609 | NeverDep of string (* rule never applies for any binding *)
610 | AndDep of dependency * dependency
611 | OrDep of dependency * dependency
7f004419 612 | NoDep | FailDep
34e49164
C
613
614and rule_with_metavars = metavar list * rule
615
616and anything =
617 FullTypeTag of fullType
618 | BaseTypeTag of baseType
619 | StructUnionTag of structUnion
620 | SignTag of sign
621 | IdentTag of ident
622 | ExpressionTag of expression
623 | ConstantTag of constant
624 | UnaryOpTag of unaryOp
625 | AssignOpTag of assignOp
626 | FixOpTag of fixOp
627 | BinaryOpTag of binaryOp
628 | ArithOpTag of arithOp
629 | LogicalOpTag of logicalOp
630 | DeclarationTag of declaration
631 | InitTag of initialiser
632 | StorageTag of storage
633 | IncFileTag of inc_file
634 | Rule_elemTag of rule_elem
635 | StatementTag of statement
636 | CaseLineTag of case_line
637 | ConstVolTag of const_vol
638 | Token of string * info option
c3e37e97 639 | Pragma of added_string list
34e49164
C
640 | Code of top_level
641 | ExprDotsTag of expression dots
642 | ParamDotsTag of parameterTypeDef dots
643 | StmtDotsTag of statement dots
644 | DeclDotsTag of declaration dots
645 | TypeCTag of typeC
646 | ParamTag of parameterTypeDef
647 | SgrepStartTag of string
648 | SgrepEndTag of string
649
650(* --------------------------------------------------------------------- *)
651
978fd7e5
C
652and exists = Exists | Forall | Undetermined
653(* | ReverseForall - idea: look back on all flow paths; not implemented *)
34e49164
C
654
655(* --------------------------------------------------------------------- *)
656
657let mkToken x = Token (x,None)
658
659(* --------------------------------------------------------------------- *)
660
951c7801
C
661let lub_count i1 i2 =
662 match (i1,i2) with
663 (MANY,MANY) -> MANY
664 | _ -> ONE
665
666(* --------------------------------------------------------------------- *)
667
34e49164
C
668let rewrap model x = {model with node = x}
669let rewrap_mcode (_,a,b,c) x = (x,a,b,c)
670let unwrap x = x.node
671let unwrap_mcode (x,_,_,_) = x
672let get_mcodekind (_,_,x,_) = x
673let get_line x = x.node_line
674let get_mcode_line (_,l,_,_) = l.line
708f4980 675let get_mcode_col (_,l,_,_) = l.column
34e49164
C
676let get_fvs x = x.free_vars
677let set_fvs fvs x = {x with free_vars = fvs}
678let get_mfvs x = x.minus_free_vars
679let set_mfvs mfvs x = {x with minus_free_vars = mfvs}
680let get_fresh x = x.fresh_vars
681let get_inherited x = x.inherited
682let get_saved x = x.saved_witness
683let get_dots_bef_aft x = x.bef_aft
684let set_dots_bef_aft d x = {x with bef_aft = d}
685let get_pos x = x.pos_info
686let set_pos x pos = {x with pos_info = pos}
690d68d1
C
687let get_test_exp x = x.true_if_test_exp
688let set_test_exp x = {x with true_if_test_exp = true}
689let get_safe_decl x = x.safe_for_multi_decls
34e49164
C
690let get_isos x = x.iso_info
691let set_isos x isos = {x with iso_info = isos}
692let get_pos_var (_,_,_,p) = p
693let set_pos_var vr (a,b,c,_) = (a,b,c,vr)
8f657093 694let drop_pos (a,b,c,_) = (a,b,c,[])
34e49164
C
695
696let get_wcfvs (whencode : ('a wrap, 'b wrap) whencode list) =
697 Common.union_all
698 (List.map
699 (function
700 WhenNot(a) -> get_fvs a
701 | WhenAlways(a) -> get_fvs a
1be43e12
C
702 | WhenModifier(_) -> []
703 | WhenNotTrue(e) -> get_fvs e
704 | WhenNotFalse(e) -> get_fvs e)
34e49164
C
705 whencode)
706
707(* --------------------------------------------------------------------- *)
708
709let get_meta_name = function
b23ff9c7
C
710 MetaMetaDecl(ar,nm) -> nm
711 | MetaIdDecl(ar,nm) -> nm
b1b2de81 712 | MetaFreshIdDecl(nm,seed) -> nm
34e49164 713 | MetaTypeDecl(ar,nm) -> nm
113803cf 714 | MetaInitDecl(ar,nm) -> nm
8f657093 715 | MetaInitListDecl(ar,nm,nm1) -> nm
34e49164
C
716 | MetaListlenDecl(nm) -> nm
717 | MetaParamDecl(ar,nm) -> nm
718 | MetaParamListDecl(ar,nm,nm1) -> nm
719 | MetaConstDecl(ar,nm,ty) -> nm
720 | MetaErrDecl(ar,nm) -> nm
721 | MetaExpDecl(ar,nm,ty) -> nm
722 | MetaIdExpDecl(ar,nm,ty) -> nm
723 | MetaLocalIdExpDecl(ar,nm,ty) -> nm
724 | MetaExpListDecl(ar,nm,nm1) -> nm
413ffc02
C
725 | MetaDeclDecl(ar,nm) -> nm
726 | MetaFieldDecl(ar,nm) -> nm
190f1acf 727 | MetaFieldListDecl(ar,nm,nm1) -> nm
34e49164
C
728 | MetaStmDecl(ar,nm) -> nm
729 | MetaStmListDecl(ar,nm) -> nm
730 | MetaFuncDecl(ar,nm) -> nm
731 | MetaLocalFuncDecl(ar,nm) -> nm
732 | MetaPosDecl(ar,nm) -> nm
733 | MetaDeclarerDecl(ar,nm) -> nm
734 | MetaIteratorDecl(ar,nm) -> nm
735
736(* --------------------------------------------------------------------- *)
737
0708f913
C
738and tag2c = function
739 FullTypeTag _ -> "FullTypeTag"
740 | BaseTypeTag _ -> "BaseTypeTag"
741 | StructUnionTag _ -> "StructUnionTag"
742 | SignTag _ -> "SignTag"
743 | IdentTag _ -> "IdentTag"
744 | ExpressionTag _ -> "ExpressionTag"
745 | ConstantTag _ -> "ConstantTag"
746 | UnaryOpTag _ -> "UnaryOpTag"
747 | AssignOpTag _ -> "AssignOpTag"
748 | FixOpTag _ -> "FixOpTag"
749 | BinaryOpTag _ -> "BinaryOpTag"
750 | ArithOpTag _ -> "ArithOpTag"
751 | LogicalOpTag _ -> "LogicalOpTag"
752 | DeclarationTag _ -> "DeclarationTag"
753 | InitTag _ -> "InitTag"
754 | StorageTag _ -> "StorageTag"
755 | IncFileTag _ -> "IncFileTag"
756 | Rule_elemTag _ -> "Rule_elemTag"
757 | StatementTag _ -> "StatementTag"
758 | CaseLineTag _ -> "CaseLineTag"
759 | ConstVolTag _ -> "ConstVolTag"
760 | Token _ -> "Token"
761 | Pragma _ -> "Pragma"
762 | Code _ -> "Code"
763 | ExprDotsTag _ -> "ExprDotsTag"
764 | ParamDotsTag _ -> "ParamDotsTag"
765 | StmtDotsTag _ -> "StmtDotsTag"
766 | DeclDotsTag _ -> "DeclDotsTag"
767 | TypeCTag _ -> "TypeCTag"
768 | ParamTag _ -> "ParamTag"
769 | SgrepStartTag _ -> "SgrepStartTag"
770 | SgrepEndTag _ -> "SgrepEndTag"
771
772(* --------------------------------------------------------------------- *)
773
708f4980 774let no_info = { line = 0; column = -1; strbef = []; straft = [] }
34e49164
C
775
776let make_term x =
777 {node = x;
778 node_line = 0;
779 free_vars = [];
780 minus_free_vars = [];
781 fresh_vars = [];
782 inherited = [];
783 saved_witness = [];
784 bef_aft = NoDots;
785 pos_info = None;
786 true_if_test_exp = false;
690d68d1 787 safe_for_multi_decls = false;
34e49164
C
788 iso_info = [] }
789
790let make_meta_rule_elem s d (fvs,fresh,inh) =
ae4735db 791 let rule = "" in
34e49164 792 {(make_term
8f657093 793 (MetaRuleElem(((rule,s),no_info,d,[]),Type_cocci.Unitary,false)))
34e49164
C
794 with free_vars = fvs; fresh_vars = fresh; inherited = inh}
795
796let make_meta_decl s d (fvs,fresh,inh) =
ae4735db 797 let rule = "" in
34e49164 798 {(make_term
8f657093 799 (MetaDecl(((rule,s),no_info,d,[]),Type_cocci.Unitary,false))) with
34e49164
C
800 free_vars = fvs; fresh_vars = fresh; inherited = inh}
801
8f657093 802let make_mcode x = (x,no_info,CONTEXT(NoPos,NOTHING),[])
34e49164
C
803
804(* --------------------------------------------------------------------- *)
805
806let equal_pos x y = x = y
807
808(* --------------------------------------------------------------------- *)
809
810let undots x =
811 match unwrap x with
812 DOTS e -> e
813 | CIRCLES e -> e
814 | STARS e -> e