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