RPC: batch operation parsing/retrieval
This commit is contained in:
parent
cb2aa6ea2b
commit
329b72d1aa
@ -212,14 +212,16 @@ module Blocks = struct
|
|||||||
end
|
end
|
||||||
|
|
||||||
module Operations = struct
|
module Operations = struct
|
||||||
|
let contents cctxt hashes =
|
||||||
|
call_service1 cctxt Services.Operations.contents hashes ()
|
||||||
let monitor cctxt ?contents () =
|
let monitor cctxt ?contents () =
|
||||||
call_streamed_service0 cctxt Services.Operations.list
|
call_streamed_service0 cctxt Services.Operations.list
|
||||||
{ monitor = Some true ; contents }
|
{ monitor = Some true ; contents }
|
||||||
end
|
end
|
||||||
|
|
||||||
module Protocols = struct
|
module Protocols = struct
|
||||||
let bytes cctxt hash =
|
let contents cctxt hash =
|
||||||
call_service1 cctxt Services.Protocols.bytes hash ()
|
call_service1 cctxt Services.Protocols.contents hash ()
|
||||||
let list cctxt ?contents () =
|
let list cctxt ?contents () =
|
||||||
call_service0 cctxt Services.Protocols.list { contents; monitor = Some false }
|
call_service0 cctxt Services.Protocols.list { contents; monitor = Some false }
|
||||||
end
|
end
|
||||||
|
@ -144,14 +144,21 @@ module Blocks : sig
|
|||||||
end
|
end
|
||||||
|
|
||||||
module Operations : sig
|
module Operations : sig
|
||||||
|
|
||||||
|
val contents:
|
||||||
|
Client_commands.context ->
|
||||||
|
Operation_hash.t list -> Store.Operation.t list Lwt.t
|
||||||
|
|
||||||
val monitor:
|
val monitor:
|
||||||
Client_commands.context ->
|
Client_commands.context ->
|
||||||
?contents:bool -> unit ->
|
?contents:bool -> unit ->
|
||||||
(Operation_hash.t * Store.Operation.t option) list list Lwt_stream.t Lwt.t
|
(Operation_hash.t * Store.Operation.t option) list list Lwt_stream.t Lwt.t
|
||||||
|
|
||||||
end
|
end
|
||||||
|
|
||||||
module Protocols : sig
|
module Protocols : sig
|
||||||
val bytes:
|
|
||||||
|
val contents:
|
||||||
Client_commands.context ->
|
Client_commands.context ->
|
||||||
Protocol_hash.t -> Store.Protocol.t Lwt.t
|
Protocol_hash.t -> Store.Protocol.t Lwt.t
|
||||||
|
|
||||||
@ -159,6 +166,7 @@ module Protocols : sig
|
|||||||
Client_commands.context ->
|
Client_commands.context ->
|
||||||
?contents:bool -> unit ->
|
?contents:bool -> unit ->
|
||||||
(Protocol_hash.t * Store.Protocol.t option) list Lwt.t
|
(Protocol_hash.t * Store.Protocol.t option) list Lwt.t
|
||||||
|
|
||||||
end
|
end
|
||||||
|
|
||||||
val bootstrapped:
|
val bootstrapped:
|
||||||
|
@ -50,7 +50,7 @@ let commands () =
|
|||||||
@@ param ~name:"protocol hash" ~desc:"" check_hash
|
@@ param ~name:"protocol hash" ~desc:"" check_hash
|
||||||
@@ stop)
|
@@ stop)
|
||||||
(fun ph cctxt ->
|
(fun ph cctxt ->
|
||||||
Client_node_rpcs.Protocols.bytes cctxt ph >>= fun proto ->
|
Client_node_rpcs.Protocols.contents cctxt ph >>= fun proto ->
|
||||||
Updater.extract "" ph proto >>= fun () ->
|
Updater.extract "" ph proto >>= fun () ->
|
||||||
cctxt.message "Extracted protocol %a" Protocol_hash.pp_short ph) ;
|
cctxt.message "Extracted protocol %a" Protocol_hash.pp_short ph) ;
|
||||||
(* | Error err -> *)
|
(* | Error err -> *)
|
||||||
|
@ -22,19 +22,24 @@ let monitor cctxt ?contents ?check () =
|
|||||||
Client_node_rpcs.Operations.monitor cctxt ?contents () >>= fun ops_stream ->
|
Client_node_rpcs.Operations.monitor cctxt ?contents () >>= fun ops_stream ->
|
||||||
let convert ops =
|
let convert ops =
|
||||||
Lwt_list.filter_map_p
|
Lwt_list.filter_map_p
|
||||||
(fun (hash, bytes) ->
|
(fun (hash, op) ->
|
||||||
match bytes with
|
match op with
|
||||||
| None -> Lwt.return (Some { hash; content = None })
|
| None -> Lwt.return (Some { hash; content = None })
|
||||||
| Some ({ Store.Operation.shell ; proto } : Updater.raw_operation) ->
|
| Some op ->
|
||||||
Client_proto_rpcs.Helpers.Parse.operation cctxt
|
Client_proto_rpcs.Helpers.Parse.operations cctxt
|
||||||
`Prevalidation ?check shell proto >>= function
|
`Prevalidation ?check [op] >>= function
|
||||||
| Ok proto -> Lwt.return (Some { hash ; content = Some (shell, proto) })
|
| Ok [proto] ->
|
||||||
|
Lwt.return (Some { hash ; content = Some (op.shell, proto) })
|
||||||
|
| Ok _ ->
|
||||||
|
lwt_log_error
|
||||||
|
"@[<v 2>Error while parsing operations@[" >>= fun () ->
|
||||||
|
Lwt.return None
|
||||||
| Error err ->
|
| Error err ->
|
||||||
lwt_log_error
|
lwt_log_error
|
||||||
"@[<v 2>Error while parsing operations@,%a@["
|
"@[<v 2>Error while parsing operations@,%a@["
|
||||||
pp_print_error err >>= fun () ->
|
pp_print_error err >>= fun () ->
|
||||||
Lwt.return None)
|
Lwt.return None)
|
||||||
(List.concat ops)
|
(List.concat ops)
|
||||||
in
|
in
|
||||||
Lwt.return (Lwt_stream.map_s convert ops_stream)
|
Lwt.return (Lwt_stream.map_s convert ops_stream)
|
||||||
|
|
||||||
|
@ -259,10 +259,9 @@ module Helpers = struct
|
|||||||
end
|
end
|
||||||
|
|
||||||
module Parse = struct
|
module Parse = struct
|
||||||
let operation cctxt block ?check shell proto =
|
let operations cctxt block ?check operations =
|
||||||
call_error_service1 cctxt
|
call_error_service1 cctxt
|
||||||
Services.Helpers.Parse.operation block
|
Services.Helpers.Parse.operations block (operations, check)
|
||||||
(({ shell ; proto } : Updater.raw_operation), check)
|
|
||||||
let block cctxt block shell proto =
|
let block cctxt block shell proto =
|
||||||
call_error_service1 cctxt
|
call_error_service1 cctxt
|
||||||
Services.Helpers.Parse.block block
|
Services.Helpers.Parse.block block
|
||||||
|
@ -318,10 +318,10 @@ module Helpers : sig
|
|||||||
end
|
end
|
||||||
|
|
||||||
module Parse : sig
|
module Parse : sig
|
||||||
val operation:
|
val operations:
|
||||||
Client_commands.context ->
|
Client_commands.context ->
|
||||||
block -> ?check:bool -> Updater.shell_operation -> MBytes.t ->
|
block -> ?check:bool -> Updater.raw_operation list ->
|
||||||
proto_operation tzresult Lwt.t
|
proto_operation list tzresult Lwt.t
|
||||||
val block:
|
val block:
|
||||||
Client_commands.context ->
|
Client_commands.context ->
|
||||||
block -> Updater.shell_block -> MBytes.t ->
|
block -> Updater.shell_block -> MBytes.t ->
|
||||||
|
@ -329,9 +329,8 @@ module RPC = struct
|
|||||||
| Some { operations } -> operations
|
| Some { operations } -> operations
|
||||||
|
|
||||||
let operation_content node hash =
|
let operation_content node hash =
|
||||||
Distributed_db.read_operation node.distributed_db hash >>= function
|
Distributed_db.read_operation node.distributed_db hash >>= fun op ->
|
||||||
| None -> Lwt.return_none
|
Lwt.return (map_option ~f:snd op)
|
||||||
| Some (_, op) -> Lwt.return (Some op)
|
|
||||||
|
|
||||||
let pending_operations node (block: block) =
|
let pending_operations node (block: block) =
|
||||||
match block with
|
match block with
|
||||||
|
@ -305,16 +305,17 @@ let list_blocks
|
|||||||
let list_operations node {Services.Operations.monitor; contents} =
|
let list_operations node {Services.Operations.monitor; contents} =
|
||||||
let monitor = match monitor with None -> false | Some x -> x in
|
let monitor = match monitor with None -> false | Some x -> x in
|
||||||
let include_ops = match contents with None -> false | Some x -> x in
|
let include_ops = match contents with None -> false | Some x -> x in
|
||||||
Node.RPC.operations node `Prevalidation >>= fun operations ->
|
Node.RPC.operations node `Prevalidation >>= fun operationss ->
|
||||||
Lwt_list.map_p
|
let fetch_operations_content operations =
|
||||||
(Lwt_list.map_p
|
if include_ops then
|
||||||
(fun hash ->
|
Lwt_list.map_s
|
||||||
if include_ops then
|
(fun h ->
|
||||||
Node.RPC.operation_content node hash >>= fun op ->
|
Node.RPC.operation_content node h >>= fun content ->
|
||||||
Lwt.return (hash, op)
|
Lwt.return (h, content))
|
||||||
else
|
operations
|
||||||
Lwt.return (hash, None)))
|
else
|
||||||
operations >>= fun operations ->
|
Lwt.return @@ ListLabels.map operations ~f:(fun h -> h, None) in
|
||||||
|
Lwt_list.map_p fetch_operations_content operationss >>= fun operations ->
|
||||||
if not monitor then
|
if not monitor then
|
||||||
RPC.Answer.return operations
|
RPC.Answer.return operations
|
||||||
else
|
else
|
||||||
@ -333,10 +334,14 @@ let list_operations node {Services.Operations.monitor; contents} =
|
|||||||
end in
|
end in
|
||||||
RPC.Answer.return_stream { next ; shutdown }
|
RPC.Answer.return_stream { next ; shutdown }
|
||||||
|
|
||||||
let get_operations node hash () =
|
let get_operations node hashes () =
|
||||||
Node.RPC.operation_content node hash >>= function
|
Lwt_list.map_p
|
||||||
| Some bytes -> RPC.Answer.return bytes
|
(fun h ->
|
||||||
| None -> raise Not_found
|
Node.RPC.operation_content node h >>= function
|
||||||
|
| None -> Lwt.fail Not_found
|
||||||
|
| Some h -> Lwt.return h)
|
||||||
|
hashes >>= fun ops ->
|
||||||
|
RPC.Answer.return ops
|
||||||
|
|
||||||
let list_protocols node {Services.Protocols.monitor; contents} =
|
let list_protocols node {Services.Protocols.monitor; contents} =
|
||||||
let monitor = match monitor with None -> false | Some x -> x in
|
let monitor = match monitor with None -> false | Some x -> x in
|
||||||
@ -393,11 +398,11 @@ let build_rpc_directory node =
|
|||||||
let dir =
|
let dir =
|
||||||
RPC.register0 dir Services.Operations.list (list_operations node) in
|
RPC.register0 dir Services.Operations.list (list_operations node) in
|
||||||
let dir =
|
let dir =
|
||||||
RPC.register1 dir Services.Operations.bytes (get_operations node) in
|
RPC.register1 dir Services.Operations.contents (get_operations node) in
|
||||||
let dir =
|
let dir =
|
||||||
RPC.register0 dir Services.Protocols.list (list_protocols node) in
|
RPC.register0 dir Services.Protocols.list (list_protocols node) in
|
||||||
let dir =
|
let dir =
|
||||||
RPC.register1 dir Services.Protocols.bytes (get_protocols node) in
|
RPC.register1 dir Services.Protocols.contents (get_protocols node) in
|
||||||
let dir =
|
let dir =
|
||||||
let implementation (net_id, pred, time, fitness, operations, header) =
|
let implementation (net_id, pred, time, fitness, operations, header) =
|
||||||
Node.RPC.block_info node (`Head 0) >>= fun bi ->
|
Node.RPC.block_info node (`Head 0) >>= fun bi ->
|
||||||
|
@ -408,16 +408,18 @@ module Operations = struct
|
|||||||
let name = "operation_id" in
|
let name = "operation_id" in
|
||||||
let descr =
|
let descr =
|
||||||
"A operation identifier in hexadecimal." in
|
"A operation identifier in hexadecimal." in
|
||||||
let construct = Operation_hash.to_b58check in
|
let construct ops =
|
||||||
|
String.concat "," (List.map Operation_hash.to_b58check ops) in
|
||||||
let destruct h =
|
let destruct h =
|
||||||
try Ok (Operation_hash.of_b58check h)
|
let ops = split ',' h in
|
||||||
|
try Ok (List.map Operation_hash.of_b58check ops)
|
||||||
with _ -> Error "Can't parse hash" in
|
with _ -> Error "Can't parse hash" in
|
||||||
RPC.Arg.make ~name ~descr ~construct ~destruct ()
|
RPC.Arg.make ~name ~descr ~construct ~destruct ()
|
||||||
|
|
||||||
let bytes =
|
let contents =
|
||||||
RPC.service
|
RPC.service
|
||||||
~input: empty
|
~input: empty
|
||||||
~output: Updater.raw_operation_encoding
|
~output: (list (dynamic_size Updater.raw_operation_encoding))
|
||||||
RPC.Path.(root / "operations" /: operations_arg)
|
RPC.Path.(root / "operations" /: operations_arg)
|
||||||
|
|
||||||
type list_param = {
|
type list_param = {
|
||||||
@ -435,6 +437,8 @@ module Operations = struct
|
|||||||
|
|
||||||
let list =
|
let list =
|
||||||
RPC.service
|
RPC.service
|
||||||
|
~description:
|
||||||
|
"List operations in the mempool."
|
||||||
~input: list_param_encoding
|
~input: list_param_encoding
|
||||||
~output:
|
~output:
|
||||||
(obj1
|
(obj1
|
||||||
@ -451,6 +455,7 @@ module Operations = struct
|
|||||||
end
|
end
|
||||||
|
|
||||||
module Protocols = struct
|
module Protocols = struct
|
||||||
|
|
||||||
let protocols_arg =
|
let protocols_arg =
|
||||||
let name = "protocol_id" in
|
let name = "protocol_id" in
|
||||||
let descr =
|
let descr =
|
||||||
@ -461,7 +466,7 @@ module Protocols = struct
|
|||||||
with _ -> Error "Can't parse hash" in
|
with _ -> Error "Can't parse hash" in
|
||||||
RPC.Arg.make ~name ~descr ~construct ~destruct ()
|
RPC.Arg.make ~name ~descr ~construct ~destruct ()
|
||||||
|
|
||||||
let bytes =
|
let contents =
|
||||||
RPC.service
|
RPC.service
|
||||||
~input: empty
|
~input: empty
|
||||||
~output:
|
~output:
|
||||||
@ -496,6 +501,7 @@ module Protocols = struct
|
|||||||
(dynamic_size Store.Protocol.encoding)))
|
(dynamic_size Store.Protocol.encoding)))
|
||||||
)))
|
)))
|
||||||
RPC.Path.(root / "protocols")
|
RPC.Path.(root / "protocols")
|
||||||
|
|
||||||
end
|
end
|
||||||
|
|
||||||
module Network = struct
|
module Network = struct
|
||||||
|
@ -99,28 +99,39 @@ module Blocks : sig
|
|||||||
end
|
end
|
||||||
|
|
||||||
module Operations : sig
|
module Operations : sig
|
||||||
val bytes:
|
|
||||||
(unit, unit * Operation_hash.t, unit, State.Operation.t) RPC.service
|
val contents:
|
||||||
|
(unit, unit * Operation_hash.t list,
|
||||||
|
unit, State.Operation.t list) RPC.service
|
||||||
|
|
||||||
|
|
||||||
type list_param = {
|
type list_param = {
|
||||||
contents: bool option ;
|
contents: bool option ;
|
||||||
monitor: bool option ;
|
monitor: bool option ;
|
||||||
}
|
}
|
||||||
|
|
||||||
val list:
|
val list:
|
||||||
(unit, unit,
|
(unit, unit,
|
||||||
list_param, (Operation_hash.t * Store.Operation.t option) list list) RPC.service
|
list_param,
|
||||||
|
(Operation_hash.t * Store.Operation.t option) list list) RPC.service
|
||||||
|
|
||||||
end
|
end
|
||||||
|
|
||||||
module Protocols : sig
|
module Protocols : sig
|
||||||
val bytes:
|
|
||||||
|
val contents:
|
||||||
(unit, unit * Protocol_hash.t, unit, Tezos_compiler.Protocol.t) RPC.service
|
(unit, unit * Protocol_hash.t, unit, Tezos_compiler.Protocol.t) RPC.service
|
||||||
|
|
||||||
type list_param = {
|
type list_param = {
|
||||||
contents: bool option ;
|
contents: bool option ;
|
||||||
monitor: bool option ;
|
monitor: bool option ;
|
||||||
}
|
}
|
||||||
|
|
||||||
val list:
|
val list:
|
||||||
(unit, unit,
|
(unit, unit,
|
||||||
list_param,
|
list_param,
|
||||||
(Protocol_hash.t * Tezos_compiler.Protocol.t option) list) RPC.service
|
(Protocol_hash.t * Tezos_compiler.Protocol.t option) list) RPC.service
|
||||||
|
|
||||||
end
|
end
|
||||||
|
|
||||||
module Network : sig
|
module Network : sig
|
||||||
|
@ -574,15 +574,16 @@ module Helpers = struct
|
|||||||
|
|
||||||
module Parse = struct
|
module Parse = struct
|
||||||
|
|
||||||
let operation custom_root =
|
let operations custom_root =
|
||||||
RPC.service
|
RPC.service
|
||||||
~description:"Parse an operation"
|
~description:"Parse operations"
|
||||||
~input:
|
~input:
|
||||||
(merge_objs
|
(obj2
|
||||||
Updater.raw_operation_encoding
|
(req "operations" (list (dynamic_size Updater.raw_operation_encoding)))
|
||||||
(obj1 (opt "check_signature" bool)))
|
(opt "check_signature" bool))
|
||||||
~output: (wrap_tzerror Operation.proto_operation_encoding)
|
~output:
|
||||||
RPC.Path.(custom_root / "helpers" / "parse" / "operation" )
|
(wrap_tzerror (list Operation.proto_operation_encoding))
|
||||||
|
RPC.Path.(custom_root / "helpers" / "parse" / "operations" )
|
||||||
|
|
||||||
let block custom_root =
|
let block custom_root =
|
||||||
RPC.service
|
RPC.service
|
||||||
|
@ -468,17 +468,18 @@ let check_signature ctxt signature shell contents =
|
|||||||
Operation.check_signature key
|
Operation.check_signature key
|
||||||
{ signature ; shell ; contents ; hash = dummy_hash }
|
{ signature ; shell ; contents ; hash = dummy_hash }
|
||||||
|
|
||||||
let parse_operation ctxt
|
let parse_operations ctxt (operations, check) =
|
||||||
(({ shell ; proto } : Updater.raw_operation), check) =
|
map_s begin fun ({ shell ; proto } : Updater.raw_operation) ->
|
||||||
Operation.parse_proto proto >>=? fun (proto, signature) ->
|
begin
|
||||||
begin
|
Operation.parse_proto proto >>=? fun (proto, signature) ->
|
||||||
match check with
|
begin match check with
|
||||||
| Some true -> check_signature ctxt signature shell proto
|
| Some true -> check_signature ctxt signature shell proto
|
||||||
| Some false | None -> return ()
|
| Some false | None -> return ()
|
||||||
end >>=? fun () ->
|
end >>|? fun () -> proto
|
||||||
return proto
|
end
|
||||||
|
end operations
|
||||||
|
|
||||||
let () = register1 Services.Helpers.Parse.operation parse_operation
|
let () = register1 Services.Helpers.Parse.operations parse_operations
|
||||||
|
|
||||||
let parse_block _ctxt raw_block =
|
let parse_block _ctxt raw_block =
|
||||||
Lwt.return (Block.parse_header raw_block) >>=? fun { proto } ->
|
Lwt.return (Block.parse_header raw_block) >>=? fun { proto } ->
|
||||||
|
Loading…
Reference in New Issue
Block a user