Alpha: documentation of RPC wrappers.

This commit is contained in:
Vincent Bernardoff 2017-03-08 18:47:01 +01:00 committed by Benjamin Canou
parent c2ae0b278a
commit d845dc9740
13 changed files with 94 additions and 20 deletions

View File

@ -16,10 +16,21 @@ type context =
message : 'a. ('a, unit) lwt_format -> 'a ; message : 'a. ('a, unit) lwt_format -> 'a ;
answer : 'a. ('a, unit) lwt_format -> 'a ; answer : 'a. ('a, unit) lwt_format -> 'a ;
log : 'a. string -> ('a, unit) lwt_format -> 'a } log : 'a. string -> ('a, unit) lwt_format -> 'a }
(** This [context] allows the client {!command} handlers to work in
various modes (command line, batch mode, web client, etc.) by
abstracting some basic operations such as logging and reading
configuration options. It is passed as parameter to the command
handler when running a command, and must be transmitted to all
basic operations, also making client commands reantrant. *)
val make_context : (string -> string -> unit Lwt.t) -> context val make_context : (string -> string -> unit Lwt.t) -> context
(** [make_context log_fun] builds a context whose logging callbacks
call [log_fun section msg], and whose [error] function calls
[Lwt.fail_with]. *)
val ignore_context : context val ignore_context : context
(** [ignore_context] is a context whose logging callbacks do nothing,
and whose [error] function calls [Lwt.fail_with]. *)
type command = (context, unit) Cli_entries.command type command = (context, unit) Cli_entries.command

View File

@ -20,6 +20,11 @@ val forge_block:
Operation_hash.t list -> Operation_hash.t list ->
MBytes.t -> MBytes.t ->
MBytes.t Lwt.t MBytes.t Lwt.t
(** [forge_block cctxt ?net ?predecessor ?timestamp fitness ops
proto_hdr] returns the serialization of a block header with
[proto_hdr] as protocol-specific part. The arguments [?net] and
[?predecessor] are infered from the current head of main network,
and [?timestamp] defaults to [Time.now ()]. *)
val validate_block: val validate_block:
Client_commands.context -> Client_commands.context ->
@ -31,6 +36,11 @@ val inject_block:
?wait:bool -> ?force:bool -> ?wait:bool -> ?force:bool ->
MBytes.t -> MBytes.t ->
Block_hash.t tzresult Lwt.t Block_hash.t tzresult Lwt.t
(** [inject_block cctxt ?wait ?force raw_block] tries to inject
[raw_block] inside the node. If [?wait] is [true], [raw_block]
will be validated before the result is returned. If [?force] is
true, the block will be injected even on non strictly increasing
fitness. *)
val inject_operation: val inject_operation:
Client_commands.context -> Client_commands.context ->

View File

@ -71,8 +71,9 @@ let inject_block cctxt block
let forge_block cctxt block let forge_block cctxt block
?force ?force
?operations ?(best_effort = operations = None) ?(sort = best_effort) ?operations ?(best_effort = operations = None) ?(sort = best_effort)
?timestamp ?max_priority ?priority ?timestamp
~seed_nonce ~src_sk src_pkh = ~priority
~seed_nonce ~src_sk () =
let block = let block =
match block with match block with
| `Prevalidation -> `Head 0 | `Prevalidation -> `Head 0
@ -91,12 +92,12 @@ let forge_block cctxt block
end >>= fun operations -> end >>= fun operations ->
begin begin
match priority with match priority with
| Some prio -> begin | `Set prio -> begin
Client_proto_rpcs.Helpers.minimal_time Client_proto_rpcs.Helpers.minimal_time
cctxt block ~prio () >>=? fun time -> cctxt block ~prio () >>=? fun time ->
return (prio, Some time) return (prio, Some time)
end end
| None -> | `Auto (src_pkh, max_priority) ->
Client_proto_rpcs.Helpers.Rights.mining_rights_for_delegate cctxt Client_proto_rpcs.Helpers.Rights.mining_rights_for_delegate cctxt
?max_priority ?max_priority
~first_level:level ~first_level:level

View File

