mining -> baking

This commit is contained in:
Arthur Breitman 2017-11-01 04:07:33 -07:00
parent 108fe7799f
commit 4fb3874fea
26 changed files with 203 additions and 203 deletions

View File

@ -50,7 +50,7 @@ let block_forged ?prev ops =
| Ok nonce -> nonce in
Block_repr.forge_header (block ops)
Block_repr.{
mining_slot = {level = Raw_level_repr.of_int32_exn 1l ; priority = 0l } ;
baking_slot = {level = Raw_level_repr.of_int32_exn 1l ; priority = 0l } ;
seed_nonce_hash = Proto.Nonce_storage.hash (generate_seed_nonce ());
proof_of_work_nonce = generate_proof_of_work_nonce () ;
}

View File

@ -10,33 +10,33 @@
open Client_commands
open Logging.Client.Mining
let run cctxt ?max_priority ~delay ?min_date delegates ~endorsement ~denunciation ~mining =
let run cctxt ?max_priority ~delay ?min_date delegates ~endorsement ~denunciation ~baking =
(* TODO really detach... *)
let endorsement =
if endorsement then
Client_mining_blocks.monitor
Client_baking_blocks.monitor
cctxt.rpc_config ?min_date ~min_heads:1 () >>=? fun block_stream ->
Client_mining_endorsement.create cctxt ~delay delegates block_stream >>= fun () ->
Client_baking_endorsement.create cctxt ~delay delegates block_stream >>= fun () ->
return ()
else
return ()
in
let denunciation =
if denunciation then
Client_mining_operations.monitor_endorsement
Client_baking_operations.monitor_endorsement
cctxt.rpc_config >>=? fun endorsement_stream ->
Client_mining_denunciation.create cctxt endorsement_stream >>= fun () ->
Client_baking_denunciation.create cctxt endorsement_stream >>= fun () ->
return ()
else
return ()
in
let forge =
if mining then begin
Client_mining_blocks.monitor
if baking then begin
Client_baking_blocks.monitor
cctxt.rpc_config ?min_date ~min_heads:1 () >>=? fun block_stream ->
Client_mining_operations.monitor_endorsement
Client_baking_operations.monitor_endorsement
cctxt.rpc_config >>=? fun endorsement_stream ->
Client_mining_forge.create cctxt
Client_baking_forge.create cctxt
?max_priority delegates block_stream endorsement_stream >>=? fun () ->
return ()
end else

View File

@ -15,4 +15,4 @@ val run:
public_key_hash list ->
endorsement:bool ->
denunciation:bool ->
mining:bool -> unit tzresult Lwt.t
baking:bool -> unit tzresult Lwt.t

View File

