2019-09-05 17:21:01 +04:00
|
|
|
(*****************************************************************************)
|
|
|
|
(* *)
|
|
|
|
(* Open Source License *)
|
|
|
|
(* Copyright (c) 2018 Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
|
|
|
|
(* *)
|
|
|
|
(* Permission is hereby granted, free of charge, to any person obtaining a *)
|
|
|
|
(* copy of this software and associated documentation files (the "Software"),*)
|
|
|
|
(* to deal in the Software without restriction, including without limitation *)
|
|
|
|
(* the rights to use, copy, modify, merge, publish, distribute, sublicense, *)
|
|
|
|
(* and/or sell copies of the Software, and to permit persons to whom the *)
|
|
|
|
(* Software is furnished to do so, subject to the following conditions: *)
|
|
|
|
(* *)
|
|
|
|
(* The above copyright notice and this permission notice shall be included *)
|
|
|
|
(* in all copies or substantial portions of the Software. *)
|
|
|
|
(* *)
|
|
|
|
(* THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR*)
|
|
|
|
(* IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, *)
|
|
|
|
(* FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL *)
|
|
|
|
(* THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER*)
|
|
|
|
(* LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING *)
|
|
|
|
(* FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER *)
|
|
|
|
(* DEALINGS IN THE SOFTWARE. *)
|
|
|
|
(* *)
|
|
|
|
(*****************************************************************************)
|
|
|
|
|
|
|
|
module type BASIC_DATA = sig
|
|
|
|
type t
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
include Compare.S with type t := t
|
2020-02-12 20:40:17 +04:00
|
|
|
|
|
|
|
val encoding : t Data_encoding.t
|
|
|
|
|
|
|
|
val pp : Format.formatter -> t -> unit
|
2019-09-05 17:21:01 +04:00
|
|
|
end
|
|
|
|
|
2019-12-19 19:09:53 +04:00
|
|
|
type t = Raw_context.t
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type context = t
|
|
|
|
|
|
|
|
type public_key = Signature.Public_key.t
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type public_key_hash = Signature.Public_key_hash.t
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type signature = Signature.t
|
|
|
|
|
|
|
|
module Tez : sig
|
|
|
|
include BASIC_DATA
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type tez = t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val zero : tez
|
|
|
|
|
|
|
|
val one_mutez : tez
|
|
|
|
|
|
|
|
val one_cent : tez
|
|
|
|
|
|
|
|
val fifty_cents : tez
|
|
|
|
|
|
|
|
val one : tez
|
2019-09-05 17:21:01 +04:00
|
|
|
|
|
|
|
val ( -? ) : tez -> tez -> tez tzresult
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val ( +? ) : tez -> tez -> tez tzresult
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val ( *? ) : tez -> int64 -> tez tzresult
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val ( /? ) : tez -> int64 -> tez tzresult
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val of_string : string -> tez option
|
|
|
|
|
|
|
|
val to_string : tez -> string
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val of_mutez : int64 -> tez option
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val to_mutez : tez -> int64
|
2019-09-05 17:21:01 +04:00
|
|
|
end
|
|
|
|
|
|
|
|
module Period : sig
|
|
|
|
include BASIC_DATA
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type period = t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val rpc_arg : period RPC_arg.arg
|
|
|
|
|
|
|
|
val of_seconds : int64 -> period tzresult
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val to_seconds : period -> int64
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val mult : int32 -> period -> period tzresult
|
|
|
|
|
|
|
|
val zero : period
|
|
|
|
|
|
|
|
val one_second : period
|
|
|
|
|
|
|
|
val one_minute : period
|
|
|
|
|
|
|
|
val one_hour : period
|
2019-09-05 17:21:01 +04:00
|
|
|
end
|
|
|
|
|
|
|
|
module Timestamp : sig
|
|
|
|
include BASIC_DATA with type t = Time.t
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type time = t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val ( +? ) : time -> Period.t -> time tzresult
|
|
|
|
|
|
|
|
val ( -? ) : time -> time -> Period.t tzresult
|
|
|
|
|
|
|
|
val of_notation : string -> time option
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val to_notation : time -> string
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val of_seconds : string -> time option
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val to_seconds_string : time -> string
|
|
|
|
|
|
|
|
val current : context -> time
|
2019-09-05 17:21:01 +04:00
|
|
|
end
|
|
|
|
|
|
|
|
module Raw_level : sig
|
|
|
|
include BASIC_DATA
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type raw_level = t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val rpc_arg : raw_level RPC_arg.arg
|
|
|
|
|
|
|
|
val diff : raw_level -> raw_level -> int32
|
|
|
|
|
|
|
|
val root : raw_level
|
|
|
|
|
|
|
|
val succ : raw_level -> raw_level
|
|
|
|
|
|
|
|
val pred : raw_level -> raw_level option
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val to_int32 : raw_level -> int32
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val of_int32 : int32 -> raw_level tzresult
|
2019-09-05 17:21:01 +04:00
|
|
|
end
|
|
|
|
|
|
|
|
module Cycle : sig
|
|
|
|
include BASIC_DATA
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type cycle = t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val rpc_arg : cycle RPC_arg.arg
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val root : cycle
|
|
|
|
|
|
|
|
val succ : cycle -> cycle
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val pred : cycle -> cycle option
|
|
|
|
|
|
|
|
val add : cycle -> int -> cycle
|
|
|
|
|
|
|
|
val sub : cycle -> int -> cycle option
|
|
|
|
|
|
|
|
val to_int32 : cycle -> int32
|
|
|
|
|
|
|
|
module Map : S.MAP with type key = cycle
|
2019-09-05 17:21:01 +04:00
|
|
|
end
|
|
|
|
|
|
|
|
module Gas : sig
|
2020-02-12 20:40:17 +04:00
|
|
|
type t = private Unaccounted | Limited of {remaining : Z.t}
|
2019-09-05 17:21:01 +04:00
|
|
|
|
|
|
|
val encoding : t Data_encoding.encoding
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val pp : Format.formatter -> t -> unit
|
|
|
|
|
|
|
|
type cost
|
|
|
|
|
|
|
|
val cost_encoding : cost Data_encoding.encoding
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val pp_cost : Format.formatter -> cost -> unit
|
|
|
|
|
|
|
|
type error += Block_quota_exceeded (* `Temporary *)
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type error += Operation_quota_exceeded (* `Temporary *)
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type error += Gas_limit_too_high (* `Permanent *)
|
|
|
|
|
|
|
|
val free : cost
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-10-17 13:45:27 +04:00
|
|
|
val atomic_step_cost : int -> cost
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val step_cost : int -> cost
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val alloc_cost : int -> cost
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val alloc_bytes_cost : int -> cost
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val alloc_mbytes_cost : int -> cost
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val alloc_bits_cost : int -> cost
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val read_bytes_cost : Z.t -> cost
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val write_bytes_cost : Z.t -> cost
|
|
|
|
|
|
|
|
val ( *@ ) : int -> cost -> cost
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val ( +@ ) : cost -> cost -> cost
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val check_limit : context -> Z.t -> unit tzresult
|
|
|
|
|
|
|
|
val set_limit : context -> Z.t -> context
|
|
|
|
|
|
|
|
val set_unlimited : context -> context
|
|
|
|
|
|
|
|
val consume : context -> cost -> context tzresult
|
|
|
|
|
|
|
|
val check_enough : context -> cost -> unit tzresult
|
|
|
|
|
|
|
|
val level : context -> t
|
|
|
|
|
|
|
|
val consumed : since:context -> until:context -> Z.t
|
|
|
|
|
|
|
|
val block_level : context -> Z.t
|
2019-09-05 17:21:01 +04:00
|
|
|
end
|
|
|
|
|
|
|
|
module Script_int : module type of Script_int_repr
|
|
|
|
|
|
|
|
module Script_timestamp : sig
|
|
|
|
open Script_int
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type t
|
2020-02-12 20:40:17 +04:00
|
|
|
|
|
|
|
val compare : t -> t -> int
|
|
|
|
|
|
|
|
val to_string : t -> string
|
|
|
|
|
|
|
|
val to_notation : t -> string option
|
|
|
|
|
|
|
|
val to_num_str : t -> string
|
|
|
|
|
|
|
|
val of_string : string -> t option
|
|
|
|
|
|
|
|
val diff : t -> t -> z num
|
|
|
|
|
|
|
|
val add_delta : t -> z num -> t
|
|
|
|
|
|
|
|
val sub_delta : t -> z num -> t
|
|
|
|
|
|
|
|
val now : context -> t
|
|
|
|
|
|
|
|
val to_zint : t -> Z.t
|
|
|
|
|
|
|
|
val of_zint : Z.t -> t
|
2019-09-05 17:21:01 +04:00
|
|
|
end
|
|
|
|
|
|
|
|
module Script : sig
|
|
|
|
type prim = Michelson_v1_primitives.prim =
|
|
|
|
| K_parameter
|
|
|
|
| K_storage
|
|
|
|
| K_code
|
|
|
|
| D_False
|
|
|
|
| D_Elt
|
|
|
|
| D_Left
|
|
|
|
| D_None
|
|
|
|
| D_Pair
|
|
|
|
| D_Right
|
|
|
|
| D_Some
|
|
|
|
| D_True
|
|
|
|
| D_Unit
|
|
|
|
| I_PACK
|
|
|
|
| I_UNPACK
|
|
|
|
| I_BLAKE2B
|
|
|
|
| I_SHA256
|
|
|
|
| I_SHA512
|
|
|
|
| I_ABS
|
|
|
|
| I_ADD
|
|
|
|
| I_AMOUNT
|
|
|
|
| I_AND
|
|
|
|
| I_BALANCE
|
|
|
|
| I_CAR
|
|
|
|
| I_CDR
|
2019-10-17 13:45:27 +04:00
|
|
|
| I_CHAIN_ID
|
2019-09-05 17:21:01 +04:00
|
|
|
| I_CHECK_SIGNATURE
|
|
|
|
| I_COMPARE
|
|
|
|
| I_CONCAT
|
|
|
|
| I_CONS
|
|
|
|
| I_CREATE_ACCOUNT
|
|
|
|
| I_CREATE_CONTRACT
|
|
|
|
| I_IMPLICIT_ACCOUNT
|
|
|
|
| I_DIP
|
|
|
|
| I_DROP
|
|
|
|
| I_DUP
|
|
|
|
| I_EDIV
|
2019-10-17 13:45:27 +04:00
|
|
|
| I_EMPTY_BIG_MAP
|
2019-09-05 17:21:01 +04:00
|
|
|
| I_EMPTY_MAP
|
|
|
|
| I_EMPTY_SET
|
|
|
|
| I_EQ
|
|
|
|
| I_EXEC
|
2019-10-17 13:45:27 +04:00
|
|
|
| I_APPLY
|
2019-09-05 17:21:01 +04:00
|
|
|
| I_FAILWITH
|
|
|
|
| I_GE
|
|
|
|
| I_GET
|
|
|
|
| I_GT
|
|
|
|
| I_HASH_KEY
|
|
|
|
| I_IF
|
|
|
|
| I_IF_CONS
|
|
|
|
| I_IF_LEFT
|
|
|
|
| I_IF_NONE
|
|
|
|
| I_INT
|
|
|
|
| I_LAMBDA
|
|
|
|
| I_LE
|
|
|
|
| I_LEFT
|
|
|
|
| I_LOOP
|
|
|
|
| I_LSL
|
|
|
|
| I_LSR
|
|
|
|
| I_LT
|
|
|
|
| I_MAP
|
|
|
|
| I_MEM
|
|
|
|
| I_MUL
|
|
|
|
| I_NEG
|
|
|
|
| I_NEQ
|
|
|
|
| I_NIL
|
|
|
|
| I_NONE
|
|
|
|
| I_NOT
|
|
|
|
| I_NOW
|
|
|
|
| I_OR
|
|
|
|
| I_PAIR
|
|
|
|
| I_PUSH
|
|
|
|
| I_RIGHT
|
|
|
|
| I_SIZE
|
|
|
|
| I_SOME
|
|
|
|
| I_SOURCE
|
|
|
|
| I_SENDER
|
|
|
|
| I_SELF
|
|
|
|
| I_SLICE
|
|
|
|
| I_STEPS_TO_QUOTA
|
|
|
|
| I_SUB
|
|
|
|
| I_SWAP
|
|
|
|
| I_TRANSFER_TOKENS
|
|
|
|
| I_SET_DELEGATE
|
|
|
|
| I_UNIT
|
|
|
|
| I_UPDATE
|
|
|
|
| I_XOR
|
|
|
|
| I_ITER
|
|
|
|
| I_LOOP_LEFT
|
|
|
|
| I_ADDRESS
|
|
|
|
| I_CONTRACT
|
|
|
|
| I_ISNAT
|
|
|
|
| I_CAST
|
|
|
|
| I_RENAME
|
2019-10-17 13:45:27 +04:00
|
|
|
| I_DIG
|
|
|
|
| I_DUG
|
2019-09-05 17:21:01 +04:00
|
|
|
| T_bool
|
|
|
|
| T_contract
|
|
|
|
| T_int
|
|
|
|
| T_key
|
|
|
|
| T_key_hash
|
|
|
|
| T_lambda
|
|
|
|
| T_list
|
|
|
|
| T_map
|
|
|
|
| T_big_map
|
|
|
|
| T_nat
|
|
|
|
| T_option
|
|
|
|
| T_or
|
|
|
|
| T_pair
|
|
|
|
| T_set
|
|
|
|
| T_signature
|
|
|
|
| T_string
|
|
|
|
| T_bytes
|
|
|
|
| T_mutez
|
|
|
|
| T_timestamp
|
|
|
|
| T_unit
|
|
|
|
| T_operation
|
|
|
|
| T_address
|
2019-10-17 13:45:27 +04:00
|
|
|
| T_chain_id
|
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type location = Micheline.canonical_location
|
|
|
|
|
|
|
|
type annot = Micheline.annot
|
|
|
|
|
|
|
|
type expr = prim Micheline.canonical
|
|
|
|
|
|
|
|
type lazy_expr = expr Data_encoding.lazy_t
|
|
|
|
|
|
|
|
val lazy_expr : expr -> lazy_expr
|
|
|
|
|
|
|
|
type node = (location, prim) Micheline.node
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
type t = {code : lazy_expr; storage : lazy_expr}
|
|
|
|
|
|
|
|
val location_encoding : location Data_encoding.t
|
|
|
|
|
|
|
|
val expr_encoding : expr Data_encoding.t
|
|
|
|
|
|
|
|
val prim_encoding : prim Data_encoding.t
|
|
|
|
|
|
|
|
val encoding : t Data_encoding.t
|
|
|
|
|
|
|
|
val lazy_expr_encoding : lazy_expr Data_encoding.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
|
|
|
val deserialized_cost : expr -> Gas.cost
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val serialized_cost : MBytes.t -> Gas.cost
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val traversal_cost : node -> Gas.cost
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val node_cost : node -> Gas.cost
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val int_node_cost : Z.t -> Gas.cost
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val int_node_cost_of_numbits : int -> Gas.cost
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val string_node_cost : string -> Gas.cost
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val string_node_cost_of_length : int -> Gas.cost
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val bytes_node_cost : MBytes.t -> Gas.cost
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val bytes_node_cost_of_length : int -> Gas.cost
|
2020-02-12 20:40:17 +04:00
|
|
|
|
|
|
|
val prim_node_cost_nonrec : expr list -> annot -> Gas.cost
|
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val prim_node_cost_nonrec_of_length : int -> annot -> Gas.cost
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val seq_node_cost_nonrec : expr list -> Gas.cost
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val seq_node_cost_nonrec_of_length : int -> Gas.cost
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val minimal_deserialize_cost : lazy_expr -> Gas.cost
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val force_decode : context -> lazy_expr -> (expr * context) tzresult Lwt.t
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val force_bytes : context -> lazy_expr -> (MBytes.t * context) tzresult Lwt.t
|
2019-10-17 13:45:27 +04:00
|
|
|
|
|
|
|
val unit_parameter : lazy_expr
|
|
|
|
|
|
|
|
module Legacy_support : sig
|
2020-02-12 20:40:17 +04:00
|
|
|
val manager_script_code : lazy_expr
|
|
|
|
|
|
|
|
val add_do :
|
|
|
|
manager_pkh:Signature.Public_key_hash.t ->
|
|
|
|
script_code:lazy_expr ->
|
|
|
|
script_storage:lazy_expr ->
|
2019-10-17 13:45:27 +04:00
|
|
|
(lazy_expr * lazy_expr) tzresult Lwt.t
|
2020-02-12 20:40:17 +04:00
|
|
|
|
|
|
|
val add_set_delegate :
|
|
|
|
manager_pkh:Signature.Public_key_hash.t ->
|
|
|
|
script_code:lazy_expr ->
|
|
|
|
script_storage:lazy_expr ->
|
2019-10-17 13:45:27 +04:00
|
|
|
(lazy_expr * lazy_expr) tzresult Lwt.t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val has_default_entrypoint : lazy_expr -> bool
|
|
|
|
|
|
|
|
val add_root_entrypoint : script_code:lazy_expr -> lazy_expr tzresult Lwt.t
|
|
|
|
end
|
2019-09-05 17:21:01 +04:00
|
|
|
end
|
|
|
|
|
|
|
|
module Constants : sig
|
|
|
|
(** Fixed constants *)
|
|
|
|
type fixed = {
|
2020-02-12 20:40:17 +04:00
|
|
|
proof_of_work_nonce_size : int;
|
|
|
|
nonce_length : int;
|
|
|
|
max_revelations_per_block : int;
|
|
|
|
max_operation_data_length : int;
|
|
|
|
max_proposals_per_delegate : int;
|
2019-09-05 17:21:01 +04:00
|
|
|
}
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val fixed_encoding : fixed Data_encoding.t
|
|
|
|
|
|
|
|
val fixed : fixed
|
|
|
|
|
|
|
|
val proof_of_work_nonce_size : int
|
|
|
|
|
|
|
|
val nonce_length : int
|
|
|
|
|
|
|
|
val max_revelations_per_block : int
|
|
|
|
|
|
|
|
val max_operation_data_length : int
|
|
|
|
|
|
|
|
val max_proposals_per_delegate : int
|
2019-09-05 17:21:01 +04:00
|
|
|
|
|
|
|
(** Constants parameterized by context *)
|
|
|
|
type parametric = {
|
2020-02-12 20:40:17 +04:00
|
|
|
preserved_cycles : int;
|
|
|
|
blocks_per_cycle : int32;
|
|
|
|
blocks_per_commitment : int32;
|
|
|
|
blocks_per_roll_snapshot : int32;
|
|
|
|
blocks_per_voting_period : int32;
|
|
|
|
time_between_blocks : Period.t list;
|
|
|
|
endorsers_per_block : int;
|
|
|
|
hard_gas_limit_per_operation : Z.t;
|
|
|
|
hard_gas_limit_per_block : Z.t;
|
|
|
|
proof_of_work_threshold : int64;
|
|
|
|
tokens_per_roll : Tez.t;
|
|
|
|
michelson_maximum_type_size : int;
|
|
|
|
seed_nonce_revelation_tip : Tez.t;
|
|
|
|
origination_size : int;
|
|
|
|
block_security_deposit : Tez.t;
|
|
|
|
endorsement_security_deposit : Tez.t;
|
|
|
|
baking_reward_per_endorsement : Tez.t list;
|
|
|
|
endorsement_reward : Tez.t list;
|
|
|
|
cost_per_byte : Tez.t;
|
|
|
|
hard_storage_limit_per_operation : Z.t;
|
|
|
|
test_chain_duration : int64;
|
|
|
|
quorum_min : int32;
|
|
|
|
quorum_max : int32;
|
|
|
|
min_proposal_quorum : int32;
|
|
|
|
initial_endorsers : int;
|
|
|
|
delay_per_missing_endorsement : Period.t;
|
2019-09-05 17:21:01 +04:00
|
|
|
}
|
2020-02-12 20:40:17 +04:00
|
|
|
|
|
|
|
val parametric_encoding : parametric Data_encoding.t
|
|
|
|
|
|
|
|
val parametric : context -> parametric
|
|
|
|
|
|
|
|
val preserved_cycles : context -> int
|
|
|
|
|
|
|
|
val blocks_per_cycle : context -> int32
|
|
|
|
|
|
|
|
val blocks_per_commitment : context -> int32
|
|
|
|
|
|
|
|
val blocks_per_roll_snapshot : context -> int32
|
|
|
|
|
|
|
|
val blocks_per_voting_period : context -> int32
|
|
|
|
|
|
|
|
val time_between_blocks : context -> Period.t list
|
|
|
|
|
|
|
|
val endorsers_per_block : context -> int
|
|
|
|
|
|
|
|
val initial_endorsers : context -> int
|
|
|
|
|
|
|
|
val delay_per_missing_endorsement : context -> Period.t
|
|
|
|
|
|
|
|
val hard_gas_limit_per_operation : context -> Z.t
|
|
|
|
|
|
|
|
val hard_gas_limit_per_block : context -> Z.t
|
|
|
|
|
|
|
|
val cost_per_byte : context -> Tez.t
|
|
|
|
|
|
|
|
val hard_storage_limit_per_operation : context -> Z.t
|
|
|
|
|
|
|
|
val proof_of_work_threshold : context -> int64
|
|
|
|
|
|
|
|
val tokens_per_roll : context -> Tez.t
|
|
|
|
|
|
|
|
val michelson_maximum_type_size : context -> int
|
|
|
|
|
|
|
|
val baking_reward_per_endorsement : context -> Tez.t list
|
|
|
|
|
|
|
|
val endorsement_reward : context -> Tez.t list
|
|
|
|
|
|
|
|
val seed_nonce_revelation_tip : context -> Tez.t
|
|
|
|
|
|
|
|
val origination_size : context -> int
|
|
|
|
|
|
|
|
val block_security_deposit : context -> Tez.t
|
|
|
|
|
|
|
|
val endorsement_security_deposit : context -> Tez.t
|
|
|
|
|
|
|
|
val test_chain_duration : context -> int64
|
|
|
|
|
|
|
|
val quorum_min : context -> int32
|
|
|
|
|
|
|
|
val quorum_max : context -> int32
|
|
|
|
|
|
|
|
val min_proposal_quorum : context -> int32
|
2019-09-05 17:21:01 +04:00
|
|
|
|
|
|
|
(** All constants: fixed and parametric *)
|
2020-02-12 20:40:17 +04:00
|
|
|
type t = {fixed : fixed; parametric : parametric}
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val encoding : t Data_encoding.t
|
2019-09-05 17:21:01 +04:00
|
|
|
end
|
|
|
|
|
|
|
|
module Voting_period : sig
|
|
|
|
include BASIC_DATA
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type voting_period = t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val rpc_arg : voting_period RPC_arg.arg
|
|
|
|
|
|
|
|
val root : voting_period
|
|
|
|
|
|
|
|
val succ : voting_period -> voting_period
|
|
|
|
|
|
|
|
type kind = Proposal | Testing_vote | Testing | Promotion_vote
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val kind_encoding : kind Data_encoding.encoding
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val to_int32 : voting_period -> int32
|
2019-09-05 17:21:01 +04:00
|
|
|
end
|
|
|
|
|
|
|
|
module Level : sig
|
|
|
|
type t = private {
|
2020-02-12 20:40:17 +04:00
|
|
|
level : Raw_level.t;
|
|
|
|
level_position : int32;
|
|
|
|
cycle : Cycle.t;
|
|
|
|
cycle_position : int32;
|
|
|
|
voting_period : Voting_period.t;
|
|
|
|
voting_period_position : int32;
|
|
|
|
expected_commitment : bool;
|
2019-09-05 17:21:01 +04:00
|
|
|
}
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
include BASIC_DATA with type t := t
|
2020-02-12 20:40:17 +04:00
|
|
|
|
|
|
|
val pp_full : Format.formatter -> t -> unit
|
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type level = t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val root : context -> level
|
|
|
|
|
|
|
|
val succ : context -> level -> level
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val pred : context -> level -> level option
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val from_raw : context -> ?offset:int32 -> Raw_level.t -> level
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val diff : level -> level -> int32
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val current : context -> level
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val last_level_in_cycle : context -> Cycle.t -> level
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val levels_in_cycle : context -> Cycle.t -> level list
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val levels_in_current_cycle : context -> ?offset:int32 -> unit -> level list
|
|
|
|
|
|
|
|
val last_allowed_fork_level : context -> Raw_level.t
|
2019-09-05 17:21:01 +04:00
|
|
|
end
|
|
|
|
|
|
|
|
module Fitness : sig
|
2020-02-12 20:40:17 +04:00
|
|
|
include module type of Fitness
|
2019-09-05 17:21:01 +04:00
|
|
|
|
|
|
|
type fitness = t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val increase : ?gap:int -> context -> context
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val current : context -> int64
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val to_int64 : fitness -> int64 tzresult
|
2019-09-05 17:21:01 +04:00
|
|
|
end
|
|
|
|
|
|
|
|
module Nonce : sig
|
|
|
|
type t
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type nonce = t
|
2020-02-12 20:40:17 +04:00
|
|
|
|
|
|
|
val encoding : nonce Data_encoding.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
|
|
|
type unrevealed = {
|
2020-02-12 20:40:17 +04:00
|
|
|
nonce_hash : Nonce_hash.t;
|
|
|
|
delegate : public_key_hash;
|
|
|
|
rewards : Tez.t;
|
|
|
|
fees : Tez.t;
|
2019-09-05 17:21:01 +04:00
|
|
|
}
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val record_hash : context -> unrevealed -> context tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val reveal : context -> Level.t -> nonce -> context tzresult Lwt.t
|
|
|
|
|
|
|
|
type status = Unrevealed of unrevealed | Revealed of nonce
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val get : context -> Level.t -> status tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val of_bytes : MBytes.t -> nonce tzresult
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val hash : nonce -> Nonce_hash.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val check_hash : nonce -> Nonce_hash.t -> bool
|
2019-09-05 17:21:01 +04:00
|
|
|
end
|
|
|
|
|
|
|
|
module Seed : sig
|
|
|
|
type seed
|
|
|
|
|
|
|
|
type error +=
|
2020-02-12 20:40:17 +04:00
|
|
|
| Unknown of {oldest : Cycle.t; cycle : Cycle.t; latest : Cycle.t}
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val for_cycle : context -> Cycle.t -> seed tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val cycle_end :
|
2019-09-05 17:21:01 +04:00
|
|
|
context -> Cycle.t -> (context * Nonce.unrevealed list) tzresult Lwt.t
|
|
|
|
|
|
|
|
val seed_encoding : seed Data_encoding.t
|
|
|
|
end
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
module Big_map : sig
|
2019-10-17 13:45:27 +04:00
|
|
|
type id = Z.t
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-10-17 13:45:27 +04:00
|
|
|
val fresh : context -> (context * id) tzresult Lwt.t
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-10-17 13:45:27 +04:00
|
|
|
val fresh_temporary : context -> context * id
|
2020-02-12 20:40:17 +04:00
|
|
|
|
|
|
|
val mem :
|
|
|
|
context -> id -> Script_expr_hash.t -> (context * bool) tzresult Lwt.t
|
|
|
|
|
|
|
|
val get_opt :
|
|
|
|
context ->
|
|
|
|
id ->
|
|
|
|
Script_expr_hash.t ->
|
|
|
|
(context * Script.expr option) tzresult Lwt.t
|
|
|
|
|
2019-10-17 13:45:27 +04:00
|
|
|
val rpc_arg : id RPC_arg.t
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-10-17 13:45:27 +04:00
|
|
|
val cleanup_temporary : context -> context Lwt.t
|
2020-02-12 20:40:17 +04:00
|
|
|
|
|
|
|
val exists :
|
|
|
|
context ->
|
|
|
|
id ->
|
|
|
|
(context * (Script.expr * Script.expr) option) tzresult Lwt.t
|
2019-10-17 13:45:27 +04:00
|
|
|
end
|
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
module Contract : sig
|
|
|
|
include BASIC_DATA
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type contract = t
|
2020-03-05 23:52:47 +04:00
|
|
|
|
|
|
|
val set_balance : context ->
|
|
|
|
contract -> Tez.t -> context tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val rpc_arg : contract RPC_arg.arg
|
|
|
|
|
|
|
|
val to_b58check : contract -> string
|
|
|
|
|
|
|
|
val of_b58check : string -> contract tzresult
|
|
|
|
|
|
|
|
val implicit_contract : public_key_hash -> contract
|
|
|
|
|
|
|
|
val is_implicit : contract -> public_key_hash option
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val exists : context -> contract -> bool tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val must_exist : context -> contract -> unit tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val allocated : context -> contract -> bool tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val must_be_allocated : context -> contract -> unit tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val list : context -> contract list Lwt.t
|
|
|
|
|
|
|
|
val get_manager_key : context -> public_key_hash -> public_key tzresult Lwt.t
|
|
|
|
|
|
|
|
val is_manager_key_revealed :
|
2019-10-17 13:45:27 +04:00
|
|
|
context -> public_key_hash -> bool tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val reveal_manager_key :
|
2019-10-17 13:45:27 +04:00
|
|
|
context -> public_key_hash -> public_key -> context tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val get_script_code :
|
2019-10-17 13:45:27 +04:00
|
|
|
context -> contract -> (context * Script.lazy_expr option) tzresult Lwt.t
|
2020-02-12 20:40:17 +04:00
|
|
|
|
|
|
|
val get_script :
|
2019-09-05 17:21:01 +04:00
|
|
|
context -> contract -> (context * Script.t option) tzresult Lwt.t
|
2020-02-12 20:40:17 +04:00
|
|
|
|
|
|
|
val get_storage :
|
2019-09-05 17:21:01 +04:00
|
|
|
context -> contract -> (context * Script.expr option) tzresult Lwt.t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val get_counter : context -> public_key_hash -> Z.t tzresult Lwt.t
|
|
|
|
|
|
|
|
val get_balance : context -> contract -> Tez.t tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val init_origination_nonce : context -> Operation_hash.t -> context
|
|
|
|
|
|
|
|
val unset_origination_nonce : context -> context
|
|
|
|
|
|
|
|
val fresh_contract_from_current_nonce :
|
|
|
|
context -> (context * t) tzresult Lwt.t
|
|
|
|
|
|
|
|
val originated_from_current_nonce :
|
|
|
|
since:context -> until:context -> contract list tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2019-10-17 13:45:27 +04:00
|
|
|
type big_map_diff_item =
|
2020-02-12 20:40:17 +04:00
|
|
|
| Update of {
|
|
|
|
big_map : Big_map.id;
|
|
|
|
diff_key : Script.expr;
|
|
|
|
diff_key_hash : Script_expr_hash.t;
|
|
|
|
diff_value : Script.expr option;
|
|
|
|
}
|
|
|
|
| Clear of Big_map.id
|
|
|
|
| Copy of Big_map.id * Big_map.id
|
|
|
|
| Alloc of {
|
|
|
|
big_map : Big_map.id;
|
|
|
|
key_type : Script.expr;
|
|
|
|
value_type : Script.expr;
|
|
|
|
}
|
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type big_map_diff = big_map_diff_item list
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val big_map_diff_encoding : big_map_diff Data_encoding.t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val originate :
|
|
|
|
context ->
|
|
|
|
contract ->
|
|
|
|
balance:Tez.t ->
|
|
|
|
script:Script.t * big_map_diff option ->
|
|
|
|
delegate:public_key_hash option ->
|
2019-10-17 13:45:27 +04:00
|
|
|
context tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
|
|
|
type error += Balance_too_low of contract * Tez.t * Tez.t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val spend : context -> contract -> Tez.t -> context tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val credit : context -> contract -> Tez.t -> context tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val update_script_storage :
|
|
|
|
context ->
|
|
|
|
contract ->
|
|
|
|
Script.expr ->
|
|
|
|
big_map_diff option ->
|
2019-09-05 17:21:01 +04:00
|
|
|
context tzresult Lwt.t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val used_storage_space : context -> t -> Z.t tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val increment_counter : context -> public_key_hash -> context tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val check_counter_increment :
|
2019-10-17 13:45:27 +04:00
|
|
|
context -> public_key_hash -> Z.t -> unit tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
|
|
|
(**/**)
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
(* Only for testing *)
|
|
|
|
type origination_nonce
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val initial_origination_nonce : Operation_hash.t -> origination_nonce
|
|
|
|
|
|
|
|
val originated_contract : origination_nonce -> contract
|
2019-09-05 17:21:01 +04:00
|
|
|
end
|
|
|
|
|
|
|
|
module Delegate : sig
|
|
|
|
type balance =
|
|
|
|
| Contract of Contract.t
|
|
|
|
| Rewards of Signature.Public_key_hash.t * Cycle.t
|
|
|
|
| Fees of Signature.Public_key_hash.t * Cycle.t
|
|
|
|
| Deposits of Signature.Public_key_hash.t * Cycle.t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
type balance_update = Debited of Tez.t | Credited of Tez.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
|
|
|
type balance_updates = (balance * balance_update) list
|
|
|
|
|
|
|
|
val balance_updates_encoding : balance_updates Data_encoding.t
|
|
|
|
|
|
|
|
val cleanup_balance_updates : balance_updates -> balance_updates
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val get : context -> Contract.t -> public_key_hash option tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val set :
|
2019-09-05 17:21:01 +04:00
|
|
|
context -> Contract.t -> public_key_hash option -> context tzresult Lwt.t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val fold :
|
|
|
|
context -> init:'a -> f:(public_key_hash -> 'a -> 'a Lwt.t) -> 'a Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val list : context -> public_key_hash list Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val freeze_deposit :
|
2019-09-05 17:21:01 +04:00
|
|
|
context -> public_key_hash -> Tez.t -> context tzresult Lwt.t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val freeze_rewards :
|
2019-09-05 17:21:01 +04:00
|
|
|
context -> public_key_hash -> Tez.t -> context tzresult Lwt.t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val freeze_fees :
|
2019-09-05 17:21:01 +04:00
|
|
|
context -> public_key_hash -> Tez.t -> context tzresult Lwt.t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val cycle_end :
|
|
|
|
context ->
|
|
|
|
Cycle.t ->
|
|
|
|
Nonce.unrevealed list ->
|
|
|
|
(context * balance_updates * Signature.Public_key_hash.t list) tzresult
|
|
|
|
Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
type frozen_balance = {deposit : Tez.t; fees : Tez.t; rewards : Tez.t}
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val punish :
|
|
|
|
context ->
|
|
|
|
public_key_hash ->
|
|
|
|
Cycle.t ->
|
2019-09-05 17:21:01 +04:00
|
|
|
(context * frozen_balance) tzresult Lwt.t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val full_balance : context -> public_key_hash -> Tez.t tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val has_frozen_balance :
|
|
|
|
context -> public_key_hash -> Cycle.t -> bool tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val frozen_balance : context -> public_key_hash -> Tez.t tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val frozen_balance_encoding : frozen_balance Data_encoding.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val frozen_balance_by_cycle_encoding :
|
|
|
|
frozen_balance Cycle.Map.t Data_encoding.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val frozen_balance_by_cycle :
|
|
|
|
context -> Signature.Public_key_hash.t -> frozen_balance Cycle.Map.t Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val staking_balance :
|
|
|
|
context -> Signature.Public_key_hash.t -> Tez.t tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val delegated_contracts :
|
|
|
|
context -> Signature.Public_key_hash.t -> Contract_repr.t list Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val delegated_balance :
|
|
|
|
context -> Signature.Public_key_hash.t -> Tez.t tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val deactivated :
|
|
|
|
context -> Signature.Public_key_hash.t -> bool tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val grace_period :
|
|
|
|
context -> Signature.Public_key_hash.t -> Cycle.t tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
end
|
|
|
|
|
|
|
|
module Vote : sig
|
|
|
|
type proposal = Protocol_hash.t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val record_proposal :
|
|
|
|
context -> Protocol_hash.t -> public_key_hash -> context tzresult Lwt.t
|
|
|
|
|
|
|
|
val get_proposals : context -> int32 Protocol_hash.Map.t tzresult Lwt.t
|
|
|
|
|
|
|
|
val clear_proposals : context -> context Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val recorded_proposal_count_for_delegate :
|
2019-09-05 17:21:01 +04:00
|
|
|
context -> public_key_hash -> int tzresult Lwt.t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val listings_encoding :
|
|
|
|
(Signature.Public_key_hash.t * int32) list Data_encoding.t
|
|
|
|
|
|
|
|
val freeze_listings : context -> context tzresult Lwt.t
|
|
|
|
|
|
|
|
val clear_listings : context -> context tzresult Lwt.t
|
|
|
|
|
|
|
|
val listing_size : context -> int32 tzresult Lwt.t
|
|
|
|
|
|
|
|
val in_listings : context -> public_key_hash -> bool Lwt.t
|
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val get_listings : context -> (public_key_hash * int32) list Lwt.t
|
|
|
|
|
|
|
|
type ballot = Yay | Nay | Pass
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
val ballot_encoding : ballot Data_encoding.t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
type ballots = {yay : int32; nay : int32; pass : int32}
|
2019-09-05 17:21:01 +04:00
|
|
|
|
|
|
|
val ballots_encoding : ballots Data_encoding.t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val has_recorded_ballot : context -> public_key_hash -> bool Lwt.t
|
|
|
|
|
|
|
|
val record_ballot :
|
2019-09-05 17:21:01 +04:00
|
|
|
context -> public_key_hash -> ballot -> context tzresult Lwt.t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val get_ballots : context -> ballots tzresult Lwt.t
|
|
|
|
|
|
|
|
val get_ballot_list :
|
|
|
|
context -> (Signature.Public_key_hash.t * ballot) list Lwt.t
|
|
|
|
|
|
|
|
val clear_ballots : context -> context Lwt.t
|
|
|
|
|
|
|
|
val get_current_period_kind : context -> Voting_period.kind tzresult Lwt.t
|
|
|
|
|
|
|
|
val set_current_period_kind :
|
2019-09-05 17:21:01 +04:00
|
|
|
context -> Voting_period.kind -> context tzresult Lwt.t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val get_current_quorum : context -> int32 tzresult Lwt.t
|
|
|
|
|
|
|
|
val get_participation_ema : context -> int32 tzresult Lwt.t
|
|
|
|
|
|
|
|
val set_participation_ema : context -> int32 -> context tzresult Lwt.t
|
2019-10-17 13:45:27 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val get_current_proposal : context -> proposal tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val init_current_proposal : context -> proposal -> context tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val clear_current_proposal : context -> context tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
end
|
|
|
|
|
|
|
|
module Block_header : sig
|
2020-02-12 20:40:17 +04:00
|
|
|
type t = {shell : Block_header.shell_header; protocol_data : protocol_data}
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
and protocol_data = {contents : contents; signature : Signature.t}
|
2019-09-05 17:21:01 +04:00
|
|
|
|
|
|
|
and contents = {
|
2020-02-12 20:40:17 +04:00
|
|
|
priority : int;
|
|
|
|
seed_nonce_hash : Nonce_hash.t option;
|
|
|
|
proof_of_work_nonce : MBytes.t;
|
2019-09-05 17:21:01 +04:00
|
|
|
}
|
|
|
|
|
|
|
|
type block_header = t
|
|
|
|
|
|
|
|
type raw = Block_header.t
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type shell_header = Block_header.shell_header
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val raw : block_header -> raw
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val hash : block_header -> Block_hash.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val hash_raw : raw -> Block_hash.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val encoding : block_header Data_encoding.encoding
|
|
|
|
|
|
|
|
val raw_encoding : raw Data_encoding.t
|
|
|
|
|
|
|
|
val contents_encoding : contents Data_encoding.t
|
|
|
|
|
|
|
|
val unsigned_encoding : (shell_header * contents) Data_encoding.t
|
|
|
|
|
|
|
|
val protocol_data_encoding : protocol_data Data_encoding.encoding
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val shell_header_encoding : shell_header Data_encoding.encoding
|
|
|
|
|
|
|
|
(** The maximum size of block headers in bytes *)
|
|
|
|
val max_header_length : int
|
2019-09-05 17:21:01 +04:00
|
|
|
end
|
|
|
|
|
|
|
|
module Kind : sig
|
|
|
|
type seed_nonce_revelation = Seed_nonce_revelation_kind
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type double_endorsement_evidence = Double_endorsement_evidence_kind
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type double_baking_evidence = Double_baking_evidence_kind
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type activate_account = Activate_account_kind
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type endorsement = Endorsement_kind
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type proposals = Proposals_kind
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type ballot = Ballot_kind
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type reveal = Reveal_kind
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type transaction = Transaction_kind
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type origination = Origination_kind
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type delegation = Delegation_kind
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type 'a manager =
|
|
|
|
| Reveal_manager_kind : reveal manager
|
|
|
|
| Transaction_manager_kind : transaction manager
|
|
|
|
| Origination_manager_kind : origination manager
|
|
|
|
| Delegation_manager_kind : delegation manager
|
|
|
|
end
|
|
|
|
|
|
|
|
type 'kind operation = {
|
2020-02-12 20:40:17 +04:00
|
|
|
shell : Operation.shell_header;
|
|
|
|
protocol_data : 'kind protocol_data;
|
2019-09-05 17:21:01 +04:00
|
|
|
}
|
|
|
|
|
|
|
|
and 'kind protocol_data = {
|
2020-02-12 20:40:17 +04:00
|
|
|
contents : 'kind contents_list;
|
|
|
|
signature : Signature.t option;
|
2019-09-05 17:21:01 +04:00
|
|
|
}
|
|
|
|
|
|
|
|
and _ contents_list =
|
|
|
|
| Single : 'kind contents -> 'kind contents_list
|
2020-02-12 20:40:17 +04:00
|
|
|
| Cons :
|
|
|
|
'kind Kind.manager contents * 'rest Kind.manager contents_list
|
|
|
|
-> ('kind * 'rest) Kind.manager contents_list
|
2019-09-05 17:21:01 +04:00
|
|
|
|
|
|
|
and _ contents =
|
2020-02-12 20:40:17 +04:00
|
|
|
| Endorsement : {level : Raw_level.t} -> Kind.endorsement contents
|
2019-09-05 17:21:01 +04:00
|
|
|
| Seed_nonce_revelation : {
|
2020-02-12 20:40:17 +04:00
|
|
|
level : Raw_level.t;
|
|
|
|
nonce : Nonce.t;
|
|
|
|
}
|
|
|
|
-> Kind.seed_nonce_revelation contents
|
2019-09-05 17:21:01 +04:00
|
|
|
| Double_endorsement_evidence : {
|
2020-02-12 20:40:17 +04:00
|
|
|
op1 : Kind.endorsement operation;
|
|
|
|
op2 : Kind.endorsement operation;
|
|
|
|
}
|
|
|
|
-> Kind.double_endorsement_evidence contents
|
2019-09-05 17:21:01 +04:00
|
|
|
| Double_baking_evidence : {
|
2020-02-12 20:40:17 +04:00
|
|
|
bh1 : Block_header.t;
|
|
|
|
bh2 : Block_header.t;
|
|
|
|
}
|
|
|
|
-> Kind.double_baking_evidence contents
|
2019-09-05 17:21:01 +04:00
|
|
|
| Activate_account : {
|
2020-02-12 20:40:17 +04:00
|
|
|
id : Ed25519.Public_key_hash.t;
|
|
|
|
activation_code : Blinded_public_key_hash.activation_code;
|
|
|
|
}
|
|
|
|
-> Kind.activate_account contents
|
2019-09-05 17:21:01 +04:00
|
|
|
| Proposals : {
|
2020-02-12 20:40:17 +04:00
|
|
|
source : Signature.Public_key_hash.t;
|
|
|
|
period : Voting_period.t;
|
|
|
|
proposals : Protocol_hash.t list;
|
|
|
|
}
|
|
|
|
-> Kind.proposals contents
|
2019-09-05 17:21:01 +04:00
|
|
|
| Ballot : {
|
2020-02-12 20:40:17 +04:00
|
|
|
source : Signature.Public_key_hash.t;
|
|
|
|
period : Voting_period.t;
|
|
|
|
proposal : Protocol_hash.t;
|
|
|
|
ballot : Vote.ballot;
|
|
|
|
}
|
|
|
|
-> Kind.ballot contents
|
2019-09-05 17:21:01 +04:00
|
|
|
| Manager_operation : {
|
2020-02-12 20:40:17 +04:00
|
|
|
source : Signature.Public_key_hash.t;
|
|
|
|
fee : Tez.tez;
|
|
|
|
counter : counter;
|
|
|
|
operation : 'kind manager_operation;
|
|
|
|
gas_limit : Z.t;
|
|
|
|
storage_limit : Z.t;
|
|
|
|
}
|
|
|
|
-> 'kind Kind.manager contents
|
2019-09-05 17:21:01 +04:00
|
|
|
|
|
|
|
and _ manager_operation =
|
|
|
|
| Reveal : Signature.Public_key.t -> Kind.reveal manager_operation
|
|
|
|
| Transaction : {
|
2020-02-12 20:40:17 +04:00
|
|
|
amount : Tez.tez;
|
|
|
|
parameters : Script.lazy_expr;
|
|
|
|
entrypoint : string;
|
|
|
|
destination : Contract.contract;
|
|
|
|
}
|
|
|
|
-> Kind.transaction manager_operation
|
2019-09-05 17:21:01 +04:00
|
|
|
| Origination : {
|
2020-02-12 20:40:17 +04:00
|
|
|
delegate : Signature.Public_key_hash.t option;
|
|
|
|
script : Script.t;
|
|
|
|
credit : Tez.tez;
|
|
|
|
preorigination : Contract.t option;
|
|
|
|
}
|
|
|
|
-> Kind.origination manager_operation
|
2019-09-05 17:21:01 +04:00
|
|
|
| Delegation :
|
2020-02-12 20:40:17 +04:00
|
|
|
Signature.Public_key_hash.t option
|
|
|
|
-> Kind.delegation manager_operation
|
2019-09-05 17:21:01 +04:00
|
|
|
|
|
|
|
and counter = Z.t
|
|
|
|
|
|
|
|
type 'kind internal_operation = {
|
2020-02-12 20:40:17 +04:00
|
|
|
source : Contract.contract;
|
|
|
|
operation : 'kind manager_operation;
|
|
|
|
nonce : int;
|
2019-09-05 17:21:01 +04:00
|
|
|
}
|
|
|
|
|
|
|
|
type packed_manager_operation =
|
|
|
|
| Manager : 'kind manager_operation -> packed_manager_operation
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
type packed_contents = Contents : 'kind contents -> packed_contents
|
2019-09-05 17:21:01 +04:00
|
|
|
|
|
|
|
type packed_contents_list =
|
|
|
|
| Contents_list : 'kind contents_list -> packed_contents_list
|
|
|
|
|
|
|
|
type packed_protocol_data =
|
|
|
|
| Operation_data : 'kind protocol_data -> packed_protocol_data
|
|
|
|
|
|
|
|
type packed_operation = {
|
2020-02-12 20:40:17 +04:00
|
|
|
shell : Operation.shell_header;
|
|
|
|
protocol_data : packed_protocol_data;
|
2019-09-05 17:21:01 +04:00
|
|
|
}
|
|
|
|
|
|
|
|
type packed_internal_operation =
|
|
|
|
| Internal_operation : 'kind internal_operation -> packed_internal_operation
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val manager_kind : 'kind manager_operation -> 'kind Kind.manager
|
2019-09-05 17:21:01 +04:00
|
|
|
|
|
|
|
module Fees : sig
|
2020-02-12 20:40:17 +04:00
|
|
|
val origination_burn : context -> (context * Tez.t) tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val record_paid_storage_space :
|
2019-09-05 17:21:01 +04:00
|
|
|
context -> Contract.t -> (context * Z.t * Z.t * Tez.t) tzresult Lwt.t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val start_counting_storage_fees : context -> context
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val burn_storage_fees :
|
2019-09-05 17:21:01 +04:00
|
|
|
context -> storage_limit:Z.t -> payer:Contract.t -> context tzresult Lwt.t
|
|
|
|
|
|
|
|
type error += Cannot_pay_storage_fee (* `Temporary *)
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type error += Operation_quota_exceeded (* `Temporary *)
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
type error += Storage_limit_too_high (* `Permanent *)
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val check_storage_limit : context -> storage_limit:Z.t -> unit tzresult
|
2019-09-05 17:21:01 +04:00
|
|
|
end
|
|
|
|
|
|
|
|
module Operation : sig
|
|
|
|
type nonrec 'kind contents = 'kind contents
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type nonrec packed_contents = packed_contents
|
2020-02-12 20:40:17 +04:00
|
|
|
|
|
|
|
val contents_encoding : packed_contents Data_encoding.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
|
|
|
type nonrec 'kind protocol_data = 'kind protocol_data
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type nonrec packed_protocol_data = packed_protocol_data
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val protocol_data_encoding : packed_protocol_data Data_encoding.t
|
|
|
|
|
|
|
|
val unsigned_encoding :
|
|
|
|
(Operation.shell_header * packed_contents_list) Data_encoding.t
|
|
|
|
|
|
|
|
type raw = Operation.t = {shell : Operation.shell_header; proto : MBytes.t}
|
|
|
|
|
|
|
|
val raw_encoding : raw Data_encoding.t
|
|
|
|
|
|
|
|
val contents_list_encoding : packed_contents_list Data_encoding.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
|
|
|
type 'kind t = 'kind operation = {
|
2020-02-12 20:40:17 +04:00
|
|
|
shell : Operation.shell_header;
|
|
|
|
protocol_data : 'kind protocol_data;
|
2019-09-05 17:21:01 +04:00
|
|
|
}
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type nonrec packed = packed_operation
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val encoding : packed Data_encoding.t
|
|
|
|
|
|
|
|
val raw : _ operation -> raw
|
|
|
|
|
|
|
|
val hash : _ operation -> Operation_hash.t
|
|
|
|
|
|
|
|
val hash_raw : raw -> Operation_hash.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val hash_packed : packed_operation -> Operation_hash.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val acceptable_passes : packed_operation -> int list
|
2019-09-05 17:21:01 +04:00
|
|
|
|
|
|
|
type error += Missing_signature (* `Permanent *)
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type error += Invalid_signature (* `Permanent *)
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val check_signature :
|
|
|
|
public_key -> Chain_id.t -> _ operation -> unit tzresult Lwt.t
|
|
|
|
|
|
|
|
val check_signature_sync :
|
|
|
|
public_key -> Chain_id.t -> _ operation -> unit tzresult
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val internal_operation_encoding : packed_internal_operation Data_encoding.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val pack : 'kind operation -> packed_operation
|
2019-09-05 17:21:01 +04:00
|
|
|
|
|
|
|
type ('a, 'b) eq = Eq : ('a, 'a) eq
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val equal : 'a operation -> 'b operation -> ('a, 'b) eq option
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
module Encoding : sig
|
2019-09-05 17:21:01 +04:00
|
|
|
type 'b case =
|
2020-02-12 20:40:17 +04:00
|
|
|
| Case : {
|
|
|
|
tag : int;
|
|
|
|
name : string;
|
|
|
|
encoding : 'a Data_encoding.t;
|
|
|
|
select : packed_contents -> 'b contents option;
|
|
|
|
proj : 'b contents -> 'a;
|
|
|
|
inj : 'a -> 'b contents;
|
|
|
|
}
|
|
|
|
-> 'b case
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val endorsement_case : Kind.endorsement case
|
|
|
|
|
|
|
|
val seed_nonce_revelation_case : Kind.seed_nonce_revelation case
|
|
|
|
|
|
|
|
val double_endorsement_evidence_case :
|
|
|
|
Kind.double_endorsement_evidence case
|
|
|
|
|
|
|
|
val double_baking_evidence_case : Kind.double_baking_evidence case
|
|
|
|
|
|
|
|
val activate_account_case : Kind.activate_account case
|
|
|
|
|
|
|
|
val proposals_case : Kind.proposals case
|
|
|
|
|
|
|
|
val ballot_case : Kind.ballot case
|
|
|
|
|
|
|
|
val reveal_case : Kind.reveal Kind.manager case
|
|
|
|
|
|
|
|
val transaction_case : Kind.transaction Kind.manager case
|
|
|
|
|
|
|
|
val origination_case : Kind.origination Kind.manager case
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val delegation_case : Kind.delegation Kind.manager case
|
|
|
|
|
|
|
|
module Manager_operations : sig
|
2019-09-05 17:21:01 +04:00
|
|
|
type 'b case =
|
2020-02-12 20:40:17 +04:00
|
|
|
| MCase : {
|
|
|
|
tag : int;
|
|
|
|
name : string;
|
|
|
|
encoding : 'a Data_encoding.t;
|
|
|
|
select :
|
|
|
|
packed_manager_operation -> 'kind manager_operation option;
|
|
|
|
proj : 'kind manager_operation -> 'a;
|
|
|
|
inj : 'a -> 'kind manager_operation;
|
|
|
|
}
|
|
|
|
-> 'kind case
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val reveal_case : Kind.reveal case
|
|
|
|
|
|
|
|
val transaction_case : Kind.transaction case
|
|
|
|
|
|
|
|
val origination_case : Kind.origination case
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val delegation_case : Kind.delegation case
|
|
|
|
end
|
2019-09-05 17:21:01 +04:00
|
|
|
end
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val of_list : packed_contents list -> packed_contents_list
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val to_list : packed_contents_list -> packed_contents list
|
2019-09-05 17:21:01 +04:00
|
|
|
end
|
|
|
|
|
|
|
|
module Roll : sig
|
|
|
|
type t = private int32
|
2020-02-12 20:40:17 +04:00
|
|
|
|
2019-09-05 17:21:01 +04:00
|
|
|
type roll = t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val encoding : roll Data_encoding.t
|
|
|
|
|
|
|
|
val snapshot_rolls : context -> context tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val cycle_end : context -> Cycle.t -> context tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val baking_rights_owner :
|
2019-09-05 17:21:01 +04:00
|
|
|
context -> Level.t -> priority:int -> public_key tzresult Lwt.t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val endorsement_rights_owner :
|
2019-09-05 17:21:01 +04:00
|
|
|
context -> Level.t -> slot:int -> public_key tzresult Lwt.t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val delegate_pubkey : context -> public_key_hash -> public_key tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val get_rolls :
|
2019-09-05 17:21:01 +04:00
|
|
|
context -> Signature.Public_key_hash.t -> roll list tzresult Lwt.t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val get_change :
|
|
|
|
context -> Signature.Public_key_hash.t -> Tez.t tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
end
|
|
|
|
|
|
|
|
module Commitment : sig
|
2020-02-12 20:40:17 +04:00
|
|
|
type t = {
|
|
|
|
blinded_public_key_hash : Blinded_public_key_hash.t;
|
|
|
|
amount : Tez.tez;
|
|
|
|
}
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val get_opt :
|
2019-09-05 17:21:01 +04:00
|
|
|
context -> Blinded_public_key_hash.t -> Tez.t option tzresult Lwt.t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val delete : context -> Blinded_public_key_hash.t -> context tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
end
|
|
|
|
|
|
|
|
module Bootstrap : sig
|
2020-02-12 20:40:17 +04:00
|
|
|
val cycle_end : context -> Cycle.t -> context tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
end
|
|
|
|
|
|
|
|
module Global : sig
|
2020-02-12 20:40:17 +04:00
|
|
|
val get_block_priority : context -> int tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val set_block_priority : context -> int -> context tzresult Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
end
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val prepare_first_block :
|
2019-09-05 17:21:01 +04:00
|
|
|
Context.t ->
|
2020-02-12 20:40:17 +04:00
|
|
|
typecheck:(context ->
|
|
|
|
Script.t ->
|
|
|
|
((Script.t * Contract.big_map_diff option) * context) tzresult
|
|
|
|
Lwt.t) ->
|
2019-09-05 17:21:01 +04:00
|
|
|
level:Int32.t ->
|
|
|
|
timestamp:Time.t ->
|
|
|
|
fitness:Fitness.t ->
|
|
|
|
context tzresult Lwt.t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val prepare :
|
2019-09-05 17:21:01 +04:00
|
|
|
Context.t ->
|
|
|
|
level:Int32.t ->
|
2019-10-17 13:45:27 +04:00
|
|
|
predecessor_timestamp:Time.t ->
|
2019-09-05 17:21:01 +04:00
|
|
|
timestamp:Time.t ->
|
|
|
|
fitness:Fitness.t ->
|
|
|
|
context tzresult Lwt.t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val finalize : ?commit_message:string -> context -> Updater.validation_result
|
|
|
|
|
|
|
|
val activate : context -> Protocol_hash.t -> context Lwt.t
|
|
|
|
|
|
|
|
val fork_test_chain : context -> Protocol_hash.t -> Time.t -> context Lwt.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val record_endorsement : context -> Signature.Public_key_hash.t -> context
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val allowed_endorsements :
|
2019-09-05 17:21:01 +04:00
|
|
|
context ->
|
|
|
|
(Signature.Public_key.t * int list * bool) Signature.Public_key_hash.Map.t
|
2020-02-12 20:40:17 +04:00
|
|
|
|
|
|
|
val init_endorsements :
|
2019-09-05 17:21:01 +04:00
|
|
|
context ->
|
|
|
|
(Signature.Public_key.t * int list * bool) Signature.Public_key_hash.Map.t ->
|
|
|
|
context
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val included_endorsements : context -> int
|
|
|
|
|
|
|
|
val reset_internal_nonce : context -> context
|
|
|
|
|
|
|
|
val fresh_internal_nonce : context -> (context * int) tzresult
|
|
|
|
|
|
|
|
val record_internal_nonce : context -> int -> context
|
|
|
|
|
|
|
|
val internal_nonce_already_recorded : context -> int -> bool
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val add_fees : context -> Tez.t -> context tzresult Lwt.t
|
|
|
|
|
|
|
|
val add_rewards : context -> Tez.t -> context tzresult Lwt.t
|
|
|
|
|
|
|
|
val add_deposit :
|
2019-09-05 17:21:01 +04:00
|
|
|
context -> Signature.Public_key_hash.t -> Tez.t -> context tzresult Lwt.t
|
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val get_fees : context -> Tez.t
|
|
|
|
|
|
|
|
val get_rewards : context -> Tez.t
|
|
|
|
|
|
|
|
val get_deposits : context -> Tez.t Signature.Public_key_hash.Map.t
|
2019-09-05 17:21:01 +04:00
|
|
|
|
2020-02-12 20:40:17 +04:00
|
|
|
val description : context Storage_description.t
|