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