Shell/RPC: use query parameters in /injection
This commit is contained in:
parent
9bc7b1e573
commit
2a93a336aa
@ -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) ->
|
||||||
Shell_services.inject_protocol cctxt proto >>= function
|
Injection_services.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 ()
|
||||||
|
@ -40,12 +40,13 @@ let commands () = Clic.[
|
|||||||
(prefixes [ "bootstrapped" ] @@
|
(prefixes [ "bootstrapped" ] @@
|
||||||
stop)
|
stop)
|
||||||
(fun () (cctxt : #Client_context.full) ->
|
(fun () (cctxt : #Client_context.full) ->
|
||||||
Shell_services.bootstrapped cctxt >>=? fun (stream, _) ->
|
Monitor_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 (timestamp: %a, validation: %a)"
|
||||||
Block_hash.pp_short hash
|
Block_hash.pp_short hash
|
||||||
Time.pp_hum time) stream >>= fun () ->
|
Time.pp_hum time
|
||||||
|
Time.pp_hum (Time.now ())) stream >>= fun () ->
|
||||||
cctxt#answer "Bootstrapped." >>= fun () ->
|
cctxt#answer "Bootstrapped." >>= fun () ->
|
||||||
return ()
|
return ()
|
||||||
)
|
)
|
||||||
|
84
src/lib_shell/injection_directory.ml
Normal file
84
src/lib_shell/injection_directory.ml
Normal file
@ -0,0 +1,84 @@
|
|||||||
|
(**************************************************************************)
|
||||||
|
(* *)
|
||||||
|
(* Copyright (c) 2014 - 2018. *)
|
||||||
|
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
|
||||||
|
(* *)
|
||||||
|
(* All rights reserved. No warranty, explicit or implicit, provided. *)
|
||||||
|
(* *)
|
||||||
|
(**************************************************************************)
|
||||||
|
|
||||||
|
let read_chain_id validator chain =
|
||||||
|
let distributed_db = Validator.distributed_db validator in
|
||||||
|
let state = Distributed_db.state distributed_db in
|
||||||
|
begin
|
||||||
|
match chain with
|
||||||
|
| None -> Lwt.return_none
|
||||||
|
| Some chain ->
|
||||||
|
Chain_directory.get_chain_id state chain >>= Lwt.return_some
|
||||||
|
end
|
||||||
|
|
||||||
|
let inject_block validator ?force ?chain bytes operations =
|
||||||
|
read_chain_id validator chain >>= fun chain_id ->
|
||||||
|
Validator.validate_block
|
||||||
|
validator ?force ?chain_id bytes operations >>=? fun (hash, block) ->
|
||||||
|
return (hash, (block >>=? fun _ -> return ()))
|
||||||
|
|
||||||
|
let inject_operation validator ?chain bytes =
|
||||||
|
read_chain_id validator chain >>= fun chain_id ->
|
||||||
|
let t =
|
||||||
|
match Data_encoding.Binary.of_bytes Operation.encoding bytes with
|
||||||
|
| None -> failwith "Can't parse the operation"
|
||||||
|
| Some op ->
|
||||||
|
Validator.inject_operation validator ?chain_id op in
|
||||||
|
let hash = Operation_hash.hash_bytes [bytes] in
|
||||||
|
Lwt.return (hash, t)
|
||||||
|
|
||||||
|
let inject_protocol state ?force:_ proto =
|
||||||
|
let proto_bytes =
|
||||||
|
Data_encoding.Binary.to_bytes_exn Protocol.encoding proto in
|
||||||
|
let hash = Protocol_hash.hash_bytes [proto_bytes] in
|
||||||
|
let validation =
|
||||||
|
Updater.compile hash proto >>= function
|
||||||
|
| false ->
|
||||||
|
failwith
|
||||||
|
"Compilation failed (%a)"
|
||||||
|
Protocol_hash.pp_short hash
|
||||||
|
| true ->
|
||||||
|
State.Protocol.store state proto >>= function
|
||||||
|
| None ->
|
||||||
|
failwith
|
||||||
|
"Previously registered protocol (%a)"
|
||||||
|
Protocol_hash.pp_short hash
|
||||||
|
| Some _ -> return ()
|
||||||
|
in
|
||||||
|
Lwt.return (hash, validation)
|
||||||
|
|
||||||
|
let build_rpc_directory validator =
|
||||||
|
|
||||||
|
let distributed_db = Validator.distributed_db validator in
|
||||||
|
let state = Distributed_db.state distributed_db in
|
||||||
|
|
||||||
|
let dir : unit RPC_directory.t ref = ref RPC_directory.empty in
|
||||||
|
let register0 s f =
|
||||||
|
dir := RPC_directory.register !dir s (fun () p q -> f p q) in
|
||||||
|
|
||||||
|
register0 Injection_services.S.block begin fun q (raw, operations) ->
|
||||||
|
inject_block validator
|
||||||
|
?chain:q#chain ~force:q#force raw operations >>=? fun (hash, wait) ->
|
||||||
|
(if q#async then return () else wait) >>=? fun () ->
|
||||||
|
return hash
|
||||||
|
end ;
|
||||||
|
|
||||||
|
register0 Injection_services.S.operation begin fun q contents ->
|
||||||
|
inject_operation validator ?chain:q#chain contents >>= fun (hash, wait) ->
|
||||||
|
(if q#async then return () else wait) >>=? fun () ->
|
||||||
|
return hash
|
||||||
|
end ;
|
||||||
|
|
||||||
|
register0 Injection_services.S.protocol begin fun q protocol ->
|
||||||
|
inject_protocol state ~force:q#force protocol >>= fun (hash, wait) ->
|
||||||
|
(if q#async then return () else wait) >>=? fun () ->
|
||||||
|
return hash
|
||||||
|
end ;
|
||||||
|
|
||||||
|
!dir
|
10
src/lib_shell/injection_directory.mli
Normal file
10
src/lib_shell/injection_directory.mli
Normal file
@ -0,0 +1,10 @@
|
|||||||
|
(**************************************************************************)
|
||||||
|
(* *)
|
||||||
|
(* Copyright (c) 2014 - 2018. *)
|
||||||
|
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
|
||||||
|
(* *)
|
||||||
|
(* All rights reserved. No warranty, explicit or implicit, provided. *)
|
||||||
|
(* *)
|
||||||
|
(**************************************************************************)
|
||||||
|
|
||||||
|
val build_rpc_directory: Validator.t -> unit RPC_directory.t
|
@ -7,7 +7,7 @@
|
|||||||
(* *)
|
(* *)
|
||||||
(**************************************************************************)
|
(**************************************************************************)
|
||||||
|
|
||||||
let build_rpc_directory validator =
|
let build_rpc_directory validator mainchain_validator =
|
||||||
|
|
||||||
let distributed_db = Validator.distributed_db validator in
|
let distributed_db = Validator.distributed_db validator in
|
||||||
let state = Distributed_db.state distributed_db in
|
let state = Distributed_db.state distributed_db in
|
||||||
@ -18,6 +18,30 @@ let build_rpc_directory validator =
|
|||||||
let gen_register1 s f =
|
let gen_register1 s f =
|
||||||
dir := RPC_directory.gen_register !dir s (fun ((), a) p q -> f a p q) in
|
dir := RPC_directory.gen_register !dir s (fun ((), a) p q -> f a p q) in
|
||||||
|
|
||||||
|
gen_register0 Monitor_services.S.bootstrapped begin fun () () ->
|
||||||
|
let block_stream, stopper =
|
||||||
|
Chain_validator.new_head_watcher mainchain_validator in
|
||||||
|
let first_run = ref true in
|
||||||
|
let next () =
|
||||||
|
if !first_run then begin
|
||||||
|
first_run := false ;
|
||||||
|
let chain_state = Chain_validator.chain_state mainchain_validator in
|
||||||
|
Chain.head chain_state >>= fun head ->
|
||||||
|
let head_hash = State.Block.hash head in
|
||||||
|
let head_header = State.Block.header head in
|
||||||
|
Lwt.return (Some (head_hash, head_header.shell.timestamp))
|
||||||
|
end else begin
|
||||||
|
Lwt.pick [
|
||||||
|
( Lwt_stream.get block_stream >|=
|
||||||
|
Option.map ~f:(fun b ->
|
||||||
|
(State.Block.hash b, (State.Block.header b).shell.timestamp)) ) ;
|
||||||
|
(Chain_validator.bootstrapped mainchain_validator >|= fun () -> None) ;
|
||||||
|
]
|
||||||
|
end in
|
||||||
|
let shutdown () = Lwt_watcher.shutdown stopper in
|
||||||
|
RPC_answer.return_stream { next ; shutdown }
|
||||||
|
end ;
|
||||||
|
|
||||||
gen_register0 Monitor_services.S.valid_blocks begin fun q () ->
|
gen_register0 Monitor_services.S.valid_blocks begin fun q () ->
|
||||||
let block_stream, stopper = State.watcher state in
|
let block_stream, stopper = State.watcher state in
|
||||||
let shutdown () = Lwt_watcher.shutdown stopper in
|
let shutdown () = Lwt_watcher.shutdown stopper in
|
||||||
|
@ -7,4 +7,5 @@
|
|||||||
(* *)
|
(* *)
|
||||||
(**************************************************************************)
|
(**************************************************************************)
|
||||||
|
|
||||||
val build_rpc_directory: Validator.t -> unit RPC_directory.t
|
val build_rpc_directory:
|
||||||
|
Validator.t -> Chain_validator.t -> unit RPC_directory.t
|
||||||
|
@ -139,9 +139,10 @@ let build_rpc_directory node =
|
|||||||
dir := RPC_directory.register !dir s (fun () p q -> f p q) in
|
dir := RPC_directory.register !dir s (fun () p q -> f p q) in
|
||||||
|
|
||||||
merge (Protocol_directory.build_rpc_directory node.state) ;
|
merge (Protocol_directory.build_rpc_directory node.state) ;
|
||||||
merge (Monitor_directory.build_rpc_directory node.validator) ;
|
merge (Monitor_directory.build_rpc_directory
|
||||||
merge (Shell_directory.build_rpc_directory
|
|
||||||
node.validator node.mainchain_validator) ;
|
node.validator node.mainchain_validator) ;
|
||||||
|
merge Shell_directory.rpc_directory ;
|
||||||
|
merge (Injection_directory.build_rpc_directory node.validator) ;
|
||||||
merge (Chain_directory.build_rpc_directory node.validator) ;
|
merge (Chain_directory.build_rpc_directory node.validator) ;
|
||||||
merge (P2p.build_rpc_directory node.p2p) ;
|
merge (P2p.build_rpc_directory node.p2p) ;
|
||||||
merge Worker_directory.rpc_directory ;
|
merge Worker_directory.rpc_directory ;
|
||||||
|
@ -7,49 +7,9 @@
|
|||||||
(* *)
|
(* *)
|
||||||
(**************************************************************************)
|
(**************************************************************************)
|
||||||
|
|
||||||
let inject_block validator ?force ?chain_id bytes operations =
|
let rpc_directory =
|
||||||
Validator.validate_block
|
|
||||||
validator ?force ?chain_id bytes operations >>=? fun (hash, block) ->
|
|
||||||
return (hash, (block >>=? fun _ -> return ()))
|
|
||||||
|
|
||||||
let inject_operation validator ?chain_id bytes =
|
|
||||||
let t =
|
|
||||||
match Data_encoding.Binary.of_bytes Operation.encoding bytes with
|
|
||||||
| None -> failwith "Can't parse the operation"
|
|
||||||
| Some op ->
|
|
||||||
Validator.inject_operation validator ?chain_id op
|
|
||||||
in
|
|
||||||
let hash = Operation_hash.hash_bytes [bytes] in
|
|
||||||
Lwt.return (hash, t)
|
|
||||||
|
|
||||||
let inject_protocol state ?force:_ proto =
|
|
||||||
let proto_bytes =
|
|
||||||
Data_encoding.Binary.to_bytes_exn Protocol.encoding proto in
|
|
||||||
let hash = Protocol_hash.hash_bytes [proto_bytes] in
|
|
||||||
let validation =
|
|
||||||
Updater.compile hash proto >>= function
|
|
||||||
| false ->
|
|
||||||
failwith
|
|
||||||
"Compilation failed (%a)"
|
|
||||||
Protocol_hash.pp_short hash
|
|
||||||
| true ->
|
|
||||||
State.Protocol.store state proto >>= function
|
|
||||||
| None ->
|
|
||||||
failwith
|
|
||||||
"Previously registered protocol (%a)"
|
|
||||||
Protocol_hash.pp_short hash
|
|
||||||
| Some _ -> return ()
|
|
||||||
in
|
|
||||||
Lwt.return (hash, validation)
|
|
||||||
|
|
||||||
let build_rpc_directory validator mainchain_validator =
|
|
||||||
|
|
||||||
let distributed_db = Validator.distributed_db validator in
|
|
||||||
let state = Distributed_db.state distributed_db in
|
|
||||||
|
|
||||||
let dir : unit RPC_directory.t ref = ref RPC_directory.empty in
|
let dir : unit RPC_directory.t ref = ref RPC_directory.empty in
|
||||||
let gen_register0 s f =
|
|
||||||
dir := RPC_directory.gen_register !dir s (fun () p q -> f p q) in
|
|
||||||
let register0 s f =
|
let register0 s f =
|
||||||
dir := RPC_directory.register !dir s (fun () p q -> f p q) in
|
dir := RPC_directory.register !dir s (fun () p q -> f p q) in
|
||||||
|
|
||||||
@ -57,49 +17,4 @@ let build_rpc_directory validator mainchain_validator =
|
|||||||
return (Data_encoding.Binary.to_bytes_exn Block_header.encoding header)
|
return (Data_encoding.Binary.to_bytes_exn Block_header.encoding header)
|
||||||
end ;
|
end ;
|
||||||
|
|
||||||
register0 Shell_services.S.inject_block begin fun () p ->
|
|
||||||
let { Shell_services.S.raw ; blocking ; force ; operations } = p in
|
|
||||||
inject_block validator ~force raw operations >>=? fun (hash, wait) ->
|
|
||||||
(if blocking then wait else return ()) >>=? fun () ->
|
|
||||||
return hash
|
|
||||||
end ;
|
|
||||||
|
|
||||||
register0 Shell_services.S.inject_operation begin fun () p ->
|
|
||||||
let (contents, blocking, chain_id) = p in
|
|
||||||
inject_operation validator ?chain_id contents >>= fun (hash, wait) ->
|
|
||||||
(if blocking then wait else return ()) >>=? fun () ->
|
|
||||||
return hash
|
|
||||||
end ;
|
|
||||||
|
|
||||||
register0 Shell_services.S.inject_protocol begin fun () p ->
|
|
||||||
let (proto, blocking, force) = p in
|
|
||||||
inject_protocol state ?force proto >>= fun (hash, wait) ->
|
|
||||||
(if blocking then wait else return ()) >>=? fun () ->
|
|
||||||
return hash
|
|
||||||
end ;
|
|
||||||
|
|
||||||
gen_register0 Shell_services.S.bootstrapped begin fun () () ->
|
|
||||||
let block_stream, stopper =
|
|
||||||
Chain_validator.new_head_watcher mainchain_validator in
|
|
||||||
let first_run = ref true in
|
|
||||||
let next () =
|
|
||||||
if !first_run then begin
|
|
||||||
first_run := false ;
|
|
||||||
let chain_state = Chain_validator.chain_state mainchain_validator in
|
|
||||||
Chain.head chain_state >>= fun head ->
|
|
||||||
let head_hash = State.Block.hash head in
|
|
||||||
let head_header = State.Block.header head in
|
|
||||||
Lwt.return (Some (head_hash, head_header.shell.timestamp))
|
|
||||||
end else begin
|
|
||||||
Lwt.pick [
|
|
||||||
( Lwt_stream.get block_stream >|=
|
|
||||||
Option.map ~f:(fun b ->
|
|
||||||
(State.Block.hash b, (State.Block.header b).shell.timestamp)) ) ;
|
|
||||||
(Chain_validator.bootstrapped mainchain_validator >|= fun () -> None) ;
|
|
||||||
]
|
|
||||||
end in
|
|
||||||
let shutdown () = Lwt_watcher.shutdown stopper in
|
|
||||||
RPC_answer.return_stream { next ; shutdown }
|
|
||||||
end ;
|
|
||||||
|
|
||||||
!dir
|
!dir
|
||||||
|
@ -7,5 +7,4 @@
|
|||||||
(* *)
|
(* *)
|
||||||
(**************************************************************************)
|
(**************************************************************************)
|
||||||
|
|
||||||
val build_rpc_directory:
|
val rpc_directory: unit RPC_directory.t
|
||||||
Validator.t -> Chain_validator.t -> unit RPC_directory.t
|
|
||||||
|
122
src/lib_shell_services/injection_services.ml
Normal file
122
src/lib_shell_services/injection_services.ml
Normal file
@ -0,0 +1,122 @@
|
|||||||
|
(**************************************************************************)
|
||||||
|
(* *)
|
||||||
|
(* Copyright (c) 2014 - 2018. *)
|
||||||
|
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
|
||||||
|
(* *)
|
||||||
|
(* All rights reserved. No warranty, explicit or implicit, provided. *)
|
||||||
|
(* *)
|
||||||
|
(**************************************************************************)
|
||||||
|
|
||||||
|
module S = struct
|
||||||
|
|
||||||
|
open Data_encoding
|
||||||
|
|
||||||
|
let path = RPC_path.(root / "injection")
|
||||||
|
|
||||||
|
let block_query =
|
||||||
|
let open RPC_query in
|
||||||
|
query (fun async force chain -> object
|
||||||
|
method async = async
|
||||||
|
method force = force
|
||||||
|
method chain = chain
|
||||||
|
end)
|
||||||
|
|+ flag "async" (fun t -> t#async)
|
||||||
|
|+ flag "force" (fun t -> t#force)
|
||||||
|
|+ opt_field "chain" Chain_services.chain_arg (fun t -> t#chain)
|
||||||
|
|> seal
|
||||||
|
|
||||||
|
let block_param =
|
||||||
|
obj2
|
||||||
|
(req "data" bytes)
|
||||||
|
(req "operations"
|
||||||
|
(list (dynamic_size (list (dynamic_size Operation.encoding)))))
|
||||||
|
|
||||||
|
let block =
|
||||||
|
RPC_service.post_service
|
||||||
|
~description:
|
||||||
|
"Inject a block in the node and broadcast it. The `operations` \
|
||||||
|
embedded in `blockHeader` might be pre-validated using a \
|
||||||
|
contextual RPCs from the latest block \
|
||||||
|
(e.g. '/blocks/head/context/preapply'). Returns the ID of the \
|
||||||
|
block. By default, the RPC will wait for the block to be \
|
||||||
|
validated before answering."
|
||||||
|
~query: block_query
|
||||||
|
~input: block_param
|
||||||
|
~output: Block_hash.encoding
|
||||||
|
RPC_path.(path / "block")
|
||||||
|
|
||||||
|
let operation_query =
|
||||||
|
let open RPC_query in
|
||||||
|
query (fun async chain -> object
|
||||||
|
method async = async
|
||||||
|
method chain = chain
|
||||||
|
end)
|
||||||
|
|+ flag "async" (fun t -> t#async)
|
||||||
|
|+ opt_field "chain" Chain_services.chain_arg (fun t -> t#chain)
|
||||||
|
|> seal
|
||||||
|
|
||||||
|
let 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: operation_query
|
||||||
|
~input: bytes
|
||||||
|
~output: Operation_hash.encoding
|
||||||
|
RPC_path.(path / "operation")
|
||||||
|
|
||||||
|
let protocol_query =
|
||||||
|
let open RPC_query in
|
||||||
|
query (fun async force -> object
|
||||||
|
method async = async
|
||||||
|
method force = force
|
||||||
|
end)
|
||||||
|
|+ flag "async" (fun t -> t#async)
|
||||||
|
|+ flag "force" (fun t -> t#force)
|
||||||
|
|> seal
|
||||||
|
|
||||||
|
|
||||||
|
let protocol =
|
||||||
|
RPC_service.post_service
|
||||||
|
~description:
|
||||||
|
"Inject a protocol in node. Returns the ID of the protocol."
|
||||||
|
~query: protocol_query
|
||||||
|
~input: Protocol.encoding
|
||||||
|
~output: Protocol_hash.encoding
|
||||||
|
RPC_path.(path / "protocol")
|
||||||
|
|
||||||
|
end
|
||||||
|
|
||||||
|
open RPC_context
|
||||||
|
|
||||||
|
let block ctxt
|
||||||
|
?(async = false) ?(force = false) ?chain
|
||||||
|
raw operations =
|
||||||
|
make_call S.block ctxt ()
|
||||||
|
(object
|
||||||
|
method async = async
|
||||||
|
method force = force
|
||||||
|
method chain = chain
|
||||||
|
end)
|
||||||
|
(raw, operations)
|
||||||
|
|
||||||
|
let operation ctxt ?(async = false) ?chain operation =
|
||||||
|
make_call S.operation ctxt ()
|
||||||
|
(object
|
||||||
|
method async = async
|
||||||
|
method chain = chain
|
||||||
|
end)
|
||||||
|
operation
|
||||||
|
|
||||||
|
let protocol ctxt ?(async = false) ?(force = false) protocol =
|
||||||
|
make_call S.protocol ctxt ()
|
||||||
|
(object
|
||||||
|
method async = async
|
||||||
|
method force = force
|
||||||
|
end)
|
||||||
|
protocol
|
56
src/lib_shell_services/injection_services.mli
Normal file
56
src/lib_shell_services/injection_services.mli
Normal file
@ -0,0 +1,56 @@
|
|||||||
|
(**************************************************************************)
|
||||||
|
(* *)
|
||||||
|
(* Copyright (c) 2014 - 2018. *)
|
||||||
|
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
|
||||||
|
(* *)
|
||||||
|
(* All rights reserved. No warranty, explicit or implicit, provided. *)
|
||||||
|
(* *)
|
||||||
|
(**************************************************************************)
|
||||||
|
|
||||||
|
open RPC_context
|
||||||
|
|
||||||
|
val block:
|
||||||
|
#simple ->
|
||||||
|
?async:bool -> ?force:bool -> ?chain:Chain_services.chain ->
|
||||||
|
MBytes.t -> Operation.t list list ->
|
||||||
|
Block_hash.t tzresult Lwt.t
|
||||||
|
(** [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 operation:
|
||||||
|
#simple ->
|
||||||
|
?async:bool -> ?chain:Chain_services.chain ->
|
||||||
|
MBytes.t ->
|
||||||
|
Operation_hash.t tzresult Lwt.t
|
||||||
|
|
||||||
|
val protocol:
|
||||||
|
#simple ->
|
||||||
|
?async:bool -> ?force:bool ->
|
||||||
|
Protocol.t ->
|
||||||
|
Protocol_hash.t tzresult Lwt.t
|
||||||
|
|
||||||
|
module S : sig
|
||||||
|
|
||||||
|
val block:
|
||||||
|
([ `POST ], unit,
|
||||||
|
unit, < async: bool ;
|
||||||
|
force: bool ;
|
||||||
|
chain: Chain_services.chain option >, MBytes.t * Operation.t list list,
|
||||||
|
Block_hash.t) RPC_service.t
|
||||||
|
|
||||||
|
val operation:
|
||||||
|
([ `POST ], unit,
|
||||||
|
unit, < async : bool;
|
||||||
|
chain : Chain_services.chain option >, MBytes.t,
|
||||||
|
Operation_hash.t) RPC_service.t
|
||||||
|
|
||||||
|
val protocol:
|
||||||
|
([ `POST ], unit,
|
||||||
|
unit, < async : bool;
|
||||||
|
force : bool >, Protocol.t,
|
||||||
|
Protocol_hash.t) RPC_service.t
|
||||||
|
|
||||||
|
end
|
@ -10,8 +10,18 @@
|
|||||||
module S = struct
|
module S = struct
|
||||||
|
|
||||||
open Data_encoding
|
open Data_encoding
|
||||||
|
|
||||||
let path = RPC_path.(root / "monitor")
|
let path = RPC_path.(root / "monitor")
|
||||||
|
|
||||||
|
let bootstrapped =
|
||||||
|
RPC_service.get_service
|
||||||
|
~description:""
|
||||||
|
~query: RPC_query.empty
|
||||||
|
~output: (obj2
|
||||||
|
(req "block" Block_hash.encoding)
|
||||||
|
(req "timestamp" Time.encoding))
|
||||||
|
RPC_path.(path / "bootstrapped")
|
||||||
|
|
||||||
let valid_blocks_query =
|
let valid_blocks_query =
|
||||||
let open RPC_query in
|
let open RPC_query in
|
||||||
query (fun protocols next_protocols chains -> object
|
query (fun protocols next_protocols chains -> object
|
||||||
@ -63,6 +73,9 @@ end
|
|||||||
|
|
||||||
open RPC_context
|
open RPC_context
|
||||||
|
|
||||||
|
let bootstrapped ctxt =
|
||||||
|
make_streamed_call S.bootstrapped ctxt () () ()
|
||||||
|
|
||||||
let valid_blocks
|
let valid_blocks
|
||||||
ctxt ?(chains = [`Main]) ?(protocols = []) ?(next_protocols = []) () =
|
ctxt ?(chains = [`Main]) ?(protocols = []) ?(next_protocols = []) () =
|
||||||
make_streamed_call S.valid_blocks ctxt () (object
|
make_streamed_call S.valid_blocks ctxt () (object
|
||||||
|
@ -9,6 +9,9 @@
|
|||||||
|
|
||||||
open RPC_context
|
open RPC_context
|
||||||
|
|
||||||
|
val bootstrapped:
|
||||||
|
#streamed -> ((Block_hash.t * Time.t) Lwt_stream.t * stopper) tzresult Lwt.t
|
||||||
|
|
||||||
val valid_blocks:
|
val valid_blocks:
|
||||||
#streamed ->
|
#streamed ->
|
||||||
?chains:Chain_services.chain list ->
|
?chains:Chain_services.chain list ->
|
||||||
@ -28,6 +31,11 @@ val protocols:
|
|||||||
|
|
||||||
module S : sig
|
module S : sig
|
||||||
|
|
||||||
|
val bootstrapped:
|
||||||
|
([ `GET ], unit,
|
||||||
|
unit, unit, unit,
|
||||||
|
Block_hash.t * Time.t) RPC_service.t
|
||||||
|
|
||||||
val valid_blocks:
|
val valid_blocks:
|
||||||
([ `GET ], unit,
|
([ `GET ], unit,
|
||||||
unit, < chains : Chain_services.chain list;
|
unit, < chains : Chain_services.chain list;
|
||||||
|
@ -19,131 +19,9 @@ module S = struct
|
|||||||
~output: (obj1 (req "block" bytes))
|
~output: (obj1 (req "block" bytes))
|
||||||
RPC_path.(root / "forge_block_header")
|
RPC_path.(root / "forge_block_header")
|
||||||
|
|
||||||
type inject_block_param = {
|
|
||||||
raw: MBytes.t ;
|
|
||||||
blocking: bool ;
|
|
||||||
force: bool ;
|
|
||||||
chain_id: Chain_id.t option ;
|
|
||||||
operations: Operation.t list list ;
|
|
||||||
}
|
|
||||||
|
|
||||||
let inject_block_param =
|
|
||||||
conv
|
|
||||||
(fun { raw ; blocking ; force ; chain_id ; operations } ->
|
|
||||||
(raw, blocking, force, chain_id, operations))
|
|
||||||
(fun (raw, blocking, force, chain_id, operations) ->
|
|
||||||
{ raw ; blocking ; force ; chain_id ; operations })
|
|
||||||
(obj5
|
|
||||||
(req "data" bytes)
|
|
||||||
(dft "blocking"
|
|
||||||
~description:
|
|
||||||
"Should the RPC wait for the block to be \
|
|
||||||
validated before answering. (default: true)"
|
|
||||||
bool
|
|
||||||
true)
|
|
||||||
(dft "force"
|
|
||||||
~description:
|
|
||||||
"Should we inject the block when its fitness is below \
|
|
||||||
the current head. (default: false)"
|
|
||||||
bool
|
|
||||||
false)
|
|
||||||
(opt "chain_id" Chain_id.encoding)
|
|
||||||
(req "operations"
|
|
||||||
(list (list (dynamic_size Operation.encoding)))))
|
|
||||||
|
|
||||||
let inject_block =
|
|
||||||
RPC_service.post_service
|
|
||||||
~description:
|
|
||||||
"Inject a block in the node and broadcast it. The `operations` \
|
|
||||||
embedded in `blockHeader` might be pre-validated using a \
|
|
||||||
contextual RPCs from the latest block \
|
|
||||||
(e.g. '/blocks/head/context/preapply'). Returns the ID of the \
|
|
||||||
block. By default, the RPC will wait for the block to be \
|
|
||||||
validated before answering."
|
|
||||||
~query: RPC_query.empty
|
|
||||||
~input: inject_block_param
|
|
||||||
~output: (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"
|
|
||||||
~title: "Tezos signed operation (hex encoded)"
|
|
||||||
bytes)
|
|
||||||
(dft "blocking"
|
|
||||||
~description:
|
|
||||||
"Should the RPC wait for the operation to be \
|
|
||||||
(pre-)validated before answering. (default: true)"
|
|
||||||
bool
|
|
||||||
true)
|
|
||||||
(opt "chain_id" Chain_id.encoding))
|
|
||||||
~output:
|
|
||||||
(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" Protocol.encoding)
|
|
||||||
(dft "blocking"
|
|
||||||
~description:
|
|
||||||
"Should the RPC wait for the protocol to be \
|
|
||||||
validated before answering. (default: true)"
|
|
||||||
bool
|
|
||||||
true)
|
|
||||||
(opt "force"
|
|
||||||
~description:
|
|
||||||
"Should we inject protocol that is invalid. (default: false)"
|
|
||||||
bool))
|
|
||||||
~output:
|
|
||||||
(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")
|
|
||||||
|
|
||||||
end
|
end
|
||||||
|
|
||||||
open RPC_context
|
open RPC_context
|
||||||
|
|
||||||
let forge_block_header ctxt header =
|
let forge_block_header ctxt header =
|
||||||
make_call S.forge_block_header ctxt () () header
|
make_call S.forge_block_header ctxt () () header
|
||||||
|
|
||||||
let inject_block ctxt
|
|
||||||
?(async = false) ?(force = false) ?chain_id
|
|
||||||
raw operations =
|
|
||||||
make_call S.inject_block ctxt () ()
|
|
||||||
{ raw ; blocking = not async ; force ; chain_id ; operations }
|
|
||||||
|
|
||||||
let inject_operation ctxt ?(async = false) ?chain_id operation =
|
|
||||||
make_call S.inject_operation ctxt () ()
|
|
||||||
(operation, not async, chain_id)
|
|
||||||
|
|
||||||
let inject_protocol ctxt ?(async = false) ?force protocol =
|
|
||||||
make_call S.inject_protocol ctxt () ()
|
|
||||||
(protocol, not async, force)
|
|
||||||
|
|
||||||
let bootstrapped ctxt =
|
|
||||||
make_streamed_call S.bootstrapped ctxt () () ()
|
|
||||||
|
@ -14,32 +14,6 @@ val forge_block_header:
|
|||||||
Block_header.t ->
|
Block_header.t ->
|
||||||
MBytes.t tzresult Lwt.t
|
MBytes.t tzresult Lwt.t
|
||||||
|
|
||||||
val inject_block:
|
|
||||||
#simple ->
|
|
||||||
?async:bool -> ?force:bool -> ?chain_id:Chain_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:
|
|
||||||
#simple ->
|
|
||||||
?async:bool -> ?chain_id:Chain_id.t ->
|
|
||||||
MBytes.t ->
|
|
||||||
Operation_hash.t tzresult Lwt.t
|
|
||||||
|
|
||||||
val inject_protocol:
|
|
||||||
#simple ->
|
|
||||||
?async:bool -> ?force:bool ->
|
|
||||||
Protocol.t ->
|
|
||||||
Protocol_hash.t tzresult Lwt.t
|
|
||||||
|
|
||||||
val bootstrapped:
|
|
||||||
#streamed -> ((Block_hash.t * Time.t) Lwt_stream.t * stopper) tzresult Lwt.t
|
|
||||||
|
|
||||||
module S : sig
|
module S : sig
|
||||||
|
|
||||||
val forge_block_header:
|
val forge_block_header:
|
||||||
@ -47,32 +21,4 @@ module S : sig
|
|||||||
unit, unit, Block_header.t,
|
unit, unit, Block_header.t,
|
||||||
MBytes.t) RPC_service.t
|
MBytes.t) RPC_service.t
|
||||||
|
|
||||||
type inject_block_param = {
|
|
||||||
raw: MBytes.t ;
|
|
||||||
blocking: bool ;
|
|
||||||
force: bool ;
|
|
||||||
chain_id: Chain_id.t option ;
|
|
||||||
operations: Operation.t list list ;
|
|
||||||
}
|
|
||||||
|
|
||||||
val inject_block:
|
|
||||||
([ `POST ], unit,
|
|
||||||
unit, unit, inject_block_param,
|
|
||||||
Block_hash.t) RPC_service.t
|
|
||||||
|
|
||||||
val inject_operation:
|
|
||||||
([ `POST ], unit,
|
|
||||||
unit, unit, (MBytes.t * bool * Chain_id.t option),
|
|
||||||
Operation_hash.t) RPC_service.t
|
|
||||||
|
|
||||||
val inject_protocol:
|
|
||||||
([ `POST ], unit,
|
|
||||||
unit, unit, (Protocol.t * bool * bool option),
|
|
||||||
Protocol_hash.t) RPC_service.t
|
|
||||||
|
|
||||||
val bootstrapped:
|
|
||||||
([ `POST ], unit,
|
|
||||||
unit, unit, unit,
|
|
||||||
Block_hash.t * Time.t) RPC_service.t
|
|
||||||
|
|
||||||
end
|
end
|
||||||
|
@ -95,7 +95,6 @@ let inject_endorsement
|
|||||||
(cctxt : #Proto_alpha.full)
|
(cctxt : #Proto_alpha.full)
|
||||||
?(chain = `Main) block level ?async
|
?(chain = `Main) block level ?async
|
||||||
src_sk slots =
|
src_sk slots =
|
||||||
Chain_services.chain_id cctxt ~chain () >>=? fun chain_id ->
|
|
||||||
Block_services.hash cctxt ~chain ~block () >>=? fun hash ->
|
Block_services.hash cctxt ~chain ~block () >>=? fun hash ->
|
||||||
Alpha_services.Forge.Consensus.endorsement cctxt
|
Alpha_services.Forge.Consensus.endorsement cctxt
|
||||||
(chain, block)
|
(chain, block)
|
||||||
@ -106,8 +105,7 @@ let inject_endorsement
|
|||||||
() >>=? fun bytes ->
|
() >>=? fun bytes ->
|
||||||
Client_keys.append
|
Client_keys.append
|
||||||
src_sk ~watermark:Endorsement bytes >>=? fun signed_bytes ->
|
src_sk ~watermark:Endorsement bytes >>=? fun signed_bytes ->
|
||||||
Shell_services.inject_operation
|
Injection_services.operation cctxt ?async ~chain signed_bytes >>=? fun oph ->
|
||||||
cctxt ?async ~chain_id signed_bytes >>=? fun oph ->
|
|
||||||
iter_s
|
iter_s
|
||||||
(fun slot ->
|
(fun slot ->
|
||||||
State.record_endorsement cctxt level hash slot oph)
|
State.record_endorsement cctxt level hash slot oph)
|
||||||
|
@ -71,9 +71,8 @@ let inject_block cctxt
|
|||||||
let block = `Hash (shell_header.Tezos_base.Block_header.predecessor, 0) in
|
let block = `Hash (shell_header.Tezos_base.Block_header.predecessor, 0) in
|
||||||
forge_block_header cctxt ~chain block
|
forge_block_header cctxt ~chain block
|
||||||
src_sk shell_header priority seed_nonce_hash >>=? fun signed_header ->
|
src_sk shell_header priority seed_nonce_hash >>=? fun signed_header ->
|
||||||
Chain_services.chain_id cctxt ~chain () >>=? fun chain_id ->
|
Injection_services.block cctxt
|
||||||
Shell_services.inject_block cctxt
|
?force ~chain signed_header operations >>=? fun block_hash ->
|
||||||
?force ~chain_id signed_header operations >>=? fun block_hash ->
|
|
||||||
return block_hash
|
return block_hash
|
||||||
|
|
||||||
type error +=
|
type error +=
|
||||||
|
@ -15,12 +15,10 @@ let inject_seed_nonce_revelation rpc_config ?(chain = `Main) block ?async nonces
|
|||||||
List.map
|
List.map
|
||||||
(fun (level, nonce) ->
|
(fun (level, nonce) ->
|
||||||
Seed_nonce_revelation { level ; nonce }) nonces in
|
Seed_nonce_revelation { level ; nonce }) nonces in
|
||||||
Chain_services.chain_id rpc_config ~chain () >>=? fun chain_id ->
|
|
||||||
Block_services.hash rpc_config ~chain ~block () >>=? fun branch ->
|
Block_services.hash rpc_config ~chain ~block () >>=? fun branch ->
|
||||||
Alpha_services.Forge.Anonymous.operations rpc_config
|
Alpha_services.Forge.Anonymous.operations rpc_config
|
||||||
(chain, block) ~branch operations >>=? fun bytes ->
|
(chain, block) ~branch operations >>=? fun bytes ->
|
||||||
Shell_services.inject_operation
|
Injection_services.operation rpc_config ?async ~chain bytes >>=? fun oph ->
|
||||||
rpc_config ?async ~chain_id bytes >>=? fun oph ->
|
|
||||||
return oph
|
return oph
|
||||||
|
|
||||||
let forge_seed_nonce_revelation
|
let forge_seed_nonce_revelation
|
||||||
|
@ -176,8 +176,7 @@ let inject_operation
|
|||||||
Lwt.return res
|
Lwt.return res
|
||||||
end >>=? fun () ->
|
end >>=? fun () ->
|
||||||
let bytes = Data_encoding.Binary.to_bytes_exn Operation.encoding op in
|
let bytes = Data_encoding.Binary.to_bytes_exn Operation.encoding op in
|
||||||
Chain_services.chain_id cctxt ~chain () >>=? fun chain_id ->
|
Injection_services.operation cctxt ~chain bytes >>=? fun oph ->
|
||||||
Shell_services.inject_operation cctxt ~chain_id bytes >>=? fun oph ->
|
|
||||||
cctxt#message "Operation successfully injected in the node." >>= fun () ->
|
cctxt#message "Operation successfully injected in the node." >>= fun () ->
|
||||||
cctxt#message "Operation hash is '%a'." Operation_hash.pp oph >>= fun () ->
|
cctxt#message "Operation hash is '%a'." Operation_hash.pp oph >>= fun () ->
|
||||||
begin
|
begin
|
||||||
|
@ -20,7 +20,7 @@ let bake cctxt ?(timestamp = Time.now ()) block command sk =
|
|||||||
[] >>=? fun (shell_header, _) ->
|
[] >>=? fun (shell_header, _) ->
|
||||||
let blk = Data.Command.forge shell_header command in
|
let blk = Data.Command.forge shell_header command in
|
||||||
Client_keys.append sk blk >>=? fun signed_blk ->
|
Client_keys.append sk blk >>=? fun signed_blk ->
|
||||||
Shell_services.inject_block cctxt signed_blk []
|
Injection_services.block cctxt signed_blk []
|
||||||
|
|
||||||
let int64_parameter =
|
let int64_parameter =
|
||||||
(Clic.parameter (fun _ p ->
|
(Clic.parameter (fun _ p ->
|
||||||
|
Loading…
Reference in New Issue
Block a user