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