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