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