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