package solidity-common

  1. Overview
  2. Docs

Generic identifiers

type program = {
  1. program_modules : module_ list;
  2. program_modules_by_id : module_ Solidity_common.IdentMap.t;
  3. program_modules_by_file : module_ Solidity_common.StringMap.t;
}

The program definition. Modules (files) are sorted in different ways, but they all are the same.

and module_ = {
  1. module_file : string;
  2. module_id : Solidity_common.Ident.t;
  3. module_units : module_units;
}

A file definition

and module_units = source_unit Solidity_common.node list
and source_unit =
  1. | Pragma of Solidity_common.Ident.t * string
    (*

    Options for the official solidity compiler

    *)
  2. | Import of import_directive
    (*

    Import directive

    *)
  3. | GlobalTypeDefinition of type_definition
    (*

    Definition of a type for the whole file

    *)
  4. | GlobalFunctionDefinition of function_definition
    (*

    Definition of a function for the whole file

    *)
  5. | GlobalVariableDefinition of state_variable_definition
    (*

    Definition of a variable for the whole file

    *)
  6. | ContractDefinition of contract_definition
    (*

    Definition of a contract

    *)

The different kind of contents.

and import_directive = {
  1. import_from : string;
  2. import_symbols : import_symbols;
}
and import_symbols =
  1. | ImportAll of ident option
  2. | ImportIdents of (ident * ident option) list
and contract_definition = {
  1. contract_name : ident;
  2. contract_kind : contract_kind;
  3. contract_abstract : bool;
  4. contract_inheritance : inheritance_specifier list;
  5. contract_parts : contract_part Solidity_common.node list;
}
and inheritance_specifier = longident * expression list
and contract_part =
  1. | TypeDefinition of type_definition
    (*

    Definition of a local type ; can be an enum or a struct

    *)
  2. | StateVariableDeclaration of state_variable_definition
    (*

    Declaration/definition of a state variable

    *)
  3. | FunctionDefinition of function_definition
    (*

    Declaration/definition of a state variable

    *)
  4. | ModifierDefinition of modifier_definition
    (*

    Definition of a modifier

    *)
  5. | EventDefinition of event_definition
    (*

    Definition of an event

    *)
  6. | UsingForDeclaration of longident * type_ option

Components of a contract

and type_definition =
  1. | EnumDefinition of enum_definition
  2. | StructDefinition of struct_definition
and enum_definition = ident * ident list
and struct_definition = ident * field_definition list
and field_definition = type_ * ident
and state_variable_definition = {
  1. var_name : ident;
  2. var_type : type_;
  3. var_visibility : visibility;
  4. var_mutability : var_mutability;
  5. var_override : longident list option;
  6. var_init : expression option;
}

Definition of a state variable. Its initializer is optional, in which case it is only a declaration.

and function_definition = {
  1. fun_name : ident;
  2. fun_params : param list;
  3. fun_returns : return list;
  4. fun_modifiers : (longident * expression list option) list;
  5. fun_visibility : visibility;
  6. fun_mutability : fun_mutability;
  7. fun_override : longident list option;
  8. fun_virtual : bool;
  9. fun_body : block option;
}

Definition of a contract function. Its body is optional, in which case it is only a declaration.

and modifier_definition = {
  1. mod_name : ident;
  2. mod_params : param list;
  3. mod_override : longident list option;
  4. mod_virtual : bool;
  5. mod_body : block option;
}

Definition of a modifier. Its body is optional, in which case it is only a declaration.

and event_definition = {
  1. event_name : ident;
  2. event_params : (type_ * bool * ident option) list;
  3. event_anonymous : bool;
}

Definition of an event.

and param = type_ * storage_location option * ident option
and return = type_ * storage_location option * ident option
and type_ =
  1. | ElementaryType of elementary_type
    (*

    A builtin elementary type

    *)
  2. | Array of type_ * expression option
    (*

    Array types

    *)
  3. | Mapping of type_ * type_
    (*

    Type of mappings with types (key, element)

    *)
  4. | FunctionType of function_type
    (*

    Type of functions

    *)
  5. | UserDefinedType of longident
    (*

    User defined type (see type_definition)

    *)

Type identifiers

and elementary_type =
  1. | TypeBool
  2. | TypeInt of int
  3. | TypeUint of int
  4. | TypeFixed of int * int
  5. | TypeUfixed of int * int
  6. | TypeAddress of bool
    (*

    bool => payable

    *)
  7. | TypeBytes of int option
    (*

    None => equivalent to byte arrays

    *)
  8. | TypeString
and function_type = {
  1. fun_type_params : param list;
  2. fun_type_returns : (type_ * storage_location option) list;
  3. fun_type_visibility : visibility;
  4. fun_type_mutability : fun_mutability;
}
and raw_statement =
  1. | Block of block
    (*

    An ordered list of statements

    *)
  2. | VariableDefinition of variable_definition
    (*

    Local variable definition

    *)
  3. | ExpressionStatement of expression
    (*

    Single expression returning nothing

    *)
  4. | IfStatement of expression * statement * statement option
    (*

    If-then-else statement; else is optional

    *)
  5. | WhileStatement of expression * statement
    (*

    While loop; expression is the boolean condition, statement is its body

    *)
  6. | DoWhileStatement of statement * expression
    (*

    Do while loop; expression is the boolean condition, statement is its body

    *)
  7. | ForStatement of statement option * expression option * expression option * statement
    (*

    For loop ; the first statement is the initializer, the next expression is the condition, the third is the for action and the last statement the loop body.

    *)
  8. | TryStatement of expression * return list * block * catch_clause list
    (*

    Try-catch statement

    *)
  9. | Emit of expression * function_call_arguments
    (*

    Event emission

    *)
  10. | Return of expression option
    (*

    Return statement

    *)
  11. | Continue
    (*

    Continue (loop statement)

    *)
  12. | Break
    (*

    Break (loop statement)

    *)
  13. | PlaceholderStatement
    (*

    Placeholder for modifiers

    *)
