Release coccinelle-0.1.6
[bpt/coccinelle.git] / parsing_cocci / .#ast0_cocci.ml.1.113
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 InitExpr of expression
207 | InitList of string mcode (*{*) * initialiser_list * string mcode (*}*)
208 | InitGccDotName of
209 string mcode (*.*) * ident (* name *) * string mcode (*=*) *
210 initialiser (* gccext: *)
211 | InitGccName of ident (* name *) * string mcode (*:*) *
212 initialiser
213 | InitGccIndex of
214 string mcode (*[*) * expression * string mcode (*]*) *
215 string mcode (*=*) * initialiser
216 | InitGccRange of
217 string mcode (*[*) * expression * string mcode (*...*) *
218 expression * string mcode (*]*) * string mcode (*=*) * initialiser
219 | IComma of string mcode (* , *)
220 | Idots of string mcode (* ... *) * initialiser option (* whencode *)
221 | OptIni of initialiser
222 | UniqueIni of initialiser
223
224 and initialiser = base_initialiser wrap
225
226 and initialiser_list = initialiser dots
227
228 (* --------------------------------------------------------------------- *)
229 (* Parameter *)
230
231 and base_parameterTypeDef =
232 VoidParam of typeC
233 | Param of typeC * ident option
234 | MetaParam of Ast.meta_name mcode * pure
235 | MetaParamList of Ast.meta_name mcode * listlen * pure
236 | PComma of string mcode
237 | Pdots of string mcode (* ... *)
238 | Pcircles of string mcode (* ooo *)
239 | OptParam of parameterTypeDef
240 | UniqueParam of parameterTypeDef
241
242 and parameterTypeDef = base_parameterTypeDef wrap
243
244 and parameter_list = parameterTypeDef dots
245
246 (* --------------------------------------------------------------------- *)
247 (* #define Parameters *)
248
249 and base_define_param =
250 DParam of ident
251 | DPComma of string mcode
252 | DPdots of string mcode (* ... *)
253 | DPcircles of string mcode (* ooo *)
254 | OptDParam of define_param
255 | UniqueDParam of define_param
256
257 and define_param = base_define_param wrap
258
259 and base_define_parameters =
260 NoParams
261 | DParams of string mcode(*( *) * define_param dots * string mcode(* )*)
262
263 and define_parameters = base_define_parameters wrap
264
265 (* --------------------------------------------------------------------- *)
266 (* Statement*)
267
268 and base_statement =
269 Decl of (info * mcodekind) (* before the decl *) * declaration
270 | Seq of string mcode (* { *) * statement dots *
271 string mcode (* } *)
272 | ExprStatement of expression * string mcode (*;*)
273 | IfThen of string mcode (* if *) * string mcode (* ( *) *
274 expression * string mcode (* ) *) *
275 statement * (info * mcodekind) (* after info *)
276 | IfThenElse of string mcode (* if *) * string mcode (* ( *) *
277 expression * string mcode (* ) *) *
278 statement * string mcode (* else *) * statement *
279 (info * mcodekind)
280 | While of string mcode (* while *) * string mcode (* ( *) *
281 expression * string mcode (* ) *) *
282 statement * (info * mcodekind) (* after info *)
283 | Do of string mcode (* do *) * statement *
284 string mcode (* while *) * string mcode (* ( *) *
285 expression * string mcode (* ) *) *
286 string mcode (* ; *)
287 | For of string mcode (* for *) * string mcode (* ( *) *
288 expression option * string mcode (*;*) *
289 expression option * string mcode (*;*) *
290 expression option * string mcode (* ) *) * statement *
291 (info * mcodekind) (* after info *)
292 | Iterator of ident (* name *) * string mcode (* ( *) *
293 expression dots * string mcode (* ) *) *
294 statement * (info * mcodekind) (* after info *)
295 | Switch of string mcode (* switch *) * string mcode (* ( *) *
296 expression * string mcode (* ) *) * string mcode (* { *) *
297 case_line dots * string mcode (* } *)
298 | Break of string mcode (* break *) * string mcode (* ; *)
299 | Continue of string mcode (* continue *) * string mcode (* ; *)
300 | Label of ident * string mcode (* : *)
301 | Goto of string mcode (* goto *) * ident * string mcode (* ; *)
302 | Return of string mcode (* return *) * string mcode (* ; *)
303 | ReturnExpr of string mcode (* return *) * expression *
304 string mcode (* ; *)
305 | MetaStmt of Ast.meta_name mcode * pure
306 | MetaStmtList of Ast.meta_name mcode(*only in statement lists*) * pure
307 | Exp of expression (* only in dotted statement lists *)
308 | TopExp of expression (* for macros body *)
309 | Ty of typeC (* only at top level *)
310 | TopInit of initialiser (* only at top level *)
311 | Disj of string mcode * statement dots list *
312 string mcode list (* the |s *) * string mcode
313 | Nest of string mcode * statement dots * string mcode *
314 (statement dots,statement) whencode list * Ast.multi
315 | Dots of string mcode (* ... *) *
316 (statement dots,statement) whencode list
317 | Circles of string mcode (* ooo *) *
318 (statement dots,statement) whencode list
319 | Stars of string mcode (* *** *) *
320 (statement dots,statement) whencode list
321 | FunDecl of (info * mcodekind) (* before the function decl *) *
322 fninfo list * ident (* name *) *
323 string mcode (* ( *) * parameter_list * string mcode (* ) *) *
324 string mcode (* { *) * statement dots *
325 string mcode (* } *)
326 | Include of string mcode (* #include *) * Ast.inc_file mcode (* file *)
327 | Define of string mcode (* #define *) * ident (* name *) *
328 define_parameters (*params*) * statement dots
329 | OptStm of statement
330 | UniqueStm of statement
331
332 and fninfo =
333 FStorage of Ast.storage mcode
334 | FType of typeC
335 | FInline of string mcode
336 | FAttr of string mcode
337
338 and ('a,'b) whencode =
339 WhenNot of 'a
340 | WhenAlways of 'b
341 | WhenModifier of Ast.when_modifier
342 | WhenNotTrue of expression
343 | WhenNotFalse of expression
344
345 and statement = base_statement wrap
346
347 and base_case_line =
348 Default of string mcode (* default *) * string mcode (*:*) * statement dots
349 | Case of string mcode (* case *) * expression * string mcode (*:*) *
350 statement dots
351 | OptCase of case_line
352
353 and case_line = base_case_line wrap
354
355 (* --------------------------------------------------------------------- *)
356 (* Positions *)
357
358 and meta_pos =
359 MetaPos of Ast.meta_name mcode * Ast.meta_name list * Ast.meta_collect
360 | NoMetaPos
361
362 (* --------------------------------------------------------------------- *)
363 (* Top-level code *)
364
365 and base_top_level =
366 DECL of statement
367 | CODE of statement dots
368 | FILEINFO of string mcode (* old file *) * string mcode (* new file *)
369 | ERRORWORDS of expression list
370 | OTHER of statement (* temporary, disappears after top_level.ml *)
371
372 and top_level = base_top_level wrap
373 and rule = top_level list
374
375 and parsed_rule =
376 CocciRule of
377 (rule * Ast.metavar list *
378 (string list * string list * Ast.dependency * string * Ast.exists)) *
379 (rule * Ast.metavar list) * Ast.ruletype
380 | ScriptRule of
381 string * Ast.dependency * (string * Ast.meta_name) list * string
382
383 (* --------------------------------------------------------------------- *)
384
385 and anything =
386 DotsExprTag of expression dots
387 | DotsInitTag of initialiser dots
388 | DotsParamTag of parameterTypeDef dots
389 | DotsStmtTag of statement dots
390 | DotsDeclTag of declaration dots
391 | DotsCaseTag of case_line dots
392 | IdentTag of ident
393 | ExprTag of expression
394 | ArgExprTag of expression (* for isos *)
395 | TestExprTag of expression (* for isos *)
396 | TypeCTag of typeC
397 | ParamTag of parameterTypeDef
398 | InitTag of initialiser
399 | DeclTag of declaration
400 | StmtTag of statement
401 | CaseLineTag of case_line
402 | TopTag of top_level
403 | IsoWhenTag of Ast.when_modifier
404 | IsoWhenTTag of expression
405 | IsoWhenFTag of expression
406 | MetaPosTag of meta_pos
407
408 let dotsExpr x = DotsExprTag x
409 let dotsParam x = DotsParamTag x
410 let dotsInit x = DotsInitTag x
411 let dotsStmt x = DotsStmtTag x
412 let dotsDecl x = DotsDeclTag x
413 let dotsCase x = DotsCaseTag x
414 let ident x = IdentTag x
415 let expr x = ExprTag x
416 let typeC x = TypeCTag x
417 let param x = ParamTag x
418 let ini x = InitTag x
419 let decl x = DeclTag x
420 let stmt x = StmtTag x
421 let case_line x = CaseLineTag x
422 let top x = TopTag x
423
424 (* --------------------------------------------------------------------- *)
425 (* Avoid cluttering the parser. Calculated in compute_lines.ml. *)
426
427 let default_info _ = (* why is this a function? *)
428 { line_start = -1; line_end = -1;
429 logical_start = -1; logical_end = -1;
430 attachable_start = true; attachable_end = true;
431 mcode_start = []; mcode_end = [];
432 column = -1; offset = -1; strings_before = []; strings_after = [] }
433
434 let default_befaft _ =
435 MIXED(ref (Ast.NOTHING,default_token_info,default_token_info))
436 let context_befaft _ =
437 CONTEXT(ref (Ast.NOTHING,default_token_info,default_token_info))
438
439 let wrap x =
440 { node = x;
441 info = default_info();
442 index = ref (-1);
443 mcodekind = ref (default_befaft());
444 exp_ty = ref None;
445 bef_aft = NoDots;
446 true_if_arg = false;
447 true_if_test = false;
448 true_if_test_exp = false;
449 iso_info = [] }
450 let context_wrap x =
451 { node = x;
452 info = default_info();
453 index = ref (-1);
454 mcodekind = ref (context_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 unwrap x = x.node
462 let unwrap_mcode (x,_,_,_,_) = x
463 let rewrap model x = { model with node = x }
464 let rewrap_mcode (_,arity,info,mcodekind,pos) x = (x,arity,info,mcodekind,pos)
465 let copywrap model x =
466 { model with node = x; index = ref !(model.index);
467 mcodekind = ref !(model.mcodekind); exp_ty = ref !(model.exp_ty)}
468 let get_pos (_,_,_,_,x) = !x
469 let get_pos_ref (_,_,_,_,x) = x
470 let set_pos pos (m,arity,info,mcodekind,_) = (m,arity,info,mcodekind,ref pos)
471 let get_info x = x.info
472 let set_info x info = {x with info = info}
473 let get_line x = x.info.line_start
474 let get_line_end x = x.info.line_end
475 let get_index x = !(x.index)
476 let set_index x i = x.index := i
477 let get_mcodekind x = !(x.mcodekind)
478 let get_mcode_mcodekind (_,_,_,mcodekind,_) = mcodekind
479 let get_mcodekind_ref x = x.mcodekind
480 let set_mcodekind x mk = x.mcodekind := mk
481 let set_type x t = x.exp_ty := t
482 let get_type x = !(x.exp_ty)
483 let get_dots_bef_aft x = x.bef_aft
484 let set_dots_bef_aft x dots_bef_aft = {x with bef_aft = dots_bef_aft}
485 let get_arg_exp x = x.true_if_arg
486 let set_arg_exp x = {x with true_if_arg = true}
487 let get_test_pos x = x.true_if_test
488 let set_test_pos x = {x with true_if_test = true}
489 let get_test_exp x = x.true_if_test_exp
490 let set_test_exp x = {x with true_if_test_exp = true}
491 let get_iso x = x.iso_info
492 let set_iso x i = if !Flag.track_iso_usage then {x with iso_info = i} else x
493 let set_mcode_data data (_,ar,info,mc,pos) = (data,ar,info,mc,pos)
494
495 (* --------------------------------------------------------------------- *)
496
497 (* unique indices, for mcode and tree nodes *)
498 let index_counter = ref 0
499 let fresh_index _ = let cur = !index_counter in index_counter := cur + 1; cur
500
501 (* --------------------------------------------------------------------- *)
502
503 let undots d =
504 match unwrap d with
505 | DOTS e -> e
506 | CIRCLES e -> e
507 | STARS e -> e
508
509 (* --------------------------------------------------------------------- *)
510
511 let rec ast0_type_to_type ty =
512 match unwrap ty with
513 ConstVol(cv,ty) -> Type_cocci.ConstVol(const_vol cv,ast0_type_to_type ty)
514 | BaseType(bty,strings) ->
515 Type_cocci.BaseType(baseType bty)
516 | Signed(sgn,None) ->
517 Type_cocci.SignedT(sign sgn,None)
518 | Signed(sgn,Some ty) ->
519 let bty = ast0_type_to_type ty in
520 Type_cocci.SignedT(sign sgn,Some bty)
521 | Pointer(ty,_) -> Type_cocci.Pointer(ast0_type_to_type ty)
522 | FunctionPointer(ty,_,_,_,_,params,_) ->
523 Type_cocci.FunctionPointer(ast0_type_to_type ty)
524 | FunctionType _ -> failwith "not supported"
525 | Array(ety,_,_,_) -> Type_cocci.Array(ast0_type_to_type ety)
526 | EnumName(su,tag) ->
527 (match unwrap tag with
528 Id(tag) ->
529 Type_cocci.EnumName(false,unwrap_mcode tag)
530 | MetaId(tag,_,_) ->
531 (Printf.printf
532 "warning: enum with a metavariable name detected.\n";
533 Printf.printf
534 "For type checking assuming the name of the metavariable is the name of the type\n";
535 let (rule,tag) = unwrap_mcode tag in
536 Type_cocci.EnumName(true,rule^tag))
537 | _ -> failwith "unexpected enum type name")
538 | StructUnionName(su,Some tag) ->
539 (match unwrap tag with
540 Id(tag) ->
541 Type_cocci.StructUnionName(structUnion su,false,unwrap_mcode tag)
542 | MetaId(tag,_,_) ->
543 (Printf.printf
544 "warning: struct/union with a metavariable name detected.\n";
545 Printf.printf
546 "For type checking assuming the name of the metavariable is the name of the type\n";
547 let (rule,tag) = unwrap_mcode tag in
548 Type_cocci.StructUnionName(structUnion su,true,rule^tag))
549 | _ -> failwith "unexpected struct/union type name")
550 | StructUnionName(su,None) -> failwith "nameless structure - what to do???"
551 | StructUnionDef(ty,_,_,_) -> ast0_type_to_type ty
552 | TypeName(name) -> Type_cocci.TypeName(unwrap_mcode name)
553 | MetaType(name,_) ->
554 Type_cocci.MetaType(unwrap_mcode name,Type_cocci.Unitary,false)
555 | DisjType(_,types,_,_) -> failwith "unexpected DisjType"
556 | OptType(ty) | UniqueType(ty) ->
557 ast0_type_to_type ty
558
559 and baseType = function
560 Ast.VoidType -> Type_cocci.VoidType
561 | Ast.CharType -> Type_cocci.CharType
562 | Ast.ShortType -> Type_cocci.ShortType
563 | Ast.IntType -> Type_cocci.IntType
564 | Ast.DoubleType -> Type_cocci.DoubleType
565 | Ast.FloatType -> Type_cocci.FloatType
566 | Ast.LongType -> Type_cocci.LongType
567 | Ast.LongLongType -> Type_cocci.LongLongType
568
569 and structUnion t =
570 match unwrap_mcode t with
571 Ast.Struct -> Type_cocci.Struct
572 | Ast.Union -> Type_cocci.Union
573
574 and sign t =
575 match unwrap_mcode t with
576 Ast.Signed -> Type_cocci.Signed
577 | Ast.Unsigned -> Type_cocci.Unsigned
578
579 and const_vol t =
580 match unwrap_mcode t with
581 Ast.Const -> Type_cocci.Const
582 | Ast.Volatile -> Type_cocci.Volatile
583
584 (* --------------------------------------------------------------------- *)
585 (* this function is a rather minimal attempt. the problem is that information
586 has been lost. but since it is only used for metavariable types in the isos,
587 perhaps it doesn't matter *)
588 and make_mcode x = (x,NONE,default_info(),context_befaft(),ref NoMetaPos)
589 let make_mcode_info x info = (x,NONE,info,context_befaft(),ref NoMetaPos)
590
591 exception TyConv
592
593 let rec reverse_type ty =
594 match ty with
595 Type_cocci.ConstVol(cv,ty) ->
596 ConstVol(reverse_const_vol cv,context_wrap(reverse_type ty))
597 | Type_cocci.BaseType(bty) ->
598 BaseType(reverse_baseType bty,[(* not used *)])
599 | Type_cocci.SignedT(sgn,None) -> Signed(reverse_sign sgn,None)
600 | Type_cocci.SignedT(sgn,Some bty) ->
601 Signed(reverse_sign sgn,Some (context_wrap(reverse_type ty)))
602 | Type_cocci.Pointer(ty) ->
603 Pointer(context_wrap(reverse_type ty),make_mcode "*")
604 | Type_cocci.EnumName(mv,tag) ->
605 if mv
606 then
607 (* not right... *)
608 EnumName
609 (make_mcode "enum",
610 context_wrap(MetaId(make_mcode ("",tag),[],Impure)))
611 else
612 EnumName(make_mcode "enum",context_wrap(Id(make_mcode tag)))
613 | Type_cocci.StructUnionName(su,mv,tag) ->
614 if mv
615 then
616 (* not right... *)
617 StructUnionName
618 (reverse_structUnion su,
619 Some(context_wrap(MetaId(make_mcode ("",tag),[],Impure))))
620 else
621 StructUnionName
622 (reverse_structUnion su,
623 Some (context_wrap(Id(make_mcode tag))))
624 | Type_cocci.TypeName(name) -> TypeName(make_mcode name)
625 | Type_cocci.MetaType(name,_,_) ->
626 MetaType(make_mcode name,Impure(*not really right*))
627 | _ -> raise TyConv
628
629 and reverse_baseType = function
630 Type_cocci.VoidType -> Ast.VoidType
631 | Type_cocci.CharType -> Ast.CharType
632 | Type_cocci.BoolType -> Ast.IntType
633 | Type_cocci.ShortType -> Ast.ShortType
634 | Type_cocci.IntType -> Ast.IntType
635 | Type_cocci.DoubleType -> Ast.DoubleType
636 | Type_cocci.FloatType -> Ast.FloatType
637 | Type_cocci.LongType -> Ast.LongType
638 | Type_cocci.LongLongType -> Ast.LongLongType
639
640 and reverse_structUnion t =
641 make_mcode
642 (match t with
643 Type_cocci.Struct -> Ast.Struct
644 | Type_cocci.Union -> Ast.Union)
645
646 and reverse_sign t =
647 make_mcode
648 (match t with
649 Type_cocci.Signed -> Ast.Signed
650 | Type_cocci.Unsigned -> Ast.Unsigned)
651
652 and reverse_const_vol t =
653 make_mcode
654 (match t with
655 Type_cocci.Const -> Ast.Const
656 | Type_cocci.Volatile -> Ast.Volatile)
657
658 (* --------------------------------------------------------------------- *)
659
660 let lub_pure x y =
661 match (x,y) with
662 (Impure,_) | (_,Impure) -> Impure
663 | (Pure,Context) | (Context,Pure) -> Impure
664 | (Pure,_) | (_,Pure) -> Pure
665 | (_,Context) | (Context,_) -> Context
666 | _ -> PureContext
667
668 (* --------------------------------------------------------------------- *)
669
670 let rule_name = ref "" (* for the convenience of the parser *)