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