Shell: simplify hash signatures
This commit is contained in:
parent
a576306052
commit
9ffead02d2
@ -127,7 +127,7 @@ module type SIGNER = sig
|
|||||||
val neuterize : secret_key -> public_key Lwt.t
|
val neuterize : secret_key -> public_key Lwt.t
|
||||||
val public_key : public_key -> Ed25519.Public_key.t Lwt.t
|
val public_key : public_key -> Ed25519.Public_key.t Lwt.t
|
||||||
val public_key_hash : public_key -> Ed25519.Public_key_hash.t Lwt.t
|
val public_key_hash : public_key -> Ed25519.Public_key_hash.t Lwt.t
|
||||||
val sign : secret_key -> MBytes.t -> Ed25519.Signature.t tzresult Lwt.t
|
val sign : secret_key -> MBytes.t -> Ed25519.t tzresult Lwt.t
|
||||||
end
|
end
|
||||||
|
|
||||||
let signers_table : (string, (module SIGNER) * bool) Hashtbl.t = Hashtbl.create 13
|
let signers_table : (string, (module SIGNER) * bool) Hashtbl.t = Hashtbl.create 13
|
||||||
@ -156,7 +156,7 @@ let sign cctxt ((Sk_locator { scheme }) as skloc) buf =
|
|||||||
|
|
||||||
let append cctxt loc buf =
|
let append cctxt loc buf =
|
||||||
sign cctxt loc buf >>|? fun signature ->
|
sign cctxt loc buf >>|? fun signature ->
|
||||||
MBytes.concat buf (Ed25519.Signature.to_bytes signature)
|
MBytes.concat buf (Ed25519.to_bytes signature)
|
||||||
|
|
||||||
let gen_keys ?(force=false) ?seed (cctxt : #Client_context.io_wallet) name =
|
let gen_keys ?(force=false) ?seed (cctxt : #Client_context.io_wallet) name =
|
||||||
let seed =
|
let seed =
|
||||||
|
@ -90,7 +90,7 @@ module type SIGNER = sig
|
|||||||
val public_key_hash : public_key -> Ed25519.Public_key_hash.t Lwt.t
|
val public_key_hash : public_key -> Ed25519.Public_key_hash.t Lwt.t
|
||||||
(** [public_key_hash pk] is the hash of [pk]. *)
|
(** [public_key_hash pk] is the hash of [pk]. *)
|
||||||
|
|
||||||
val sign : secret_key -> MBytes.t -> Ed25519.Signature.t tzresult Lwt.t
|
val sign : secret_key -> MBytes.t -> Ed25519.t tzresult Lwt.t
|
||||||
(** [sign sk data] is signature obtained by signing [data] with
|
(** [sign sk data] is signature obtained by signing [data] with
|
||||||
[sk]. *)
|
[sk]. *)
|
||||||
end
|
end
|
||||||
@ -105,7 +105,7 @@ val find_signer_for_key :
|
|||||||
#Client_context.io_wallet -> scheme:string -> (module SIGNER) tzresult Lwt.t
|
#Client_context.io_wallet -> scheme:string -> (module SIGNER) tzresult Lwt.t
|
||||||
val sign :
|
val sign :
|
||||||
#Client_context.io_wallet ->
|
#Client_context.io_wallet ->
|
||||||
sk_locator -> MBytes.t -> Ed25519.Signature.t tzresult Lwt.t
|
sk_locator -> MBytes.t -> Ed25519.t tzresult Lwt.t
|
||||||
val append :
|
val append :
|
||||||
#Client_context.io_wallet ->
|
#Client_context.io_wallet ->
|
||||||
sk_locator -> MBytes.t -> MBytes.t tzresult Lwt.t
|
sk_locator -> MBytes.t -> MBytes.t tzresult Lwt.t
|
||||||
|
@ -23,6 +23,7 @@ module type PrefixedName = sig
|
|||||||
end
|
end
|
||||||
|
|
||||||
module Make_minimal (K : Name) = struct
|
module Make_minimal (K : Name) = struct
|
||||||
|
|
||||||
open Blake2
|
open Blake2
|
||||||
type t = Blake2b.hash
|
type t = Blake2b.hash
|
||||||
|
|
||||||
@ -33,29 +34,37 @@ module Make_minimal (K : Name) = struct
|
|||||||
| None -> 32
|
| None -> 32
|
||||||
| Some x -> x
|
| Some x -> x
|
||||||
|
|
||||||
let of_string s =
|
let of_string_opt s =
|
||||||
if String.length s <> size then
|
if String.length s <> size then
|
||||||
None
|
None
|
||||||
else
|
else
|
||||||
Some (Blake2b.Hash (Cstruct.of_string s))
|
Some (Blake2b.Hash (Cstruct.of_string s))
|
||||||
let of_string_exn s =
|
let of_string s =
|
||||||
match of_string s with
|
match of_string_opt s with
|
||||||
| None ->
|
| None ->
|
||||||
let msg =
|
generic_error "%s.of_string: wrong string size (%d)"
|
||||||
Printf.sprintf "%s.of_string: wrong string size (%d)"
|
K.name (String.length s)
|
||||||
K.name (String.length s) in
|
| Some h -> Ok h
|
||||||
raise (Invalid_argument msg)
|
let of_string_exn s =
|
||||||
|
match of_string_opt s with
|
||||||
|
| None ->
|
||||||
|
Format.kasprintf invalid_arg
|
||||||
|
"%s.of_string: wrong string size (%d)"
|
||||||
|
K.name (String.length s)
|
||||||
| Some h -> h
|
| Some h -> h
|
||||||
let to_string (Blake2b.Hash h) = Cstruct.to_string h
|
let to_string (Blake2b.Hash h) = Cstruct.to_string h
|
||||||
|
|
||||||
let of_hex s = of_string (Hex.to_string (`Hex s))
|
let of_hex s = of_string (Hex.to_string s)
|
||||||
let of_hex_exn s = of_string_exn (Hex.to_string (`Hex s))
|
let of_hex_opt s = of_string_opt (Hex.to_string s)
|
||||||
let to_hex s =
|
let of_hex_exn s = of_string_exn (Hex.to_string s)
|
||||||
let `Hex s = Hex.of_string (to_string s) in
|
let to_hex s = Hex.of_string (to_string s)
|
||||||
s
|
|
||||||
|
|
||||||
let compare (Blake2b.Hash h1) (Blake2b.Hash h2) = Cstruct.compare h1 h2
|
let pp ppf h =
|
||||||
let equal x y = compare x y = 0
|
let `Hex h = to_hex h in
|
||||||
|
Format.pp_print_string ppf h
|
||||||
|
let pp_short ppf h =
|
||||||
|
let `Hex h = to_hex h in
|
||||||
|
Format.pp_print_string ppf (String.sub h 0 8)
|
||||||
|
|
||||||
let of_bytes_opt b =
|
let of_bytes_opt b =
|
||||||
if MBytes.length b <> size then
|
if MBytes.length b <> size then
|
||||||
@ -77,8 +86,8 @@ module Make_minimal (K : Name) = struct
|
|||||||
generic_error "Failed to deserialize a hash (%s)" K.name
|
generic_error "Failed to deserialize a hash (%s)" K.name
|
||||||
let to_bytes (Blake2b.Hash h) = Cstruct.to_bigarray h
|
let to_bytes (Blake2b.Hash h) = Cstruct.to_bigarray h
|
||||||
|
|
||||||
let read src off = of_bytes_exn @@ MBytes.sub src off size
|
(* let read src off = of_bytes_exn @@ MBytes.sub src off size *)
|
||||||
let write dst off h = MBytes.blit (to_bytes h) 0 dst off size
|
(* let write dst off h = MBytes.blit (to_bytes h) 0 dst off size *)
|
||||||
|
|
||||||
let hash_bytes ?key l =
|
let hash_bytes ?key l =
|
||||||
let key = Option.map ~f:Cstruct.of_bigarray key in
|
let key = Option.map ~f:Cstruct.of_bigarray key in
|
||||||
@ -94,16 +103,16 @@ module Make_minimal (K : Name) = struct
|
|||||||
|
|
||||||
let path_length = 6
|
let path_length = 6
|
||||||
let to_path key l =
|
let to_path key l =
|
||||||
let key = to_hex key in
|
let `Hex key = to_hex key in
|
||||||
String.sub key 0 2 :: String.sub key 2 2 ::
|
String.sub key 0 2 :: String.sub key 2 2 ::
|
||||||
String.sub key 4 2 :: String.sub key 6 2 ::
|
String.sub key 4 2 :: String.sub key 6 2 ::
|
||||||
String.sub key 8 2 :: String.sub key 10 (size * 2 - 10) :: l
|
String.sub key 8 2 :: String.sub key 10 (size * 2 - 10) :: l
|
||||||
let of_path path =
|
let of_path path =
|
||||||
let path = String.concat "" path in
|
let path = String.concat "" path in
|
||||||
of_hex path
|
of_hex_opt (`Hex path)
|
||||||
let of_path_exn path =
|
let of_path_exn path =
|
||||||
let path = String.concat "" path in
|
let path = String.concat "" path in
|
||||||
of_hex_exn path
|
of_hex_exn (`Hex path)
|
||||||
|
|
||||||
let prefix_path p =
|
let prefix_path p =
|
||||||
let `Hex p = Hex.of_string p in
|
let `Hex p = Hex.of_string p in
|
||||||
@ -116,10 +125,12 @@ module Make_minimal (K : Name) = struct
|
|||||||
and p6 = if len > 10 then String.sub p 10 (min (len - 10) (size * 2 - 10)) else "" in
|
and p6 = if len > 10 then String.sub p 10 (min (len - 10) (size * 2 - 10)) else "" in
|
||||||
[ p1 ; p2 ; p3 ; p4 ; p5 ; p6 ]
|
[ p1 ; p2 ; p3 ; p4 ; p5 ; p6 ]
|
||||||
|
|
||||||
let zero =
|
let zero = of_hex_exn (`Hex (String.make (size * 2) '0'))
|
||||||
match of_hex (String.make (size * 2) '0') with
|
|
||||||
| Some c -> c
|
include Compare.Make(struct
|
||||||
| None -> assert false
|
type nonrec t = t
|
||||||
|
let compare (Blake2b.Hash h1) (Blake2b.Hash h2) = Cstruct.compare h1 h2
|
||||||
|
end)
|
||||||
|
|
||||||
end
|
end
|
||||||
|
|
||||||
@ -142,9 +153,9 @@ module Make (R : sig
|
|||||||
conv to_bytes of_bytes_exn (Fixed.bytes size)
|
conv to_bytes of_bytes_exn (Fixed.bytes size)
|
||||||
|
|
||||||
let hash =
|
let hash =
|
||||||
if size >= 8 then
|
if Compare.Int.(size >= 8) then
|
||||||
fun h -> Int64.to_int (MBytes.get_int64 (to_bytes h) 0)
|
fun h -> Int64.to_int (MBytes.get_int64 (to_bytes h) 0)
|
||||||
else if size >= 4 then
|
else if Compare.Int.(size >= 4) then
|
||||||
fun h -> Int32.to_int (MBytes.get_int32 (to_bytes h) 0)
|
fun h -> Int32.to_int (MBytes.get_int32 (to_bytes h) 0)
|
||||||
else
|
else
|
||||||
fun h ->
|
fun h ->
|
||||||
@ -155,16 +166,17 @@ module Make (R : sig
|
|||||||
done ;
|
done ;
|
||||||
!r
|
!r
|
||||||
|
|
||||||
type Base58.data += Hash of t
|
type Base58.data += Data of t
|
||||||
|
|
||||||
let b58check_encoding =
|
let b58check_encoding =
|
||||||
R.register_encoding
|
R.register_encoding
|
||||||
~prefix: K.b58check_prefix
|
~prefix: K.b58check_prefix
|
||||||
~length: size
|
~length: size
|
||||||
~wrap: (fun s -> Hash s)
|
~wrap: (fun s -> Data s)
|
||||||
~of_raw: (fun h -> of_string h) ~to_raw:to_string
|
~of_raw: of_string_opt
|
||||||
|
~to_raw: to_string
|
||||||
|
|
||||||
include Hash.Make(struct
|
include Helpers.Make(struct
|
||||||
type nonrec t = t
|
type nonrec t = t
|
||||||
let title = title
|
let title = title
|
||||||
let name = name
|
let name = name
|
||||||
@ -325,3 +337,10 @@ include
|
|||||||
let title = ""
|
let title = ""
|
||||||
let size = None
|
let size = None
|
||||||
end)
|
end)
|
||||||
|
|
||||||
|
let pp ppf h =
|
||||||
|
let `Hex h = to_hex h in
|
||||||
|
Format.pp_print_string ppf h
|
||||||
|
let pp_short ppf h =
|
||||||
|
let `Hex h = to_hex h in
|
||||||
|
Format.pp_print_string ppf (String.sub h 0 8)
|
||||||
|
@ -12,6 +12,7 @@
|
|||||||
(** {2 Predefined Hashes } ****************************************************)
|
(** {2 Predefined Hashes } ****************************************************)
|
||||||
|
|
||||||
include S.MINIMAL_HASH
|
include S.MINIMAL_HASH
|
||||||
|
include S.RAW_DATA with type t := t
|
||||||
|
|
||||||
(** {2 Building Hashes} *******************************************************)
|
(** {2 Building Hashes} *******************************************************)
|
||||||
|
|
||||||
|
@ -21,26 +21,28 @@ let hash_string ?key l = extract (Block_hash.hash_string ?key l)
|
|||||||
|
|
||||||
let size = 4
|
let size = 4
|
||||||
|
|
||||||
let compare = String.compare
|
let of_string_opt s =
|
||||||
let equal = String.equal
|
|
||||||
|
|
||||||
let of_string s =
|
|
||||||
if String.length s <> size then None else Some s
|
if String.length s <> size then None else Some s
|
||||||
let of_string_exn s =
|
let of_string s =
|
||||||
match of_string s with
|
match of_string_opt s with
|
||||||
| None ->
|
| None ->
|
||||||
let msg =
|
generic_error
|
||||||
Printf.sprintf "%s.of_string: wrong string size (%d)"
|
"%s.of_string: wrong string size (%d)"
|
||||||
name (String.length s) in
|
name (String.length s)
|
||||||
raise (Invalid_argument msg)
|
| Some h -> Ok h
|
||||||
|
let of_string_exn s =
|
||||||
|
match of_string_opt s with
|
||||||
|
| None ->
|
||||||
|
Format.kasprintf invalid_arg
|
||||||
|
"%s.of_string_exn: wrong string size (%d)"
|
||||||
|
name (String.length s)
|
||||||
| Some h -> h
|
| Some h -> h
|
||||||
|
|
||||||
let to_string s = s
|
let to_string s = s
|
||||||
let of_hex s = of_string (Hex.to_string (`Hex s))
|
let of_hex s = of_string (Hex.to_string s)
|
||||||
let of_hex_exn s = of_string_exn (Hex.to_string (`Hex s))
|
let of_hex_opt s = of_string_opt (Hex.to_string s)
|
||||||
let to_hex s =
|
let of_hex_exn s = of_string_exn (Hex.to_string s)
|
||||||
let `Hex s = Hex.of_string (to_string s) in
|
let to_hex s = Hex.of_string (to_string s)
|
||||||
s
|
|
||||||
|
|
||||||
|
|
||||||
let of_bytes_opt b =
|
let of_bytes_opt b =
|
||||||
@ -63,35 +65,35 @@ let of_bytes s =
|
|||||||
generic_error "Failed to deserialize a hash (%s)" name
|
generic_error "Failed to deserialize a hash (%s)" name
|
||||||
let to_bytes = MBytes.of_string
|
let to_bytes = MBytes.of_string
|
||||||
|
|
||||||
let read src off = of_bytes_exn @@ MBytes.sub src off size
|
(* let read src off = of_bytes_exn @@ MBytes.sub src off size *)
|
||||||
let write dst off h = MBytes.blit (to_bytes h) 0 dst off size
|
(* let write dst off h = MBytes.blit (to_bytes h) 0 dst off size *)
|
||||||
|
|
||||||
let path_length = 1
|
let path_length = 1
|
||||||
let to_path key l = to_hex key :: l
|
let to_path key l =
|
||||||
|
let `Hex h = to_hex key in
|
||||||
|
h :: l
|
||||||
let of_path path =
|
let of_path path =
|
||||||
let path = String.concat "" path in
|
let path = String.concat "" path in
|
||||||
of_hex path
|
of_hex_opt (`Hex path)
|
||||||
let of_path_exn path =
|
let of_path_exn path =
|
||||||
let path = String.concat "" path in
|
let path = String.concat "" path in
|
||||||
of_hex_exn path
|
of_hex_exn (`Hex path)
|
||||||
|
|
||||||
let prefix_path p =
|
let prefix_path p =
|
||||||
let `Hex p = Hex.of_string p in
|
let `Hex p = Hex.of_string p in
|
||||||
[ p ]
|
[ p ]
|
||||||
|
|
||||||
let zero =
|
let zero = of_hex_exn (`Hex (String.make (size * 2) '0'))
|
||||||
match of_hex (String.make (size * 2) '0') with
|
|
||||||
| Some c -> c
|
|
||||||
| None -> assert false
|
|
||||||
|
|
||||||
type Base58.data += Hash of t
|
type Base58.data += Data of t
|
||||||
|
|
||||||
let b58check_encoding =
|
let b58check_encoding =
|
||||||
Base58.register_encoding
|
Base58.register_encoding
|
||||||
~prefix: Base58.Prefix.chain_id
|
~prefix: Base58.Prefix.chain_id
|
||||||
~length: size
|
~length: size
|
||||||
~wrap: (fun s -> Hash s)
|
~wrap: (fun s -> Data s)
|
||||||
~of_raw:of_string ~to_raw: (fun h -> h)
|
~of_raw: of_string_opt
|
||||||
|
~to_raw: to_string
|
||||||
|
|
||||||
let raw_encoding =
|
let raw_encoding =
|
||||||
let open Data_encoding in
|
let open Data_encoding in
|
||||||
@ -102,7 +104,12 @@ let hash h =
|
|||||||
|
|
||||||
let of_block_hash bh = hash_bytes [Block_hash.to_bytes bh]
|
let of_block_hash bh = hash_bytes [Block_hash.to_bytes bh]
|
||||||
|
|
||||||
include Hash.Make(struct
|
include Compare.Make(struct
|
||||||
|
type nonrec t = t
|
||||||
|
let compare = String.compare
|
||||||
|
end)
|
||||||
|
|
||||||
|
include Helpers.Make(struct
|
||||||
type nonrec t = t
|
type nonrec t = t
|
||||||
let title = title
|
let title = title
|
||||||
let name = name
|
let name = name
|
||||||
|
@ -7,9 +7,11 @@
|
|||||||
(* *)
|
(* *)
|
||||||
(**************************************************************************)
|
(**************************************************************************)
|
||||||
|
|
||||||
|
open Error_monad
|
||||||
|
|
||||||
module Public_key_hash = Blake2B.Make(Base58)(struct
|
module Public_key_hash = Blake2B.Make(Base58)(struct
|
||||||
let name = "Ed25519.Public_key_hash"
|
let name = "Ed25519.Public_key_hash"
|
||||||
let title = "An Ed25519 public key ID"
|
let title = "An Ed25519 public key hash"
|
||||||
let b58check_prefix = Base58.Prefix.ed25519_public_key_hash
|
let b58check_prefix = Base58.Prefix.ed25519_public_key_hash
|
||||||
let size = Some 20
|
let size = Some 20
|
||||||
end)
|
end)
|
||||||
@ -23,53 +25,27 @@ module Public_key = struct
|
|||||||
|
|
||||||
type t = Sign.public Sign.key
|
type t = Sign.public Sign.key
|
||||||
|
|
||||||
include Compare.Make(struct
|
let name = "Ed25519.Public_key"
|
||||||
type nonrec t = t
|
let title = "Ed25519 public key"
|
||||||
let compare a b =
|
|
||||||
Cstruct.compare (Sign.to_cstruct a) (Sign.to_cstruct b)
|
|
||||||
end)
|
|
||||||
|
|
||||||
type Base58.data +=
|
|
||||||
| Public_key of t
|
|
||||||
|
|
||||||
let to_string s = Cstruct.to_string (Sign.to_cstruct s)
|
let to_string s = Cstruct.to_string (Sign.to_cstruct s)
|
||||||
let of_string s = Sign.pk_of_cstruct (Cstruct.of_string s)
|
let of_string_opt s = Sign.pk_of_cstruct (Cstruct.of_string s)
|
||||||
|
|
||||||
|
let to_bytes pk = Cstruct.to_bigarray (Sign.to_cstruct pk)
|
||||||
|
let of_bytes_opt s = Sign.pk_of_cstruct (Cstruct.of_bigarray s)
|
||||||
|
|
||||||
|
let size = Sign.pkbytes
|
||||||
|
|
||||||
|
type Base58.data +=
|
||||||
|
| Data of t
|
||||||
|
|
||||||
let b58check_encoding =
|
let b58check_encoding =
|
||||||
Base58.register_encoding
|
Base58.register_encoding
|
||||||
~prefix: Base58.Prefix.ed25519_public_key
|
~prefix: Base58.Prefix.ed25519_public_key
|
||||||
~length:Sign.pkbytes
|
~length: size
|
||||||
~to_raw:to_string
|
~to_raw: to_string
|
||||||
~of_raw:of_string
|
~of_raw: of_string_opt
|
||||||
~wrap:(fun x -> Public_key x)
|
~wrap: (fun x -> Data x)
|
||||||
|
|
||||||
let of_b58check_opt s = Base58.simple_decode b58check_encoding s
|
|
||||||
let of_b58check_exn s =
|
|
||||||
match Base58.simple_decode b58check_encoding s with
|
|
||||||
| Some x -> x
|
|
||||||
| None -> Pervasives.failwith
|
|
||||||
(Printf.sprintf "%s is not an ed25519 public key" s)
|
|
||||||
let to_b58check s = Base58.simple_encode b58check_encoding s
|
|
||||||
let pp ppf t = Format.fprintf ppf "%s" (to_b58check t)
|
|
||||||
|
|
||||||
let of_hex s = of_string (Hex.to_string s)
|
|
||||||
let of_hex_exn s =
|
|
||||||
match of_string (Hex.to_string s) with
|
|
||||||
| Some x -> x
|
|
||||||
| None -> invalid_arg "Public_key.of_hex_exn"
|
|
||||||
let to_hex s = Hex.of_string (to_string s)
|
|
||||||
|
|
||||||
let of_bytes_opt s =
|
|
||||||
Sign.pk_of_cstruct (Cstruct.of_bigarray s)
|
|
||||||
|
|
||||||
let of_bytes_exn s =
|
|
||||||
match of_bytes_opt s with
|
|
||||||
| None ->
|
|
||||||
Pervasives.invalid_arg "Ed25519.Public_key.of_bytes_exn: argument is not a serialized public key"
|
|
||||||
| Some pk -> pk
|
|
||||||
let size = Sign.pkbytes
|
|
||||||
|
|
||||||
let to_bytes pk = Cstruct.to_bigarray (Sign.to_cstruct pk)
|
|
||||||
|
|
||||||
let () =
|
let () =
|
||||||
Base58.check_encoded_prefix b58check_encoding "edpk" 54
|
Base58.check_encoded_prefix b58check_encoding "edpk" 54
|
||||||
@ -78,36 +54,42 @@ module Public_key = struct
|
|||||||
Public_key_hash.hash_bytes
|
Public_key_hash.hash_bytes
|
||||||
[ Cstruct.to_bigarray (Sign.to_cstruct v) ]
|
[ Cstruct.to_bigarray (Sign.to_cstruct v) ]
|
||||||
|
|
||||||
let encoding =
|
include Compare.Make(struct
|
||||||
let open Data_encoding in
|
type nonrec t = t
|
||||||
splitted
|
let compare a b =
|
||||||
~json:
|
Cstruct.compare (Sign.to_cstruct a) (Sign.to_cstruct b)
|
||||||
(describe
|
end)
|
||||||
~title: "An Ed25519 public key (Tezos_crypto.Base58Check encoded)" @@
|
|
||||||
conv
|
include Helpers.MakeRaw(struct
|
||||||
(fun s -> to_b58check s)
|
type nonrec t = t
|
||||||
(fun s ->
|
let name = name
|
||||||
match of_b58check_opt s with
|
let of_bytes_opt = of_bytes_opt
|
||||||
| Some x -> x
|
let of_string_opt = of_string_opt
|
||||||
| None -> Data_encoding.Json.cannot_destruct
|
let to_string = to_string
|
||||||
"Ed25519 public key: unexpected prefix.")
|
end)
|
||||||
string)
|
|
||||||
~binary:
|
include Helpers.MakeB58(struct
|
||||||
(conv
|
type nonrec t = t
|
||||||
to_bytes
|
let title = title
|
||||||
of_bytes_exn
|
let name = name
|
||||||
(Fixed.bytes size))
|
let b58check_encoding = b58check_encoding
|
||||||
let of_b58check s =
|
end)
|
||||||
match of_b58check_opt s with
|
|
||||||
| Some x -> Ok x
|
include Helpers.MakeEncoder(struct
|
||||||
| None ->
|
type nonrec t = t
|
||||||
Error_monad.generic_error
|
let name = name
|
||||||
"Failed to read a base58-encoded Ed25519 public key"
|
let title = title
|
||||||
let param
|
let raw_encoding =
|
||||||
?(name="ed25519-public")
|
let open Data_encoding in
|
||||||
?(desc="Ed25519 public key (b58check-encoded)") t =
|
conv to_bytes of_bytes_exn (Fixed.bytes size)
|
||||||
Clic.(param ~name ~desc
|
let of_b58check = of_b58check
|
||||||
(parameter (fun _ str -> Lwt.return (of_b58check str))) t)
|
let of_b58check_opt = of_b58check_opt
|
||||||
|
let of_b58check_exn = of_b58check_exn
|
||||||
|
let to_b58check = to_b58check
|
||||||
|
let to_short_b58check = to_short_b58check
|
||||||
|
end)
|
||||||
|
|
||||||
|
let pp ppf t = Format.fprintf ppf "%s" (to_b58check t)
|
||||||
|
|
||||||
end
|
end
|
||||||
|
|
||||||
@ -115,44 +97,12 @@ module Secret_key = struct
|
|||||||
|
|
||||||
type t = Sign.secret Sign.key
|
type t = Sign.secret Sign.key
|
||||||
|
|
||||||
let to_public_key = Sign.public
|
let name = "Ed25519.Secret_key"
|
||||||
|
let title = "An Ed25519 secret key"
|
||||||
|
|
||||||
type Base58.data +=
|
let size = Sign.seedbytes
|
||||||
| Secret_key of t
|
|
||||||
|
|
||||||
let seed_encoding =
|
|
||||||
Base58.register_encoding
|
|
||||||
~prefix: Base58.Prefix.ed25519_seed
|
|
||||||
~length:Sign.seedbytes
|
|
||||||
~to_raw:(fun sk -> Cstruct.to_string (Sign.seed sk))
|
|
||||||
~of_raw:(fun buf ->
|
|
||||||
let seed = Cstruct.of_string buf in
|
|
||||||
match Sign.keypair ~seed () with
|
|
||||||
| exception _ -> None
|
|
||||||
| _pk, sk -> Some sk)
|
|
||||||
~wrap:(fun sk -> Secret_key sk)
|
|
||||||
|
|
||||||
let secret_key_encoding =
|
|
||||||
Base58.register_encoding
|
|
||||||
~prefix: Base58.Prefix.ed25519_secret_key
|
|
||||||
~length:Sign.skbytes
|
|
||||||
~to_raw:(fun sk -> Cstruct.to_string (Sign.to_cstruct sk))
|
|
||||||
~of_raw:(fun buf -> Sign.sk_of_cstruct (Cstruct.of_string buf))
|
|
||||||
~wrap:(fun x -> Secret_key x)
|
|
||||||
|
|
||||||
let of_b58check_opt s =
|
|
||||||
match Base58.simple_decode seed_encoding s with
|
|
||||||
| Some x -> Some x
|
|
||||||
| None -> Base58.simple_decode secret_key_encoding s
|
|
||||||
|
|
||||||
let of_b58check_exn s =
|
|
||||||
match of_b58check_opt s with
|
|
||||||
| Some x -> x
|
|
||||||
| None -> Pervasives.failwith
|
|
||||||
(Printf.sprintf "%s is not an ed25519 secret key" s)
|
|
||||||
let to_b58check s = Base58.simple_encode seed_encoding s
|
|
||||||
let pp ppf t = Format.fprintf ppf "%s" (to_b58check t)
|
|
||||||
|
|
||||||
|
let to_bytes x = Cstruct.to_bigarray (Sign.seed x)
|
||||||
let of_bytes_opt s =
|
let of_bytes_opt s =
|
||||||
let s = Cstruct.of_bigarray s in
|
let s = Cstruct.of_bigarray s in
|
||||||
match Cstruct.len s with
|
match Cstruct.len s with
|
||||||
@ -160,137 +110,171 @@ module Secret_key = struct
|
|||||||
| 64 -> Sign.sk_of_cstruct s
|
| 64 -> Sign.sk_of_cstruct s
|
||||||
| _ -> None
|
| _ -> None
|
||||||
|
|
||||||
let of_bytes_exn s =
|
let to_string s = MBytes.to_string (to_bytes s)
|
||||||
match of_bytes_opt s with
|
let of_string_opt s = of_bytes_opt (MBytes.of_string s)
|
||||||
| None ->
|
|
||||||
Pervasives.invalid_arg "Ed25519.Secret_key.of_bytes_exn: argument is not a serialized seed"
|
|
||||||
| Some sk -> sk
|
|
||||||
|
|
||||||
let to_bytes x = Cstruct.to_bigarray (Sign.seed x)
|
let to_public_key = Sign.public
|
||||||
let size = Sign.seedbytes
|
|
||||||
|
|
||||||
let () =
|
type Base58.data +=
|
||||||
Base58.check_encoded_prefix seed_encoding "edsk" 54 ;
|
| Data of t
|
||||||
Base58.check_encoded_prefix secret_key_encoding "edsk" 98
|
|
||||||
|
|
||||||
let encoding =
|
let b58check_encoding =
|
||||||
let open Data_encoding in
|
Base58.register_encoding
|
||||||
splitted
|
~prefix: Base58.Prefix.ed25519_seed
|
||||||
~json:
|
~length: size
|
||||||
(describe
|
~to_raw: (fun sk -> Cstruct.to_string (Sign.seed sk))
|
||||||
~title: "An Ed25519 secret key (Tezos_crypto.Base58Check encoded)" @@
|
~of_raw: (fun buf ->
|
||||||
conv
|
let seed = Cstruct.of_string buf in
|
||||||
(fun s -> to_b58check s)
|
match Sign.keypair ~seed () with
|
||||||
(fun s ->
|
| exception _ -> None
|
||||||
match of_b58check_opt s with
|
| _pk, sk -> Some sk)
|
||||||
| Some x -> x
|
~wrap: (fun sk -> Data sk)
|
||||||
| None -> Data_encoding.Json.cannot_destruct
|
|
||||||
"Ed25519 secret key: unexpected prefix.")
|
let secret_key_encoding =
|
||||||
string)
|
Base58.register_encoding
|
||||||
~binary:
|
~prefix: Base58.Prefix.ed25519_secret_key
|
||||||
(conv
|
~length: Sign.skbytes
|
||||||
to_bytes
|
~to_raw: (fun sk -> Cstruct.to_string (Sign.to_cstruct sk))
|
||||||
of_bytes_exn
|
~of_raw: (fun buf -> Sign.sk_of_cstruct (Cstruct.of_string buf))
|
||||||
(Fixed.bytes size))
|
~wrap: (fun x -> Data x)
|
||||||
|
|
||||||
|
let of_b58check_opt s =
|
||||||
|
match Base58.simple_decode b58check_encoding s with
|
||||||
|
| Some x -> Some x
|
||||||
|
| None -> Base58.simple_decode secret_key_encoding s
|
||||||
|
let of_b58check_exn s =
|
||||||
|
match of_b58check_opt s with
|
||||||
|
| Some x -> x
|
||||||
|
| None -> Format.kasprintf Pervasives.failwith "Unexpected data (%s)" name
|
||||||
let of_b58check s =
|
let of_b58check s =
|
||||||
match of_b58check_opt s with
|
match of_b58check_opt s with
|
||||||
| Some x -> Ok x
|
| Some x -> Ok x
|
||||||
| None ->
|
| None ->
|
||||||
Error_monad.generic_error
|
generic_error
|
||||||
"Failed to read a base58-encoded Ed25519 secret key"
|
"Failed to read a b58check_encoding data (%s): %S"
|
||||||
let param
|
name s
|
||||||
?(name="ed25519-secret")
|
|
||||||
?(desc="Ed25519 secret key (b58check-encoded)") t =
|
let to_b58check s = Base58.simple_encode b58check_encoding s
|
||||||
Clic.(param ~name ~desc
|
let to_short_b58check s =
|
||||||
(parameter (fun _ str -> Lwt.return (of_b58check str))) t)
|
String.sub
|
||||||
|
(to_b58check s) 0
|
||||||
|
(10 + String.length (Base58.prefix b58check_encoding))
|
||||||
|
|
||||||
|
let () =
|
||||||
|
Base58.check_encoded_prefix b58check_encoding "edsk" 54 ;
|
||||||
|
Base58.check_encoded_prefix secret_key_encoding "edsk" 98
|
||||||
|
|
||||||
|
include Compare.Make(struct
|
||||||
|
type nonrec t = t
|
||||||
|
let compare a b =
|
||||||
|
Cstruct.compare (Sign.to_cstruct a) (Sign.to_cstruct b)
|
||||||
|
end)
|
||||||
|
|
||||||
|
include Helpers.MakeRaw(struct
|
||||||
|
type nonrec t = t
|
||||||
|
let name = name
|
||||||
|
let of_bytes_opt = of_bytes_opt
|
||||||
|
let of_string_opt = of_string_opt
|
||||||
|
let to_string = to_string
|
||||||
|
end)
|
||||||
|
|
||||||
|
include Helpers.MakeEncoder(struct
|
||||||
|
type nonrec t = t
|
||||||
|
let name = name
|
||||||
|
let title = title
|
||||||
|
let raw_encoding =
|
||||||
|
let open Data_encoding in
|
||||||
|
conv to_bytes of_bytes_exn (Fixed.bytes size)
|
||||||
|
let of_b58check = of_b58check
|
||||||
|
let of_b58check_opt = of_b58check_opt
|
||||||
|
let of_b58check_exn = of_b58check_exn
|
||||||
|
let to_b58check = to_b58check
|
||||||
|
let to_short_b58check = to_short_b58check
|
||||||
|
end)
|
||||||
|
|
||||||
|
let pp ppf t = Format.fprintf ppf "%s" (to_b58check t)
|
||||||
|
|
||||||
end
|
end
|
||||||
|
|
||||||
|
type t = MBytes.t
|
||||||
|
|
||||||
|
let name = "Ed25519"
|
||||||
|
let title = "An Ed25519 signature"
|
||||||
|
|
||||||
|
let size = Sign.bytes
|
||||||
|
|
||||||
|
let of_bytes_opt s =
|
||||||
|
if MBytes.length s = size then Some s else None
|
||||||
|
let to_bytes x = x
|
||||||
|
|
||||||
|
let to_string s = MBytes.to_string (to_bytes s)
|
||||||
|
let of_string_opt s = of_bytes_opt (MBytes.of_string s)
|
||||||
|
|
||||||
|
type Base58.data +=
|
||||||
|
| Data of t
|
||||||
|
|
||||||
|
let b58check_encoding =
|
||||||
|
Base58.register_encoding
|
||||||
|
~prefix: Base58.Prefix.ed25519_signature
|
||||||
|
~length: size
|
||||||
|
~to_raw: MBytes.to_string
|
||||||
|
~of_raw: (fun s -> Some (MBytes.of_string s))
|
||||||
|
~wrap: (fun x -> Data x)
|
||||||
|
|
||||||
|
let () =
|
||||||
|
Base58.check_encoded_prefix b58check_encoding "edsig" 99
|
||||||
|
|
||||||
|
include Compare.Make(struct
|
||||||
|
type nonrec t = t
|
||||||
|
let compare = MBytes.compare
|
||||||
|
end)
|
||||||
|
|
||||||
|
include Helpers.MakeRaw(struct
|
||||||
|
type nonrec t = t
|
||||||
|
let name = name
|
||||||
|
let of_bytes_opt = of_bytes_opt
|
||||||
|
let of_string_opt = of_string_opt
|
||||||
|
let to_string = to_string
|
||||||
|
end)
|
||||||
|
|
||||||
|
include Helpers.MakeB58(struct
|
||||||
|
type nonrec t = t
|
||||||
|
let title = title
|
||||||
|
let name = name
|
||||||
|
let b58check_encoding = b58check_encoding
|
||||||
|
end)
|
||||||
|
|
||||||
|
include Helpers.MakeEncoder(struct
|
||||||
|
type nonrec t = t
|
||||||
|
let name = name
|
||||||
|
let title = title
|
||||||
|
let raw_encoding =
|
||||||
|
let open Data_encoding in
|
||||||
|
conv to_bytes of_bytes_exn (Fixed.bytes size)
|
||||||
|
let of_b58check = of_b58check
|
||||||
|
let of_b58check_opt = of_b58check_opt
|
||||||
|
let of_b58check_exn = of_b58check_exn
|
||||||
|
let to_b58check = to_b58check
|
||||||
|
let to_short_b58check = to_short_b58check
|
||||||
|
end)
|
||||||
|
|
||||||
|
let pp ppf t = Format.fprintf ppf "%s" (to_b58check t)
|
||||||
|
|
||||||
|
let zero = MBytes.init size '\000'
|
||||||
|
|
||||||
let sign key msg =
|
let sign key msg =
|
||||||
Cstruct.(to_bigarray (Sign.detached ~key (of_bigarray msg)))
|
Cstruct.(to_bigarray (Sign.detached ~key (of_bigarray msg)))
|
||||||
|
|
||||||
module Signature = struct
|
let check public_key signature msg =
|
||||||
|
Sign.verify_detached ~key:public_key
|
||||||
|
~signature:(Cstruct.of_bigarray signature)
|
||||||
|
(Cstruct.of_bigarray msg)
|
||||||
|
|
||||||
type t = MBytes.t
|
let append key msg =
|
||||||
|
MBytes.concat msg (sign key msg)
|
||||||
|
|
||||||
type Base58.data +=
|
let concat msg signature =
|
||||||
| Signature of t
|
MBytes.concat msg signature
|
||||||
|
|
||||||
let b58check_encoding =
|
|
||||||
Base58.register_encoding
|
|
||||||
~prefix: Base58.Prefix.ed25519_signature
|
|
||||||
~length:Sign.bytes
|
|
||||||
~to_raw:MBytes.to_string
|
|
||||||
~of_raw:(fun s -> Some (MBytes.of_string s))
|
|
||||||
~wrap:(fun x -> Signature x)
|
|
||||||
|
|
||||||
let of_b58check_opt s = Base58.simple_decode b58check_encoding s
|
|
||||||
let of_b58check_exn s =
|
|
||||||
match Base58.simple_decode b58check_encoding s with
|
|
||||||
| Some x -> x
|
|
||||||
| None -> Pervasives.failwith
|
|
||||||
(Printf.sprintf "%s is not an ed25519 signature" s)
|
|
||||||
let to_b58check s = Base58.simple_encode b58check_encoding s
|
|
||||||
let pp ppf t = Format.fprintf ppf "%s" (to_b58check t)
|
|
||||||
|
|
||||||
let of_bytes_opt s =
|
|
||||||
if MBytes.length s = Sign.bytes then Some s else None
|
|
||||||
|
|
||||||
let of_bytes_exn s =
|
|
||||||
match of_bytes_opt s with
|
|
||||||
| None ->
|
|
||||||
Pervasives.invalid_arg "Ed25519.Signature.of_bytes_exn: argument is not a serialized signature"
|
|
||||||
| Some signature -> signature
|
|
||||||
|
|
||||||
let to_bytes x = x
|
|
||||||
let size = Sign.bytes
|
|
||||||
let zero = MBytes.init size '\000'
|
|
||||||
|
|
||||||
let () =
|
|
||||||
Base58.check_encoded_prefix b58check_encoding "edsig" 99
|
|
||||||
|
|
||||||
let check public_key signature msg =
|
|
||||||
Sign.verify_detached ~key:public_key
|
|
||||||
~signature:(Cstruct.of_bigarray signature)
|
|
||||||
(Cstruct.of_bigarray msg)
|
|
||||||
|
|
||||||
let append key msg =
|
|
||||||
MBytes.concat msg (sign key msg)
|
|
||||||
|
|
||||||
let concat msg signature =
|
|
||||||
MBytes.concat msg signature
|
|
||||||
|
|
||||||
let encoding =
|
|
||||||
let open Data_encoding in
|
|
||||||
splitted
|
|
||||||
~json:
|
|
||||||
(describe
|
|
||||||
~title: "An Ed25519 signature (Base58Check encoded)" @@
|
|
||||||
conv
|
|
||||||
(fun s -> to_b58check s)
|
|
||||||
(fun s ->
|
|
||||||
match of_b58check_opt s with
|
|
||||||
| Some x -> x
|
|
||||||
| None -> Data_encoding.Json.cannot_destruct
|
|
||||||
"Ed25519 signature: unexpected prefix.")
|
|
||||||
string)
|
|
||||||
~binary:
|
|
||||||
(conv
|
|
||||||
to_bytes
|
|
||||||
of_bytes_exn
|
|
||||||
(Fixed.bytes size))
|
|
||||||
let of_b58check s =
|
|
||||||
match of_b58check_opt s with
|
|
||||||
| Some x -> Ok x
|
|
||||||
| None ->
|
|
||||||
Error_monad.generic_error
|
|
||||||
"Failed to read a base58-encoded Ed25519 signature"
|
|
||||||
let param
|
|
||||||
?(name="ed25519-signature")
|
|
||||||
?(desc="Ed25519 signature (b58check-encoded)") t =
|
|
||||||
Clic.(param ~name ~desc
|
|
||||||
(parameter (fun _ str -> Lwt.return (of_b58check str))) t)
|
|
||||||
end
|
|
||||||
|
|
||||||
module Seed = struct
|
module Seed = struct
|
||||||
|
|
||||||
@ -298,12 +282,19 @@ module Seed = struct
|
|||||||
|
|
||||||
let generate () = Rand.gen 32
|
let generate () = Rand.gen 32
|
||||||
let extract = Sign.seed
|
let extract = Sign.seed
|
||||||
end
|
|
||||||
|
|
||||||
let generate_key () =
|
end
|
||||||
let pk, sk = Sign.keypair () in
|
|
||||||
(Public_key.hash pk, pk, sk)
|
|
||||||
|
|
||||||
let generate_seeded_key seed =
|
let generate_seeded_key seed =
|
||||||
let pk, sk = Sign.keypair ~seed () in
|
let pk, sk = Sign.keypair ~seed () in
|
||||||
(Public_key.hash pk, pk, sk)
|
(Public_key.hash pk, pk, sk)
|
||||||
|
|
||||||
|
let generate_key () =
|
||||||
|
let seed = Seed.generate () in
|
||||||
|
generate_seeded_key seed
|
||||||
|
|
||||||
|
include Compare.Make(struct
|
||||||
|
type nonrec t = t
|
||||||
|
let compare = MBytes.compare
|
||||||
|
end)
|
||||||
|
|
||||||
|
@ -9,114 +9,9 @@
|
|||||||
|
|
||||||
(** Tezos - Ed25519 cryptography *)
|
(** Tezos - Ed25519 cryptography *)
|
||||||
|
|
||||||
open Error_monad
|
include S.SIGNATURE
|
||||||
|
|
||||||
(** {2 Hashed public keys for user ID} ***************************************)
|
include S.RAW_DATA with type t := t
|
||||||
|
|
||||||
module Public_key_hash : S.HASH
|
|
||||||
|
|
||||||
(** {2 Signature} ************************************************************)
|
|
||||||
|
|
||||||
module Public_key : sig
|
|
||||||
|
|
||||||
include Compare.S
|
|
||||||
val pp : Format.formatter -> t -> unit
|
|
||||||
|
|
||||||
val hash: t -> Public_key_hash.t
|
|
||||||
|
|
||||||
type Base58.data +=
|
|
||||||
| Public_key of t
|
|
||||||
|
|
||||||
val of_b58check_exn: string -> t
|
|
||||||
val of_b58check_opt: string -> t option
|
|
||||||
val of_b58check: string -> t tzresult
|
|
||||||
val to_b58check: t -> string
|
|
||||||
|
|
||||||
val to_hex: t -> Hex.t
|
|
||||||
val of_hex: Hex.t -> t option
|
|
||||||
val of_hex_exn: Hex.t -> t
|
|
||||||
|
|
||||||
val of_bytes_exn: MBytes.t -> t
|
|
||||||
val of_bytes_opt: MBytes.t -> t option
|
|
||||||
val to_bytes: t -> MBytes.t
|
|
||||||
|
|
||||||
val size: int
|
|
||||||
|
|
||||||
val encoding: t Data_encoding.t
|
|
||||||
val param:
|
|
||||||
?name:string ->
|
|
||||||
?desc:string ->
|
|
||||||
('a, 'b) Clic.params ->
|
|
||||||
(t -> 'a, 'b) Clic.params
|
|
||||||
|
|
||||||
end
|
|
||||||
|
|
||||||
module Secret_key : sig
|
|
||||||
|
|
||||||
type t
|
|
||||||
val pp : Format.formatter -> t -> unit
|
|
||||||
|
|
||||||
val to_public_key: t -> Public_key.t
|
|
||||||
|
|
||||||
type Base58.data +=
|
|
||||||
| Secret_key of t
|
|
||||||
|
|
||||||
val of_b58check_exn: string -> t
|
|
||||||
val of_b58check_opt: string -> t option
|
|
||||||
val of_b58check: string -> t tzresult
|
|
||||||
val to_b58check: t -> string
|
|
||||||
|
|
||||||
val of_bytes_exn: MBytes.t -> t
|
|
||||||
val of_bytes_opt: MBytes.t -> t option
|
|
||||||
val to_bytes: t -> MBytes.t
|
|
||||||
|
|
||||||
val size: int
|
|
||||||
|
|
||||||
val encoding: t Data_encoding.t
|
|
||||||
val param:
|
|
||||||
?name:string ->
|
|
||||||
?desc:string ->
|
|
||||||
('a, 'b) Clic.params ->
|
|
||||||
(t -> 'a, 'b) Clic.params
|
|
||||||
|
|
||||||
end
|
|
||||||
|
|
||||||
module Signature : sig
|
|
||||||
|
|
||||||
type t
|
|
||||||
val pp : Format.formatter -> t -> unit
|
|
||||||
|
|
||||||
type Base58.data +=
|
|
||||||
| Signature of t
|
|
||||||
|
|
||||||
val of_b58check_exn: string -> t
|
|
||||||
val of_b58check_opt: string -> t option
|
|
||||||
val of_b58check: string -> t tzresult
|
|
||||||
val to_b58check: t -> string
|
|
||||||
|
|
||||||
val of_bytes_exn: MBytes.t -> t
|
|
||||||
val of_bytes_opt: MBytes.t -> t option
|
|
||||||
val to_bytes: t -> MBytes.t
|
|
||||||
|
|
||||||
val encoding: t Data_encoding.t
|
|
||||||
val param:
|
|
||||||
?name:string ->
|
|
||||||
?desc:string ->
|
|
||||||
('a, 'b) Clic.params ->
|
|
||||||
(t -> 'a, 'b) Clic.params
|
|
||||||
|
|
||||||
val size: int
|
|
||||||
|
|
||||||
val zero: t
|
|
||||||
|
|
||||||
(** Check a signature *)
|
|
||||||
val check: Public_key.t -> t -> MBytes.t -> bool
|
|
||||||
|
|
||||||
(** Append a signature *)
|
|
||||||
val append: Secret_key.t -> MBytes.t -> MBytes.t
|
|
||||||
val concat: MBytes.t -> t -> MBytes.t
|
|
||||||
|
|
||||||
end
|
|
||||||
|
|
||||||
module Seed : sig
|
module Seed : sig
|
||||||
type t
|
type t
|
||||||
@ -124,8 +19,4 @@ module Seed : sig
|
|||||||
val extract : Secret_key.t -> t
|
val extract : Secret_key.t -> t
|
||||||
end
|
end
|
||||||
|
|
||||||
val sign: Secret_key.t -> MBytes.t -> Signature.t
|
|
||||||
|
|
||||||
val generate_key: unit -> (Public_key_hash.t * Public_key.t * Secret_key.t)
|
|
||||||
val generate_seeded_key: Seed.t -> (Public_key_hash.t * Public_key.t * Secret_key.t)
|
val generate_seeded_key: Seed.t -> (Public_key_hash.t * Public_key.t * Secret_key.t)
|
||||||
|
|
||||||
|
@ -1,115 +0,0 @@
|
|||||||
(**************************************************************************)
|
|
||||||
(* *)
|
|
||||||
(* Copyright (c) 2014 - 2018. *)
|
|
||||||
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
|
|
||||||
(* *)
|
|
||||||
(* All rights reserved. No warranty, explicit or implicit, provided. *)
|
|
||||||
(* *)
|
|
||||||
(**************************************************************************)
|
|
||||||
|
|
||||||
module Make(H : sig
|
|
||||||
type t
|
|
||||||
val title: string
|
|
||||||
val name: string
|
|
||||||
val b58check_encoding: t Base58.encoding
|
|
||||||
val raw_encoding: t Data_encoding.t
|
|
||||||
val compare: t -> t -> int
|
|
||||||
val equal: t -> t -> bool
|
|
||||||
val hash: t -> int
|
|
||||||
end) = struct
|
|
||||||
|
|
||||||
let of_b58check_opt s =
|
|
||||||
Base58.simple_decode H.b58check_encoding s
|
|
||||||
let of_b58check_exn s =
|
|
||||||
match Base58.simple_decode H.b58check_encoding s with
|
|
||||||
| Some x -> x
|
|
||||||
| None -> Format.kasprintf Pervasives.failwith "Unexpected hash (%s)" H.name
|
|
||||||
let of_b58check s =
|
|
||||||
match of_b58check_opt s with
|
|
||||||
| Some x -> Ok x
|
|
||||||
| None ->
|
|
||||||
Error_monad.generic_error "Failed to read a base58-encoded hash (%s)" H.name
|
|
||||||
let to_b58check s = Base58.simple_encode H.b58check_encoding s
|
|
||||||
let to_short_b58check s =
|
|
||||||
String.sub
|
|
||||||
(to_b58check s) 0
|
|
||||||
(10 + String.length (Base58.prefix H.b58check_encoding))
|
|
||||||
|
|
||||||
let pp ppf t =
|
|
||||||
Format.pp_print_string ppf (to_b58check t)
|
|
||||||
|
|
||||||
let pp_short ppf t =
|
|
||||||
Format.pp_print_string ppf (to_short_b58check t)
|
|
||||||
|
|
||||||
let encoding =
|
|
||||||
let open Data_encoding in
|
|
||||||
splitted
|
|
||||||
~binary:
|
|
||||||
H.raw_encoding
|
|
||||||
~json:
|
|
||||||
(describe ~title: (H.title ^ " (Base58Check-encoded Blake2B hash)") @@
|
|
||||||
conv to_b58check (Data_encoding.Json.wrap_error of_b58check_exn) string)
|
|
||||||
|
|
||||||
let rpc_arg =
|
|
||||||
RPC_arg.make
|
|
||||||
~name:(Format.asprintf "hash.%s" H.name)
|
|
||||||
~descr:(Format.asprintf "A b58check-encoded hash (%s)" H.name)
|
|
||||||
~destruct:
|
|
||||||
(fun s ->
|
|
||||||
match of_b58check_opt s with
|
|
||||||
| None ->
|
|
||||||
Error (Format.asprintf
|
|
||||||
"failed to decode b58check-encoded hash (%s): %S"
|
|
||||||
H.name s)
|
|
||||||
| Some v -> Ok v)
|
|
||||||
~construct:to_b58check
|
|
||||||
()
|
|
||||||
|
|
||||||
let param ?(name=H.name) ?(desc=H.title) t =
|
|
||||||
Clic.param
|
|
||||||
~name
|
|
||||||
~desc (Clic.parameter (fun _ str -> Lwt.return (of_b58check str))) t
|
|
||||||
|
|
||||||
module Set = struct
|
|
||||||
include Set.Make(struct type t = H.t let compare = H.compare end)
|
|
||||||
exception Found of elt
|
|
||||||
let random_elt s =
|
|
||||||
let n = Random.int (cardinal s) in
|
|
||||||
try
|
|
||||||
ignore
|
|
||||||
(fold (fun x i -> if i = n then raise (Found x) ; i+1) s 0 : int) ;
|
|
||||||
assert false
|
|
||||||
with Found x -> x
|
|
||||||
let encoding =
|
|
||||||
Data_encoding.conv
|
|
||||||
elements
|
|
||||||
(fun l -> List.fold_left (fun m x -> add x m) empty l)
|
|
||||||
Data_encoding.(list encoding)
|
|
||||||
end
|
|
||||||
|
|
||||||
module Table = struct
|
|
||||||
include Hashtbl.Make(struct
|
|
||||||
type t = H.t
|
|
||||||
let hash = H.hash
|
|
||||||
let equal = H.equal
|
|
||||||
end)
|
|
||||||
let encoding arg_encoding =
|
|
||||||
Data_encoding.conv
|
|
||||||
(fun h -> fold (fun k v l -> (k, v) :: l) h [])
|
|
||||||
(fun l ->
|
|
||||||
let h = create (List.length l) in
|
|
||||||
List.iter (fun (k,v) -> add h k v) l ;
|
|
||||||
h)
|
|
||||||
Data_encoding.(list (tup2 encoding arg_encoding))
|
|
||||||
end
|
|
||||||
|
|
||||||
module Map = struct
|
|
||||||
include Map.Make(struct type t = H.t let compare = H.compare end)
|
|
||||||
let encoding arg_encoding =
|
|
||||||
Data_encoding.conv
|
|
||||||
bindings
|
|
||||||
(fun l -> List.fold_left (fun m (k,v) -> add k v m) empty l)
|
|
||||||
Data_encoding.(list (tup2 encoding arg_encoding))
|
|
||||||
end
|
|
||||||
|
|
||||||
end
|
|
210
src/lib_crypto/helpers.ml
Normal file
210
src/lib_crypto/helpers.ml
Normal file
@ -0,0 +1,210 @@
|
|||||||
|
(**************************************************************************)
|
||||||
|
(* *)
|
||||||
|
(* Copyright (c) 2014 - 2018. *)
|
||||||
|
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
|
||||||
|
(* *)
|
||||||
|
(* All rights reserved. No warranty, explicit or implicit, provided. *)
|
||||||
|
(* *)
|
||||||
|
(**************************************************************************)
|
||||||
|
|
||||||
|
open Error_monad
|
||||||
|
|
||||||
|
module MakeRaw(H : sig
|
||||||
|
type t
|
||||||
|
val name: string
|
||||||
|
val of_bytes_opt: MBytes.t -> t option
|
||||||
|
val to_string: t -> string
|
||||||
|
val of_string_opt: string -> t option
|
||||||
|
end) = struct
|
||||||
|
|
||||||
|
let of_bytes_exn s =
|
||||||
|
match H.of_bytes_opt s with
|
||||||
|
| None ->
|
||||||
|
Format.kasprintf invalid_arg "of_bytes_exn (%s)" H.name
|
||||||
|
| Some pk -> pk
|
||||||
|
let of_bytes s =
|
||||||
|
match H.of_bytes_opt s with
|
||||||
|
| None -> generic_error "of_bytes (%s)" H.name
|
||||||
|
| Some pk -> Ok pk
|
||||||
|
|
||||||
|
let of_string_exn s =
|
||||||
|
match H.of_string_opt s with
|
||||||
|
| None ->
|
||||||
|
Format.kasprintf invalid_arg "of_string_exn (%s)" H.name
|
||||||
|
| Some pk -> pk
|
||||||
|
let of_string s =
|
||||||
|
match H.of_string_opt s with
|
||||||
|
| None -> generic_error "of_string (%s)" H.name
|
||||||
|
| Some pk -> Ok pk
|
||||||
|
|
||||||
|
let to_hex s = Hex.of_string (H.to_string s)
|
||||||
|
let of_hex_opt s = H.of_string_opt (Hex.to_string s)
|
||||||
|
let of_hex_exn s =
|
||||||
|
match H.of_string_opt (Hex.to_string s) with
|
||||||
|
| Some x -> x
|
||||||
|
| None ->
|
||||||
|
Format.kasprintf invalid_arg "of_hex_exn (%s)" H.name
|
||||||
|
let of_hex s =
|
||||||
|
match of_hex_opt s with
|
||||||
|
| None -> generic_error "of_hex (%s)" H.name
|
||||||
|
| Some pk -> ok pk
|
||||||
|
end
|
||||||
|
|
||||||
|
module MakeB58(H : sig
|
||||||
|
type t
|
||||||
|
val title: string
|
||||||
|
val name: string
|
||||||
|
val b58check_encoding: t Base58.encoding
|
||||||
|
end) = struct
|
||||||
|
|
||||||
|
let of_b58check_opt s =
|
||||||
|
Base58.simple_decode H.b58check_encoding s
|
||||||
|
let of_b58check_exn s =
|
||||||
|
match of_b58check_opt s with
|
||||||
|
| Some x -> x
|
||||||
|
| None -> Format.kasprintf Pervasives.failwith "Unexpected data (%s)" H.name
|
||||||
|
let of_b58check s =
|
||||||
|
match of_b58check_opt s with
|
||||||
|
| Some x -> Ok x
|
||||||
|
| None ->
|
||||||
|
generic_error
|
||||||
|
"Failed to read a b58check_encoding data (%s): %S"
|
||||||
|
H.name s
|
||||||
|
|
||||||
|
let to_b58check s = Base58.simple_encode H.b58check_encoding s
|
||||||
|
let to_short_b58check s =
|
||||||
|
String.sub
|
||||||
|
(to_b58check s) 0
|
||||||
|
(10 + String.length (Base58.prefix H.b58check_encoding))
|
||||||
|
|
||||||
|
end
|
||||||
|
|
||||||
|
module MakeEncoder(H : sig
|
||||||
|
type t
|
||||||
|
val title: string
|
||||||
|
val name: string
|
||||||
|
val to_b58check: t -> string
|
||||||
|
val to_short_b58check: t -> string
|
||||||
|
val of_b58check: string -> t tzresult
|
||||||
|
val of_b58check_exn: string -> t
|
||||||
|
val of_b58check_opt: string -> t option
|
||||||
|
val raw_encoding: t Data_encoding.t
|
||||||
|
end) = struct
|
||||||
|
|
||||||
|
let pp ppf t =
|
||||||
|
Format.pp_print_string ppf (H.to_b58check t)
|
||||||
|
|
||||||
|
let pp_short ppf t =
|
||||||
|
Format.pp_print_string ppf (H.to_short_b58check t)
|
||||||
|
|
||||||
|
let encoding =
|
||||||
|
let open Data_encoding in
|
||||||
|
splitted
|
||||||
|
~binary:
|
||||||
|
H.raw_encoding
|
||||||
|
~json:
|
||||||
|
(describe ~title: (H.title ^ " (Base58Check-encoded)") @@
|
||||||
|
conv
|
||||||
|
H.to_b58check
|
||||||
|
(Data_encoding.Json.wrap_error H.of_b58check_exn)
|
||||||
|
string)
|
||||||
|
|
||||||
|
let rpc_arg =
|
||||||
|
RPC_arg.make
|
||||||
|
~name: H.name
|
||||||
|
~descr: (Format.asprintf "%s (Base58Check-encoded)" H.name)
|
||||||
|
~destruct:
|
||||||
|
(fun s ->
|
||||||
|
match H.of_b58check_opt s with
|
||||||
|
| None ->
|
||||||
|
Error (Format.asprintf
|
||||||
|
"failed to decode Base58Check-encoded data (%s): %S"
|
||||||
|
H.name s)
|
||||||
|
| Some v -> Ok v)
|
||||||
|
~construct: H.to_b58check
|
||||||
|
()
|
||||||
|
|
||||||
|
let param ?(name=H.name) ?(desc=H.title) t =
|
||||||
|
Clic.param ~name ~desc
|
||||||
|
(Clic.parameter (fun _ str -> Lwt.return (H.of_b58check str))) t
|
||||||
|
|
||||||
|
end
|
||||||
|
|
||||||
|
module MakeIterator(H : sig
|
||||||
|
type t
|
||||||
|
val encoding: t Data_encoding.t
|
||||||
|
val compare: t -> t -> int
|
||||||
|
val equal: t -> t -> bool
|
||||||
|
val hash: t -> int
|
||||||
|
end) = struct
|
||||||
|
|
||||||
|
module Set = struct
|
||||||
|
include Set.Make(struct type t = H.t let compare = H.compare end)
|
||||||
|
exception Found of elt
|
||||||
|
let random_elt s =
|
||||||
|
let n = Random.int (cardinal s) in
|
||||||
|
try
|
||||||
|
ignore
|
||||||
|
(fold (fun x i -> if i = n then raise (Found x) ; i+1) s 0 : int) ;
|
||||||
|
assert false
|
||||||
|
with Found x -> x
|
||||||
|
let encoding =
|
||||||
|
Data_encoding.conv
|
||||||
|
elements
|
||||||
|
(fun l -> List.fold_left (fun m x -> add x m) empty l)
|
||||||
|
Data_encoding.(list H.encoding)
|
||||||
|
end
|
||||||
|
|
||||||
|
module Table = struct
|
||||||
|
include Hashtbl.Make(struct
|
||||||
|
type t = H.t
|
||||||
|
let hash = H.hash
|
||||||
|
let equal = H.equal
|
||||||
|
end)
|
||||||
|
let encoding arg_encoding =
|
||||||
|
Data_encoding.conv
|
||||||
|
(fun h -> fold (fun k v l -> (k, v) :: l) h [])
|
||||||
|
(fun l ->
|
||||||
|
let h = create (List.length l) in
|
||||||
|
List.iter (fun (k,v) -> add h k v) l ;
|
||||||
|
h)
|
||||||
|
Data_encoding.(list (tup2 H.encoding arg_encoding))
|
||||||
|
end
|
||||||
|
|
||||||
|
module Map = struct
|
||||||
|
include Map.Make(struct type t = H.t let compare = H.compare end)
|
||||||
|
let encoding arg_encoding =
|
||||||
|
Data_encoding.conv
|
||||||
|
bindings
|
||||||
|
(fun l -> List.fold_left (fun m (k,v) -> add k v m) empty l)
|
||||||
|
Data_encoding.(list (tup2 H.encoding arg_encoding))
|
||||||
|
end
|
||||||
|
|
||||||
|
end
|
||||||
|
|
||||||
|
module Make(H : sig
|
||||||
|
type t
|
||||||
|
val title: string
|
||||||
|
val name: string
|
||||||
|
val b58check_encoding: t Base58.encoding
|
||||||
|
val raw_encoding: t Data_encoding.t
|
||||||
|
val compare: t -> t -> int
|
||||||
|
val equal: t -> t -> bool
|
||||||
|
val hash: t -> int
|
||||||
|
end) = struct
|
||||||
|
|
||||||
|
include MakeB58(H)
|
||||||
|
include MakeEncoder(struct
|
||||||
|
include H
|
||||||
|
let to_b58check = to_b58check
|
||||||
|
let to_short_b58check = to_short_b58check
|
||||||
|
let of_b58check = of_b58check
|
||||||
|
let of_b58check_opt = of_b58check_opt
|
||||||
|
let of_b58check_exn = of_b58check_exn
|
||||||
|
end)
|
||||||
|
include MakeIterator(struct
|
||||||
|
include H
|
||||||
|
let encoding = encoding
|
||||||
|
end)
|
||||||
|
|
||||||
|
end
|
@ -24,43 +24,45 @@ module type MINIMAL_HASH = sig
|
|||||||
val name: string
|
val name: string
|
||||||
val title: string
|
val title: string
|
||||||
|
|
||||||
|
val pp: Format.formatter -> t -> unit
|
||||||
|
val pp_short: Format.formatter -> t -> unit
|
||||||
|
|
||||||
|
include Compare.S with type t := t
|
||||||
|
|
||||||
val hash_bytes: ?key:Cstruct.buffer -> Cstruct.buffer list -> t
|
val hash_bytes: ?key:Cstruct.buffer -> Cstruct.buffer list -> t
|
||||||
val hash_string: ?key:string -> string list -> t
|
val hash_string: ?key: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 -> Cstruct.buffer
|
|
||||||
val of_bytes_opt: Cstruct.buffer -> t option
|
|
||||||
val of_bytes_exn: Cstruct.buffer -> t
|
|
||||||
|
|
||||||
val read: Cstruct.buffer -> int -> t
|
|
||||||
val write: Cstruct.buffer -> 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
|
|
||||||
|
|
||||||
val zero: t
|
val zero: t
|
||||||
|
|
||||||
end
|
end
|
||||||
|
|
||||||
module type HASH = sig
|
module type RAW_DATA = sig
|
||||||
|
|
||||||
include MINIMAL_HASH
|
type t
|
||||||
|
|
||||||
|
val size: int (* in bytes *)
|
||||||
|
val to_hex: t -> Hex.t
|
||||||
|
val of_hex: Hex.t -> t tzresult
|
||||||
|
val of_hex_opt: Hex.t -> t option
|
||||||
|
val of_hex_exn: Hex.t -> t
|
||||||
|
|
||||||
|
val to_string: t -> string
|
||||||
|
val of_string: string -> t tzresult
|
||||||
|
val of_string_opt: string -> t option
|
||||||
|
val of_string_exn: string -> t
|
||||||
|
|
||||||
|
val to_bytes: t -> MBytes.t
|
||||||
|
|
||||||
|
val of_bytes: MBytes.t -> t tzresult
|
||||||
|
val of_bytes_opt: MBytes.t -> t option
|
||||||
|
val of_bytes_exn: MBytes.t -> t
|
||||||
|
|
||||||
|
end
|
||||||
|
|
||||||
|
module type B58_DATA = sig
|
||||||
|
|
||||||
|
type t
|
||||||
|
|
||||||
val of_bytes: Cstruct.buffer -> t tzresult
|
|
||||||
val to_b58check: t -> string
|
val to_b58check: t -> string
|
||||||
val to_short_b58check: t -> string
|
val to_short_b58check: t -> string
|
||||||
|
|
||||||
@ -68,13 +70,17 @@ module type HASH = sig
|
|||||||
val of_b58check_exn: string -> t
|
val of_b58check_exn: string -> t
|
||||||
val of_b58check_opt: string -> t option
|
val of_b58check_opt: string -> t option
|
||||||
|
|
||||||
type Base58.data += Hash of t
|
type Base58.data += Data of t
|
||||||
val b58check_encoding: t Base58.encoding
|
val b58check_encoding: t Base58.encoding
|
||||||
|
|
||||||
val pp: Format.formatter -> t -> unit
|
end
|
||||||
val pp_short: Format.formatter -> t -> unit
|
|
||||||
|
module type ENCODER = sig
|
||||||
|
|
||||||
|
type t
|
||||||
|
|
||||||
val encoding: t Data_encoding.t
|
val encoding: t Data_encoding.t
|
||||||
|
|
||||||
val rpc_arg: t RPC_arg.t
|
val rpc_arg: t RPC_arg.t
|
||||||
|
|
||||||
val param:
|
val param:
|
||||||
@ -83,6 +89,19 @@ module type HASH = sig
|
|||||||
('a, 'arg) Clic.params ->
|
('a, 'arg) Clic.params ->
|
||||||
(t -> 'a, 'arg) Clic.params
|
(t -> 'a, 'arg) Clic.params
|
||||||
|
|
||||||
|
end
|
||||||
|
|
||||||
|
module type INDEXES = sig
|
||||||
|
|
||||||
|
type t
|
||||||
|
|
||||||
|
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
|
||||||
|
|
||||||
module Set : sig
|
module Set : sig
|
||||||
include Set.S with type elt = t
|
include Set.S with type elt = t
|
||||||
val random_elt: t -> elt
|
val random_elt: t -> elt
|
||||||
@ -101,10 +120,18 @@ module type HASH = sig
|
|||||||
|
|
||||||
end
|
end
|
||||||
|
|
||||||
|
module type HASH = sig
|
||||||
|
include MINIMAL_HASH
|
||||||
|
include RAW_DATA with type t := t
|
||||||
|
include B58_DATA with type t := t
|
||||||
|
include ENCODER with type t := t
|
||||||
|
include INDEXES with type t := t
|
||||||
|
end
|
||||||
|
|
||||||
module type MERKLE_TREE = sig
|
module type MERKLE_TREE = sig
|
||||||
|
|
||||||
type elt
|
type elt
|
||||||
val elt_bytes: elt -> Cstruct.buffer
|
val elt_bytes: elt -> MBytes.t
|
||||||
|
|
||||||
include HASH
|
include HASH
|
||||||
|
|
||||||
@ -122,3 +149,72 @@ module type MERKLE_TREE = sig
|
|||||||
val check_path: path -> elt -> t * int
|
val check_path: path -> elt -> t * int
|
||||||
|
|
||||||
end
|
end
|
||||||
|
|
||||||
|
module type SIGNATURE = sig
|
||||||
|
|
||||||
|
module Public_key_hash : sig
|
||||||
|
|
||||||
|
type t
|
||||||
|
|
||||||
|
val hash_bytes: ?key:MBytes.t -> MBytes.t list -> t
|
||||||
|
val hash_string: ?key:string -> string list -> t
|
||||||
|
|
||||||
|
val pp: Format.formatter -> t -> unit
|
||||||
|
val pp_short: Format.formatter -> t -> unit
|
||||||
|
include Compare.S with type t := t
|
||||||
|
include RAW_DATA with type t := t
|
||||||
|
include B58_DATA with type t := t
|
||||||
|
include ENCODER with type t := t
|
||||||
|
include INDEXES with type t := t
|
||||||
|
|
||||||
|
end
|
||||||
|
|
||||||
|
module Public_key : sig
|
||||||
|
|
||||||
|
type t
|
||||||
|
|
||||||
|
val pp: Format.formatter -> t -> unit
|
||||||
|
include Compare.S with type t := t
|
||||||
|
include RAW_DATA with type t := t
|
||||||
|
include B58_DATA with type t := t
|
||||||
|
include ENCODER with type t := t
|
||||||
|
|
||||||
|
val hash: t -> Public_key_hash.t
|
||||||
|
|
||||||
|
end
|
||||||
|
|
||||||
|
module Secret_key : sig
|
||||||
|
|
||||||
|
type t
|
||||||
|
|
||||||
|
val pp: Format.formatter -> t -> unit
|
||||||
|
include Compare.S with type t := t
|
||||||
|
include RAW_DATA with type t := t
|
||||||
|
include B58_DATA with type t := t
|
||||||
|
include ENCODER with type t := t
|
||||||
|
|
||||||
|
val to_public_key: t -> Public_key.t
|
||||||
|
|
||||||
|
end
|
||||||
|
|
||||||
|
type t
|
||||||
|
|
||||||
|
val pp: Format.formatter -> t -> unit
|
||||||
|
include Compare.S with type t := t
|
||||||
|
include B58_DATA with type t := t
|
||||||
|
include ENCODER with type t := t
|
||||||
|
|
||||||
|
val zero: t
|
||||||
|
|
||||||
|
(** Check a signature *)
|
||||||
|
val check: Public_key.t -> t -> MBytes.t -> bool
|
||||||
|
|
||||||
|
(** Append a signature *)
|
||||||
|
val append: Secret_key.t -> MBytes.t -> MBytes.t
|
||||||
|
val concat: MBytes.t -> t -> MBytes.t
|
||||||
|
|
||||||
|
val sign: Secret_key.t -> MBytes.t -> t
|
||||||
|
|
||||||
|
val generate_key: unit -> (Public_key_hash.t * Public_key.t * Secret_key.t)
|
||||||
|
|
||||||
|
end
|
||||||
|
@ -9,81 +9,4 @@
|
|||||||
|
|
||||||
(** Tezos - Ed25519 cryptography *)
|
(** Tezos - Ed25519 cryptography *)
|
||||||
|
|
||||||
(** {2 Hashed public keys for user ID} ***************************************)
|
include S.SIGNATURE
|
||||||
|
|
||||||
module Public_key_hash : S.HASH
|
|
||||||
|
|
||||||
|
|
||||||
(** {2 Signature} ************************************************************)
|
|
||||||
|
|
||||||
module Public_key : sig
|
|
||||||
|
|
||||||
include Compare.S
|
|
||||||
val encoding: t Data_encoding.t
|
|
||||||
|
|
||||||
val hash: t -> Public_key_hash.t
|
|
||||||
|
|
||||||
type Base58.data +=
|
|
||||||
| Public_key of t
|
|
||||||
|
|
||||||
val of_b58check_exn: string -> t
|
|
||||||
val of_b58check_opt: string -> t option
|
|
||||||
val to_b58check: t -> string
|
|
||||||
|
|
||||||
val of_bytes_exn: MBytes.t -> t
|
|
||||||
val of_bytes_opt: MBytes.t -> t option
|
|
||||||
val to_bytes: t -> MBytes.t
|
|
||||||
|
|
||||||
val to_hex: t -> [ `Hex of string ]
|
|
||||||
val of_hex: [ `Hex of string ] -> t option
|
|
||||||
val of_hex_exn: [ `Hex of string ] -> t
|
|
||||||
|
|
||||||
end
|
|
||||||
|
|
||||||
module Secret_key : sig
|
|
||||||
|
|
||||||
type t
|
|
||||||
val encoding: t Data_encoding.t
|
|
||||||
|
|
||||||
type Base58.data +=
|
|
||||||
| Secret_key of t
|
|
||||||
|
|
||||||
val of_b58check_exn: string -> t
|
|
||||||
val of_b58check_opt: string -> t option
|
|
||||||
val to_b58check: t -> string
|
|
||||||
|
|
||||||
val of_bytes_exn: MBytes.t -> t
|
|
||||||
val of_bytes_opt: MBytes.t -> t option
|
|
||||||
val to_bytes: t -> MBytes.t
|
|
||||||
|
|
||||||
end
|
|
||||||
|
|
||||||
module Signature : sig
|
|
||||||
|
|
||||||
type t
|
|
||||||
val encoding: t Data_encoding.t
|
|
||||||
|
|
||||||
type Base58.data +=
|
|
||||||
| Signature of t
|
|
||||||
|
|
||||||
val of_b58check_exn: string -> t
|
|
||||||
val of_b58check_opt: string -> t option
|
|
||||||
val to_b58check: t -> string
|
|
||||||
|
|
||||||
val of_bytes_exn: MBytes.t -> t
|
|
||||||
val of_bytes_opt: MBytes.t -> t option
|
|
||||||
val to_bytes: t -> MBytes.t
|
|
||||||
|
|
||||||
(** Checks a signature *)
|
|
||||||
val check: Public_key.t -> t -> MBytes.t -> bool
|
|
||||||
|
|
||||||
(** Append a signature *)
|
|
||||||
val append: Secret_key.t -> MBytes.t -> MBytes.t
|
|
||||||
|
|
||||||
val zero: t
|
|
||||||
|
|
||||||
end
|
|
||||||
|
|
||||||
val sign: Secret_key.t -> MBytes.t -> Signature.t
|
|
||||||
|
|
||||||
val generate_key: unit -> (Public_key_hash.t * Public_key.t * Secret_key.t)
|
|
||||||
|
@ -49,38 +49,47 @@ module type MINIMAL_HASH = sig
|
|||||||
val name: string
|
val name: string
|
||||||
val title: string
|
val title: string
|
||||||
|
|
||||||
|
val pp: Format.formatter -> t -> unit
|
||||||
|
val pp_short: Format.formatter -> t -> unit
|
||||||
|
|
||||||
|
include Compare.S with type t := t
|
||||||
|
|
||||||
val hash_bytes: ?key:MBytes.t -> MBytes.t list -> t
|
val hash_bytes: ?key:MBytes.t -> MBytes.t list -> t
|
||||||
val hash_string: ?key:string -> string list -> t
|
val hash_string: ?key: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_opt: 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
|
|
||||||
|
|
||||||
val zero: t
|
val zero: t
|
||||||
|
|
||||||
end
|
end
|
||||||
|
|
||||||
|
module type RAW_DATA = sig
|
||||||
|
type t
|
||||||
|
val size: int (* in bytes *)
|
||||||
|
val to_bytes: t -> MBytes.t
|
||||||
|
val of_bytes_opt: MBytes.t -> t option
|
||||||
|
val of_bytes_exn: MBytes.t -> t
|
||||||
|
end
|
||||||
|
|
||||||
|
module type B58_DATA = sig
|
||||||
|
|
||||||
|
type t
|
||||||
|
|
||||||
|
val to_b58check: t -> string
|
||||||
|
val to_short_b58check: t -> string
|
||||||
|
|
||||||
|
val of_b58check_exn: string -> t
|
||||||
|
val of_b58check_opt: string -> t option
|
||||||
|
|
||||||
|
type Base58.data += Data of t
|
||||||
|
val b58check_encoding: t Base58.encoding
|
||||||
|
|
||||||
|
end
|
||||||
|
|
||||||
|
module type ENCODER = sig
|
||||||
|
type t
|
||||||
|
val encoding: t Data_encoding.t
|
||||||
|
val rpc_arg: t RPC_arg.t
|
||||||
|
end
|
||||||
|
|
||||||
module type SET = sig
|
module type SET = sig
|
||||||
type elt
|
type elt
|
||||||
type t
|
type t
|
||||||
@ -149,37 +158,37 @@ module type MAP = sig
|
|||||||
val mapi: (key -> 'a -> 'b) -> 'a t -> 'b t
|
val mapi: (key -> 'a -> 'b) -> 'a t -> 'b t
|
||||||
end
|
end
|
||||||
|
|
||||||
module type HASH = sig
|
module type INDEXES = sig
|
||||||
|
|
||||||
include MINIMAL_HASH
|
type t
|
||||||
|
|
||||||
val encoding: t Data_encoding.t
|
val to_path: t -> string list -> string list
|
||||||
|
val of_path: string list -> t option
|
||||||
|
val of_path_exn: string list -> t
|
||||||
|
|
||||||
val to_b58check: t -> string
|
val prefix_path: string -> string list
|
||||||
val to_short_b58check: t -> string
|
val path_length: int
|
||||||
type Base58.data += Hash of t
|
|
||||||
val b58check_encoding: t Base58.encoding
|
|
||||||
|
|
||||||
val of_b58check_exn: string -> t
|
|
||||||
val of_b58check_opt: string -> t option
|
|
||||||
|
|
||||||
val pp: Format.formatter -> t -> unit
|
|
||||||
val pp_short: Format.formatter -> t -> unit
|
|
||||||
|
|
||||||
val rpc_arg: t RPC_arg.t
|
|
||||||
|
|
||||||
module Set : sig
|
module Set : sig
|
||||||
include SET with type elt = t
|
include Set.S with type elt = t
|
||||||
val encoding: t Data_encoding.t
|
val encoding: t Data_encoding.t
|
||||||
end
|
end
|
||||||
|
|
||||||
module Map : sig
|
module Map : sig
|
||||||
include MAP with type key = t
|
include Map.S with type key = t
|
||||||
val encoding: 'a Data_encoding.t -> 'a t Data_encoding.t
|
val encoding: 'a Data_encoding.t -> 'a t Data_encoding.t
|
||||||
end
|
end
|
||||||
|
|
||||||
end
|
end
|
||||||
|
|
||||||
|
module type HASH = sig
|
||||||
|
include MINIMAL_HASH
|
||||||
|
include RAW_DATA with type t := t
|
||||||
|
include B58_DATA with type t := t
|
||||||
|
include ENCODER with type t := t
|
||||||
|
include INDEXES with type t := t
|
||||||
|
end
|
||||||
|
|
||||||
module type MERKLE_TREE = sig
|
module type MERKLE_TREE = sig
|
||||||
type elt
|
type elt
|
||||||
include HASH
|
include HASH
|
||||||
@ -193,3 +202,53 @@ 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
|
||||||
|
|
||||||
|
module type SIGNATURE = sig
|
||||||
|
|
||||||
|
module Public_key_hash : sig
|
||||||
|
|
||||||
|
type t
|
||||||
|
|
||||||
|
val hash_bytes: ?key:MBytes.t -> MBytes.t list -> t
|
||||||
|
val hash_string: ?key:string -> string list -> t
|
||||||
|
|
||||||
|
val pp: Format.formatter -> t -> unit
|
||||||
|
val pp_short: Format.formatter -> t -> unit
|
||||||
|
include Compare.S with type t := t
|
||||||
|
include RAW_DATA with type t := t
|
||||||
|
include B58_DATA with type t := t
|
||||||
|
include ENCODER with type t := t
|
||||||
|
include INDEXES with type t := t
|
||||||
|
|
||||||
|
end
|
||||||
|
|
||||||
|
module Public_key : sig
|
||||||
|
|
||||||
|
type t
|
||||||
|
|
||||||
|
val pp: Format.formatter -> t -> unit
|
||||||
|
include Compare.S with type t := t
|
||||||
|
include B58_DATA with type t := t
|
||||||
|
include ENCODER with type t := t
|
||||||
|
|
||||||
|
val hash: t -> Public_key_hash.t
|
||||||
|
|
||||||
|
end
|
||||||
|
|
||||||
|
type t
|
||||||
|
|
||||||
|
val pp: Format.formatter -> t -> unit
|
||||||
|
include RAW_DATA with type t := t
|
||||||
|
include Compare.S with type t := t
|
||||||
|
include B58_DATA with type t := t
|
||||||
|
include ENCODER with type t := t
|
||||||
|
|
||||||
|
val zero: t
|
||||||
|
|
||||||
|
(** Check a signature *)
|
||||||
|
val check: Public_key.t -> t -> MBytes.t -> bool
|
||||||
|
|
||||||
|
val concat: MBytes.t -> t -> MBytes.t
|
||||||
|
|
||||||
|
end
|
||||||
|
|
||||||
|
@ -127,8 +127,7 @@ module Make (Context : CONTEXT) = struct
|
|||||||
and type 'a RPC_directory.t = 'a RPC_directory.t
|
and type 'a RPC_directory.t = 'a RPC_directory.t
|
||||||
and type Ed25519.Public_key_hash.t = Ed25519.Public_key_hash.t
|
and type Ed25519.Public_key_hash.t = Ed25519.Public_key_hash.t
|
||||||
and type Ed25519.Public_key.t = Ed25519.Public_key.t
|
and type Ed25519.Public_key.t = Ed25519.Public_key.t
|
||||||
and type Ed25519.Secret_key.t = Ed25519.Secret_key.t
|
and type Ed25519.t = Ed25519.t
|
||||||
and type Ed25519.Signature.t = Ed25519.Signature.t
|
|
||||||
and type 'a Micheline.canonical = 'a Micheline.canonical
|
and type 'a Micheline.canonical = 'a Micheline.canonical
|
||||||
and type ('a, 'b) RPC_path.t = ('a, 'b) RPC_path.t
|
and type ('a, 'b) RPC_path.t = ('a, 'b) RPC_path.t
|
||||||
and type ('a, 'b) Micheline.node = ('a, 'b) Micheline.node
|
and type ('a, 'b) Micheline.node = ('a, 'b) Micheline.node
|
||||||
@ -191,33 +190,38 @@ module Make (Context : CONTEXT) = struct
|
|||||||
module S = struct
|
module S = struct
|
||||||
module type T = Tezos_base.S.T
|
module type T = Tezos_base.S.T
|
||||||
module type HASHABLE = Tezos_base.S.HASHABLE
|
module type HASHABLE = Tezos_base.S.HASHABLE
|
||||||
module type MINIMAL_HASH = sig
|
module type MINIMAL_HASH = S.MINIMAL_HASH
|
||||||
|
module type B58_DATA = sig
|
||||||
|
|
||||||
type t
|
type t
|
||||||
|
|
||||||
val name: string
|
val to_b58check: t -> string
|
||||||
val title: string
|
val to_short_b58check: t -> string
|
||||||
|
|
||||||
val hash_bytes: ?key:MBytes.t -> MBytes.t list -> t
|
val of_b58check_exn: string -> t
|
||||||
val hash_string: ?key:string -> string list -> t
|
val of_b58check_opt: string -> t option
|
||||||
|
|
||||||
|
type Base58.data += Data of t
|
||||||
|
val b58check_encoding: t Base58.encoding
|
||||||
|
|
||||||
|
end
|
||||||
|
module type RAW_DATA = sig
|
||||||
|
type t
|
||||||
val size: int (* in bytes *)
|
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 to_bytes: t -> MBytes.t
|
||||||
val of_bytes_opt: MBytes.t -> t option
|
val of_bytes_opt: MBytes.t -> t option
|
||||||
val of_bytes_exn: MBytes.t -> t
|
val of_bytes_exn: MBytes.t -> t
|
||||||
|
end
|
||||||
|
module type ENCODER = sig
|
||||||
|
type t
|
||||||
|
val encoding: t Data_encoding.t
|
||||||
|
val rpc_arg: t RPC_arg.t
|
||||||
|
end
|
||||||
|
module type SET = Tezos_base.S.SET
|
||||||
|
module type MAP = Tezos_base.S.MAP
|
||||||
|
module type INDEXES = sig
|
||||||
|
|
||||||
val read: MBytes.t -> int -> t
|
type t
|
||||||
val write: MBytes.t -> int -> t -> unit
|
|
||||||
|
|
||||||
val to_path: t -> string list -> string list
|
val to_path: t -> string list -> string list
|
||||||
val of_path: string list -> t option
|
val of_path: string list -> t option
|
||||||
@ -226,41 +230,24 @@ module Make (Context : CONTEXT) = struct
|
|||||||
val prefix_path: string -> string list
|
val prefix_path: string -> string list
|
||||||
val path_length: int
|
val path_length: int
|
||||||
|
|
||||||
val zero: t
|
|
||||||
|
|
||||||
end
|
|
||||||
module type SET = Tezos_base.S.SET
|
|
||||||
module type MAP = Tezos_base.S.MAP
|
|
||||||
module type HASH = sig
|
|
||||||
|
|
||||||
include MINIMAL_HASH
|
|
||||||
|
|
||||||
val encoding: t Data_encoding.t
|
|
||||||
|
|
||||||
val to_b58check: t -> string
|
|
||||||
val to_short_b58check: t -> string
|
|
||||||
type Base58.data += Hash of t
|
|
||||||
val b58check_encoding: t Base58.encoding
|
|
||||||
|
|
||||||
val of_b58check_exn: string -> t
|
|
||||||
val of_b58check_opt: string -> t option
|
|
||||||
|
|
||||||
val pp: Format.formatter -> t -> unit
|
|
||||||
val pp_short: Format.formatter -> t -> unit
|
|
||||||
|
|
||||||
val rpc_arg: t RPC_arg.t
|
|
||||||
|
|
||||||
module Set : sig
|
module Set : sig
|
||||||
include SET with type elt = t
|
include Set.S with type elt = t
|
||||||
val encoding: t Data_encoding.t
|
val encoding: t Data_encoding.t
|
||||||
end
|
end
|
||||||
|
|
||||||
module Map : sig
|
module Map : sig
|
||||||
include MAP with type key = t
|
include Map.S with type key = t
|
||||||
val encoding: 'a Data_encoding.t -> 'a t Data_encoding.t
|
val encoding: 'a Data_encoding.t -> 'a t Data_encoding.t
|
||||||
end
|
end
|
||||||
|
|
||||||
end
|
end
|
||||||
|
module type HASH = sig
|
||||||
|
include MINIMAL_HASH
|
||||||
|
include RAW_DATA with type t := t
|
||||||
|
include B58_DATA with type t := t
|
||||||
|
include ENCODER with type t := t
|
||||||
|
include INDEXES with type t := t
|
||||||
|
end
|
||||||
|
|
||||||
module type MERKLE_TREE = sig
|
module type MERKLE_TREE = sig
|
||||||
type elt
|
type elt
|
||||||
@ -275,6 +262,56 @@ module Make (Context : CONTEXT) = struct
|
|||||||
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
|
||||||
|
|
||||||
|
module type SIGNATURE = sig
|
||||||
|
|
||||||
|
module Public_key_hash : sig
|
||||||
|
|
||||||
|
type t
|
||||||
|
|
||||||
|
val hash_bytes: ?key:MBytes.t -> MBytes.t list -> t
|
||||||
|
val hash_string: ?key:string -> string list -> t
|
||||||
|
|
||||||
|
val pp: Format.formatter -> t -> unit
|
||||||
|
val pp_short: Format.formatter -> t -> unit
|
||||||
|
include Compare.S with type t := t
|
||||||
|
include RAW_DATA with type t := t
|
||||||
|
include B58_DATA with type t := t
|
||||||
|
include ENCODER with type t := t
|
||||||
|
include INDEXES with type t := t
|
||||||
|
|
||||||
|
end
|
||||||
|
|
||||||
|
module Public_key : sig
|
||||||
|
|
||||||
|
type t
|
||||||
|
|
||||||
|
val pp: Format.formatter -> t -> unit
|
||||||
|
include Compare.S with type t := t
|
||||||
|
include B58_DATA with type t := t
|
||||||
|
include ENCODER with type t := t
|
||||||
|
|
||||||
|
val hash: t -> Public_key_hash.t
|
||||||
|
|
||||||
|
end
|
||||||
|
|
||||||
|
type t
|
||||||
|
|
||||||
|
val pp: Format.formatter -> t -> unit
|
||||||
|
include RAW_DATA with type t := t
|
||||||
|
include Compare.S with type t := t
|
||||||
|
include B58_DATA with type t := t
|
||||||
|
include ENCODER with type t := t
|
||||||
|
|
||||||
|
val zero: t
|
||||||
|
|
||||||
|
(** Check a signature *)
|
||||||
|
val check: Public_key.t -> t -> MBytes.t -> bool
|
||||||
|
|
||||||
|
val concat: MBytes.t -> t -> MBytes.t
|
||||||
|
|
||||||
|
end
|
||||||
|
|
||||||
end
|
end
|
||||||
module Error_monad = struct
|
module Error_monad = struct
|
||||||
type 'a shell_tzresult = 'a Error_monad.tzresult
|
type 'a shell_tzresult = 'a Error_monad.tzresult
|
||||||
|
@ -120,8 +120,7 @@ module Make (Context : CONTEXT) : sig
|
|||||||
and type 'a RPC_directory.t = 'a RPC_directory.t
|
and type 'a RPC_directory.t = 'a RPC_directory.t
|
||||||
and type Ed25519.Public_key_hash.t = Ed25519.Public_key_hash.t
|
and type Ed25519.Public_key_hash.t = Ed25519.Public_key_hash.t
|
||||||
and type Ed25519.Public_key.t = Ed25519.Public_key.t
|
and type Ed25519.Public_key.t = Ed25519.Public_key.t
|
||||||
and type Ed25519.Secret_key.t = Ed25519.Secret_key.t
|
and type Ed25519.t = Ed25519.t
|
||||||
and type Ed25519.Signature.t = Ed25519.Signature.t
|
|
||||||
and type 'a Micheline.canonical = 'a Micheline.canonical
|
and type 'a Micheline.canonical = 'a Micheline.canonical
|
||||||
and type ('a, 'b) Micheline.node = ('a, 'b) Micheline.node
|
and type ('a, 'b) Micheline.node = ('a, 'b) Micheline.node
|
||||||
and type Data_encoding.json_schema = Data_encoding.json_schema
|
and type Data_encoding.json_schema = Data_encoding.json_schema
|
||||||
|
@ -26,7 +26,7 @@ let equal_operation ?msg op1 op2 =
|
|||||||
| _ -> false in
|
| _ -> false in
|
||||||
let prn = function
|
let prn = function
|
||||||
| None -> "none"
|
| None -> "none"
|
||||||
| Some op -> Operation_hash.to_hex (Operation.hash op) in
|
| Some op -> Operation_hash.to_b58check (Operation.hash op) in
|
||||||
equal ?msg ~prn ~eq op1 op2
|
equal ?msg ~prn ~eq op1 op2
|
||||||
|
|
||||||
let equal_block ?msg st1 st2 =
|
let equal_block ?msg st1 st2 =
|
||||||
@ -37,7 +37,7 @@ let equal_block ?msg st1 st2 =
|
|||||||
| _ -> false in
|
| _ -> false in
|
||||||
let prn = function
|
let prn = function
|
||||||
| None -> "none"
|
| None -> "none"
|
||||||
| Some st -> Block_hash.to_hex (Block_header.hash st) in
|
| Some st -> Block_hash.to_b58check (Block_header.hash st) in
|
||||||
equal ?msg ~prn ~eq st1 st2
|
equal ?msg ~prn ~eq st1 st2
|
||||||
|
|
||||||
let make_equal_list eq prn ?(msg="") x y =
|
let make_equal_list eq prn ?(msg="") x y =
|
||||||
|
@ -111,12 +111,14 @@ let check_block s h b =
|
|||||||
Store.Block.Contents.read (s, h) >>= function
|
Store.Block.Contents.read (s, h) >>= function
|
||||||
| Ok b' when equal b b' -> Lwt.return_unit
|
| Ok b' when equal b b' -> Lwt.return_unit
|
||||||
| Ok _ ->
|
| Ok _ ->
|
||||||
Printf.eprintf "Error while reading block %s\n%!" (Block_hash.to_hex h);
|
Format.eprintf
|
||||||
|
"Error while reading block %a\n%!"
|
||||||
|
Block_hash.pp_short h ;
|
||||||
exit 1
|
exit 1
|
||||||
| Error err ->
|
| Error err ->
|
||||||
Format.eprintf "@[Error while reading block %s:@ %a\n@]"
|
Format.eprintf "@[Error while reading block %a:@ %a\n@]"
|
||||||
(Block_hash.to_hex h)
|
Block_hash.pp_short h
|
||||||
pp_print_error err;
|
pp_print_error err ;
|
||||||
exit 1
|
exit 1
|
||||||
|
|
||||||
let test_block s =
|
let test_block s =
|
||||||
|
@ -34,7 +34,7 @@ let commit = commit ~time:Time.epoch ~message:""
|
|||||||
|
|
||||||
let block2 =
|
let block2 =
|
||||||
Block_hash.of_hex_exn
|
Block_hash.of_hex_exn
|
||||||
"2222222222222222222222222222222222222222222222222222222222222222"
|
(`Hex "2222222222222222222222222222222222222222222222222222222222222222")
|
||||||
|
|
||||||
let create_block2 idx genesis_commit =
|
let create_block2 idx genesis_commit =
|
||||||
checkout idx genesis_commit >>= function
|
checkout idx genesis_commit >>= function
|
||||||
@ -48,7 +48,7 @@ let create_block2 idx genesis_commit =
|
|||||||
|
|
||||||
let block3a =
|
let block3a =
|
||||||
Block_hash.of_hex_exn
|
Block_hash.of_hex_exn
|
||||||
"3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a"
|
(`Hex "3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a3a")
|
||||||
|
|
||||||
let create_block3a idx block2_commit =
|
let create_block3a idx block2_commit =
|
||||||
checkout idx block2_commit >>= function
|
checkout idx block2_commit >>= function
|
||||||
@ -61,11 +61,11 @@ let create_block3a idx block2_commit =
|
|||||||
|
|
||||||
let block3b =
|
let block3b =
|
||||||
Block_hash.of_hex_exn
|
Block_hash.of_hex_exn
|
||||||
"3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b"
|
(`Hex "3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b3b")
|
||||||
|
|
||||||
let block3c =
|
let block3c =
|
||||||
Block_hash.of_hex_exn
|
Block_hash.of_hex_exn
|
||||||
"3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c"
|
(`Hex "3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c3c")
|
||||||
|
|
||||||
let create_block3b idx block2_commit =
|
let create_block3b idx block2_commit =
|
||||||
checkout idx block2_commit >>= function
|
checkout idx block2_commit >>= function
|
||||||
|
@ -82,7 +82,7 @@ module Account = struct
|
|||||||
|
|
||||||
type t = {
|
type t = {
|
||||||
alias : string ;
|
alias : string ;
|
||||||
sk : secret_key ;
|
sk : Ed25519.Secret_key.t ;
|
||||||
pk : public_key ;
|
pk : public_key ;
|
||||||
pkh : public_key_hash ;
|
pkh : public_key_hash ;
|
||||||
contract : Contract.t ;
|
contract : Contract.t ;
|
||||||
@ -258,7 +258,7 @@ module Protocol = struct
|
|||||||
~period:next_level.voting_period
|
~period:next_level.voting_period
|
||||||
~proposals
|
~proposals
|
||||||
() >>=? fun bytes ->
|
() >>=? fun bytes ->
|
||||||
let signed_bytes = Ed25519.Signature.append sk bytes in
|
let signed_bytes = Ed25519.append sk bytes in
|
||||||
return (Tezos_base.Operation.of_bytes_exn signed_bytes)
|
return (Tezos_base.Operation.of_bytes_exn signed_bytes)
|
||||||
|
|
||||||
let ballot ?(block = `Head 0) ~src:({ pkh; sk } : Account.t) ~proposal ballot =
|
let ballot ?(block = `Head 0) ~src:({ pkh; sk } : Account.t) ~proposal ballot =
|
||||||
@ -271,7 +271,7 @@ module Protocol = struct
|
|||||||
~proposal
|
~proposal
|
||||||
~ballot
|
~ballot
|
||||||
() >>=? fun bytes ->
|
() >>=? fun bytes ->
|
||||||
let signed_bytes = Ed25519.Signature.append sk bytes in
|
let signed_bytes = Ed25519.append sk bytes in
|
||||||
return (Tezos_base.Operation.of_bytes_exn signed_bytes)
|
return (Tezos_base.Operation.of_bytes_exn signed_bytes)
|
||||||
|
|
||||||
end
|
end
|
||||||
@ -300,7 +300,7 @@ module Assert = struct
|
|||||||
| _ -> false in
|
| _ -> false in
|
||||||
let prn = function
|
let prn = function
|
||||||
| None -> "none"
|
| None -> "none"
|
||||||
| Some pkh -> Ed25519.Public_key_hash.to_hex pkh in
|
| Some pkh -> Ed25519.Public_key_hash.to_b58check pkh in
|
||||||
equal ?msg ~prn ~eq pkh1 pkh2
|
equal ?msg ~prn ~eq pkh1 pkh2
|
||||||
|
|
||||||
let equal_tez ?msg tz1 tz2 =
|
let equal_tez ?msg tz1 tz2 =
|
||||||
@ -472,7 +472,7 @@ module Endorse = struct
|
|||||||
~level:level.level
|
~level:level.level
|
||||||
~slots:[slot]
|
~slots:[slot]
|
||||||
() >>=? fun bytes ->
|
() >>=? fun bytes ->
|
||||||
let signed_bytes = Ed25519.Signature.append src_sk bytes in
|
let signed_bytes = Ed25519.append src_sk bytes in
|
||||||
return (Tezos_base.Operation.of_bytes_exn signed_bytes)
|
return (Tezos_base.Operation.of_bytes_exn signed_bytes)
|
||||||
|
|
||||||
let signing_slots
|
let signing_slots
|
||||||
|
@ -37,7 +37,7 @@ module Account : sig
|
|||||||
|
|
||||||
val encoding : t Data_encoding.t
|
val encoding : t Data_encoding.t
|
||||||
val pp_account : Format.formatter -> t -> unit
|
val pp_account : Format.formatter -> t -> unit
|
||||||
val create : ?keys:(secret_key * public_key) -> string -> t
|
val create : ?keys:(Ed25519.Secret_key.t * public_key) -> string -> t
|
||||||
(** [create ?keys alias] is an account with alias [alias]. If
|
(** [create ?keys alias] is an account with alias [alias]. If
|
||||||
[?keys] is [None], a pair of keys will be minted. *)
|
[?keys] is [None], a pair of keys will be minted. *)
|
||||||
|
|
||||||
|
@ -55,8 +55,7 @@ let transfer cctxt
|
|||||||
~destination ?parameters ~fee () >>=? fun bytes ->
|
~destination ?parameters ~fee () >>=? fun bytes ->
|
||||||
Block_services.predecessor cctxt block >>=? fun predecessor ->
|
Block_services.predecessor cctxt block >>=? fun predecessor ->
|
||||||
Client_keys.sign cctxt src_sk bytes >>=? fun signature ->
|
Client_keys.sign cctxt src_sk bytes >>=? fun signature ->
|
||||||
let signed_bytes =
|
let signed_bytes = Ed25519.concat bytes signature in
|
||||||
MBytes.concat bytes (Ed25519.Signature.to_bytes signature) in
|
|
||||||
let oph = Operation_hash.hash_bytes [ signed_bytes ] in
|
let oph = Operation_hash.hash_bytes [ signed_bytes ] in
|
||||||
Alpha_services.Helpers.apply_operation cctxt block
|
Alpha_services.Helpers.apply_operation cctxt block
|
||||||
predecessor oph bytes (Some signature) >>=? fun contracts ->
|
predecessor oph bytes (Some signature) >>=? fun contracts ->
|
||||||
@ -74,8 +73,7 @@ let reveal cctxt
|
|||||||
cctxt block
|
cctxt block
|
||||||
~branch ~source ~sourcePubKey:src_pk ~counter ~fee () >>=? fun bytes ->
|
~branch ~source ~sourcePubKey:src_pk ~counter ~fee () >>=? fun bytes ->
|
||||||
Client_keys.sign cctxt src_sk bytes >>=? fun signature ->
|
Client_keys.sign cctxt src_sk bytes >>=? fun signature ->
|
||||||
let signed_bytes =
|
let signed_bytes = Ed25519.concat bytes signature in
|
||||||
MBytes.concat bytes (Ed25519.Signature.to_bytes signature) in
|
|
||||||
let oph = Operation_hash.hash_bytes [ signed_bytes ] in
|
let oph = Operation_hash.hash_bytes [ signed_bytes ] in
|
||||||
Shell_services.inject_operation
|
Shell_services.inject_operation
|
||||||
cctxt ~chain_id signed_bytes >>=? fun injected_oph ->
|
cctxt ~chain_id signed_bytes >>=? fun injected_oph ->
|
||||||
@ -86,7 +84,7 @@ let originate rpc_config ?chain_id ~block ?signature bytes =
|
|||||||
let signed_bytes =
|
let signed_bytes =
|
||||||
match signature with
|
match signature with
|
||||||
| None -> bytes
|
| None -> bytes
|
||||||
| Some signature -> Ed25519.Signature.concat bytes signature in
|
| Some signature -> Ed25519.concat bytes signature in
|
||||||
Block_services.predecessor rpc_config block >>=? fun predecessor ->
|
Block_services.predecessor rpc_config block >>=? fun predecessor ->
|
||||||
let oph = Operation_hash.hash_bytes [ signed_bytes ] in
|
let oph = Operation_hash.hash_bytes [ signed_bytes ] in
|
||||||
Alpha_services.Helpers.apply_operation rpc_config block
|
Alpha_services.Helpers.apply_operation rpc_config block
|
||||||
@ -137,7 +135,7 @@ let delegate_contract cctxt
|
|||||||
~branch ~source ?sourcePubKey:src_pk ~counter ~fee delegate_opt
|
~branch ~source ?sourcePubKey:src_pk ~counter ~fee delegate_opt
|
||||||
>>=? fun bytes ->
|
>>=? fun bytes ->
|
||||||
Client_keys.sign cctxt manager_sk bytes >>=? fun signature ->
|
Client_keys.sign cctxt manager_sk bytes >>=? fun signature ->
|
||||||
let signed_bytes = Ed25519.Signature.concat bytes signature in
|
let signed_bytes = Ed25519.concat bytes signature in
|
||||||
let oph = Operation_hash.hash_bytes [ signed_bytes ] in
|
let oph = Operation_hash.hash_bytes [ signed_bytes ] in
|
||||||
Shell_services.inject_operation
|
Shell_services.inject_operation
|
||||||
cctxt ~chain_id signed_bytes >>=? fun injected_oph ->
|
cctxt ~chain_id signed_bytes >>=? fun injected_oph ->
|
||||||
@ -185,7 +183,7 @@ let dictate rpc_config block command seckey =
|
|||||||
Alpha_services.Forge.Dictator.operation
|
Alpha_services.Forge.Dictator.operation
|
||||||
rpc_config block ~branch command >>=? fun bytes ->
|
rpc_config block ~branch command >>=? fun bytes ->
|
||||||
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.concat bytes signature in
|
||||||
let oph = Operation_hash.hash_bytes [ signed_bytes ] in
|
let oph = Operation_hash.hash_bytes [ signed_bytes ] in
|
||||||
Shell_services.inject_operation
|
Shell_services.inject_operation
|
||||||
rpc_config ~chain_id signed_bytes >>=? fun injected_oph ->
|
rpc_config ~chain_id signed_bytes >>=? fun injected_oph ->
|
||||||
|
@ -132,5 +132,5 @@ val dictate :
|
|||||||
#Proto_alpha.rpc_context ->
|
#Proto_alpha.rpc_context ->
|
||||||
Block_services.block ->
|
Block_services.block ->
|
||||||
dictator_operation ->
|
dictator_operation ->
|
||||||
secret_key ->
|
Ed25519.Secret_key.t ->
|
||||||
Operation_hash.t tzresult Lwt.t
|
Operation_hash.t tzresult Lwt.t
|
||||||
|
@ -109,11 +109,8 @@ let trace
|
|||||||
let hash_and_sign (data : Michelson_v1_parser.parsed) (typ : Michelson_v1_parser.parsed) sk block cctxt =
|
let hash_and_sign (data : Michelson_v1_parser.parsed) (typ : Michelson_v1_parser.parsed) sk block cctxt =
|
||||||
Alpha_services.Helpers.hash_data cctxt block (data.expanded, typ.expanded) >>=? fun hash ->
|
Alpha_services.Helpers.hash_data cctxt block (data.expanded, typ.expanded) >>=? fun hash ->
|
||||||
Client_keys.sign cctxt sk (MBytes.of_string hash) >>=? fun signature ->
|
Client_keys.sign cctxt sk (MBytes.of_string hash) >>=? fun signature ->
|
||||||
return (hash,
|
let `Hex signature = Ed25519.to_hex signature in
|
||||||
signature |>
|
return (hash, signature)
|
||||||
Data_encoding.Binary.to_bytes Ed25519.Signature.encoding |>
|
|
||||||
MBytes.to_hex |>
|
|
||||||
(fun (`Hex s) -> s))
|
|
||||||
|
|
||||||
let typecheck_data
|
let typecheck_data
|
||||||
~(data : Michelson_v1_parser.parsed)
|
~(data : Michelson_v1_parser.parsed)
|
||||||
|
@ -51,8 +51,7 @@ module Script = struct
|
|||||||
end
|
end
|
||||||
type public_key = Ed25519.Public_key.t
|
type public_key = Ed25519.Public_key.t
|
||||||
type public_key_hash = Ed25519.Public_key_hash.t
|
type public_key_hash = Ed25519.Public_key_hash.t
|
||||||
type secret_key = Ed25519.Secret_key.t
|
type signature = Ed25519.t
|
||||||
type signature = Ed25519.Signature.t
|
|
||||||
|
|
||||||
module Constants = struct
|
module Constants = struct
|
||||||
include Constants_repr
|
include Constants_repr
|
||||||
|
@ -19,8 +19,7 @@ type context = t
|
|||||||
|
|
||||||
type public_key = Ed25519.Public_key.t
|
type public_key = Ed25519.Public_key.t
|
||||||
type public_key_hash = Ed25519.Public_key_hash.t
|
type public_key_hash = Ed25519.Public_key_hash.t
|
||||||
type secret_key = Ed25519.Secret_key.t
|
type signature = Ed25519.t
|
||||||
type signature = Ed25519.Signature.t
|
|
||||||
|
|
||||||
module Tez : sig
|
module Tez : sig
|
||||||
|
|
||||||
@ -574,7 +573,7 @@ module Block_header : sig
|
|||||||
type t = {
|
type t = {
|
||||||
shell: Block_header.shell_header ;
|
shell: Block_header.shell_header ;
|
||||||
protocol_data: protocol_data ;
|
protocol_data: protocol_data ;
|
||||||
signature: Ed25519.Signature.t ;
|
signature: Ed25519.t ;
|
||||||
}
|
}
|
||||||
|
|
||||||
and protocol_data = {
|
and protocol_data = {
|
||||||
|
@ -247,8 +247,8 @@ let first_endorsement_slots
|
|||||||
select_delegate delegate delegate_list max_priority
|
select_delegate delegate delegate_list max_priority
|
||||||
|
|
||||||
let check_hash hash stamp_threshold =
|
let check_hash hash stamp_threshold =
|
||||||
let bytes = Block_hash.to_string hash in
|
let bytes = Block_hash.to_bytes hash in
|
||||||
let word = String.get_int64 bytes 0 in
|
let word = MBytes.get_int64 bytes 0 in
|
||||||
Compare.Uint64.(word < stamp_threshold)
|
Compare.Uint64.(word < stamp_threshold)
|
||||||
|
|
||||||
let check_header_hash header stamp_threshold =
|
let check_header_hash header stamp_threshold =
|
||||||
@ -265,7 +265,7 @@ let check_proof_of_work_stamp ctxt block =
|
|||||||
let check_signature block key =
|
let check_signature block key =
|
||||||
let check_signature key { Block_header.protocol_data ; shell ; signature } =
|
let check_signature key { Block_header.protocol_data ; shell ; signature } =
|
||||||
let unsigned_header = Block_header.forge_unsigned shell protocol_data in
|
let unsigned_header = Block_header.forge_unsigned shell protocol_data in
|
||||||
Ed25519.Signature.check key signature unsigned_header in
|
Ed25519.check key signature unsigned_header in
|
||||||
if check_signature key block then
|
if check_signature key block then
|
||||||
return ()
|
return ()
|
||||||
else
|
else
|
||||||
|
@ -13,7 +13,7 @@
|
|||||||
type t = {
|
type t = {
|
||||||
shell: Block_header.shell_header ;
|
shell: Block_header.shell_header ;
|
||||||
protocol_data: protocol_data ;
|
protocol_data: protocol_data ;
|
||||||
signature: Ed25519.Signature.t ;
|
signature: Ed25519.t ;
|
||||||
}
|
}
|
||||||
|
|
||||||
and protocol_data = {
|
and protocol_data = {
|
||||||
@ -47,7 +47,7 @@ let signed_protocol_data_encoding =
|
|||||||
let open Data_encoding in
|
let open Data_encoding in
|
||||||
merge_objs
|
merge_objs
|
||||||
protocol_data_encoding
|
protocol_data_encoding
|
||||||
(obj1 (req "signature" Ed25519.Signature.encoding))
|
(obj1 (req "signature" Ed25519.encoding))
|
||||||
|
|
||||||
let unsigned_header_encoding =
|
let unsigned_header_encoding =
|
||||||
let open Data_encoding in
|
let open Data_encoding in
|
||||||
@ -73,8 +73,9 @@ let max_header_length =
|
|||||||
proof_of_work_nonce =
|
proof_of_work_nonce =
|
||||||
MBytes.create Constants_repr.proof_of_work_nonce_size ;
|
MBytes.create Constants_repr.proof_of_work_nonce_size ;
|
||||||
seed_nonce_hash = Some Nonce_hash.zero } in
|
seed_nonce_hash = Some Nonce_hash.zero } in
|
||||||
let signature = Ed25519.Signature.zero in
|
Data_encoding.Binary.length
|
||||||
Data_encoding.Binary.length signed_protocol_data_encoding (fake, signature)
|
signed_protocol_data_encoding
|
||||||
|
(fake, Ed25519.zero)
|
||||||
|
|
||||||
|
|
||||||
(** Header parsing entry point *)
|
(** Header parsing entry point *)
|
||||||
|
@ -11,7 +11,7 @@
|
|||||||
type t = {
|
type t = {
|
||||||
shell: Block_header.shell_header ;
|
shell: Block_header.shell_header ;
|
||||||
protocol_data: protocol_data ;
|
protocol_data: protocol_data ;
|
||||||
signature: Ed25519.Signature.t ;
|
signature: Ed25519.t ;
|
||||||
}
|
}
|
||||||
|
|
||||||
and protocol_data = {
|
and protocol_data = {
|
||||||
|
@ -33,8 +33,8 @@ let to_b58check = function
|
|||||||
|
|
||||||
let of_b58check s =
|
let of_b58check s =
|
||||||
match Base58.decode s with
|
match Base58.decode s with
|
||||||
| Some (Ed25519.Public_key_hash.Hash h) -> ok (Implicit h)
|
| Some (Ed25519.Public_key_hash.Data h) -> ok (Implicit h)
|
||||||
| Some (Contract_hash.Hash h) -> ok (Originated h)
|
| Some (Contract_hash.Data h) -> ok (Originated h)
|
||||||
| _ -> error (Invalid_contract_notation s)
|
| _ -> error (Invalid_contract_notation s)
|
||||||
|
|
||||||
let pp ppf = function
|
let pp ppf = function
|
||||||
|
@ -51,7 +51,7 @@ module S = struct
|
|||||||
(req "pred_block" Block_hash.encoding)
|
(req "pred_block" Block_hash.encoding)
|
||||||
(req "operation_hash" Operation_hash.encoding)
|
(req "operation_hash" Operation_hash.encoding)
|
||||||
(req "forged_operation" bytes)
|
(req "forged_operation" bytes)
|
||||||
(opt "signature" Ed25519.Signature.encoding))
|
(opt "signature" Ed25519.encoding))
|
||||||
~output: (obj1 (req "contracts" (list Contract.encoding)))
|
~output: (obj1 (req "contracts" (list Contract.encoding)))
|
||||||
RPC_path.(custom_root / "apply_operation")
|
RPC_path.(custom_root / "apply_operation")
|
||||||
|
|
||||||
|
@ -18,7 +18,7 @@ val minimal_time:
|
|||||||
|
|
||||||
val apply_operation:
|
val apply_operation:
|
||||||
'a #RPC_context.simple ->
|
'a #RPC_context.simple ->
|
||||||
'a -> Block_hash.t -> Operation_hash.t -> MBytes.t -> Ed25519.Signature.t option ->
|
'a -> Block_hash.t -> Operation_hash.t -> MBytes.t -> Ed25519.t option ->
|
||||||
(Contract.t list) shell_tzresult Lwt.t
|
(Contract.t list) shell_tzresult Lwt.t
|
||||||
|
|
||||||
val run_code:
|
val run_code:
|
||||||
|
@ -19,7 +19,7 @@ let raw_encoding = Operation.encoding
|
|||||||
type operation = {
|
type operation = {
|
||||||
shell: Operation.shell_header ;
|
shell: Operation.shell_header ;
|
||||||
contents: proto_operation ;
|
contents: proto_operation ;
|
||||||
signature: Ed25519.Signature.t option ;
|
signature: Ed25519.t option ;
|
||||||
}
|
}
|
||||||
|
|
||||||
and proto_operation =
|
and proto_operation =
|
||||||
@ -379,7 +379,7 @@ module Encoding = struct
|
|||||||
let mu_signed_proto_operation_encoding op_encoding =
|
let mu_signed_proto_operation_encoding op_encoding =
|
||||||
merge_objs
|
merge_objs
|
||||||
(mu_proto_operation_encoding op_encoding)
|
(mu_proto_operation_encoding op_encoding)
|
||||||
(obj1 (varopt "signature" Ed25519.Signature.encoding))
|
(obj1 (varopt "signature" Ed25519.encoding))
|
||||||
|
|
||||||
let operation_encoding =
|
let operation_encoding =
|
||||||
mu "operation"
|
mu "operation"
|
||||||
@ -476,7 +476,7 @@ let check_signature key { shell ; contents ; signature } =
|
|||||||
fail Missing_signature
|
fail Missing_signature
|
||||||
| Sourced_operations _, Some signature ->
|
| Sourced_operations _, Some signature ->
|
||||||
let unsigned_operation = forge shell contents in
|
let unsigned_operation = forge shell contents in
|
||||||
if Ed25519.Signature.check key signature unsigned_operation then
|
if Ed25519.check key signature unsigned_operation then
|
||||||
return ()
|
return ()
|
||||||
else
|
else
|
||||||
fail Invalid_signature
|
fail Invalid_signature
|
||||||
|
@ -19,7 +19,7 @@ val raw_encoding: raw Data_encoding.t
|
|||||||
type operation = {
|
type operation = {
|
||||||
shell: Operation.shell_header ;
|
shell: Operation.shell_header ;
|
||||||
contents: proto_operation ;
|
contents: proto_operation ;
|
||||||
signature: Ed25519.Signature.t option ;
|
signature: Ed25519.t option ;
|
||||||
}
|
}
|
||||||
|
|
||||||
and proto_operation =
|
and proto_operation =
|
||||||
@ -112,7 +112,7 @@ val acceptable_passes: operation -> int list
|
|||||||
|
|
||||||
val parse_proto:
|
val parse_proto:
|
||||||
MBytes.t ->
|
MBytes.t ->
|
||||||
(proto_operation * Ed25519.Signature.t option) tzresult Lwt.t
|
(proto_operation * Ed25519.t option) tzresult Lwt.t
|
||||||
|
|
||||||
type error += Missing_signature (* `Permanent *)
|
type error += Missing_signature (* `Permanent *)
|
||||||
type error += Invalid_signature (* `Permanent *)
|
type error += Invalid_signature (* `Permanent *)
|
||||||
|
@ -766,7 +766,7 @@ let rec interp
|
|||||||
let gas = Gas.consume gas Gas.Cost_of.check_signature in
|
let gas = Gas.consume gas Gas.Cost_of.check_signature in
|
||||||
Gas.check gas >>=? fun () ->
|
Gas.check gas >>=? fun () ->
|
||||||
let message = MBytes.of_string message in
|
let message = MBytes.of_string message in
|
||||||
let res = Ed25519.Signature.check key signature message in
|
let res = Ed25519.check key signature message in
|
||||||
logged_return (Item (res, rest), gas, ctxt)
|
logged_return (Item (res, rest), gas, ctxt)
|
||||||
| Hash_key, Item (key, rest) ->
|
| Hash_key, Item (key, rest) ->
|
||||||
logged_return (Item (Ed25519.Public_key.hash key, rest), Gas.consume gas Gas.Cost_of.hash_key, ctxt)
|
logged_return (Item (Ed25519.Public_key.hash key, rest), Gas.consume gas Gas.Cost_of.hash_key, ctxt)
|
||||||
|
@ -576,7 +576,7 @@ let rec unparse_data
|
|||||||
| Signature_t, s ->
|
| Signature_t, s ->
|
||||||
let `Hex text =
|
let `Hex text =
|
||||||
MBytes.to_hex
|
MBytes.to_hex
|
||||||
(Data_encoding.Binary.to_bytes Ed25519.Signature.encoding s) in
|
(Data_encoding.Binary.to_bytes Ed25519.encoding s) in
|
||||||
String (-1, text)
|
String (-1, text)
|
||||||
| Tez_t, v ->
|
| Tez_t, v ->
|
||||||
String (-1, Tez.to_string v)
|
String (-1, Tez.to_string v)
|
||||||
@ -1082,7 +1082,7 @@ let rec parse_data
|
|||||||
(* Signatures *)
|
(* Signatures *)
|
||||||
| Signature_t, String (_, s) -> begin try
|
| Signature_t, String (_, s) -> begin try
|
||||||
match Data_encoding.Binary.of_bytes
|
match Data_encoding.Binary.of_bytes
|
||||||
Ed25519.Signature.encoding
|
Ed25519.encoding
|
||||||
(MBytes.of_hex (`Hex s)) with
|
(MBytes.of_hex (`Hex s)) with
|
||||||
| Some s -> return s
|
| Some s -> return s
|
||||||
| None -> raise Not_found
|
| None -> raise Not_found
|
||||||
|
@ -95,7 +95,7 @@ let equal_pkh ?msg pkh1 pkh2 =
|
|||||||
| _ -> false in
|
| _ -> false in
|
||||||
let prn = function
|
let prn = function
|
||||||
| None -> "none"
|
| None -> "none"
|
||||||
| Some pkh -> Ed25519.Public_key_hash.to_hex pkh in
|
| Some pkh -> Ed25519.Public_key_hash.to_b58check pkh in
|
||||||
Assert.equal ?msg ~prn ~eq pkh1 pkh2
|
Assert.equal ?msg ~prn ~eq pkh1 pkh2
|
||||||
|
|
||||||
let equal_int64 ?msg =
|
let equal_int64 ?msg =
|
||||||
|
@ -104,7 +104,7 @@ let sign src oph protop =
|
|||||||
let signed_proto_operation_encoding =
|
let signed_proto_operation_encoding =
|
||||||
Data_encoding.merge_objs
|
Data_encoding.merge_objs
|
||||||
Operation.proto_operation_encoding
|
Operation.proto_operation_encoding
|
||||||
(obj1 @@ varopt "signature" Ed25519.Signature.encoding) in
|
(obj1 @@ varopt "signature" Ed25519.encoding) in
|
||||||
let proto_bytes =
|
let proto_bytes =
|
||||||
Data_encoding.Binary.to_bytes
|
Data_encoding.Binary.to_bytes
|
||||||
signed_proto_operation_encoding
|
signed_proto_operation_encoding
|
||||||
|
@ -60,7 +60,7 @@ val endorsement_full :
|
|||||||
|
|
||||||
val sign :
|
val sign :
|
||||||
Helpers_account.t option -> Tezos_base.Operation.shell_header ->
|
Helpers_account.t option -> Tezos_base.Operation.shell_header ->
|
||||||
proto_operation -> MBytes.t * Ed25519.Signature.t option
|
proto_operation -> MBytes.t * Ed25519.t option
|
||||||
|
|
||||||
val main_of_proto :
|
val main_of_proto :
|
||||||
Helpers_account.t -> Tezos_base.Operation.shell_header ->
|
Helpers_account.t -> Tezos_base.Operation.shell_header ->
|
||||||
|
@ -8,6 +8,7 @@
|
|||||||
(**************************************************************************)
|
(**************************************************************************)
|
||||||
|
|
||||||
open Proto_alpha
|
open Proto_alpha
|
||||||
|
open Alpha_context
|
||||||
open Error_monad
|
open Error_monad
|
||||||
|
|
||||||
let name = "Isolate Activation"
|
let name = "Isolate Activation"
|
||||||
@ -19,60 +20,59 @@ open Isolate_helpers
|
|||||||
|
|
||||||
(* Generated commitment with secret included in commitment storage :
|
(* Generated commitment with secret included in commitment storage :
|
||||||
|
|
||||||
pk = 097291124abb881ccdeea4f9a6912f34e3379586853360fa8ced414c1a3dee11
|
(blind = "abc")
|
||||||
pkh =dca88243fece75e9c22e63d162a8ada8f0cf4d94
|
|
||||||
pk_b58 =tz1fkmDXEQdua3u71vstaKwR4h8KY7oT1PDF
|
|
||||||
amount = 1868898542104
|
|
||||||
secret =c5422e3864b9e6c5260e2aac76ea0f3d28d4fff7
|
|
||||||
|
|
||||||
half_pkh = dca88243fece75e9c22e
|
pk = edpktiPG79C8CRTMxua67NEaVKH7AydAMWRiC5KHQv78Ckx4UrZYBy
|
||||||
blinded_pkh : 4a6af2f5c466bf0a7a1001a1e9468cbfca82cef6
|
pkh = tz1fkmDXEQdua3u71vstaKwR4h8KY7oT1PDF
|
||||||
amount :1868898542104130027 *)
|
amount = 1868898542104.130027
|
||||||
|
|
||||||
let used_blind = MBytes.of_string "abc"
|
secret = 0xc5422e3864b9e6c5260e2aac76ea0f3d28d4fff7
|
||||||
|
|
||||||
let hash_bytes pkh_bytes bytes =
|
half_pkh = 0xdca88243fece75e9c22e
|
||||||
let open Ed25519.Public_key_hash in
|
blinded_pkh : 0x4a6af2f5c466bf0a7a1001a1e9468cbfca82cef6
|
||||||
let hb = to_bytes (hash_bytes [ bytes ; pkh_bytes ]) in
|
|
||||||
hash_bytes [ bytes ; hb ]
|
*)
|
||||||
|
|
||||||
|
let pk =
|
||||||
|
Ed25519.Public_key.of_b58check_exn
|
||||||
|
"edpktiPG79C8CRTMxua67NEaVKH7AydAMWRiC5KHQv78Ckx4UrZYBy"
|
||||||
|
let pkh = Ed25519.Public_key.hash pk
|
||||||
|
let half_pkh =
|
||||||
|
let len = Ed25519.Public_key_hash.size / 2 in
|
||||||
|
MBytes.sub (Ed25519.Public_key_hash.to_bytes pkh) 0 (len / 2)
|
||||||
|
|
||||||
|
let given_secret =
|
||||||
|
Blinded_public_key_hash.secret_of_hex
|
||||||
|
"c5422e3864b9e6c5260e2aac76ea0f3d28d4fff7"
|
||||||
|
|
||||||
|
let expected_blinded_pkh =
|
||||||
|
Blinded_public_key_hash.of_hex
|
||||||
|
"4a6af2f5c466bf0a7a1001a1e9468cbfca82cef6"
|
||||||
|
|
||||||
|
let expected_amount =
|
||||||
|
match Tez.of_mutez 1868898542104130027L with
|
||||||
|
| Some s -> s
|
||||||
|
| _ -> assert false
|
||||||
|
|
||||||
let test_hash_correctness () =
|
let test_hash_correctness () =
|
||||||
let open Ed25519 in
|
|
||||||
|
|
||||||
let module PKH = Public_key_hash in
|
let blinded_pkh =
|
||||||
|
Blinded_public_key_hash.of_ed25519_pkh given_secret pkh in
|
||||||
|
|
||||||
let pk = Public_key.of_hex_exn (`Hex "097291124abb881ccdeea4f9a6912f34e3379586853360fa8ced414c1a3dee11") in
|
Assert.equal
|
||||||
let pkh = PKH.of_hex_exn "dca88243fece75e9c22e63d162a8ada8f0cf4d94" in
|
~msg: __LOC__
|
||||||
let pkh_b58c = "tz1fkmDXEQdua3u71vstaKwR4h8KY7oT1PDF" in
|
~eq: Blinded_public_key_hash.(=)
|
||||||
let given_secret = MBytes.of_hex (`Hex "c5422e3864b9e6c5260e2aac76ea0f3d28d4fff7") in
|
blinded_pkh expected_blinded_pkh ;
|
||||||
let expected_half_pkh = MBytes.of_hex (`Hex "dca88243fece75e9c22e") in
|
|
||||||
let expected_blinded_pkh = MBytes.of_hex (`Hex "4a6af2f5c466bf0a7a1001a1e9468cbfca82cef6") in
|
|
||||||
|
|
||||||
Assert.equal ~eq:(Public_key_hash.equal) (Public_key.hash pk) pkh;
|
|
||||||
let pkh_bytes = PKH.to_bytes pkh in
|
|
||||||
|
|
||||||
let pkh' = PKH.of_b58check_exn pkh_b58c in
|
|
||||||
|
|
||||||
Assert.equal ~eq:(PKH.equal) pkh pkh';
|
|
||||||
|
|
||||||
let half_pkh'_bytes = MBytes.sub (PKH.to_bytes pkh') 0 10 in
|
|
||||||
Assert.equal ~eq:(MBytes.equal) half_pkh'_bytes expected_half_pkh;
|
|
||||||
|
|
||||||
let blinded_pkh = PKH.to_bytes (PKH.hash_bytes ~key:given_secret [ pkh_bytes ]) in
|
|
||||||
Assert.equal ~eq:(MBytes.equal) blinded_pkh expected_blinded_pkh;
|
|
||||||
|
|
||||||
return ()
|
return ()
|
||||||
|
|
||||||
let test_simple_activation () =
|
let test_simple_activation () =
|
||||||
let module PKH = Ed25519.Public_key_hash in
|
|
||||||
Init.main () >>=? fun starting_block ->
|
Init.main () >>=? fun starting_block ->
|
||||||
|
|
||||||
let id = Ed25519.Public_key_hash.of_b58check_exn "tz1fkmDXEQdua3u71vstaKwR4h8KY7oT1PDF" in
|
let activation_operation =
|
||||||
let secret =
|
Alpha_context.Activation
|
||||||
Blinded_public_key_hash.secret_of_hex
|
{ id = pkh ; secret = given_secret } in
|
||||||
"c5422e3864b9e6c5260e2aac76ea0f3d28d4fff7" in
|
|
||||||
|
|
||||||
let activation_operation = Alpha_context.(Activation { id ; secret }) in
|
|
||||||
|
|
||||||
Proto_alpha.Apply.apply_anonymous_operation
|
Proto_alpha.Apply.apply_anonymous_operation
|
||||||
starting_block.tezos_context
|
starting_block.tezos_context
|
||||||
@ -80,19 +80,14 @@ let test_simple_activation () =
|
|||||||
starting_block.hash
|
starting_block.hash
|
||||||
activation_operation >>=? fun (ctxt, _, _, _) ->
|
activation_operation >>=? fun (ctxt, _, _, _) ->
|
||||||
|
|
||||||
let open Proto_alpha.Alpha_context in
|
let contract = Contract.implicit_contract pkh in
|
||||||
|
|
||||||
Lwt.return @@ Contract.of_b58check "tz1fkmDXEQdua3u71vstaKwR4h8KY7oT1PDF" >>=? fun ctrt ->
|
Contract.get_balance ctxt contract >>=? fun amount ->
|
||||||
|
|
||||||
Proto_alpha.Alpha_context.Contract.get_balance ctxt ctrt >>=? fun amount ->
|
Assert.equal
|
||||||
|
~msg: __LOC__
|
||||||
let expected_amount =
|
~eq:Tez.equal
|
||||||
match Tez.of_mutez 1868898542104130027L with
|
amount expected_amount ;
|
||||||
| Some s -> s
|
|
||||||
| _ -> Assert.fail_msg "Invalid conversion"
|
|
||||||
in
|
|
||||||
|
|
||||||
Assert.equal ~eq:(Tez.equal) amount expected_amount;
|
|
||||||
|
|
||||||
return ()
|
return ()
|
||||||
|
|
||||||
|
@ -63,7 +63,7 @@ module Command = struct
|
|||||||
let open Data_encoding in
|
let open Data_encoding in
|
||||||
obj2
|
obj2
|
||||||
(req "content" encoding)
|
(req "content" encoding)
|
||||||
(req "signature" Ed25519.Signature.encoding)
|
(req "signature" Ed25519.encoding)
|
||||||
|
|
||||||
let forge shell command =
|
let forge shell command =
|
||||||
Data_encoding.Binary.to_bytes
|
Data_encoding.Binary.to_bytes
|
||||||
@ -77,9 +77,8 @@ module Pubkey = struct
|
|||||||
let pubkey_key = ["genesis_key"]
|
let pubkey_key = ["genesis_key"]
|
||||||
|
|
||||||
let default =
|
let default =
|
||||||
let pubkey =
|
Ed25519.Public_key.of_b58check_exn
|
||||||
"4d5373455738070434f214826d301a1c206780d7f789fcbf94c2149b2e0718cc" in
|
"edpkuEH8DSby4w167NpxYbMagBapWvM8jsqKJpiW3JpVD7Af8oGmEo"
|
||||||
Ed25519.Public_key.of_hex_exn (`Hex pubkey)
|
|
||||||
|
|
||||||
let get_pubkey ctxt =
|
let get_pubkey ctxt =
|
||||||
Context.get ctxt pubkey_key >>= function
|
Context.get ctxt pubkey_key >>= function
|
||||||
|
@ -41,20 +41,15 @@ let validation_passes = []
|
|||||||
type block = {
|
type block = {
|
||||||
shell: Block_header.shell_header ;
|
shell: Block_header.shell_header ;
|
||||||
command: Data.Command.t ;
|
command: Data.Command.t ;
|
||||||
signature: Ed25519.Signature.t ;
|
signature: Ed25519.t ;
|
||||||
}
|
}
|
||||||
|
|
||||||
let max_block_length =
|
let max_block_length =
|
||||||
Data_encoding.Binary.length
|
Data_encoding.Binary.length
|
||||||
Data.Command.encoding
|
Data.Command.encoding
|
||||||
(Activate_testchain { protocol = Protocol_hash.hash_bytes [] ;
|
(Activate_testchain { protocol = Protocol_hash.zero ;
|
||||||
delay = 0L })
|
delay = 0L })
|
||||||
+
|
+ Ed25519.size
|
||||||
begin
|
|
||||||
match Data_encoding.Binary.fixed_length Ed25519.Signature.encoding with
|
|
||||||
| None -> assert false
|
|
||||||
| Some len -> len
|
|
||||||
end
|
|
||||||
|
|
||||||
let parse_block { Block_header.shell ; protocol_data } : block tzresult =
|
let parse_block { Block_header.shell ; protocol_data } : block tzresult =
|
||||||
match
|
match
|
||||||
@ -67,7 +62,7 @@ let check_signature ctxt { shell ; command ; signature } =
|
|||||||
let bytes = Data.Command.forge shell command in
|
let bytes = Data.Command.forge shell command in
|
||||||
Data.Pubkey.get_pubkey ctxt >>= fun public_key ->
|
Data.Pubkey.get_pubkey ctxt >>= fun public_key ->
|
||||||
fail_unless
|
fail_unless
|
||||||
(Ed25519.Signature.check public_key signature bytes)
|
(Ed25519.check public_key signature bytes)
|
||||||
Invalid_signature
|
Invalid_signature
|
||||||
|
|
||||||
type validation_state = Updater.validation_result
|
type validation_state = Updater.validation_result
|
||||||
|
Loading…
Reference in New Issue
Block a user