Legend:
Page
Library
Module
Module type
Parameter
Class
Class type
Source
Source file cst_cpp.ml
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835(* Yoann Padioleau
*
* Copyright (C) 2010-2014 Facebook
* Copyright (C) 2008-2009 University of Urbana Champaign
* Copyright (C) 2006-2007 Ecole des Mines de Nantes
* Copyright (C) 2002 Yoann Padioleau
*
* This program is free software; you can redistribute it and/or
* modify it under the terms of the GNU General Public License (GPL)
* version 2 as published by the Free Software Foundation.
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* file license.txt for more details.
*)(*****************************************************************************)(* Prelude *)(*****************************************************************************)(*
* This is a big file ... C++ is a big and complicated language ...
* This file started with a simple AST for C. It was then extended
* to deal with cpp idioms (see 'cppext:' tag), gcc extensions (see gccext),
* and finally C++ constructs (see c++ext). A few kencc extensions
* were also recently added (see kenccext).
*
* gcc introduced StatementExpr which made expr and statement mutually
* recursive. It also added NestedFunc for even more mutual recursivity ...
* With C++ templates, because template arguments can be types or expressions
* and because templates are also qualifiers, almost all types
* are now mutually recursive ...
*
* Like most other ASTs in pfff, it's actually more a Concrete Syntax Tree.
* Some stuff are tagged 'semantic:' which means that they are computed
* after parsing.
*
* See also lang_c/parsing/ast_c.ml and lang_clang/parsing/ast_clang.ml
* (as well as mini/ast_minic.ml).
*
* todo:
* - migrate everything to wrap2, e.g. no more expressionbis, statementbis
* - support C++0x11, e.g. lambdas
*
* related work:
* - https://github.com/facebook/facebook-clang-plugins
* or https://github.com/Antique-team/clangml
* but by both using clang they work after preprocessing. This is
* fine for bug finding, but for codemap we need to parse as is,
* and we need to do it fast (calling clang is super expensive because
* calling cpp and parsing the end result is expensive)
* - EDG
* - see the CC'09 paper
*)(*****************************************************************************)(* The AST C++ related types *)(*****************************************************************************)(* ------------------------------------------------------------------------- *)(* Token/info *)(* ------------------------------------------------------------------------- *)typetok=Parse_info.t(* a shortcut to annotate some information with token/position information *)and'awrap='a*toklist(* TODO: change to 'a * tok *)and'awrap2='a*tokand'aparen=tok*'a*tokand'abrace=tok*'a*tokand'abracket=tok*'a*tokand'aangle=tok*'a*tokand'acomma_list='awraplistand'acomma_list2=('a,tok(* the comma *))Common.eitherlist(* with tarzan *)(* ------------------------------------------------------------------------- *)(* Ident, name, scope qualifier *)(* ------------------------------------------------------------------------- *)(* c++ext: in C 'name' and 'ident' are equivalent and are just strings.
* In C++ 'name' can have a complex form like 'A::B::list<int>::size'.
* I use Q for qualified. I also have a special type to make the difference
* between intermediate idents (the classname or template_id) and final idents.
* Note that sometimes final idents are also classnames and can have final
* template_id.
*
* Sometimes some elements are not allowed at certain places, for instance
* converters can not have an associated Qtop. But I prefered to simplify
* and have a unique type for all those different kinds of names.
*)typename=tok(*::*)option*(qualifier*tok(*::*))list*identandident=(* function name, macro name, variable, classname, enumname, namespace *)|IdIdentofsimple_ident(* c++ext: *)|IdTemplateIdofsimple_ident*template_arguments|IdDestructoroftok(*~*)*simple_ident|IdOperatoroftok*(operator*toklist)|IdConverteroftok*fullTypeandsimple_ident=stringwrap2andtemplate_arguments=template_argumentcomma_listangleandtemplate_argument=(fullType,expression)Common.eitherandqualifier=|QClassnameofsimple_ident(* classname or namespacename *)|QTemplateIdofsimple_ident*template_arguments(* special cases *)andclass_name=name(* only IdIdent or IdTemplateId *)andnamespace_name=name(* only IdIdent *)andtypedef_name=name(* only IdIdent *)andenum_name=name(* only IdIdent *)andident_name=name(* only IdIdent *)(* TODO: do like in parsing_c/
* and ident_string =
* | RegularName of string wrap
*
* (* cppext: *)
* | CppConcatenatedName of (string wrap) wrap2 (* the ## separators *) list
* (* normally only used inside list of things, as in parameters or arguments
* * in which case, cf cpp-manual, it has a special meaning *)
* | CppVariadicName of string wrap (* ## s *)
* | CppIdentBuilder of string wrap (* s ( ) *) *
* ((string wrap) wrap2 list) (* arguments *)
*)(* ------------------------------------------------------------------------- *)(* Types *)(* ------------------------------------------------------------------------- *)(* We could have a more precise type in fullType, in expression, etc, but
* it would require too much things at parsing time such as checking whether
* there is no conflicts structname, computing value, etc. It's better to
* separate concerns, so I put '=>' to mean what we would really like. In fact
* what we really like is defining another fullType, expression, etc
* from scratch, because many stuff are just sugar.
*
* invariant: Array and FunctionType have also typeQualifier but they
* dont have sense. I put this to factorise some code. If you look in
* grammar, you see that we can never specify const for the array
* himself (but we can do it for pointer).
*)andfullType=typeQualifier*typeCandtypeC=typeCbiswrap(* less: rename to TBase, TPointer, etc *)andtypeCbis=|BaseTypeofbaseType|Pointerof(* '*' *)fullType(* c++ext: *)|Referenceof(* '&' *)fullType|ArrayofconstExpressionoptionbracket*fullType|FunctionTypeoffunctionType|EnumNameoftok(* 'enum' *)*simple_ident(*enum_name*)|StructUnionNameofstructUnionwrap2*simple_ident(*ident_name*)(* c++ext: TypeName can now correspond also to a classname or enumname
* and is a name so can have some IdTemplateId in it.
*)|TypeNameofname(*typedef_name*)(* only to disambiguate I think *)|TypenameKwdoftok(* 'typename' *)*name(*typedef_name*)(* gccext: TypeOfType may seems useless, why declare a __typeof__(int)
* x; ? But when used with macro, it allows to fix a problem of C which
* is that type declaration can be spread around the ident. Indeed it
* may be difficult to have a macro such as '#define macro(type,
* ident) type ident;' because when you want to do a macro(char[256],
* x), then it will generate invalid code, but with a '#define
* macro(type, ident) __typeof(type) ident;' it will work. *)|TypeOfoftok*(fullType,expression)Common.eitherparen(* should be really just at toplevel *)|EnumDefofenum_definition(* => string * int list *)(* c++ext: bigger type now *)|StructDefofclass_definition(* forunparser: *)|ParenTypeoffullTypeparenandbaseType=|Void|IntTypeofintType|FloatTypeoffloatType(* stdC: type section. 'char' and 'signed char' are different *)andintType=|CChar(* obsolete? | CWchar *)|Siofsigned(* c++ext: maybe could be put in baseType instead ? *)|CBool|WChar_tandsigned=sign*baseandbase=|CChar2|CShort|CInt|CLong(* gccext: *)|CLongLongandsign=Signed|UnSignedandfloatType=CFloat|CDouble|CLongDoubleandtypeQualifier={const:tokoption;volatile:tokoption;}(* TODO: like in parsing_c/
* (* gccext: cppext: *)
* and attribute = attributebis wrap
* and attributebis =
* | Attribute of string
*)(* ------------------------------------------------------------------------- *)(* Expressions *)(* ------------------------------------------------------------------------- *)(* Because of StatementExpr, we can have more 'new scope', but it's
* rare I think. For instance with 'array of constExpression' we could
* have an StatementExpr and a new (local) struct defined. Same for
* Constructor.
*)andexpression=expressionbiswrapandexpressionbis=(* Id can be an enumeration constant, variable, function name.
* cppext: Id can also be the name of a macro. sparse says
* "an identifier with a meaning is a symbol".
* c++ext: Id is now a 'name' instead of a 'string' and can be
* also an operator name.
*)|Idofname*ident_info(* semantic: see check_variables_cpp.ml *)|Cofconstant(* I used to have FunCallSimple but not that useful, and we want scope info
* for FunCallSimple too because can have fn(...) where fn is actually
* a local *)|Callofexpression*argumentcomma_listparen(* gccext: x ? /* empty */ : y <=> x ? x : y; *)|CondExprofexpression*expressionoption*expression(* should be considered as statements, bad C langage *)|Sequenceofexpression*expression|Assignmentofexpression*assignOp*expression|Postfixofexpression*fixOp|Infixofexpression*fixOp(* contains GetRef and Deref!! todo: lift up? *)|Unaryofexpression*unaryOp|Binaryofexpression*binaryOp*expression|ArrayAccessofexpression*expressionbracket(* The Pt is redundant normally, could be replace by DeRef RecordAccess *)|RecordAccessofexpression*name|RecordPtAccessofexpression*name(* c++ext: note that second paramater is an expression, not a name *)|RecordStarAccessofexpression*expression|RecordPtStarAccessofexpression*expression|SizeOfExproftok*expression|SizeOfTypeoftok*fullTypeparen|CastoffullTypeparen*expression(* gccext: *)|StatementExprofcompoundparen(* ( { } ) new scope*)(* gccext: kenccext: *)|GccConstructoroffullTypeparen*initialisercomma_listbrace(* c++ext: *)|Thisoftok|ConstructedObjectoffullType*argumentcomma_listparen|TypeIdoftok*(fullType,expression)Common.eitherparen|CplusplusCastofcast_operatorwrap2*fullTypeangle*expressionparen|Newoftok(*::*)option*tok*argumentcomma_listparenoption(* placement *)*fullType*argumentcomma_listparenoption(* initializer *)|Deleteoftok(*::*)option*expression|DeleteArrayoftok(*::*)option*expression|Throwofexpressionoption(* forunparser: *)|ParenExprofexpressionparen(* sgrep-ext: *)|Ellipsesoftok|ExprTodo(* see check_variables_cpp.ml *)andident_info={mutablei_scope:Scope_code.t;}(* cppext: normmally just expression *)andargument=(expression,weird_argument)Common.eitherandweird_argument=|ArgTypeoffullType(* for really unparsable stuff ... we just bailout *)|ArgActionofaction_macroandaction_macro=|ActMiscoftoklist(* I put 'string' for Int and Float because 'int' would not be enough.
* Indeed OCaml int are 31 bits. So it's simpler to use 'string'.
* Same reason to have 'string' instead of 'int list' for the String case.
*
* note: '-2' is not a constant; it is the unary operator '-'
* applied to the constant '2'. So the string must represent a positive
* integer only.
*)andconstant=|Intof(string(* * intType*))|Floatof(string*floatType)|Charof(string*isWchar)(* normally it is equivalent to Int *)|Stringof(string*isWchar)|MultiString(* can contain MacroString *)(* c++ext: *)|BoolofboolandisWchar=IsWchar|IsCharandunaryOp=(* less: could be lift up, those are really important operators *)|GetRef|DeRef(* gccext: via &&label notation *)|GetRefLabel|UnPlus|UnMinus|Tilde|NotandassignOp=SimpleAssign|OpAssignofarithOpandfixOp=Dec|IncandbinaryOp=ArithofarithOp|LogicaloflogicalOpandarithOp=|Plus|Minus|Mul|Div|Mod|DecLeft|DecRight|And|Or|XorandlogicalOp=|Inf|Sup|InfEq|SupEq|Eq|NotEq|AndLog|OrLog(* c++ext: used elsewhere but prefer to define it close to other operators *)andptrOp=PtrStarOp|PtrOpandallocOp=NewOp|DeleteOp|NewArrayOp|DeleteArrayOpandaccessop=ParenOp|ArrayOpandoperator=|BinaryOpofbinaryOp|AssignOpofassignOp|FixOpoffixOp|PtrOpOpofptrOp|AccessOpofaccessop|AllocOpofallocOp|UnaryTildeOp|UnaryNotOp|CommaOp(* c++ext: *)andcast_operator=|Static_cast|Dynamic_cast|Const_cast|Reinterpret_castandconstExpression=expression(* => int *)(* ------------------------------------------------------------------------- *)(* Statements *)(* ------------------------------------------------------------------------- *)(* note: assignement is not a statement, it's an expression :(
* (wonderful C language).
* note: I use 'and' for type definition because gccext allows statements as
* expressions, so we need mutual recursive type definition now.
*)andstatement=statementbiswrapandstatementbis=|Compoundofcompound(* new scope *)|ExprStatementofexprStatement|Labeledoflabeled|Selectionofselection|Iterationofiteration|Jumpofjump(* c++ext: in C this constructor could be outside the statement type, in a
* decl type, because declarations are only at the beginning of a compound
* normally. But in C++ we can freely mix declarations and statements.
*)|DeclStmtofblock_declaration(* c++ext: *)|Tryoftok*compound*handlerlist(* gccext: *)|NestedFuncoffunc_definition(* cppext: *)|MacroStmt|StmtTodo(* cppext: c++ext:
* old: compound = (declaration list * statement list)
* old: (declaration, statement) either list
*)andcompound=statement_sequencablelistbraceandexprStatement=expressionoptionandlabeled=|Labelofstring*statement|Caseofexpression*statement|CaseRangeofexpression*expression*statement(* gccext: *)|Defaultofstatementandselection=|Ifoftok*expressionparen*statement*tokoption*statement(* need to check that all elements in the compound start
* with a case:, otherwise it's unreachable code.
*)|Switchoftok*expressionparen*statementanditeration=|Whileoftok*expressionparen*statement|DoWhileoftok*statement*tok*expressionparen*tok(*;*)|Foroftok*(exprStatementwrap*exprStatementwrap*exprStatementwrap)paren*statement(* cppext: *)|MacroIterationofsimple_ident*argumentcomma_listparen*statementandjump=|Gotoofstring|Continue|Break|Return|ReturnExprofexpression(* gccext: goto *exp ';' *)|GotoComputedofexpression(* c++ext: *)andhandler=tok*exception_declarationparen*compoundandexception_declaration=|ExnDeclEllipsisoftok|ExnDeclofparameter(* easier to put at statement_list level than statement level *)andstatement_sequencable=|StmtElemofstatement(* cppext: *)|CppDirectiveStmtofcpp_directive|IfdefStmtofifdef_directive(* * statement list *)(* ------------------------------------------------------------------------- *)(* Block Declaration *)(* ------------------------------------------------------------------------- *)(* a.k.a declaration_statement *)andblock_declaration=(* Before I had a Typedef constructor, but why make this special case and not
* have also StructDef, EnumDef, so that 'struct t {...} v' which would
* then generate two declarations. If you want a cleaner C AST use
* ast_c.ml.
* note: before the need for unparser, I didn't have a DeclList but just
* a Decl.
*)|DeclListofonedeclcomma_list*tok(*;*)(* cppext: todo? now factorize with MacroTop ? *)|MacroDecloftoklist*simple_ident*argumentcomma_listparen*tok(* c++ext: using namespace *)|UsingDeclof(tok*name*tok(*;*))|UsingDirectiveoftok*tok(*'namespace'*)*namespace_name*tok(*;*)|NameSpaceAliasoftok*simple_ident*tok(*=*)*namespace_name*tok(*;*)(* gccext: *)|Asmoftok*tokoption(*volatile*)*asmbodyparen*tok(*;*)(* gccext: *)andasmbody=toklist(* string list *)*colonwrap(* : *)listandcolon=Colonofcolon_optioncomma_listandcolon_option=colon_optionbiswrapandcolon_optionbis=ColonMisc|ColonExprofexpressionparen(* ------------------------------------------------------------------------- *)(* Variable definition (and also field definition) *)(* ------------------------------------------------------------------------- *)(* note: onedecl includes prototype declarations and class_declarations!
* c++ext: onedecl now covers also field definitions as fields can have
* storage in C++.
*)andonedecl={(* option cos can have empty declaration or struct tag declaration.
* kenccext: name can also be empty because of anonymous fields.
*)v_namei:(name*initoption)option;v_type:fullType;v_storage:storage;(* v_attr: attribute list; *)(* gccext: *)}andstorage=NoSto|StoTypedefoftok|StoofstorageClasswrap2andstorageClass=Auto|Static|Register|Extern(* Friend ???? Mutable? *)(*c++ext: TODO *)(* I am not sure what it means to declare a prototype inline, but gcc
* accepts it. *)and_func_specifier=Inline|Virtualandinit=|EqInitoftok(*=*)*initialiser(* c++ext: constructed object *)|ObjInitofargumentcomma_listparenandinitialiser=|InitExprofexpression|InitListofinitialisercomma_listbrace(* gccext: *)|InitDesignatorsofdesignatorlist*tok(*=*)*initialiser|InitFieldOldofsimple_ident*tok(*:*)*initialiser|InitIndexOldofexpressionbracket*initialiser(* ex: [2].y = x, or .y[2] or .y.x. They can be nested *)anddesignator=|DesignatorFieldoftok(*:*)*simple_ident|DesignatorIndexofexpressionbracket|DesignatorRangeof(expression*tok(*...*)*expression)bracket(* ------------------------------------------------------------------------- *)(* Function definition *)(* ------------------------------------------------------------------------- *)(* Normally we should define another type functionType2 because there
* are more restrictions on what can define a function than a pointer
* function. For instance a function declaration can omit the name of the
* parameter wheras a function definition can not. But, in some cases such
* as 'f(void) {', there is no name too, so I simplified and reused the
* same functionType type for both declarations and function definitions.
*)andfunc_definition={f_name:name;f_type:functionType;f_storage:storage;(* todo: gccext: inline or not:, f_inline: tok option *)f_body:compound;(*f_attr: attribute list;*)(* gccext: *)}andfunctionType={ft_ret:fullType;(* fake return type for ctor/dtor *)ft_params:parametercomma_listparen;ft_dots:(tok(*,*)*tok(*...*))option;(* c++ext: *)ft_const:tokoption;(* only for methods *)ft_throw:exn_specoption;}andparameter={p_name:simple_identoption;p_type:fullType;p_register:tokoption;(* c++ext: *)p_val:(tok(*=*)*expression)option;}andexn_spec=(tok*namecomma_list2paren)(* less: simplify? need differentiate at this level? could have
* is_ctor, is_dtor helper instead.
*)andfunc_or_else=|FunctionOrMethodoffunc_definition(* c++ext: special member function *)|Constructoroffunc_definition(* TODO explicit/inline, chain_call *)|Destructoroffunc_definitionandmethod_decl=|MethodDeclofonedecl*(tok*tok)option(* '=' '0' *)*tok(*;*)|ConstructorDeclofsimple_ident*parametercomma_listparen*tok(*;*)|DestructorDecloftok(*~*)*simple_ident*tokoptionparen*exn_specoption*tok(*;*)(* ------------------------------------------------------------------------- *)(* enum definition *)(* ------------------------------------------------------------------------- *)(* less: use a record *)andenum_definition=tok(*enum*)*simple_identoption*enum_elemcomma_listbraceandenum_elem={e_name:simple_ident;e_val:(tok(*=*)*constExpression)option;}(* ------------------------------------------------------------------------- *)(* Class definition *)(* ------------------------------------------------------------------------- *)andclass_definition={c_kind:structUnionwrap2;(* the ident can be a template_id when do template specialization. *)c_name:ident_name(*class_name??*)option;(* c++ext: *)c_inherit:(tok(* ':' *)*base_clausecomma_list)option;c_members:class_member_sequencablelistbrace(* new scope *);}andstructUnion=|Struct|Union(* c++ext: *)|Classandbase_clause={i_name:class_name;i_virtual:tokoption;i_access:access_specwrap2option;}(* used in inheritance spec (base_clause) and class_member *)andaccess_spec=Public|Private|Protected(* was called field wrap before *)andclass_member=(* could put outside and take class_member list *)|Accessofaccess_specwrap2*tok(*:*)(* before unparser, I didn't have a FieldDeclList but just a Field. *)|MemberFieldoffieldkindcomma_list*tok(*';'*)|MemberFuncoffunc_or_else|MemberDeclofmethod_decl|QualifiedIdInClassofname(* ?? *)*tok(*;*)|TemplateDeclInClassof(tok*template_parameters*declaration)|UsingDeclInClassof(tok(*using*)*name*tok(*;*))(* gccext: and maybe c++ext: *)|EmptyFieldoftok(*;*)(* At first I thought that a bitfield could be only Signed/Unsigned.
* But it seems that gcc allow char i:4. C rule must say that you
* can cast into int so enum too, ...
* c++ext: FieldDecl was before Simple of string option * fullType
* but in c++ fields can also have storage (e.g. static) so now reuse
* ondecl.
*)andfieldkind=|FieldDeclofonedecl|BitFieldofsimple_identoption*tok(*:*)*fullType*constExpression(* fullType => BitFieldInt | BitFieldUnsigned *)andclass_member_sequencable=|ClassElemofclass_member(* cppext: *)|CppDirectiveStructofcpp_directive|IfdefStructofifdef_directive(* * field list *)(* ------------------------------------------------------------------------- *)(* cppext: cpp directives, #ifdef, #define and #include body *)(* ------------------------------------------------------------------------- *)andcpp_directive=|Defineoftok(* #define*)*simple_ident*define_kind*define_val|Includeoftok(* #include s *)*inc_kind*string(* path *)|Undefofsimple_ident(* #undef xxx *)|PragmaAndCooftokanddefine_kind=|DefineVar|DefineFuncofstringwrapcomma_listparenanddefine_val=|DefineExprofexpression|DefineStmtofstatement|DefineTypeoffullType|DefineFunctionoffunc_definition|DefineInitofinitialiser(* in practice only { } with possible ',' *)(* ?? *)|DefineTextofstringwrap|DefineEmpty|DefineDoWhileZeroofstatementwrap(* do { } while(0) *)|DefinePrintWrapperoftok(* if *)*expressionparen*name|DefineTodoandinc_kind=|Local(* "" *)|Standard(* <> *)|Weird(* ex: #include SYSTEM_H *)(* less: 'a ifdefed = 'a list wrap (* ifdef elsif else endif *) *)andifdef_directive=ifdefkindwrap2andifdefkind=|Ifdef(* todo? of string? *)(* less: IfIf of formula_cpp ? *)|IfdefElse|IfdefElseif|IfdefEndif(* less:
* set in Parsing_hacks.set_ifdef_parenthize_info. It internally use
* a global so it means if you parse the same file twice you may get
* different id. I try now to avoid this pb by resetting it each
* time I parse a file.
*
* and matching_tag =
* IfdefTag of (int (* tag *) * int (* total with this tag *))
*)(* ------------------------------------------------------------------------- *)(* The toplevel elements *)(* ------------------------------------------------------------------------- *)(* it's not really 'toplevel' because the elements below can be nested
* inside namespaces or some extern. It's not really 'declaration'
* either because it can defines stuff. But I keep the C++ standard
* terminology.
*
* note that we use 'block_declaration' below, not 'statement'.
*)anddeclaration=|BlockDeclofblock_declaration(* include struct/globals/... definitions *)|Funcoffunc_or_else(* c++ext: *)|TemplateDecloftok*template_parameters*declaration|TemplateSpecializationoftok*unitangle*declaration(* the list can be empty *)|ExternCoftok*tok*declaration|ExternCListoftok*tok*declaration_sequencablelistbrace(* the list can be empty *)|NameSpaceoftok*simple_ident*declaration_sequencablelistbrace(* after have some semantic info *)|NameSpaceExtendofstring*declaration_sequencablelist|NameSpaceAnonoftok*declaration_sequencablelistbrace(* gccext: allow redundant ';' *)|EmptyDefoftok|DeclTodo(* c++ext: *)andtemplate_parameter=parameter(* todo? more? *)andtemplate_parameters=template_parametercomma_listangle(* easier to put at statement_list level than statement level *)anddeclaration_sequencable=|DeclElemofdeclaration(* cppext: *)|CppDirectiveDeclofcpp_directive|IfdefDeclofifdef_directive(* * toplevel list *)(* cppext: *)|MacroTopofsimple_ident*argumentcomma_listparen*tokoption|MacroVarTopofsimple_ident*tok(* ; *)(* could also be in decl *)|NotParsedCorrectlyoftoklistandtoplevel=declaration_sequencableandprogram=toplevellist(* ------------------------------------------------------------------------- *)(* Any *)(* ------------------------------------------------------------------------- *)andany=|Programofprogram|Topleveloftoplevel|Cppofcpp_directive|Stmtofstatement|Exprofexpression|TypeoffullType|Nameofname|BlockDecl2ofblock_declaration|ClassDefofclass_definition|FuncDefoffunc_definition|FuncOrElseoffunc_or_else|ClassMemberofclass_member|OneDeclofonedecl|Initofinitialiser|Stmtsofstatementlist|Constantofconstant|Argumentofargument|Parameterofparameter|Bodyofcompound|Infooftok|InfoListoftoklist(* with tarzan *)(*****************************************************************************)(* Some constructors *)(*****************************************************************************)letnQ={const=None;volatile=None}letnoIdInfo()={i_scope=Scope_code.NoScope;}letnoii=[]letnoQscope=[](*****************************************************************************)(* Wrappers *)(*****************************************************************************)letunwrapx=fstxletuncommaxs=List.mapfstxsletunparen(_,x,_)=xletunbrace(_,x,_)=xletunwrap_typeC(_qu,(typeC,_ii))=typeC(* When want add some info in AST that does not correspond to
* an existing C element.
* old: when don't want 'synchronize' on it in unparse_c.ml
* (now have other mark for tha matter).
* used by parsing hacks
*)letmake_expandedii=letnoVirtPos=({Parse_info.str="";charpos=0;line=0;column=0;file=""},-1)inlet(a,b)=noVirtPosin{iiwithParse_info.token=Parse_info.ExpandedTok(Parse_info.get_original_token_locationii.Parse_info.token,a,b)}(* used by parsing hacks *)letrewrap_pinfopiii={iiwithParse_info.token=pi}(* used while migrating the use of 'string' to 'name' in check_variables *)let(string_of_name_tmp:name->string)=funname->let(_opt,_qu,id)=nameinmatchidwith|IdIdent(s,_)->s|_->failwith"TODO:string_of_name_tmp"let(ii_of_id_name:name->toklist)=funname->let(_opt,_qu,id)=nameinmatchidwith|IdIdent(_s,ii)->[ii]|IdOperator(_,(_op,ii))->ii|IdConverter(_tok,_ft)->failwith"ii_of_id_name: IdConverter"|IdDestructor(tok,(_s,ii))->[tok;ii]|IdTemplateId((_s,ii),_args)->[ii]