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