2016-09-08 21:13:10 +04:00
|
|
|
(**************************************************************************)
|
|
|
|
(* *)
|
|
|
|
(* Copyright (c) 2014 - 2016. *)
|
|
|
|
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
|
|
|
|
(* *)
|
|
|
|
(* All rights reserved. No warranty, explicit or implicit, provided. *)
|
|
|
|
(* *)
|
|
|
|
(**************************************************************************)
|
|
|
|
|
|
|
|
let (//) = Filename.concat
|
|
|
|
let (>>=) = Lwt.bind
|
|
|
|
let (>|=) = Lwt.(>|=)
|
|
|
|
|
|
|
|
open Utils
|
|
|
|
|
2016-11-25 22:46:50 +04:00
|
|
|
let () =
|
|
|
|
let expected_primitive = "blake2b"
|
|
|
|
and primitive = Sodium.Generichash.primitive in
|
|
|
|
if primitive <> expected_primitive then begin
|
|
|
|
Printf.eprintf
|
|
|
|
"FATAL ERROR: \
|
|
|
|
invalid value for Sodium.Generichash.primitive: %S (expected %S)@."
|
|
|
|
primitive expected_primitive ;
|
|
|
|
exit 1
|
|
|
|
end
|
|
|
|
|
2016-09-08 21:13:10 +04:00
|
|
|
(*-- Signatures -------------------------------------------------------------*)
|
|
|
|
|
2016-11-14 19:26:34 +04:00
|
|
|
module type MINIMAL_HASH = sig
|
|
|
|
|
2016-09-08 21:13:10 +04:00
|
|
|
type t
|
|
|
|
|
2016-11-14 19:26:34 +04:00
|
|
|
val name: string
|
|
|
|
val title: string
|
|
|
|
|
2016-09-08 21:13:10 +04:00
|
|
|
val hash_bytes: MBytes.t list -> t
|
|
|
|
val hash_string: string list -> t
|
|
|
|
val size: int (* in bytes *)
|
|
|
|
val compare: t -> t -> int
|
|
|
|
val equal: t -> t -> bool
|
|
|
|
val of_hex: string -> t
|
|
|
|
val to_hex: t -> string
|
2016-11-25 22:46:50 +04:00
|
|
|
val of_string: string -> t
|
|
|
|
val to_string: t -> string
|
2016-09-08 21:13:10 +04:00
|
|
|
val to_bytes: t -> MBytes.t
|
|
|
|
val of_bytes: MBytes.t -> t
|
|
|
|
val read: MBytes.t -> int -> t
|
|
|
|
val write: MBytes.t -> int -> t -> unit
|
|
|
|
val to_path: t -> string list
|
|
|
|
val of_path: string list -> t
|
2016-10-06 20:30:04 +04:00
|
|
|
val prefix_path: string -> string list
|
2016-09-08 21:13:10 +04:00
|
|
|
val path_len: int
|
2016-11-14 19:26:34 +04:00
|
|
|
|
|
|
|
end
|
|
|
|
|
|
|
|
module type HASH = sig
|
|
|
|
|
|
|
|
include MINIMAL_HASH
|
|
|
|
|
2017-02-19 21:22:32 +04:00
|
|
|
val of_b58check: string -> t
|
|
|
|
val to_b58check: t -> string
|
|
|
|
val to_short_b58check: t -> string
|
2016-09-08 21:13:10 +04:00
|
|
|
val encoding: t Data_encoding.t
|
|
|
|
val pp: Format.formatter -> t -> unit
|
|
|
|
val pp_short: Format.formatter -> t -> unit
|
2017-02-19 21:22:32 +04:00
|
|
|
type Base58.data += Hash of t
|
|
|
|
val b58check_encoding: t Base58.encoding
|
2016-11-14 19:26:34 +04:00
|
|
|
|
2016-09-08 21:13:10 +04:00
|
|
|
end
|
|
|
|
|
|
|
|
module type Name = sig
|
2016-11-14 19:26:34 +04:00
|
|
|
val name: string
|
|
|
|
val title: string
|
2016-11-25 22:46:50 +04:00
|
|
|
val size: int option
|
2016-11-14 19:26:34 +04:00
|
|
|
end
|
|
|
|
|
|
|
|
module type PrefixedName = sig
|
|
|
|
include Name
|
2017-02-19 21:22:32 +04:00
|
|
|
val b58check_prefix: string
|
2016-09-08 21:13:10 +04:00
|
|
|
end
|
|
|
|
|
|
|
|
(*-- Type specific Hash builder ---------------------------------------------*)
|
|
|
|
|
2016-11-25 22:46:50 +04:00
|
|
|
module Make_minimal_Blake2B (K : Name) = struct
|
2016-09-08 21:13:10 +04:00
|
|
|
|
2016-11-25 22:46:50 +04:00
|
|
|
type t = Sodium.Generichash.hash
|
2016-09-08 21:13:10 +04:00
|
|
|
|
2016-11-14 19:26:34 +04:00
|
|
|
include K
|
|
|
|
|
2016-11-25 22:46:50 +04:00
|
|
|
let size =
|
|
|
|
match K.size with
|
|
|
|
| None -> 32
|
|
|
|
| Some x -> x
|
2016-09-08 21:13:10 +04:00
|
|
|
|
2016-11-25 22:46:50 +04:00
|
|
|
let of_string s =
|
2016-09-08 21:13:10 +04:00
|
|
|
if String.length s <> size then begin
|
|
|
|
let msg =
|
2016-11-25 22:46:50 +04:00
|
|
|
Printf.sprintf "%s.of_string: wrong string size (%d)"
|
|
|
|
K.name (String.length s) in
|
2016-09-08 21:13:10 +04:00
|
|
|
raise (Invalid_argument msg)
|
2016-11-25 22:46:50 +04:00
|
|
|
end ;
|
|
|
|
Sodium.Generichash.Bytes.to_hash (Bytes.of_string s)
|
|
|
|
let to_string s = Bytes.to_string (Sodium.Generichash.Bytes.of_hash s)
|
2016-09-08 21:13:10 +04:00
|
|
|
|
2016-11-25 22:46:50 +04:00
|
|
|
let of_hex s = of_string (Hex_encode.hex_decode s)
|
|
|
|
let to_hex s = Hex_encode.hex_encode (to_string s)
|
2016-09-08 21:13:10 +04:00
|
|
|
|
2016-11-25 22:46:50 +04:00
|
|
|
let compare = Sodium.Generichash.compare
|
|
|
|
let equal x y = compare x y = 0
|
2016-09-08 21:13:10 +04:00
|
|
|
|
|
|
|
let of_bytes b =
|
2016-11-25 22:46:50 +04:00
|
|
|
if MBytes.length b <> size then begin
|
2016-09-08 21:13:10 +04:00
|
|
|
let msg =
|
2016-11-25 22:46:50 +04:00
|
|
|
Printf.sprintf "%s.of_bytes: wrong string size (%d)"
|
|
|
|
K.name (MBytes.length b) in
|
2016-09-08 21:13:10 +04:00
|
|
|
raise (Invalid_argument msg)
|
2016-11-25 22:46:50 +04:00
|
|
|
end ;
|
|
|
|
Sodium.Generichash.Bigbytes.to_hash b
|
|
|
|
let to_bytes = Sodium.Generichash.Bigbytes.of_hash
|
2016-09-08 21:13:10 +04:00
|
|
|
|
2016-11-25 22:46:50 +04:00
|
|
|
let read src off = of_bytes @@ MBytes.sub src off size
|
|
|
|
let write dst off h = MBytes.blit (to_bytes h) 0 dst off size
|
2016-09-08 21:13:10 +04:00
|
|
|
|
|
|
|
let hash_bytes l =
|
2016-11-25 22:46:50 +04:00
|
|
|
let open Sodium.Generichash in
|
|
|
|
let state = init ~size () in
|
|
|
|
List.iter (Bigbytes.update state) l ;
|
|
|
|
final state
|
2016-09-08 21:13:10 +04:00
|
|
|
|
|
|
|
let hash_string l =
|
2016-11-25 22:46:50 +04:00
|
|
|
let open Sodium.Generichash in
|
|
|
|
let state = init ~size () in
|
|
|
|
List.iter
|
|
|
|
(fun s -> Bytes.update state (BytesLabels.unsafe_of_string s))
|
|
|
|
l ;
|
|
|
|
final state
|
2016-09-08 21:13:10 +04:00
|
|
|
|
2016-11-25 22:46:50 +04:00
|
|
|
module Set = Set.Make(struct type nonrec t = t let compare = compare end)
|
2016-09-08 21:13:10 +04:00
|
|
|
|
|
|
|
let fold_read f buf off len init =
|
|
|
|
let last = off + len * size in
|
|
|
|
if last > MBytes.length buf then
|
|
|
|
invalid_arg "Hash.read_set: invalid size.";
|
|
|
|
let rec loop acc off =
|
|
|
|
if off >= last then
|
|
|
|
acc
|
|
|
|
else
|
|
|
|
let hash = read buf off in
|
|
|
|
loop (f hash acc) (off + size)
|
|
|
|
in
|
|
|
|
loop init off
|
|
|
|
|
2016-11-25 22:46:50 +04:00
|
|
|
module Map = Map.Make(struct type nonrec t = t let compare = compare end)
|
2016-09-08 21:13:10 +04:00
|
|
|
module Table =
|
|
|
|
Hashtbl.Make(struct
|
2016-11-25 22:46:50 +04:00
|
|
|
type nonrec t = t
|
|
|
|
let hash s =
|
|
|
|
Int64.to_int
|
|
|
|
(EndianString.BigEndian.get_int64
|
|
|
|
(Bytes.unsafe_to_string (Sodium.Generichash.Bytes.of_hash s))
|
|
|
|
0)
|
2016-09-08 21:13:10 +04:00
|
|
|
let equal = equal
|
|
|
|
end)
|
|
|
|
|
2016-11-14 19:26:34 +04:00
|
|
|
let path_len = 6
|
2016-09-08 21:13:10 +04:00
|
|
|
let to_path key =
|
|
|
|
let key = to_hex key in
|
|
|
|
[ String.sub key 0 2 ; String.sub key 2 2 ;
|
|
|
|
String.sub key 4 2 ; String.sub key 6 2 ;
|
2016-11-14 19:26:34 +04:00
|
|
|
String.sub key 8 2 ; String.sub key 10 (size * 2 - 10) ]
|
2016-09-08 21:13:10 +04:00
|
|
|
let of_path path =
|
|
|
|
let path = String.concat "" path in
|
|
|
|
of_hex path
|
|
|
|
|
2016-10-06 20:30:04 +04:00
|
|
|
let prefix_path p =
|
2016-11-25 22:46:50 +04:00
|
|
|
let p = Hex_encode.hex_encode p in
|
2016-10-06 20:30:04 +04:00
|
|
|
let len = String.length p in
|
|
|
|
let p1 = if len >= 2 then String.sub p 0 2 else ""
|
|
|
|
and p2 = if len >= 4 then String.sub p 2 2 else ""
|
|
|
|
and p3 = if len >= 6 then String.sub p 4 2 else ""
|
|
|
|
and p4 = if len >= 8 then String.sub p 6 2 else ""
|
2016-11-14 19:26:34 +04:00
|
|
|
and p5 = if len >= 10 then String.sub p 8 2 else ""
|
|
|
|
and p6 = if len > 10 then String.sub p 10 (len - 10) else "" in
|
|
|
|
[ p1 ; p2 ; p3 ; p4 ; p5 ; p6 ]
|
|
|
|
|
|
|
|
end
|
|
|
|
|
2016-11-25 22:46:50 +04:00
|
|
|
module Make_Blake2B (R : sig
|
2016-11-14 19:26:34 +04:00
|
|
|
val register_encoding:
|
|
|
|
prefix: string ->
|
2017-02-19 21:22:32 +04:00
|
|
|
length:int ->
|
2016-11-14 19:26:34 +04:00
|
|
|
to_raw: ('a -> string) ->
|
|
|
|
of_raw: (string -> 'a option) ->
|
2017-02-19 21:22:32 +04:00
|
|
|
wrap: ('a -> Base58.data) ->
|
|
|
|
'a Base58.encoding
|
2016-11-14 19:26:34 +04:00
|
|
|
end) (K : PrefixedName) = struct
|
|
|
|
|
2016-11-25 22:46:50 +04:00
|
|
|
include Make_minimal_Blake2B(K)
|
2016-10-06 20:30:04 +04:00
|
|
|
|
2016-09-08 21:13:10 +04:00
|
|
|
(* Serializers *)
|
|
|
|
|
2017-02-19 21:22:32 +04:00
|
|
|
type Base58.data += Hash of t
|
2016-11-14 19:26:34 +04:00
|
|
|
|
2017-02-19 21:22:32 +04:00
|
|
|
let b58check_encoding =
|
2016-11-14 19:26:34 +04:00
|
|
|
R.register_encoding
|
2017-02-19 21:22:32 +04:00
|
|
|
~prefix: K.b58check_prefix
|
|
|
|
~length:size
|
2016-11-25 22:46:50 +04:00
|
|
|
~wrap: (fun s -> Hash s)
|
|
|
|
~of_raw:(fun h -> Some (of_string h)) ~to_raw:to_string
|
2016-11-14 19:26:34 +04:00
|
|
|
|
2017-02-19 21:22:32 +04:00
|
|
|
let of_b58check s =
|
|
|
|
match Base58.simple_decode b58check_encoding s with
|
2016-11-14 19:26:34 +04:00
|
|
|
| Some x -> x
|
|
|
|
| None -> Format.kasprintf failwith "Unexpected hash (%s)" K.name
|
2017-02-19 21:22:32 +04:00
|
|
|
let to_b58check s = Base58.simple_encode b58check_encoding s
|
2016-11-14 19:26:34 +04:00
|
|
|
|
2017-02-19 21:22:32 +04:00
|
|
|
let to_short_b58check s =
|
|
|
|
String.sub (to_b58check s) 0 (10 + 2 * String.length K.b58check_prefix)
|
2016-11-14 19:26:34 +04:00
|
|
|
|
2016-09-08 21:13:10 +04:00
|
|
|
let encoding =
|
|
|
|
let open Data_encoding in
|
|
|
|
splitted
|
|
|
|
~binary:
|
|
|
|
(conv to_bytes of_bytes (Fixed.bytes size))
|
|
|
|
~json:
|
2017-02-19 21:22:32 +04:00
|
|
|
(describe ~title: (K.title ^ " (Base58Check-encoded Sha256)") @@
|
|
|
|
conv to_b58check (Data_encoding.Json.wrap_error of_b58check) string)
|
2016-09-08 21:13:10 +04:00
|
|
|
|
|
|
|
let param ?(name=K.name) ?(desc=K.title) t =
|
2017-02-19 21:22:32 +04:00
|
|
|
Cli_entries.param ~name ~desc (fun _ str -> Lwt.return (of_b58check str)) t
|
2016-09-08 21:13:10 +04:00
|
|
|
|
|
|
|
let pp ppf t =
|
2017-02-19 21:22:32 +04:00
|
|
|
Format.pp_print_string ppf (to_b58check t)
|
2016-09-08 21:13:10 +04:00
|
|
|
|
|
|
|
let pp_short ppf t =
|
2017-02-19 21:22:32 +04:00
|
|
|
Format.pp_print_string ppf (to_short_b58check t)
|
2016-09-08 21:13:10 +04:00
|
|
|
|
|
|
|
end
|
|
|
|
|
|
|
|
(*-- Hash sets and maps -----------------------------------------------------*)
|
|
|
|
|
|
|
|
module Hash_set (Hash : HASH) = struct
|
|
|
|
include Set.Make (Hash)
|
|
|
|
let encoding =
|
|
|
|
Data_encoding.conv
|
|
|
|
elements
|
|
|
|
(fun l -> List.fold_left (fun m x -> add x m) empty l)
|
|
|
|
Data_encoding.(list Hash.encoding)
|
|
|
|
end
|
|
|
|
|
|
|
|
module Hash_map (Hash : HASH) = struct
|
|
|
|
include Map.Make (Hash)
|
|
|
|
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 Hash.encoding arg_encoding))
|
|
|
|
end
|
|
|
|
|
2017-01-14 16:13:35 +04:00
|
|
|
module Hash_table (Hash : MINIMAL_HASH)
|
2016-09-08 21:13:10 +04:00
|
|
|
: Hashtbl.S with type key = Hash.t
|
|
|
|
= Hashtbl.Make (struct
|
|
|
|
type t = Hash.t
|
|
|
|
let equal = Hash.equal
|
|
|
|
let hash v =
|
2016-11-25 22:46:50 +04:00
|
|
|
let raw_hash = Hash.to_string v in
|
2016-09-08 21:13:10 +04:00
|
|
|
let int64_hash = EndianString.BigEndian.get_int64 raw_hash 0 in
|
|
|
|
Int64.to_int int64_hash
|
|
|
|
end)
|
|
|
|
|
|
|
|
(*-- Pre-instanciated hashes ------------------------------------------------*)
|
|
|
|
|
|
|
|
module Block_hash =
|
2017-02-19 21:22:32 +04:00
|
|
|
Make_Blake2B (Base58) (struct
|
2016-09-08 21:13:10 +04:00
|
|
|
let name = "Block_hash"
|
|
|
|
let title = "A Tezos block ID"
|
2017-02-19 21:22:32 +04:00
|
|
|
let b58check_prefix = Base58.Prefix.block_hash
|
2016-11-25 22:46:50 +04:00
|
|
|
let size = None
|
2016-09-08 21:13:10 +04:00
|
|
|
end)
|
|
|
|
|
|
|
|
module Block_hash_set = Hash_set (Block_hash)
|
|
|
|
module Block_hash_map = Hash_map (Block_hash)
|
|
|
|
module Block_hash_table = Hash_table (Block_hash)
|
|
|
|
|
|
|
|
module Operation_hash =
|
2017-02-19 21:22:32 +04:00
|
|
|
Make_Blake2B (Base58) (struct
|
2016-09-08 21:13:10 +04:00
|
|
|
let name = "Operation_hash"
|
|
|
|
let title = "A Tezos operation ID"
|
2017-02-19 21:22:32 +04:00
|
|
|
let b58check_prefix = Base58.Prefix.operation_hash
|
2016-11-25 22:46:50 +04:00
|
|
|
let size = None
|
2016-09-08 21:13:10 +04:00
|
|
|
end)
|
|
|
|
|
|
|
|
module Operation_hash_set = Hash_set (Operation_hash)
|
|
|
|
module Operation_hash_map = Hash_map (Operation_hash)
|
|
|
|
module Operation_hash_table = Hash_table (Operation_hash)
|
|
|
|
|
|
|
|
module Protocol_hash =
|
2017-02-19 21:22:32 +04:00
|
|
|
Make_Blake2B (Base58) (struct
|
2016-09-08 21:13:10 +04:00
|
|
|
let name = "Protocol_hash"
|
|
|
|
let title = "A Tezos protocol ID"
|
2017-02-19 21:22:32 +04:00
|
|
|
let b58check_prefix = Base58.Prefix.protocol_hash
|
2016-11-25 22:46:50 +04:00
|
|
|
let size = None
|
2016-09-08 21:13:10 +04:00
|
|
|
end)
|
|
|
|
|
|
|
|
module Protocol_hash_set = Hash_set (Protocol_hash)
|
|
|
|
module Protocol_hash_map = Hash_map (Protocol_hash)
|
|
|
|
module Protocol_hash_table = Hash_table (Protocol_hash)
|
2016-11-25 22:46:50 +04:00
|
|
|
|
|
|
|
module Generic_hash =
|
|
|
|
Make_minimal_Blake2B (struct
|
|
|
|
let name = "Generic_hash"
|
|
|
|
let title = ""
|
|
|
|
let size = None
|
|
|
|
end)
|
|
|
|
|
2017-02-19 21:22:32 +04:00
|
|
|
let () =
|
|
|
|
Base58.check_encoded_prefix Block_hash.b58check_encoding "B" 51 ;
|
|
|
|
Base58.check_encoded_prefix Operation_hash.b58check_encoding "o" 51 ;
|
|
|
|
Base58.check_encoded_prefix Protocol_hash.b58check_encoding "P" 51
|