00eb537d5f1561787af74ab05419eb4b816c20b3
[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 module TC = Type_cocci
27
28 (* --------------------------------------------------------------------- *)
29 (* Modified code *)
30
31 type arity = OPT | UNIQUE | NONE
32
33 type token_info =
34 { tline_start : int; tline_end : int;
35 left_offset : int; right_offset : int }
36 let 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
40 CONTEXT - see insert_plus.ml *)
41
42 type mcodekind =
43 MINUS of (Ast.anything Ast.replacement * 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 list 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 : TC.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 * Ast.seed * pure
107 | MetaFunc of Ast.meta_name mcode * Ast.idconstraint * pure
108 | MetaLocalFunc of Ast.meta_name mcode * Ast.idconstraint * pure
109 | DisjId of string mcode * ident list *
110 string mcode list (* the |s *) * string mcode
111 | OptIdent of ident
112 | UniqueIdent of ident
113
114 and ident = base_ident wrap
115
116 (* --------------------------------------------------------------------- *)
117 (* Expression *)
118
119 and base_expression =
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 *)
145 | MetaErr of Ast.meta_name mcode * constraints * pure
146 | MetaExpr of Ast.meta_name mcode * constraints *
147 TC.typeC list option * Ast.form * pure
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
161 and expression = base_expression wrap
162
163 and constraints =
164 NoConstraint
165 | NotIdCstrt of Ast.reconstraint
166 | NotExpCstrt of expression list
167 | SubExpCstrt of Ast.meta_name list
168
169 and listlen =
170 MetaListLen of Ast.meta_name mcode
171 | CstListLen of int
172 | AnyListLen
173
174 (* --------------------------------------------------------------------- *)
175 (* Types *)
176
177 and base_typeC =
178 ConstVol of Ast.const_vol mcode * typeC
179 | BaseType of Ast.baseType * string mcode list
180 | Signed of Ast.sign mcode * typeC option
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 (* ] *)
190 | EnumName of string mcode (*enum*) * ident option (* name *)
191 | EnumDef of typeC (* either StructUnionName or metavar *) *
192 string mcode (* { *) * expression dots * string mcode (* } *)
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
203 and 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
210 and base_declaration =
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 *)
216 | MetaFieldList of Ast.meta_name mcode * listlen * pure (* structure fields *)
217 | Init of Ast.storage mcode option * typeC * ident * string mcode (*=*) *
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
231 and declaration = base_declaration wrap
232
233 (* --------------------------------------------------------------------- *)
234 (* Initializers *)
235
236 and base_initialiser =
237 MetaInit of Ast.meta_name mcode * pure
238 | MetaInitList of Ast.meta_name mcode * listlen * pure
239 | InitExpr of expression
240 | InitList of string mcode (*{*) * initialiser_list * string mcode (*}*) *
241 (* true if ordered, as for array, false if unordered, as for struct *)
242 bool
243 | InitGccExt of
244 designator list (* name *) * string mcode (*=*) *
245 initialiser (* gccext: *)
246 | InitGccName of ident (* name *) * string mcode (*:*) *
247 initialiser
248 | IComma of string mcode (* , *)
249 | Idots of string mcode (* ... *) * initialiser option (* whencode *)
250 | OptIni of initialiser
251 | UniqueIni of initialiser
252
253 and 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
260 and initialiser = base_initialiser wrap
261
262 and initialiser_list = initialiser dots
263
264 (* --------------------------------------------------------------------- *)
265 (* Parameter *)
266
267 and 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
278 and parameterTypeDef = base_parameterTypeDef wrap
279
280 and parameter_list = parameterTypeDef dots
281
282 (* --------------------------------------------------------------------- *)
283 (* #define Parameters *)
284
285 and 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
293 and define_param = base_define_param wrap
294
295 and base_define_parameters =
296 NoParams
297 | DParams of string mcode(*( *) * define_param dots * string mcode(* )*)
298
299 and define_parameters = base_define_parameters wrap
300
301 (* --------------------------------------------------------------------- *)
302 (* Statement*)
303
304 and base_statement =
305 Decl of (info * mcodekind) (* before the decl *) * declaration
306 | Seq of string mcode (* { *) * statement dots *
307 string mcode (* } *)
308 | ExprStatement of expression option * string mcode (*;*)
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 (* { *) *
333 statement (*decl*) dots *
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 *)
347 | TopInit of initialiser (* only at top level *)
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 *)
364 | Undef of string mcode (* #define *) * ident (* name *)
365 | Define of string mcode (* #define *) * ident (* name *) *
366 define_parameters (*params*) * statement dots
367 | OptStm of statement
368 | UniqueStm of statement
369
370 and fninfo =
371 FStorage of Ast.storage mcode
372 | FType of typeC
373 | FInline of string mcode
374 | FAttr of string mcode
375
376 and ('a,'b) whencode =
377 WhenNot of 'a
378 | WhenAlways of 'b
379 | WhenModifier of Ast.when_modifier
380 | WhenNotTrue of expression
381 | WhenNotFalse of expression
382
383 and statement = base_statement wrap
384
385 and 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
389 | DisjCase of string mcode * case_line list *
390 string mcode list (* the |s *) * string mcode
391 | OptCase of case_line
392
393 and case_line = base_case_line wrap
394
395 (* --------------------------------------------------------------------- *)
396 (* Positions *)
397
398 and meta_pos =
399 MetaPos of Ast.meta_name mcode * Ast.meta_name list * Ast.meta_collect
400
401 (* --------------------------------------------------------------------- *)
402 (* Top-level code *)
403
404 and base_top_level =
405 DECL of statement
406 | CODE of statement dots
407 | FILEINFO of string mcode (* old file *) * string mcode (* new file *)
408 | ERRORWORDS of expression list
409 | OTHER of statement (* temporary, disappears after top_level.ml *)
410
411 and top_level = base_top_level wrap
412 and rule = top_level list
413
414 and parsed_rule =
415 CocciRule of
416 (rule * Ast.metavar list *
417 (string list * string list * Ast.dependency * string * Ast.exists)) *
418 (rule * Ast.metavar list) * Ast.ruletype
419 | ScriptRule of string (* name *) *
420 string * Ast.dependency *
421 (Ast.script_meta_name * Ast.meta_name * Ast.metavar) list *
422 Ast.meta_name list (*script vars*) *
423 string
424 | InitialScriptRule of string (* name *) *string * Ast.dependency * string
425 | FinalScriptRule of string (* name *) *string * Ast.dependency * string
426
427 (* --------------------------------------------------------------------- *)
428
429 and anything =
430 DotsExprTag of expression dots
431 | DotsInitTag of initialiser dots
432 | DotsParamTag of parameterTypeDef dots
433 | DotsStmtTag of statement dots
434 | DotsDeclTag of declaration dots
435 | DotsCaseTag of case_line dots
436 | IdentTag of ident
437 | ExprTag of expression
438 | ArgExprTag of expression (* for isos *)
439 | TestExprTag of expression (* for isos *)
440 | TypeCTag of typeC
441 | ParamTag of parameterTypeDef
442 | InitTag of initialiser
443 | DeclTag of declaration
444 | StmtTag of statement
445 | CaseLineTag of case_line
446 | TopTag of top_level
447 | IsoWhenTag of Ast.when_modifier
448 | IsoWhenTTag of expression
449 | IsoWhenFTag of expression
450 | MetaPosTag of meta_pos
451
452 let dotsExpr x = DotsExprTag x
453 let dotsParam x = DotsParamTag x
454 let dotsInit x = DotsInitTag x
455 let dotsStmt x = DotsStmtTag x
456 let dotsDecl x = DotsDeclTag x
457 let dotsCase x = DotsCaseTag x
458 let ident x = IdentTag x
459 let expr x = ExprTag x
460 let typeC x = TypeCTag x
461 let param x = ParamTag x
462 let ini x = InitTag x
463 let decl x = DeclTag x
464 let stmt x = StmtTag x
465 let case_line x = CaseLineTag x
466 let top x = TopTag x
467
468 (* --------------------------------------------------------------------- *)
469 (* Avoid cluttering the parser. Calculated in compute_lines.ml. *)
470
471 let pos_info =
472 { line_start = -1; line_end = -1;
473 logical_start = -1; logical_end = -1;
474 column = -1; offset = -1; }
475
476 let default_info _ = (* why is this a function? *)
477 { pos_info = pos_info;
478 attachable_start = true; attachable_end = true;
479 mcode_start = []; mcode_end = [];
480 strings_before = []; strings_after = [] }
481
482 let default_befaft _ =
483 MIXED(ref (Ast.NOTHING,default_token_info,default_token_info))
484 let context_befaft _ =
485 CONTEXT(ref (Ast.NOTHING,default_token_info,default_token_info))
486 let minus_befaft _ = MINUS(ref (Ast.NOREPLACEMENT,default_token_info))
487
488 let wrap x =
489 { node = x;
490 info = default_info();
491 index = ref (-1);
492 mcodekind = ref (default_befaft());
493 exp_ty = ref None;
494 bef_aft = NoDots;
495 true_if_arg = false;
496 true_if_test = false;
497 true_if_test_exp = false;
498 iso_info = [] }
499 let context_wrap x =
500 { node = x;
501 info = default_info();
502 index = ref (-1);
503 mcodekind = ref (context_befaft());
504 exp_ty = ref None;
505 bef_aft = NoDots;
506 true_if_arg = false;
507 true_if_test = false;
508 true_if_test_exp = false;
509 iso_info = [] }
510 let unwrap x = x.node
511 let unwrap_mcode (x,_,_,_,_,_) = x
512 let rewrap model x = { model with node = x }
513 let rewrap_mcode (_,arity,info,mcodekind,pos,adj) x =
514 (x,arity,info,mcodekind,pos,adj)
515 let copywrap model x =
516 { model with node = x; index = ref !(model.index);
517 mcodekind = ref !(model.mcodekind); exp_ty = ref !(model.exp_ty)}
518 let get_pos (_,_,_,_,x,_) = !x
519 let get_pos_ref (_,_,_,_,x,_) = x
520 let set_pos pos (m,arity,info,mcodekind,_,adj) =
521 (m,arity,info,mcodekind,ref pos,adj)
522 let get_info x = x.info
523 let set_info x info = {x with info = info}
524 let get_line x = x.info.pos_info.line_start
525 let get_line_end x = x.info.pos_info.line_end
526 let get_index x = !(x.index)
527 let set_index x i = x.index := i
528 let get_mcodekind x = !(x.mcodekind)
529 let get_mcode_mcodekind (_,_,_,mcodekind,_,_) = mcodekind
530 let get_mcodekind_ref x = x.mcodekind
531 let set_mcodekind x mk = x.mcodekind := mk
532 let set_type x t = x.exp_ty := t
533 let get_type x = !(x.exp_ty)
534 let get_dots_bef_aft x = x.bef_aft
535 let set_dots_bef_aft x dots_bef_aft = {x with bef_aft = dots_bef_aft}
536 let get_arg_exp x = x.true_if_arg
537 let set_arg_exp x = {x with true_if_arg = true}
538 let get_test_pos x = x.true_if_test
539 let set_test_pos x = {x with true_if_test = true}
540 let get_test_exp x = x.true_if_test_exp
541 let set_test_exp x = {x with true_if_test_exp = true}
542 let get_iso x = x.iso_info
543 let set_iso x i = if !Flag.track_iso_usage then {x with iso_info = i} else x
544 let set_mcode_data data (_,ar,info,mc,pos,adj) = (data,ar,info,mc,pos,adj)
545
546 (* --------------------------------------------------------------------- *)
547
548 (* unique indices, for mcode and tree nodes *)
549 let index_counter = ref 0
550 let fresh_index _ = let cur = !index_counter in index_counter := cur + 1; cur
551
552 (* --------------------------------------------------------------------- *)
553
554 let undots d =
555 match unwrap d with
556 | DOTS e -> e
557 | CIRCLES e -> e
558 | STARS e -> e
559
560 (* --------------------------------------------------------------------- *)
561
562 let rec ast0_type_to_type ty =
563 match unwrap ty with
564 ConstVol(cv,ty) -> TC.ConstVol(const_vol cv,ast0_type_to_type ty)
565 | BaseType(bty,strings) ->
566 TC.BaseType(baseType bty)
567 | Signed(sgn,None) ->
568 TC.SignedT(sign sgn,None)
569 | Signed(sgn,Some ty) ->
570 let bty = ast0_type_to_type ty in
571 TC.SignedT(sign sgn,Some bty)
572 | Pointer(ty,_) -> TC.Pointer(ast0_type_to_type ty)
573 | FunctionPointer(ty,_,_,_,_,params,_) ->
574 TC.FunctionPointer(ast0_type_to_type ty)
575 | FunctionType _ -> failwith "not supported"
576 | Array(ety,_,_,_) -> TC.Array(ast0_type_to_type ety)
577 | EnumName(su,Some tag) ->
578 (match unwrap tag with
579 Id(tag) ->
580 TC.EnumName(TC.Name(unwrap_mcode tag))
581 | MetaId(tag,_,_,_) ->
582 (Printf.printf
583 "warning: enum with a metavariable name detected.\n";
584 Printf.printf
585 "For type checking assuming the name of the metavariable is the name of the type\n";
586 TC.EnumName(TC.MV(unwrap_mcode tag,TC.Unitary,false)))
587 | _ -> failwith "unexpected enum type name")
588 | EnumName(su,None) -> failwith "nameless enum - what to do???"
589 | EnumDef(ty,_,_,_) -> ast0_type_to_type ty
590 | StructUnionName(su,Some tag) ->
591 (match unwrap tag with
592 Id(tag) ->
593 TC.StructUnionName(structUnion su,TC.Name(unwrap_mcode tag))
594 | MetaId(tag,Ast.IdNoConstraint,_,_) ->
595 (Common.pr2
596 "warning: struct/union with a metavariable name detected.\n";
597 Common.pr2
598 "For type checking assuming the name of the metavariable is the name of the type\n";
599 TC.StructUnionName(structUnion su,
600 TC.MV(unwrap_mcode tag,TC.Unitary,false)))
601 | MetaId(tag,_,_,_) ->
602 (* would have to duplicate the type in type_cocci.ml?
603 perhaps polymorphism would help? *)
604 failwith "constraints not supported on struct type name"
605 | _ -> failwith "unexpected struct/union type name")
606 | StructUnionName(su,None) -> failwith "nameless structure - what to do???"
607 | StructUnionDef(ty,_,_,_) -> ast0_type_to_type ty
608 | TypeName(name) -> TC.TypeName(unwrap_mcode name)
609 | MetaType(name,_) ->
610 TC.MetaType(unwrap_mcode name,TC.Unitary,false)
611 | DisjType(_,types,_,_) ->
612 Common.pr2_once
613 "disjtype not supported in smpl type inference, assuming unknown";
614 TC.Unknown
615 | OptType(ty) | UniqueType(ty) ->
616 ast0_type_to_type ty
617
618 and baseType = function
619 Ast.VoidType -> TC.VoidType
620 | Ast.CharType -> TC.CharType
621 | Ast.ShortType -> TC.ShortType
622 | Ast.IntType -> TC.IntType
623 | Ast.DoubleType -> TC.DoubleType
624 | Ast.FloatType -> TC.FloatType
625 | Ast.LongType -> TC.LongType
626 | Ast.LongLongType -> TC.LongLongType
627 | Ast.SizeType -> TC.SizeType
628 | Ast.SSizeType -> TC.SSizeType
629 | Ast.PtrDiffType -> TC.PtrDiffType
630
631 and structUnion t =
632 match unwrap_mcode t with
633 Ast.Struct -> TC.Struct
634 | Ast.Union -> TC.Union
635
636 and sign t =
637 match unwrap_mcode t with
638 Ast.Signed -> TC.Signed
639 | Ast.Unsigned -> TC.Unsigned
640
641 and const_vol t =
642 match unwrap_mcode t with
643 Ast.Const -> TC.Const
644 | Ast.Volatile -> TC.Volatile
645
646 (* --------------------------------------------------------------------- *)
647 (* this function is a rather minimal attempt. the problem is that information
648 has been lost. but since it is only used for metavariable types in the isos,
649 perhaps it doesn't matter *)
650 and make_mcode x = (x,NONE,default_info(),context_befaft(),ref [],-1)
651 let make_mcode_info x info = (x,NONE,info,context_befaft(),ref [],-1)
652 and make_minus_mcode x =
653 (x,NONE,default_info(),minus_befaft(),ref [],-1)
654
655 exception TyConv
656
657 let rec reverse_type ty =
658 match ty with
659 TC.ConstVol(cv,ty) ->
660 ConstVol(reverse_const_vol cv,context_wrap(reverse_type ty))
661 | TC.BaseType(bty) ->
662 BaseType(reverse_baseType bty,[(* not used *)])
663 | TC.SignedT(sgn,None) -> Signed(reverse_sign sgn,None)
664 | TC.SignedT(sgn,Some bty) ->
665 Signed(reverse_sign sgn,Some (context_wrap(reverse_type ty)))
666 | TC.Pointer(ty) ->
667 Pointer(context_wrap(reverse_type ty),make_mcode "*")
668 | TC.EnumName(TC.MV(name,_,_)) ->
669 EnumName
670 (make_mcode "enum",
671 Some (context_wrap(MetaId(make_mcode name,Ast.IdNoConstraint,Ast.NoVal,
672 Impure))))
673 | TC.EnumName(TC.Name tag) ->
674 EnumName(make_mcode "enum",Some(context_wrap(Id(make_mcode tag))))
675 | TC.StructUnionName(su,TC.MV(name,_,_)) ->
676 (* not right?... *)
677 StructUnionName
678 (reverse_structUnion su,
679 Some(context_wrap(MetaId(make_mcode name,Ast.IdNoConstraint,Ast.NoVal,
680 Impure(*not really right*)))))
681 | TC.StructUnionName(su,TC.Name tag) ->
682 StructUnionName
683 (reverse_structUnion su,
684 Some (context_wrap(Id(make_mcode tag))))
685 | TC.TypeName(name) -> TypeName(make_mcode name)
686 | TC.MetaType(name,_,_) ->
687 MetaType(make_mcode name,Impure(*not really right*))
688 | _ -> raise TyConv
689
690 and reverse_baseType = function
691 TC.VoidType -> Ast.VoidType
692 | TC.CharType -> Ast.CharType
693 | TC.BoolType -> Ast.IntType
694 | TC.ShortType -> Ast.ShortType
695 | TC.IntType -> Ast.IntType
696 | TC.DoubleType -> Ast.DoubleType
697 | TC.FloatType -> Ast.FloatType
698 | TC.LongType -> Ast.LongType
699 | TC.LongLongType -> Ast.LongLongType
700 | TC.SizeType -> Ast.SizeType
701 | TC.SSizeType -> Ast.SSizeType
702 | TC.PtrDiffType -> Ast.PtrDiffType
703
704
705 and reverse_structUnion t =
706 make_mcode
707 (match t with
708 TC.Struct -> Ast.Struct
709 | TC.Union -> Ast.Union)
710
711 and reverse_sign t =
712 make_mcode
713 (match t with
714 TC.Signed -> Ast.Signed
715 | TC.Unsigned -> Ast.Unsigned)
716
717 and reverse_const_vol t =
718 make_mcode
719 (match t with
720 TC.Const -> Ast.Const
721 | TC.Volatile -> Ast.Volatile)
722
723 (* --------------------------------------------------------------------- *)
724
725 let lub_pure x y =
726 match (x,y) with
727 (Impure,_) | (_,Impure) -> Impure
728 | (Pure,Context) | (Context,Pure) -> Impure
729 | (Pure,_) | (_,Pure) -> Pure
730 | (_,Context) | (Context,_) -> Context
731 | _ -> PureContext
732
733 (* --------------------------------------------------------------------- *)
734
735 let rule_name = ref "" (* for the convenience of the parser *)