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