@ -8,6 +8,10 @@
(**************************************************************************) (**************************************************************************)
val generate_seed_nonce: unit -> Nonce.t val generate_seed_nonce: unit -> Nonce.t
(** [generate_seed_nonce ()] is a random nonce that is typically used
in block headers. When baking, bakers generate random nonces whose
hash is commited in the block they bake. They will typically
reveal the aforementionned nonce during the next cycle. *)
val inject_block: val inject_block:
Client_commands.context -> Client_commands.context ->
@ -20,6 +24,11 @@ val inject_block:
src_sk:secret_key -> src_sk:secret_key ->
Operation_hash.t list -> Operation_hash.t list ->
Block_hash.t tzresult Lwt.t Block_hash.t tzresult Lwt.t
(** [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
precomputed). [src_sk] is used to sign the block header. *)
val forge_block: val forge_block:
Client_commands.context -> Client_commands.context ->
@ -29,11 +38,10 @@ val forge_block:
?best_effort:bool -> ?best_effort:bool ->
?sort:bool -> ?sort:bool ->
?timestamp:Time.t -> ?timestamp:Time.t ->
?max_priority:int -> priority:[`Set of int | `Auto of (public_key_hash * int option)] ->
?priority:int ->
seed_nonce:Nonce.t -> seed_nonce:Nonce.t ->
src_sk:secret_key -> src_sk:secret_key ->
public_key_hash -> unit ->
Block_hash.t tzresult Lwt.t Block_hash.t tzresult Lwt.t
module State : sig module State : sig

View File

