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