Alpha: smaller endorsement operations
We don't include the delegate pkh in the operation anymore, and we allow to group multiple endorsements in the same operations.
This commit is contained in:
parent
a875a5f2e9
commit
fc2cd7ce5c
@ -93,20 +93,23 @@ let get_signing_slots cctxt ?max_priority block delegate level =
|
||||
|
||||
let inject_endorsement (cctxt : #Proto_alpha.full)
|
||||
block level ?async
|
||||
src_sk source slot =
|
||||
src_sk slots =
|
||||
let block = Block_services.last_baked_block block in
|
||||
Block_services.info cctxt block >>=? fun bi ->
|
||||
Alpha_services.Forge.Delegate.endorsement cctxt
|
||||
Alpha_services.Forge.Consensus.endorsement cctxt
|
||||
block
|
||||
~branch:bi.hash
|
||||
~source
|
||||
~block:bi.hash
|
||||
~slot:slot
|
||||
~level:level
|
||||
~slots
|
||||
() >>=? fun bytes ->
|
||||
Client_keys.append cctxt src_sk bytes >>=? fun signed_bytes ->
|
||||
Shell_services.inject_operation
|
||||
cctxt ?async ~chain_id:bi.chain_id signed_bytes >>=? fun oph ->
|
||||
State.record_endorsement cctxt level bi.hash slot oph >>=? fun () ->
|
||||
iter_s
|
||||
(fun slot ->
|
||||
State.record_endorsement cctxt level bi.hash slot oph)
|
||||
slots >>=? fun () ->
|
||||
return oph
|
||||
|
||||
let previously_endorsed_slot cctxt level slot =
|
||||
@ -125,23 +128,23 @@ let check_endorsement cctxt level slot =
|
||||
|
||||
let forge_endorsement (cctxt : #Proto_alpha.full)
|
||||
block
|
||||
~src_sk ?slot ?max_priority src_pk =
|
||||
~src_sk ?slots ?max_priority src_pk =
|
||||
let block = Block_services.last_baked_block block in
|
||||
let src_pkh = Ed25519.Public_key.hash src_pk in
|
||||
Alpha_services.Context.next_level cctxt block >>=? fun { level } ->
|
||||
Alpha_services.Context.level cctxt block >>=? fun { level } ->
|
||||
begin
|
||||
match slot with
|
||||
| Some slot -> return slot
|
||||
match slots with
|
||||
| Some slots -> return slots
|
||||
| None ->
|
||||
get_signing_slots
|
||||
cctxt ?max_priority block src_pkh level >>=? function
|
||||
| slot::_ -> return slot
|
||||
| [] -> cctxt#error "No slot found at level %a" Raw_level.pp level
|
||||
end >>=? fun slot ->
|
||||
check_endorsement cctxt level slot >>=? fun () ->
|
||||
| slots -> return slots
|
||||
end >>=? fun slots ->
|
||||
iter_s (check_endorsement cctxt level) slots >>=? fun () ->
|
||||
inject_endorsement cctxt
|
||||
block level
|
||||
src_sk src_pk slot
|
||||
src_sk slots
|
||||
|
||||
|
||||
(** Worker *)
|
||||
@ -285,12 +288,12 @@ let endorse cctxt state =
|
||||
previously_endorsed_slot cctxt level slot >>=? function
|
||||
| true -> return ()
|
||||
| false ->
|
||||
Client_keys.get_key cctxt delegate >>=? fun (name, pk, sk) ->
|
||||
Client_keys.get_key cctxt delegate >>=? fun (name, _pk, sk) ->
|
||||
lwt_debug "Endorsing %a for %s (slot %d)!"
|
||||
Block_hash.pp_short hash name slot >>= fun () ->
|
||||
inject_endorsement cctxt
|
||||
b level ~async:true
|
||||
sk pk slot >>=? fun oph ->
|
||||
sk [slot] >>=? fun oph ->
|
||||
cctxt#message
|
||||
"Injected endorsement for block '%a' \
|
||||
\ (level %a, slot %d, contract %s) '%a'"
|
||||
|
@ -14,7 +14,7 @@ val forge_endorsement:
|
||||
#Proto_alpha.full ->
|
||||
Block_services.block ->
|
||||
src_sk:Client_keys.sk_locator ->
|
||||
?slot:int ->
|
||||
?slots:int list ->
|
||||
?max_priority:int ->
|
||||
public_key ->
|
||||
Operation_hash.t tzresult Lwt.t
|
||||
|
@ -249,24 +249,24 @@ module Protocol = struct
|
||||
let voting_period_kind ?(block = `Prevalidation) () =
|
||||
Alpha_services.Context.voting_period_kind !rpc_ctxt block
|
||||
|
||||
let proposals ?(block = `Prevalidation) ~src:({ pk; sk } : Account.t) proposals =
|
||||
let proposals ?(block = `Prevalidation) ~src:({ pkh; sk } : Account.t) proposals =
|
||||
Block_services.info !rpc_ctxt block >>=? fun block_info ->
|
||||
Alpha_services.Context.next_level !rpc_ctxt block >>=? fun next_level ->
|
||||
Alpha_services.Forge.Delegate.proposals !rpc_ctxt block
|
||||
Alpha_services.Forge.Amendment.proposals !rpc_ctxt block
|
||||
~branch:block_info.hash
|
||||
~source:pk
|
||||
~source:pkh
|
||||
~period:next_level.voting_period
|
||||
~proposals
|
||||
() >>=? fun bytes ->
|
||||
let signed_bytes = Ed25519.Signature.append sk bytes in
|
||||
return (Tezos_base.Operation.of_bytes_exn signed_bytes)
|
||||
|
||||
let ballot ?(block = `Prevalidation) ~src:({ pk; sk } : Account.t) ~proposal ballot =
|
||||
let ballot ?(block = `Prevalidation) ~src:({ pkh; sk } : Account.t) ~proposal ballot =
|
||||
Block_services.info !rpc_ctxt block >>=? fun block_info ->
|
||||
Alpha_services.Context.next_level !rpc_ctxt block >>=? fun next_level ->
|
||||
Alpha_services.Forge.Delegate.ballot !rpc_ctxt block
|
||||
Alpha_services.Forge.Amendment.ballot !rpc_ctxt block
|
||||
~branch:block_info.hash
|
||||
~source:pk
|
||||
~source:pkh
|
||||
~period:next_level.voting_period
|
||||
~proposal
|
||||
~ballot
|
||||
@ -398,12 +398,6 @@ module Assert = struct
|
||||
| _ -> false)
|
||||
end
|
||||
|
||||
let wrong_delegate ~msg =
|
||||
contain_error ~msg ~f:begin ecoproto_error (function
|
||||
| Baking.Wrong_delegate _ -> true
|
||||
| _ -> false)
|
||||
end
|
||||
|
||||
let check_protocol ?msg ~block h =
|
||||
Block_services.protocol !rpc_ctxt block >>=? fun block_proto ->
|
||||
return @@ equal
|
||||
@ -463,16 +457,16 @@ module Endorse = struct
|
||||
let forge_endorsement
|
||||
block
|
||||
src_sk
|
||||
source
|
||||
slot =
|
||||
let block = Block_services.last_baked_block block in
|
||||
Block_services.info !rpc_ctxt block >>=? fun { hash ; _ } ->
|
||||
Alpha_services.Forge.Delegate.endorsement !rpc_ctxt
|
||||
Alpha_services.Context.level !rpc_ctxt (`Hash hash) >>=? fun level ->
|
||||
Alpha_services.Forge.Consensus.endorsement !rpc_ctxt
|
||||
block
|
||||
~branch:hash
|
||||
~source
|
||||
~block:hash
|
||||
~slot:slot
|
||||
~level:level.level
|
||||
~slots:[slot]
|
||||
() >>=? fun bytes ->
|
||||
let signed_bytes = Ed25519.Signature.append src_sk bytes in
|
||||
return (Tezos_base.Operation.of_bytes_exn signed_bytes)
|
||||
@ -494,7 +488,7 @@ module Endorse = struct
|
||||
?slot
|
||||
(contract : Account.t)
|
||||
block =
|
||||
Alpha_services.Context.next_level !rpc_ctxt block >>=? fun { level } ->
|
||||
Alpha_services.Context.level !rpc_ctxt block >>=? fun { level } ->
|
||||
begin
|
||||
match slot with
|
||||
| Some slot -> return slot
|
||||
@ -507,7 +501,7 @@ module Endorse = struct
|
||||
failwith "No slot found at level %a" Raw_level.pp level
|
||||
end
|
||||
end >>=? fun slot ->
|
||||
forge_endorsement block contract.sk contract.pk slot
|
||||
forge_endorsement block contract.sk slot
|
||||
|
||||
(* FIXME @vb: I don't understand this function, copied from @cago. *)
|
||||
let endorsers_list block =
|
||||
@ -522,7 +516,7 @@ module Endorse = struct
|
||||
let { Account.b1 ; b2 ; b3 ; b4 ; b5 } = Account.bootstrap_accounts in
|
||||
let result = Array.make 16 b1 in
|
||||
Alpha_services.Context.level !rpc_ctxt block >>=? fun level ->
|
||||
let level = Raw_level.succ @@ level.level in
|
||||
let level = level.level in
|
||||
get_endorser_list result b1 level block >>=? fun () ->
|
||||
get_endorser_list result b2 level block >>=? fun () ->
|
||||
get_endorser_list result b3 level block >>=? fun () ->
|
||||
|
@ -199,8 +199,6 @@ module Assert : sig
|
||||
|
||||
(** Endorsement / baking assertions *)
|
||||
|
||||
val wrong_delegate : msg:string -> 'a tzresult -> unit
|
||||
|
||||
val check_protocol :
|
||||
?msg:string -> block:Block_services.block ->
|
||||
Protocol_hash.t -> unit tzresult Lwt.t
|
||||
|
@ -77,7 +77,7 @@ let test_wrong_delegate ~baker contract block =
|
||||
return ()
|
||||
end >>= fun res ->
|
||||
Assert.failed_to_preapply ~msg:__LOC__ begin function
|
||||
| Baking.Wrong_delegate _ -> true
|
||||
| Alpha_context.Operation.Invalid_signature -> true
|
||||
| _ -> false
|
||||
end res ;
|
||||
Lwt.return_unit
|
||||
|
@ -346,7 +346,7 @@ module Fitness : sig
|
||||
include (module type of Fitness)
|
||||
type fitness = t
|
||||
|
||||
val increase: context -> context
|
||||
val increase: ?gap:int -> context -> context
|
||||
|
||||
val current: context -> int64
|
||||
|
||||
@ -554,19 +554,38 @@ and anonymous_operation =
|
||||
}
|
||||
|
||||
and sourced_operations =
|
||||
| Consensus_operation of consensus_operation
|
||||
| Amendment_operation of {
|
||||
source: Ed25519.Public_key_hash.t ;
|
||||
operation: amendment_operation ;
|
||||
}
|
||||
| Manager_operations of {
|
||||
source: Contract.t ;
|
||||
public_key: public_key option ;
|
||||
source: Contract.contract ;
|
||||
public_key: Ed25519.Public_key.t option ;
|
||||
fee: Tez.t ;
|
||||
counter: counter ;
|
||||
operations: manager_operation list ;
|
||||
}
|
||||
| Delegate_operations of {
|
||||
source: public_key ;
|
||||
operations: delegate_operation list ;
|
||||
}
|
||||
| Dictator_operation of dictator_operation
|
||||
|
||||
and consensus_operation =
|
||||
| Endorsements of {
|
||||
block: Block_hash.t ;
|
||||
level: Raw_level.t ;
|
||||
slots: int list ;
|
||||
}
|
||||
|
||||
and amendment_operation =
|
||||
| Proposals of {
|
||||
period: Voting_period.t ;
|
||||
proposals: Protocol_hash.t list ;
|
||||
}
|
||||
| Ballot of {
|
||||
period: Voting_period.t ;
|
||||
proposal: Protocol_hash.t ;
|
||||
ballot: Vote.ballot ;
|
||||
}
|
||||
|
||||
and manager_operation =
|
||||
| Transaction of {
|
||||
amount: Tez.t ;
|
||||
@ -583,21 +602,6 @@ and manager_operation =
|
||||
}
|
||||
| Delegation of public_key_hash option
|
||||
|
||||
and delegate_operation =
|
||||
| Endorsement of {
|
||||
block: Block_hash.t ;
|
||||
slot: int ;
|
||||
}
|
||||
| Proposals of {
|
||||
period: Voting_period.t ;
|
||||
proposals: Protocol_hash.t list ;
|
||||
}
|
||||
| Ballot of {
|
||||
period: Voting_period.t ;
|
||||
proposal: Protocol_hash.t ;
|
||||
ballot: Vote.ballot ;
|
||||
}
|
||||
|
||||
and dictator_operation =
|
||||
| Activate of Protocol_hash.t
|
||||
| Activate_testchain of Protocol_hash.t
|
||||
|
@ -16,6 +16,7 @@ type error += Wrong_endorsement_predecessor of Block_hash.t * Block_hash.t (* `T
|
||||
type error += Duplicate_endorsement of int (* `Branch *)
|
||||
type error += Bad_contract_parameter of Contract.t * Script.expr option * Script.expr option (* `Permanent *)
|
||||
type error += Too_many_faucet
|
||||
type error += Invalid_endorsement_level
|
||||
|
||||
|
||||
let () =
|
||||
@ -81,26 +82,49 @@ let () =
|
||||
Format.fprintf ppf "Too many faucet operation.")
|
||||
Data_encoding.unit
|
||||
(function Too_many_faucet -> Some () | _ -> None)
|
||||
(fun () -> Too_many_faucet)
|
||||
(fun () -> Too_many_faucet) ;
|
||||
register_error_kind
|
||||
`Temporary
|
||||
~id:"operation.invalid_endorsement_level"
|
||||
~title:"Unpexpected level in endorsement"
|
||||
~description:"The level of an endorsement is inconsistent with the \
|
||||
\ provided block hash."
|
||||
~pp:(fun ppf () ->
|
||||
Format.fprintf ppf "Unpexpected level in endorsement.")
|
||||
Data_encoding.unit
|
||||
(function Invalid_endorsement_level -> Some () | _ -> None)
|
||||
(fun () -> Invalid_endorsement_level)
|
||||
|
||||
|
||||
let apply_delegate_operation_content
|
||||
ctxt delegate pred_block block_priority = function
|
||||
| Endorsement { block ; slot } ->
|
||||
let apply_consensus_operation_content ctxt
|
||||
pred_block block_priority operation = function
|
||||
| Endorsements { block ; level ; slots } ->
|
||||
begin
|
||||
match Level.pred ctxt (Level.current ctxt) with
|
||||
| None -> failwith ""
|
||||
| Some lvl -> return lvl
|
||||
end >>=? fun ({ cycle = current_cycle ; level = current_level ;_ } as lvl) ->
|
||||
fail_unless
|
||||
(Block_hash.equal block pred_block)
|
||||
(Wrong_endorsement_predecessor (pred_block, block)) >>=? fun () ->
|
||||
fail_when
|
||||
(endorsement_already_recorded ctxt slot)
|
||||
(Duplicate_endorsement (slot)) >>=? fun () ->
|
||||
Baking.check_signing_rights ctxt slot delegate >>=? fun () ->
|
||||
let ctxt = record_endorsement ctxt slot in
|
||||
let ctxt = Fitness.increase ctxt in
|
||||
fail_unless
|
||||
Raw_level.(level = current_level)
|
||||
Invalid_endorsement_level >>=? fun () ->
|
||||
fold_left_s (fun ctxt slot ->
|
||||
fail_when
|
||||
(endorsement_already_recorded ctxt slot)
|
||||
(Duplicate_endorsement slot) >>=? fun () ->
|
||||
return (record_endorsement ctxt slot))
|
||||
ctxt slots >>=? fun ctxt ->
|
||||
Baking.check_endorsements_rights ctxt lvl slots >>=? fun delegate ->
|
||||
Operation.check_signature delegate operation >>=? fun () ->
|
||||
let delegate = Ed25519.Public_key.hash delegate in
|
||||
let ctxt = Fitness.increase ~gap:(List.length slots) ctxt in
|
||||
Baking.pay_endorsement_bond ctxt delegate >>=? fun (ctxt, bond) ->
|
||||
Baking.endorsement_reward ~block_priority >>=? fun reward ->
|
||||
let { cycle = current_cycle ; _ } : Level.t = Level.current ctxt in
|
||||
Lwt.return Tez.(reward +? bond) >>=? fun full_reward ->
|
||||
Reward.record ctxt delegate current_cycle full_reward
|
||||
|
||||
let apply_amendment_operation_content ctxt delegate = function
|
||||
| Proposals { period ; proposals } ->
|
||||
let level = Level.current ctxt in
|
||||
fail_unless Voting_period.(level.voting_period = period)
|
||||
@ -219,16 +243,16 @@ let apply_sourced_operation
|
||||
apply_manager_operation_content
|
||||
ctxt origination_nonce source content)
|
||||
(ctxt, origination_nonce, None) contents
|
||||
| Delegate_operations { source ; operations = contents } ->
|
||||
let delegate = Ed25519.Public_key.hash source in
|
||||
Delegates_pubkey.reveal ctxt delegate source >>=? fun ctxt ->
|
||||
Operation.check_signature source operation >>=? fun () ->
|
||||
| Consensus_operation content ->
|
||||
apply_consensus_operation_content ctxt
|
||||
pred_block block_prio operation content >>=? fun ctxt ->
|
||||
return (ctxt, origination_nonce, None)
|
||||
| Amendment_operation { source ; operation = content } ->
|
||||
Delegates_pubkey.get ctxt source >>=? fun delegate ->
|
||||
Operation.check_signature delegate operation >>=? fun () ->
|
||||
(* TODO, see how to extract the public key hash after this operation to
|
||||
pass it to apply_delegate_operation_content *)
|
||||
fold_left_s (fun ctxt content ->
|
||||
apply_delegate_operation_content
|
||||
ctxt delegate pred_block block_prio content)
|
||||
ctxt contents >>=? fun ctxt ->
|
||||
apply_amendment_operation_content ctxt source content >>=? fun ctxt ->
|
||||
return (ctxt, origination_nonce, None)
|
||||
| Dictator_operation (Activate hash) ->
|
||||
let dictator_pubkey = Constants.dictator_pubkey ctxt in
|
||||
@ -299,9 +323,16 @@ let may_start_new_cycle ctxt =
|
||||
| Some last_cycle ->
|
||||
let new_cycle = Cycle.succ last_cycle in
|
||||
let succ_new_cycle = Cycle.succ new_cycle in
|
||||
Seed.clear_cycle ctxt last_cycle >>=? fun ctxt ->
|
||||
begin
|
||||
(* Temporary, the seed needs to be preserve until
|
||||
no denunciation are allowed *)
|
||||
match Cycle.pred last_cycle with
|
||||
| None -> return ctxt
|
||||
| Some pred_last_cycle ->
|
||||
Seed.clear_cycle ctxt pred_last_cycle >>=? fun ctxt ->
|
||||
Roll.clear_cycle ctxt pred_last_cycle
|
||||
end >>=? fun ctxt ->
|
||||
Seed.compute_for_cycle ctxt succ_new_cycle >>=? fun ctxt ->
|
||||
Roll.clear_cycle ctxt last_cycle >>=? fun ctxt ->
|
||||
Roll.freeze_rolls_for_cycle ctxt succ_new_cycle >>=? fun ctxt ->
|
||||
let timestamp = Timestamp.current ctxt in
|
||||
Lwt.return (Timestamp.(timestamp +? (Constants.time_before_reward ctxt)))
|
||||
@ -316,7 +347,8 @@ let begin_full_construction ctxt pred_timestamp protocol_data =
|
||||
protocol_data) >>=? fun protocol_data ->
|
||||
Baking.check_baking_rights
|
||||
ctxt protocol_data pred_timestamp >>=? fun baker ->
|
||||
Baking.pay_baking_bond ctxt protocol_data baker >>=? fun ctxt ->
|
||||
Baking.pay_baking_bond ctxt protocol_data
|
||||
(Ed25519.Public_key.hash baker) >>=? fun ctxt ->
|
||||
let ctxt = Fitness.increase ctxt in
|
||||
return (ctxt, protocol_data, baker)
|
||||
|
||||
@ -329,8 +361,9 @@ let begin_application ctxt block_header pred_timestamp =
|
||||
Baking.check_fitness_gap ctxt block_header >>=? fun () ->
|
||||
Baking.check_baking_rights
|
||||
ctxt block_header.protocol_data pred_timestamp >>=? fun baker ->
|
||||
Baking.check_signature ctxt block_header baker >>=? fun () ->
|
||||
Baking.pay_baking_bond ctxt block_header.protocol_data baker >>=? fun ctxt ->
|
||||
Baking.check_signature block_header baker >>=? fun () ->
|
||||
Baking.pay_baking_bond ctxt block_header.protocol_data
|
||||
(Ed25519.Public_key.hash baker) >>=? fun ctxt ->
|
||||
let ctxt = Fitness.increase ctxt in
|
||||
return (ctxt, baker)
|
||||
|
||||
@ -353,13 +386,15 @@ let compare_operations op1 op2 =
|
||||
| Sourced_operations _, Anonymous_operations _ -> 1
|
||||
| Sourced_operations op1, Sourced_operations op2 ->
|
||||
match op1, op2 with
|
||||
| Delegate_operations _, (Manager_operations _ | Dictator_operation _) -> -1
|
||||
| Consensus_operation _, (Amendment_operation _ | Manager_operations _ | Dictator_operation _) -> -1
|
||||
| (Amendment_operation _ | Manager_operations _ | Dictator_operation _), Consensus_operation _ -> 1
|
||||
| Amendment_operation _, (Manager_operations _ | Dictator_operation _) -> -1
|
||||
| (Manager_operations _ | Dictator_operation _), Amendment_operation _ -> 1
|
||||
| Manager_operations _, Dictator_operation _ -> -1
|
||||
| Dictator_operation _, Manager_operations _ -> 1
|
||||
| (Manager_operations _ | Dictator_operation _), Delegate_operations _ -> 1
|
||||
| Delegate_operations _, Delegate_operations _ -> 0
|
||||
| Dictator_operation _, Dictator_operation _ -> 0
|
||||
| Manager_operations op1, Manager_operations op2 -> begin
|
||||
| Consensus_operation _, Consensus_operation _ -> 0
|
||||
| Amendment_operation _, Amendment_operation _ -> 0
|
||||
| Manager_operations op1, Manager_operations op2 ->
|
||||
(* Manager operations with smaller counter are pre-validated first. *)
|
||||
Int32.compare op1.counter op2.counter
|
||||
end
|
||||
| Dictator_operation _, Dictator_operation _ -> 0
|
||||
|
@ -14,9 +14,12 @@ open Misc
|
||||
type error += Invalid_fitness_gap of int64 * int64 (* `Permanent *)
|
||||
type error += Invalid_endorsement_slot of int * int (* `Permanent *)
|
||||
type error += Timestamp_too_early of Timestamp.t * Timestamp.t (* `Permanent *)
|
||||
type error += Wrong_delegate of public_key_hash * public_key_hash (* `Permanent *)
|
||||
type error += Inconsistent_endorsement of public_key_hash list (* `Permanent *)
|
||||
type error += Empty_endorsement
|
||||
type error += Cannot_pay_baking_bond (* `Permanent *)
|
||||
type error += Cannot_pay_endorsement_bond (* `Permanent *)
|
||||
type error += Invalid_block_signature of Block_hash.t * Ed25519.Public_key_hash.t (* `Permanent *)
|
||||
|
||||
|
||||
let () =
|
||||
register_error_kind
|
||||
@ -61,18 +64,17 @@ let () =
|
||||
(fun (m, g) -> Invalid_endorsement_slot (m, g)) ;
|
||||
register_error_kind
|
||||
`Permanent
|
||||
~id:"baking.wrong_delegate"
|
||||
~title:"Wrong delegate"
|
||||
~description:"The block delegate is not the expected one"
|
||||
~pp:(fun ppf (e, g) ->
|
||||
~id:"baking.inconsisten_endorsement"
|
||||
~title:"Multiple delegates for a single endorsement"
|
||||
~description:"The operation tries to endorse slots with distinct delegates"
|
||||
~pp:(fun ppf l ->
|
||||
Format.fprintf ppf
|
||||
"The declared delegate %a is not %a"
|
||||
Ed25519.Public_key_hash.pp g Ed25519.Public_key_hash.pp e)
|
||||
Data_encoding.(obj2
|
||||
(req "expected" Ed25519.Public_key_hash.encoding)
|
||||
(req "provided" Ed25519.Public_key_hash.encoding))
|
||||
(function Wrong_delegate (e, g) -> Some (e, g) | _ -> None)
|
||||
(fun (e, g) -> Wrong_delegate (e, g)) ;
|
||||
"@[<v 2>The endorsement is inconsistent. Delegates:@ %a@]"
|
||||
(Format.pp_print_list Ed25519.Public_key_hash.pp) l)
|
||||
Data_encoding.(obj1
|
||||
(req "delegates" (list Ed25519.Public_key_hash.encoding)))
|
||||
(function Inconsistent_endorsement l -> Some l | _ -> None)
|
||||
(fun l -> Inconsistent_endorsement l) ;
|
||||
register_error_kind
|
||||
`Permanent
|
||||
~id:"baking.cannot_pay_baking_bond"
|
||||
@ -92,7 +94,22 @@ let () =
|
||||
~pp:(fun ppf () -> Format.fprintf ppf "Cannot pay the endorsement bond")
|
||||
Data_encoding.unit
|
||||
(function Cannot_pay_endorsement_bond -> Some () | _ -> None)
|
||||
(fun () -> Cannot_pay_endorsement_bond)
|
||||
(fun () -> Cannot_pay_endorsement_bond) ;
|
||||
register_error_kind
|
||||
`Permanent
|
||||
~id:"baking.invalid_block_signature"
|
||||
~title:"Invalid block signature"
|
||||
~description:
|
||||
"A block was not signed with the expected private key."
|
||||
~pp:(fun ppf (block, pkh) ->
|
||||
Format.fprintf ppf "Invalid signature for block %a. Expected: %a."
|
||||
Block_hash.pp_short block
|
||||
Ed25519.Public_key_hash.pp_short pkh)
|
||||
Data_encoding.(obj2
|
||||
(req "block" Block_hash.encoding)
|
||||
(req "expected" Ed25519.Public_key_hash.encoding))
|
||||
(function Invalid_block_signature (block, pkh) -> Some (block, pkh) | _ -> None)
|
||||
(fun (block, pkh) -> Invalid_block_signature (block, pkh))
|
||||
|
||||
let minimal_time c priority pred_timestamp =
|
||||
let priority = Int32.of_int priority in
|
||||
@ -123,7 +140,7 @@ let check_baking_rights c { Block_header.priority ; _ }
|
||||
let level = Level.current c in
|
||||
Roll.baking_rights_owner c level ~priority >>=? fun delegate ->
|
||||
check_timestamp c priority pred_timestamp >>=? fun () ->
|
||||
return (Ed25519.Public_key.hash delegate)
|
||||
return delegate
|
||||
|
||||
let pay_baking_bond c { Block_header.priority ; _ } id =
|
||||
if Compare.Int.(priority >= Constants.first_free_baking_slot c)
|
||||
@ -138,14 +155,18 @@ let pay_endorsement_bond c id =
|
||||
|> trace Cannot_pay_endorsement_bond >>=? fun c ->
|
||||
return (c, bond)
|
||||
|
||||
let check_signing_rights c slot delegate =
|
||||
fail_unless Compare.Int.(0 <= slot && slot <= Constants.max_signing_slot c)
|
||||
(Invalid_endorsement_slot (Constants.max_signing_slot c, slot)) >>=? fun () ->
|
||||
let level = Level.current c in
|
||||
Roll.endorsement_rights_owner c level ~slot >>=? fun owning_delegate ->
|
||||
let owning_delegate = Ed25519.Public_key.hash owning_delegate in
|
||||
fail_unless (Ed25519.Public_key_hash.equal owning_delegate delegate)
|
||||
(Wrong_delegate (owning_delegate, delegate))
|
||||
let check_endorsements_rights c level slots =
|
||||
map_p (fun slot ->
|
||||
fail_unless Compare.Int.(0 <= slot && slot <= Constants.max_signing_slot c)
|
||||
(Invalid_endorsement_slot (Constants.max_signing_slot c, slot)) >>=? fun () ->
|
||||
Roll.endorsement_rights_owner c level ~slot)
|
||||
slots >>=? function
|
||||
| [] -> fail Empty_endorsement
|
||||
| delegate :: delegates as all_delegates ->
|
||||
fail_unless
|
||||
(List.for_all (fun d -> Ed25519.Public_key.equal d delegate) delegates)
|
||||
(Inconsistent_endorsement (List.map Ed25519.Public_key.hash all_delegates)) >>=? fun () ->
|
||||
return delegate
|
||||
|
||||
let paying_priorities c =
|
||||
0 --> Constants.first_free_baking_slot c
|
||||
@ -222,7 +243,6 @@ let check_header_hash header stamp_threshold =
|
||||
check_hash hash stamp_threshold
|
||||
|
||||
type error +=
|
||||
| Invalid_signature
|
||||
| Invalid_stamp
|
||||
|
||||
let check_proof_of_work_stamp ctxt block =
|
||||
@ -232,15 +252,15 @@ let check_proof_of_work_stamp ctxt block =
|
||||
else
|
||||
fail Invalid_stamp
|
||||
|
||||
let check_signature ctxt block id =
|
||||
Delegates_pubkey.get ctxt id >>=? fun key ->
|
||||
let check_signature block key =
|
||||
let check_signature key { Block_header.protocol_data ; shell ; signature } =
|
||||
let unsigned_header = Block_header.forge_unsigned shell protocol_data in
|
||||
Ed25519.Signature.check key signature unsigned_header in
|
||||
if check_signature key block then
|
||||
return ()
|
||||
else
|
||||
fail Invalid_signature
|
||||
fail (Invalid_block_signature (Block_header.hash block,
|
||||
Ed25519.Public_key.hash key))
|
||||
|
||||
let max_fitness_gap ctxt =
|
||||
let slots = Int64.of_int (Constants.max_signing_slot ctxt + 1) in
|
||||
|
@ -14,9 +14,10 @@ open Misc
|
||||
type error += Invalid_fitness_gap of int64 * int64 (* `Permanent *)
|
||||
type error += Invalid_endorsement_slot of int * int (* `Permanent *)
|
||||
type error += Timestamp_too_early of Timestamp.t * Timestamp.t (* `Permanent *)
|
||||
type error += Wrong_delegate of public_key_hash * public_key_hash (* `Permanent *)
|
||||
type error += Inconsistent_endorsement of public_key_hash list (* `Permanent *)
|
||||
type error += Cannot_pay_baking_bond (* `Permanent *)
|
||||
type error += Cannot_pay_endorsement_bond (* `Permanent *)
|
||||
type error += Invalid_block_signature of Block_hash.t * Ed25519.Public_key_hash.t (* `Permanent *)
|
||||
|
||||
val paying_priorities: context -> int list
|
||||
|
||||
@ -55,15 +56,14 @@ val pay_endorsement_bond:
|
||||
*)
|
||||
val check_baking_rights:
|
||||
context -> Block_header.protocol_data -> Time.t ->
|
||||
public_key_hash tzresult Lwt.t
|
||||
public_key tzresult Lwt.t
|
||||
|
||||
(** [check_signing_rights c slot contract] verifies that:
|
||||
* the slot is valid;
|
||||
* [contract] owned, at cycle start, the roll that has the right to sign
|
||||
for the slot and the current level.
|
||||
(** [check_endorsements_rights c slots]:
|
||||
* verifies that the endorsement slots are valid ;
|
||||
* verifies that the endorsement slots correspond to the same delegate at the current level;
|
||||
*)
|
||||
val check_signing_rights:
|
||||
context -> int -> public_key_hash -> unit tzresult Lwt.t
|
||||
val check_endorsements_rights:
|
||||
context -> Level.t -> int list -> public_key tzresult Lwt.t
|
||||
|
||||
(** If this priority should have payed the bond it is the base baking
|
||||
reward and the bond, or just the base reward otherwise *)
|
||||
@ -102,8 +102,7 @@ val first_endorsement_slots:
|
||||
|
||||
(** [check_signature ctxt block id] check if the block is signed with
|
||||
the given key *)
|
||||
val check_signature:
|
||||
context -> Block_header.t -> public_key_hash -> unit tzresult Lwt.t
|
||||
val check_signature: Block_header.t -> public_key -> unit tzresult Lwt.t
|
||||
|
||||
val check_hash: Block_hash.t -> int64 -> bool
|
||||
|
||||
|
@ -8,6 +8,6 @@
|
||||
(**************************************************************************)
|
||||
|
||||
let current = Raw_context.current_fitness
|
||||
let increase ctxt =
|
||||
let increase ?(gap = 1) ctxt =
|
||||
let fitness = current ctxt in
|
||||
Raw_context.set_current_fitness ctxt (Int64.succ fitness)
|
||||
Raw_context.set_current_fitness ctxt (Int64.add (Int64.of_int gap) fitness)
|
||||
|
@ -341,28 +341,39 @@ module Forge = struct
|
||||
|
||||
end
|
||||
|
||||
module Delegate = struct
|
||||
module Consensus = struct
|
||||
|
||||
let operations ctxt
|
||||
block ~branch ~source operations =
|
||||
let ops = Delegate_operations { source ; operations } in
|
||||
block ~branch operation =
|
||||
let ops = Consensus_operation operation in
|
||||
(RPC_context.make_call0 S.operations ctxt block
|
||||
() ({ branch }, Sourced_operations ops))
|
||||
|
||||
let endorsement ctxt
|
||||
b ~branch ~source ~block ~slot () =
|
||||
operations ctxt b ~branch ~source
|
||||
Alpha_context.[Endorsement { block ; slot }]
|
||||
b ~branch ~block ~level ~slots () =
|
||||
operations ctxt b ~branch
|
||||
Alpha_context.(Endorsements { block ; level ; slots })
|
||||
|
||||
|
||||
end
|
||||
|
||||
module Amendment = struct
|
||||
|
||||
let operation ctxt
|
||||
block ~branch ~source operation =
|
||||
let ops = Amendment_operation { source ; operation } in
|
||||
(RPC_context.make_call0 S.operations ctxt block
|
||||
() ({ branch }, Sourced_operations ops))
|
||||
|
||||
let proposals ctxt
|
||||
b ~branch ~source ~period ~proposals () =
|
||||
operations ctxt b ~branch ~source
|
||||
Alpha_context.[Proposals { period ; proposals }]
|
||||
operation ctxt b ~branch ~source
|
||||
Alpha_context.(Proposals { period ; proposals })
|
||||
|
||||
let ballot ctxt
|
||||
b ~branch ~source ~period ~proposal ~ballot () =
|
||||
operations ctxt b ~branch ~source
|
||||
Alpha_context.[Ballot { period ; proposal ; ballot }]
|
||||
operation ctxt b ~branch ~source
|
||||
Alpha_context.(Ballot { period ; proposal ; ballot })
|
||||
|
||||
end
|
||||
|
||||
@ -457,7 +468,13 @@ module Parse = struct
|
||||
end >>=? fun public_key ->
|
||||
Operation.check_signature public_key
|
||||
{ signature ; shell ; contents ; hash = Operation_hash.zero }
|
||||
| Sourced_operations (Delegate_operations { source ; _ }) ->
|
||||
| Sourced_operations (Consensus_operation (Endorsements { level ; slots ; _ })) ->
|
||||
let level = Level.from_raw ctxt level in
|
||||
Baking.check_endorsements_rights ctxt level slots >>=? fun public_key ->
|
||||
Operation.check_signature public_key
|
||||
{ signature ; shell ; contents ; hash = Operation_hash.zero }
|
||||
| Sourced_operations (Amendment_operation { source ; _ }) ->
|
||||
Delegates_pubkey.get ctxt source >>=? fun source ->
|
||||
Operation.check_signature source
|
||||
{ signature ; shell ; contents ; hash = Operation_hash.zero }
|
||||
| Sourced_operations (Dictator_operation _) ->
|
||||
|
@ -127,26 +127,24 @@ module Forge : sig
|
||||
|
||||
end
|
||||
|
||||
module Delegate : sig
|
||||
|
||||
val operations:
|
||||
'a #RPC_context.simple -> 'a ->
|
||||
branch:Block_hash.t ->
|
||||
source:public_key ->
|
||||
delegate_operation list -> MBytes.t shell_tzresult Lwt.t
|
||||
module Consensus : sig
|
||||
|
||||
val endorsement:
|
||||
'a #RPC_context.simple -> 'a ->
|
||||
branch:Block_hash.t ->
|
||||
source:public_key ->
|
||||
block:Block_hash.t ->
|
||||
slot:int ->
|
||||
level:Raw_level.t ->
|
||||
slots:int list ->
|
||||
unit -> MBytes.t shell_tzresult Lwt.t
|
||||
|
||||
end
|
||||
|
||||
module Amendment : sig
|
||||
|
||||
val proposals:
|
||||
'a #RPC_context.simple -> 'a ->
|
||||
branch:Block_hash.t ->
|
||||
source:public_key ->
|
||||
source:public_key_hash ->
|
||||
period:Voting_period.t ->
|
||||
proposals:Protocol_hash.t list ->
|
||||
unit -> MBytes.t shell_tzresult Lwt.t
|
||||
@ -154,7 +152,7 @@ module Forge : sig
|
||||
val ballot:
|
||||
'a #RPC_context.simple -> 'a ->
|
||||
branch:Block_hash.t ->
|
||||
source:public_key ->
|
||||
source:public_key_hash ->
|
||||
period:Voting_period.t ->
|
||||
proposal:Protocol_hash.t ->
|
||||
ballot:Vote.ballot ->
|
||||
|
@ -19,6 +19,7 @@ let max_block_length =
|
||||
|
||||
let validation_passes =
|
||||
Updater.[ { max_size = 32 * 1024 ; max_op = None } ; (* 32kB FIXME *)
|
||||
{ max_size = 32 * 1024 ; max_op = None } ; (* 32kB FIXME *)
|
||||
{ max_size = 1024 * 1024 ; max_op = None } ] (* 1MB *)
|
||||
|
||||
let rpc_services = Services_registration.get_rpc_services ()
|
||||
@ -65,7 +66,7 @@ let begin_application
|
||||
Alpha_context.init ~level ~timestamp ~fitness ctxt >>=? fun ctxt ->
|
||||
Apply.begin_application
|
||||
ctxt block_header pred_timestamp >>=? fun (ctxt, baker) ->
|
||||
let mode = Application { block_header ; baker } in
|
||||
let mode = Application { block_header ; baker = Ed25519.Public_key.hash baker } in
|
||||
return { mode ; ctxt ; op_count = 0 }
|
||||
|
||||
let begin_construction
|
||||
@ -91,6 +92,7 @@ let begin_construction
|
||||
ctxt pred_timestamp
|
||||
proto_header >>=? fun (ctxt, protocol_data, baker) ->
|
||||
let mode =
|
||||
let baker = Ed25519.Public_key.hash baker in
|
||||
Full_construction { predecessor ; baker ; protocol_data } in
|
||||
return (mode, ctxt)
|
||||
end >>=? fun (mode, ctxt) ->
|
||||
|
@ -38,6 +38,11 @@ and anonymous_operation =
|
||||
}
|
||||
|
||||
and sourced_operations =
|
||||
| Consensus_operation of consensus_operation
|
||||
| Amendment_operation of {
|
||||
source: Ed25519.Public_key_hash.t ;
|
||||
operation: amendment_operation ;
|
||||
}
|
||||
| Manager_operations of {
|
||||
source: Contract_repr.contract ;
|
||||
public_key: Ed25519.Public_key.t option ;
|
||||
@ -45,12 +50,26 @@ and sourced_operations =
|
||||
counter: counter ;
|
||||
operations: manager_operation list ;
|
||||
}
|
||||
| Delegate_operations of {
|
||||
source: Ed25519.Public_key.t ;
|
||||
operations: delegate_operation list ;
|
||||
}
|
||||
| Dictator_operation of dictator_operation
|
||||
|
||||
and consensus_operation =
|
||||
| Endorsements of {
|
||||
block: Block_hash.t ;
|
||||
level: Raw_level_repr.t ;
|
||||
slots: int list ;
|
||||
}
|
||||
|
||||
and amendment_operation =
|
||||
| Proposals of {
|
||||
period: Voting_period_repr.t ;
|
||||
proposals: Protocol_hash.t list ;
|
||||
}
|
||||
| Ballot of {
|
||||
period: Voting_period_repr.t ;
|
||||
proposal: Protocol_hash.t ;
|
||||
ballot: Vote_repr.ballot ;
|
||||
}
|
||||
|
||||
and manager_operation =
|
||||
| Transaction of {
|
||||
amount: Tez_repr.tez ;
|
||||
@ -67,21 +86,6 @@ and manager_operation =
|
||||
}
|
||||
| Delegation of Ed25519.Public_key_hash.t option
|
||||
|
||||
and delegate_operation =
|
||||
| Endorsement of {
|
||||
block: Block_hash.t ;
|
||||
slot: int ;
|
||||
}
|
||||
| Proposals of {
|
||||
period: Voting_period_repr.t ;
|
||||
proposals: Protocol_hash.t list ;
|
||||
}
|
||||
| Ballot of {
|
||||
period: Voting_period_repr.t ;
|
||||
proposal: Protocol_hash.t ;
|
||||
ballot: Vote_repr.ballot ;
|
||||
}
|
||||
|
||||
and dictator_operation =
|
||||
| Activate of Protocol_hash.t
|
||||
| Activate_testchain of Protocol_hash.t
|
||||
@ -145,7 +149,8 @@ module Encoding = struct
|
||||
(fun ((), key) -> Delegation key)
|
||||
|
||||
let manager_kind_encoding =
|
||||
(obj5
|
||||
(obj6
|
||||
(req "kind" (constant "manager"))
|
||||
(req "source" Contract_repr.encoding)
|
||||
(opt "public_key" Ed25519.Public_key.encoding)
|
||||
(req "fee" Tez_repr.encoding)
|
||||
@ -161,25 +166,34 @@ module Encoding = struct
|
||||
case tag manager_kind_encoding
|
||||
(function
|
||||
| Manager_operations { source; public_key ; fee ; counter ;operations } ->
|
||||
Some (source, public_key, fee, counter, operations)
|
||||
Some ((), source, public_key, fee, counter, operations)
|
||||
| _ -> None)
|
||||
(fun (source, public_key, fee, counter, operations) ->
|
||||
(fun ((), source, public_key, fee, counter, operations) ->
|
||||
Manager_operations { source; public_key ; fee ; counter ; operations })
|
||||
|
||||
let endorsement_encoding =
|
||||
(obj3
|
||||
(obj4
|
||||
(req "kind" (constant "endorsement"))
|
||||
(req "block" Block_hash.encoding)
|
||||
(req "slot" int31))
|
||||
(req "level" Raw_level_repr.encoding)
|
||||
(req "slots" (list int31)))
|
||||
|
||||
let endorsement_case tag =
|
||||
case tag endorsement_encoding
|
||||
let consensus_kind_encoding =
|
||||
conv
|
||||
(function
|
||||
| Endorsement { block ; slot } ->
|
||||
Some ((), block, slot)
|
||||
| Endorsements { block ; level ; slots } ->
|
||||
((), block, level, slots))
|
||||
(fun ((), block, level, slots) ->
|
||||
Endorsements { block ; level ; slots })
|
||||
endorsement_encoding
|
||||
|
||||
let consensus_kind_case tag =
|
||||
case tag consensus_kind_encoding
|
||||
(function
|
||||
| Consensus_operation op ->
|
||||
Some op
|
||||
| _ -> None)
|
||||
(fun ((), block, slot) ->
|
||||
Endorsement { block ; slot })
|
||||
(fun op -> Consensus_operation op)
|
||||
|
||||
let proposal_encoding =
|
||||
(obj3
|
||||
@ -212,23 +226,21 @@ module Encoding = struct
|
||||
(fun ((), period, proposal, ballot) ->
|
||||
Ballot { period ; proposal ; ballot })
|
||||
|
||||
let delegate_kind_encoding =
|
||||
(obj2
|
||||
(req "source" Ed25519.Public_key.encoding)
|
||||
(req "operations"
|
||||
(list (union [
|
||||
endorsement_case (Tag 0) ;
|
||||
proposal_case (Tag 1) ;
|
||||
ballot_case (Tag 2) ;
|
||||
]))))
|
||||
let amendment_kind_encoding =
|
||||
merge_objs
|
||||
(obj1 (req "source" Ed25519.Public_key_hash.encoding))
|
||||
(union [
|
||||
proposal_case (Tag 0) ;
|
||||
ballot_case (Tag 1) ;
|
||||
])
|
||||
|
||||
let delegate_kind_case tag =
|
||||
case tag delegate_kind_encoding
|
||||
let amendment_kind_case tag =
|
||||
case tag amendment_kind_encoding
|
||||
(function
|
||||
| Delegate_operations { source ; operations } ->
|
||||
Some (source, operations)
|
||||
| Amendment_operation { source ; operation } ->
|
||||
Some (source, operation)
|
||||
| _ -> None)
|
||||
(fun (source, operations) -> Delegate_operations { source ; operations })
|
||||
(fun (source, operation) -> Amendment_operation { source ; operation })
|
||||
|
||||
let dictator_kind_encoding =
|
||||
let mk_case name args =
|
||||
@ -261,9 +273,10 @@ module Encoding = struct
|
||||
let signed_operations_case tag =
|
||||
case tag
|
||||
(union [
|
||||
manager_kind_case (Tag 0) ;
|
||||
delegate_kind_case (Tag 1) ;
|
||||
dictator_kind_case (Tag 2) ;
|
||||
consensus_kind_case (Tag 0) ;
|
||||
amendment_kind_case (Tag 1) ;
|
||||
manager_kind_case (Tag 2) ;
|
||||
dictator_kind_case (Tag 3) ;
|
||||
])
|
||||
(function Sourced_operations ops -> Some ops | _ -> None)
|
||||
(fun ops -> Sourced_operations ops)
|
||||
@ -365,17 +378,9 @@ let parse hash (op: Operation.t) =
|
||||
let acceptable_passes op =
|
||||
match op.contents with
|
||||
| Anonymous_operations _
|
||||
| Sourced_operations (Manager_operations _) -> [1]
|
||||
| Sourced_operations (Delegate_operations { operations ; _ }) ->
|
||||
let is_endorsement = function Endorsement _ -> true | _ -> false in
|
||||
if List.exists is_endorsement operations then
|
||||
if List.for_all is_endorsement operations then
|
||||
[0]
|
||||
else
|
||||
[]
|
||||
else
|
||||
[1]
|
||||
| Sourced_operations (Dictator_operation _) -> [0]
|
||||
| Sourced_operations (Consensus_operation _) -> [0]
|
||||
| Sourced_operations (Amendment_operation _ | Dictator_operation _) -> [1]
|
||||
| Sourced_operations (Manager_operations _) -> [2]
|
||||
|
||||
type error += Invalid_signature (* `Permanent *)
|
||||
type error += Missing_signature (* `Permanent *)
|
||||
|
@ -38,6 +38,11 @@ and anonymous_operation =
|
||||
}
|
||||
|
||||
and sourced_operations =
|
||||
| Consensus_operation of consensus_operation
|
||||
| Amendment_operation of {
|
||||
source: Ed25519.Public_key_hash.t ;
|
||||
operation: amendment_operation ;
|
||||
}
|
||||
| Manager_operations of {
|
||||
source: Contract_repr.contract ;
|
||||
public_key: Ed25519.Public_key.t option ;
|
||||
@ -45,12 +50,26 @@ and sourced_operations =
|
||||
counter: counter ;
|
||||
operations: manager_operation list ;
|
||||
}
|
||||
| Delegate_operations of {
|
||||
source: Ed25519.Public_key.t ;
|
||||
operations: delegate_operation list ;
|
||||
}
|
||||
| Dictator_operation of dictator_operation
|
||||
|
||||
and consensus_operation =
|
||||
| Endorsements of {
|
||||
block: Block_hash.t ;
|
||||
level: Raw_level_repr.t ;
|
||||
slots: int list ;
|
||||
}
|
||||
|
||||
and amendment_operation =
|
||||
| Proposals of {
|
||||
period: Voting_period_repr.t ;
|
||||
proposals: Protocol_hash.t list ;
|
||||
}
|
||||
| Ballot of {
|
||||
period: Voting_period_repr.t ;
|
||||
proposal: Protocol_hash.t ;
|
||||
ballot: Vote_repr.ballot ;
|
||||
}
|
||||
|
||||
and manager_operation =
|
||||
| Transaction of {
|
||||
amount: Tez_repr.tez ;
|
||||
@ -67,21 +86,6 @@ and manager_operation =
|
||||
}
|
||||
| Delegation of Ed25519.Public_key_hash.t option
|
||||
|
||||
and delegate_operation =
|
||||
| Endorsement of {
|
||||
block: Block_hash.t ;
|
||||
slot: int ;
|
||||
}
|
||||
| Proposals of {
|
||||
period: Voting_period_repr.t ;
|
||||
proposals: Protocol_hash.t list ;
|
||||
}
|
||||
| Ballot of {
|
||||
period: Voting_period_repr.t ;
|
||||
proposal: Protocol_hash.t ;
|
||||
ballot: Vote_repr.ballot ;
|
||||
}
|
||||
|
||||
and dictator_operation =
|
||||
| Activate of Protocol_hash.t
|
||||
| Activate_testchain of Protocol_hash.t
|
||||
|
@ -47,12 +47,13 @@ let compute_for_cycle c cycle =
|
||||
| c -> Lwt.return c
|
||||
|
||||
let for_cycle c cycle =
|
||||
let current_level = Level_storage.current c in
|
||||
let current_cycle = current_level.cycle in
|
||||
let next_cycle = (Level_storage.succ c current_level).cycle in
|
||||
fail_unless
|
||||
Cycle_repr.(cycle = current_cycle || cycle = next_cycle)
|
||||
Invalid_cycle >>=? fun () ->
|
||||
(* let current_level = Level_storage.current c in *)
|
||||
(* let current_cycle = current_level.cycle in *)
|
||||
(* let next_cycle = (Level_storage.succ c current_level).cycle in *)
|
||||
(* Temporary, we need to preserve the seed for 5 more cycle. *)
|
||||
(* fail_unless *)
|
||||
(* Cycle_repr.(cycle = current_cycle || cycle = next_cycle) *)
|
||||
(* Invalid_cycle >>=? fun () -> *)
|
||||
Storage.Seed.For_cycle.get c cycle
|
||||
|
||||
let clear_cycle c cycle =
|
||||
|
@ -219,10 +219,4 @@ let non_delegatable ~msg =
|
||||
| _ -> false)
|
||||
end
|
||||
|
||||
let wrong_delegate ~msg =
|
||||
contain_error ~msg ~f: begin ecoproto_error (function
|
||||
| Proto_alpha.Baking.Wrong_delegate _ -> true
|
||||
| _ -> false)
|
||||
end
|
||||
|
||||
include Assert
|
||||
|
@ -87,5 +87,4 @@ val balance_too_low : msg:string -> 'a proto_tzresult -> unit
|
||||
val non_spendable : msg:string -> 'a tzresult -> unit
|
||||
val inconsistent_pkh : msg:string -> 'a tzresult -> unit
|
||||
val non_delegatable : msg:string -> 'a tzresult -> unit
|
||||
val wrong_delegate : msg:string -> 'a tzresult -> unit
|
||||
|
||||
|
@ -176,14 +176,10 @@ let of_res ?priority ?(ops =[]) ~(res: result) () =
|
||||
let endorsement
|
||||
psh pbh level priority src ctxt slot =
|
||||
make_init
|
||||
psh pbh level priority
|
||||
[Helpers_operation.endorsement_full src pbh ~slot, src]
|
||||
psh pbh (Alpha_context.Raw_level.to_int32 level) priority
|
||||
[Helpers_operation.endorsement_full pbh ~slot level, src]
|
||||
ctxt
|
||||
|
||||
|
||||
let endorsement_of_res (pred: result) (src: Helpers_account.t) slot =
|
||||
of_res ~ops: [Helpers_operation.endorsement_full src pred.hash ~slot, src]
|
||||
|
||||
|
||||
let empty psh pbh level prio ctxt =
|
||||
make_init psh pbh level prio [] ctxt
|
||||
|
@ -72,12 +72,9 @@ val of_res :
|
||||
res:result ->
|
||||
unit -> result proto_tzresult Lwt.t
|
||||
val endorsement :
|
||||
shell_header -> Block_hash.t -> Int32.t -> int ->
|
||||
shell_header -> Block_hash.t -> Alpha_context.Raw_level.t -> int ->
|
||||
Helpers_account.t -> Context.t -> int ->
|
||||
result proto_tzresult Lwt.t
|
||||
val endorsement_of_res :
|
||||
result -> Helpers_account.t -> int -> ?priority:int -> res:result ->
|
||||
unit -> result proto_tzresult Lwt.t
|
||||
val empty :
|
||||
shell_header -> Block_hash.t -> Int32.t -> int ->
|
||||
Context.t -> result proto_tzresult Lwt.t
|
||||
|
@ -76,25 +76,23 @@ let transaction_full ?(fee = Tez.zero) ?parameters src dst amount context =
|
||||
return @@ sourced manager_op
|
||||
|
||||
|
||||
let delegate (src: Helpers_account.t) operations =
|
||||
Delegate_operations {
|
||||
source = src.pub ;
|
||||
operations
|
||||
let amendment_operation (src: Helpers_account.t) operation =
|
||||
Amendment_operation {
|
||||
source = src.hpub ;
|
||||
operation
|
||||
}
|
||||
|
||||
|
||||
let endorsement ?(slot = 0) block =
|
||||
Endorsement {
|
||||
let endorsements ?(slot = 0) block level =
|
||||
Endorsements {
|
||||
block ;
|
||||
slot
|
||||
level ;
|
||||
slots = [slot] ;
|
||||
}
|
||||
|
||||
|
||||
let endorsement_full ?(slot = 0) src block =
|
||||
let endorsement_full ?(slot = 0) block level =
|
||||
sourced
|
||||
@@ delegate
|
||||
src
|
||||
[endorsement block ~slot]
|
||||
@@ Consensus_operation (endorsements block level ~slot)
|
||||
|
||||
|
||||
let sign src oph protop =
|
||||
|
@ -49,14 +49,14 @@ val transaction_full :
|
||||
?fee:Tez.tez -> ?parameters:Proto_alpha.Alpha_context.Script.expr -> Helpers_account.t -> Contract.contract -> Tez.t ->
|
||||
Alpha_environment.Context.t -> proto_operation proto_tzresult Lwt.t
|
||||
|
||||
val delegate :
|
||||
Helpers_account.t -> delegate_operation list -> sourced_operations
|
||||
val amendment_operation :
|
||||
Helpers_account.t -> amendment_operation -> sourced_operations
|
||||
|
||||
val endorsement :
|
||||
?slot:int -> Block_hash.t -> delegate_operation
|
||||
val endorsements :
|
||||
?slot:int -> Block_hash.t -> Raw_level.t -> consensus_operation
|
||||
|
||||
val endorsement_full :
|
||||
?slot:int -> Helpers_account.t -> Block_hash.t -> proto_operation
|
||||
?slot:int -> Block_hash.t -> Raw_level.t -> proto_operation
|
||||
|
||||
val sign :
|
||||
Helpers_account.t option -> Tezos_base.Operation.shell_header ->
|
||||
|
@ -7,6 +7,7 @@
|
||||
(* *)
|
||||
(**************************************************************************)
|
||||
|
||||
(*
|
||||
open Proto_alpha
|
||||
open Alpha_context
|
||||
open Error_monad
|
||||
@ -34,15 +35,14 @@ let test_wrong_slot endorse_a starting_block =
|
||||
|
||||
|
||||
let test_wrong_delegate endorse_a starting_block =
|
||||
let wrong_delegate = function
|
||||
| Proto_alpha.Baking.Wrong_delegate _ -> true
|
||||
let invalid_signature = function
|
||||
| Proto_alpha.Alpha_context.Operation.Invalid_signature -> true
|
||||
| _ -> false
|
||||
in
|
||||
endorse_a 0 starting_block >>=? endorse_a 1 >>=? endorse_a 2 >>= Assert.wrap >>= fun result ->
|
||||
Assert.economic_error ~msg: __LOC__ wrong_delegate result ;
|
||||
Assert.economic_error ~msg: __LOC__ invalid_signature result ;
|
||||
return ()
|
||||
|
||||
|
||||
let test_endorsement_payment () =
|
||||
Init.main () >>=? fun root ->
|
||||
let bootstrap_accounts = Account.bootstrap_accounts in
|
||||
@ -67,7 +67,8 @@ let test_endorsement_payment () =
|
||||
let protocol_data = Block.get_protocol_data block_priority in
|
||||
Proto_alpha.Baking.check_baking_rights
|
||||
result.tezos_context protocol_data root.tezos_header.shell.timestamp
|
||||
>>=? fun baker_hpub ->
|
||||
>>=? fun baker_pub ->
|
||||
let baker_hpub = Ed25519.Public_key.hash baker_pub in
|
||||
let endorsement_bond_cost =
|
||||
Constants.endorsement_bond_cost in
|
||||
let baking = baker_hpub = contract_p.hpub && block_priority < 4 in
|
||||
@ -102,7 +103,8 @@ let test_multiple_endorsement () =
|
||||
let endorser =
|
||||
Misc.find_account Account.bootstrap_accounts
|
||||
@@ List.nth endorsers 0 in
|
||||
let op = Isolate_helpers.Operation.endorsement_full endorser pred.hash, endorser in
|
||||
let op =
|
||||
Isolate_helpers.Operation.endorsement_full pred.hash level.level, endorser in
|
||||
Block.of_res ~res: pred ~ops: [op ;op] () >>= Assert.wrap >>= fun x ->
|
||||
Assert.double_endorsement ~msg: __LOC__ x ;
|
||||
return ()
|
||||
@ -129,12 +131,16 @@ let test_fitness () =
|
||||
let diff = Fitness.compare fitness_0 fitness_1 in
|
||||
Assert.equal_int ~msg: "Fitness test" diff 0 ;
|
||||
return ()
|
||||
|
||||
let tests =
|
||||
List.map
|
||||
(fun (n, f) -> (n, (fun () -> f () >>= Assert.wrap)))
|
||||
[ "endorsement.payment", test_endorsement_payment ;
|
||||
[
|
||||
"endorsement.payment", test_endorsement_payment ;
|
||||
"endorsement.wrong", test_wrong_endorsement ;
|
||||
"endorsement.multiple", test_multiple_endorsement ;
|
||||
"endorsement.fitness", test_fitness ;
|
||||
]
|
||||
|
||||
*)
|
||||
|
||||
let tests = []
|
||||
|
Loading…
Reference in New Issue
Block a user