Module Clang.Ast

The module includes Clang__ast which contains the declaration of the abstract syntax tree. Since the abstract syntax tree is a pure type declaration without value definition, the declaration is written in a separate module, written in an implementation file (.ml) without interface file (.mli)).

include module type of sig ... end
type elaborated_type_keyword = Clang__bindings.clang_ext_elaboratedtypekeyword
type character_kind = Clang__bindings.clang_ext_characterkind
type unary_expr_kind = Clang__bindings.clang_ext_unaryexpr
type unary_operator_kind = Clang__bindings.clang_ext_unaryoperatorkind
type binary_operator_kind = Clang__bindings.clang_ext_binaryoperatorkind
type builtin_type = Clang__bindings.cxtypekind
val equal_elaborated_type_keyword : elaborated_type_keyword -> elaborated_type_keyword -> Ppx_deriving_runtime.bool
val equal_character_kind : character_kind -> character_kind -> Ppx_deriving_runtime.bool
val equal_unary_expr_kind : unary_expr_kind -> unary_expr_kind -> Ppx_deriving_runtime.bool
val equal_unary_operator_kind : unary_operator_kind -> unary_operator_kind -> Ppx_deriving_runtime.bool
val equal_binary_operator_kind : binary_operator_kind -> binary_operator_kind -> Ppx_deriving_runtime.bool
val equal_builtin_type : builtin_type -> builtin_type -> Ppx_deriving_runtime.bool
val compare_elaborated_type_keyword : elaborated_type_keyword -> elaborated_type_keyword -> Ppx_deriving_runtime.int
val compare_character_kind : character_kind -> character_kind -> Ppx_deriving_runtime.int
val compare_unary_expr_kind : unary_expr_kind -> unary_expr_kind -> Ppx_deriving_runtime.int
val compare_unary_operator_kind : unary_operator_kind -> unary_operator_kind -> Ppx_deriving_runtime.int
val compare_binary_operator_kind : binary_operator_kind -> binary_operator_kind -> Ppx_deriving_runtime.int
val compare_builtin_type : builtin_type -> builtin_type -> Ppx_deriving_runtime.int
val pp_elaborated_type_keyword : Format.formatter -> elaborated_type_keyword -> Ppx_deriving_runtime.unit
val show_elaborated_type_keyword : elaborated_type_keyword -> Ppx_deriving_runtime.string
val pp_character_kind : Format.formatter -> character_kind -> Ppx_deriving_runtime.unit
val show_character_kind : character_kind -> Ppx_deriving_runtime.string
val pp_unary_expr_kind : Format.formatter -> unary_expr_kind -> Ppx_deriving_runtime.unit
val show_unary_expr_kind : unary_expr_kind -> Ppx_deriving_runtime.string
val pp_unary_operator_kind : Format.formatter -> unary_operator_kind -> Ppx_deriving_runtime.unit
val show_unary_operator_kind : unary_operator_kind -> Ppx_deriving_runtime.string
val pp_binary_operator_kind : Format.formatter -> binary_operator_kind -> Ppx_deriving_runtime.unit
val show_binary_operator_kind : binary_operator_kind -> Ppx_deriving_runtime.string
val pp_builtin_type : Format.formatter -> builtin_type -> Ppx_deriving_runtime.unit
val show_builtin_type : builtin_type -> Ppx_deriving_runtime.string
type concrete_location = Clang__ast.concrete_location = {
filename : string;
line : int;
column : int;
}
type source_location = Clang__ast.source_location =
| Clang of Clang__bindings.cxsourcelocation
| Concrete of concrete_location
type integer_literal = Clang__ast.integer_literal =
| Int of int
| CXInt of Clang__bindings.cxint
val equal_integer_literal : integer_literal -> integer_literal -> Ppx_deriving_runtime.bool
val compare_integer_literal : integer_literal -> integer_literal -> Ppx_deriving_runtime.int
type floating_literal = Clang__ast.floating_literal =
| Float of float
| CXFloat of Clang__bindings.cxfloat
val equal_floating_literal : floating_literal -> floating_literal -> Ppx_deriving_runtime.bool
val compare_floating_literal : floating_literal -> floating_literal -> Ppx_deriving_runtime.int
type 'qual_type open_decoration = 'qual_type Clang__ast.open_decoration =
| Cursor of Clang__bindings.cxcursor
| Custom of {
location : source_location option;
qual_type : 'qual_type option;
}
type ('a, 'qual_type) open_node = ('a'qual_type) Clang__ast.open_node = {
decoration : 'qual_type open_decoration;
desc : 'a;
}
val equal_open_node : ('a -> 'a -> Ppx_deriving_runtime.bool) -> ('qual_type -> 'qual_type -> Ppx_deriving_runtime.bool) -> ('a'qual_type) open_node -> ('a'qual_type) open_node -> Ppx_deriving_runtime.bool
val compare_open_node : ('a -> 'a -> Ppx_deriving_runtime.int) -> ('qual_type -> 'qual_type -> Ppx_deriving_runtime.int) -> ('a'qual_type) open_node -> ('a'qual_type) open_node -> Ppx_deriving_runtime.int
val pp_open_node : (Format.formatter -> 'a -> Ppx_deriving_runtime.unit) -> (Format.formatter -> 'qual_type -> Ppx_deriving_runtime.unit) -> Format.formatter -> ('a'qual_type) open_node -> Ppx_deriving_runtime.unit
val show_open_node : (Format.formatter -> 'a -> Ppx_deriving_runtime.unit) -> (Format.formatter -> 'qual_type -> Ppx_deriving_runtime.unit) -> ('a'qual_type) open_node -> Ppx_deriving_runtime.string
class 'selfbase_iter : object ... end
class 'selfbase_map : object ... end
class virtual 'bbase_reduce : object ... end
class virtual 'cbase_mapreduce : object ... end
type qual_type = Clang__ast.qual_type = {
cxtype : Clang__bindings.cxtype;
const : bool;
volatile : bool;
restrict : bool;
desc : type_desc;
}
type type_desc = Clang__ast.type_desc =
| Pointer of qual_type
| ConstantArray of {
element : qual_type;
size : int;
}
| IncompleteArray of qual_type
| VariableArray of {
element : qual_type;
size : expr;
}
| Elaborated of {
keyword : elaborated_type_keyword;
named_type : qual_type;
}
| Enum of string
| FunctionType of function_type
| Record of string
| Typedef of string
| Complex of qual_type
| ParenType of qual_type
| BuiltinType of builtin_type
type function_type = Clang__ast.function_type = {
calling_conv : Clang__bindings.cxcallingconv;
result : qual_type;
args : args option;
}
type args = Clang__ast.args = {
non_variadic : (string * qual_type) list;
variadic : bool;
}
type stmt = (stmt_descqual_type) open_node
type stmt_desc = Clang__ast.stmt_desc =
| Null
| Compound of stmt list
| For of {
init : stmt option;
condition_variable : var_decl option;
cond : expr option;
inc : stmt option;
body : stmt;
}
| If of {
init : stmt option;
condition_variable : var_decl option;
cond : expr;
then_branch : stmt;
else_branch : stmt option;
}
| Switch of {
init : stmt option;
condition_variable : var_decl option;
cond : expr;
body : stmt;
}
| Case of {
lhs : expr;
rhs : expr option;
body : stmt;
}
| Default of stmt
| While of {
condition_variable : var_decl option;
cond : expr;
body : stmt;
}
| Do of {
body : stmt;
cond : expr;
}
| Label of {
label : label_ref;
body : stmt;
}
| Goto of label_ref
| IndirectGoto of expr
| Continue
| Break
| GCCAsm of string * (string, qual_type) open_node list
| MSAsm of string
| Return of expr option
| Decl of decl list
| Expr of expr
| OtherStmt
type expr = (expr_descqual_type) open_node
type expr_desc = Clang__ast.expr_desc =
| IntegerLiteral of integer_literal
| FloatingLiteral of floating_literal
| StringLiteral of string
| CharacterLiteral of {
kind : character_kind;
value : int;
}
| ImaginaryLiteral of expr
| UnaryOperator of {
kind : unary_operator_kind;
operand : expr;
}
| BinaryOperator of {
lhs : expr;
kind : binary_operator_kind;
rhs : expr;
}
| DeclRef of string
| Call of {
callee : expr;
args : expr list;
}
| Cast of {
kind : cast_kind;
qual_type : qual_type;
operand : expr;
}
| Member of {
base : expr;
arrow : bool;
field : (string, qual_type) open_node;
}
| ArraySubscript of {
base : expr;
index : expr;
}
| ConditionalOperator of {
cond : expr;
then_branch : expr option;
else_branch : expr;
}
| Paren of expr
| AddrLabel of string
| InitList of expr list
| CompoundLiteral of {
qual_type : qual_type;
init : expr;
}
| UnaryExpr of {
kind : unary_expr_kind;
argument : unary_expr_or_type_trait;
}
| UnexposedExpr of {
s : string;
}
| OtherExpr
type cast_kind = Clang__ast.cast_kind =
| CStyle
| Implicit
type unary_expr_or_type_trait = Clang__ast.unary_expr_or_type_trait =
| ArgumentExpr of expr
| ArgumentType of qual_type
type decl = (decl_descqual_type) open_node
type decl_desc = Clang__ast.decl_desc =
| Function of {
linkage : Clang__bindings.cxlinkagekind;
function_type : function_type;
name : string;
body : stmt option;
}
| Var of var_decl_desc
| EnumDecl of {
name : string;
constants : enum_constant list;
}
| RecordDecl of {
keyword : elaborated_type_keyword;
name : string;
fields : decl list;
}
| TypedefDecl of {
name : string;
underlying_type : qual_type;
}
| Field of {
name : string;
qual_type : qual_type;
bitwidth : expr option;
}
| OtherDecl
type label_ref = string
type enum_constant = (enum_constant_descqual_type) open_node
type enum_constant_desc = Clang__ast.enum_constant_desc = {
name : string;
init : expr option;
}
type var_decl = (var_decl_descqual_type) open_node
type var_decl_desc = Clang__ast.var_decl_desc = {
linkage : Clang__bindings.cxlinkagekind;
name : string;
qual_type : qual_type;
init : expr option;
}
type translation_unit = (translation_unit_descqual_type) open_node
type translation_unit_desc = Clang__ast.translation_unit_desc = {
filename : string;
items : decl list;
}
val pp_qual_type : Format.formatter -> qual_type -> Ppx_deriving_runtime.unit
val show_qual_type : qual_type -> Ppx_deriving_runtime.string
val pp_type_desc : Format.formatter -> type_desc -> Ppx_deriving_runtime.unit
val show_type_desc : type_desc -> Ppx_deriving_runtime.string
val pp_function_type : Format.formatter -> function_type -> Ppx_deriving_runtime.unit
val show_function_type : function_type -> Ppx_deriving_runtime.string
val pp_args : Format.formatter -> args -> Ppx_deriving_runtime.unit
val show_args : args -> Ppx_deriving_runtime.string
val pp_stmt : Format.formatter -> stmt -> Ppx_deriving_runtime.unit
val show_stmt : stmt -> Ppx_deriving_runtime.string
val pp_stmt_desc : Format.formatter -> stmt_desc -> Ppx_deriving_runtime.unit
val show_stmt_desc : stmt_desc -> Ppx_deriving_runtime.string
val pp_expr : Format.formatter -> expr -> Ppx_deriving_runtime.unit
val show_expr : expr -> Ppx_deriving_runtime.string
val pp_expr_desc : Format.formatter -> expr_desc -> Ppx_deriving_runtime.unit
val show_expr_desc : expr_desc -> Ppx_deriving_runtime.string
val pp_cast_kind : Format.formatter -> cast_kind -> Ppx_deriving_runtime.unit
val show_cast_kind : cast_kind -> Ppx_deriving_runtime.string
val pp_unary_expr_or_type_trait : Format.formatter -> unary_expr_or_type_trait -> Ppx_deriving_runtime.unit
val show_unary_expr_or_type_trait : unary_expr_or_type_trait -> Ppx_deriving_runtime.string
val pp_decl : Format.formatter -> decl -> Ppx_deriving_runtime.unit
val show_decl : decl -> Ppx_deriving_runtime.string
val pp_decl_desc : Format.formatter -> decl_desc -> Ppx_deriving_runtime.unit
val show_decl_desc : decl_desc -> Ppx_deriving_runtime.string
val pp_label_ref : Format.formatter -> label_ref -> Ppx_deriving_runtime.unit
val show_label_ref : label_ref -> Ppx_deriving_runtime.string
val pp_enum_constant : Format.formatter -> enum_constant -> Ppx_deriving_runtime.unit
val show_enum_constant : enum_constant -> Ppx_deriving_runtime.string
val pp_enum_constant_desc : Format.formatter -> enum_constant_desc -> Ppx_deriving_runtime.unit
val show_enum_constant_desc : enum_constant_desc -> Ppx_deriving_runtime.string
val pp_var_decl : Format.formatter -> var_decl -> Ppx_deriving_runtime.unit
val show_var_decl : var_decl -> Ppx_deriving_runtime.string
val pp_var_decl_desc : Format.formatter -> var_decl_desc -> Ppx_deriving_runtime.unit
val show_var_decl_desc : var_decl_desc -> Ppx_deriving_runtime.string
val pp_translation_unit : Format.formatter -> translation_unit -> Ppx_deriving_runtime.unit
val show_translation_unit : translation_unit -> Ppx_deriving_runtime.string
val pp_translation_unit_desc : Format.formatter -> translation_unit_desc -> Ppx_deriving_runtime.unit
val show_translation_unit_desc : translation_unit_desc -> Ppx_deriving_runtime.string
val equal_qual_type : qual_type -> qual_type -> Ppx_deriving_runtime.bool
val equal_type_desc : type_desc -> type_desc -> Ppx_deriving_runtime.bool
val equal_function_type : function_type -> function_type -> Ppx_deriving_runtime.bool
val equal_args : args -> args -> Ppx_deriving_runtime.bool
val equal_stmt : stmt -> stmt -> Ppx_deriving_runtime.bool
val equal_stmt_desc : stmt_desc -> stmt_desc -> Ppx_deriving_runtime.bool
val equal_expr : expr -> expr -> Ppx_deriving_runtime.bool
val equal_expr_desc : expr_desc -> expr_desc -> Ppx_deriving_runtime.bool
val equal_cast_kind : cast_kind -> cast_kind -> Ppx_deriving_runtime.bool
val equal_unary_expr_or_type_trait : unary_expr_or_type_trait -> unary_expr_or_type_trait -> Ppx_deriving_runtime.bool
val equal_decl : decl -> decl -> Ppx_deriving_runtime.bool
val equal_decl_desc : decl_desc -> decl_desc -> Ppx_deriving_runtime.bool
val equal_label_ref : label_ref -> label_ref -> Ppx_deriving_runtime.bool
val equal_enum_constant : enum_constant -> enum_constant -> Ppx_deriving_runtime.bool
val equal_enum_constant_desc : enum_constant_desc -> enum_constant_desc -> Ppx_deriving_runtime.bool
val equal_var_decl : var_decl -> var_decl -> Ppx_deriving_runtime.bool
val equal_var_decl_desc : var_decl_desc -> var_decl_desc -> Ppx_deriving_runtime.bool
val equal_translation_unit : translation_unit -> translation_unit -> Ppx_deriving_runtime.bool
val equal_translation_unit_desc : translation_unit_desc -> translation_unit_desc -> Ppx_deriving_runtime.bool
val compare_qual_type : qual_type -> qual_type -> Ppx_deriving_runtime.int
val compare_type_desc : type_desc -> type_desc -> Ppx_deriving_runtime.int
val compare_function_type : function_type -> function_type -> Ppx_deriving_runtime.int
val compare_args : args -> args -> Ppx_deriving_runtime.int
val compare_stmt : stmt -> stmt -> Ppx_deriving_runtime.int
val compare_stmt_desc : stmt_desc -> stmt_desc -> Ppx_deriving_runtime.int
val compare_expr : expr -> expr -> Ppx_deriving_runtime.int
val compare_expr_desc : expr_desc -> expr_desc -> Ppx_deriving_runtime.int
val compare_cast_kind : cast_kind -> cast_kind -> Ppx_deriving_runtime.int
val compare_unary_expr_or_type_trait : unary_expr_or_type_trait -> unary_expr_or_type_trait -> Ppx_deriving_runtime.int
val compare_decl : decl -> decl -> Ppx_deriving_runtime.int
val compare_decl_desc : decl_desc -> decl_desc -> Ppx_deriving_runtime.int
val compare_label_ref : label_ref -> label_ref -> Ppx_deriving_runtime.int
val compare_enum_constant : enum_constant -> enum_constant -> Ppx_deriving_runtime.int
val compare_enum_constant_desc : enum_constant_desc -> enum_constant_desc -> Ppx_deriving_runtime.int
val compare_var_decl : var_decl -> var_decl -> Ppx_deriving_runtime.int
val compare_var_decl_desc : var_decl_desc -> var_decl_desc -> Ppx_deriving_runtime.int
val compare_translation_unit : translation_unit -> translation_unit -> Ppx_deriving_runtime.int
val compare_translation_unit_desc : translation_unit_desc -> translation_unit_desc -> Ppx_deriving_runtime.int
class virtual 'biter : object ... end
class virtual 'cmap : object ... end
class virtual 'breduce : object ... end
class virtual 'cmapreduce : object ... end
type decoration = qual_type open_decoration
type 'a node = ('aqual_type) open_node
module Options : sig ... end