@ -29,7 +29,7 @@ let create cctxt endorsement_stream =
| `Endorsement (Some (Ok e)) ->
last_get_endorsement := None ;
Client_keys.Public_key_hash.name cctxt
e.Client_mining_operations.source >>= function
e.Client_baking_operations.source >>= function
| Ok source ->
lwt_debug
"Discovered endorsement for block %a by %s (slot @[<h>%a@])"

View File

@ -9,5 +9,5 @@
val create:
Client_commands.context ->
Client_mining_operations.valid_endorsement tzresult Lwt_stream.t ->
Client_baking_operations.valid_endorsement tzresult Lwt_stream.t ->
unit Lwt.t

View File

@ -178,14 +178,14 @@ let forge_endorsement cctxt
type state = {
delegates: public_key_hash list ;
mutable best: Client_mining_blocks.block_info ;
mutable best: Client_baking_blocks.block_info ;
mutable to_endorse: endorsement list ;
delay: int64;
}
and endorsement = {
time: Time.t ;
delegate: public_key_hash ;
block: Client_mining_blocks.block_info ;
block: Client_baking_blocks.block_info ;
slot: int;
}
@ -217,7 +217,7 @@ let drop_old_endorsement ~before state =
state.to_endorse
let schedule_endorsements cctxt state bis =
let may_endorse (block: Client_mining_blocks.block_info) delegate time =
let may_endorse (block: Client_baking_blocks.block_info) delegate time =
Client_keys.Public_key_hash.name cctxt delegate >>=? fun name ->
lwt_log_info "May endorse block %a for %s"
Block_hash.pp_short block.hash name >>= fun () ->

View File

@ -21,5 +21,5 @@ val create:
Client_commands.context ->
delay: int ->
public_key_hash list ->
Client_mining_blocks.block_info list tzresult Lwt_stream.t ->
Client_baking_blocks.block_info list tzresult Lwt_stream.t ->
unit Lwt.t

View File

@ -60,7 +60,7 @@ let assert_valid_operations_hash shell_header operations =
(Operation_list_list_hash.equal
operations_hash shell_header.Tezos_data.Block_header.operations_hash)
(failure
"Client_mining_forge.inject_block: \
"Client_baking_forge.inject_block: \
inconsistent header.")
let inject_block cctxt
@ -79,7 +79,7 @@ type error +=
let () =
register_error_kind
`Permanent
~id:"Client_mining_forge.failed_to_preapply"
~id:"Client_baking_forge.failed_to_preapply"
~title: "Fail to preapply an operation"
~description: ""
~pp:(fun ppf (op, err) ->
@ -126,17 +126,17 @@ let forge_block cctxt block
cctxt block ~prio () >>=? fun time ->
return (prio, time)
end
| `Auto (src_pkh, max_priority, free_mining) ->
| `Auto (src_pkh, max_priority, free_baking) ->
Client_proto_rpcs.Context.next_level cctxt block >>=? fun { level } ->
Client_proto_rpcs.Helpers.Rights.mining_rights_for_delegate cctxt
Client_proto_rpcs.Helpers.Rights.baking_rights_for_delegate cctxt
?max_priority
~first_level:level
~last_level:level
block src_pkh () >>=? fun possibilities ->
try
begin
if free_mining then
Client_proto_rpcs.Constants.first_free_mining_slot cctxt block
if free_baking then
Client_proto_rpcs.Constants.first_free_baking_slot cctxt block
else
return 0
end >>=? fun min_prio ->
@ -299,19 +299,19 @@ end = struct
end
let get_mining_slot cctxt
?max_priority (bi: Client_mining_blocks.block_info) delegates =
let get_baking_slot cctxt
?max_priority (bi: Client_baking_blocks.block_info) delegates =
let block = `Hash bi.hash in
let level = Raw_level.succ bi.level.level in
Lwt_list.filter_map_p
(fun delegate ->
Client_proto_rpcs.Helpers.Rights.mining_rights_for_delegate cctxt
Client_proto_rpcs.Helpers.Rights.baking_rights_for_delegate cctxt
?max_priority
~first_level:level
~last_level:level
block delegate () >>= function
| Error errs ->
log_error "Error while fetching mining possibilities:\n%a"
log_error "Error while fetching baking possibilities:\n%a"
pp_print_error errs ;
Lwt.return_none
| Ok slots ->
@ -327,18 +327,18 @@ let get_mining_slot cctxt
| [] -> Lwt.return None
| slot :: _ -> Lwt.return (Some slot)
let rec insert_mining_slot slot = function
let rec insert_baking_slot slot = function
| [] -> [slot]
| ((timestamp,_) :: _) as slots when Time.(fst slot < timestamp) ->
slot :: slots
| slot' :: slots -> slot' :: insert_mining_slot slot slots
| slot' :: slots -> slot' :: insert_baking_slot slot slots
type state = {
genesis: Block_hash.t ;
delegates: public_key_hash list ;
mutable best: Client_mining_blocks.block_info ;
mutable best: Client_baking_blocks.block_info ;
mutable future_slots:
(Time.t * (Client_mining_blocks.block_info * int * public_key_hash)) list ;
(Time.t * (Client_baking_blocks.block_info * int * public_key_hash)) list ;
}
let create_state genesis delegates best =
@ -375,7 +375,7 @@ let get_unrevealed_nonces cctxt ?(force = false) block =
match Cycle.pred cur_cycle with
| None -> return []
| Some cycle ->
Client_mining_blocks.blocks_from_cycle
Client_baking_blocks.blocks_from_cycle
cctxt.rpc_config block cycle >>=? fun blocks ->
filter_map_s (fun hash ->
Client_proto_nonces.find cctxt hash >>= function
@ -417,10 +417,10 @@ let get_delegates cctxt state =
| _ :: _ as delegates -> return delegates
let insert_block
cctxt ?max_priority state (bi: Client_mining_blocks.block_info) =
cctxt ?max_priority state (bi: Client_baking_blocks.block_info) =
begin
safe_get_unrevealed_nonces cctxt (`Hash bi.hash) >>= fun nonces ->
Client_mining_revelation.forge_seed_nonce_revelation
Client_baking_revelation.forge_seed_nonce_revelation
cctxt ~force:true (`Hash bi.hash) (List.map snd nonces)
end >>= fun _ignore_error ->
if Fitness.compare state.best.fitness bi.fitness < 0 then begin
@ -429,21 +429,21 @@ let insert_block
~before:(Time.add state.best.timestamp (-1800L)) state ;
end ;
get_delegates cctxt state >>=? fun delegates ->
get_mining_slot cctxt.rpc_config ?max_priority bi delegates >>= function
get_baking_slot cctxt.rpc_config ?max_priority bi delegates >>= function
| None ->
lwt_debug
"Can't compute slot for %a" Block_hash.pp_short bi.hash >>= fun () ->
return ()
| Some ((timestamp, (_,_,delegate)) as slot) ->
Client_keys.Public_key_hash.name cctxt delegate >>=? fun name ->
lwt_log_info "New mining slot at %a for %s after %a"
lwt_log_info "New baking slot at %a for %s after %a"
Time.pp_hum timestamp
name
Block_hash.pp_short bi.hash >>= fun () ->
state.future_slots <- insert_mining_slot slot state.future_slots ;
state.future_slots <- insert_baking_slot slot state.future_slots ;
return ()
let pop_mining_slots state =
let pop_baking_slots state =
let now = Time.now () in
let rec pop acc = function
| [] -> List.rev acc, []
@ -463,19 +463,19 @@ let insert_blocks cctxt ?max_priority state bis =
Lwt.return_unit
let mine cctxt state =
let slots = pop_mining_slots state in
let slots = pop_baking_slots state in
let seed_nonce = generate_seed_nonce () in
let seed_nonce_hash = Nonce.hash seed_nonce in
filter_map_s
(fun (timestamp, (bi, priority, delegate)) ->
let block = `Hash bi.Client_mining_blocks.hash in
let block = `Hash bi.Client_baking_blocks.hash in
let timestamp =
if Block_hash.equal bi.Client_mining_blocks.hash state.genesis then
if Block_hash.equal bi.Client_baking_blocks.hash state.genesis then
Time.now ()
else
timestamp in
Client_keys.Public_key_hash.name cctxt delegate >>=? fun name ->
lwt_debug "Try mining after %a (slot %d) for %s (%a)"
lwt_debug "Try baking after %a (slot %d) for %s (%a)"
Block_hash.pp_short bi.hash
priority name Time.pp_hum timestamp >>= fun () ->
Client_node_rpcs.Blocks.pending_operations cctxt.rpc_config
@ -550,9 +550,9 @@ let mine cctxt state =
let create
cctxt ?max_priority delegates
(block_stream:
Client_mining_blocks.block_info list tzresult Lwt_stream.t)
Client_baking_blocks.block_info list tzresult Lwt_stream.t)
(endorsement_stream:
Client_mining_operations.valid_endorsement tzresult Lwt_stream.t) =
Client_baking_operations.valid_endorsement tzresult Lwt_stream.t) =
Lwt_stream.get block_stream >>= function
| None | Some (Ok [] | Error _) ->
cctxt.Client_commands.error "Can't fetch the current block head."
@ -592,7 +592,7 @@ let create
"@[<hov 2>Discoverer blocks:@ %a@]"
(Format.pp_print_list
(fun ppf bi ->
Block_hash.pp_short ppf bi.Client_mining_blocks.hash))
Block_hash.pp_short ppf bi.Client_baking_blocks.hash))
bis
>>= fun () ->
insert_blocks cctxt ?max_priority state bis >>= fun () ->
@ -602,22 +602,22 @@ let create
Lwt.cancel timeout ;
last_get_endorsement := None ;
Client_keys.Public_key_hash.name cctxt
e.Client_mining_operations.source >>= fun _source ->
e.Client_baking_operations.source >>= fun _source ->
(* TODO *)
worker_loop ()
| `Timeout ->
lwt_debug "Waking up for mining..." >>= fun () ->
lwt_debug "Waking up for baking..." >>= fun () ->
begin
mine cctxt state >>= function
| Ok () -> Lwt.return_unit
| Error errs ->
lwt_log_error "Error while mining:\n%a"
lwt_log_error "Error while baking:\n%a"
pp_print_error
errs >>= fun () ->
Lwt.return_unit
end >>= fun () ->
worker_loop () in
lwt_log_info "Starting mining daemon" >>= fun () ->
lwt_log_info "Starting baking daemon" >>= fun () ->
worker_loop () >>= fun () ->
return ()

View File

@ -25,7 +25,7 @@ val inject_block:
(** [inject_block cctxt blk ?force ~priority ~timestamp ~fitness
~seed_nonce ~src_sk ops] tries to inject a block in the node. If
[?force] is set, the fitness check will be bypassed. [priority]
will be used to compute the mining slot (level is
will be used to compute the baking slot (level is
precomputed). [src_sk] is used to sign the block header. *)
type error +=
@ -55,11 +55,11 @@ val forge_block:
* Mining priority: If [`Auto] is used, it will be computed from
the public key hash of the specified contract, optionally capped
to a maximum value, and optionnaly restricting for free mining slot.
to a maximum value, and optionnaly restricting for free baking slot.
* Timestamp: If [?timestamp] is set, and is compatible with the
computed mining priority, it will be used. Otherwise, it will be
set at the best mining priority.
computed baking priority, it will be used. Otherwise, it will be
set at the best baking priority.
*)
module State : sig
@ -75,8 +75,8 @@ val create:
Client_commands.context ->
?max_priority: int ->
public_key_hash list ->
Client_mining_blocks.block_info list tzresult Lwt_stream.t ->
Client_mining_operations.valid_endorsement tzresult Lwt_stream.t ->
Client_baking_blocks.block_info list tzresult Lwt_stream.t ->
Client_baking_operations.valid_endorsement tzresult Lwt_stream.t ->
unit tzresult Lwt.t
val get_unrevealed_nonces:

View File

@ -12,7 +12,7 @@ open Client_commands
open Client_proto_contracts
let mine_block cctxt block
?force ?max_priority ?(free_mining=false) ?src_sk delegate =
?force ?max_priority ?(free_baking=false) ?src_sk delegate =
begin
match src_sk with
| None ->
@ -22,21 +22,21 @@ let mine_block cctxt block
end >>=? fun src_sk ->
Client_proto_rpcs.Context.level cctxt.rpc_config block >>=? fun level ->
let level = Raw_level.succ level.level in
let seed_nonce = Client_mining_forge.generate_seed_nonce () in
let seed_nonce = Client_baking_forge.generate_seed_nonce () in
let seed_nonce_hash = Nonce.hash seed_nonce in
Client_mining_forge.forge_block cctxt.rpc_config
Client_baking_forge.forge_block cctxt.rpc_config
~timestamp:(Time.now ())
?force
~seed_nonce_hash ~src_sk block
~priority:(`Auto (delegate, max_priority, free_mining)) () >>=? fun block_hash ->
Client_mining_forge.State.record_block cctxt level block_hash seed_nonce
~priority:(`Auto (delegate, max_priority, free_baking)) () >>=? fun block_hash ->
Client_baking_forge.State.record_block cctxt level block_hash seed_nonce
|> trace_exn (Failure "Error while recording block") >>=? fun () ->
cctxt.message "Injected block %a" Block_hash.pp_short block_hash >>= fun () ->
return ()
let endorse_block cctxt ?force ?max_priority delegate =
Client_keys.get_key cctxt delegate >>=? fun (_src_name, src_pk, src_sk) ->
Client_mining_endorsement.forge_endorsement cctxt
Client_baking_endorsement.forge_endorsement cctxt
cctxt.config.block ?force ?max_priority ~src_sk src_pk >>=? fun oph ->
cctxt.answer "Operation successfully injected in the node." >>= fun () ->
cctxt.answer "Operation hash is '%a'." Operation_hash.pp oph >>= fun () ->
@ -55,7 +55,7 @@ let get_predecessor_cycle cctxt cycle =
let do_reveal cctxt ?force block blocks =
let nonces = List.map snd blocks in
Client_mining_revelation.forge_seed_nonce_revelation cctxt
Client_baking_revelation.forge_seed_nonce_revelation cctxt
block ?force nonces >>=? fun () ->
Client_proto_nonces.dels cctxt (List.map fst blocks) >>=? fun () ->
return ()
@ -65,7 +65,7 @@ let reveal_block_nonces cctxt ?force block_hashes =
(fun hash ->
Lwt.catch
(fun () ->
Client_mining_blocks.info cctxt.rpc_config (`Hash hash) >>= function
Client_baking_blocks.info cctxt.rpc_config (`Hash hash) >>= function
| Ok bi -> Lwt.return (Some bi)
| Error _ ->
Lwt.fail Not_found)
@ -75,7 +75,7 @@ let reveal_block_nonces cctxt ?force block_hashes =
Block_hash.pp_short hash >>= fun () ->
Lwt.return_none))
block_hashes >>= fun block_infos ->
filter_map_s (fun (bi : Client_mining_blocks.block_info) ->
filter_map_s (fun (bi : Client_baking_blocks.block_info) ->
Client_proto_nonces.find cctxt bi.hash >>= function
| None ->
cctxt.warning "Cannot find nonces for block %a (ignoring)@."
@ -88,18 +88,18 @@ let reveal_block_nonces cctxt ?force block_hashes =
let reveal_nonces cctxt ?force () =
let block = Client_rpcs.last_mined_block cctxt.config.block in
Client_mining_forge.get_unrevealed_nonces
Client_baking_forge.get_unrevealed_nonces
cctxt ?force block >>=? fun nonces ->
do_reveal cctxt ?force cctxt.config.block nonces
open Client_proto_args
let run_daemon cctxt max_priority endorsement_delay delegates ~endorsement ~mining ~denunciation =
Client_mining_daemon.run cctxt
let run_daemon cctxt max_priority endorsement_delay delegates ~endorsement ~baking ~denunciation =
Client_baking_daemon.run cctxt
?max_priority
~delay:endorsement_delay
~min_date:((Time.add (Time.now ()) (Int64.neg 1800L)))
~endorsement ~mining ~denunciation
~endorsement ~baking ~denunciation
(List.map snd delegates)
let group =
@ -111,15 +111,15 @@ let commands () =
[
command ~group ~desc: "Launch a daemon that handles delegate operations."
(args5 max_priority_arg endorsement_delay_arg
Daemon.mining_switch Daemon.endorsement_switch Daemon.denunciation_switch)
Daemon.baking_switch Daemon.endorsement_switch Daemon.denunciation_switch)
(prefixes [ "launch" ; "daemon" ]
@@ seq_of_param Client_keys.Public_key_hash.alias_param)
(fun (max_priority, endorsement_delay, mining, endorsement, denunciation) delegates cctxt ->
let (endorsement, mining, denunciation) =
if (not endorsement) && (not mining) && (not denunciation)
(fun (max_priority, endorsement_delay, baking, endorsement, denunciation) delegates cctxt ->
let (endorsement, baking, denunciation) =
if (not endorsement) && (not baking) && (not denunciation)
then (true, true, true)
else (endorsement, mining, denunciation) in
run_daemon cctxt max_priority endorsement_delay ~endorsement ~mining ~denunciation delegates) ;
else (endorsement, baking, denunciation) in
run_daemon cctxt max_priority endorsement_delay ~endorsement ~baking ~denunciation delegates) ;
command ~group ~desc: "Forge and inject an endorsement operation"
(args2 force_switch max_priority_arg)
(prefixes [ "endorse"; "for" ]
@ -130,14 +130,14 @@ let commands () =
endorse_block cctxt
~force ?max_priority delegate) ;
command ~group ~desc: "Forge and inject block using the delegate rights"
(args3 max_priority_arg force_switch free_mining_switch)
(args3 max_priority_arg force_switch free_baking_switch)
(prefixes [ "mine"; "for" ]
@@ Client_keys.Public_key_hash.alias_param
~name:"miner" ~desc: "name of the delegate owning the mining right"
~name:"miner" ~desc: "name of the delegate owning the baking right"
@@ stop)
(fun (max_priority, force, free_mining) (_, delegate) cctxt ->
(fun (max_priority, force, free_baking) (_, delegate) cctxt ->
mine_block cctxt cctxt.config.block
~force ?max_priority ~free_mining delegate) ;
~force ?max_priority ~free_baking delegate) ;
command ~group ~desc: "Forge and inject a seed-nonce revelation operation"
(args1 force_switch)
(prefixes [ "reveal"; "nonce"; "for" ]

View File

@ -12,7 +12,7 @@ val mine_block:
Client_proto_rpcs.block ->
?force:bool ->
?max_priority: int ->
?free_mining: bool ->
?free_baking: bool ->
?src_sk:secret_key ->
public_key_hash ->
unit tzresult Lwt.t

View File

@ -127,15 +127,15 @@ let fee_arg =
let max_priority_arg =
arg
~parameter:"-max-priority"
~doc:"Set the max_priority used when looking for mining slot."
~doc:"Set the max_priority used when looking for baking slot."
(fun _ s ->
try return (int_of_string s)
with _ -> fail (Bad_max_priority s))
let free_mining_switch =
let free_baking_switch =
switch
~parameter:"-free-mining"
~doc:"Only consider free mining slots."
~parameter:"-free-baking"
~doc:"Only consider free baking slots."
let endorsement_delay_arg =
default_arg
@ -147,10 +147,10 @@ let endorsement_delay_arg =
with _ -> fail (Bad_endorsement_delay s))
module Daemon = struct
let mining_switch =
let baking_switch =
switch
~parameter:"-mining"
~doc:"Run the mining daemon"
~parameter:"-baking"
~doc:"Run the baking daemon"
let endorsement_switch =
switch
~parameter:"-endorsement"

View File

@ -19,7 +19,7 @@ val delegate_arg: (string option, Client_commands.context) arg
val delegatable_switch: (bool, Client_commands.context) arg
val non_spendable_switch: (bool, Client_commands.context) arg
val max_priority_arg: (int option, Client_commands.context) arg
val free_mining_switch: (bool, Client_commands.context) arg
val free_baking_switch: (bool, Client_commands.context) arg
val force_switch: (bool, Client_commands.context) arg
val endorsement_delay_arg: (int, Client_commands.context) arg
@ -35,7 +35,7 @@ val tez_param :
(Tez.t -> 'a, Client_commands.context, 'ret) Cli_entries.params
module Daemon : sig
val mining_switch: (bool, Client_commands.context) arg
val baking_switch: (bool, Client_commands.context) arg
val endorsement_switch: (bool, Client_commands.context) arg
val denunciation_switch: (bool, Client_commands.context) arg
end

View File

@ -59,8 +59,8 @@ module Constants = struct
call_error_service1 cctxt Services.Constants.time_before_reward block ()
let slot_durations cctxt block =
call_error_service1 cctxt Services.Constants.slot_durations block ()
let first_free_mining_slot cctxt block =
call_error_service1 cctxt Services.Constants.first_free_mining_slot block ()
let first_free_baking_slot cctxt block =
call_error_service1 cctxt Services.Constants.first_free_baking_slot block ()
let max_signing_slot cctxt block =
call_error_service1 cctxt Services.Constants.max_signing_slot block ()
let instructions_per_transaction cctxt block =
@ -171,11 +171,11 @@ module Helpers = struct
call_error_service2 cctxt Services.Helpers.levels block cycle ()
module Rights = struct
type mining_slot = Raw_level.t * int * Time.t
type baking_slot = Raw_level.t * int * Time.t
type endorsement_slot = Raw_level.t * int
let mining_rights_for_delegate cctxt
let baking_rights_for_delegate cctxt
b c ?max_priority ?first_level ?last_level () =
call_error_service2 cctxt Services.Helpers.Rights.mining_rights_for_delegate
call_error_service2 cctxt Services.Helpers.Rights.baking_rights_for_delegate
b c (max_priority, first_level, last_level)
let endorsement_rights_for_delegate cctxt
b c ?max_priority ?first_level ?last_level () =
@ -289,9 +289,9 @@ module Helpers = struct
end
(* type slot = *)
(* raw_level * int * timestamp option *)
(* let mining_possibilities *)
(* let baking_possibilities *)
(* b c ?max_priority ?first_level ?last_level () = *)
(* call_error_service2 Services.Helpers.Context.Contract.mining_possibilities *)
(* call_error_service2 Services.Helpers.Context.Contract.baking_possibilities *)
(* b c (max_priority, first_level, last_level) *)
(* (\* let endorsement_possibilities b c ?max_priority ?first_level ?last_level () = *\) *)
(* call_error_service2 Services.Helpers.Context.Contract.endorsement_possibilities *)

View File

@ -38,7 +38,7 @@ module Constants : sig
val slot_durations:
Client_rpcs.config ->
block -> (Period.t list) tzresult Lwt.t
val first_free_mining_slot:
val first_free_baking_slot:
Client_rpcs.config ->
block -> int tzresult Lwt.t
val max_signing_slot:
@ -181,14 +181,14 @@ module Helpers : sig
block -> Cycle.t -> (Raw_level.t * Raw_level.t) tzresult Lwt.t
module Rights : sig
type mining_slot = Raw_level.t * int * Time.t
type baking_slot = Raw_level.t * int * Time.t
type endorsement_slot = Raw_level.t * int
val mining_rights_for_delegate:
val baking_rights_for_delegate:
Client_rpcs.config ->
block -> public_key_hash ->
?max_priority:int -> ?first_level:Raw_level.t ->
?last_level:Raw_level.t -> unit ->
(mining_slot list) tzresult Lwt.t
(baking_slot list) tzresult Lwt.t
val endorsement_rights_for_delegate:
Client_rpcs.config ->
block -> public_key_hash ->

View File

@ -269,9 +269,9 @@ let begin_full_construction ctxt pred_timestamp proto_header =
Lwt.return
(Block_header.parse_unsigned_proto_header
proto_header) >>=? fun proto_header ->
Mining.check_mining_rights
Mining.check_baking_rights
ctxt proto_header pred_timestamp >>=? fun miner ->
Mining.pay_mining_bond ctxt proto_header miner >>=? fun ctxt ->
Mining.pay_baking_bond ctxt proto_header miner >>=? fun ctxt ->
let ctxt = Fitness.increase ctxt in
return (ctxt, proto_header, miner)
@ -282,17 +282,17 @@ let begin_partial_construction ctxt =
let begin_application ctxt block_header pred_timestamp =
Mining.check_proof_of_work_stamp ctxt block_header >>=? fun () ->
Mining.check_fitness_gap ctxt block_header >>=? fun () ->
Mining.check_mining_rights
Mining.check_baking_rights
ctxt block_header.proto pred_timestamp >>=? fun miner ->
Mining.check_signature ctxt block_header miner >>=? fun () ->
Mining.pay_mining_bond ctxt block_header.proto miner >>=? fun ctxt ->
Mining.pay_baking_bond ctxt block_header.proto miner >>=? fun ctxt ->
let ctxt = Fitness.increase ctxt in
return (ctxt, miner)
let finalize_application ctxt block_proto_header miner =
(* end of level (from this point nothing should fail) *)
let priority = block_proto_header.Block_header.priority in
let reward = Mining.base_mining_reward ctxt ~priority in
let reward = Mining.base_baking_reward ctxt ~priority in
Nonce.record_hash ctxt
miner reward block_proto_header.seed_nonce_hash >>=? fun ctxt ->
Reward.pay_due_rewards ctxt >>=? fun ctxt ->

View File

@ -22,11 +22,11 @@ let origination_burn =
Tez_repr.of_cents_exn 1_00L
let minimal_contract_balance =
Tez_repr.of_cents_exn 1_00L
let mining_bond_cost =
let baking_bond_cost =
Tez_repr.of_cents_exn 1000_00L
let endorsement_bond_cost =
Tez_repr.of_cents_exn 1000_00L
let mining_reward =
let baking_reward =
Tez_repr.of_cents_exn 150_00L
let endorsement_reward =
Tez_repr.of_cents_exn 150_00L
@ -38,7 +38,7 @@ type constants = {
voting_period_length: int32 ;
time_before_reward: Period_repr.t ;
slot_durations: Period_repr.t list ;
first_free_mining_slot: int ;
first_free_baking_slot: int ;
max_signing_slot: int ;
instructions_per_transaction: int ;
proof_of_work_threshold: int64 ;
@ -58,7 +58,7 @@ let default = {
Int64.(mul 365L (mul 24L 3600L)) ;
slot_durations =
List.map Period_repr.of_seconds_exn [ 60L ] ;
first_free_mining_slot = 16 ;
first_free_baking_slot = 16 ;
max_signing_slot = 15 ;
instructions_per_transaction = 16 * 1024 ;
proof_of_work_threshold =
@ -102,9 +102,9 @@ let constants_encoding =
and slot_durations =
opt Compare_slot_durations.(=)
default.slot_durations c.slot_durations
and first_free_mining_slot =
and first_free_baking_slot =
opt Compare.Int.(=)
default.first_free_mining_slot c.first_free_mining_slot
default.first_free_baking_slot c.first_free_baking_slot
and max_signing_slot =
opt Compare.Int.(=)
default.max_signing_slot c.max_signing_slot
@ -125,7 +125,7 @@ let constants_encoding =
voting_period_length,
time_before_reward,
slot_durations,
first_free_mining_slot,
first_free_baking_slot,
max_signing_slot,
instructions_per_transaction,
proof_of_work_threshold,
@ -135,7 +135,7 @@ let constants_encoding =
voting_period_length,
time_before_reward,
slot_durations,
first_free_mining_slot,
first_free_baking_slot,
max_signing_slot,
instructions_per_transaction,
proof_of_work_threshold,
@ -151,8 +151,8 @@ let constants_encoding =
slot_durations =
unopt default.slot_durations @@
slot_durations ;
first_free_mining_slot =
unopt default.first_free_mining_slot first_free_mining_slot ;
first_free_baking_slot =
unopt default.first_free_baking_slot first_free_baking_slot ;
max_signing_slot =
unopt default.max_signing_slot max_signing_slot ;
instructions_per_transaction =
@ -171,7 +171,7 @@ let constants_encoding =
(opt "voting_period_length" int32)
(opt "time_before_reward" int64)
(opt "slot_durations" (list Period_repr.encoding))
(opt "first_free_mining_slot" uint16)
(opt "first_free_baking_slot" uint16)
(opt "max_signing_slot" uint16)
(opt "instructions_per_transaction" int31)
(opt "proof_of_work_threshold" int64)

View File

@ -15,13 +15,13 @@ 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 += Cannot_pay_mining_bond (* `Permanent *)
type error += Cannot_pay_baking_bond (* `Permanent *)
type error += Cannot_pay_endorsement_bond (* `Permanent *)
let () =
register_error_kind
`Permanent
~id:"mining.timestamp_too_early"
~id:"baking.timestamp_too_early"
~title:"Block forged too early"
~description:"The block timestamp is before the first slot \
for this miner at this level"
@ -35,7 +35,7 @@ let () =
(fun (r, p) -> Timestamp_too_early (r, p)) ;
register_error_kind
`Permanent
~id:"mining.invalid_fitness_gap"
~id:"baking.invalid_fitness_gap"
~title:"Invalid fitness gap"
~description:"The gap of fitness is out of bounds"
~pp:(fun ppf (m, g) ->
@ -48,12 +48,12 @@ let () =
(fun (m, g) -> Invalid_fitness_gap (m, g)) ;
register_error_kind
`Permanent
~id:"mining.invalid_slot"
~id:"baking.invalid_slot"
~title:"Invalid slot"
~description:"The mining slot is out of bounds"
~description:"The baking slot is out of bounds"
~pp:(fun ppf (m, g) ->
Format.fprintf ppf
"The mining slot %d is not between 0 and %d" g m)
"The baking slot %d is not between 0 and %d" g m)
Data_encoding.(obj2
(req "maximum" int16)
(req "provided" int16))
@ -61,7 +61,7 @@ let () =
(fun (m, g) -> Invalid_endorsement_slot (m, g)) ;
register_error_kind
`Permanent
~id:"mining.wrong_delegate"
~id:"baking.wrong_delegate"
~title:"Wrong delegate"
~description:"The block delegate is not the expected one"
~pp:(fun ppf (e, g) ->
@ -75,17 +75,17 @@ let () =
(fun (e, g) -> Wrong_delegate (e, g)) ;
register_error_kind
`Permanent
~id:"mining.cannot_pay_mining_bond"
~title:"Cannot pay mining bond"
~id:"baking.cannot_pay_baking_bond"
~title:"Cannot pay baking bond"
~description:
"Impossible to take the required tokens on the miner's contract"
~pp:(fun ppf () -> Format.fprintf ppf "Cannot pay the mining bond")
~pp:(fun ppf () -> Format.fprintf ppf "Cannot pay the baking bond")
Data_encoding.unit
(function Cannot_pay_mining_bond -> Some () | _ -> None)
(fun () -> Cannot_pay_mining_bond) ;
(function Cannot_pay_baking_bond -> Some () | _ -> None)
(fun () -> Cannot_pay_baking_bond) ;
register_error_kind
`Permanent
~id:"mining.cannot_pay_endorsement_bond"
~id:"baking.cannot_pay_endorsement_bond"
~title:"Cannot pay endorsement bond"
~description:
"Impossible to take the required tokens on the endorser's contract"
@ -118,19 +118,19 @@ let check_timestamp c priority pred_timestamp =
fail_unless Timestamp.(minimal_time <= timestamp)
(Timestamp_too_early (minimal_time, timestamp))
let check_mining_rights c { Block_header.priority }
let check_baking_rights c { Block_header.priority }
pred_timestamp =
let level = Level.current c in
Roll.mining_rights_owner c level ~priority >>=? fun delegate ->
Roll.baking_rights_owner c level ~priority >>=? fun delegate ->
check_timestamp c priority pred_timestamp >>=? fun () ->
return delegate
let pay_mining_bond c { Block_header.priority } id =
if Compare.Int.(priority >= Constants.first_free_mining_slot c)
let pay_baking_bond c { Block_header.priority } id =
if Compare.Int.(priority >= Constants.first_free_baking_slot c)
then return c
else
Contract.spend c (Contract.default_contract id) Constants.mining_bond_cost
|> trace Cannot_pay_mining_bond
Contract.spend c (Contract.default_contract id) Constants.baking_bond_cost
|> trace Cannot_pay_baking_bond
let pay_endorsement_bond c id =
let bond = Constants.endorsement_bond_cost in
@ -147,17 +147,17 @@ let check_signing_rights c slot delegate =
(Wrong_delegate (owning_delegate, delegate))
let paying_priorities c =
0 --> Constants.first_free_mining_slot c
0 --> Constants.first_free_baking_slot c
let bond_and_reward =
match Tez.(Constants.mining_bond_cost +? Constants.mining_reward) with
match Tez.(Constants.baking_bond_cost +? Constants.baking_reward) with
| Ok v -> v
| Error _ -> assert false
let base_mining_reward c ~priority =
if Compare.Int.(priority < Constants.first_free_mining_slot c)
let base_baking_reward c ~priority =
if Compare.Int.(priority < Constants.first_free_baking_slot c)
then bond_and_reward
else Constants.mining_reward
else Constants.baking_reward
type error += Incorect_priority
@ -168,9 +168,9 @@ let endorsement_reward ~block_priority:prio =
Tez.(Constants.endorsement_reward /? (Int64.(succ (of_int prio))))
else fail Incorect_priority
let mining_priorities c level =
let baking_priorities c level =
let rec f priority =
Roll.mining_rights_owner c level ~priority >>=? fun delegate ->
Roll.baking_rights_owner c level ~priority >>=? fun delegate ->
return (LCons (delegate, (fun () -> f (succ priority))))
in
f 0
@ -197,11 +197,11 @@ let select_delegate delegate delegate_list max_priority =
in
loop [] delegate_list 0
let first_mining_priorities
let first_baking_priorities
ctxt
?(max_priority = Constants.first_free_mining_slot ctxt)
?(max_priority = Constants.first_free_baking_slot ctxt)
delegate level =
mining_priorities ctxt level >>=? fun delegate_list ->
baking_priorities ctxt level >>=? fun delegate_list ->
select_delegate delegate delegate_list max_priority
let first_endorsement_slots

View File

@ -15,7 +15,7 @@ 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 += Cannot_pay_mining_bond (* `Permanent *)
type error += Cannot_pay_baking_bond (* `Permanent *)
type error += Cannot_pay_endorsement_bond (* `Permanent *)
val paying_priorities: context -> int list
@ -27,7 +27,7 @@ val minimal_time: context -> int -> Time.t -> Time.t tzresult Lwt.t
mine. Fail with [Invalid_slot_durations_constant] if the minimal
time cannot be computed. *)
val pay_mining_bond:
val pay_baking_bond:
context ->
Block_header.proto_header ->
public_key_hash ->
@ -36,12 +36,12 @@ val pay_mining_bond:
val pay_endorsement_bond:
context -> public_key_hash -> (context * Tez.t) tzresult Lwt.t
(** [check_mining_rights ctxt block pred_timestamp] verifies that:
(** [check_baking_rights ctxt block pred_timestamp] verifies that:
* the contract that owned the roll at cycle start has the block signer as delegate.
* the timestamp is coherent with the announced slot.
* the bond have been payed if the slot is below [Constants.first_free_mining_slot].
* the bond have been payed if the slot is below [Constants.first_free_baking_slot].
*)
val check_mining_rights:
val check_baking_rights:
context -> Block_header.proto_header -> Time.t ->
public_key_hash tzresult Lwt.t
@ -53,27 +53,27 @@ val check_mining_rights:
val check_signing_rights:
context -> int -> public_key_hash -> unit tzresult Lwt.t
(** If this priority should have payed the bond it is the base mining
(** If this priority should have payed the bond it is the base baking
reward and the bond, or just the base reward otherwise *)
val base_mining_reward: context -> priority:int -> Tez.t
val base_baking_reward: context -> priority:int -> Tez.t
val endorsement_reward: block_priority:int -> Tez.t tzresult Lwt.t
val mining_priorities:
val baking_priorities:
context -> Level.t -> public_key_hash lazy_list
(** [mining_priorities ctxt level] is the lazy list of contract's
(** [baking_priorities ctxt level] is the lazy list of contract's
public key hashes that are allowed to mine for [level]. *)
val endorsement_priorities:
context -> Level.t -> public_key_hash lazy_list
val first_mining_priorities:
val first_baking_priorities:
context ->
?max_priority:int ->
public_key_hash ->
Level.t ->
int list tzresult Lwt.t
(** [first_mining_priorities ctxt ?max_priority contract_hash level]
(** [first_baking_priorities ctxt ?max_priority contract_hash level]
is a list of priorities of max [?max_priority] elements, where the
delegate of [contract_hash] is allowed to mine for [level]. If
[?max_priority] is [None], a sensible number of priorities is

View File

@ -80,8 +80,8 @@ module Random = struct
end
let mining_rights_owner c level ~priority =
Random.owner c "mining" level priority
let baking_rights_owner c level ~priority =
Random.owner c "baking" level priority
let endorsement_rights_owner c level ~slot =
Random.owner c "endorsement" level slot

View File

@ -34,7 +34,7 @@ val freeze_rolls_for_cycle :
val clear_cycle :
Storage.t -> Cycle_repr.t -> Storage.t tzresult Lwt.t
val mining_rights_owner :
val baking_rights_owner :
Storage.t -> Level_repr.t -> priority:int ->
Ed25519.Public_key_hash.t tzresult Lwt.t

View File

@ -102,13 +102,13 @@ module Constants = struct
describe ~title: "time between slots" (list Period.encoding))
RPC.Path.(custom_root / "constants" / "time_between_slots")
let first_free_mining_slot custom_root =
let first_free_baking_slot custom_root =
RPC.service
~description: "First free mining slot"
~description: "First free baking slot"
~input: empty
~output: (wrap_tzerror @@
describe ~title: "first free mining slot" uint16)
RPC.Path.(custom_root / "constants" / "first_free_mining_slot")
describe ~title: "first free baking slot" uint16)
RPC.Path.(custom_root / "constants" / "first_free_baking_slot")
let max_signing_slot custom_root =
RPC.service
@ -470,13 +470,13 @@ module Helpers = struct
(req "level" Raw_level.encoding)
(req "priority" int31))
let mining_slot_encoding =
let baking_slot_encoding =
(obj3
(req "level" Raw_level.encoding)
(req "priority" int31)
(req "timestamp" Timestamp.encoding))
let mining_rights custom_root =
let baking_rights custom_root =
RPC.service
~description:
"List gelegates allowed to mine for the next level, \
@ -485,14 +485,14 @@ module Helpers = struct
~output: (wrap_tzerror @@
obj2
(req "level" Raw_level.encoding)
(req "mining_rights"
(req "baking_rights"
(list
(obj2
(req "delegate" Ed25519.Public_key_hash.encoding)
(req "timestamp" Timestamp.encoding)))))
RPC.Path.(custom_root / "helpers" / "rights" / "mining")
RPC.Path.(custom_root / "helpers" / "rights" / "baking")
let mining_rights_for_level custom_root =
let baking_rights_for_level custom_root =
RPC.service
~description:
"List delegate allowed to mine for a given level, \
@ -504,36 +504,36 @@ module Helpers = struct
(req "delegates"
(list Ed25519.Public_key_hash.encoding)))
RPC.Path.(custom_root / "helpers" / "rights"
/ "mining" / "level" /: Raw_level.arg )
/ "baking" / "level" /: Raw_level.arg )
let mining_levels custom_root =
let baking_levels custom_root =
RPC.service
~description:
"List level for which we might computed mining rights."
"List level for which we might computed baking rights."
~input: empty
~output: (wrap_tzerror @@
obj1 (req "levels" (list Raw_level.encoding)))
RPC.Path.(custom_root / "helpers" / "rights"
/ "mining" / "level" )
/ "baking" / "level" )
let mining_rights_for_delegate custom_root =
let baking_rights_for_delegate custom_root =
RPC.service
~description: "Future mining rights for a given delegate."
~description: "Future baking rights for a given delegate."
~input: slots_range_encoding
~output: (wrap_tzerror (Data_encoding.list mining_slot_encoding))
~output: (wrap_tzerror (Data_encoding.list baking_slot_encoding))
RPC.Path.(custom_root / "helpers" / "rights"
/ "mining" / "delegate" /: Context.Key.public_key_hash_arg )
/ "baking" / "delegate" /: Context.Key.public_key_hash_arg )
let mining_delegates custom_root =
let baking_delegates custom_root =
RPC.service
~description:
"List delegates with mining rights."
"List delegates with baking rights."
~input: empty
~output: (wrap_tzerror @@
obj1 (req "delegates"
(list Ed25519.Public_key_hash.encoding)))
RPC.Path.(custom_root / "helpers" / "rights"
/ "mining" / "delegate" )
/ "baking" / "delegate" )
let endorsement_rights custom_root =
RPC.service

View File

@ -112,11 +112,11 @@ let slot_durations ctxt =
let () = register0 Services.Constants.slot_durations slot_durations
let first_free_mining_slot ctxt =
return @@ Constants.first_free_mining_slot ctxt
let first_free_baking_slot ctxt =
return @@ Constants.first_free_baking_slot ctxt
let () =
register0 Services.Constants.first_free_mining_slot first_free_mining_slot
register0 Services.Constants.first_free_baking_slot first_free_baking_slot
let max_signing_slot ctxt =
return @@ Constants.max_signing_slot ctxt
@ -250,7 +250,7 @@ let () =
| Some (shell, contents) ->
let operation = { hash ; shell ; contents ; signature } in
let level = Tezos_context.Level.current ctxt in
Mining.mining_priorities ctxt level >>=? fun (Misc.LCons (miner_pkh, _)) ->
Mining.baking_priorities ctxt level >>=? fun (Misc.LCons (miner_pkh, _)) ->
let miner_contract = Contract.default_contract miner_pkh in
let block_prio = 0 in
Apply.apply_operation
@ -327,15 +327,15 @@ let () = register2 Services.Helpers.levels levels
(*-- Helpers.Rights ----------------------------------------------------------*)
let default_max_mining_priority ctxt arg =
let default = Constants.first_free_mining_slot ctxt in
let default_max_baking_priority ctxt arg =
let default = Constants.first_free_baking_slot ctxt in
match arg with
| None -> 2 * default
| Some m -> m
let mining_rights ctxt level max =
let max = default_max_mining_priority ctxt max in
Mining.mining_priorities ctxt level >>=? fun contract_list ->
let baking_rights ctxt level max =
let max = default_max_baking_priority ctxt max in
Mining.baking_priorities ctxt level >>=? fun contract_list ->
let rec loop l n =
match n with
| 0 -> return []
@ -349,10 +349,10 @@ let mining_rights ctxt level max =
return (level.level, prio)
let () =
register1 Services.Helpers.Rights.mining_rights
register1 Services.Helpers.Rights.baking_rights
(fun ctxt max ->
let level = Level.current ctxt in
mining_rights ctxt level max >>=? fun (raw_level, slots) ->
baking_rights ctxt level max >>=? fun (raw_level, slots) ->
begin
Lwt_list.filter_map_p (fun x -> x) @@
List.mapi
@ -366,14 +366,14 @@ let () =
return (raw_level, timed_slots))
let () =
register2 Services.Helpers.Rights.mining_rights_for_level
register2 Services.Helpers.Rights.baking_rights_for_level
(fun ctxt raw_level max ->
let level = Level.from_raw ctxt raw_level in
mining_rights ctxt level max)
baking_rights ctxt level max)
let mining_rights_for_delegate
let baking_rights_for_delegate
ctxt contract (max_priority, min_level, max_level) =
let max_priority = default_max_mining_priority ctxt max_priority in
let max_priority = default_max_baking_priority ctxt max_priority in
let current_level = Level.current ctxt in
let min_level = match min_level with
| None -> current_level
@ -389,7 +389,7 @@ let mining_rights_for_delegate
then return []
else
loop (Level.succ ctxt level) >>=? fun t ->
Mining.first_mining_priorities
Mining.first_baking_priorities
ctxt ~max_priority contract level >>=? fun priorities ->
let raw_level = level.level in
Error_monad.map_s
@ -403,8 +403,8 @@ let mining_rights_for_delegate
loop min_level
let () =
register2 Services.Helpers.Rights.mining_rights_for_delegate
mining_rights_for_delegate
register2 Services.Helpers.Rights.baking_rights_for_delegate
baking_rights_for_delegate
let default_max_endorsement_priority ctxt arg =
let default = Constants.max_signing_slot ctxt in

View File

@ -68,9 +68,9 @@ module Constants = struct
let slot_durations c =
let constants = Storage.constants c in
constants.slot_durations
let first_free_mining_slot c =
let first_free_baking_slot c =
let constants = Storage.constants c in
constants.first_free_mining_slot
constants.first_free_baking_slot
let max_signing_slot c =
let constants = Storage.constants c in
constants.max_signing_slot

View File

@ -172,13 +172,13 @@ end
module Constants : sig
val proof_of_work_nonce_size: int
val mining_reward: Tez.t
val baking_reward: Tez.t
val endorsement_reward: Tez.t
val max_number_of_operations: int
val nonce_length: int
val seed_nonce_revelation_tip: Tez.t
val origination_burn: Tez.t
val mining_bond_cost: Tez.t
val baking_bond_cost: Tez.t
val endorsement_bond_cost: Tez.t
val faucet_credit: Tez.t
@ -186,7 +186,7 @@ module Constants : sig
val voting_period_length: context -> int32
val time_before_reward: context -> Period.t
val slot_durations: context -> Period.t list
val first_free_mining_slot: context -> int
val first_free_baking_slot: context -> int
val max_signing_slot: context -> int
val instructions_per_transaction: context -> int
val proof_of_work_threshold: context -> int64
@ -593,7 +593,7 @@ module Roll : sig
val freeze_rolls_for_cycle: context -> Cycle.t -> context tzresult Lwt.t
val clear_cycle: context -> Cycle.t -> context tzresult Lwt.t
val mining_rights_owner:
val baking_rights_owner:
context -> Level.t -> priority:int -> public_key_hash tzresult Lwt.t
val endorsement_rights_owner:

View File

@ -84,7 +84,7 @@ module Node = struct
end
module Client = struct
module Blocks = Make(struct let name = "client.blocks" end)
module Mining = Make(struct let name = "client.mining" end)
module Mining = Make(struct let name = "client.baking" end)
module Endorsement = Make(struct let name = "client.endorsement" end)
module Revelation = Make(struct let name = "client.revealation" end)
module Denunciation = Make(struct let name = "client.denunciation" end)