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