Options.t stores flags that change the construction of the abstract syntax tree. Beware that the nodes that are ignored by default can differ from one version of Clang to the other.

val parse_file : ?⁠index:cxindex -> ?⁠command_line_args:string list -> ?⁠unsaved_files:cxunsavedfile list -> ?⁠clang_options:Cxtranslationunit_flags.t -> ?⁠options:Options.t -> string -> translation_unit

parse_file ?index ?command_line_args ?unsaved_files ?clang_options ?options filename parses file filename and returns its translation unit. This function is equivalent to Clang.parse_file (where options becomes clang_options), but returns the high-level representation of the translation unit (as obtained by of_cxtranslationunit).

val parse_file_res : ?⁠index:cxindex -> ?⁠command_line_args:string list -> ?⁠unsaved_files:cxunsavedfile list -> ?⁠clang_options:Cxtranslationunit_flags.t -> ?⁠options:Options.t -> string -> (translation_unitcxerrorcode) Stdcompat.result

Equivalent to parse_file but returns a result instead of raising Failure _ if parsing fails.

val parse_string : ?⁠index:cxindex -> ?⁠filename:string -> ?⁠command_line_args:string list -> ?⁠unsaved_files:cxunsavedfile list -> ?⁠clang_options:Cxtranslationunit_flags.t -> ?⁠options:Options.t -> string -> translation_unit

