package pfff

  1. Overview
  2. Docs
Legend:
Library
Module
Module type
Parameter
Class
Class type
type tok = Parse_info.t
and 'a wrap = 'a * tok
and 'a wrapx = 'a * tok list
and 'a paren = tok * 'a * tok
and 'a brace = tok * 'a * tok
and 'a bracket = tok * 'a * tok
and 'a angle = tok * 'a * tok
and 'a comma_list = 'a wrapx list
and 'a comma_list2 = ('a, tok) Common.either list
and sc = tok
type name = tok option * (qualifier * tok) list * ident_or_op
and ident_or_op =
  1. | IdIdent of ident
  2. | IdTemplateId of ident * template_arguments
  3. | IdDestructor of tok * ident
  4. | IdOperator of tok * operator * tok list
  5. | IdConverter of tok * type_
and ident = string wrap
and template_arguments = template_argument comma_list angle
and template_argument = (type_, expr) Common.either
and qualifier =
  1. | QClassname of ident
  2. | QTemplateId of ident * template_arguments
and class_name = name
and namespace_name = name
and typedef_name = name
and enum_name = name
and ident_name = name
and type_ = typeQualifier * typeC
and typeC =
  1. | BaseType of baseType
  2. | Pointer of tok * type_
  3. | Reference of tok * type_
  4. | Array of constExpression option bracket * type_
  5. | FunctionType of functionType
  6. | EnumName of tok * ident
  7. | StructUnionName of structUnion wrap * ident
  8. | TypeName of name
  9. | TypenameKwd of tok * name
  10. | TypeOf of tok * (type_, expr) Common.either paren
  11. | EnumDef of enum_definition
  12. | StructDef of class_definition
  13. | ParenType of type_ paren
and baseType =
  1. | Void of tok
  2. | IntType of intType * tok list
  3. | FloatType of floatType * tok list
and intType =
  1. | CChar
  2. | Si of signed
  3. | CBool
  4. | WChar_t
and signed = sign * base
and base =
  1. | CChar2
  2. | CShort
  3. | CInt
  4. | CLong
  5. | CLongLong
and sign =
  1. | Signed
  2. | UnSigned
and floatType =
  1. | CFloat
  2. | CDouble
  3. | CLongDouble
and typeQualifier = {
  1. const : tok option;
  2. volatile : tok option;
}
and expr =
  1. | Id of name * ident_info
  2. | C of constant
  3. | Call of expr * argument comma_list paren
  4. | CondExpr of expr * tok * expr option * tok * expr
  5. | Sequence of expr * tok * expr
  6. | Assign of expr * assignOp * expr
  7. | Postfix of expr * fixOp wrap
  8. | Infix of expr * fixOp wrap
  9. | Unary of expr * unaryOp wrap
  10. | Binary of expr * binaryOp wrap * expr
  11. | ArrayAccess of expr * expr bracket
  12. | RecordAccess of expr * tok * name
  13. | RecordPtAccess of expr * tok * name
  14. | RecordStarAccess of expr * tok * expr
  15. | RecordPtStarAccess of expr * tok * expr
  16. | SizeOfExpr of tok * expr
  17. | SizeOfType of tok * type_ paren
  18. | Cast of type_ paren * expr
  19. | StatementExpr of compound paren
  20. | GccConstructor of type_ paren * initialiser comma_list brace
  21. | This of tok
  22. | ConstructedObject of type_ * argument comma_list paren
  23. | TypeId of tok * (type_, expr) Common.either paren
  24. | CplusplusCast of cast_operator wrap * type_ angle * expr paren
  25. | New of tok option * tok * argument comma_list paren option * type_ * argument comma_list paren option
  26. | Delete of tok option * tok * expr
  27. | DeleteArray of tok option * tok * unit bracket * expr
  28. | Throw of tok * expr option
  29. | ParenExpr of expr paren
  30. | Ellipses of tok
  31. | ExprTodo of tok
and ident_info = {
  1. mutable i_scope : Scope_code.t;
}
and argument =
  1. | Arg of expr
  2. | ArgType of type_
  3. | ArgAction of action_macro
and action_macro =
  1. | ActMisc of tok list
and constant =
  1. | Int of string wrap
  2. | Float of string wrap * floatType
  3. | Char of string wrap * isWchar
  4. | String of string wrap * isWchar
  5. | MultiString of string wrap list
  6. | Bool of bool wrap
and isWchar =
  1. | IsWchar
  2. | IsChar
and unaryOp =
  1. | UnPlus
  2. | UnMinus
  3. | Tilde
  4. | Not
  5. | GetRef
  6. | DeRef
  7. | GetRefLabel
and assignOp =
  1. | SimpleAssign of tok
  2. | OpAssign of arithOp wrap
and fixOp =
  1. | Dec
  2. | Inc
