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