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