parse_string ?index ?filename ?command_line_args ?unsaved_files ?clang_options ?options contents parses string contents and returns its translation unit. This function is equivalent to Clang.parse_string (where options becomes clang_options), but returns the high-level representation of the translation unit (as obtained by of_cxtranslationunit).

val parse_string_res : ?⁠index:cxindex -> ?⁠filename:string -> ?⁠command_line_args:string list -> ?⁠unsaved_files:cxunsavedfile list -> ?⁠clang_options:Cxtranslationunit_flags.t -> ?⁠options:Options.t -> string -> (translation_unitcxerrorcode) Stdcompat.result

Equivalent to parse_string_res but returns a result instead of raising Failure _ if parsing fails.

val of_cxtranslationunit : ?⁠options:Options.t -> cxtranslationunit -> translation_unit

of_cxtranslationunit ?options tu translates tu into its high-level representation.

val node : ?⁠decoration:decoration -> ?⁠cursor:cxcursor -> ?⁠location:source_location -> ?⁠qual_type:qual_type -> 'a -> 'a node

node ?decoration desc returns a node with the given desc value and decoration. decoration can be given by one of the three following forms: (1) a value for ?decoration, or (2) a value for ?cursor, or (3) by either a value for location, or a value for qual_type, or both. These three forms cannot be mixed, otherwise Invalid_arg _ is raised.

