Proto_sigs: split the deprecated module Hash
This commit is contained in:
parent
04465e3ac6
commit
f2de3ffa3e
@ -42,21 +42,17 @@ module Make(Param : sig val name: string end)() = struct
|
|||||||
module Data_encoding = Data_encoding
|
module Data_encoding = Data_encoding
|
||||||
module Time = Time
|
module Time = Time
|
||||||
module Ed25519 = Ed25519
|
module Ed25519 = Ed25519
|
||||||
module Hash = struct
|
module S = struct
|
||||||
include Tezos_crypto
|
|
||||||
include Tezos_crypto.S
|
include Tezos_crypto.S
|
||||||
module Net_id = Net_id
|
include S
|
||||||
|
end
|
||||||
module Block_hash = Block_hash
|
module Block_hash = Block_hash
|
||||||
module Operation_hash = Operation_hash
|
module Operation_hash = Operation_hash
|
||||||
module Operation_list_hash = Operation_list_hash
|
module Operation_list_hash = Operation_list_hash
|
||||||
module Operation_list_list_hash = Operation_list_list_hash
|
module Operation_list_list_hash = Operation_list_list_hash
|
||||||
module Context_hash = Context_hash
|
module Context_hash = Context_hash
|
||||||
module Protocol_hash = Protocol_hash
|
module Protocol_hash = Protocol_hash
|
||||||
module Make_minimal_Blake2B = Blake2B.Make_minimal
|
|
||||||
module Make_Blake2B = Blake2B.Make
|
|
||||||
end
|
|
||||||
module Blake2B = Blake2B
|
module Blake2B = Blake2B
|
||||||
module S = S
|
|
||||||
module Fitness = Fitness
|
module Fitness = Fitness
|
||||||
module Operation = Operation
|
module Operation = Operation
|
||||||
module Block_header = Block_header
|
module Block_header = Block_header
|
||||||
|
@ -20,7 +20,18 @@ let () =
|
|||||||
|
|
||||||
(*-- Type specific Hash builder ---------------------------------------------*)
|
(*-- Type specific Hash builder ---------------------------------------------*)
|
||||||
|
|
||||||
module Make_minimal (K : S.Name) = struct
|
module type Name = sig
|
||||||
|
val name : string
|
||||||
|
val title : string
|
||||||
|
val size : int option
|
||||||
|
end
|
||||||
|
|
||||||
|
module type PrefixedName = sig
|
||||||
|
include Name
|
||||||
|
val b58check_prefix : string
|
||||||
|
end
|
||||||
|
|
||||||
|
module Make_minimal (K : Name) = struct
|
||||||
|
|
||||||
type t = Sodium.Generichash.hash
|
type t = Sodium.Generichash.hash
|
||||||
|
|
||||||
@ -133,7 +144,7 @@ module Make (R : sig
|
|||||||
of_raw: (string -> 'a option) ->
|
of_raw: (string -> 'a option) ->
|
||||||
wrap: ('a -> Base58.data) ->
|
wrap: ('a -> Base58.data) ->
|
||||||
'a Base58.encoding
|
'a Base58.encoding
|
||||||
end) (K : S.PrefixedName) = struct
|
end) (K : PrefixedName) = struct
|
||||||
|
|
||||||
include Make_minimal(K)
|
include Make_minimal(K)
|
||||||
|
|
||||||
@ -353,7 +364,7 @@ module Make_merkle_tree
|
|||||||
wrap: ('a -> Base58.data) ->
|
wrap: ('a -> Base58.data) ->
|
||||||
'a Base58.encoding
|
'a Base58.encoding
|
||||||
end)
|
end)
|
||||||
(K : S.PrefixedName)
|
(K : PrefixedName)
|
||||||
(Contents: sig
|
(Contents: sig
|
||||||
type t
|
type t
|
||||||
val to_bytes: t -> MBytes.t
|
val to_bytes: t -> MBytes.t
|
||||||
|
@ -13,8 +13,25 @@
|
|||||||
|
|
||||||
include S.INTERNAL_MINIMAL_HASH
|
include S.INTERNAL_MINIMAL_HASH
|
||||||
|
|
||||||
|
(** {2 Building Hashes} *******************************************************)
|
||||||
|
|
||||||
|
(** The parameters for creating a new Hash type using
|
||||||
|
{!Make_Blake2B}. Both {!name} and {!title} are only informative,
|
||||||
|
used in error messages and serializers. *)
|
||||||
|
|
||||||
|
module type Name = sig
|
||||||
|
val name : string
|
||||||
|
val title : string
|
||||||
|
val size : int option
|
||||||
|
end
|
||||||
|
|
||||||
|
module type PrefixedName = sig
|
||||||
|
include Name
|
||||||
|
val b58check_prefix : string
|
||||||
|
end
|
||||||
|
|
||||||
(** Builds a new Hash type using Blake2B. *)
|
(** Builds a new Hash type using Blake2B. *)
|
||||||
module Make_minimal (Name : S.Name) : S.INTERNAL_MINIMAL_HASH
|
module Make_minimal (Name : Name) : S.INTERNAL_MINIMAL_HASH
|
||||||
module Make
|
module Make
|
||||||
(Register : sig
|
(Register : sig
|
||||||
val register_encoding:
|
val register_encoding:
|
||||||
@ -25,7 +42,7 @@ module Make
|
|||||||
wrap: ('a -> Base58.data) ->
|
wrap: ('a -> Base58.data) ->
|
||||||
'a Base58.encoding
|
'a Base58.encoding
|
||||||
end)
|
end)
|
||||||
(Name : S.PrefixedName) : S.INTERNAL_HASH
|
(Name : PrefixedName) : S.INTERNAL_HASH
|
||||||
|
|
||||||
(**/**)
|
(**/**)
|
||||||
|
|
||||||
@ -39,7 +56,7 @@ module Make_merkle_tree
|
|||||||
wrap: ('a -> Base58.data) ->
|
wrap: ('a -> Base58.data) ->
|
||||||
'a Base58.encoding
|
'a Base58.encoding
|
||||||
end)
|
end)
|
||||||
(K : S.PrefixedName)
|
(K : PrefixedName)
|
||||||
(Contents: sig
|
(Contents: sig
|
||||||
type t
|
type t
|
||||||
val to_bytes: t -> MBytes.t
|
val to_bytes: t -> MBytes.t
|
||||||
|
@ -126,20 +126,3 @@ module type MERKLE_TREE = sig
|
|||||||
val check_path: path -> elt -> t * int
|
val check_path: path -> elt -> t * int
|
||||||
val path_encoding: path Data_encoding.t
|
val path_encoding: path Data_encoding.t
|
||||||
end
|
end
|
||||||
|
|
||||||
(** {2 Building Hashes} *******************************************************)
|
|
||||||
|
|
||||||
(** The parameters for creating a new Hash type using
|
|
||||||
{!Make_Blake2B}. Both {!name} and {!title} are only informative,
|
|
||||||
used in error messages and serializers. *)
|
|
||||||
|
|
||||||
module type Name = sig
|
|
||||||
val name : string
|
|
||||||
val title : string
|
|
||||||
val size : int option
|
|
||||||
end
|
|
||||||
|
|
||||||
module type PrefixedName = sig
|
|
||||||
include Name
|
|
||||||
val b58check_prefix : string
|
|
||||||
end
|
|
||||||
|
@ -47,8 +47,7 @@ let () = Format.kasprintf Jbuild_plugin.V1.send {|
|
|||||||
-w +a-4-6-7-9-29-32-40..42-44-45-48
|
-w +a-4-6-7-9-29-32-40..42-44-45-48
|
||||||
-warn-error -a+8
|
-warn-error -a+8
|
||||||
-open Tezos_embedded_protocol_environment_%s__Environment
|
-open Tezos_embedded_protocol_environment_%s__Environment
|
||||||
-open Error_monad
|
-open Error_monad))
|
||||||
-open Hash))
|
|
||||||
(modules (:standard \ Environment Registerer))))
|
(modules (:standard \ Environment Registerer))))
|
||||||
|
|
||||||
(library
|
(library
|
||||||
|
@ -43,7 +43,6 @@ let opened_modules = [
|
|||||||
"Tezos_protocol_environment" ;
|
"Tezos_protocol_environment" ;
|
||||||
"Pervasives" ;
|
"Pervasives" ;
|
||||||
"Error_monad" ;
|
"Error_monad" ;
|
||||||
"Hash" ;
|
|
||||||
"Logging" ;
|
"Logging" ;
|
||||||
]
|
]
|
||||||
|
|
||||||
|
@ -40,12 +40,17 @@
|
|||||||
v1/RPC_directory.mli
|
v1/RPC_directory.mli
|
||||||
|
|
||||||
v1/base58.mli
|
v1/base58.mli
|
||||||
v1/hash.mli
|
v1/s.mli
|
||||||
v1/blake2B.mli
|
v1/blake2B.mli
|
||||||
v1/ed25519.mli
|
v1/ed25519.mli
|
||||||
|
v1/block_hash.mli
|
||||||
|
v1/operation_hash.mli
|
||||||
|
v1/operation_list_hash.mli
|
||||||
|
v1/operation_list_list_hash.mli
|
||||||
|
v1/protocol_hash.mli
|
||||||
|
v1/context_hash.mli
|
||||||
|
|
||||||
;; Tezos specifics
|
;; Tezos specifics
|
||||||
v1/s.mli
|
|
||||||
v1/micheline.mli
|
v1/micheline.mli
|
||||||
v1/block_header.mli
|
v1/block_header.mli
|
||||||
v1/fitness.mli
|
v1/fitness.mli
|
||||||
|
@ -24,7 +24,6 @@ let dump_file oc file =
|
|||||||
let opened_modules = [
|
let opened_modules = [
|
||||||
"Pervasives" ;
|
"Pervasives" ;
|
||||||
"Error_monad" ;
|
"Error_monad" ;
|
||||||
"Hash" ;
|
|
||||||
]
|
]
|
||||||
|
|
||||||
let include_mli oc file =
|
let include_mli oc file =
|
||||||
|
@ -9,7 +9,22 @@
|
|||||||
|
|
||||||
(** Builds a new Hash type using Blake2B. *)
|
(** Builds a new Hash type using Blake2B. *)
|
||||||
|
|
||||||
module Make_minimal (Name : Hash.Name) : Hash.MINIMAL_HASH
|
(** The parameters for creating a new Hash type using
|
||||||
|
{!Make_Blake2B}. Both {!name} and {!title} are only informative,
|
||||||
|
used in error messages and serializers. *)
|
||||||
|
|
||||||
|
module type Name = sig
|
||||||
|
val name : string
|
||||||
|
val title : string
|
||||||
|
val size : int option
|
||||||
|
end
|
||||||
|
|
||||||
|
module type PrefixedName = sig
|
||||||
|
include Name
|
||||||
|
val b58check_prefix : string
|
||||||
|
end
|
||||||
|
|
||||||
|
module Make_minimal (Name : Name) : S.MINIMAL_HASH
|
||||||
module Make
|
module Make
|
||||||
(Register : sig
|
(Register : sig
|
||||||
val register_encoding:
|
val register_encoding:
|
||||||
@ -20,5 +35,5 @@ module Make
|
|||||||
wrap: ('a -> Base58.data) ->
|
wrap: ('a -> Base58.data) ->
|
||||||
'a Base58.encoding
|
'a Base58.encoding
|
||||||
end)
|
end)
|
||||||
(Name : Hash.PrefixedName) : HASH
|
(Name : PrefixedName) : S.HASH
|
||||||
|
|
||||||
|
11
src/lib_protocol_environment_sigs/v1/block_hash.mli
Normal file
11
src/lib_protocol_environment_sigs/v1/block_hash.mli
Normal file
@ -0,0 +1,11 @@
|
|||||||
|
(**************************************************************************)
|
||||||
|
(* *)
|
||||||
|
(* Copyright (c) 2014 - 2017. *)
|
||||||
|
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
|
||||||
|
(* *)
|
||||||
|
(* All rights reserved. No warranty, explicit or implicit, provided. *)
|
||||||
|
(* *)
|
||||||
|
(**************************************************************************)
|
||||||
|
|
||||||
|
(** Blocks hashes / IDs. *)
|
||||||
|
include S.HASH
|
11
src/lib_protocol_environment_sigs/v1/context_hash.mli
Normal file
11
src/lib_protocol_environment_sigs/v1/context_hash.mli
Normal file
@ -0,0 +1,11 @@
|
|||||||
|
(**************************************************************************)
|
||||||
|
(* *)
|
||||||
|
(* Copyright (c) 2014 - 2017. *)
|
||||||
|
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
|
||||||
|
(* *)
|
||||||
|
(* All rights reserved. No warranty, explicit or implicit, provided. *)
|
||||||
|
(* *)
|
||||||
|
(**************************************************************************)
|
||||||
|
|
||||||
|
(** Commited context hashes / IDs. *)
|
||||||
|
include S.HASH
|
@ -11,7 +11,7 @@
|
|||||||
|
|
||||||
(** {2 Hashed public keys for user ID} ***************************************)
|
(** {2 Hashed public keys for user ID} ***************************************)
|
||||||
|
|
||||||
module Public_key_hash : Hash.HASH
|
module Public_key_hash : S.HASH
|
||||||
|
|
||||||
|
|
||||||
(** {2 Signature} ************************************************************)
|
(** {2 Signature} ************************************************************)
|
||||||
|
@ -1,137 +0,0 @@
|
|||||||
(**************************************************************************)
|
|
||||||
(* *)
|
|
||||||
(* Copyright (c) 2014 - 2017. *)
|
|
||||||
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
|
|
||||||
(* *)
|
|
||||||
(* All rights reserved. No warranty, explicit or implicit, provided. *)
|
|
||||||
(* *)
|
|
||||||
(**************************************************************************)
|
|
||||||
|
|
||||||
(** Tezos - Manipulation and creation of hashes *)
|
|
||||||
|
|
||||||
(** {2 Hash Types} ************************************************************)
|
|
||||||
|
|
||||||
(** The signature of an abstract hash type, as produced by functor
|
|
||||||
{!Make_SHA256}. The {!t} type is abstracted for separating the
|
|
||||||
various kinds of hashes in the system at typing time. Each type is
|
|
||||||
equipped with functions to use it as is of as keys in the database
|
|
||||||
or in memory sets and maps. *)
|
|
||||||
|
|
||||||
module type MINIMAL_HASH = sig
|
|
||||||
|
|
||||||
type t
|
|
||||||
|
|
||||||
val name: string
|
|
||||||
val title: string
|
|
||||||
|
|
||||||
val hash_bytes: MBytes.t list -> t
|
|
||||||
val hash_string: string list -> t
|
|
||||||
val size: int (* in bytes *)
|
|
||||||
val compare: t -> t -> int
|
|
||||||
val equal: t -> t -> bool
|
|
||||||
|
|
||||||
val to_hex: t -> string
|
|
||||||
val of_hex: string -> t option
|
|
||||||
val of_hex_exn: string -> t
|
|
||||||
|
|
||||||
val to_string: t -> string
|
|
||||||
val of_string: string -> t option
|
|
||||||
val of_string_exn: string -> t
|
|
||||||
|
|
||||||
val to_bytes: t -> MBytes.t
|
|
||||||
val of_bytes: MBytes.t -> t option
|
|
||||||
val of_bytes_exn: MBytes.t -> t
|
|
||||||
|
|
||||||
val read: MBytes.t -> int -> t
|
|
||||||
val write: MBytes.t -> int -> t -> unit
|
|
||||||
|
|
||||||
val to_path: t -> string list -> string list
|
|
||||||
val of_path: string list -> t option
|
|
||||||
val of_path_exn: string list -> t
|
|
||||||
|
|
||||||
val prefix_path: string -> string list
|
|
||||||
val path_length: int
|
|
||||||
|
|
||||||
end
|
|
||||||
|
|
||||||
module type HASH = sig
|
|
||||||
|
|
||||||
include MINIMAL_HASH
|
|
||||||
|
|
||||||
val of_b58check_exn: string -> t
|
|
||||||
val of_b58check_opt: string -> t option
|
|
||||||
val to_b58check: t -> string
|
|
||||||
val to_short_b58check: t -> string
|
|
||||||
val encoding: t Data_encoding.t
|
|
||||||
val pp: Format.formatter -> t -> unit
|
|
||||||
val pp_short: Format.formatter -> t -> unit
|
|
||||||
type Base58.data += Hash of t
|
|
||||||
val b58check_encoding: t Base58.encoding
|
|
||||||
|
|
||||||
val rpc_arg: t RPC_arg.t
|
|
||||||
|
|
||||||
module Set : sig
|
|
||||||
include Set.S with type elt = t
|
|
||||||
val encoding: t Data_encoding.t
|
|
||||||
end
|
|
||||||
|
|
||||||
module Map : sig
|
|
||||||
include Map.S with type key = t
|
|
||||||
val encoding: 'a Data_encoding.t -> 'a t Data_encoding.t
|
|
||||||
end
|
|
||||||
|
|
||||||
end
|
|
||||||
|
|
||||||
module type MERKLE_TREE = sig
|
|
||||||
type elt
|
|
||||||
include HASH
|
|
||||||
val compute: elt list -> t
|
|
||||||
val empty: t
|
|
||||||
type path =
|
|
||||||
| Left of path * t
|
|
||||||
| Right of t * path
|
|
||||||
| Op
|
|
||||||
val compute_path: elt list -> int -> path
|
|
||||||
val check_path: path -> elt -> t * int
|
|
||||||
val path_encoding: path Data_encoding.t
|
|
||||||
end
|
|
||||||
|
|
||||||
(** {2 Building Hashes} *******************************************************)
|
|
||||||
|
|
||||||
(** The parameters for creating a new Hash type using
|
|
||||||
{!Make_Blake2B}. Both {!name} and {!title} are only informative,
|
|
||||||
used in error messages and serializers. *)
|
|
||||||
|
|
||||||
module type Name = sig
|
|
||||||
val name : string
|
|
||||||
val title : string
|
|
||||||
val size : int option
|
|
||||||
end
|
|
||||||
|
|
||||||
module type PrefixedName = sig
|
|
||||||
include Name
|
|
||||||
val b58check_prefix : string
|
|
||||||
end
|
|
||||||
|
|
||||||
(** {2 Predefined Hashes } ****************************************************)
|
|
||||||
|
|
||||||
(** Blocks hashes / IDs. *)
|
|
||||||
module Block_hash : HASH
|
|
||||||
|
|
||||||
(** Operations hashes / IDs. *)
|
|
||||||
module Operation_hash : HASH
|
|
||||||
|
|
||||||
(** List of operations hashes / IDs. *)
|
|
||||||
module Operation_list_hash :
|
|
||||||
MERKLE_TREE with type elt = Operation_hash.t
|
|
||||||
|
|
||||||
module Operation_list_list_hash :
|
|
||||||
MERKLE_TREE with type elt = Operation_list_hash.t
|
|
||||||
|
|
||||||
(** Protocol versions / source hashes. *)
|
|
||||||
module Protocol_hash : HASH
|
|
||||||
|
|
||||||
(** Commited conntext. *)
|
|
||||||
module Context_hash : HASH
|
|
||||||
|
|
||||||
module Net_id : HASH
|
|
11
src/lib_protocol_environment_sigs/v1/operation_hash.mli
Normal file
11
src/lib_protocol_environment_sigs/v1/operation_hash.mli
Normal file
@ -0,0 +1,11 @@
|
|||||||
|
(**************************************************************************)
|
||||||
|
(* *)
|
||||||
|
(* Copyright (c) 2014 - 2017. *)
|
||||||
|
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
|
||||||
|
(* *)
|
||||||
|
(* All rights reserved. No warranty, explicit or implicit, provided. *)
|
||||||
|
(* *)
|
||||||
|
(**************************************************************************)
|
||||||
|
|
||||||
|
(** Operations hashes / IDs. *)
|
||||||
|
include S.HASH
|
12
src/lib_protocol_environment_sigs/v1/operation_list_hash.mli
Normal file
12
src/lib_protocol_environment_sigs/v1/operation_list_hash.mli
Normal file
@ -0,0 +1,12 @@
|
|||||||
|
(**************************************************************************)
|
||||||
|
(* *)
|
||||||
|
(* Copyright (c) 2014 - 2017. *)
|
||||||
|
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
|
||||||
|
(* *)
|
||||||
|
(* All rights reserved. No warranty, explicit or implicit, provided. *)
|
||||||
|
(* *)
|
||||||
|
(**************************************************************************)
|
||||||
|
|
||||||
|
(** Blocks hashes / IDs. *)
|
||||||
|
include S.MERKLE_TREE with type elt = Operation_hash.t
|
||||||
|
|
@ -0,0 +1,11 @@
|
|||||||
|
(**************************************************************************)
|
||||||
|
(* *)
|
||||||
|
(* Copyright (c) 2014 - 2017. *)
|
||||||
|
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
|
||||||
|
(* *)
|
||||||
|
(* All rights reserved. No warranty, explicit or implicit, provided. *)
|
||||||
|
(* *)
|
||||||
|
(**************************************************************************)
|
||||||
|
|
||||||
|
(** Blocks hashes / IDs. *)
|
||||||
|
include S.MERKLE_TREE with type elt = Operation_list_hash.t
|
11
src/lib_protocol_environment_sigs/v1/protocol_hash.mli
Normal file
11
src/lib_protocol_environment_sigs/v1/protocol_hash.mli
Normal file
@ -0,0 +1,11 @@
|
|||||||
|
(**************************************************************************)
|
||||||
|
(* *)
|
||||||
|
(* Copyright (c) 2014 - 2017. *)
|
||||||
|
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
|
||||||
|
(* *)
|
||||||
|
(* All rights reserved. No warranty, explicit or implicit, provided. *)
|
||||||
|
(* *)
|
||||||
|
(**************************************************************************)
|
||||||
|
|
||||||
|
(** Protocol hashes / IDs. *)
|
||||||
|
include S.HASH
|
@ -44,3 +44,90 @@ module type HASHABLE = sig
|
|||||||
val hash_raw: MBytes.t -> hash
|
val hash_raw: MBytes.t -> hash
|
||||||
|
|
||||||
end
|
end
|
||||||
|
|
||||||
|
(** {2 Hash Types} ************************************************************)
|
||||||
|
|
||||||
|
(** The signature of an abstract hash type, as produced by functor
|
||||||
|
{!Make_SHA256}. The {!t} type is abstracted for separating the
|
||||||
|
various kinds of hashes in the system at typing time. Each type is
|
||||||
|
equipped with functions to use it as is of as keys in the database
|
||||||
|
or in memory sets and maps. *)
|
||||||
|
|
||||||
|
module type MINIMAL_HASH = sig
|
||||||
|
|
||||||
|
type t
|
||||||
|
|
||||||
|
val name: string
|
||||||
|
val title: string
|
||||||
|
|
||||||
|
val hash_bytes: MBytes.t list -> t
|
||||||
|
val hash_string: string list -> t
|
||||||
|
val size: int (* in bytes *)
|
||||||
|
val compare: t -> t -> int
|
||||||
|
val equal: t -> t -> bool
|
||||||
|
|
||||||
|
val to_hex: t -> string
|
||||||
|
val of_hex: string -> t option
|
||||||
|
val of_hex_exn: string -> t
|
||||||
|
|
||||||
|
val to_string: t -> string
|
||||||
|
val of_string: string -> t option
|
||||||
|
val of_string_exn: string -> t
|
||||||
|
|
||||||
|
val to_bytes: t -> MBytes.t
|
||||||
|
val of_bytes: MBytes.t -> t option
|
||||||
|
val of_bytes_exn: MBytes.t -> t
|
||||||
|
|
||||||
|
val read: MBytes.t -> int -> t
|
||||||
|
val write: MBytes.t -> int -> t -> unit
|
||||||
|
|
||||||
|
val to_path: t -> string list -> string list
|
||||||
|
val of_path: string list -> t option
|
||||||
|
val of_path_exn: string list -> t
|
||||||
|
|
||||||
|
val prefix_path: string -> string list
|
||||||
|
val path_length: int
|
||||||
|
|
||||||
|
end
|
||||||
|
|
||||||
|
module type HASH = sig
|
||||||
|
|
||||||
|
include MINIMAL_HASH
|
||||||
|
|
||||||
|
val of_b58check_exn: string -> t
|
||||||
|
val of_b58check_opt: string -> t option
|
||||||
|
val to_b58check: t -> string
|
||||||
|
val to_short_b58check: t -> string
|
||||||
|
val encoding: t Data_encoding.t
|
||||||
|
val pp: Format.formatter -> t -> unit
|
||||||
|
val pp_short: Format.formatter -> t -> unit
|
||||||
|
type Base58.data += Hash of t
|
||||||
|
val b58check_encoding: t Base58.encoding
|
||||||
|
|
||||||
|
val rpc_arg: t RPC_arg.t
|
||||||
|
|
||||||
|
module Set : sig
|
||||||
|
include Set.S with type elt = t
|
||||||
|
val encoding: t Data_encoding.t
|
||||||
|
end
|
||||||
|
|
||||||
|
module Map : sig
|
||||||
|
include Map.S with type key = t
|
||||||
|
val encoding: 'a Data_encoding.t -> 'a t Data_encoding.t
|
||||||
|
end
|
||||||
|
|
||||||
|
end
|
||||||
|
|
||||||
|
module type MERKLE_TREE = sig
|
||||||
|
type elt
|
||||||
|
include HASH
|
||||||
|
val compute: elt list -> t
|
||||||
|
val empty: t
|
||||||
|
type path =
|
||||||
|
| Left of path * t
|
||||||
|
| Right of t * path
|
||||||
|
| Op
|
||||||
|
val compute_path: elt list -> int -> path
|
||||||
|
val check_path: path -> elt -> t * int
|
||||||
|
val path_encoding: path Data_encoding.t
|
||||||
|
end
|
||||||
|
@ -97,11 +97,12 @@ module Node_protocol_environment_sigs = struct
|
|||||||
and type 'a Data_encoding.t = 'a Data_encoding.t
|
and type 'a Data_encoding.t = 'a Data_encoding.t
|
||||||
and type 'a Lwt.t = 'a Lwt.t
|
and type 'a Lwt.t = 'a Lwt.t
|
||||||
and type ('a, 'b) Pervasives.result = ('a, 'b) result
|
and type ('a, 'b) Pervasives.result = ('a, 'b) result
|
||||||
and type Hash.Net_id.t = Net_id.t
|
and type Block_hash.t = Block_hash.t
|
||||||
and type Hash.Block_hash.t = Block_hash.t
|
and type Operation_hash.t = Operation_hash.t
|
||||||
and type Hash.Operation_hash.t = Operation_hash.t
|
and type Operation_list_hash.t = Operation_list_hash.t
|
||||||
and type Hash.Operation_list_list_hash.t = Operation_list_list_hash.t
|
and type Operation_list_list_hash.t = Operation_list_list_hash.t
|
||||||
and type Hash.Context_hash.t = Context_hash.t
|
and type Context_hash.t = Context_hash.t
|
||||||
|
and type Protocol_hash.t = Protocol_hash.t
|
||||||
and type Context.t = Context.t
|
and type Context.t = Context.t
|
||||||
and type Time.t = Time.t
|
and type Time.t = Time.t
|
||||||
and type MBytes.t = MBytes.t
|
and type MBytes.t = MBytes.t
|
||||||
|
@ -87,11 +87,12 @@ module Node_protocol_environment_sigs : sig
|
|||||||
and type 'a Data_encoding.t = 'a Data_encoding.t
|
and type 'a Data_encoding.t = 'a Data_encoding.t
|
||||||
and type 'a Lwt.t = 'a Lwt.t
|
and type 'a Lwt.t = 'a Lwt.t
|
||||||
and type ('a, 'b) Pervasives.result = ('a, 'b) result
|
and type ('a, 'b) Pervasives.result = ('a, 'b) result
|
||||||
and type Hash.Net_id.t = Net_id.t
|
and type Block_hash.t = Block_hash.t
|
||||||
and type Hash.Block_hash.t = Block_hash.t
|
and type Operation_hash.t = Operation_hash.t
|
||||||
and type Hash.Operation_hash.t = Operation_hash.t
|
and type Operation_list_hash.t = Operation_list_hash.t
|
||||||
and type Hash.Operation_list_list_hash.t = Operation_list_list_hash.t
|
and type Operation_list_list_hash.t = Operation_list_list_hash.t
|
||||||
and type Hash.Context_hash.t = Context_hash.t
|
and type Context_hash.t = Context_hash.t
|
||||||
|
and type Protocol_hash.t = Protocol_hash.t
|
||||||
and type Context.t = Context.t
|
and type Context.t = Context.t
|
||||||
and type Time.t = Time.t
|
and type Time.t = Time.t
|
||||||
and type MBytes.t = MBytes.t
|
and type MBytes.t = MBytes.t
|
||||||
|
Loading…
Reference in New Issue
Block a user