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