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