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