and raw_expression =
  1. | BooleanLiteral of bool
  2. | NumberLiteral of Q.t * number_unit * int option
  3. | StringLiteral of string
  4. | AddressLiteral of string
  5. | IdentifierExpression of ident
  6. | ImmediateArray of expression list
  7. | ArrayAccess of expression * expression option
  8. | ArraySlice of expression * expression option * expression option
  9. | TupleExpression of expression option list
  10. | PrefixExpression of unary_operator * expression
  11. | SuffixExpression of expression * unary_operator
  12. | CompareExpression of expression * compare_operator * expression
  13. | BinaryExpression of expression * binary_operator * expression
  14. | AssignExpression of expression * expression
  15. | AssignBinaryExpression of expression * binary_operator * expression
  16. | IfExpression of expression * expression * expression
  17. | FieldExpression of expression * ident
  18. | FunctionCallExpression of expression * function_call_arguments
  19. | CallOptions of expression * (ident * expression) list
  20. | NewExpression of type_
  21. | TypeExpression of type_
and block = statement list
and catch_clause = ident option * param list * block
and variable_definition =
  1. | VarInfer of ident option list * expression
    (*

    Variable without type

    *)
  2. | VarType of (type_ * storage_location option * ident) option list * expression option
    (*

    Typed variable

    *)
and function_call_arguments =
  1. | ExpressionList of expression list
    (*

    Anonymous arguments

    *)
  2. | NameValueList of (ident * expression) list
    (*

    Named arguments

    *)
and contract_kind =
  1. | Contract
  2. | Library
  3. | Interface
and storage_location =
  1. | Memory
  2. | Storage
  3. | Calldata
and var_mutability =
  1. | MMutable
  2. | MConstant
  3. | MImmutable
and fun_mutability =
  1. | MPure
  2. | MView
  3. | MPayable
  4. | MNonPayable
and visibility =
  1. | VInternal
  2. | VExternal
  3. | VPublic
  4. | VPrivate
and number_unit =
  1. | Unit
  2. | Wei
  3. | Kwei
  4. | Mwei
  5. | Gwei
  6. | Twei
  7. | Pwei
  8. | Ether
  9. | Hours
  10. | Minutes
  11. | Seconds
  12. | Days
  13. | Weeks
  14. | Years
and unary_operator =
  1. | UPlus
  2. | UMinus
  3. | UNot
  4. | ULNot
  5. | UInc
  6. | UDec
  7. | UDelete
and binary_operator =
  1. | BPlus
  2. | BMinus
  3. | BDiv
  4. | BMod
  5. | BTimes
  6. | BExp
  7. | BLShift
  8. | BRShift
  9. | BAnd
  10. | BOr
  11. | BXor
  12. | BLAnd
  13. | BLOr
and compare_operator =
  1. | CEq
  2. | CNeq
  3. | CLt
  4. | CGt
  5. | CLeq
  6. | CGeq
val is_contract : contract_kind -> bool
val is_library : contract_kind -> bool
val is_interface : contract_kind -> bool
val is_mutable : var_mutability -> bool
val is_constant : var_mutability -> bool
val is_immutable : var_mutability -> bool
val is_payable : fun_mutability -> bool
val is_nonpayable : fun_mutability -> bool
val is_external : visibility -> bool
val is_internal : visibility -> bool
val is_private : visibility -> bool
val is_public : visibility -> bool
val is_inheritable : visibility -> bool

True iff not private

val same_mutability : fun_mutability -> fun_mutability -> bool

Checks the equality of mutabilities

val convertible_mutability : from:fun_mutability -> to_:fun_mutability -> bool

Tests if a function with `from` mutability can be overridden by a function with `to` mutability.

val same_visibility : visibility -> visibility -> bool

Checks the equality of visibilities

val convertible_visibility : from:visibility -> to_:visibility -> bool

Tests if a function with `from` visibility can be overridden by a function with `to` visibility.

val apply_unit : Q.t -> number_unit -> Q.t

Returns the quantity in argument with the unit in argument in the smallest quantity of the language of the similar unit. Examples: * `apply_unit 1 Minutes = 60 (Seconds)` * `apply_unit 1 Ether = 1e15 (Wei)` * `apply_unit 1 Unit = 1 (Unit)`

val apply_unop : unary_operator -> Q.t -> Q.t option

Apply the unary operator in argument to a zarith rational. Returns `None` when applying UNot on non-integers If the operator is not an arithmetical operator, also returns `None`.

val apply_binop : Q.t -> binary_operator -> Q.t -> Q.t option

Apply the binary operator in argument to a zarith rational. If the operator is not an arithmetical operator, returns `None`.