@ -23,8 +23,9 @@ let mine_block cctxt block ?force ?max_priority ?src_sk delegate =
let seed_nonce = Client_mining_forge.generate_seed_nonce () in let seed_nonce = Client_mining_forge.generate_seed_nonce () in
Client_mining_forge.forge_block cctxt Client_mining_forge.forge_block cctxt
~timestamp:(Time.now ()) ~timestamp:(Time.now ())
?force ?max_priority ?force
~seed_nonce ~src_sk block delegate >>=? fun block_hash -> ~seed_nonce ~src_sk block
~priority:(`Auto (delegate, max_priority)) () >>=? fun block_hash ->
Client_mining_forge.State.record_block cctxt level block_hash seed_nonce Client_mining_forge.State.record_block cctxt level block_hash seed_nonce
|> trace_exn (Failure "Error while recording block") >>=? fun () -> |> trace_exn (Failure "Error while recording block") >>=? fun () ->
cctxt.message "Injected block %a" Block_hash.pp_short block_hash >>= fun () -> cctxt.message "Injected block %a" Block_hash.pp_short block_hash >>= fun () ->

View File

@ -51,9 +51,15 @@ module Context : sig
val level: val level:
Client_commands.context -> Client_commands.context ->
block -> Level.t tzresult Lwt.t block -> Level.t tzresult Lwt.t
(** [level cctxt blk] returns the (protocol view of the) level of
[blk]. *)
val next_level: val next_level:
Client_commands.context -> Client_commands.context ->
block -> Level.t tzresult Lwt.t block -> Level.t tzresult Lwt.t
(** [next_level cctxt blk] returns the (protocol view of the) level
of the successor of [blk]. *)
module Nonce : sig module Nonce : sig
val hash: val hash:
Client_commands.context -> Client_commands.context ->
@ -130,6 +136,10 @@ module Helpers : sig
val minimal_time: val minimal_time:
Client_commands.context -> Client_commands.context ->
block -> ?prio:int -> unit -> Time.t tzresult Lwt.t block -> ?prio:int -> unit -> Time.t tzresult Lwt.t
(** [minimal_time cctxt blk ?prio ()] is the minimal acceptable
timestamp for the successor of [blk]. [?prio] defaults to
[0]. *)
val apply_operation: val apply_operation:
Client_commands.context -> Client_commands.context ->
block -> Block_hash.t -> Operation_hash.t -> MBytes.t -> MBytes.t option -> block -> Block_hash.t -> Operation_hash.t -> MBytes.t -> MBytes.t option ->
@ -309,6 +319,17 @@ module Helpers : sig
seed_nonce_hash:Nonce_hash.t -> seed_nonce_hash:Nonce_hash.t ->
proof_of_work_nonce:MBytes.t -> proof_of_work_nonce:MBytes.t ->
unit -> MBytes.t tzresult Lwt.t unit -> MBytes.t tzresult Lwt.t
(** [block cctxt root ~net ~predecessor ~timestamp ~fitness
~operations ~level ~priority ~seed_nonce_hash
~proof_of_work_nonce ()] returns the binary serialization of
a block header (comprising the shell and protocol-specific
part), rooted at [root], belonging to [net], with
predecessor [predecessor], [timestamp], [fitness],
associated operations [operations], level [level] (the
protocol cannot deduce it from [predecessor] on its own),
priority [priority] (the priority of this miner in the
mining queue associated to [level]), [seed_nonce_hash] (the
chosen seed that we will reveal in the next cycle). *)
end end
module Parse : sig module Parse : sig

View File

@ -28,6 +28,11 @@ module RPC : sig
val inject_block: val inject_block:
t -> ?force:bool -> MBytes.t -> t -> ?force:bool -> MBytes.t ->
(Block_hash.t * unit tzresult Lwt.t) tzresult Lwt.t (Block_hash.t * unit tzresult Lwt.t) tzresult Lwt.t
(** [inject_block node ?force bytes] tries to insert [bytes]
(supposedly the serialization of a block header) inside
[node]. If [?force] is true, the block will be inserted even on
non strictly increasing fitness. *)
val inject_operation: val inject_operation:
t -> ?force:bool -> MBytes.t -> t -> ?force:bool -> MBytes.t ->
(Operation_hash.t * unit tzresult Lwt.t) Lwt.t (Operation_hash.t * unit tzresult Lwt.t) Lwt.t

View File

@ -171,7 +171,7 @@ module Blocks = struct
let info = let info =
RPC.service RPC.service
~description:"All the block informations." ~description:"All the information about a block."
~input: ~input:
(conv (conv
(fun x -> Some x) (fun x -> Some x)
@ -648,7 +648,7 @@ let inject_block =
contextual RPCs from the latest block \ contextual RPCs from the latest block \
(e.g. '/blocks/head/context/preapply'). Returns the ID of the \ (e.g. '/blocks/head/context/preapply'). Returns the ID of the \
block. By default, the RPC will wait for the block to be \ block. By default, the RPC will wait for the block to be \
validated before to answer." validated before answering."
~input: ~input:
(conv (conv
(fun (block, blocking, force) -> (fun (block, blocking, force) ->
@ -661,7 +661,7 @@ let inject_block =
(describe (describe
~description: ~description:
"Should the RPC wait for the block to be \ "Should the RPC wait for the block to be \
validated before to answer. (default: true)" validated before answering. (default: true)"
bool)) bool))
(opt "force" (opt "force"
(describe (describe
@ -681,7 +681,7 @@ let inject_operation =
ID of the operation. The `signedOperationContents` should be \ ID of the operation. The `signedOperationContents` should be \
constructed using a contextual RPCs from the latest block \ constructed using a contextual RPCs from the latest block \
and signed by the client. By default, the RPC will wait for \ and signed by the client. By default, the RPC will wait for \
the operation to be (pre-)validated before to answer. See \ the operation to be (pre-)validated before answering. See \
RPCs ubder /blocks/prevalidation for more details on the \ RPCs ubder /blocks/prevalidation for more details on the \
prevalidation context." prevalidation context."
~input: ~input:
@ -693,7 +693,7 @@ let inject_operation =
(describe (describe
~description: ~description:
"Should the RPC wait for the operation to be \ "Should the RPC wait for the operation to be \
(pre-)validated before to answer. (default: true)" (pre-)validated before answering. (default: true)"
bool) bool)
true) true)
(opt "force" (opt "force"
@ -748,7 +748,7 @@ let inject_protocol =
(describe (describe
~description: ~description:
"Should the RPC wait for the protocol to be \ "Should the RPC wait for the protocol to be \
validated before to answer. (default: true)" validated before answering. (default: true)"
bool) bool)
true) true)
(opt "force" (opt "force"

View File

@ -37,4 +37,7 @@ val unsigned_header_encoding:
val forge_header: val forge_header:
Updater.shell_block -> proto_header -> MBytes.t Updater.shell_block -> proto_header -> MBytes.t
(** [forge_header shell_hdr proto_hdr] is the binary serialization
(using [unsigned_header_encoding]) of a block header,
comprising both the shell and the protocol part of the header,
without the signature. *)

View File

@ -15,6 +15,11 @@ val paying_priorities: context -> int32 list
val minimal_time: val minimal_time:
context -> int32 -> Time.t -> Time.t tzresult Lwt.t context -> int32 -> Time.t -> Time.t tzresult Lwt.t
(** [minimal_time ctxt priority pred_block_time] returns the minimal
time, given the predecessor block timestamp [pred_block_time],
after which a miner with priority [priority] is allowed to
mine. Fail with [Invalid_slot_durations_constant] if the minimal
time cannot be computed. *)
val pay_mining_bond: val pay_mining_bond:
context -> context ->
@ -47,10 +52,11 @@ val base_mining_reward: context -> priority:int32 -> Tez.t
val endorsement_reward: block_priority:int32 -> Tez.t tzresult Lwt.t val endorsement_reward: block_priority:int32 -> Tez.t tzresult Lwt.t
(** The contract owning rolls for the first mining priorities of a level. *)
val mining_priorities: val mining_priorities:
context -> Level.t -> public_key_hash lazy_list context -> Level.t -> public_key_hash lazy_list
(** [mining_priorities ctxt level] is the lazy list of contract's
public key hashes that are allowed to mine for [level]. *)
val endorsement_priorities: val endorsement_priorities:
context -> Level.t -> public_key_hash lazy_list context -> Level.t -> public_key_hash lazy_list
@ -60,6 +66,11 @@ val first_mining_priorities:
public_key_hash -> public_key_hash ->
Level.t -> Level.t ->
int32 list tzresult Lwt.t int32 list tzresult Lwt.t
(** [first_mining_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
returned. *)
val first_endorsement_slots: val first_endorsement_slots:
context -> context ->

View File

@ -344,7 +344,7 @@ let mining_rights_for_delegate
Tezos_context.Timestamp.get_current ctxt >>= fun timestamp -> Tezos_context.Timestamp.get_current ctxt >>= fun timestamp ->
Mining.minimal_time ctxt priority timestamp >>= function Mining.minimal_time ctxt priority timestamp >>= function
| Ok time -> Lwt.return (raw_level, Int32.to_int priority, Some time) | Ok time -> Lwt.return (raw_level, Int32.to_int priority, Some time)
| Error _ -> Lwt.return (raw_level, Int32.to_int priority, None)) | Error _ -> Lwt.return (raw_level, Int32.to_int priority, None))
priorities >>= fun priorities -> priorities >>= fun priorities ->
return (priorities @ t) return (priorities @ t)
in in

View File

@ -69,6 +69,9 @@ module Timestamp : sig
val to_seconds: time -> string val to_seconds: time -> string
val get_current: context -> Time.t Lwt.t val get_current: context -> Time.t Lwt.t
(** [get_current ctxt] returns the current timestamp of [ctxt]. When
[ctxt] is the context of a block, the block timestamp is used,
otherwise a timestamp is inferred otherwise. *)
end end

View File

@ -177,7 +177,7 @@ let mine contract =
let seed_nonce = Client_mining_forge.generate_seed_nonce () in let seed_nonce = Client_mining_forge.generate_seed_nonce () in
Client_mining_forge.forge_block cctxt Client_mining_forge.forge_block cctxt
~timestamp:(Time.now ()) ~seed_nonce ~src_sk:contract.secret_key ~timestamp:(Time.now ()) ~seed_nonce ~src_sk:contract.secret_key
block contract.public_key_hash >>=? fun block_hash -> block ~priority:(`Auto (contract.public_key_hash, None)) () >>=? fun block_hash ->
return () return ()
let ecoproto_error f = function let ecoproto_error f = function