Alpha: change counters from int32 to Z.t
This commit is contained in:
parent
5452d89f6c
commit
12b7a49f96
@ -13,6 +13,9 @@ type t
|
||||
val zero: t
|
||||
val one: t
|
||||
|
||||
val succ: t -> t
|
||||
(** Returns its argument plus one. *)
|
||||
|
||||
val abs: t -> t
|
||||
(** Absolute value. *)
|
||||
|
||||
|
@ -49,7 +49,7 @@ let reveal cctxt
|
||||
?branch ~source ~src_pk ~src_sk ~fee () =
|
||||
Alpha_services.Contract.counter
|
||||
cctxt (chain, block) source >>=? fun pcounter ->
|
||||
let counter = Int32.succ pcounter in
|
||||
let counter = Z.succ pcounter in
|
||||
Alpha_services.Contract.manager_key
|
||||
cctxt (chain, block) source >>=? fun (_, key) ->
|
||||
match key with
|
||||
@ -319,4 +319,3 @@ let activate_account
|
||||
(Activate_account _ as op, result) ->
|
||||
return (oph, op, result)
|
||||
| _ -> .
|
||||
|
||||
|
@ -354,7 +354,7 @@ let inject_manager_operation
|
||||
: (Operation_hash.t * kind Kind.manager contents * kind Kind.manager contents_result) tzresult Lwt.t =
|
||||
Alpha_services.Contract.counter
|
||||
cctxt (chain, block) source >>=? fun pcounter ->
|
||||
let counter = Int32.succ pcounter in
|
||||
let counter = Z.succ pcounter in
|
||||
Alpha_services.Contract.manager_key
|
||||
cctxt (chain, block) source >>=? fun (_, key) ->
|
||||
let is_reveal : type kind. kind manager_operation -> bool = function
|
||||
@ -367,7 +367,7 @@ let inject_manager_operation
|
||||
(Manager_operation { source ; fee = Tez.zero ; counter ;
|
||||
gas_limit = Z.zero ; storage_limit = 0L ;
|
||||
operation = Reveal src_pk },
|
||||
Single (Manager_operation { source ; fee ; counter = Int32.succ counter ;
|
||||
Single (Manager_operation { source ; fee ; counter = Z.succ counter ;
|
||||
gas_limit ; storage_limit ; operation })) in
|
||||
inject_operation cctxt ~chain ~block ?confirmations
|
||||
?branch ~src_sk contents >>=? fun (oph, op, result) ->
|
||||
@ -387,4 +387,3 @@ let inject_manager_operation
|
||||
| Single_and_result (Manager_operation _ as op, result) ->
|
||||
return (oph, op, result)
|
||||
| _ -> assert false (* Grrr... *)
|
||||
|
||||
|
@ -216,13 +216,13 @@ let pp_manager_operation_contents_and_result ppf
|
||||
"@[<v 0>@[<v 2>Manager signed operations:@,\
|
||||
From: %a@,\
|
||||
Fee to the baker: %s%a@,\
|
||||
Expected counter: %ld@,\
|
||||
Expected counter: %s@,\
|
||||
Gas limit: %s@,\
|
||||
Storage limit: %Ld bytes"
|
||||
Contract.pp source
|
||||
Client_proto_args.tez_sym
|
||||
Tez.pp fee
|
||||
counter
|
||||
(Z.to_string counter)
|
||||
(Z.to_string gas_limit)
|
||||
storage_limit ;
|
||||
begin match balance_updates with
|
||||
|
@ -519,7 +519,7 @@ module Contract : sig
|
||||
val get_storage:
|
||||
context -> contract -> (context * Script.expr option) tzresult Lwt.t
|
||||
|
||||
val get_counter: context -> contract -> int32 tzresult Lwt.t
|
||||
val get_counter: context -> contract -> Z.t tzresult Lwt.t
|
||||
val get_balance:
|
||||
context -> contract -> Tez.t tzresult Lwt.t
|
||||
|
||||
@ -569,7 +569,7 @@ module Contract : sig
|
||||
context -> contract -> context tzresult Lwt.t
|
||||
|
||||
val check_counter_increment:
|
||||
context -> contract -> int32 -> unit tzresult Lwt.t
|
||||
context -> contract -> Z.t -> unit tzresult Lwt.t
|
||||
|
||||
module Big_map : sig
|
||||
val mem:
|
||||
@ -851,7 +851,7 @@ and _ manager_operation =
|
||||
| Delegation :
|
||||
Signature.Public_key_hash.t option -> Kind.delegation manager_operation
|
||||
|
||||
and counter = Int32.t
|
||||
and counter = Z.t
|
||||
|
||||
type 'kind internal_operation = {
|
||||
source: Contract.contract ;
|
||||
|
@ -17,7 +17,7 @@ type info = {
|
||||
balance: Tez.t ;
|
||||
spendable: bool ;
|
||||
delegate: bool * public_key_hash option ;
|
||||
counter: int32 ;
|
||||
counter: counter ;
|
||||
script: Script.t option ;
|
||||
}
|
||||
|
||||
@ -40,7 +40,7 @@ let info_encoding =
|
||||
(req "setable" bool)
|
||||
(opt "value" Signature.Public_key_hash.encoding))
|
||||
(opt "script" Script.encoding)
|
||||
(req "counter" int32)
|
||||
(req "counter" n)
|
||||
|
||||
module S = struct
|
||||
|
||||
@ -80,7 +80,7 @@ module S = struct
|
||||
RPC_service.get_service
|
||||
~description: "Access the counter of a contract, if any."
|
||||
~query: RPC_query.empty
|
||||
~output: int32
|
||||
~output: z
|
||||
RPC_path.(custom_root /: Contract.rpc_arg / "counter")
|
||||
|
||||
let spendable =
|
||||
|
@ -17,7 +17,7 @@ type info = {
|
||||
balance: Tez.t ;
|
||||
spendable: bool ;
|
||||
delegate: bool * public_key_hash option ;
|
||||
counter: int32 ;
|
||||
counter: counter ;
|
||||
script: Script.t option ;
|
||||
}
|
||||
|
||||
@ -48,7 +48,7 @@ val is_spendable:
|
||||
'a #RPC_context.simple -> 'a -> Contract.t -> bool shell_tzresult Lwt.t
|
||||
|
||||
val counter:
|
||||
'a #RPC_context.simple -> 'a -> Contract.t -> int32 shell_tzresult Lwt.t
|
||||
'a #RPC_context.simple -> 'a -> Contract.t -> counter shell_tzresult Lwt.t
|
||||
|
||||
val script:
|
||||
'a #RPC_context.simple -> 'a -> Contract.t -> Script.t shell_tzresult Lwt.t
|
||||
|
@ -9,8 +9,8 @@
|
||||
|
||||
type error +=
|
||||
| Balance_too_low of Contract_repr.contract * Tez_repr.t * Tez_repr.t (* `Temporary *)
|
||||
| Counter_in_the_past of Contract_repr.contract * int32 * int32 (* `Branch *)
|
||||
| Counter_in_the_future of Contract_repr.contract * int32 * int32 (* `Temporary *)
|
||||
| Counter_in_the_past of Contract_repr.contract * Z.t * Z.t (* `Branch *)
|
||||
| Counter_in_the_future of Contract_repr.contract * Z.t * Z.t (* `Temporary *)
|
||||
| Unspendable_contract of Contract_repr.contract (* `Permanent *)
|
||||
| Non_existing_contract of Contract_repr.contract (* `Temporary *)
|
||||
| Empty_implicit_contract of Signature.Public_key_hash.t (* `Temporary *)
|
||||
@ -54,13 +54,15 @@ let () =
|
||||
~description:"An operation assumed a contract counter in the future"
|
||||
~pp:(fun ppf (contract, exp, found) ->
|
||||
Format.fprintf ppf
|
||||
"Counter %ld not yet reached for contract %a (expected %ld)"
|
||||
found Contract_repr.pp contract exp)
|
||||
"Counter %s not yet reached for contract %a (expected %s)"
|
||||
(Z.to_string found)
|
||||
Contract_repr.pp contract
|
||||
(Z.to_string exp))
|
||||
Data_encoding.
|
||||
(obj3
|
||||
(req "contract" Contract_repr.encoding)
|
||||
(req "expected" int32)
|
||||
(req "found" int32))
|
||||
(req "expected" z)
|
||||
(req "found" z))
|
||||
(function Counter_in_the_future (c, x, y) -> Some (c, x, y) | _ -> None)
|
||||
(fun (c, x, y) -> Counter_in_the_future (c, x, y)) ;
|
||||
register_error_kind
|
||||
@ -70,13 +72,15 @@ let () =
|
||||
~description:"An operation assumed a contract counter in the past"
|
||||
~pp:(fun ppf (contract, exp, found) ->
|
||||
Format.fprintf ppf
|
||||
"Counter %ld already used for contract %a (expected %ld)"
|
||||
found Contract_repr.pp contract exp)
|
||||
"Counter %s already used for contract %a (expected %s)"
|
||||
(Z.to_string found)
|
||||
Contract_repr.pp contract
|
||||
(Z.to_string exp))
|
||||
Data_encoding.
|
||||
(obj3
|
||||
(req "contract" Contract_repr.encoding)
|
||||
(req "expected" int32)
|
||||
(req "found" int32))
|
||||
(req "expected" z)
|
||||
(req "found" z))
|
||||
(function Counter_in_the_past (c, x, y) -> Some (c, x, y) | _ -> None)
|
||||
(fun (c, x, y) -> Counter_in_the_past (c, x, y)) ;
|
||||
register_error_kind
|
||||
@ -200,7 +204,7 @@ let update_script_big_map c contract = function
|
||||
let create_base c contract
|
||||
~balance ~manager ~delegate ?script ~spendable ~delegatable =
|
||||
(match Contract_repr.is_implicit contract with
|
||||
| None -> return 0l
|
||||
| None -> return Z.zero
|
||||
| Some _ -> Storage.Contract.Global_counter.get c) >>=? fun counter ->
|
||||
Storage.Contract.Balance.init c contract balance >>=? fun c ->
|
||||
Storage.Contract.Manager.init c contract (Manager_repr.Hash manager) >>=? fun c ->
|
||||
@ -292,19 +296,19 @@ let originated_from_current_nonce ~since: ctxt_since ~until: ctxt_until =
|
||||
|
||||
let check_counter_increment c contract counter =
|
||||
Storage.Contract.Counter.get c contract >>=? fun contract_counter ->
|
||||
let expected = Int32.succ contract_counter in
|
||||
if Compare.Int32.(expected = counter)
|
||||
let expected = Z.succ contract_counter in
|
||||
if Compare.Z.(expected = counter)
|
||||
then return ()
|
||||
else if Compare.Int32.(expected > counter) then
|
||||
else if Compare.Z.(expected > counter) then
|
||||
fail (Counter_in_the_past (contract, expected, counter))
|
||||
else
|
||||
fail (Counter_in_the_future (contract, expected, counter))
|
||||
|
||||
let increment_counter c contract =
|
||||
Storage.Contract.Global_counter.get c >>=? fun global_counter ->
|
||||
Storage.Contract.Global_counter.set c (Int32.succ global_counter) >>=? fun c ->
|
||||
Storage.Contract.Global_counter.set c (Z.succ global_counter) >>=? fun c ->
|
||||
Storage.Contract.Counter.get c contract >>=? fun contract_counter ->
|
||||
Storage.Contract.Counter.set c contract (Int32.succ contract_counter)
|
||||
Storage.Contract.Counter.set c contract (Z.succ contract_counter)
|
||||
|
||||
let get_script c contract =
|
||||
Storage.Contract.Code.get_option c contract >>=? fun (c, code) ->
|
||||
@ -450,7 +454,7 @@ let spend c contract amount =
|
||||
else spend_from_script c contract amount
|
||||
|
||||
let init c =
|
||||
Storage.Contract.Global_counter.init c 0l
|
||||
Storage.Contract.Global_counter.init c Z.zero
|
||||
|
||||
let used_storage_space c contract =
|
||||
Storage.Contract.Used_storage_space.get_option c contract >>=? function
|
||||
|
@ -9,8 +9,8 @@
|
||||
|
||||
type error +=
|
||||
| Balance_too_low of Contract_repr.contract * Tez_repr.t * Tez_repr.t (* `Temporary *)
|
||||
| Counter_in_the_past of Contract_repr.contract * int32 * int32 (* `Branch *)
|
||||
| Counter_in_the_future of Contract_repr.contract * int32 * int32 (* `Temporary *)
|
||||
| Counter_in_the_past of Contract_repr.contract * Z.t * Z.t (* `Branch *)
|
||||
| Counter_in_the_future of Contract_repr.contract * Z.t * Z.t (* `Temporary *)
|
||||
| Unspendable_contract of Contract_repr.contract (* `Permanent *)
|
||||
| Non_existing_contract of Contract_repr.contract (* `Temporary *)
|
||||
| Empty_implicit_contract of Signature.Public_key_hash.t (* `Temporary *)
|
||||
@ -30,7 +30,7 @@ val must_be_allocated: Raw_context.t -> Contract_repr.t -> unit tzresult Lwt.t
|
||||
val list: Raw_context.t -> Contract_repr.t list Lwt.t
|
||||
|
||||
val check_counter_increment:
|
||||
Raw_context.t -> Contract_repr.t -> int32 -> unit tzresult Lwt.t
|
||||
Raw_context.t -> Contract_repr.t -> Z.t -> unit tzresult Lwt.t
|
||||
|
||||
val increment_counter:
|
||||
Raw_context.t -> Contract_repr.t -> Raw_context.t tzresult Lwt.t
|
||||
@ -53,7 +53,7 @@ val reveal_manager_key:
|
||||
Raw_context.t tzresult Lwt.t
|
||||
|
||||
val get_balance: Raw_context.t -> Contract_repr.t -> Tez_repr.t tzresult Lwt.t
|
||||
val get_counter: Raw_context.t -> Contract_repr.t -> int32 tzresult Lwt.t
|
||||
val get_counter: Raw_context.t -> Contract_repr.t -> Z.t tzresult Lwt.t
|
||||
|
||||
val get_script:
|
||||
Raw_context.t -> Contract_repr.t -> (Raw_context.t * Script_repr.t option) tzresult Lwt.t
|
||||
|
@ -64,7 +64,7 @@ module Forge : sig
|
||||
branch:Block_hash.t ->
|
||||
source:Contract.t ->
|
||||
?sourcePubKey:public_key ->
|
||||
counter:int32 ->
|
||||
counter:counter ->
|
||||
fee:Tez.t ->
|
||||
gas_limit:Z.t ->
|
||||
storage_limit:Int64.t ->
|
||||
@ -75,7 +75,7 @@ module Forge : sig
|
||||
branch:Block_hash.t ->
|
||||
source:Contract.t ->
|
||||
sourcePubKey:public_key ->
|
||||
counter:int32 ->
|
||||
counter:counter ->
|
||||
fee:Tez.t ->
|
||||
unit -> MBytes.t shell_tzresult Lwt.t
|
||||
|
||||
@ -84,7 +84,7 @@ module Forge : sig
|
||||
branch:Block_hash.t ->
|
||||
source:Contract.t ->
|
||||
?sourcePubKey:public_key ->
|
||||
counter:int32 ->
|
||||
counter:counter ->
|
||||
amount:Tez.t ->
|
||||
destination:Contract.t ->
|
||||
?parameters:Script.expr ->
|
||||
@ -98,7 +98,7 @@ module Forge : sig
|
||||
branch:Block_hash.t ->
|
||||
source:Contract.t ->
|
||||
?sourcePubKey:public_key ->
|
||||
counter:int32 ->
|
||||
counter:counter ->
|
||||
managerPubKey:public_key_hash ->
|
||||
balance:Tez.t ->
|
||||
?spendable:bool ->
|
||||
@ -115,7 +115,7 @@ module Forge : sig
|
||||
branch:Block_hash.t ->
|
||||
source:Contract.t ->
|
||||
?sourcePubKey:public_key ->
|
||||
counter:int32 ->
|
||||
counter:counter ->
|
||||
fee:Tez.t ->
|
||||
public_key_hash option ->
|
||||
MBytes.t shell_tzresult Lwt.t
|
||||
|
@ -245,13 +245,13 @@ let compare_operations op1 op2 =
|
||||
|
||||
(* Manager operations with smaller counter are pre-validated first. *)
|
||||
| Single (Manager_operation op1), Single (Manager_operation op2) ->
|
||||
Int32.compare op1.counter op2.counter
|
||||
Z.compare op1.counter op2.counter
|
||||
| Cons (Manager_operation op1, _), Single (Manager_operation op2) ->
|
||||
Int32.compare op1.counter op2.counter
|
||||
Z.compare op1.counter op2.counter
|
||||
| Single (Manager_operation op1), Cons (Manager_operation op2, _) ->
|
||||
Int32.compare op1.counter op2.counter
|
||||
Z.compare op1.counter op2.counter
|
||||
| Cons (Manager_operation op1, _), Cons (Manager_operation op2, _) ->
|
||||
Int32.compare op1.counter op2.counter
|
||||
Z.compare op1.counter op2.counter
|
||||
|
||||
let init ctxt block_header =
|
||||
let level = block_header.Block_header.level in
|
||||
|
@ -111,7 +111,7 @@ and _ manager_operation =
|
||||
| Delegation :
|
||||
Signature.Public_key_hash.t option -> Kind.delegation manager_operation
|
||||
|
||||
and counter = Int32.t
|
||||
and counter = Z.t
|
||||
|
||||
let manager_kind : type kind. kind manager_operation -> kind Kind.manager =
|
||||
function
|
||||
@ -472,7 +472,7 @@ module Encoding = struct
|
||||
(obj5
|
||||
(req "source" Contract_repr.encoding)
|
||||
(req "fee" Tez_repr.encoding)
|
||||
(req "counter" int32)
|
||||
(req "counter" z)
|
||||
(req "gas_limit" z)
|
||||
(req "storage_limit" int64))
|
||||
|
||||
|
@ -112,7 +112,7 @@ and _ manager_operation =
|
||||
| Delegation :
|
||||
Signature.Public_key_hash.t option -> Kind.delegation manager_operation
|
||||
|
||||
and counter = Int32.t
|
||||
and counter = Z.t
|
||||
|
||||
type 'kind internal_operation = {
|
||||
source: Contract_repr.contract ;
|
||||
|
@ -19,6 +19,11 @@ module Int32 = struct
|
||||
let encoding = Data_encoding.int32
|
||||
end
|
||||
|
||||
module Z = struct
|
||||
type t = Z.t
|
||||
let encoding = Data_encoding.z
|
||||
end
|
||||
|
||||
module Int64 = struct
|
||||
type t = Int64.t
|
||||
let encoding = Data_encoding.int64
|
||||
@ -84,7 +89,7 @@ module Contract = struct
|
||||
Make_single_data_storage
|
||||
(Raw_context)
|
||||
(struct let name = ["global_counter"] end)
|
||||
(Int32)
|
||||
(Z)
|
||||
|
||||
module Indexed_context =
|
||||
Make_indexed_subcontext
|
||||
@ -158,7 +163,7 @@ module Contract = struct
|
||||
module Counter =
|
||||
Indexed_context.Make_map
|
||||
(struct let name = ["counter"] end)
|
||||
(Int32)
|
||||
(Z)
|
||||
|
||||
module Code =
|
||||
Indexed_context.Make_carbonated_map
|
||||
|
@ -90,9 +90,9 @@ module Contract : sig
|
||||
module `Contract`. *)
|
||||
|
||||
module Global_counter : sig
|
||||
val get : Raw_context.t -> int32 tzresult Lwt.t
|
||||
val set : Raw_context.t -> int32 -> Raw_context.t tzresult Lwt.t
|
||||
val init : Raw_context.t -> int32 -> Raw_context.t tzresult Lwt.t
|
||||
val get : Raw_context.t -> Z.t tzresult Lwt.t
|
||||
val set : Raw_context.t -> Z.t -> Raw_context.t tzresult Lwt.t
|
||||
val init : Raw_context.t -> Z.t -> Raw_context.t tzresult Lwt.t
|
||||
end
|
||||
|
||||
(** The domain of alive contracts *)
|
||||
@ -159,7 +159,7 @@ module Contract : sig
|
||||
|
||||
module Counter : Indexed_data_storage
|
||||
with type key = Contract_repr.t
|
||||
and type value = int32
|
||||
and type value = Z.t
|
||||
and type t := Raw_context.t
|
||||
|
||||
module Code : Non_iterable_indexed_carbonated_data_storage
|
||||
|
@ -38,7 +38,7 @@ module Contract : sig
|
||||
deposit, fees ot rewards. *)
|
||||
val balance: ?kind:balance_kind -> t -> Contract.t -> Tez.t tzresult Lwt.t
|
||||
|
||||
val counter: t -> Contract.t -> int32 tzresult Lwt.t
|
||||
val counter: t -> Contract.t -> Z.t tzresult Lwt.t
|
||||
val manager: t -> Contract.t -> Account.t tzresult Lwt.t
|
||||
val is_manager_key_revealed: t -> Contract.t -> bool tzresult Lwt.t
|
||||
|
||||
|
@ -55,7 +55,7 @@ let manager_operation
|
||||
Context.Contract.counter ctxt source >>=? fun counter ->
|
||||
Context.Contract.manager ctxt source >>=? fun account ->
|
||||
let public_key = Option.unopt ~default:account.pk public_key in
|
||||
let counter = Int32.succ counter in
|
||||
let counter = Z.succ counter in
|
||||
Context.Contract.is_manager_key_revealed ctxt source >>=? function
|
||||
| true ->
|
||||
let op =
|
||||
@ -82,7 +82,7 @@ let manager_operation
|
||||
Manager_operation {
|
||||
source ;
|
||||
fee ;
|
||||
counter = Int32.succ counter ;
|
||||
counter = Z.succ counter ;
|
||||
operation ;
|
||||
gas_limit ;
|
||||
storage_limit ;
|
||||
@ -94,7 +94,7 @@ let revelation ctxt public_key =
|
||||
let source = Contract.implicit_contract pkh in
|
||||
Context.Contract.counter ctxt source >>=? fun counter ->
|
||||
Context.Contract.manager ctxt source >>=? fun account ->
|
||||
let counter = Int32.succ counter in
|
||||
let counter = Z.succ counter in
|
||||
let sop =
|
||||
Contents_list
|
||||
(Single
|
||||
|
Loading…
Reference in New Issue
Block a user