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