and binaryOp =
  1. | Arith of arithOp
  2. | Logical of logicalOp
and arithOp =
  1. | Plus
  2. | Minus
  3. | Mul
  4. | Div
  5. | Mod
  6. | DecLeft
  7. | DecRight
  8. | And
  9. | Or
  10. | Xor
and logicalOp =
  1. | Inf
  2. | Sup
  3. | InfEq
  4. | SupEq
  5. | Eq
  6. | NotEq
  7. | AndLog
  8. | OrLog
and ptrOp =
  1. | PtrStarOp
  2. | PtrOp
and allocOp =
  1. | NewOp
  2. | DeleteOp
  3. | NewArrayOp
  4. | DeleteArrayOp
and accessop =
  1. | ParenOp
  2. | ArrayOp
and operator =
  1. | BinaryOp of binaryOp
  2. | AssignOp of assignOp
  3. | FixOp of fixOp
  4. | PtrOpOp of ptrOp
  5. | AccessOp of accessop
  6. | AllocOp of allocOp
  7. | UnaryTildeOp
  8. | UnaryNotOp
  9. | CommaOp
and cast_operator =
  1. | Static_cast
  2. | Dynamic_cast
  3. | Const_cast
  4. | Reinterpret_cast
and constExpression = expr
and stmt =
  1. | Compound of compound
  2. | ExprStatement of expr option * sc
  3. | If of tok * expr paren * stmt * (tok * stmt) option
  4. | Switch of tok * expr paren * stmt
  5. | While of tok * expr paren * stmt
  6. | DoWhile of tok * stmt * tok * expr paren * sc
  7. | For of tok * (expr option * sc * expr option * sc * expr option) paren * stmt
  8. | MacroIteration of ident * argument comma_list paren * stmt
  9. | Jump of jump * sc
  10. | Label of string wrap * tok * stmt
  11. | Case of tok * expr * tok * stmt
  12. | CaseRange of tok * expr * tok * expr * tok * stmt
  13. | Default of tok * tok * stmt
  14. | DeclStmt of block_declaration
  15. | Try of tok * compound * handler list
  16. | NestedFunc of func_definition
  17. | MacroStmt of tok
  18. | StmtTodo of tok
and compound = stmt_sequencable list brace
and jump =
  1. | Goto of tok * string wrap
  2. | Continue of tok
  3. | Break of tok
  4. | Return of tok * expr option
  5. | GotoComputed of tok * tok * expr
and exception_declaration =
  1. | ExnDeclEllipsis of tok
  2. | ExnDecl of parameter
and stmt_sequencable =
  1. | StmtElem of stmt
  2. | CppDirectiveStmt of cpp_directive
  3. | IfdefStmt of ifdef_directive
and block_declaration =
  1. | DeclList of onedecl comma_list * sc
  2. | MacroDecl of tok list * ident * argument comma_list paren * tok
  3. | UsingDecl of tok * name * sc
  4. | UsingDirective of tok * tok * namespace_name * sc
  5. | NameSpaceAlias of tok * ident * tok * namespace_name * sc
  6. | Asm of tok * tok option * asmbody paren * sc
and asmbody = string wrap list * colon list
and colon =
  1. | Colon of tok * colon_option comma_list
and colon_option =
  1. | ColonExpr of tok list * expr paren
  2. | ColonMisc of tok list
and onedecl = {
  1. v_namei : (name * init option) option;
  2. v_type : type_;
  3. v_storage : storage;
}
and storage =
  1. | NoSto
  2. | StoTypedef of tok
  3. | Sto of storageClass wrap
and storageClass =
  1. | Auto
  2. | Static
  3. | Register
  4. | Extern
and _func_specifier =
  1. | Inline
  2. | Virtual
and init =
  1. | EqInit of tok * initialiser
  2. | ObjInit of argument comma_list paren
and initialiser =
  1. | InitExpr of expr
  2. | InitList of initialiser comma_list brace
  3. | InitDesignators of designator list * tok * initialiser
  4. | InitFieldOld of ident * tok * initialiser
  5. | InitIndexOld of expr bracket * initialiser
and designator =
  1. | DesignatorField of tok * ident
  2. | DesignatorIndex of expr bracket
  3. | DesignatorRange of (expr * tok * expr) bracket
and func_definition = {
  1. f_name : name;
  2. f_type : functionType;
  3. f_storage : storage;
  4. f_body : compound;
}
and functionType = {
  1. ft_ret : type_;
  2. ft_params : parameter comma_list paren;
  3. ft_dots : (tok * tok) option;
  4. ft_const : tok option;
  5. ft_throw : exn_spec option;
}
and parameter = {
  1. p_name : ident option;
  2. p_type : type_;
  3. p_register : tok option;
  4. p_val : (tok * expr) option;
}
and exn_spec = tok * name comma_list2 paren
and func_or_else =
  1. | FunctionOrMethod of func_definition
  2. | Constructor of func_definition
  3. | Destructor of func_definition
