Release coccinelle-0.2.3rc1
[bpt/coccinelle.git] / parsing_cocci / ast0_cocci.ml
1 (*
2 * Copyright 2005-2010, Ecole des Mines de Nantes, University of Copenhagen
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
23 (*
24 * Copyright 2005-2010, Ecole des Mines de Nantes, University of Copenhagen
25 * Yoann Padioleau, Julia Lawall, Rene Rydhof Hansen, Henrik Stuart, Gilles Muller, Nicolas Palix
26 * This file is part of Coccinelle.
27 *
28 * Coccinelle is free software: you can redistribute it and/or modify
29 * it under the terms of the GNU General Public License as published by
30 * the Free Software Foundation, according to version 2 of the License.
31 *
32 * Coccinelle is distributed in the hope that it will be useful,
33 * but WITHOUT ANY WARRANTY; without even the implied warranty of
34 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
35 * GNU General Public License for more details.
36 *
37 * You should have received a copy of the GNU General Public License
38 * along with Coccinelle. If not, see <http://www.gnu.org/licenses/>.
39 *
40 * The authors reserve the right to distribute this or future versions of
41 * Coccinelle under other licenses.
42 *)
43
44
45 module Ast = Ast_cocci
46
47 (* --------------------------------------------------------------------- *)
48 (* Modified code *)
49
50 type arity = OPT | UNIQUE | NONE
51
52 type token_info =
53 { tline_start : int; tline_end : int;
54 left_offset : int; right_offset : int }
55 let default_token_info =
56 { tline_start = -1; tline_end = -1; left_offset = -1; right_offset = -1 }
57
58 (* MIXED is like CONTEXT, since sometimes MIXED things have to revert to
59 CONTEXT - see insert_plus.ml *)
60 type count = ONE (* + *) | MANY (* ++ *)
61
62 type mcodekind =
63 MINUS of (Ast.anything list list * token_info) ref
64 | PLUS of Ast.count
65 | CONTEXT of (Ast.anything Ast.befaft * token_info * token_info) ref
66 | MIXED of (Ast.anything Ast.befaft * token_info * token_info) ref
67
68 type position_info = { line_start : int; line_end : int;
69 logical_start : int; logical_end : int;
70 column : int; offset : int; }
71
72 type info = { pos_info : position_info;
73 attachable_start : bool; attachable_end : bool;
74 mcode_start : mcodekind list; mcode_end : mcodekind list;
75 (* the following are only for + code *)
76 strings_before : (Ast.added_string * position_info) list;
77 strings_after : (Ast.added_string * position_info) list }
78
79 (* adjacency index is incremented when we skip over dots or nest delimiters
80 it is used in deciding how much to remove, when two adjacent code tokens are
81 removed. *)
82 type 'a mcode =
83 'a * arity * info * mcodekind * meta_pos ref (* pos, - only *) *
84 int (* adjacency_index *)
85 (* int ref is an index *)
86 and 'a wrap =
87 { node : 'a;
88 info : info;
89 index : int ref;
90 mcodekind : mcodekind ref;
91 exp_ty : Type_cocci.typeC option ref; (* only for expressions *)
92 bef_aft : dots_bef_aft; (* only for statements *)
93 true_if_arg : bool; (* true if "arg_exp", only for exprs *)
94 true_if_test : bool; (* true if "test position", only for exprs *)
95 true_if_test_exp : bool;(* true if "test_exp from iso", only for exprs *)
96 (*nonempty if this represents the use of an iso*)
97 iso_info : (string*anything) list }
98
99 and dots_bef_aft =
100 NoDots | AddingBetweenDots of statement | DroppingBetweenDots of statement
101
102 (* for iso metavariables, true if they can only match nonmodified terms with
103 all metavariables unitary
104 for SP metavariables, true if the metavariable is unitary (valid up to
105 isomorphism phase only)
106 In SP, the only options are impure and context
107 *)
108 and pure = Impure | Pure | Context | PureContext (* pure and only context *)
109
110 (* --------------------------------------------------------------------- *)
111 (* --------------------------------------------------------------------- *)
112 (* Dots *)
113
114 and 'a base_dots =
115 DOTS of 'a list
116 | CIRCLES of 'a list
117 | STARS of 'a list
118
119 and 'a dots = 'a base_dots wrap
120
121 (* --------------------------------------------------------------------- *)
122 (* Identifier *)
123
124 and base_ident =
125 Id of string mcode
126 | MetaId of Ast.meta_name mcode * Ast.idconstraint * pure
127 | MetaFunc of Ast.meta_name mcode * Ast.idconstraint * pure
128 | MetaLocalFunc of Ast.meta_name mcode * Ast.idconstraint * pure
129 | OptIdent of ident
130 | UniqueIdent of ident
131
132 and ident = base_ident wrap
133
134 (* --------------------------------------------------------------------- *)
135 (* Expression *)
136
137 and base_expression =
138 Ident of ident
139 | Constant of Ast.constant mcode
140 | FunCall of expression * string mcode (* ( *) *
141 expression dots * string mcode (* ) *)
142 | Assignment of expression * Ast.assignOp mcode * expression *
143 bool (* true if it can match an initialization *)
144 | CondExpr of expression * string mcode (* ? *) * expression option *
145 string mcode (* : *) * expression
146 | Postfix of expression * Ast.fixOp mcode
147 | Infix of expression * Ast.fixOp mcode
148 | Unary of expression * Ast.unaryOp mcode
149 | Binary of expression * Ast.binaryOp mcode * expression
150 | Nested of expression * Ast.binaryOp mcode * expression
151 | Paren of string mcode (* ( *) * expression *
152 string mcode (* ) *)
153 | ArrayAccess of expression * string mcode (* [ *) * expression *
154 string mcode (* ] *)
155 | RecordAccess of expression * string mcode (* . *) * ident
156 | RecordPtAccess of expression * string mcode (* -> *) * ident
157 | Cast of string mcode (* ( *) * typeC * string mcode (* ) *) *
158 expression
159 | SizeOfExpr of string mcode (* sizeof *) * expression
160 | SizeOfType of string mcode (* sizeof *) * string mcode (* ( *) *
161 typeC * string mcode (* ) *)
162 | TypeExp of typeC (* type name used as an expression, only in args *)
163 | MetaErr of Ast.meta_name mcode * constraints * pure
164 | MetaExpr of Ast.meta_name mcode * constraints *
165 Type_cocci.typeC list option * Ast.form * pure
166 | MetaExprList of Ast.meta_name mcode (* only in arg lists *) *
167 listlen * pure
168 | EComma of string mcode (* only in arg lists *)
169 | DisjExpr of string mcode * expression list *
170 string mcode list (* the |s *) * string mcode
171 | NestExpr of string mcode * expression dots * string mcode *
172 expression option * Ast.multi
173 | Edots of string mcode (* ... *) * expression option
174 | Ecircles of string mcode (* ooo *) * expression option
175 | Estars of string mcode (* *** *) * expression option
176 | OptExp of expression
177 | UniqueExp of expression
178
179 and expression = base_expression wrap
180
181 and constraints =
182 NoConstraint
183 | NotIdCstrt of Ast.reconstraint
184 | NotExpCstrt of expression list
185 | SubExpCstrt of Ast.meta_name list
186
187 and listlen = Ast.meta_name mcode option
188
189 (* --------------------------------------------------------------------- *)
190 (* Types *)
191
192 and base_typeC =
193 ConstVol of Ast.const_vol mcode * typeC
194 | BaseType of Ast.baseType * string mcode list
195 | Signed of Ast.sign mcode * typeC option
196 | Pointer of typeC * string mcode (* * *)
197 | FunctionPointer of typeC *
198 string mcode(* ( *)*string mcode(* * *)*string mcode(* ) *)*
199 string mcode (* ( *)*parameter_list*string mcode(* ) *)
200 | FunctionType of typeC option *
201 string mcode (* ( *) * parameter_list *
202 string mcode (* ) *)
203 | Array of typeC * string mcode (* [ *) *
204 expression option * string mcode (* ] *)
205 | EnumName of string mcode (*enum*) * ident (* name *)
206 | StructUnionName of Ast.structUnion mcode * ident option (* name *)
207 | StructUnionDef of typeC (* either StructUnionName or metavar *) *
208 string mcode (* { *) * declaration dots * string mcode (* } *)
209 | TypeName of string mcode
210 | MetaType of Ast.meta_name mcode * pure
211 | DisjType of string mcode * typeC list * (* only after iso *)
212 string mcode list (* the |s *) * string mcode
213 | OptType of typeC
214 | UniqueType of typeC
215
216 and typeC = base_typeC wrap
217
218 (* --------------------------------------------------------------------- *)
219 (* Variable declaration *)
220 (* Even if the Cocci program specifies a list of declarations, they are
221 split out into multiple declarations of a single variable each. *)
222
223 and base_declaration =
224 Init of Ast.storage mcode option * typeC * ident * string mcode (*=*) *
225 initialiser * string mcode (*;*)
226 | UnInit of Ast.storage mcode option * typeC * ident * string mcode (* ; *)
227 | TyDecl of typeC * string mcode (* ; *)
228 | MacroDecl of ident (* name *) * string mcode (* ( *) *
229 expression dots * string mcode (* ) *) * string mcode (* ; *)
230 | Typedef of string mcode (* typedef *) * typeC * typeC * string mcode (*;*)
231 | DisjDecl of string mcode * declaration list *
232 string mcode list (* the |s *) * string mcode
233 (* Ddots is for a structure declaration *)
234 | Ddots of string mcode (* ... *) * declaration option (* whencode *)
235 | OptDecl of declaration
236 | UniqueDecl of declaration
237
238 and declaration = base_declaration wrap
239
240 (* --------------------------------------------------------------------- *)
241 (* Initializers *)
242
243 and base_initialiser =
244 MetaInit of Ast.meta_name mcode * pure
245 | InitExpr of expression
246 | InitList of string mcode (*{*) * initialiser_list * string mcode (*}*)
247 | InitGccExt of
248 designator list (* name *) * string mcode (*=*) *
249 initialiser (* gccext: *)
250 | InitGccName of ident (* name *) * string mcode (*:*) *
251 initialiser
252 | IComma of string mcode (* , *)
253 | Idots of string mcode (* ... *) * initialiser option (* whencode *)
254 | OptIni of initialiser
255 | UniqueIni of initialiser
256
257 and designator =
258 DesignatorField of string mcode (* . *) * ident
259 | DesignatorIndex of string mcode (* [ *) * expression * string mcode (* ] *)
260 | DesignatorRange of
261 string mcode (* [ *) * expression * string mcode (* ... *) *
262 expression * string mcode (* ] *)
263
264 and initialiser = base_initialiser wrap
265
266 and initialiser_list = initialiser dots
267
268 (* --------------------------------------------------------------------- *)
269 (* Parameter *)
270
271 and base_parameterTypeDef =
272 VoidParam of typeC
273 | Param of typeC * ident option
274 | MetaParam of Ast.meta_name mcode * pure
275 | MetaParamList of Ast.meta_name mcode * listlen * pure
276 | PComma of string mcode
277 | Pdots of string mcode (* ... *)
278 | Pcircles of string mcode (* ooo *)
279 | OptParam of parameterTypeDef
280 | UniqueParam of parameterTypeDef
281
282 and parameterTypeDef = base_parameterTypeDef wrap
283
284 and parameter_list = parameterTypeDef dots
285
286 (* --------------------------------------------------------------------- *)
287 (* #define Parameters *)
288
289 and base_define_param =
290 DParam of ident
291 | DPComma of string mcode
292 | DPdots of string mcode (* ... *)
293 | DPcircles of string mcode (* ooo *)
294 | OptDParam of define_param
295 | UniqueDParam of define_param
296
297 and define_param = base_define_param wrap
298
299 and base_define_parameters =
300 NoParams
301 | DParams of string mcode(*( *) * define_param dots * string mcode(* )*)
302
303 and define_parameters = base_define_parameters wrap
304
305 (* --------------------------------------------------------------------- *)
306 (* Statement*)
307
308 and base_statement =
309 Decl of (info * mcodekind) (* before the decl *) * declaration
310 | Seq of string mcode (* { *) * statement dots *
311 string mcode (* } *)
312 | ExprStatement of expression * string mcode (*;*)
313 | IfThen of string mcode (* if *) * string mcode (* ( *) *
314 expression * string mcode (* ) *) *
315 statement * (info * mcodekind) (* after info *)
316 | IfThenElse of string mcode (* if *) * string mcode (* ( *) *
317 expression * string mcode (* ) *) *
318 statement * string mcode (* else *) * statement *
319 (info * mcodekind)
320 | While of string mcode (* while *) * string mcode (* ( *) *
321 expression * string mcode (* ) *) *
322 statement * (info * mcodekind) (* after info *)
323 | Do of string mcode (* do *) * statement *
324 string mcode (* while *) * string mcode (* ( *) *
325 expression * string mcode (* ) *) *
326 string mcode (* ; *)
327 | For of string mcode (* for *) * string mcode (* ( *) *
328 expression option * string mcode (*;*) *
329 expression option * string mcode (*;*) *
330 expression option * string mcode (* ) *) * statement *
331 (info * mcodekind) (* after info *)
332 | Iterator of ident (* name *) * string mcode (* ( *) *
333 expression dots * string mcode (* ) *) *
334 statement * (info * mcodekind) (* after info *)
335 | Switch of string mcode (* switch *) * string mcode (* ( *) *
336 expression * string mcode (* ) *) * string mcode (* { *) *
337 statement (*decl*) dots *
338 case_line dots * string mcode (* } *)
339 | Break of string mcode (* break *) * string mcode (* ; *)
340 | Continue of string mcode (* continue *) * string mcode (* ; *)
341 | Label of ident * string mcode (* : *)
342 | Goto of string mcode (* goto *) * ident * string mcode (* ; *)
343 | Return of string mcode (* return *) * string mcode (* ; *)
344 | ReturnExpr of string mcode (* return *) * expression *
345 string mcode (* ; *)
346 | MetaStmt of Ast.meta_name mcode * pure
347 | MetaStmtList of Ast.meta_name mcode(*only in statement lists*) * pure
348 | Exp of expression (* only in dotted statement lists *)
349 | TopExp of expression (* for macros body *)
350 | Ty of typeC (* only at top level *)
351 | TopInit of initialiser (* only at top level *)
352 | Disj of string mcode * statement dots list *
353 string mcode list (* the |s *) * string mcode
354 | Nest of string mcode * statement dots * string mcode *
355 (statement dots,statement) whencode list * Ast.multi
356 | Dots of string mcode (* ... *) *
357 (statement dots,statement) whencode list
358 | Circles of string mcode (* ooo *) *
359 (statement dots,statement) whencode list
360 | Stars of string mcode (* *** *) *
361 (statement dots,statement) whencode list
362 | FunDecl of (info * mcodekind) (* before the function decl *) *
363 fninfo list * ident (* name *) *
364 string mcode (* ( *) * parameter_list * string mcode (* ) *) *
365 string mcode (* { *) * statement dots *
366 string mcode (* } *)
367 | Include of string mcode (* #include *) * Ast.inc_file mcode (* file *)
368 | Define of string mcode (* #define *) * ident (* name *) *
369 define_parameters (*params*) * statement dots
370 | OptStm of statement
371 | UniqueStm of statement
372
373 and fninfo =
374 FStorage of Ast.storage mcode
375 | FType of typeC
376 | FInline of string mcode
377 | FAttr of string mcode
378
379 and ('a,'b) whencode =
380 WhenNot of 'a
381 | WhenAlways of 'b
382 | WhenModifier of Ast.when_modifier
383 | WhenNotTrue of expression
384 | WhenNotFalse of expression
385
386 and statement = base_statement wrap
387
388 and base_case_line =
389 Default of string mcode (* default *) * string mcode (*:*) * statement dots
390 | Case of string mcode (* case *) * expression * string mcode (*:*) *
391 statement dots
392 | DisjCase of string mcode * case_line list *
393 string mcode list (* the |s *) * string mcode
394 | OptCase of case_line
395
396 and case_line = base_case_line wrap
397
398 (* --------------------------------------------------------------------- *)
399 (* Positions *)
400
401 and meta_pos =
402 MetaPos of Ast.meta_name mcode * Ast.meta_name list * Ast.meta_collect
403 | NoMetaPos
404
405 (* --------------------------------------------------------------------- *)
406 (* Top-level code *)
407
408 and base_top_level =
409 DECL of statement
410 | CODE of statement dots
411 | FILEINFO of string mcode (* old file *) * string mcode (* new file *)
412 | ERRORWORDS of expression list
413 | OTHER of statement (* temporary, disappears after top_level.ml *)
414
415 and top_level = base_top_level wrap
416 and rule = top_level list
417
418 and parsed_rule =
419 CocciRule of
420 (rule * Ast.metavar list *
421 (string list * string list * Ast.dependency * string * Ast.exists)) *
422 (rule * Ast.metavar list) * Ast.ruletype
423 | ScriptRule of
424 string * Ast.dependency * (string * Ast.meta_name) list * string
425 | InitialScriptRule of string * Ast.dependency * string
426 | FinalScriptRule of string * Ast.dependency * string
427
428 (* --------------------------------------------------------------------- *)
429
430 and anything =
431 DotsExprTag of expression dots
432 | DotsInitTag of initialiser dots
433 | DotsParamTag of parameterTypeDef dots
434 | DotsStmtTag of statement dots
435 | DotsDeclTag of declaration dots
436 | DotsCaseTag of case_line dots
437 | IdentTag of ident
438 | ExprTag of expression
439 | ArgExprTag of expression (* for isos *)
440 | TestExprTag of expression (* for isos *)
441 | TypeCTag of typeC
442 | ParamTag of parameterTypeDef
443 | InitTag of initialiser
444 | DeclTag of declaration
445 | StmtTag of statement
446 | CaseLineTag of case_line
447 | TopTag of top_level
448 | IsoWhenTag of Ast.when_modifier
449 | IsoWhenTTag of expression
450 | IsoWhenFTag of expression
451 | MetaPosTag of meta_pos
452
453 let dotsExpr x = DotsExprTag x
454 let dotsParam x = DotsParamTag x
455 let dotsInit x = DotsInitTag x
456 let dotsStmt x = DotsStmtTag x
457 let dotsDecl x = DotsDeclTag x
458 let dotsCase x = DotsCaseTag x
459 let ident x = IdentTag x
460 let expr x = ExprTag x
461 let typeC x = TypeCTag x
462 let param x = ParamTag x
463 let ini x = InitTag x
464 let decl x = DeclTag x
465 let stmt x = StmtTag x
466 let case_line x = CaseLineTag x
467 let top x = TopTag x
468
469 (* --------------------------------------------------------------------- *)
470 (* Avoid cluttering the parser. Calculated in compute_lines.ml. *)
471
472 let pos_info =
473 { line_start = -1; line_end = -1;
474 logical_start = -1; logical_end = -1;
475 column = -1; offset = -1; }
476
477 let default_info _ = (* why is this a function? *)
478 { pos_info = pos_info;
479 attachable_start = true; attachable_end = true;
480 mcode_start = []; mcode_end = [];
481 strings_before = []; strings_after = [] }
482
483 let default_befaft _ =
484 MIXED(ref (Ast.NOTHING,default_token_info,default_token_info))
485 let context_befaft _ =
486 CONTEXT(ref (Ast.NOTHING,default_token_info,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) -> Type_cocci.ConstVol(const_vol cv,ast0_type_to_type ty)
565 | BaseType(bty,strings) ->
566 Type_cocci.BaseType(baseType bty)
567 | Signed(sgn,None) ->
568 Type_cocci.SignedT(sign sgn,None)
569 | Signed(sgn,Some ty) ->
570 let bty = ast0_type_to_type ty in
571 Type_cocci.SignedT(sign sgn,Some bty)
572 | Pointer(ty,_) -> Type_cocci.Pointer(ast0_type_to_type ty)
573 | FunctionPointer(ty,_,_,_,_,params,_) ->
574 Type_cocci.FunctionPointer(ast0_type_to_type ty)
575 | FunctionType _ -> failwith "not supported"
576 | Array(ety,_,_,_) -> Type_cocci.Array(ast0_type_to_type ety)
577 | EnumName(su,tag) ->
578 (match unwrap tag with
579 Id(tag) ->
580 Type_cocci.EnumName(false,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 let (rule,tag) = unwrap_mcode tag in
587 Type_cocci.EnumName(true,rule^tag))
588 | _ -> failwith "unexpected enum type name")
589 | StructUnionName(su,Some tag) ->
590 (match unwrap tag with
591 Id(tag) ->
592 Type_cocci.StructUnionName(structUnion su,false,unwrap_mcode tag)
593 | MetaId(tag,_,_) ->
594 (Common.pr2
595 "warning: struct/union with a metavariable name detected.\n";
596 Common.pr2
597 "For type checking assuming the name of the metavariable is the name of the type\n";
598 let (rule,tag) = unwrap_mcode tag in
599 Type_cocci.StructUnionName(structUnion su,true,rule^tag))
600 | _ -> failwith "unexpected struct/union type name")
601 | StructUnionName(su,None) -> failwith "nameless structure - what to do???"
602 | StructUnionDef(ty,_,_,_) -> ast0_type_to_type ty
603 | TypeName(name) -> Type_cocci.TypeName(unwrap_mcode name)
604 | MetaType(name,_) ->
605 Type_cocci.MetaType(unwrap_mcode name,Type_cocci.Unitary,false)
606 | DisjType(_,types,_,_) ->
607 Common.pr2_once
608 "disjtype not supported in smpl type inference, assuming unknown";
609 Type_cocci.Unknown
610 | OptType(ty) | UniqueType(ty) ->
611 ast0_type_to_type ty
612
613 and baseType = function
614 Ast.VoidType -> Type_cocci.VoidType
615 | Ast.CharType -> Type_cocci.CharType
616 | Ast.ShortType -> Type_cocci.ShortType
617 | Ast.IntType -> Type_cocci.IntType
618 | Ast.DoubleType -> Type_cocci.DoubleType
619 | Ast.FloatType -> Type_cocci.FloatType
620 | Ast.LongType -> Type_cocci.LongType
621 | Ast.LongLongType -> Type_cocci.LongLongType
622
623 and structUnion t =
624 match unwrap_mcode t with
625 Ast.Struct -> Type_cocci.Struct
626 | Ast.Union -> Type_cocci.Union
627
628 and sign t =
629 match unwrap_mcode t with
630 Ast.Signed -> Type_cocci.Signed
631 | Ast.Unsigned -> Type_cocci.Unsigned
632
633 and const_vol t =
634 match unwrap_mcode t with
635 Ast.Const -> Type_cocci.Const
636 | Ast.Volatile -> Type_cocci.Volatile
637
638 (* --------------------------------------------------------------------- *)
639 (* this function is a rather minimal attempt. the problem is that information
640 has been lost. but since it is only used for metavariable types in the isos,
641 perhaps it doesn't matter *)
642 and make_mcode x = (x,NONE,default_info(),context_befaft(),ref NoMetaPos,-1)
643 let make_mcode_info x info = (x,NONE,info,context_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 context_wrap(MetaId(make_mcode (rule,tag),Ast.IdNoConstraint,
666 Impure)))
667 else
668 EnumName(make_mcode "enum",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 *)