Coccinelle release-1.0.0-rc11
[bpt/coccinelle.git] / parsing_cocci / ast0_cocci.ml
CommitLineData
f537ebc4 1(*
17ba0788
C
2 * Copyright 2012, INRIA
3 * Julia Lawall, Gilles Muller
4 * Copyright 2010-2011, INRIA, University of Copenhagen
f537ebc4
C
5 * Julia Lawall, Rene Rydhof Hansen, Gilles Muller, Nicolas Palix
6 * Copyright 2005-2009, Ecole des Mines de Nantes, University of Copenhagen
7 * Yoann Padioleau, Julia Lawall, Rene Rydhof Hansen, Henrik Stuart, Gilles Muller, Nicolas Palix
8 * This file is part of Coccinelle.
9 *
10 * Coccinelle is free software: you can redistribute it and/or modify
11 * it under the terms of the GNU General Public License as published by
12 * the Free Software Foundation, according to version 2 of the License.
13 *
14 * Coccinelle is distributed in the hope that it will be useful,
15 * but WITHOUT ANY WARRANTY; without even the implied warranty of
16 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
17 * GNU General Public License for more details.
18 *
19 * You should have received a copy of the GNU General Public License
20 * along with Coccinelle. If not, see <http://www.gnu.org/licenses/>.
21 *
22 * The authors reserve the right to distribute this or future versions of
23 * Coccinelle under other licenses.
24 *)
25
26
34e49164 27module Ast = Ast_cocci
e6509c05 28module TC = Type_cocci
34e49164
C
29
30(* --------------------------------------------------------------------- *)
31(* Modified code *)
32
33type arity = OPT | UNIQUE | NONE
34
35type token_info =
36 { tline_start : int; tline_end : int;
37 left_offset : int; right_offset : int }
38let default_token_info =
39 { tline_start = -1; tline_end = -1; left_offset = -1; right_offset = -1 }
40
41(* MIXED is like CONTEXT, since sometimes MIXED things have to revert to
42CONTEXT - see insert_plus.ml *)
951c7801 43
34e49164 44type mcodekind =
8babbc8f 45 MINUS of (Ast.anything Ast.replacement * token_info) ref
951c7801 46 | PLUS of Ast.count
34e49164
C
47 | CONTEXT of (Ast.anything Ast.befaft * token_info * token_info) ref
48 | MIXED of (Ast.anything Ast.befaft * token_info * token_info) ref
49
0708f913
C
50type position_info = { line_start : int; line_end : int;
51 logical_start : int; logical_end : int;
52 column : int; offset : int; }
53
54type info = { pos_info : position_info;
34e49164
C
55 attachable_start : bool; attachable_end : bool;
56 mcode_start : mcodekind list; mcode_end : mcodekind list;
34e49164 57 (* the following are only for + code *)
c3e37e97 58 strings_before : (Ast.added_string * position_info) list;
97111a47
C
59 strings_after : (Ast.added_string * position_info) list;
60 isSymbolIdent : bool; (* is the token a symbol identifier or not *) }
34e49164 61
708f4980
C
62(* adjacency index is incremented when we skip over dots or nest delimiters
63it is used in deciding how much to remove, when two adjacent code tokens are
64removed. *)
65type 'a mcode =
17ba0788 66 'a * arity * info * mcodekind * anything list ref (* pos, - only *) *
708f4980 67 int (* adjacency_index *)
34e49164
C
68(* int ref is an index *)
69and 'a wrap =
70 { node : 'a;
71 info : info;
72 index : int ref;
73 mcodekind : mcodekind ref;
e6509c05 74 exp_ty : TC.typeC option ref; (* only for expressions *)
34e49164
C
75 bef_aft : dots_bef_aft; (* only for statements *)
76 true_if_arg : bool; (* true if "arg_exp", only for exprs *)
77 true_if_test : bool; (* true if "test position", only for exprs *)
78 true_if_test_exp : bool;(* true if "test_exp from iso", only for exprs *)
79 (*nonempty if this represents the use of an iso*)
80 iso_info : (string*anything) list }
81
82and dots_bef_aft =
83 NoDots | AddingBetweenDots of statement | DroppingBetweenDots of statement
84
85(* for iso metavariables, true if they can only match nonmodified terms with
86 all metavariables unitary
87 for SP metavariables, true if the metavariable is unitary (valid up to
88 isomorphism phase only)
89 In SP, the only options are impure and context
90*)
91and pure = Impure | Pure | Context | PureContext (* pure and only context *)
92
93(* --------------------------------------------------------------------- *)
94(* --------------------------------------------------------------------- *)
95(* Dots *)
96
97and 'a base_dots =
98 DOTS of 'a list
99 | CIRCLES of 'a list
100 | STARS of 'a list
101
102and 'a dots = 'a base_dots wrap
103
104(* --------------------------------------------------------------------- *)
105(* Identifier *)
106
107and base_ident =
951c7801 108 Id of string mcode
8babbc8f 109 | MetaId of Ast.meta_name mcode * Ast.idconstraint * Ast.seed * pure
951c7801
C
110 | MetaFunc of Ast.meta_name mcode * Ast.idconstraint * pure
111 | MetaLocalFunc of Ast.meta_name mcode * Ast.idconstraint * pure
d3f655c6
C
112 | DisjId of string mcode * ident list *
113 string mcode list (* the |s *) * string mcode
34e49164
C
114 | OptIdent of ident
115 | UniqueIdent of ident
116
117and ident = base_ident wrap
118
119(* --------------------------------------------------------------------- *)
120(* Expression *)
121
faf9a90c 122and base_expression =
34e49164
C
123 Ident of ident
124 | Constant of Ast.constant mcode
125 | FunCall of expression * string mcode (* ( *) *
126 expression dots * string mcode (* ) *)
127 | Assignment of expression * Ast.assignOp mcode * expression *
128 bool (* true if it can match an initialization *)
17ba0788 129 | Sequence of expression * string mcode (* , *) * expression
34e49164
C
130 | CondExpr of expression * string mcode (* ? *) * expression option *
131 string mcode (* : *) * expression
132 | Postfix of expression * Ast.fixOp mcode
133 | Infix of expression * Ast.fixOp mcode
134 | Unary of expression * Ast.unaryOp mcode
135 | Binary of expression * Ast.binaryOp mcode * expression
136 | Nested of expression * Ast.binaryOp mcode * expression
137 | Paren of string mcode (* ( *) * expression *
138 string mcode (* ) *)
139 | ArrayAccess of expression * string mcode (* [ *) * expression *
140 string mcode (* ] *)
141 | RecordAccess of expression * string mcode (* . *) * ident
142 | RecordPtAccess of expression * string mcode (* -> *) * ident
143 | Cast of string mcode (* ( *) * typeC * string mcode (* ) *) *
144 expression
145 | SizeOfExpr of string mcode (* sizeof *) * expression
146 | SizeOfType of string mcode (* sizeof *) * string mcode (* ( *) *
147 typeC * string mcode (* ) *)
148 | TypeExp of typeC (* type name used as an expression, only in args *)
7fe62b65
C
149 | Constructor of string mcode (* ( *) * typeC * string mcode (* ) *) *
150 initialiser
951c7801
C
151 | MetaErr of Ast.meta_name mcode * constraints * pure
152 | MetaExpr of Ast.meta_name mcode * constraints *
e6509c05 153 TC.typeC list option * Ast.form * pure
34e49164
C
154 | MetaExprList of Ast.meta_name mcode (* only in arg lists *) *
155 listlen * pure
17ba0788 156 | AsExpr of expression * expression (* as expr, always metavar *)
34e49164
C
157 | EComma of string mcode (* only in arg lists *)
158 | DisjExpr of string mcode * expression list *
159 string mcode list (* the |s *) * string mcode
160 | NestExpr of string mcode * expression dots * string mcode *
161 expression option * Ast.multi
162 | Edots of string mcode (* ... *) * expression option
163 | Ecircles of string mcode (* ooo *) * expression option
164 | Estars of string mcode (* *** *) * expression option
165 | OptExp of expression
166 | UniqueExp of expression
167
168and expression = base_expression wrap
169
951c7801
C
170and constraints =
171 NoConstraint
5636bb2c 172 | NotIdCstrt of Ast.reconstraint
951c7801 173 | NotExpCstrt of expression list
5636bb2c 174 | SubExpCstrt of Ast.meta_name list
951c7801 175
88e71198
C
176and listlen =
177 MetaListLen of Ast.meta_name mcode
178 | CstListLen of int
179 | AnyListLen
34e49164
C
180
181(* --------------------------------------------------------------------- *)
182(* Types *)
183
faf9a90c 184and base_typeC =
34e49164 185 ConstVol of Ast.const_vol mcode * typeC
faf9a90c
C
186 | BaseType of Ast.baseType * string mcode list
187 | Signed of Ast.sign mcode * typeC option
34e49164
C
188 | Pointer of typeC * string mcode (* * *)
189 | FunctionPointer of typeC *
190 string mcode(* ( *)*string mcode(* * *)*string mcode(* ) *)*
191 string mcode (* ( *)*parameter_list*string mcode(* ) *)
192 | FunctionType of typeC option *
193 string mcode (* ( *) * parameter_list *
194 string mcode (* ) *)
195 | Array of typeC * string mcode (* [ *) *
196 expression option * string mcode (* ] *)
c491d8ee
C
197 | EnumName of string mcode (*enum*) * ident option (* name *)
198 | EnumDef of typeC (* either StructUnionName or metavar *) *
199 string mcode (* { *) * expression dots * string mcode (* } *)
34e49164
C
200 | StructUnionName of Ast.structUnion mcode * ident option (* name *)
201 | StructUnionDef of typeC (* either StructUnionName or metavar *) *
202 string mcode (* { *) * declaration dots * string mcode (* } *)
203 | TypeName of string mcode
204 | MetaType of Ast.meta_name mcode * pure
17ba0788 205 | AsType of typeC * typeC (* as type, always metavar *)
34e49164
C
206 | DisjType of string mcode * typeC list * (* only after iso *)
207 string mcode list (* the |s *) * string mcode
208 | OptType of typeC
209 | UniqueType of typeC
210
211and typeC = base_typeC wrap
212
213(* --------------------------------------------------------------------- *)
214(* Variable declaration *)
215(* Even if the Cocci program specifies a list of declarations, they are
216 split out into multiple declarations of a single variable each. *)
217
218and base_declaration =
413ffc02
C
219 MetaDecl of Ast.meta_name mcode * pure (* variables *)
220 (* the following are kept separate from MetaDecls because ultimately
221 they don't match the same thin at all. Consider whether there
222 should be a separate type for fields, as in the C AST *)
223 | MetaField of Ast.meta_name mcode * pure (* structure fields *)
190f1acf 224 | MetaFieldList of Ast.meta_name mcode * listlen * pure (* structure fields *)
17ba0788 225 | AsDecl of declaration * declaration
413ffc02 226 | Init of Ast.storage mcode option * typeC * ident * string mcode (*=*) *
34e49164
C
227 initialiser * string mcode (*;*)
228 | UnInit of Ast.storage mcode option * typeC * ident * string mcode (* ; *)
229 | TyDecl of typeC * string mcode (* ; *)
230 | MacroDecl of ident (* name *) * string mcode (* ( *) *
231 expression dots * string mcode (* ) *) * string mcode (* ; *)
17ba0788
C
232 | MacroDeclInit of ident (* name *) * string mcode (* ( *) *
233 expression dots * string mcode (* ) *) * string mcode (*=*) *
234 initialiser * string mcode (* ; *)
34e49164
C
235 | Typedef of string mcode (* typedef *) * typeC * typeC * string mcode (*;*)
236 | DisjDecl of string mcode * declaration list *
237 string mcode list (* the |s *) * string mcode
238 (* Ddots is for a structure declaration *)
239 | Ddots of string mcode (* ... *) * declaration option (* whencode *)
240 | OptDecl of declaration
241 | UniqueDecl of declaration
242
243and declaration = base_declaration wrap
244
245(* --------------------------------------------------------------------- *)
246(* Initializers *)
247
248and base_initialiser =
113803cf 249 MetaInit of Ast.meta_name mcode * pure
8f657093 250 | MetaInitList of Ast.meta_name mcode * listlen * pure
17ba0788 251 | AsInit of initialiser * initialiser (* as init, always metavar *)
113803cf 252 | InitExpr of expression
c491d8ee
C
253 | InitList of string mcode (*{*) * initialiser_list * string mcode (*}*) *
254 (* true if ordered, as for array, false if unordered, as for struct *)
255 bool
113803cf
C
256 | InitGccExt of
257 designator list (* name *) * string mcode (*=*) *
34e49164
C
258 initialiser (* gccext: *)
259 | InitGccName of ident (* name *) * string mcode (*:*) *
260 initialiser
34e49164
C
261 | IComma of string mcode (* , *)
262 | Idots of string mcode (* ... *) * initialiser option (* whencode *)
263 | OptIni of initialiser
264 | UniqueIni of initialiser
265
113803cf
C
266and designator =
267 DesignatorField of string mcode (* . *) * ident
268 | DesignatorIndex of string mcode (* [ *) * expression * string mcode (* ] *)
269 | DesignatorRange of
270 string mcode (* [ *) * expression * string mcode (* ... *) *
271 expression * string mcode (* ] *)
272
34e49164
C
273and initialiser = base_initialiser wrap
274
275and initialiser_list = initialiser dots
276
277(* --------------------------------------------------------------------- *)
278(* Parameter *)
279
280and base_parameterTypeDef =
281 VoidParam of typeC
282 | Param of typeC * ident option
283 | MetaParam of Ast.meta_name mcode * pure
284 | MetaParamList of Ast.meta_name mcode * listlen * pure
285 | PComma of string mcode
286 | Pdots of string mcode (* ... *)
287 | Pcircles of string mcode (* ooo *)
288 | OptParam of parameterTypeDef
289 | UniqueParam of parameterTypeDef
290
291and parameterTypeDef = base_parameterTypeDef wrap
292
293and parameter_list = parameterTypeDef dots
294
295(* --------------------------------------------------------------------- *)
296(* #define Parameters *)
297
298and base_define_param =
299 DParam of ident
300 | DPComma of string mcode
301 | DPdots of string mcode (* ... *)
302 | DPcircles of string mcode (* ooo *)
303 | OptDParam of define_param
304 | UniqueDParam of define_param
305
306and define_param = base_define_param wrap
307
308and base_define_parameters =
309 NoParams
310 | DParams of string mcode(*( *) * define_param dots * string mcode(* )*)
311
312and define_parameters = base_define_parameters wrap
313
314(* --------------------------------------------------------------------- *)
315(* Statement*)
316
317and base_statement =
318 Decl of (info * mcodekind) (* before the decl *) * declaration
319 | Seq of string mcode (* { *) * statement dots *
320 string mcode (* } *)
8babbc8f 321 | ExprStatement of expression option * string mcode (*;*)
34e49164
C
322 | IfThen of string mcode (* if *) * string mcode (* ( *) *
323 expression * string mcode (* ) *) *
324 statement * (info * mcodekind) (* after info *)
325 | IfThenElse of string mcode (* if *) * string mcode (* ( *) *
326 expression * string mcode (* ) *) *
327 statement * string mcode (* else *) * statement *
328 (info * mcodekind)
329 | While of string mcode (* while *) * string mcode (* ( *) *
330 expression * string mcode (* ) *) *
331 statement * (info * mcodekind) (* after info *)
332 | Do of string mcode (* do *) * statement *
333 string mcode (* while *) * string mcode (* ( *) *
334 expression * string mcode (* ) *) *
335 string mcode (* ; *)
336 | For of string mcode (* for *) * string mcode (* ( *) *
337 expression option * string mcode (*;*) *
338 expression option * string mcode (*;*) *
339 expression option * string mcode (* ) *) * statement *
340 (info * mcodekind) (* after info *)
341 | Iterator of ident (* name *) * string mcode (* ( *) *
342 expression dots * string mcode (* ) *) *
343 statement * (info * mcodekind) (* after info *)
344 | Switch of string mcode (* switch *) * string mcode (* ( *) *
345 expression * string mcode (* ) *) * string mcode (* { *) *
fc1ad971 346 statement (*decl*) dots *
34e49164
C
347 case_line dots * string mcode (* } *)
348 | Break of string mcode (* break *) * string mcode (* ; *)
349 | Continue of string mcode (* continue *) * string mcode (* ; *)
350 | Label of ident * string mcode (* : *)
351 | Goto of string mcode (* goto *) * ident * string mcode (* ; *)
352 | Return of string mcode (* return *) * string mcode (* ; *)
353 | ReturnExpr of string mcode (* return *) * expression *
354 string mcode (* ; *)
355 | MetaStmt of Ast.meta_name mcode * pure
356 | MetaStmtList of Ast.meta_name mcode(*only in statement lists*) * pure
17ba0788 357 | AsStmt of statement * statement (* as statement, always metavar *)
34e49164
C
358 | Exp of expression (* only in dotted statement lists *)
359 | TopExp of expression (* for macros body *)
360 | Ty of typeC (* only at top level *)
1be43e12 361 | TopInit of initialiser (* only at top level *)
34e49164
C
362 | Disj of string mcode * statement dots list *
363 string mcode list (* the |s *) * string mcode
364 | Nest of string mcode * statement dots * string mcode *
365 (statement dots,statement) whencode list * Ast.multi
366 | Dots of string mcode (* ... *) *
367 (statement dots,statement) whencode list
368 | Circles of string mcode (* ooo *) *
369 (statement dots,statement) whencode list
370 | Stars of string mcode (* *** *) *
371 (statement dots,statement) whencode list
372 | FunDecl of (info * mcodekind) (* before the function decl *) *
373 fninfo list * ident (* name *) *
374 string mcode (* ( *) * parameter_list * string mcode (* ) *) *
375 string mcode (* { *) * statement dots *
376 string mcode (* } *)
377 | Include of string mcode (* #include *) * Ast.inc_file mcode (* file *)
3a314143 378 | Undef of string mcode (* #define *) * ident (* name *)
34e49164
C
379 | Define of string mcode (* #define *) * ident (* name *) *
380 define_parameters (*params*) * statement dots
381 | OptStm of statement
382 | UniqueStm of statement
383
384and fninfo =
385 FStorage of Ast.storage mcode
386 | FType of typeC
387 | FInline of string mcode
388 | FAttr of string mcode
389
390and ('a,'b) whencode =
391 WhenNot of 'a
392 | WhenAlways of 'b
393 | WhenModifier of Ast.when_modifier
1be43e12
C
394 | WhenNotTrue of expression
395 | WhenNotFalse of expression
34e49164
C
396
397and statement = base_statement wrap
398
399and base_case_line =
400 Default of string mcode (* default *) * string mcode (*:*) * statement dots
401 | Case of string mcode (* case *) * expression * string mcode (*:*) *
402 statement dots
fc1ad971
C
403 | DisjCase of string mcode * case_line list *
404 string mcode list (* the |s *) * string mcode
34e49164
C
405 | OptCase of case_line
406
407and case_line = base_case_line wrap
408
409(* --------------------------------------------------------------------- *)
410(* Positions *)
411
412and meta_pos =
413 MetaPos of Ast.meta_name mcode * Ast.meta_name list * Ast.meta_collect
34e49164
C
414
415(* --------------------------------------------------------------------- *)
416(* Top-level code *)
417
418and base_top_level =
65038c61
C
419 NONDECL of statement
420 | TOPCODE of statement dots
34e49164
C
421 | CODE of statement dots
422 | FILEINFO of string mcode (* old file *) * string mcode (* new file *)
423 | ERRORWORDS of expression list
424 | OTHER of statement (* temporary, disappears after top_level.ml *)
425
426and top_level = base_top_level wrap
427and rule = top_level list
428
429and parsed_rule =
430 CocciRule of
431 (rule * Ast.metavar list *
432 (string list * string list * Ast.dependency * string * Ast.exists)) *
faf9a90c 433 (rule * Ast.metavar list) * Ast.ruletype
174d1640 434 | ScriptRule of string (* name *) *
aba5c457
C
435 string * Ast.dependency *
436 (Ast.script_meta_name * Ast.meta_name * Ast.metavar) list *
413ffc02 437 Ast.meta_name list (*script vars*) *
174d1640
C
438 string
439 | InitialScriptRule of string (* name *) *string * Ast.dependency * string
440 | FinalScriptRule of string (* name *) *string * Ast.dependency * string
34e49164
C
441
442(* --------------------------------------------------------------------- *)
443
97111a47
C
444and dependency =
445 Dep of string (* rule applies for the current binding *)
446 | AntiDep of dependency (* rule doesn't apply for the current binding *)
447 | EverDep of string (* rule applies for some binding *)
448 | NeverDep of string (* rule never applies for any binding *)
449 | AndDep of dependency * dependency
450 | OrDep of dependency * dependency
451 | NoDep | FailDep
452
453(* --------------------------------------------------------------------- *)
454
34e49164
C
455and anything =
456 DotsExprTag of expression dots
457 | DotsInitTag of initialiser dots
458 | DotsParamTag of parameterTypeDef dots
459 | DotsStmtTag of statement dots
460 | DotsDeclTag of declaration dots
461 | DotsCaseTag of case_line dots
462 | IdentTag of ident
463 | ExprTag of expression
464 | ArgExprTag of expression (* for isos *)
465 | TestExprTag of expression (* for isos *)
466 | TypeCTag of typeC
467 | ParamTag of parameterTypeDef
468 | InitTag of initialiser
469 | DeclTag of declaration
470 | StmtTag of statement
471 | CaseLineTag of case_line
472 | TopTag of top_level
473 | IsoWhenTag of Ast.when_modifier
1be43e12
C
474 | IsoWhenTTag of expression
475 | IsoWhenFTag of expression
34e49164 476 | MetaPosTag of meta_pos
17ba0788 477 | HiddenVarTag of anything list (* in iso_compile/pattern only *)
34e49164
C
478
479let dotsExpr x = DotsExprTag x
480let dotsParam x = DotsParamTag x
481let dotsInit x = DotsInitTag x
482let dotsStmt x = DotsStmtTag x
483let dotsDecl x = DotsDeclTag x
484let dotsCase x = DotsCaseTag x
485let ident x = IdentTag x
486let expr x = ExprTag x
487let typeC x = TypeCTag x
488let param x = ParamTag x
489let ini x = InitTag x
490let decl x = DeclTag x
491let stmt x = StmtTag x
492let case_line x = CaseLineTag x
493let top x = TopTag x
494
495(* --------------------------------------------------------------------- *)
496(* Avoid cluttering the parser. Calculated in compute_lines.ml. *)
497
0708f913 498let pos_info =
34e49164
C
499 { line_start = -1; line_end = -1;
500 logical_start = -1; logical_end = -1;
0708f913
C
501 column = -1; offset = -1; }
502
503let default_info _ = (* why is this a function? *)
504 { pos_info = pos_info;
34e49164
C
505 attachable_start = true; attachable_end = true;
506 mcode_start = []; mcode_end = [];
97111a47 507 strings_before = []; strings_after = []; isSymbolIdent = false; }
34e49164
C
508
509let default_befaft _ =
510 MIXED(ref (Ast.NOTHING,default_token_info,default_token_info))
511let context_befaft _ =
512 CONTEXT(ref (Ast.NOTHING,default_token_info,default_token_info))
8babbc8f 513 let minus_befaft _ = MINUS(ref (Ast.NOREPLACEMENT,default_token_info))
34e49164
C
514
515let wrap x =
516 { node = x;
517 info = default_info();
518 index = ref (-1);
519 mcodekind = ref (default_befaft());
520 exp_ty = ref None;
521 bef_aft = NoDots;
522 true_if_arg = false;
523 true_if_test = false;
524 true_if_test_exp = false;
525 iso_info = [] }
526let context_wrap x =
527 { node = x;
528 info = default_info();
529 index = ref (-1);
530 mcodekind = ref (context_befaft());
531 exp_ty = ref None;
532 bef_aft = NoDots;
533 true_if_arg = false;
534 true_if_test = false;
535 true_if_test_exp = false;
536 iso_info = [] }
537let unwrap x = x.node
708f4980 538let unwrap_mcode (x,_,_,_,_,_) = x
34e49164 539let rewrap model x = { model with node = x }
708f4980
C
540let rewrap_mcode (_,arity,info,mcodekind,pos,adj) x =
541 (x,arity,info,mcodekind,pos,adj)
34e49164
C
542let copywrap model x =
543 { model with node = x; index = ref !(model.index);
544 mcodekind = ref !(model.mcodekind); exp_ty = ref !(model.exp_ty)}
708f4980
C
545let get_pos (_,_,_,_,x,_) = !x
546let get_pos_ref (_,_,_,_,x,_) = x
547let set_pos pos (m,arity,info,mcodekind,_,adj) =
548 (m,arity,info,mcodekind,ref pos,adj)
34e49164
C
549let get_info x = x.info
550let set_info x info = {x with info = info}
0708f913
C
551let get_line x = x.info.pos_info.line_start
552let get_line_end x = x.info.pos_info.line_end
34e49164
C
553let get_index x = !(x.index)
554let set_index x i = x.index := i
555let get_mcodekind x = !(x.mcodekind)
708f4980 556let get_mcode_mcodekind (_,_,_,mcodekind,_,_) = mcodekind
34e49164
C
557let get_mcodekind_ref x = x.mcodekind
558let set_mcodekind x mk = x.mcodekind := mk
559let set_type x t = x.exp_ty := t
560let get_type x = !(x.exp_ty)
561let get_dots_bef_aft x = x.bef_aft
562let set_dots_bef_aft x dots_bef_aft = {x with bef_aft = dots_bef_aft}
563let get_arg_exp x = x.true_if_arg
564let set_arg_exp x = {x with true_if_arg = true}
565let get_test_pos x = x.true_if_test
566let set_test_pos x = {x with true_if_test = true}
567let get_test_exp x = x.true_if_test_exp
568let set_test_exp x = {x with true_if_test_exp = true}
569let get_iso x = x.iso_info
570let set_iso x i = if !Flag.track_iso_usage then {x with iso_info = i} else x
708f4980 571let set_mcode_data data (_,ar,info,mc,pos,adj) = (data,ar,info,mc,pos,adj)
34e49164
C
572
573(* --------------------------------------------------------------------- *)
574
17ba0788
C
575let rec meta_pos_name = function
576 HiddenVarTag(vars) ->
577 (* totally fake, just drop the rest, only for isos *)
578 meta_pos_name (List.hd vars)
579 | MetaPosTag(MetaPos(name,constraints,_)) -> name
580 | ExprTag(e) ->
581 (match unwrap e with
582 MetaExpr(name,constraints,ty,form,pure) -> name
583 | _ -> failwith "bad metavariable")
584 | TypeCTag(t) ->
585 (match unwrap t with
586 MetaType(name,pure) -> name
587 | _ -> failwith "bad metavariable")
588 | DeclTag(d) ->
589 (match unwrap d with
590 MetaDecl(name,pure) -> name
591 | _ -> failwith "bad metavariable")
592 | InitTag(i) ->
593 (match unwrap i with
594 MetaInit(name,pure) -> name
595 | _ -> failwith "bad metavariable")
596 | StmtTag(s) ->
597 (match unwrap s with
598 MetaStmt(name,pure) -> name
599 | _ -> failwith "bad metavariable")
600 | _ -> failwith "bad metavariable"
601
602(* --------------------------------------------------------------------- *)
603
34e49164
C
604(* unique indices, for mcode and tree nodes *)
605let index_counter = ref 0
606let fresh_index _ = let cur = !index_counter in index_counter := cur + 1; cur
607
608(* --------------------------------------------------------------------- *)
609
610let undots d =
611 match unwrap d with
612 | DOTS e -> e
613 | CIRCLES e -> e
614 | STARS e -> e
615
616(* --------------------------------------------------------------------- *)
617
618let rec ast0_type_to_type ty =
619 match unwrap ty with
e6509c05 620 ConstVol(cv,ty) -> TC.ConstVol(const_vol cv,ast0_type_to_type ty)
faf9a90c 621 | BaseType(bty,strings) ->
e6509c05 622 TC.BaseType(baseType bty)
faf9a90c 623 | Signed(sgn,None) ->
e6509c05 624 TC.SignedT(sign sgn,None)
faf9a90c
C
625 | Signed(sgn,Some ty) ->
626 let bty = ast0_type_to_type ty in
e6509c05
C
627 TC.SignedT(sign sgn,Some bty)
628 | Pointer(ty,_) -> TC.Pointer(ast0_type_to_type ty)
34e49164 629 | FunctionPointer(ty,_,_,_,_,params,_) ->
e6509c05 630 TC.FunctionPointer(ast0_type_to_type ty)
65038c61 631 | FunctionType _ -> TC.Unknown (*failwith "not supported"*)
e6509c05 632 | Array(ety,_,_,_) -> TC.Array(ast0_type_to_type ety)
c491d8ee 633 | EnumName(su,Some tag) ->
faf9a90c
C
634 (match unwrap tag with
635 Id(tag) ->
e6509c05 636 TC.EnumName(TC.Name(unwrap_mcode tag))
8babbc8f 637 | MetaId(tag,_,_,_) ->
993936c0
C
638 (Common.pr2_once
639 "warning: enum with a metavariable name detected.";
640 Common.pr2_once
faf9a90c 641 "For type checking assuming the name of the metavariable is the name of the type\n";
e6509c05 642 TC.EnumName(TC.MV(unwrap_mcode tag,TC.Unitary,false)))
faf9a90c 643 | _ -> failwith "unexpected enum type name")
17ba0788 644 | EnumName(su,None) -> TC.EnumName TC.NoName
c491d8ee 645 | EnumDef(ty,_,_,_) -> ast0_type_to_type ty
34e49164
C
646 | StructUnionName(su,Some tag) ->
647 (match unwrap tag with
648 Id(tag) ->
e6509c05 649 TC.StructUnionName(structUnion su,TC.Name(unwrap_mcode tag))
8babbc8f 650 | MetaId(tag,Ast.IdNoConstraint,_,_) ->
993936c0
C
651 (Common.pr2_once
652 "warning: struct/union with a metavariable name detected.";
653 Common.pr2_once
34e49164 654 "For type checking assuming the name of the metavariable is the name of the type\n";
e6509c05
C
655 TC.StructUnionName(structUnion su,
656 TC.MV(unwrap_mcode tag,TC.Unitary,false)))
8babbc8f 657 | MetaId(tag,_,_,_) ->
e6509c05
C
658 (* would have to duplicate the type in type_cocci.ml?
659 perhaps polymorphism would help? *)
660 failwith "constraints not supported on struct type name"
34e49164 661 | _ -> failwith "unexpected struct/union type name")
17ba0788 662 | StructUnionName(su,None) -> TC.StructUnionName(structUnion su,TC.NoName)
34e49164 663 | StructUnionDef(ty,_,_,_) -> ast0_type_to_type ty
e6509c05 664 | TypeName(name) -> TC.TypeName(unwrap_mcode name)
34e49164 665 | MetaType(name,_) ->
e6509c05 666 TC.MetaType(unwrap_mcode name,TC.Unitary,false)
17ba0788 667 | AsType(ty,asty) -> failwith "not created yet"
978fd7e5
C
668 | DisjType(_,types,_,_) ->
669 Common.pr2_once
670 "disjtype not supported in smpl type inference, assuming unknown";
e6509c05 671 TC.Unknown
34e49164
C
672 | OptType(ty) | UniqueType(ty) ->
673 ast0_type_to_type ty
674
faf9a90c 675and baseType = function
e6509c05
C
676 Ast.VoidType -> TC.VoidType
677 | Ast.CharType -> TC.CharType
678 | Ast.ShortType -> TC.ShortType
f3c4ece6 679 | Ast.ShortIntType -> TC.ShortIntType
e6509c05
C
680 | Ast.IntType -> TC.IntType
681 | Ast.DoubleType -> TC.DoubleType
f3c4ece6 682 | Ast.LongDoubleType -> TC.LongDoubleType
e6509c05
C
683 | Ast.FloatType -> TC.FloatType
684 | Ast.LongType -> TC.LongType
f3c4ece6 685 | Ast.LongIntType -> TC.LongIntType
e6509c05 686 | Ast.LongLongType -> TC.LongLongType
f3c4ece6 687 | Ast.LongLongIntType -> TC.LongLongIntType
1eddfd50
C
688 | Ast.SizeType -> TC.SizeType
689 | Ast.SSizeType -> TC.SSizeType
690 | Ast.PtrDiffType -> TC.PtrDiffType
34e49164
C
691
692and structUnion t =
693 match unwrap_mcode t with
e6509c05
C
694 Ast.Struct -> TC.Struct
695 | Ast.Union -> TC.Union
34e49164
C
696
697and sign t =
698 match unwrap_mcode t with
e6509c05
C
699 Ast.Signed -> TC.Signed
700 | Ast.Unsigned -> TC.Unsigned
34e49164
C
701
702and const_vol t =
703 match unwrap_mcode t with
e6509c05
C
704 Ast.Const -> TC.Const
705 | Ast.Volatile -> TC.Volatile
34e49164
C
706
707(* --------------------------------------------------------------------- *)
708(* this function is a rather minimal attempt. the problem is that information
709has been lost. but since it is only used for metavariable types in the isos,
710perhaps it doesn't matter *)
8f657093
C
711and make_mcode x = (x,NONE,default_info(),context_befaft(),ref [],-1)
712let make_mcode_info x info = (x,NONE,info,context_befaft(),ref [],-1)
c491d8ee 713and make_minus_mcode x =
8f657093 714 (x,NONE,default_info(),minus_befaft(),ref [],-1)
34e49164
C
715
716exception TyConv
717
718let rec reverse_type ty =
719 match ty with
e6509c05 720 TC.ConstVol(cv,ty) ->
485bce71 721 ConstVol(reverse_const_vol cv,context_wrap(reverse_type ty))
e6509c05 722 | TC.BaseType(bty) ->
faf9a90c 723 BaseType(reverse_baseType bty,[(* not used *)])
e6509c05
C
724 | TC.SignedT(sgn,None) -> Signed(reverse_sign sgn,None)
725 | TC.SignedT(sgn,Some bty) ->
faf9a90c 726 Signed(reverse_sign sgn,Some (context_wrap(reverse_type ty)))
e6509c05 727 | TC.Pointer(ty) ->
485bce71 728 Pointer(context_wrap(reverse_type ty),make_mcode "*")
e6509c05
C
729 | TC.EnumName(TC.MV(name,_,_)) ->
730 EnumName
731 (make_mcode "enum",
8babbc8f 732 Some (context_wrap(MetaId(make_mcode name,Ast.IdNoConstraint,Ast.NoVal,
e6509c05
C
733 Impure))))
734 | TC.EnumName(TC.Name tag) ->
735 EnumName(make_mcode "enum",Some(context_wrap(Id(make_mcode tag))))
736 | TC.StructUnionName(su,TC.MV(name,_,_)) ->
737 (* not right?... *)
738 StructUnionName
739 (reverse_structUnion su,
8babbc8f 740 Some(context_wrap(MetaId(make_mcode name,Ast.IdNoConstraint,Ast.NoVal,
e6509c05
C
741 Impure(*not really right*)))))
742 | TC.StructUnionName(su,TC.Name tag) ->
743 StructUnionName
744 (reverse_structUnion su,
745 Some (context_wrap(Id(make_mcode tag))))
746 | TC.TypeName(name) -> TypeName(make_mcode name)
747 | TC.MetaType(name,_,_) ->
34e49164
C
748 MetaType(make_mcode name,Impure(*not really right*))
749 | _ -> raise TyConv
750
faf9a90c 751and reverse_baseType = function
e6509c05
C
752 TC.VoidType -> Ast.VoidType
753 | TC.CharType -> Ast.CharType
754 | TC.BoolType -> Ast.IntType
755 | TC.ShortType -> Ast.ShortType
f3c4ece6 756 | TC.ShortIntType -> Ast.ShortIntType
e6509c05
C
757 | TC.IntType -> Ast.IntType
758 | TC.DoubleType -> Ast.DoubleType
f3c4ece6 759 | TC.LongDoubleType -> Ast.LongDoubleType
e6509c05
C
760 | TC.FloatType -> Ast.FloatType
761 | TC.LongType -> Ast.LongType
f3c4ece6 762 | TC.LongIntType -> Ast.LongIntType
e6509c05 763 | TC.LongLongType -> Ast.LongLongType
f3c4ece6 764 | TC.LongLongIntType -> Ast.LongLongIntType
1eddfd50
C
765 | TC.SizeType -> Ast.SizeType
766 | TC.SSizeType -> Ast.SSizeType
767 | TC.PtrDiffType -> Ast.PtrDiffType
768
34e49164
C
769
770and reverse_structUnion t =
771 make_mcode
772 (match t with
e6509c05
C
773 TC.Struct -> Ast.Struct
774 | TC.Union -> Ast.Union)
34e49164
C
775
776and reverse_sign t =
777 make_mcode
778 (match t with
e6509c05
C
779 TC.Signed -> Ast.Signed
780 | TC.Unsigned -> Ast.Unsigned)
34e49164
C
781
782and reverse_const_vol t =
783 make_mcode
784 (match t with
e6509c05
C
785 TC.Const -> Ast.Const
786 | TC.Volatile -> Ast.Volatile)
34e49164
C
787
788(* --------------------------------------------------------------------- *)
789
790let lub_pure x y =
791 match (x,y) with
792 (Impure,_) | (_,Impure) -> Impure
793 | (Pure,Context) | (Context,Pure) -> Impure
794 | (Pure,_) | (_,Pure) -> Pure
795 | (_,Context) | (Context,_) -> Context
796 | _ -> PureContext
797
798(* --------------------------------------------------------------------- *)
799
800let rule_name = ref "" (* for the convenience of the parser *)