Release coccinelle-0.2.1-rc1
[bpt/coccinelle.git] / parsing_c / ast_c.ml
CommitLineData
0708f913 1(* Yoann Padioleau
ae4735db
C
2 *
3 * Copyright (C) 2010, University of Copenhagen DIKU and INRIA.
0708f913 4 * Copyright (C) 2002, 2006, 2007, 2008, 2009 Yoann Padioleau
34e49164
C
5 *
6 * This program is free software; you can redistribute it and/or
7 * modify it under the terms of the GNU General Public License (GPL)
8 * version 2 as published by the Free Software Foundation.
ae4735db 9 *
34e49164
C
10 * This program 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 * file license.txt for more details.
14 *)
15open Common
16
17(*****************************************************************************)
18(* The AST C related types *)
19(*****************************************************************************)
b1b2de81
C
20(*
21 * Some stuff are tagged semantic: which means that they are computed
ae4735db
C
22 * after parsing.
23 *
24 * This means that some elements in this AST are present only if
b1b2de81
C
25 * some annotation/transformation has been done on the original AST returned
26 * by the parser. Cf type_annotater, comment_annotater, cpp_ast_c, etc.
27 *)
28
29
30(* ------------------------------------------------------------------------- *)
31(* Token/info *)
32(* ------------------------------------------------------------------------- *)
34e49164 33
ae4735db
C
34(* To allow some transformations over the AST, we keep as much information
35 * as possible in the AST such as the tokens content and their locations.
485bce71
C
36 * Those info are called 'info' (how original) and can be tagged.
37 * For instance one tag may say that the unparser should remove this token.
ae4735db 38 *
485bce71 39 * Update: Now I use a ref! in those 'info' so take care.
0708f913 40 * That means that modifications of the info of tokens can have
ae4735db 41 * an effect on the info stored in the ast (which is sometimes
0708f913 42 * convenient, cf unparse_c.ml or comment_annotater_c.ml)
ae4735db
C
43 *
44 * convention: I often use 'ii' for the name of a list of info.
45 *
46 * Sometimes we want to add someting at the beginning or at the end
485bce71
C
47 * of a construct. For 'function' and 'decl' we want to add something
48 * to their left and for 'if' 'while' et 'for' and so on at their right.
49 * We want some kinds of "virtual placeholders" that represent the start or
50 * end of a construct. We use fakeInfo for that purpose.
51 * To identify those cases I have added a fakestart/fakeend comment.
ae4735db 52 *
485bce71 53 * cocci: Each token will be decorated in the future by the mcodekind
34e49164
C
54 * of cocci. It is the job of the pretty printer to look at this
55 * information and decide to print or not the token (and also the
56 * pending '+' associated sometimes with the token).
ae4735db 57 *
34e49164
C
58 * The first time that we parse the original C file, the mcodekind is
59 * empty, or more precisely all is tagged as a CONTEXT with NOTHING
60 * associated. This is what I call a "clean" expr/statement/....
ae4735db 61 *
34e49164
C
62 * Each token will also be decorated in the future with an environment,
63 * because the pending '+' may contain metavariables that refer to some
64 * C code.
ae4735db 65 *
34e49164
C
66 *)
67
68(* forunparser: *)
69
91eba41f 70type posl = int * int (* line-col, for MetaPosValList, for position variables *)
708f4980 71 (* with sexp *)
485bce71
C
72
73(* the virtual position is set in Parsing_hacks.insert_virtual_positions *)
34e49164 74type virtual_position = Common.parse_info * int (* character offset *)
708f4980 75 (* with sexp *)
485bce71 76
ae4735db 77type parse_info =
34e49164
C
78 (* Present both in ast and list of tokens *)
79 | OriginTok of Common.parse_info
80 (* Present only in ast and generated after parsing. Used mainly
81 * by Julia, to add stuff at virtual places, beginning of func or decl *)
82 | FakeTok of string * virtual_position
83 (* Present both in ast and list of tokens. *)
84 | ExpandedTok of Common.parse_info * virtual_position
0708f913 85
34e49164
C
86 (* Present neither in ast nor in list of tokens
87 * but only in the '+' of the mcode of some tokens. Those kind of tokens
88 * are used to be able to use '=' to compare big ast portions.
89 *)
90 | AbstractLineTok of Common.parse_info (* local to the abstracted thing *)
708f4980 91 (* with sexp *)
34e49164 92
ae4735db 93type info = {
34e49164 94 pinfo : parse_info;
b1b2de81
C
95
96 (* this cocci_tag can be changed, which is how we can express some program
ae4735db 97 * transformations by tagging the tokens involved in this transformation.
485bce71 98 *)
951c7801 99 cocci_tag: (Ast_cocci.mcodekind * metavars_binding list) option ref;
0708f913 100 (* set in comment_annotater_c.ml *)
485bce71 101 comments_tag: comments_around ref;
b1b2de81 102
34e49164
C
103 (* todo? token_info : sometimes useful to know what token it was *)
104 }
105and il = info list
106
107(* wrap2 is like wrap, except that I use it often for separator such
108 * as ','. In that case the info is associated to the argument that
ae4735db
C
109 * follows, so in 'a,b' I will have in the list [(a,[]); (b,[','])].
110 *
111 * wrap3 is like wrap, except that I use it in case sometimes it
708f4980
C
112 * will be empty because the info will be included in a nested
113 * entity (e.g. for Ident in expr because it's inlined in the name)
114 * so user should never assume List.length wrap3 > 0.
115 *)
34e49164
C
116and 'a wrap = 'a * il
117and 'a wrap2 = 'a * il
708f4980 118and 'a wrap3 = 'a * il (* * evotype*)
34e49164 119
b1b2de81
C
120(* ------------------------------------------------------------------------- *)
121(* Name *)
122(* ------------------------------------------------------------------------- *)
123
124(* was called 'ident' before, but 'name' is I think better
951c7801 125 * as concatenated strings can be used not only for identifiers and for
b1b2de81 126 * declarators, but also for fields, for labels, etc.
951c7801 127 *
708f4980
C
128 * Note: because now the info is embeded in the name, the info for
129 * expression like Ident, or types like Typename, are not anymore
130 * stored in the expression or type. Hence if you assume this,
131 * which was true before, you are now wrong. So never write code like
132 * let (unwrape,_), ii = e and use 'ii' believing it contains
133 * the local ii to e. If you want to do that, use the appropiate
134 * wrapper get_local_ii_of_expr_inlining_ii_of_name.
b1b2de81 135 *)
951c7801 136and name =
b1b2de81
C
137 | RegularName of string wrap
138 | CppConcatenatedName of (string wrap) wrap2 (* the ## separators *) list
139 (* normally only used inside list of things, as in parameters or arguments
140 * in which case, cf cpp-manual, it has a special meaning *)
141 | CppVariadicName of string wrap (* ## s *)
951c7801 142 | CppIdentBuilder of string wrap (* s ( ) *) *
b1b2de81
C
143 ((string wrap) wrap2 list) (* arguments *)
144
145
34e49164
C
146(* ------------------------------------------------------------------------- *)
147(* C Type *)
148(* ------------------------------------------------------------------------- *)
149(* Could have more precise type in fullType, in expression, etc, but
150 * it requires to do too much things in parsing such as checking no
151 * conflicting structname, computing value, etc. Better to separate
91eba41f 152 * concern. So I put '=>' to mean what we would really like. In fact
34e49164
C
153 * what we really like is defining another fullType, expression, etc
154 * from scratch, because many stuff are just sugar.
ae4735db 155 *
34e49164
C
156 * invariant: Array and FunctionType have also typeQualifier but they
157 * dont have sense. I put this to factorise some code. If you look in
91eba41f 158 * the grammar, you see that we can never specify const for the array
ae4735db 159 * himself (but we can do it for pointer) or function, we always
91eba41f 160 * have in the action rule of the grammar a { (nQ, FunctionType ...) }.
ae4735db
C
161 *
162 *
34e49164
C
163 * Because of ExprStatement, we can have more 'new scope' events, but
164 * rare I think. For instance with 'array of constExpression' there can
165 * have an exprStatement and a new (local) struct defined. Same for
166 * Constructor.
ae4735db 167 *
b1b2de81 168 *)
34e49164
C
169
170
171and fullType = typeQualifier * typeC
708f4980 172 and typeC = typeCbis wrap (* todo reput wrap3 *)
34e49164 173
b1b2de81 174 and typeCbis =
34e49164
C
175 | BaseType of baseType
176
177 | Pointer of fullType
178 | Array of constExpression option * fullType
179 | FunctionType of functionType
180
ae4735db 181 | Enum of string option * enumType
34e49164
C
182 | StructUnion of structUnion * string option * structType (* new scope *)
183
184 | EnumName of string
ae4735db 185 | StructUnionName of structUnion * string
34e49164 186
b1b2de81 187 | TypeName of name * fullType option (* semantic: filled later *)
ae4735db 188
34e49164
C
189 | ParenType of fullType (* forunparser: *)
190
ae4735db
C
191 (* gccext: TypeOfType below may seems useless; Why declare a
192 * __typeof__(int) x; ?
b1b2de81 193 * When used with macros, it allows to fix a problem of C which
34e49164 194 * is that type declaration can be spread around the ident. Indeed it
ae4735db
C
195 * may be difficult to have a macro such as
196 * '#define macro(type, ident) type ident;'
197 * because when you want to do a
198 * macro(char[256], x),
199 * then it will generate invalid code, but with a
200 * '#define macro(type, ident) __typeof(type) ident;'
201 * it will work.
b1b2de81 202 *)
ae4735db
C
203 | TypeOfExpr of expression
204 | TypeOfType of fullType
485bce71
C
205
206 (* cppext: IfdefType TODO *)
ae4735db
C
207
208(* -------------------------------------- *)
209 and baseType = Void
210 | IntType of intType
34e49164
C
211 | FloatType of floatType
212
ae4735db 213 (* stdC: type section
34e49164 214 * add a | SizeT ?
ae4735db 215 * note: char and signed char are semantically different!!
34e49164
C
216 *)
217 and intType = CChar (* obsolete? | CWchar *)
218 | Si of signed
219
220 and signed = sign * base
221 and base = CChar2 | CShort | CInt | CLong | CLongLong (* gccext: *)
222 and sign = Signed | UnSigned
223
224 and floatType = CFloat | CDouble | CLongDouble
225
226
ae4735db 227 (* -------------------------------------- *)
34e49164 228 and structUnion = Struct | Union
ae4735db
C
229 and structType = field list
230 and field =
485bce71 231 | DeclarationField of field_declaration
b1b2de81 232 (* gccext: *)
708f4980 233 | EmptyField of info
b1b2de81 234
485bce71 235 (* cppext: *)
ae4735db 236 | MacroDeclField of (string * argument wrap2 list)
708f4980 237 wrap (* optional ';'*)
485bce71
C
238
239 (* cppext: *)
240 | CppDirectiveStruct of cpp_directive
241 | IfdefStruct of ifdef_directive (* * field list list *)
242
34e49164
C
243
244 (* before unparser, I didn't have a FieldDeclList but just a Field. *)
ae4735db 245 and field_declaration =
485bce71 246 | FieldDeclList of fieldkind wrap2 list (* , *) wrap (* ; *)
34e49164
C
247
248 (* At first I thought that a bitfield could be only Signed/Unsigned.
249 * But it seems that gcc allow char i:4. C rule must say that you
ae4735db 250 * can cast into int so enum too, ...
34e49164 251 *)
ae4735db 252 and fieldkind =
b1b2de81 253 | Simple of name option * fullType
ae4735db 254 | BitField of name option * fullType *
b1b2de81 255 info (* : *) * constExpression
ae4735db 256 (* fullType => BitFieldInt | BitFieldUnsigned *)
34e49164
C
257
258
ae4735db
C
259 (* -------------------------------------- *)
260 and enumType = (name * (info (* = *) * constExpression) option)
261 wrap2 (* , *) list
34e49164
C
262 (* => string * int list *)
263
264
ae4735db 265 (* -------------------------------------- *)
34e49164
C
266 (* return * (params * has "...") *)
267 and functionType = fullType * (parameterType wrap2 list * bool wrap)
ae4735db 268 and parameterType =
b1b2de81
C
269 { p_namei: name option;
270 p_register: bool wrap;
271 p_type: fullType;
272 }
273 (* => (bool (register) * fullType) list * bool *)
34e49164
C
274
275
ae4735db 276and typeQualifier = typeQualifierbis wrap
34e49164
C
277and typeQualifierbis = {const: bool; volatile: bool}
278
485bce71
C
279(* gccext: cppext: *)
280and attribute = attributebis wrap
281 and attributebis =
951c7801 282 | Attribute of string
34e49164
C
283
284(* ------------------------------------------------------------------------- *)
285(* C expression *)
286(* ------------------------------------------------------------------------- *)
708f4980 287and expression = (expressionbis * exp_info ref (* semantic: *)) wrap3
485bce71 288 and exp_info = exp_type option * test
0708f913 289 and exp_type = fullType (* Type_c.completed_and_simplified *) * local
485bce71
C
290 and local = LocalVar of parse_info | NotLocalVar (* cocci: *)
291 and test = Test | NotTest (* cocci: *)
292
951c7801 293 and expressionbis =
34e49164
C
294
295 (* Ident can be a enumeration constant, a simple variable, a name of a func.
296 * With cppext, Ident can also be the name of a macro. Sparse says
b1b2de81
C
297 * "an identifier with a meaning is a symbol" *)
298 | Ident of name (* todo? more semantic info such as LocalFunc *)
299
951c7801 300 | Constant of constant
34e49164 301 | FunCall of expression * argument wrap2 (* , *) list
b1b2de81 302 (* gccext: x ? /* empty */ : y <=> x ? x : y; hence the 'option' below *)
34e49164
C
303 | CondExpr of expression * expression option * expression
304
305 (* should be considered as statements, bad C langage *)
faf9a90c
C
306 | Sequence of expression * expression
307 | Assignment of expression * assignOp * expression
34e49164 308
91eba41f
C
309
310 | Postfix of expression * fixOp
311 | Infix of expression * fixOp
312
951c7801
C
313 | Unary of expression * unaryOp
314 | Binary of expression * binaryOp * expression
34e49164 315
91eba41f
C
316 | ArrayAccess of expression * expression
317
318 (* field ident access *)
b1b2de81
C
319 | RecordAccess of expression * name
320 | RecordPtAccess of expression * name
34e49164
C
321 (* redundant normally, could replace it by DeRef RecordAcces *)
322
ae4735db
C
323 | SizeOfExpr of expression
324 | SizeOfType of fullType
325 | Cast of fullType * expression
34e49164 326
ae4735db
C
327 (* gccext: *)
328 | StatementExpr of compound wrap (* ( ) new scope *)
329 | Constructor of fullType * initialiser wrap2 (* , *) list
34e49164
C
330
331 (* forunparser: *)
ae4735db 332 | ParenExpr of expression
34e49164 333
485bce71
C
334 (* cppext: IfdefExpr TODO *)
335
34e49164 336 (* cppext: normmally just expression *)
708f4980 337 and argument = (expression, weird_argument) Common.either
ae4735db 338 and weird_argument =
34e49164
C
339 | ArgType of parameterType
340 | ArgAction of action_macro
ae4735db 341 and action_macro =
485bce71 342 (* todo: ArgStatement of statement, possibly have ghost token *)
ae4735db 343 | ActMisc of il
34e49164
C
344
345
346 (* I put string for Int and Float because int would not be enough because
347 * OCaml int are 31 bits. So simpler to do string. Same reason to have
348 * string instead of int list for the String case.
ae4735db 349 *
b1b2de81 350 * note: -2 is not a constant, it is the unary operator '-'
34e49164
C
351 * applied to constant 2. So the string must represent a positive
352 * integer only. *)
353
ae4735db 354 and constant =
0708f913
C
355 | String of (string * isWchar)
356 | MultiString of string list (* can contain MacroString, todo: more info *)
34e49164 357 | Char of (string * isWchar) (* normally it is equivalent to Int *)
708f4980 358 | Int of (string * intType)
34e49164
C
359 | Float of (string * floatType)
360
361 and isWchar = IsWchar | IsChar
362
ae4735db
C
363
364 and unaryOp = GetRef | DeRef | UnPlus | UnMinus | Tilde | Not
485bce71 365 | GetRefLabel (* gccext: GetRefLabel, via &&label notation *)
34e49164
C
366 and assignOp = SimpleAssign | OpAssign of arithOp
367 and fixOp = Dec | Inc
368
369 and binaryOp = Arith of arithOp | Logical of logicalOp
370
ae4735db 371 and arithOp =
34e49164 372 | Plus | Minus | Mul | Div | Mod
ae4735db 373 | DecLeft | DecRight
34e49164
C
374 | And | Or | Xor
375
ae4735db
C
376 and logicalOp =
377 | Inf | Sup | InfEq | SupEq
378 | Eq | NotEq
34e49164
C
379 | AndLog | OrLog
380
381 and constExpression = expression (* => int *)
382
383
384(* ------------------------------------------------------------------------- *)
385(* C statement *)
386(* ------------------------------------------------------------------------- *)
387(* note: that assignement is not a statement but an expression;
388 * wonderful C langage.
ae4735db 389 *
34e49164 390 * note: I use 'and' for type definition cos gccext allow statement as
ae4735db
C
391 * expression, so need mutual recursive type definition.
392 *
b1b2de81 393 *)
34e49164 394
708f4980 395and statement = statementbis wrap3
ae4735db 396 and statementbis =
34e49164
C
397 | Labeled of labeled
398 | Compound of compound (* new scope *)
399 | ExprStatement of exprStatement
400 | Selection of selection (* have fakeend *)
401 | Iteration of iteration (* have fakeend *)
402 | Jump of jump
403
404 (* simplify cocci: only at the beginning of a compound normally *)
ae4735db 405 | Decl of declaration
34e49164
C
406
407 (* gccext: *)
408 | Asm of asmbody
409 | NestedFunc of definition
410
411 (* cppext: *)
412 | MacroStmt
ae4735db 413
34e49164
C
414
415
b1b2de81 416 and labeled = Label of name * statement
ae4735db 417 | Case of expression * statement
34e49164
C
418 | CaseRange of expression * expression * statement (* gccext: *)
419 | Default of statement
420
ae4735db
C
421 (* cppext:
422 * old: compound = (declaration list * statement list)
423 * old: (declaration, statement) either list
34e49164 424 * Simplify cocci to just have statement list, by integrating Decl in stmt.
ae4735db 425 *
485bce71 426 * update: now introduce also the _sequencable to allow ifdef in the middle.
b1b2de81
C
427 * Indeed, I now allow ifdefs in the ast but they must be only between
428 * "sequencable" elements. They can be put in a type only if this type
ae4735db
C
429 * is used in a list, like at the toplevel, used in a 'toplevel list',
430 * or inside a compound, used in a 'statement list'. I must not allow
431 * ifdef anywhere. For instance I can not make ifdef a statement
b1b2de81
C
432 * cos some instruction like If accept only one statement and the
433 * ifdef directive must not take the place of a legitimate instruction.
434 * We had a similar phenomena in SmPL where we have the notion
ae4735db 435 * of statement and sequencable statement too. Once you have
b1b2de81
C
436 * such a type of sequencable thing, then s/xx list/xx_sequencable list/
437 * and introduce the ifdef.
ae4735db 438 *
b1b2de81
C
439 * update: those ifdefs are either passed, or present in the AST but in
440 * a flat form. To structure those flat ifdefs you have to run
441 * a transformation that will put in a tree the statements inside
442 * ifdefs branches. Cf cpp_ast_c.ml. This is for instance the difference
443 * between a IfdefStmt (flat) and IfdefStmt2 (tree structured).
ae4735db 444 *
34e49164 445 *)
ae4735db 446 and compound = statement_sequencable list
485bce71
C
447
448 (* cppext: easier to put at statement_list level than statement level *)
ae4735db 449 and statement_sequencable =
485bce71 450 | StmtElem of statement
b1b2de81 451
ae4735db 452 (* cppext: *)
485bce71 453 | CppDirectiveStmt of cpp_directive
ae4735db 454 | IfdefStmt of ifdef_directive
485bce71
C
455
456 (* this will be build in cpp_ast_c from the previous flat IfdefStmt *)
457 | IfdefStmt2 of ifdef_directive list * (statement_sequencable list) list
34e49164
C
458
459 and exprStatement = expression option
460
ae4735db 461 (* for Switch, need check that all elements in the compound start
34e49164
C
462 * with a case:, otherwise unreachable code.
463 *)
ae4735db 464 and selection =
34e49164 465 | If of expression * statement * statement
ae4735db 466 | Switch of expression * statement
485bce71 467
34e49164 468
ae4735db 469 and iteration =
34e49164
C
470 | While of expression * statement
471 | DoWhile of statement * expression
472 | For of exprStatement wrap * exprStatement wrap * exprStatement wrap *
473 statement
485bce71 474 (* cppext: *)
34e49164
C
475 | MacroIteration of string * argument wrap2 list * statement
476
b1b2de81 477 and jump = Goto of name
ae4735db 478 | Continue | Break
34e49164
C
479 | Return | ReturnExpr of expression
480 | GotoComputed of expression (* gccext: goto *exp ';' *)
481
482
483 (* gccext: *)
484 and asmbody = il (* string list *) * colon wrap (* : *) list
485 and colon = Colon of colon_option wrap2 list
486 and colon_option = colon_option_bis wrap
487 and colon_option_bis = ColonMisc | ColonExpr of expression
488
489
490(* ------------------------------------------------------------------------- *)
491(* Declaration *)
492(* ------------------------------------------------------------------------- *)
ae4735db 493(* (string * ...) option cos can have empty declaration or struct tag
34e49164 494 * declaration.
ae4735db
C
495 *
496 * Before I had a Typedef constructor, but why make this special case and not
497 * have StructDef, EnumDef, ... so that 'struct t {...} v' will generate 2
485bce71 498 * declarations ? So I try to generalise and not have Typedef either. This
34e49164 499 * requires more work in parsing. Better to separate concern.
ae4735db 500 *
34e49164
C
501 * Before the need for unparser, I didn't have a DeclList but just a Decl.
502 *
503 * I am not sure what it means to declare a prototype inline, but gcc
ae4735db 504 * accepts it.
34e49164
C
505 *)
506
ae4735db 507and declaration =
34e49164
C
508 | DeclList of onedecl wrap2 (* , *) list wrap (* ; fakestart sto *)
509 (* cppext: *)
708f4980 510 | MacroDecl of (string * argument wrap2 list) wrap (* fakestart *)
34e49164 511
ae4735db 512 and onedecl =
b1b2de81 513 { v_namei: (name * (info (* = *) * initialiser) option) option;
485bce71 514 v_type: fullType;
ae4735db 515 (* semantic: set in type annotated and used in cocci_vs_c
978fd7e5
C
516 * when we transform some initialisation into affectation
517 *)
518 v_type_bis: fullType (* Type_c.completed_and_simplified *) option ref;
485bce71
C
519 v_storage: storage;
520 v_local: local_decl; (* cocci: *)
521 v_attr: attribute list; (* gccext: *)
522 }
523 and storage = storagebis * bool (* gccext: inline or not *)
34e49164
C
524 and storagebis = NoSto | StoTypedef | Sto of storageClass
525 and storageClass = Auto | Static | Register | Extern
526
b1b2de81
C
527 and local_decl = LocalDecl | NotLocalDecl
528
978fd7e5
C
529 (* fullType is the type used if the type should be converted to
530 an assignment. It can be adjusted in the type annotation
531 phase when typedef information is availalble *)
34e49164 532 and initialiser = initialiserbis wrap
ae4735db
C
533 and initialiserbis =
534 | InitExpr of expression
535 | InitList of initialiser wrap2 (* , *) list
34e49164
C
536 (* gccext: *)
537 | InitDesignators of designator list * initialiser
538 | InitFieldOld of string * initialiser
539 | InitIndexOld of expression * initialiser
540
541 (* ex: [2].y = x, or .y[2] or .y.x. They can be nested *)
ae4735db
C
542 and designator = designatorbis wrap
543 and designatorbis =
544 | DesignatorField of string
34e49164
C
545 | DesignatorIndex of expression
546 | DesignatorRange of expression * expression
ae4735db 547
34e49164
C
548(* ------------------------------------------------------------------------- *)
549(* Function definition *)
550(* ------------------------------------------------------------------------- *)
ae4735db
C
551(* Normally we should define another type functionType2 because there
552 * are more restrictions on what can define a function than a pointer
34e49164 553 * function. For instance a function declaration can omit the name of the
b1b2de81 554 * parameter whereas a function definition can not. But, in some cases such
ae4735db 555 * as 'f(void) {', there is no name too, so I simplified and reused the
34e49164 556 * same functionType type for both declaration and function definition.
ae4735db 557 *
b1b2de81
C
558 * Also old style C does not have type in the parameter, so again simpler
559 * to abuse the functionType and allow missing type.
34e49164 560 *)
b1b2de81 561and definition = definitionbis wrap (* ( ) { } fakestart sto *)
ae4735db 562 and definitionbis =
b1b2de81 563 { f_name: name;
708f4980 564 f_type: functionType; (* less? a functionType2 ? *)
485bce71
C
565 f_storage: storage;
566 f_body: compound;
567 f_attr: attribute list; (* gccext: *)
91eba41f 568 f_old_c_style: declaration list option;
485bce71
C
569 }
570 (* cppext: IfdefFunHeader TODO *)
34e49164
C
571
572(* ------------------------------------------------------------------------- *)
485bce71 573(* cppext: cpp directives, #ifdef, #define and #include body *)
34e49164 574(* ------------------------------------------------------------------------- *)
485bce71 575and cpp_directive =
ae4735db
C
576 | Define of define
577 | Include of includ
485bce71 578 | Undef of string wrap
ae4735db 579 | PragmaAndCo of il
b1b2de81 580(*| Ifdef ? no, ifdefs are handled differently, cf ifdef_directive below *)
485bce71 581
708f4980 582and define = string wrap (* #define s eol *) * (define_kind * define_val)
34e49164
C
583 and define_kind =
584 | DefineVar
485bce71 585 | DefineFunc of ((string wrap) wrap2 list) wrap (* () *)
ae4735db 586 and define_val =
b1b2de81 587 (* most common case; e.g. to define int constant *)
ae4735db 588 | DefineExpr of expression
91eba41f 589
34e49164
C
590 | DefineStmt of statement
591 | DefineType of fullType
485bce71 592 | DefineDoWhileZero of (statement * expression) wrap (* do { } while(0) *)
91eba41f 593
34e49164 594 | DefineFunction of definition
485bce71 595 | DefineInit of initialiser (* in practice only { } with possible ',' *)
b1b2de81 596
485bce71
C
597 (* TODO DefineMulti of define_val list *)
598
34e49164
C
599 | DefineText of string wrap
600 | DefineEmpty
601
485bce71 602 | DefineTodo
34e49164
C
603
604
485bce71 605
ae4735db 606and includ =
485bce71
C
607 { i_include: inc_file wrap; (* #include s *)
608 (* cocci: computed in ? *)
609 i_rel_pos: include_rel_pos option ref;
610 (* cocci: cf -test incl *)
ae4735db 611 i_is_in_ifdef: bool;
485bce71
C
612 (* cf cpp_ast_c.ml. set to None at parsing time. *)
613 i_content: (Common.filename (* full path *) * program) option;
614 }
ae4735db 615 and inc_file =
34e49164
C
616 | Local of inc_elem list
617 | NonLocal of inc_elem list
0708f913 618 | Weird of string (* ex: #include SYSTEM_H *)
34e49164
C
619 and inc_elem = string
620
485bce71 621 (* cocci: to tag the first of #include <xx/> and last of #include <yy/>
ae4735db 622 *
485bce71
C
623 * The first_of and last_of store the list of prefixes that was
624 * introduced by the include. On #include <a/b/x>, if the include was
625 * the first in the file, it would give in first_of the following
ae4735db
C
626 * prefixes a/b/c; a/b/; a/ ; <empty>
627 *
485bce71
C
628 * This is set after parsing, in cocci.ml, in update_rel_pos.
629 *)
ae4735db 630 and include_rel_pos = {
485bce71
C
631 first_of : string list list;
632 last_of : string list list;
34e49164
C
633 }
634
485bce71
C
635
636
b1b2de81
C
637(* todo? to specialize if someone need more info *)
638and ifdef_directive = (* or and 'a ifdefed = 'a list wrap *)
639 | IfdefDirective of (ifdefkind * matching_tag) wrap
ae4735db 640 and ifdefkind =
b1b2de81
C
641 | Ifdef (* todo? of string ? of formula_cpp ? *)
642 | IfdefElseif (* same *)
643 | IfdefElse (* same *)
ae4735db
C
644 | IfdefEndif
645 (* set in Parsing_hacks.set_ifdef_parenthize_info. It internally use
b1b2de81 646 * a global so it means if you parse the same file twice you may get
ae4735db 647 * different id. I try now to avoid this pb by resetting it each
b1b2de81
C
648 * time I parse a file.
649 *)
ae4735db 650 and matching_tag =
b1b2de81
C
651 IfdefTag of (int (* tag *) * int (* total with this tag *))
652
653
485bce71
C
654
655
656
34e49164
C
657(* ------------------------------------------------------------------------- *)
658(* The toplevels elements *)
659(* ------------------------------------------------------------------------- *)
660and toplevel =
661 | Declaration of declaration
662 | Definition of definition
ae4735db 663
34e49164 664 (* cppext: *)
485bce71
C
665 | CppTop of cpp_directive
666 | IfdefTop of ifdef_directive (* * toplevel list *)
667
34e49164 668 (* cppext: *)
ae4735db
C
669 | MacroTop of string * argument wrap2 list * il
670
34e49164
C
671 | EmptyDef of il (* gccext: allow redundant ';' *)
672 | NotParsedCorrectly of il
673
34e49164
C
674 | FinalDef of info (* EOF *)
675
676(* ------------------------------------------------------------------------- *)
677and program = toplevel list
678
34e49164
C
679(*****************************************************************************)
680(* Cocci Bindings *)
681(*****************************************************************************)
ae4735db
C
682(* Was previously in pattern.ml, but because of the transformer,
683 * we need to decorate each token with some cocci code AND the environment
34e49164
C
684 * for this cocci code.
685 *)
686and metavars_binding = (Ast_cocci.meta_name, metavar_binding_kind) assoc
ae4735db 687 and metavar_binding_kind =
34e49164
C
688 | MetaIdVal of string
689 | MetaFuncVal of string
690 | MetaLocalFuncVal of string
691
692 | MetaExprVal of expression (* a "clean expr" *)
693 | MetaExprListVal of argument wrap2 list
694 | MetaParamVal of parameterType
695 | MetaParamListVal of parameterType wrap2 list
696
697 | MetaTypeVal of fullType
113803cf 698 | MetaInitVal of initialiser
34e49164
C
699 | MetaStmtVal of statement
700
701 (* Could also be in Lib_engine.metavars_binding2 with the ParenVal,
702 * because don't need to have the value for a position in the env of
703 * a '+'. But ParenVal or LabelVal are used only by CTL, they are not
704 * variables accessible via SmPL whereas the position can be one day
705 * so I think it's better to put MetaPosVal here *)
706 | MetaPosVal of (Ast_cocci.fixpos * Ast_cocci.fixpos) (* max, min *)
485bce71
C
707 | MetaPosValList of
708 (Common.filename * string (*element*) * posl * posl) list (* min, max *)
34e49164
C
709 | MetaListlenVal of int
710
711
712(*****************************************************************************)
713(* C comments *)
714(*****************************************************************************)
715
ae4735db 716(* convention: I often use "m" for comments as I can not use "c"
485bce71 717 * (already use for c stuff) and "com" is too long.
34e49164
C
718 *)
719
0708f913
C
720(* this type will be associated to each token.
721 *)
34e49164 722and comments_around = {
0708f913
C
723 mbefore: Token_c.comment_like_token list;
724 mafter: Token_c.comment_like_token list;
708f4980
C
725
726 (* less: could remove ? do something simpler than CComment for
727 * coccinelle, cf above. *)
728 mbefore2: comment_and_relative_pos list;
729 mafter2: comment_and_relative_pos list;
730 }
34e49164
C
731 and comment_and_relative_pos = {
732
733 minfo: Common.parse_info;
734 (* the int represent the number of lines of difference between the
735 * current token and the comment. When on same line, this number is 0.
736 * When previous line, -1. In some way the after/before in previous
737 * record is useless because the sign of the integer can helps
738 * do the difference too, but I keep it that way.
739 *)
740 mpos: int;
741 (* todo?
ae4735db 742 * cppbetween: bool; touse? if false positive
34e49164
C
743 * is_alone_in_line: bool; (*for labels, to avoid false positive*)
744 *)
708f4980 745 }
34e49164
C
746
747and comment = Common.parse_info
748and com = comment list ref
34e49164 749
708f4980 750 (* with sexp *)
34e49164
C
751
752
753(*****************************************************************************)
754(* Some constructors *)
755(*****************************************************************************)
756let nullQualif = ({const=false; volatile= false}, [])
ae4735db 757let nQ = nullQualif
34e49164
C
758
759let defaultInt = (BaseType (IntType (Si (Signed, CInt))))
760
761let noType () = ref (None,NotTest)
762let noInstr = (ExprStatement (None), [])
763let noTypedefDef () = None
764
ae4735db 765let emptyMetavarsBinding =
34e49164
C
766 ([]: metavars_binding)
767
708f4980 768let emptyAnnotCocci =
34e49164 769 (Ast_cocci.CONTEXT (Ast_cocci.NoPos,Ast_cocci.NOTHING),
951c7801 770 ([] : metavars_binding list))
34e49164 771
ae4735db 772let emptyAnnot =
951c7801 773 (None: (Ast_cocci.mcodekind * metavars_binding list) option)
708f4980
C
774
775(* compatibility mode *)
ae4735db 776let mcode_and_env_of_cocciref aref =
708f4980
C
777 match !aref with
778 | Some x -> x
779 | None -> emptyAnnotCocci
780
781
34e49164
C
782let emptyComments= {
783 mbefore = [];
784 mafter = [];
708f4980
C
785 mbefore2 = [];
786 mafter2 = [];
34e49164
C
787}
788
789
790(* for include, some meta information needed by cocci *)
ae4735db 791let noRelPos () =
34e49164 792 ref (None: include_rel_pos option)
ae4735db 793let noInIfdef () =
34e49164
C
794 ref false
795
796
ae4735db 797(* When want add some info in ast that does not correspond to
34e49164
C
798 * an existing C element.
799 * old: or when don't want 'synchronize' on it in unparse_c.ml
800 * (now have other mark for tha matter).
801 *)
802let no_virt_pos = ({str="";charpos=0;line=0;column=0;file=""},-1)
803
ae4735db 804let fakeInfo pi =
34e49164
C
805 { pinfo = FakeTok ("",no_virt_pos);
806 cocci_tag = ref emptyAnnot;
807 comments_tag = ref emptyComments;
808 }
809
485bce71
C
810let noii = []
811let noattr = []
812let noi_content = (None: ((Common.filename * program) option))
34e49164
C
813
814(*****************************************************************************)
815(* Wrappers *)
816(*****************************************************************************)
817let unwrap = fst
818
113803cf 819let unwrap2 = fst
34e49164
C
820
821let unwrap_expr ((unwrap_e, typ), iie) = unwrap_e
822let rewrap_expr ((_old_unwrap_e, typ), iie) newe = ((newe, typ), iie)
823
708f4980
C
824let unwrap_typeC (qu, (typeC, ii)) = typeC
825let rewrap_typeC (qu, (typeC, ii)) newtypeC = (qu, (newtypeC, ii))
826
827let unwrap_typeCbis (typeC, ii) = typeC
828
829let unwrap_st (unwrap_st, ii) = unwrap_st
830
831(* ------------------------------------------------------------------------- *)
832let mk_e unwrap_e ii = (unwrap_e, noType()), ii
833let mk_e_bis unwrap_e ty ii = (unwrap_e, ty), ii
834
835let mk_ty typeC ii = nQ, (typeC, ii)
836let mk_tybis typeC ii = (typeC, ii)
837
838let mk_st unwrap_st ii = (unwrap_st, ii)
839
840(* ------------------------------------------------------------------------- *)
841let get_ii_typeC_take_care (typeC, ii) = ii
842let get_ii_st_take_care (st, ii) = ii
843let get_ii_expr_take_care (e, ii) = ii
844
845let get_st_and_ii (st, ii) = st, ii
846let get_ty_and_ii (qu, (typeC, ii)) = qu, (typeC, ii)
847let get_e_and_ii (e, ii) = e, ii
848
849
850(* ------------------------------------------------------------------------- *)
34e49164
C
851let get_type_expr ((unwrap_e, typ), iie) = !typ
852let set_type_expr ((unwrap_e, oldtyp), iie) newtyp =
853 oldtyp := newtyp
854 (* old: (unwrap_e, newtyp), iie *)
855
ae4735db 856let get_onlytype_expr ((unwrap_e, typ), iie) =
91eba41f
C
857 match !typ with
858 | Some (ft,_local), _test -> Some ft
859 | None, _ -> None
860
ae4735db 861let get_onlylocal_expr ((unwrap_e, typ), iie) =
0708f913
C
862 match !typ with
863 | Some (ft,local), _test -> Some local
864 | None, _ -> None
865
91eba41f 866(* ------------------------------------------------------------------------- *)
ae4735db 867let rewrap_str s ii =
34e49164
C
868 {ii with pinfo =
869 (match ii.pinfo with
870 OriginTok pi -> OriginTok { pi with Common.str = s;}
871 | ExpandedTok (pi,vpi) -> ExpandedTok ({ pi with Common.str = s;},vpi)
872 | FakeTok (_,vpi) -> FakeTok (s,vpi)
873 | AbstractLineTok pi -> OriginTok { pi with Common.str = s;})}
874
ae4735db 875let rewrap_pinfo pi ii =
34e49164
C
876 {ii with pinfo = pi}
877
708f4980
C
878
879
34e49164
C
880(* info about the current location *)
881let get_pi = function
882 OriginTok pi -> pi
883 | ExpandedTok (_,(pi,_)) -> pi
884 | FakeTok (_,(pi,_)) -> pi
885 | AbstractLineTok pi -> pi
886
887(* original info *)
888let get_opi = function
889 OriginTok pi -> pi
708f4980 890 | ExpandedTok (pi,_) -> pi (* diff with get_pi *)
34e49164
C
891 | FakeTok (_,_) -> failwith "no position information"
892 | AbstractLineTok pi -> pi
893
34e49164
C
894let str_of_info ii =
895 match ii.pinfo with
896 OriginTok pi -> pi.Common.str
897 | ExpandedTok (pi,_) -> pi.Common.str
898 | FakeTok (s,_) -> s
899 | AbstractLineTok pi -> pi.Common.str
900
901let get_info f ii =
902 match ii.pinfo with
903 OriginTok pi -> f pi
904 | ExpandedTok (_,(pi,_)) -> f pi
905 | FakeTok (_,(pi,_)) -> f pi
906 | AbstractLineTok pi -> f pi
907
908let get_orig_info f ii =
909 match ii.pinfo with
910 OriginTok pi -> f pi
708f4980 911 | ExpandedTok (pi,_) -> f pi (* diff with get_info *)
34e49164
C
912 | FakeTok (_,(pi,_)) -> f pi
913 | AbstractLineTok pi -> f pi
914
915let make_expanded ii =
916 {ii with pinfo = ExpandedTok (get_opi ii.pinfo,no_virt_pos)}
917
918let pos_of_info ii = get_info (function x -> x.Common.charpos) ii
919let opos_of_info ii = get_orig_info (function x -> x.Common.charpos) ii
920let line_of_info ii = get_orig_info (function x -> x.Common.line) ii
921let col_of_info ii = get_orig_info (function x -> x.Common.column) ii
922let file_of_info ii = get_orig_info (function x -> x.Common.file) ii
708f4980 923let mcode_of_info ii = fst (mcode_and_env_of_cocciref ii.cocci_tag)
34e49164
C
924let pinfo_of_info ii = ii.pinfo
925let parse_info_of_info ii = get_pi ii.pinfo
926
ae4735db 927let strloc_of_info ii =
978fd7e5
C
928 spf "%s:%d" (file_of_info ii) (line_of_info ii)
929
485bce71
C
930let is_fake ii =
931 match ii.pinfo with
932 FakeTok (_,_) -> true
933 | _ -> false
934
ae4735db 935let is_origintok ii =
485bce71
C
936 match ii.pinfo with
937 | OriginTok pi -> true
938 | _ -> false
939
91eba41f 940(* ------------------------------------------------------------------------- *)
34e49164 941type posrv = Real of Common.parse_info | Virt of virtual_position
485bce71 942
34e49164
C
943let compare_pos ii1 ii2 =
944 let get_pos = function
945 OriginTok pi -> Real pi
946 | FakeTok (s,vpi) -> Virt vpi
947 | ExpandedTok (pi,vpi) -> Virt vpi
948 | AbstractLineTok pi -> Real pi in (* used for printing *)
949 let pos1 = get_pos (pinfo_of_info ii1) in
950 let pos2 = get_pos (pinfo_of_info ii2) in
951 match (pos1,pos2) with
faf9a90c
C
952 (Real p1, Real p2) ->
953 compare p1.Common.charpos p2.Common.charpos
34e49164 954 | (Virt (p1,_), Real p2) ->
b1b2de81 955 if (compare p1.Common.charpos p2.Common.charpos) =|= (-1) then (-1) else 1
34e49164 956 | (Real p1, Virt (p2,_)) ->
b1b2de81 957 if (compare p1.Common.charpos p2.Common.charpos) =|= 1 then 1 else (-1)
34e49164
C
958 | (Virt (p1,o1), Virt (p2,o2)) ->
959 let poi1 = p1.Common.charpos in
960 let poi2 = p2.Common.charpos in
961 match compare poi1 poi2 with
962 -1 -> -1
963 | 0 -> compare o1 o2
964 | x -> x
965
ae4735db 966let equal_posl (l1,c1) (l2,c2) =
34e49164
C
967 (l1 =|= l2) && (c1 =|= c2)
968
969let info_to_fixpos ii =
970 match pinfo_of_info ii with
971 OriginTok pi -> Ast_cocci.Real pi.Common.charpos
972 | ExpandedTok (_,(pi,offset)) ->
973 Ast_cocci.Virt (pi.Common.charpos,offset)
974 | FakeTok (_,(pi,offset)) ->
975 Ast_cocci.Virt (pi.Common.charpos,offset)
976 | AbstractLineTok pi -> failwith "unexpected abstract"
977
485bce71 978(* cocci: *)
34e49164 979let is_test (e : expression) =
708f4980 980 let (_,info), _ = e in
34e49164 981 let (_,test) = !info in
b1b2de81 982 test =*= Test
34e49164
C
983
984(*****************************************************************************)
985(* Abstract line *)
986(*****************************************************************************)
987
988(* When we have extended the C Ast to add some info to the tokens,
989 * such as its line number in the file, we can not use anymore the
990 * ocaml '=' to compare Ast elements. To overcome this problem, to be
991 * able to use again '=', we just have to get rid of all those extra
992 * information, to "abstract those line" (al) information.
ae4735db 993 *
91eba41f
C
994 * Julia then modifies it a little to have a tokenindex, so the original
995 * true al_info is in fact real_al_info.
34e49164
C
996 *)
997
ae4735db 998let al_info tokenindex x =
34e49164
C
999 { pinfo =
1000 (AbstractLineTok
1001 {charpos = tokenindex;
1002 line = tokenindex;
1003 column = tokenindex;
1004 file = "";
1005 str = str_of_info x});
1006 cocci_tag = ref emptyAnnot;
1007 comments_tag = ref emptyComments;
1008 }
1009
ae4735db 1010let semi_al_info x =
34e49164
C
1011 { x with
1012 cocci_tag = ref emptyAnnot;
1013 comments_tag = ref emptyComments;
1014 }
1015
ae4735db 1016let magic_real_number = -10
91eba41f 1017
ae4735db 1018let real_al_info x =
91eba41f
C
1019 { pinfo =
1020 (AbstractLineTok
1021 {charpos = magic_real_number;
1022 line = magic_real_number;
1023 column = magic_real_number;
1024 file = "";
1025 str = str_of_info x});
1026 cocci_tag = ref emptyAnnot;
1027 comments_tag = ref emptyComments;
1028 }
1029
b1b2de81
C
1030let al_comments x =
1031 let keep_cpp l =
1032 List.filter (function (Token_c.TCommentCpp _,_) -> true | _ -> false) l in
1033 let al_com (x,i) =
1034 (x,{i with Common.charpos = magic_real_number;
1035 Common.line = magic_real_number;
1036 Common.column = magic_real_number}) in
1037 {mbefore = []; (* duplicates mafter of the previous token *)
708f4980
C
1038 mafter = List.map al_com (keep_cpp x.mafter);
1039 mbefore2=[];
1040 mafter2=[];
1041 }
b1b2de81 1042
ae4735db 1043let al_info_cpp tokenindex x =
b1b2de81
C
1044 { pinfo =
1045 (AbstractLineTok
1046 {charpos = tokenindex;
1047 line = tokenindex;
1048 column = tokenindex;
1049 file = "";
1050 str = str_of_info x});
1051 cocci_tag = ref emptyAnnot;
1052 comments_tag = ref (al_comments !(x.comments_tag));
1053 }
1054
ae4735db 1055let semi_al_info_cpp x =
b1b2de81
C
1056 { x with
1057 cocci_tag = ref emptyAnnot;
1058 comments_tag = ref (al_comments !(x.comments_tag));
1059 }
1060
ae4735db 1061let real_al_info_cpp x =
b1b2de81
C
1062 { pinfo =
1063 (AbstractLineTok
1064 {charpos = magic_real_number;
1065 line = magic_real_number;
1066 column = magic_real_number;
1067 file = "";
1068 str = str_of_info x});
1069 cocci_tag = ref emptyAnnot;
1070 comments_tag = ref (al_comments !(x.comments_tag));
1071 }
1072
91eba41f 1073
34e49164
C
1074(*****************************************************************************)
1075(* Views *)
1076(*****************************************************************************)
1077
1078(* Transform a list of arguments (or parameters) where the commas are
1079 * represented via the wrap2 and associated with an element, with
1080 * a list where the comma are on their own. f(1,2,2) was
1081 * [(1,[]); (2,[,]); (2,[,])] and become [1;',';2;',';2].
ae4735db 1082 *
34e49164
C
1083 * Used in cocci_vs_c.ml, to have a more direct correspondance between
1084 * the ast_cocci of julia and ast_c.
1085 *)
ae4735db 1086let rec (split_comma: 'a wrap2 list -> ('a, il) either list) =
34e49164
C
1087 function
1088 | [] -> []
ae4735db
C
1089 | (e, ii)::xs ->
1090 if null ii
34e49164
C
1091 then (Left e)::split_comma xs
1092 else Right ii::Left e::split_comma xs
1093
ae4735db 1094let rec (unsplit_comma: ('a, il) either list -> 'a wrap2 list) =
34e49164
C
1095 function
1096 | [] -> []
ae4735db 1097 | Right ii::Left e::xs ->
34e49164 1098 (e, ii)::unsplit_comma xs
ae4735db 1099 | Left e::xs ->
34e49164
C
1100 let empty_ii = [] in
1101 (e, empty_ii)::unsplit_comma xs
ae4735db 1102 | Right ii::_ ->
34e49164
C
1103 raise Impossible
1104
1105
1106
1107
485bce71
C
1108(*****************************************************************************)
1109(* Helpers, could also be put in lib_parsing_c.ml instead *)
1110(*****************************************************************************)
1111
91eba41f
C
1112(* should maybe be in pretty_print_c ? *)
1113
ae4735db 1114let s_of_inc_file inc_file =
485bce71
C
1115 match inc_file with
1116 | Local xs -> xs +> Common.join "/"
1117 | NonLocal xs -> xs +> Common.join "/"
0708f913 1118 | Weird s -> s
485bce71 1119
ae4735db 1120let s_of_inc_file_bis inc_file =
485bce71
C
1121 match inc_file with
1122 | Local xs -> "\"" ^ xs +> Common.join "/" ^ "\""
1123 | NonLocal xs -> "<" ^ xs +> Common.join "/" ^ ">"
0708f913 1124 | Weird s -> s
485bce71 1125
ae4735db 1126let fieldname_of_fieldkind fieldkind =
b1b2de81 1127 match fieldkind with
485bce71 1128 | Simple (sopt, ft) -> sopt
b1b2de81 1129 | BitField (sopt, ft, info, expr) -> sopt
485bce71 1130
91eba41f 1131
ae4735db 1132let s_of_attr attr =
91eba41f
C
1133 attr
1134 +> List.map (fun (Attribute s, ii) -> s)
1135 +> Common.join ","
113803cf 1136
708f4980
C
1137
1138(* ------------------------------------------------------------------------- *)
ae4735db 1139let str_of_name ident =
b1b2de81
C
1140 match ident with
1141 | RegularName (s,ii) -> s
ae4735db 1142 | CppConcatenatedName xs ->
b1b2de81
C
1143 xs +> List.map (fun (x,iiop) -> unwrap x) +> Common.join "##"
1144 | CppVariadicName (s, ii) -> "##" ^ s
ae4735db
C
1145 | CppIdentBuilder ((s,iis), xs) ->
1146 s ^ "(" ^
b1b2de81
C
1147 (xs +> List.map (fun ((x,iix), iicomma) -> x) +> Common.join ",") ^
1148 ")"
1149
ae4735db 1150let get_s_and_ii_of_name name =
708f4980 1151 match name with
ae4735db 1152 | RegularName (s, iis) -> s, iis
708f4980 1153 | CppIdentBuilder ((s, iis), xs) -> s, iis
ae4735db 1154 | CppVariadicName (s,iis) ->
708f4980
C
1155 let (iop, iis) = Common.tuple_of_list2 iis in
1156 s, [iis]
ae4735db 1157 | CppConcatenatedName xs ->
b1b2de81
C
1158 (match xs with
1159 | [] -> raise Impossible
ae4735db 1160 | ((s,iis),noiiop)::xs ->
708f4980 1161 s, iis
b1b2de81 1162 )
b1b2de81 1163
ae4735db 1164let get_s_and_info_of_name name =
708f4980
C
1165 let (s,ii) = get_s_and_ii_of_name name in
1166 s, List.hd ii
1167
ae4735db 1168let info_of_name name =
708f4980
C
1169 let (s,ii) = get_s_and_ii_of_name name in
1170 List.hd ii
1171
ae4735db 1172let ii_of_name name =
708f4980
C
1173 let (s,ii) = get_s_and_ii_of_name name in
1174 ii
1175
ae4735db 1176let get_local_ii_of_expr_inlining_ii_of_name e =
708f4980
C
1177 let (ebis,_),ii = e in
1178 match ebis, ii with
ae4735db 1179 | Ident name, noii ->
708f4980
C
1180 assert(null noii);
1181 ii_of_name name
ae4735db 1182 | RecordAccess (e, name), ii ->
708f4980 1183 ii @ ii_of_name name
ae4735db 1184 | RecordPtAccess (e, name), ii ->
708f4980
C
1185 ii @ ii_of_name name
1186 | _, ii -> ii
1187
1188
1189let get_local_ii_of_tybis_inlining_ii_of_name ty =
1190 match ty with
1191 | TypeName (name, _typ), [] -> ii_of_name name
1192 | _, ii -> ii
1193
978fd7e5 1194(* the following is used to obtain the argument to LocalVar *)
ae4735db 1195let info_of_type ft =
978fd7e5
C
1196 let (qu, ty) = ft in
1197 (* bugfix: because of string->name, the ii can be deeper *)
1198 let ii = get_local_ii_of_tybis_inlining_ii_of_name ty in
1199 match ii with
1200 | ii::_ -> ii.pinfo
1201 | [] -> failwith "type has no text; need to think again"
1202
708f4980
C
1203(* only Label and Goto have name *)
1204let get_local_ii_of_st_inlining_ii_of_name st =
1205 match st with
1206 | Labeled (Label (name, st)), ii -> ii_of_name name @ ii
ae4735db 1207 | Jump (Goto name), ii ->
708f4980
C
1208 let (i1, i3) = Common.tuple_of_list2 ii in
1209 [i1] @ ii_of_name name @ [i3]
1210 | _, ii -> ii
1211
ae4735db 1212
708f4980
C
1213
1214(* ------------------------------------------------------------------------- *)
ae4735db 1215let name_of_parameter param =
b1b2de81
C
1216 param.p_namei +> Common.map_option (str_of_name)
1217