val cursor_of_decoration : decoration -> cxcursor

cursor_of_decoration decoration returns the cursor associated to decoration if any, or the null cursor otherwise (as returned by get_null_cursor).

val cursor_of_node : 'a node -> cxcursor

cursor_of_node node is equivalent to cursor_of_decoration node.decoration.

val location_of_decoration : decoration -> source_location

location_of_decoration decoration returns the location associated to decoration if any, or the location of the null cursor otherwise (as returned by get_null_cursor).

val location_of_node : 'a node -> source_location

location_of_node node is equivalent to location_of_decoration node.decoration.

val get_presumed_location : source_location -> concrete_location

get_presumed_location location returns the concrete location associated to location. If location is libclang's, then this function calls Clang.get_presumed_location (which honors # line directive).

val get_expansion_location : source_location -> concrete_location

get_expansion_location location returns the concrete location associated to location. If location is libclang's, then this function calls Clang.get_expansion_location (which ignores # line directive).

val string_of_elaborated_type_keyword : elaborated_type_keyword -> string

Alias for ext_elaborated_type_get_keyword_spelling: returns the keyword as a string, "struct", "union", "enum", ...

val string_of_unary_operator_kind : unary_operator_kind -> string

Alias for ext_unary_operator_get_opcode_spelling: returns the operator as a string, "++", "+", "&", ...

