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