Release coccinelle-0.1.8
[bpt/coccinelle.git] / parsing_cocci / ast0_cocci.ml
CommitLineData
34e49164 1(*
faf9a90c 2* Copyright 2005-2009, Ecole des Mines de Nantes, University of Copenhagen
34e49164
C
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
23module Ast = Ast_cocci
24
25(* --------------------------------------------------------------------- *)
26(* Modified code *)
27
28type arity = OPT | UNIQUE | NONE
29
30type token_info =
31 { tline_start : int; tline_end : int;
32 left_offset : int; right_offset : int }
33let 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
37CONTEXT - see insert_plus.ml *)
38type 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
0708f913
C
44type position_info = { line_start : int; line_end : int;
45 logical_start : int; logical_end : int;
46 column : int; offset : int; }
47
48type info = { pos_info : position_info;
34e49164
C
49 attachable_start : bool; attachable_end : bool;
50 mcode_start : mcodekind list; mcode_end : mcodekind list;
34e49164 51 (* the following are only for + code *)
0708f913
C
52 strings_before : (string * position_info) list;
53 strings_after : (string * position_info) list }
34e49164 54
708f4980
C
55(* adjacency index is incremented when we skip over dots or nest delimiters
56it is used in deciding how much to remove, when two adjacent code tokens are
57removed. *)
58type 'a mcode =
59 'a * arity * info * mcodekind * meta_pos ref (* pos, - only *) *
60 int (* adjacency_index *)
34e49164
C
61(* int ref is an index *)
62and '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
75and 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*)
84and pure = Impure | Pure | Context | PureContext (* pure and only context *)
85
86(* --------------------------------------------------------------------- *)
87(* --------------------------------------------------------------------- *)
88(* Dots *)
89
90and 'a base_dots =
91 DOTS of 'a list
92 | CIRCLES of 'a list
93 | STARS of 'a list
94
95and 'a dots = 'a base_dots wrap
96
97(* --------------------------------------------------------------------- *)
98(* Identifier *)
99
100and 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
108and ident = base_ident wrap
109
110(* --------------------------------------------------------------------- *)
111(* Expression *)
112
faf9a90c 113and base_expression =
34e49164
C
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
155and expression = base_expression wrap
156
157and listlen = Ast.meta_name mcode option
158
159(* --------------------------------------------------------------------- *)
160(* Types *)
161
faf9a90c 162and base_typeC =
34e49164 163 ConstVol of Ast.const_vol mcode * typeC
faf9a90c
C
164 | BaseType of Ast.baseType * string mcode list
165 | Signed of Ast.sign mcode * typeC option
34e49164
C
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 (* ] *)
faf9a90c 175 | EnumName of string mcode (*enum*) * ident (* name *)
34e49164
C
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
186and 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
193and 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
208and declaration = base_declaration wrap
209
210(* --------------------------------------------------------------------- *)
211(* Initializers *)
212
213and base_initialiser =
113803cf
C
214 MetaInit of Ast.meta_name mcode * pure
215 | InitExpr of expression
34e49164 216 | InitList of string mcode (*{*) * initialiser_list * string mcode (*}*)
113803cf
C
217 | InitGccExt of
218 designator list (* name *) * string mcode (*=*) *
34e49164
C
219 initialiser (* gccext: *)
220 | InitGccName of ident (* name *) * string mcode (*:*) *
221 initialiser
34e49164
C
222 | IComma of string mcode (* , *)
223 | Idots of string mcode (* ... *) * initialiser option (* whencode *)
224 | OptIni of initialiser
225 | UniqueIni of initialiser
226
113803cf
C
227and 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
34e49164
C
234and initialiser = base_initialiser wrap
235
236and initialiser_list = initialiser dots
237
238(* --------------------------------------------------------------------- *)
239(* Parameter *)
240
241and 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
252and parameterTypeDef = base_parameterTypeDef wrap
253
254and parameter_list = parameterTypeDef dots
255
256(* --------------------------------------------------------------------- *)
257(* #define Parameters *)
258
259and 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
267and define_param = base_define_param wrap
268
269and base_define_parameters =
270 NoParams
271 | DParams of string mcode(*( *) * define_param dots * string mcode(* )*)
272
273and define_parameters = base_define_parameters wrap
274
275(* --------------------------------------------------------------------- *)
276(* Statement*)
277
278and 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 case_line dots * string mcode (* } *)
308 | Break of string mcode (* break *) * string mcode (* ; *)
309 | Continue of string mcode (* continue *) * string mcode (* ; *)
310 | Label of ident * string mcode (* : *)
311 | Goto of string mcode (* goto *) * ident * string mcode (* ; *)
312 | Return of string mcode (* return *) * string mcode (* ; *)
313 | ReturnExpr of string mcode (* return *) * expression *
314 string mcode (* ; *)
315 | MetaStmt of Ast.meta_name mcode * pure
316 | MetaStmtList of Ast.meta_name mcode(*only in statement lists*) * pure
317 | Exp of expression (* only in dotted statement lists *)
318 | TopExp of expression (* for macros body *)
319 | Ty of typeC (* only at top level *)
1be43e12 320 | TopInit of initialiser (* only at top level *)
34e49164
C
321 | Disj of string mcode * statement dots list *
322 string mcode list (* the |s *) * string mcode
323 | Nest of string mcode * statement dots * string mcode *
324 (statement dots,statement) whencode list * Ast.multi
325 | Dots of string mcode (* ... *) *
326 (statement dots,statement) whencode list
327 | Circles of string mcode (* ooo *) *
328 (statement dots,statement) whencode list
329 | Stars of string mcode (* *** *) *
330 (statement dots,statement) whencode list
331 | FunDecl of (info * mcodekind) (* before the function decl *) *
332 fninfo list * ident (* name *) *
333 string mcode (* ( *) * parameter_list * string mcode (* ) *) *
334 string mcode (* { *) * statement dots *
335 string mcode (* } *)
336 | Include of string mcode (* #include *) * Ast.inc_file mcode (* file *)
337 | Define of string mcode (* #define *) * ident (* name *) *
338 define_parameters (*params*) * statement dots
339 | OptStm of statement
340 | UniqueStm of statement
341
342and fninfo =
343 FStorage of Ast.storage mcode
344 | FType of typeC
345 | FInline of string mcode
346 | FAttr of string mcode
347
348and ('a,'b) whencode =
349 WhenNot of 'a
350 | WhenAlways of 'b
351 | WhenModifier of Ast.when_modifier
1be43e12
C
352 | WhenNotTrue of expression
353 | WhenNotFalse of expression
34e49164
C
354
355and statement = base_statement wrap
356
357and base_case_line =
358 Default of string mcode (* default *) * string mcode (*:*) * statement dots
359 | Case of string mcode (* case *) * expression * string mcode (*:*) *
360 statement dots
361 | OptCase of case_line
362
363and case_line = base_case_line wrap
364
365(* --------------------------------------------------------------------- *)
366(* Positions *)
367
368and meta_pos =
369 MetaPos of Ast.meta_name mcode * Ast.meta_name list * Ast.meta_collect
370 | NoMetaPos
371
372(* --------------------------------------------------------------------- *)
373(* Top-level code *)
374
375and base_top_level =
376 DECL of statement
377 | CODE of statement dots
378 | FILEINFO of string mcode (* old file *) * string mcode (* new file *)
379 | ERRORWORDS of expression list
380 | OTHER of statement (* temporary, disappears after top_level.ml *)
381
382and top_level = base_top_level wrap
383and rule = top_level list
384
385and parsed_rule =
386 CocciRule of
387 (rule * Ast.metavar list *
388 (string list * string list * Ast.dependency * string * Ast.exists)) *
faf9a90c 389 (rule * Ast.metavar list) * Ast.ruletype
34e49164
C
390 | ScriptRule of
391 string * Ast.dependency * (string * Ast.meta_name) list * string
b1b2de81
C
392 | InitialScriptRule of string * string
393 | FinalScriptRule of string * string
34e49164
C
394
395(* --------------------------------------------------------------------- *)
396
397and 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
1be43e12
C
416 | IsoWhenTTag of expression
417 | IsoWhenFTag of expression
34e49164
C
418 | MetaPosTag of meta_pos
419
420let dotsExpr x = DotsExprTag x
421let dotsParam x = DotsParamTag x
422let dotsInit x = DotsInitTag x
423let dotsStmt x = DotsStmtTag x
424let dotsDecl x = DotsDeclTag x
425let dotsCase x = DotsCaseTag x
426let ident x = IdentTag x
427let expr x = ExprTag x
428let typeC x = TypeCTag x
429let param x = ParamTag x
430let ini x = InitTag x
431let decl x = DeclTag x
432let stmt x = StmtTag x
433let case_line x = CaseLineTag x
434let top x = TopTag x
435
436(* --------------------------------------------------------------------- *)
437(* Avoid cluttering the parser. Calculated in compute_lines.ml. *)
438
0708f913 439let pos_info =
34e49164
C
440 { line_start = -1; line_end = -1;
441 logical_start = -1; logical_end = -1;
0708f913
C
442 column = -1; offset = -1; }
443
444let default_info _ = (* why is this a function? *)
445 { pos_info = pos_info;
34e49164
C
446 attachable_start = true; attachable_end = true;
447 mcode_start = []; mcode_end = [];
0708f913 448 strings_before = []; strings_after = [] }
34e49164
C
449
450let default_befaft _ =
451 MIXED(ref (Ast.NOTHING,default_token_info,default_token_info))
452let context_befaft _ =
453 CONTEXT(ref (Ast.NOTHING,default_token_info,default_token_info))
454
455let 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 = [] }
466let 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 = [] }
477let unwrap x = x.node
708f4980 478let unwrap_mcode (x,_,_,_,_,_) = x
34e49164 479let rewrap model x = { model with node = x }
708f4980
C
480let rewrap_mcode (_,arity,info,mcodekind,pos,adj) x =
481 (x,arity,info,mcodekind,pos,adj)
34e49164
C
482let copywrap model x =
483 { model with node = x; index = ref !(model.index);
484 mcodekind = ref !(model.mcodekind); exp_ty = ref !(model.exp_ty)}
708f4980
C
485let get_pos (_,_,_,_,x,_) = !x
486let get_pos_ref (_,_,_,_,x,_) = x
487let set_pos pos (m,arity,info,mcodekind,_,adj) =
488 (m,arity,info,mcodekind,ref pos,adj)
34e49164
C
489let get_info x = x.info
490let set_info x info = {x with info = info}
0708f913
C
491let get_line x = x.info.pos_info.line_start
492let get_line_end x = x.info.pos_info.line_end
34e49164
C
493let get_index x = !(x.index)
494let set_index x i = x.index := i
495let get_mcodekind x = !(x.mcodekind)
708f4980 496let get_mcode_mcodekind (_,_,_,mcodekind,_,_) = mcodekind
34e49164
C
497let get_mcodekind_ref x = x.mcodekind
498let set_mcodekind x mk = x.mcodekind := mk
499let set_type x t = x.exp_ty := t
500let get_type x = !(x.exp_ty)
501let get_dots_bef_aft x = x.bef_aft
502let set_dots_bef_aft x dots_bef_aft = {x with bef_aft = dots_bef_aft}
503let get_arg_exp x = x.true_if_arg
504let set_arg_exp x = {x with true_if_arg = true}
505let get_test_pos x = x.true_if_test
506let set_test_pos x = {x with true_if_test = true}
507let get_test_exp x = x.true_if_test_exp
508let set_test_exp x = {x with true_if_test_exp = true}
509let get_iso x = x.iso_info
510let set_iso x i = if !Flag.track_iso_usage then {x with iso_info = i} else x
708f4980 511let set_mcode_data data (_,ar,info,mc,pos,adj) = (data,ar,info,mc,pos,adj)
34e49164
C
512
513(* --------------------------------------------------------------------- *)
514
515(* unique indices, for mcode and tree nodes *)
516let index_counter = ref 0
517let fresh_index _ = let cur = !index_counter in index_counter := cur + 1; cur
518
519(* --------------------------------------------------------------------- *)
520
521let undots d =
522 match unwrap d with
523 | DOTS e -> e
524 | CIRCLES e -> e
525 | STARS e -> e
526
527(* --------------------------------------------------------------------- *)
528
529let 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)
faf9a90c
C
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)
34e49164
C
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)
faf9a90c
C
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")
34e49164
C
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 (Printf.printf
562 "warning: struct/union with a metavariable name detected.\n";
563 Printf.printf
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,_,_) -> failwith "unexpected DisjType"
574 | OptType(ty) | UniqueType(ty) ->
575 ast0_type_to_type ty
576
faf9a90c 577and baseType = function
34e49164
C
578 Ast.VoidType -> Type_cocci.VoidType
579 | Ast.CharType -> Type_cocci.CharType
580 | Ast.ShortType -> Type_cocci.ShortType
581 | Ast.IntType -> Type_cocci.IntType
582 | Ast.DoubleType -> Type_cocci.DoubleType
583 | Ast.FloatType -> Type_cocci.FloatType
584 | Ast.LongType -> Type_cocci.LongType
faf9a90c 585 | Ast.LongLongType -> Type_cocci.LongLongType
34e49164
C
586
587and structUnion t =
588 match unwrap_mcode t with
589 Ast.Struct -> Type_cocci.Struct
590 | Ast.Union -> Type_cocci.Union
591
592and sign t =
593 match unwrap_mcode t with
594 Ast.Signed -> Type_cocci.Signed
595 | Ast.Unsigned -> Type_cocci.Unsigned
596
597and const_vol t =
598 match unwrap_mcode t with
599 Ast.Const -> Type_cocci.Const
600 | Ast.Volatile -> Type_cocci.Volatile
601
602(* --------------------------------------------------------------------- *)
603(* this function is a rather minimal attempt. the problem is that information
604has been lost. but since it is only used for metavariable types in the isos,
605perhaps it doesn't matter *)
708f4980
C
606and make_mcode x = (x,NONE,default_info(),context_befaft(),ref NoMetaPos,-1)
607let make_mcode_info x info = (x,NONE,info,context_befaft(),ref NoMetaPos,-1)
34e49164
C
608
609exception TyConv
610
611let rec reverse_type ty =
612 match ty with
613 Type_cocci.ConstVol(cv,ty) ->
485bce71 614 ConstVol(reverse_const_vol cv,context_wrap(reverse_type ty))
faf9a90c
C
615 | Type_cocci.BaseType(bty) ->
616 BaseType(reverse_baseType bty,[(* not used *)])
617 | Type_cocci.SignedT(sgn,None) -> Signed(reverse_sign sgn,None)
618 | Type_cocci.SignedT(sgn,Some bty) ->
619 Signed(reverse_sign sgn,Some (context_wrap(reverse_type ty)))
34e49164 620 | Type_cocci.Pointer(ty) ->
485bce71 621 Pointer(context_wrap(reverse_type ty),make_mcode "*")
faf9a90c
C
622 | Type_cocci.EnumName(mv,tag) ->
623 if mv
624 then
625 (* not right... *)
626 EnumName
627 (make_mcode "enum",
628 context_wrap(MetaId(make_mcode ("",tag),[],Impure)))
629 else
630 EnumName(make_mcode "enum",context_wrap(Id(make_mcode tag)))
34e49164
C
631 | Type_cocci.StructUnionName(su,mv,tag) ->
632 if mv
633 then
634 (* not right... *)
485bce71
C
635 StructUnionName
636 (reverse_structUnion su,
637 Some(context_wrap(MetaId(make_mcode ("",tag),[],Impure))))
34e49164 638 else
485bce71
C
639 StructUnionName
640 (reverse_structUnion su,
641 Some (context_wrap(Id(make_mcode tag))))
34e49164
C
642 | Type_cocci.TypeName(name) -> TypeName(make_mcode name)
643 | Type_cocci.MetaType(name,_,_) ->
644 MetaType(make_mcode name,Impure(*not really right*))
645 | _ -> raise TyConv
646
faf9a90c
C
647and reverse_baseType = function
648 Type_cocci.VoidType -> Ast.VoidType
649 | Type_cocci.CharType -> Ast.CharType
650 | Type_cocci.BoolType -> Ast.IntType
651 | Type_cocci.ShortType -> Ast.ShortType
652 | Type_cocci.IntType -> Ast.IntType
653 | Type_cocci.DoubleType -> Ast.DoubleType
654 | Type_cocci.FloatType -> Ast.FloatType
655 | Type_cocci.LongType -> Ast.LongType
656 | Type_cocci.LongLongType -> Ast.LongLongType
34e49164
C
657
658and reverse_structUnion t =
659 make_mcode
660 (match t with
661 Type_cocci.Struct -> Ast.Struct
662 | Type_cocci.Union -> Ast.Union)
663
664and reverse_sign t =
665 make_mcode
666 (match t with
667 Type_cocci.Signed -> Ast.Signed
668 | Type_cocci.Unsigned -> Ast.Unsigned)
669
670and reverse_const_vol t =
671 make_mcode
672 (match t with
673 Type_cocci.Const -> Ast.Const
674 | Type_cocci.Volatile -> Ast.Volatile)
675
676(* --------------------------------------------------------------------- *)
677
678let lub_pure x y =
679 match (x,y) with
680 (Impure,_) | (_,Impure) -> Impure
681 | (Pure,Context) | (Context,Pure) -> Impure
682 | (Pure,_) | (_,Pure) -> Pure
683 | (_,Context) | (Context,_) -> Context
684 | _ -> PureContext
685
686(* --------------------------------------------------------------------- *)
687
688let rule_name = ref "" (* for the convenience of the parser *)