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