val string_of_binary_operator_kind : binary_operator_kind -> string

Alias for ext_binary_operator_get_opcode_spelling: returns the operator as a string, "+", "=", "<<", ...

val literal_of_int : int -> integer_literal

literal_of_int i returns the integer literal i.

val int64_of_literal_opt : integer_literal -> Stdcompat.Int64.t option

int64_of_literal_opt x returns Some i if x is representable as a 64-bit integer value i, or None otherwise.

val int64_of_literal : integer_literal -> Stdcompat.Int64.t

int64_of_literal x returns i if x is representable as a 64-bit integer value i, or raises Failure _ otherwise.

val int_of_literal_opt : integer_literal -> int option

int_of_literal_opt x returns Some i if x is representable as an integer value i, or None otherwise.

val int_of_literal : integer_literal -> int

int_of_literal x returns i if x is representable as an integer value i, or raises Failure _ otherwise.

val string_of_integer_literal : integer_literal -> string

string_of_integer_literal f is an alias for Clang__bindings.ext_int_to_string, radix 10 and signed.

val literal_of_float : float -> floating_literal

literal_of_float f returns the floating literal f.

val float_of_literal : floating_literal -> float

float_of_cxfloat f is an alias for Clang__bindings.ext_float_convert_to_double.

val string_of_floating_literal : floating_literal -> string

string_of_float_literal f is an alias for Clang__bindings.ext_float_to_string.