and method_decl =
  1. | MethodDecl of onedecl * (tok * tok) option * sc
  2. | ConstructorDecl of ident * parameter comma_list paren * sc
  3. | DestructorDecl of tok * ident * tok option paren * exn_spec option * sc
and enum_definition = tok * ident option * enum_elem comma_list brace
and enum_elem = {
  1. e_name : ident;
  2. e_val : (tok * constExpression) option;
}
and class_definition = {
  1. c_kind : structUnion wrap;
  2. c_name : ident_name option;
  3. c_inherit : (tok * base_clause comma_list) option;
  4. c_members : class_member_sequencable list brace;
}
and structUnion =
  1. | Struct
  2. | Union
  3. | Class
and base_clause = {
  1. i_name : class_name;
  2. i_virtual : tok option;
  3. i_access : access_spec wrap option;
}
and access_spec =
  1. | Public
  2. | Private
  3. | Protected
and class_member =
  1. | Access of access_spec wrap * tok
  2. | MemberField of fieldkind comma_list * sc
  3. | MemberFunc of func_or_else
  4. | MemberDecl of method_decl
  5. | QualifiedIdInClass of name * sc
  6. | TemplateDeclInClass of tok * template_parameters * declaration
  7. | UsingDeclInClass of tok * name * sc
  8. | EmptyField of sc
and fieldkind =
  1. | FieldDecl of onedecl
  2. | BitField of ident option * tok * type_ * constExpression
and class_member_sequencable =
  1. | ClassElem of class_member
  2. | CppDirectiveStruct of cpp_directive
  3. | IfdefStruct of ifdef_directive
and cpp_directive =
  1. | Define of tok * ident * define_kind * define_val
  2. | Include of tok * inc_kind * string
  3. | Undef of ident
  4. | PragmaAndCo of tok
and define_kind =
  1. | DefineVar
  2. | DefineFunc of string wrap comma_list paren
and define_val =
  1. | DefineExpr of expr
  2. | DefineStmt of stmt
  3. | DefineType of type_
  4. | DefineFunction of func_definition
  5. | DefineInit of initialiser
  6. | DefineEmpty
  7. | DefineDoWhileZero of tok * stmt * tok * tok paren
  8. | DefinePrintWrapper of tok * expr paren * name
  9. | DefineTodo
and inc_kind =
  1. | Local
  2. | Standard
  3. | Weird
and ifdef_directive = ifdefkind wrap
and ifdefkind =
  1. | Ifdef
  2. | IfdefElse
  3. | IfdefElseif
  4. | IfdefEndif
and declaration =
  1. | BlockDecl of block_declaration
  2. | Func of func_or_else
  3. | TemplateDecl of tok * template_parameters * declaration
  4. | TemplateSpecialization of tok * unit angle * declaration
  5. | ExternC of tok * tok * declaration
  6. | ExternCList of tok * tok * declaration_sequencable list brace
  7. | NameSpace of tok * ident * declaration_sequencable list brace
  8. | NameSpaceExtend of string * declaration_sequencable list
  9. | NameSpaceAnon of tok * declaration_sequencable list brace
  10. | EmptyDef of sc
  11. | DeclTodo
and template_parameter = parameter
and template_parameters = template_parameter comma_list angle
and declaration_sequencable =
  1. | DeclElem of declaration
  2. | CppDirectiveDecl of cpp_directive
  3. | IfdefDecl of ifdef_directive
  4. | MacroTop of ident * argument comma_list paren * tok option
  5. | MacroVarTop of ident * sc
  6. | NotParsedCorrectly of tok list
and program = toplevel list
and any =
  1. | Program of program
  2. | Toplevel of toplevel
  3. | Cpp of cpp_directive
  4. | Stmt of stmt
  5. | Expr of expr
  6. | Type of type_
  7. | Name of name
  8. | BlockDecl2 of block_declaration
  9. | ClassDef of class_definition
  10. | FuncDef of func_definition
  11. | FuncOrElse of func_or_else
  12. | ClassMember of class_member
  13. | OneDecl of onedecl
  14. | Init of initialiser
  15. | Stmts of stmt list
  16. | Constant of constant
  17. | Argument of argument
  18. | Parameter of parameter
  19. | Body of compound
  20. | Info of tok
  21. | InfoList of tok list
val nQ : typeQualifier
val noIdInfo : unit -> ident_info
val noQscope : 'a list
val unwrap : ('a * 'b) -> 'a
val uncomma : ('a * 'b) list -> 'a list
val unparen : ('a * 'b * 'c) -> 'b
val unbrace : ('a * 'b * 'c) -> 'b
val unwrap_typeC : ('a * 'b) -> 'b
val string_of_name_tmp : name -> string
val ii_of_id_name : name -> tok list