Client refactor: Move Client_node_rpcs into Shell_services

This commit is contained in:
Grégoire Henry 2018-02-08 10:51:02 +01:00
parent 21789be756
commit 1858bdd852
15 changed files with 277 additions and 287 deletions

View File

@ -193,7 +193,7 @@ let rec count =
let list url (cctxt : Client_commands.full_context) = let list url (cctxt : Client_commands.full_context) =
let args = String.split '/' url in let args = String.split '/' url in
Client_node_rpcs.describe cctxt Shell_services.describe cctxt
~recurse:true args >>=? fun tree -> ~recurse:true args >>=? fun tree ->
let open RPC_description in let open RPC_description in
let collected_args = ref [] in let collected_args = ref [] in
@ -293,7 +293,7 @@ let list url (cctxt : Client_commands.full_context) =
let schema url (cctxt : Client_commands.full_context) = let schema url (cctxt : Client_commands.full_context) =
let args = String.split '/' url in let args = String.split '/' url in
let open RPC_description in let open RPC_description in
Client_node_rpcs.describe cctxt ~recurse:false args >>=? function Shell_services.describe cctxt ~recurse:false args >>=? function
| Static { services } -> begin | Static { services } -> begin
match RPC_service.MethMap.find `POST services with match RPC_service.MethMap.find `POST services with
| exception Not_found -> | exception Not_found ->
@ -318,7 +318,7 @@ let schema url (cctxt : Client_commands.full_context) =
let format url (cctxt : #Client_commands.logging_rpcs) = let format url (cctxt : #Client_commands.logging_rpcs) =
let args = String.split '/' url in let args = String.split '/' url in
let open RPC_description in let open RPC_description in
Client_node_rpcs.describe cctxt ~recurse:false args >>=? function Shell_services.describe cctxt ~recurse:false args >>=? function
| Static { services } -> begin | Static { services } -> begin
match RPC_service.MethMap.find `POST services with match RPC_service.MethMap.find `POST services with
| exception Not_found -> | exception Not_found ->
@ -369,7 +369,7 @@ let display_answer (cctxt : #Client_commands.full_context) = function
let call raw_url (cctxt : #Client_commands.full_context) = let call raw_url (cctxt : #Client_commands.full_context) =
let uri = Uri.of_string raw_url in let uri = Uri.of_string raw_url in
let args = String.split_path (Uri.path uri) in let args = String.split_path (Uri.path uri) in
Client_node_rpcs.describe cctxt ~recurse:false args >>=? function Shell_services.describe cctxt ~recurse:false args >>=? function
| Static { services } -> begin | Static { services } -> begin
match RPC_service.MethMap.find `POST services with match RPC_service.MethMap.find `POST services with
| exception Not_found -> | exception Not_found ->

View File

@ -24,7 +24,7 @@ let commands () = Cli_entries.[
~desc: "the prefix of the hash to complete" @@ ~desc: "the prefix of the hash to complete" @@
stop) stop)
(fun unique prefix (cctxt : Client_commands.full_context) -> (fun unique prefix (cctxt : Client_commands.full_context) ->
Client_node_rpcs.complete Shell_services.complete
cctxt ~block:cctxt#block prefix >>=? fun completions -> cctxt ~block:cctxt#block prefix >>=? fun completions ->
match completions with match completions with
| [] -> Pervasives.exit 3 | [] -> Pervasives.exit 3
@ -38,7 +38,7 @@ let commands () = Cli_entries.[
(prefixes [ "bootstrapped" ] @@ (prefixes [ "bootstrapped" ] @@
stop) stop)
(fun () (cctxt : Client_commands.full_context) -> (fun () (cctxt : Client_commands.full_context) ->
Client_node_rpcs.bootstrapped cctxt >>=? fun stream -> Shell_services.bootstrapped cctxt >>=? fun (stream, _) ->
Lwt_stream.iter_s Lwt_stream.iter_s
(fun (hash, time) -> (fun (hash, time) ->
cctxt#message "Current head: %a (%a)" cctxt#message "Current head: %a (%a)"

View File

@ -1,49 +0,0 @@
(**************************************************************************)
(* *)
(* Copyright (c) 2014 - 2018. *)
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
(* *)
(* All rights reserved. No warranty, explicit or implicit, provided. *)
(* *)
(**************************************************************************)
(* Tezos Command line interface - RPC Calls *)
open Client_rpcs
let errors (rpc : #Client_rpcs.ctxt) =
call_service0 rpc RPC_error.service ()
let forge_block_header rpc header =
call_service0 rpc Shell_services.forge_block_header header
let inject_block cctxt
?(async = false) ?(force = false) ?net_id
raw operations =
call_err_service0 cctxt Shell_services.inject_block
{ raw ; blocking = not async ; force ; net_id ; operations }
let inject_operation cctxt ?(async = false) ?net_id operation =
call_err_service0 cctxt Shell_services.inject_operation
(operation, not async, net_id)
let inject_protocol cctxt ?(async = false) ?force protocol =
call_err_service0 cctxt Shell_services.inject_protocol
(protocol, not async, force)
let bootstrapped cctxt =
call_streamed_service0 cctxt Shell_services.bootstrapped ()
let complete cctxt ?block prefix =
match block with
| None ->
call_service1 cctxt Shell_services.complete prefix ()
| Some block ->
Block_services.complete cctxt block prefix
let describe cctxt ?(recurse = true) path =
Client_rpcs.call_service cctxt
Shell_services.describe
((), path) { recurse } ()
end

View File

@ -1,54 +0,0 @@
(**************************************************************************)
(* *)
(* Copyright (c) 2014 - 2018. *)
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
(* *)
(* All rights reserved. No warranty, explicit or implicit, provided. *)
(* *)
(**************************************************************************)
val errors:
#Client_rpcs.ctxt -> Json_schema.schema tzresult Lwt.t
val forge_block_header:
#Client_rpcs.ctxt ->
Block_header.t ->
MBytes.t tzresult Lwt.t
val inject_block:
#Client_rpcs.ctxt ->
?async:bool -> ?force:bool -> ?net_id:Net_id.t ->
MBytes.t -> Operation.t list list ->
Block_hash.t tzresult Lwt.t
(** [inject_block cctxt ?async ?force raw_block] tries to inject
[raw_block] inside the node. If [?async] 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:
#Client_rpcs.ctxt ->
?async:bool -> ?net_id:Net_id.t ->
MBytes.t ->
Operation_hash.t tzresult Lwt.t
val inject_protocol:
#Client_rpcs.ctxt ->
?async:bool -> ?force:bool ->
Protocol.t ->
Protocol_hash.t tzresult Lwt.t
end
val bootstrapped:
#Client_rpcs.ctxt -> (Block_hash.t * Time.t) Lwt_stream.t tzresult Lwt.t
val complete:
#Client_rpcs.ctxt ->
?block:Block_services.block -> string -> string list tzresult Lwt.t
val describe:
#Client_rpcs.ctxt ->
?recurse:bool -> string list ->
Data_encoding.json_schema RPC_description.directory tzresult Lwt.t

View File

@ -39,7 +39,7 @@ let commands () =
Lwt.catch Lwt.catch
(fun () -> (fun () ->
Lwt_utils_unix.Protocol.read_dir dirname >>=? fun (_hash, proto) -> Lwt_utils_unix.Protocol.read_dir dirname >>=? fun (_hash, proto) ->
Client_node_rpcs.inject_protocol cctxt proto >>= function Shell_services.inject_protocol cctxt proto >>= function
| Ok hash -> | Ok hash ->
cctxt#message "Injected protocol %a successfully" Protocol_hash.pp_short hash >>= fun () -> cctxt#message "Injected protocol %a successfully" Protocol_hash.pp_short hash >>= fun () ->
return () return ()

View File

@ -43,3 +43,8 @@ let wrap param_encoding =
(function Error x -> Some x | _ -> None) (function Error x -> Some x | _ -> None)
(fun x -> Error x) ; (fun x -> Error x) ;
] ]
module F = struct
open RPC_context
let schema ctxt = make_call service ctxt () () ()
end

View File

@ -13,3 +13,8 @@ val service:
([ `POST ], unit, unit, unit, unit, Json_schema.schema) RPC_service.t ([ `POST ], unit, unit, unit, unit, Json_schema.schema) RPC_service.t
val encoding: error list Data_encoding.t val encoding: error list Data_encoding.t
val wrap: 'a Data_encoding.t -> 'a tzresult Data_encoding.encoding val wrap: 'a Data_encoding.t -> 'a tzresult Data_encoding.encoding
module F : sig
open RPC_context
val schema: #simple -> Json_schema.schema tzresult Lwt.t
end

View File

@ -401,18 +401,18 @@ let build_rpc_directory node =
let res = let res =
Data_encoding.Binary.to_bytes Block_header.encoding header in Data_encoding.Binary.to_bytes Block_header.encoding header in
RPC_answer.return res in RPC_answer.return res in
RPC_directory.register0 dir Shell_services.forge_block_header RPC_directory.register0 dir Shell_services.S.forge_block_header
implementation in implementation in
let dir = let dir =
let implementation () let implementation ()
{ Shell_services.raw ; blocking ; force ; operations } = { Shell_services.S.raw ; blocking ; force ; operations } =
begin begin
Node.RPC.inject_block Node.RPC.inject_block
node ~force node ~force
raw operations >>=? fun (hash, wait) -> raw operations >>=? fun (hash, wait) ->
(if blocking then wait else return ()) >>=? fun () -> return hash (if blocking then wait else return ()) >>=? fun () -> return hash
end >>= RPC_answer.return in end >>= RPC_answer.return in
RPC_directory.register0 dir Shell_services.inject_block implementation in RPC_directory.register0 dir Shell_services.S.inject_block implementation in
let dir = let dir =
let implementation () (contents, blocking, net_id) = let implementation () (contents, blocking, net_id) =
Node.RPC.inject_operation Node.RPC.inject_operation
@ -420,25 +420,25 @@ let build_rpc_directory node =
begin begin
(if blocking then wait else return ()) >>=? fun () -> return hash (if blocking then wait else return ()) >>=? fun () -> return hash
end >>= RPC_answer.return in end >>= RPC_answer.return in
RPC_directory.register0 dir Shell_services.inject_operation implementation in RPC_directory.register0 dir Shell_services.S.inject_operation implementation in
let dir = let dir =
let implementation () (proto, blocking, force) = let implementation () (proto, blocking, force) =
Node.RPC.inject_protocol ?force node proto >>= fun (hash, wait) -> Node.RPC.inject_protocol ?force node proto >>= fun (hash, wait) ->
begin begin
(if blocking then wait else return ()) >>=? fun () -> return hash (if blocking then wait else return ()) >>=? fun () -> return hash
end >>= RPC_answer.return in end >>= RPC_answer.return in
RPC_directory.register0 dir Shell_services.inject_protocol implementation in RPC_directory.register0 dir Shell_services.S.inject_protocol implementation in
let dir = let dir =
let implementation () () = let implementation () () =
RPC_answer.return_stream (Node.RPC.bootstrapped node) in RPC_answer.return_stream (Node.RPC.bootstrapped node) in
RPC_directory.register0 dir Shell_services.bootstrapped implementation in RPC_directory.register0 dir Shell_services.S.bootstrapped implementation in
let dir = let dir =
let implementation () () = let implementation () () =
RPC_answer.return RPC_answer.return
Data_encoding.Json.(schema Error_monad.error_encoding) in Data_encoding.Json.(schema Error_monad.error_encoding) in
RPC_directory.register0 dir RPC_error.service implementation in RPC_directory.register0 dir RPC_error.service implementation in
let dir = let dir =
RPC_directory.register1 dir Shell_services.complete RPC_directory.register1 dir Shell_services.S.complete
(fun s () () -> (fun s () () ->
Node.RPC.complete node s >>= RPC_answer.return) in Node.RPC.complete node s >>= RPC_answer.return) in
let dir = let dir =
@ -616,5 +616,5 @@ let build_rpc_directory node =
Node.RPC.Network.Point.events node point |> RPC_answer.return in Node.RPC.Network.Point.events node point |> RPC_answer.return in
RPC_directory.register1 dir P2p_services.Points.S.events implementation in RPC_directory.register1 dir P2p_services.Points.S.events implementation in
let dir = let dir =
RPC_directory.register_describe_directory_service dir Shell_services.describe in RPC_directory.register_describe_directory_service dir Shell_services.S.describe in
dir dir

View File

@ -7,152 +7,188 @@
(* *) (* *)
(**************************************************************************) (**************************************************************************)
open Data_encoding module S = struct
let forge_block_header = open Data_encoding
RPC_service.post_service
~description: "Forge a block header"
~query: RPC_query.empty
~input: Block_header.encoding
~output: (obj1 (req "block" bytes))
RPC_path.(root / "forge_block_header")
type inject_block_param = { let forge_block_header =
raw: MBytes.t ; RPC_service.post_service
blocking: bool ; ~description: "Forge a block header"
force: bool ; ~query: RPC_query.empty
net_id: Net_id.t option ; ~input: Block_header.encoding
operations: Operation.t list list ; ~output: (obj1 (req "block" bytes))
} RPC_path.(root / "forge_block_header")
let inject_block_param = type inject_block_param = {
conv raw: MBytes.t ;
(fun { raw ; blocking ; force ; net_id ; operations } -> blocking: bool ;
(raw, blocking, force, net_id, operations)) force: bool ;
(fun (raw, blocking, force, net_id, operations) -> net_id: Net_id.t option ;
{ raw ; blocking ; force ; net_id ; operations }) operations: Operation.t list list ;
(obj5 }
(req "data" bytes)
(dft "blocking"
(describe
~description:
"Should the RPC wait for the block to be \
validated before answering. (default: true)"
bool)
true)
(dft "force"
(describe
~description:
"Should we inject the block when its fitness is below \
the current head. (default: false)"
bool)
false)
(opt "net_id" Net_id.encoding)
(req "operations"
(describe
~description:"..."
(list (list (dynamic_size Operation.encoding))))))
let inject_block = let inject_block_param =
RPC_service.post_service conv
~description: (fun { raw ; blocking ; force ; net_id ; operations } ->
"Inject a block in the node and broadcast it. The `operations` \ (raw, blocking, force, net_id, operations))
embedded in `blockHeader` might be pre-validated using a \ (fun (raw, blocking, force, net_id, operations) ->
contextual RPCs from the latest block \ { raw ; blocking ; force ; net_id ; operations })
(e.g. '/blocks/head/context/preapply'). Returns the ID of the \ (obj5
block. By default, the RPC will wait for the block to be \ (req "data" bytes)
validated before answering."
~query: RPC_query.empty
~input: inject_block_param
~output:
(RPC_error.wrap @@
(obj1 (req "block_hash" Block_hash.encoding)))
RPC_path.(root / "inject_block")
let inject_operation =
RPC_service.post_service
~description:
"Inject an operation in node and broadcast it. Returns the \
ID of the operation. The `signedOperationContents` should be \
constructed using a contextual RPCs from the latest block \
and signed by the client. By default, the RPC will wait for \
the operation to be (pre-)validated before answering. See \
RPCs under /blocks/prevalidation for more details on the \
prevalidation context."
~query: RPC_query.empty
~input:
(obj3
(req "signedOperationContents"
(describe ~title: "Tezos signed operation (hex encoded)"
bytes))
(dft "blocking" (dft "blocking"
(describe (describe
~description: ~description:
"Should the RPC wait for the operation to be \ "Should the RPC wait for the block to be \
(pre-)validated before answering. (default: true)"
bool)
true)
(opt "net_id" Net_id.encoding))
~output:
(RPC_error.wrap @@
describe
~title: "Hash of the injected operation" @@
(obj1 (req "injectedOperation" Operation_hash.encoding)))
RPC_path.(root / "inject_operation")
let inject_protocol =
RPC_service.post_service
~description:
"Inject a protocol in node. Returns the ID of the protocol."
~query: RPC_query.empty
~input:
(obj3
(req "protocol"
(describe ~title: "Tezos protocol" Protocol.encoding))
(dft "blocking"
(describe
~description:
"Should the RPC wait for the protocol to be \
validated before answering. (default: true)" validated before answering. (default: true)"
bool) bool)
true) true)
(opt "force" (dft "force"
(describe (describe
~description: ~description:
"Should we inject protocol that is invalid. (default: false)" "Should we inject the block when its fitness is below \
bool))) the current head. (default: false)"
~output: bool)
(RPC_error.wrap @@ false)
describe (opt "net_id" Net_id.encoding)
~title: "Hash of the injected protocol" @@ (req "operations"
(obj1 (req "injectedProtocol" Protocol_hash.encoding))) (describe
RPC_path.(root / "inject_protocol") ~description:"..."
(list (list (dynamic_size Operation.encoding))))))
let bootstrapped = let inject_block =
RPC_service.post_service RPC_service.post_service
~description:"" ~description:
~query: RPC_query.empty "Inject a block in the node and broadcast it. The `operations` \
~input: empty embedded in `blockHeader` might be pre-validated using a \
~output: (obj2 contextual RPCs from the latest block \
(req "block" Block_hash.encoding) (e.g. '/blocks/head/context/preapply'). Returns the ID of the \
(req "timestamp" Time.encoding)) block. By default, the RPC will wait for the block to be \
RPC_path.(root / "bootstrapped") validated before answering."
~query: RPC_query.empty
~input: inject_block_param
~output:
(RPC_error.wrap @@
(obj1 (req "block_hash" Block_hash.encoding)))
RPC_path.(root / "inject_block")
let complete = let inject_operation =
let prefix_arg = RPC_service.post_service
let destruct s = Ok s ~description:
and construct s = s in "Inject an operation in node and broadcast it. Returns the \
RPC_arg.make ~name:"prefix" ~destruct ~construct () in ID of the operation. The `signedOperationContents` should be \
RPC_service.post_service constructed using a contextual RPCs from the latest block \
~description: "Try to complete a prefix of a Base58Check-encoded data. \ and signed by the client. By default, the RPC will wait for \
This RPC is actually able to complete hashes of \ the operation to be (pre-)validated before answering. See \
block and hashes of operations." RPCs under /blocks/prevalidation for more details on the \
~query: RPC_query.empty prevalidation context."
~input: empty ~query: RPC_query.empty
~output: (list string) ~input:
RPC_path.(root / "complete" /: prefix_arg ) (obj3
(req "signedOperationContents"
(describe ~title: "Tezos signed operation (hex encoded)"
bytes))
(dft "blocking"
(describe
~description:
"Should the RPC wait for the operation to be \
(pre-)validated before answering. (default: true)"
bool)
true)
(opt "net_id" Net_id.encoding))
~output:
(RPC_error.wrap @@
describe
~title: "Hash of the injected operation" @@
(obj1 (req "injectedOperation" Operation_hash.encoding)))
RPC_path.(root / "inject_operation")
let describe = let inject_protocol =
RPC_service.description_service RPC_service.post_service
~description: "RPCs documentation and input/output schema" ~description:
RPC_path.(root / "describe") "Inject a protocol in node. Returns the ID of the protocol."
~query: RPC_query.empty
~input:
(obj3
(req "protocol"
(describe ~title: "Tezos protocol" Protocol.encoding))
(dft "blocking"
(describe
~description:
"Should the RPC wait for the protocol to be \
validated before answering. (default: true)"
bool)
true)
(opt "force"
(describe
~description:
"Should we inject protocol that is invalid. (default: false)"
bool)))
~output:
(RPC_error.wrap @@
describe
~title: "Hash of the injected protocol" @@
(obj1 (req "injectedProtocol" Protocol_hash.encoding)))
RPC_path.(root / "inject_protocol")
let bootstrapped =
RPC_service.post_service
~description:""
~query: RPC_query.empty
~input: empty
~output: (obj2
(req "block" Block_hash.encoding)
(req "timestamp" Time.encoding))
RPC_path.(root / "bootstrapped")
let complete =
let prefix_arg =
let destruct s = Ok s
and construct s = s in
RPC_arg.make ~name:"prefix" ~destruct ~construct () in
RPC_service.post_service
~description: "Try to complete a prefix of a Base58Check-encoded data. \
This RPC is actually able to complete hashes of \
block and hashes of operations."
~query: RPC_query.empty
~input: empty
~output: (list string)
RPC_path.(root / "complete" /: prefix_arg )
let describe =
RPC_service.description_service
~description: "RPCs documentation and input/output schema"
RPC_path.(root / "describe")
end
open RPC_context
let forge_block_header ctxt header =
make_call S.forge_block_header ctxt () () header
let inject_block ctxt
?(async = false) ?(force = false) ?net_id
raw operations =
make_err_call S.inject_block ctxt () ()
{ raw ; blocking = not async ; force ; net_id ; operations }
let inject_operation ctxt ?(async = false) ?net_id operation =
make_err_call S.inject_operation ctxt () ()
(operation, not async, net_id)
let inject_protocol ctxt ?(async = false) ?force protocol =
make_err_call S.inject_protocol ctxt () ()
(protocol, not async, force)
let bootstrapped ctxt =
make_streamed_call S.bootstrapped ctxt () () ()
let complete ctxt ?block prefix =
match block with
| None ->
make_call1 S.complete ctxt prefix () ()
| Some block ->
Block_services.complete ctxt block prefix
let describe ctxt ?(recurse = true) path =
make_call1 S.describe ctxt path { recurse } ()

View File

@ -7,42 +7,89 @@
(* *) (* *)
(**************************************************************************) (**************************************************************************)
val forge_block_header:
([ `POST ], unit,
unit, unit, Block_header.t,
MBytes.t) RPC_service.t
type inject_block_param = { open RPC_context
raw: MBytes.t ;
blocking: bool ; val forge_block_header:
force: bool ; #simple ->
net_id: Net_id.t option ; Block_header.t ->
operations: Operation.t list list ; MBytes.t tzresult Lwt.t
}
val inject_block: val inject_block:
([ `POST ], unit, #simple ->
unit, unit, inject_block_param, ?async:bool -> ?force:bool -> ?net_id:Net_id.t ->
Block_hash.t tzresult) RPC_service.t MBytes.t -> Operation.t list list ->
Block_hash.t tzresult Lwt.t
(** [inject_block cctxt ?async ?force raw_block] tries to inject
[raw_block] inside the node. If [?async] 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:
([ `POST ], unit, #simple ->
unit, unit, (MBytes.t * bool * Net_id.t option), ?async:bool -> ?net_id:Net_id.t ->
Operation_hash.t tzresult) RPC_service.t MBytes.t ->
Operation_hash.t tzresult Lwt.t
val inject_protocol: val inject_protocol:
([ `POST ], unit, #simple ->
unit, unit, (Protocol.t * bool * bool option), ?async:bool -> ?force:bool ->
Protocol_hash.t tzresult) RPC_service.t Protocol.t ->
Protocol_hash.t tzresult Lwt.t
val bootstrapped: val bootstrapped:
([ `POST ], unit, #streamed -> ((Block_hash.t * Time.t) Lwt_stream.t * stopper) tzresult Lwt.t
unit, unit, unit,
Block_hash.t * Time.t) RPC_service.t
val complete: val complete:
([ `POST ], unit, #simple ->
unit * string, unit, unit, ?block:Block_services.block -> string -> string list tzresult Lwt.t
string list) RPC_service.t
val describe: (unit, unit) RPC_service.description_service val describe:
#simple ->
?recurse:bool -> string list ->
Data_encoding.json_schema RPC_description.directory tzresult Lwt.t
module S : sig
val forge_block_header:
([ `POST ], unit,
unit, unit, Block_header.t,
MBytes.t) RPC_service.t
type inject_block_param = {
raw: MBytes.t ;
blocking: bool ;
force: bool ;
net_id: Net_id.t option ;
operations: Operation.t list list ;
}
val inject_block:
([ `POST ], unit,
unit, unit, inject_block_param,
Block_hash.t tzresult) RPC_service.t
val inject_operation:
([ `POST ], unit,
unit, unit, (MBytes.t * bool * Net_id.t option),
Operation_hash.t tzresult) RPC_service.t
val inject_protocol:
([ `POST ], unit,
unit, unit, (Protocol.t * bool * bool option),
Protocol_hash.t tzresult) RPC_service.t
val bootstrapped:
([ `POST ], unit,
unit, unit, unit,
Block_hash.t * Time.t) RPC_service.t
val complete:
([ `POST ], unit,
unit * string, unit, unit,
string list) RPC_service.t
val describe: (unit, unit) RPC_service.description_service
end

View File

@ -104,7 +104,7 @@ let inject_endorsement (cctxt : Client_commands.full_context)
~slot:slot ~slot:slot
() >>=? fun bytes -> () >>=? fun bytes ->
Client_keys.append src_sk bytes >>=? fun signed_bytes -> Client_keys.append src_sk bytes >>=? fun signed_bytes ->
Client_node_rpcs.inject_operation Shell_services.inject_operation
cctxt ?async ~net_id:bi.net_id signed_bytes >>=? fun oph -> cctxt ?async ~net_id:bi.net_id signed_bytes >>=? fun oph ->
State.record_endorsement cctxt level bi.hash slot oph >>=? fun () -> State.record_endorsement cctxt level bi.hash slot oph >>=? fun () ->
return oph return oph

View File

@ -67,7 +67,7 @@ let inject_block cctxt
let block = `Hash shell_header.Tezos_base.Block_header.predecessor in let block = `Hash shell_header.Tezos_base.Block_header.predecessor in
forge_block_header cctxt block forge_block_header cctxt block
src_sk shell_header priority seed_nonce_hash >>=? fun signed_header -> src_sk shell_header priority seed_nonce_hash >>=? fun signed_header ->
Client_node_rpcs.inject_block cctxt Shell_services.inject_block cctxt
?force ?net_id signed_header operations >>=? fun block_hash -> ?force ?net_id signed_header operations >>=? fun block_hash ->
return block_hash return block_hash

View File

@ -19,7 +19,7 @@ let inject_seed_nonce_revelation rpc_config block ?async nonces =
Block_services.info rpc_config block >>=? fun bi -> Block_services.info rpc_config block >>=? fun bi ->
Client_proto_rpcs.Helpers.Forge.Anonymous.operations rpc_config Client_proto_rpcs.Helpers.Forge.Anonymous.operations rpc_config
block ~branch:bi.hash operations >>=? fun bytes -> block ~branch:bi.hash operations >>=? fun bytes ->
Client_node_rpcs.inject_operation Shell_services.inject_operation
rpc_config ?async ~net_id:bi.net_id rpc_config ?async ~net_id:bi.net_id
bytes >>=? fun oph -> bytes >>=? fun oph ->
return oph return oph

View File

@ -68,7 +68,7 @@ let transfer rpc_config
let oph = Operation_hash.hash_bytes [ signed_bytes ] in let oph = Operation_hash.hash_bytes [ signed_bytes ] in
Client_proto_rpcs.Helpers.apply_operation rpc_config block Client_proto_rpcs.Helpers.apply_operation rpc_config block
predecessor oph bytes (Some signature) >>=? fun contracts -> predecessor oph bytes (Some signature) >>=? fun contracts ->
Client_node_rpcs.inject_operation Shell_services.inject_operation
rpc_config ~net_id signed_bytes >>=? fun injected_oph -> rpc_config ~net_id signed_bytes >>=? fun injected_oph ->
assert (Operation_hash.equal oph injected_oph) ; assert (Operation_hash.equal oph injected_oph) ;
return (oph, contracts) return (oph, contracts)
@ -83,7 +83,7 @@ let originate rpc_config ?net_id ~block ?signature bytes =
Client_proto_rpcs.Helpers.apply_operation rpc_config block Client_proto_rpcs.Helpers.apply_operation rpc_config block
predecessor oph bytes signature >>=? function predecessor oph bytes signature >>=? function
| [ contract ] -> | [ contract ] ->
Client_node_rpcs.inject_operation Shell_services.inject_operation
rpc_config ?net_id signed_bytes >>=? fun injected_oph -> rpc_config ?net_id signed_bytes >>=? fun injected_oph ->
assert (Operation_hash.equal oph injected_oph) ; assert (Operation_hash.equal oph injected_oph) ;
return (oph, contract) return (oph, contract)
@ -136,7 +136,7 @@ let delegate_contract rpc_config
Client_keys.sign manager_sk bytes >>=? fun signature -> Client_keys.sign manager_sk bytes >>=? fun signature ->
let signed_bytes = Ed25519.Signature.concat bytes signature in let signed_bytes = Ed25519.Signature.concat bytes signature in
let oph = Operation_hash.hash_bytes [ signed_bytes ] in let oph = Operation_hash.hash_bytes [ signed_bytes ] in
Client_node_rpcs.inject_operation Shell_services.inject_operation
rpc_config ~net_id signed_bytes >>=? fun injected_oph -> rpc_config ~net_id signed_bytes >>=? fun injected_oph ->
assert (Operation_hash.equal oph injected_oph) ; assert (Operation_hash.equal oph injected_oph) ;
return oph return oph
@ -185,7 +185,7 @@ let dictate rpc_config block command seckey =
let signature = Ed25519.sign seckey bytes in let signature = Ed25519.sign seckey bytes in
let signed_bytes = Ed25519.Signature.concat bytes signature in let signed_bytes = Ed25519.Signature.concat bytes signature in
let oph = Operation_hash.hash_bytes [ signed_bytes ] in let oph = Operation_hash.hash_bytes [ signed_bytes ] in
Client_node_rpcs.inject_operation Shell_services.inject_operation
rpc_config ~net_id signed_bytes >>=? fun injected_oph -> rpc_config ~net_id signed_bytes >>=? fun injected_oph ->
assert (Operation_hash.equal oph injected_oph) ; assert (Operation_hash.equal oph injected_oph) ;
return oph return oph

View File

@ -32,7 +32,7 @@ let bake rpc_config ?(timestamp = Time.now ()) block command sk =
Data_encoding.Binary.to_bytes Block_header.encoding Data_encoding.Binary.to_bytes Block_header.encoding
{ shell = shell_header ; proto = proto_header } in { shell = shell_header ; proto = proto_header } in
Client_keys.append sk blk >>=? fun signed_blk -> Client_keys.append sk blk >>=? fun signed_blk ->
Client_node_rpcs.inject_block rpc_config signed_blk [] Shell_services.inject_block rpc_config signed_blk []
let int64_parameter = let int64_parameter =
(Cli_entries.parameter (fun _ p -> (Cli_entries.parameter (fun _ p ->