OPAM: use the hex
package
It replaces our own `Hex_encode` module.
This commit is contained in:
parent
0c9592bca7
commit
9405b702e9
@ -53,8 +53,8 @@ let max x y = if x <= y then y else x
|
||||
|
||||
let rec pp fmt = function
|
||||
| [] -> ()
|
||||
| [f] -> Format.fprintf fmt "%s" (Hex_encode.hex_of_bytes f)
|
||||
| f1 :: f -> Format.fprintf fmt "%s::%a" (Hex_encode.hex_of_bytes f1) pp f
|
||||
| [f] -> Format.fprintf fmt "%a" Hex.pp (MBytes.to_hex f)
|
||||
| f1 :: f -> Format.fprintf fmt "%a::%a" Hex.pp (MBytes.to_hex f1) pp f
|
||||
|
||||
let encoding =
|
||||
let open Data_encoding in
|
||||
|
@ -26,7 +26,7 @@ let pp_block ppf
|
||||
@ Fitness: @[<v>%a@]\
|
||||
@ Operations hash: %a\
|
||||
@ Operations: @[<v>%a@]\
|
||||
@ Data (hex encoded): \"%s\"@]"
|
||||
@ Data (hex encoded): \"%a\"@]"
|
||||
Block_hash.pp hash
|
||||
Test_network_status.pp test_network
|
||||
level
|
||||
@ -35,10 +35,7 @@ let pp_block ppf
|
||||
Protocol_hash.pp protocol
|
||||
Net_id.pp net_id
|
||||
Time.pp_hum timestamp
|
||||
(Format.pp_print_list
|
||||
~pp_sep:Format.pp_print_space
|
||||
Format.pp_print_string)
|
||||
(List.map Hex_encode.hex_of_bytes fitness)
|
||||
Fitness.pp fitness
|
||||
Operation_list_list_hash.pp operations_hash
|
||||
(fun ppf -> function
|
||||
| None -> Format.fprintf ppf "None"
|
||||
@ -48,7 +45,7 @@ let pp_block ppf
|
||||
(fun ppf (oph, _) -> Operation_hash.pp ppf oph))
|
||||
ppf operations)
|
||||
operations
|
||||
(Hex_encode.hex_of_bytes data)
|
||||
Hex.pp (MBytes.to_hex data)
|
||||
|
||||
let stuck_node_report cctxt file =
|
||||
let ppf = Format.formatter_of_out_channel (open_out file) in
|
||||
|
@ -46,9 +46,11 @@ module Make_minimal (K : S.Name) = struct
|
||||
| Some h -> h
|
||||
let to_string s = Bytes.to_string (Sodium.Generichash.Bytes.of_hash s)
|
||||
|
||||
let of_hex s = of_string (Hex_encode.hex_decode s)
|
||||
let of_hex_exn s = of_string_exn (Hex_encode.hex_decode s)
|
||||
let to_hex s = Hex_encode.hex_encode (to_string s)
|
||||
let of_hex s = of_string (Hex.to_string (`Hex s))
|
||||
let of_hex_exn s = of_string_exn (Hex.to_string (`Hex s))
|
||||
let to_hex s =
|
||||
let `Hex s = Hex.of_string (to_string s) in
|
||||
s
|
||||
|
||||
let compare = Sodium.Generichash.compare
|
||||
let equal x y = compare x y = 0
|
||||
@ -99,7 +101,7 @@ module Make_minimal (K : S.Name) = struct
|
||||
of_hex_exn path
|
||||
|
||||
let prefix_path p =
|
||||
let p = Hex_encode.hex_encode p in
|
||||
let `Hex p = Hex.of_string p in
|
||||
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 ""
|
||||
|
@ -33,14 +33,18 @@ module Public_key = struct
|
||||
type Base58.data +=
|
||||
| Public_key of t
|
||||
|
||||
let to_string s = Bytes.to_string (Sodium.Sign.Bytes.of_public_key s)
|
||||
let of_string_exn x = Sodium.Sign.Bytes.to_public_key (Bytes.of_string x)
|
||||
let of_string x =
|
||||
try Some (of_string_exn x)
|
||||
with _ -> None
|
||||
|
||||
let b58check_encoding =
|
||||
Base58.register_encoding
|
||||
~prefix: Base58.Prefix.ed25519_public_key
|
||||
~length:Sodium.Sign.public_key_size
|
||||
~to_raw:(fun x -> Bytes.to_string (Sodium.Sign.Bytes.of_public_key x))
|
||||
~of_raw:(fun x ->
|
||||
try Some (Sodium.Sign.Bytes.to_public_key (Bytes.of_string x))
|
||||
with _ -> None)
|
||||
~to_raw:to_string
|
||||
~of_raw:of_string
|
||||
~wrap:(fun x -> Public_key x)
|
||||
|
||||
let of_b58check_opt s = Base58.simple_decode b58check_encoding s
|
||||
@ -54,6 +58,10 @@ module Public_key = struct
|
||||
| None -> generic_error "Unexpected hash (ed25519 public key)"
|
||||
let to_b58check s = Base58.simple_encode b58check_encoding s
|
||||
|
||||
let of_hex s = of_string (Hex.to_string s)
|
||||
let of_hex_exn s = of_string_exn (Hex.to_string s)
|
||||
let to_hex s = Hex.of_string (to_string s)
|
||||
|
||||
let of_bytes s = Sodium.Sign.Bytes.to_public_key s
|
||||
|
||||
let param ?(name="ed25519-public") ?(desc="Ed25519 public key (b58check-encoded)") t =
|
||||
@ -222,10 +230,11 @@ module Seed = struct
|
||||
let to_hex s =
|
||||
Sodium.Sign.Bytes.of_seed s
|
||||
|> Bytes.to_string
|
||||
|> Hex_encode.hex_encode
|
||||
|> Hex.of_string
|
||||
|> (fun (`Hex s) -> s)
|
||||
|
||||
let of_hex s =
|
||||
Hex_encode.hex_decode s
|
||||
Hex.to_string (`Hex s)
|
||||
|> Bytes.of_string
|
||||
|> Sodium.Sign.Bytes.to_seed
|
||||
|
||||
|
@ -36,6 +36,10 @@ module Public_key : sig
|
||||
val of_b58check_opt: string -> t option
|
||||
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: Bytes.t -> t
|
||||
|
||||
end
|
||||
|
@ -36,9 +36,11 @@ let of_string_exn s =
|
||||
| Some h -> h
|
||||
let to_string s = s
|
||||
|
||||
let of_hex s = of_string (Hex_encode.hex_decode s)
|
||||
let of_hex_exn s = of_string_exn (Hex_encode.hex_decode s)
|
||||
let to_hex s = Hex_encode.hex_encode (to_string s)
|
||||
let of_hex s = of_string (Hex.to_string (`Hex s))
|
||||
let of_hex_exn s = of_string_exn (Hex.to_string (`Hex s))
|
||||
let to_hex s =
|
||||
let `Hex s = Hex.of_string (to_string s) in
|
||||
s
|
||||
|
||||
let compare = String.compare
|
||||
let equal = String.equal
|
||||
@ -135,7 +137,7 @@ let of_path_exn path =
|
||||
of_hex_exn path
|
||||
|
||||
let prefix_path p =
|
||||
let p = Hex_encode.hex_encode p in
|
||||
let `Hex p = Hex.of_string p in
|
||||
[ p ]
|
||||
|
||||
module Table = struct
|
||||
|
@ -315,9 +315,12 @@ module Json = struct
|
||||
format = None ;
|
||||
id = None } in
|
||||
conv ~schema
|
||||
Hex_encode.hex_of_bytes
|
||||
(wrap_error Hex_encode.bytes_of_hex)
|
||||
string
|
||||
MBytes.to_hex
|
||||
(wrap_error MBytes.of_hex)
|
||||
(conv
|
||||
(fun (`Hex h) -> h)
|
||||
(fun h -> `Hex h)
|
||||
string)
|
||||
|
||||
let rec lift_union : type a. a t -> a t = fun e ->
|
||||
match e.encoding with
|
||||
|
@ -1,49 +0,0 @@
|
||||
(**************************************************************************)
|
||||
(* *)
|
||||
(* Copyright (c) 2014 - 2017. *)
|
||||
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
|
||||
(* *)
|
||||
(* All rights reserved. No warranty, explicit or implicit, provided. *)
|
||||
(* *)
|
||||
(**************************************************************************)
|
||||
|
||||
(* Tezos Utility library - Hexadecimal encoding *)
|
||||
|
||||
(* From OCaml's stdlib. See [Digest.to_hex], and [hex_of_bytes], [hex_encode]
|
||||
below for examples. *)
|
||||
let gen_encode length get s =
|
||||
let n = length s in
|
||||
let result = Bytes.create (n*2) in
|
||||
for i = 0 to n-1 do
|
||||
Bytes.blit_string (Printf.sprintf "%02x" (get s i)) 0 result (2*i) 2;
|
||||
done;
|
||||
Bytes.unsafe_to_string result
|
||||
|
||||
let hex_of_bytes = gen_encode MBytes.length MBytes.get_uint8
|
||||
let hex_encode = gen_encode String.length (fun s i -> int_of_char s.[i])
|
||||
|
||||
(* From OCaml's stdlib. See [Digest.from_hex], and [hex_decode], [bytes_of_hex]
|
||||
below for examples. *)
|
||||
let gen_decode create set h =
|
||||
let n = String.length h in
|
||||
if n mod 2 <> 0 then invalid_arg ("hex_decode: " ^ h);
|
||||
let digit c =
|
||||
match c with
|
||||
| '0'..'9' -> int_of_char c - int_of_char '0'
|
||||
| 'A'..'F' -> int_of_char c - int_of_char 'A' + 10
|
||||
| 'a'..'f' -> int_of_char c - int_of_char 'a' + 10
|
||||
| _c -> invalid_arg ("hex_decode: " ^ h)
|
||||
in
|
||||
let byte i = digit h.[i] lsl 4 + digit h.[i+1] in
|
||||
let result = create (n / 2) in
|
||||
for i = 0 to n/2 - 1 do
|
||||
set result i (byte (2 * i));
|
||||
done;
|
||||
result
|
||||
|
||||
let hex_decode s =
|
||||
gen_decode Bytes.create (fun s i c -> Bytes.set s i (char_of_int c)) s |>
|
||||
Bytes.unsafe_to_string
|
||||
|
||||
let bytes_of_hex s =
|
||||
gen_decode MBytes.create MBytes.set_int8 s
|
@ -1,24 +0,0 @@
|
||||
(**************************************************************************)
|
||||
(* *)
|
||||
(* Copyright (c) 2014 - 2017. *)
|
||||
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
|
||||
(* *)
|
||||
(* All rights reserved. No warranty, explicit or implicit, provided. *)
|
||||
(* *)
|
||||
(**************************************************************************)
|
||||
|
||||
(** Tezos Utility library - Hexadecimal encoding *)
|
||||
|
||||
(** Parses a sequence of hexadecimal characters pairs as bytes *)
|
||||
val hex_of_bytes: MBytes.t -> string
|
||||
|
||||
(** Prints a sequence of bytes as hexadecimal characters pairs *)
|
||||
val bytes_of_hex: string -> MBytes.t
|
||||
|
||||
(** Interprets a sequence of hexadecimal characters pairs representing
|
||||
bytes as the characters codes of an OCaml string. *)
|
||||
val hex_decode: string -> string
|
||||
|
||||
(** Formats the codes of the characters of an OCaml string as a
|
||||
sequence of hexadecimal character pairs. *)
|
||||
val hex_encode: string -> string
|
@ -89,7 +89,8 @@ let hash_and_sign (data : Michelson_v1_parser.parsed) (typ : Michelson_v1_parser
|
||||
return (hash,
|
||||
signature |>
|
||||
Data_encoding.Binary.to_bytes Ed25519.Signature.encoding |>
|
||||
Hex_encode.hex_of_bytes)
|
||||
MBytes.to_hex |>
|
||||
(fun (`Hex s) -> s))
|
||||
|
||||
let typecheck_data
|
||||
~(data : Michelson_v1_parser.parsed)
|
||||
|
@ -57,8 +57,7 @@ type constants = {
|
||||
michelson_maximum_type_size: int;
|
||||
}
|
||||
|
||||
let read_public_key s =
|
||||
Ed25519.Public_key.of_bytes (Bytes.of_string (Hex_encode.hex_decode s))
|
||||
let read_public_key s = Ed25519.Public_key.of_hex_exn (`Hex s)
|
||||
|
||||
let default = {
|
||||
cycle_length = 2048l ;
|
||||
|
@ -601,9 +601,9 @@ let rec unparse_data
|
||||
| Contract_t _, (_, _, c) ->
|
||||
String (-1, Contract.to_b58check c)
|
||||
| Signature_t, s ->
|
||||
let text =
|
||||
Hex_encode.hex_encode
|
||||
(MBytes.to_string (Data_encoding.Binary.to_bytes Ed25519.Signature.encoding s)) in
|
||||
let `Hex text =
|
||||
MBytes.to_hex
|
||||
(Data_encoding.Binary.to_bytes Ed25519.Signature.encoding s) in
|
||||
String (-1, text)
|
||||
| Tez_t, v ->
|
||||
String (-1, Tez.to_string v)
|
||||
@ -1075,7 +1075,7 @@ let rec parse_data
|
||||
| Signature_t, String (_, s) -> begin try
|
||||
match Data_encoding.Binary.of_bytes
|
||||
Ed25519.Signature.encoding
|
||||
(MBytes.of_string (Hex_encode.hex_decode s)) with
|
||||
(MBytes.of_hex (`Hex s)) with
|
||||
| Some s -> return s
|
||||
| None -> raise Not_found
|
||||
with _ ->
|
||||
|
@ -81,8 +81,7 @@ module Pubkey = struct
|
||||
let default =
|
||||
let pubkey =
|
||||
"4d5373455738070434f214826d301a1c206780d7f789fcbf94c2149b2e0718cc" in
|
||||
Ed25519.Public_key.of_bytes
|
||||
(Bytes.of_string (Hex_encode.hex_decode pubkey))
|
||||
Ed25519.Public_key.of_hex_exn (`Hex pubkey)
|
||||
|
||||
let get_pubkey ctxt =
|
||||
Context.get ctxt pubkey_key >>= function
|
||||
|
@ -31,7 +31,6 @@ module Make(Param : sig val name: string end)() = struct
|
||||
module Nativeint = Nativeint
|
||||
module Buffer = Buffer
|
||||
module Format = Format
|
||||
module Hex_encode = Hex_encode
|
||||
module Z = Z
|
||||
module Lwt_sequence = Lwt_sequence
|
||||
module Lwt = Lwt
|
||||
|
@ -25,7 +25,6 @@
|
||||
|
||||
;; Tezos extended stdlib
|
||||
v1/mBytes.mli
|
||||
v1/hex_encode.mli
|
||||
v1/compare.mli
|
||||
v1/data_encoding.mli
|
||||
v1/error_monad.mli
|
||||
|
@ -32,6 +32,10 @@ module Public_key : sig
|
||||
|
||||
val of_bytes: Bytes.t -> 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
|
||||
|
@ -1,24 +0,0 @@
|
||||
(**************************************************************************)
|
||||
(* *)
|
||||
(* Copyright (c) 2014 - 2017. *)
|
||||
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
|
||||
(* *)
|
||||
(* All rights reserved. No warranty, explicit or implicit, provided. *)
|
||||
(* *)
|
||||
(**************************************************************************)
|
||||
|
||||
(** Tezos Utility library - Hexadecimal encoding *)
|
||||
|
||||
(** Parses a sequence of hexadecimal characters pairs as bytes *)
|
||||
val hex_of_bytes: MBytes.t -> string
|
||||
|
||||
(** Prints a sequence of bytes as hexadecimal characters pairs *)
|
||||
val bytes_of_hex: string -> MBytes.t
|
||||
|
||||
(** Interprets a sequence of hexadecimal characters pairs representing
|
||||
bytes as the characters codes of an OCaml string. *)
|
||||
val hex_decode: string -> string
|
||||
|
||||
(** Formats the codes of the characters of an OCaml string as a
|
||||
sequence of hexadecimal character pairs. *)
|
||||
val hex_encode: string -> string
|
@ -130,3 +130,6 @@ val (>) : t -> t -> bool
|
||||
val compare : t -> t -> int
|
||||
|
||||
val concat: t -> t -> t
|
||||
|
||||
val to_hex: t -> [ `Hex of string ]
|
||||
val of_hex: [ `Hex of string ] -> t
|
||||
|
@ -3,7 +3,7 @@
|
||||
(library
|
||||
((name tezos_stdlib)
|
||||
(public_name tezos-stdlib)
|
||||
(libraries (ocplib-endian.bigstring cstruct stringext))
|
||||
(libraries (ocplib-endian.bigstring cstruct stringext hex))
|
||||
(flags (:standard -safe-string))))
|
||||
|
||||
(alias
|
||||
|
@ -64,6 +64,9 @@ let of_string buf =
|
||||
unsafe_blit_string_to_bigstring buf 0 c 0 buflen;
|
||||
c
|
||||
|
||||
let to_hex s = Hex.of_cstruct (Cstruct.of_bigarray s)
|
||||
let of_hex s = Cstruct.to_bigarray (Hex.to_cstruct s)
|
||||
|
||||
let substring src srcoff len =
|
||||
if len < 0 || srcoff < 0 || length src - srcoff < len then
|
||||
raise (Invalid_argument (invalid_bounds srcoff len));
|
||||
|
@ -149,3 +149,6 @@ val compare : t -> t -> int
|
||||
|
||||
val concat: t -> t -> t
|
||||
(** Returns a new array with adjacent copies of the two input arrays **)
|
||||
|
||||
val to_hex: t -> Hex.t
|
||||
val of_hex: Hex.t -> t
|
||||
|
@ -10,6 +10,7 @@ depends: [
|
||||
"ocamlfind" { build }
|
||||
"jbuilder" { build & >= "1.0+beta15" }
|
||||
"cstruct"
|
||||
"hex"
|
||||
"ocplib-endian"
|
||||
"stringext"
|
||||
]
|
||||
|
@ -8,8 +8,8 @@
|
||||
(**************************************************************************)
|
||||
|
||||
let hex_of_buffer buf =
|
||||
Hex_encode.hex_of_bytes (MBytes_buffer.to_mbytes buf)
|
||||
|
||||
let `Hex s = MBytes.to_hex (MBytes_buffer.to_mbytes buf) in
|
||||
s
|
||||
|
||||
let assert_hex_eq buf =
|
||||
Assert.equal ~prn:(fun x -> x) (hex_of_buffer buf)
|
||||
|
Loading…
Reference in New Issue
Block a user