Ledger: add support for animal names in URI

This commit is contained in:
Vincent Bernardoff 2018-10-02 19:43:49 +08:00 committed by Benjamin Canou
parent 50f367e27b
commit 4fa4ab0b8f
No known key found for this signature in database
GPG Key ID: 73607948459DC5F8

View File

@ -125,6 +125,39 @@ let () =
(function LedgerError e -> Some e | _ -> None) (function LedgerError e -> Some e | _ -> None)
(fun e -> LedgerError e) (fun e -> LedgerError e)
type id =
| Animals of Ledger_names.t * Ledgerwallet_tezos.curve
| Pkh of Signature.Public_key_hash.t
let pp_id ppf = function
| Pkh pkh -> Signature.Public_key_hash.pp ppf pkh
| Animals (cthd, curve) ->
Format.fprintf ppf "%a/%a" Ledger_names.pp cthd
Ledgerwallet_tezos.pp_curve curve
let parse_animals animals =
match String.split '-' animals with
| [c; t; h; d] -> Some { Ledger_names.c ; t ; h ; d }
| _ -> None
let id_of_uri uri =
let host = Uri.host uri in
match Option.apply host
~f:Signature.Public_key_hash.of_b58check_opt with
| Some pkh -> return (Pkh pkh)
| None ->
match Option.apply host ~f:parse_animals,
Option.apply (List.hd_opt (String.split '/' (Uri.path uri)))
~f:Ledgerwallet_tezos.curve_of_string with
| Some animals, Some curve ->
return (Animals (animals, curve))
| _ ->
failwith "No public key hash or animal names in %a"
Uri.pp_hum uri
let id_of_pk_uri (uri : pk_uri) = id_of_uri (uri :> Uri.t)
let id_of_sk_uri (uri : sk_uri) = id_of_uri (uri :> Uri.t)
let wrap_ledger_cmd f = let wrap_ledger_cmd f =
let buf = Buffer.create 100 in let buf = Buffer.create 100 in
let pp = Format.formatter_of_buffer buf in let pp = Format.formatter_of_buffer buf in
@ -179,10 +212,12 @@ module Ledger = struct
device_info : Hidapi.device_info ; device_info : Hidapi.device_info ;
version : Ledgerwallet_tezos.Version.t ; version : Ledgerwallet_tezos.Version.t ;
git_commit : string option ; git_commit : string option ;
of_curve : (Ledgerwallet_tezos.curve * (Signature.Public_key.t * of_curve : (Ledgerwallet_tezos.curve *
Signature.Public_key_hash.t)) list ; (Signature.Public_key.t *
of_pkh : (Signature.Public_key_hash.t * (Signature.Public_key.t * Signature.Public_key_hash.t)) list ;
Ledgerwallet_tezos.curve)) list ; of_pkh : (Signature.Public_key_hash.t *
(Signature.Public_key.t *
Ledgerwallet_tezos.curve)) list ;
} }
let create ?git_commit ~device_info ~version ~of_curve ~of_pkh () = let create ?git_commit ~device_info ~version ~of_curve ~of_pkh () =
@ -195,26 +230,39 @@ module Ledger = struct
else else
[ Ed25519 ; Secp256k1 ; Secp256r1 ] [ Ed25519 ; Secp256k1 ; Secp256r1 ]
let of_hidapi ?pkh device_info h = let animals_of_pkh pkh =
let find_ledgers ?git_commit version = pkh |> Signature.Public_key_hash.to_string |>
fold_left_s begin fun (pkh_found, of_curve, of_pkh) curve -> Ledger_names.crouching_tiger
get_public_key h curve [] >>|? fun pk ->
let cur_pkh = Signature.Public_key.hash pk in let find_ledgers ?id ?git_commit h device_info version =
pkh_found || fold_left_s begin fun (ledger_found, of_curve, of_pkh) curve ->
Option.unopt_map pkh ~default:false ~f:(fun pkh -> pkh = cur_pkh), get_public_key h curve [] >>|? fun pk ->
(curve, (pk, cur_pkh)) :: of_curve, let cur_pkh = Signature.Public_key.hash pk in
(cur_pkh, (pk, curve)) :: of_pkh let cur_animals = animals_of_pkh cur_pkh in
end (false, [], []) (curves version) log_info "Found PK: %a" Signature.Public_key.pp pk ;
>>=? fun (pkh_found, of_curve, of_pkh) -> log_info "Found PKH: %a" Signature.Public_key_hash.pp cur_pkh ;
match pkh with log_info "Found Animals: %a" Ledger_names.pp cur_animals ;
| None -> ledger_found ||
return (Some (create ?git_commit ~device_info ~version (match id with
~of_curve ~of_pkh ())) | Some (Pkh pkh) when pkh = cur_pkh -> true
| Some _ when pkh_found -> | Some (Animals (animals, _)) when animals = cur_animals -> true
return (Some (create ?git_commit ~device_info ~version | _ -> false),
~of_curve ~of_pkh ())) (curve, (pk, cur_pkh)) :: of_curve,
| _ -> return None (cur_pkh, (pk, curve)) :: of_pkh
in end (false, [], []) (curves version)
>>=? fun (ledger_found, of_curve, of_pkh) ->
match id with
| None ->
return_some
(create ?git_commit ~device_info ~version
~of_curve ~of_pkh ())
| Some _ when ledger_found ->
return_some
(create ?git_commit ~device_info ~version
~of_curve ~of_pkh ())
| _ -> return None
let of_hidapi ?id device_info h =
let buf = Buffer.create 100 in let buf = Buffer.create 100 in
let pp = Format.formatter_of_buffer buf in let pp = Format.formatter_of_buffer buf in
let version = Ledgerwallet_tezos.get_version ~pp h in let version = Ledgerwallet_tezos.get_version ~pp h in
@ -231,13 +279,16 @@ module Ledger = struct
} in } in
warn "Impossible to read Tezos version, assuming %a" warn "Impossible to read Tezos version, assuming %a"
Ledgerwallet_tezos.Version.pp version ; Ledgerwallet_tezos.Version.pp version ;
find_ledgers version find_ledgers ?id h device_info version
| Error e -> | Error e ->
warn "WARNING:@ The device at [%s] is not a Tezos application@ (%a)" warn "WARNING:@ The device at [%s] is not a Tezos application@ \
%a"
device_info.Hidapi.path device_info.Hidapi.path
Ledgerwallet.Transport.pp_error e ; Ledgerwallet.Transport.pp_error e ;
return None return None
| Ok ({ major; minor; patch; _ } as version) -> | Ok ({ major; minor; patch; _ } as version) ->
log_info "Found a %a application at [%s]"
Ledgerwallet_tezos.Version.pp version device_info.path ;
begin begin
if (major, minor, patch) >= (1, 4, 0) then if (major, minor, patch) >= (1, 4, 0) then
wrap_ledger_cmd (fun pp -> wrap_ledger_cmd (fun pp ->
@ -245,29 +296,31 @@ module Ledger = struct
return_some c return_some c
else return_none else return_none
end >>=? fun git_commit -> end >>=? fun git_commit ->
find_ledgers ?git_commit version find_ledgers ?id ?git_commit h device_info version
end end
let find_ledgers ?pkh () = let find_ledgers ?id () =
let ledgers = Hidapi.enumerate ~vendor_id ~product_id () in let ledgers = Hidapi.enumerate ~vendor_id ~product_id () in
log_info "Found %d Ledger(s)" (List.length ledgers) ;
filter_map_s begin fun device_info -> filter_map_s begin fun device_info ->
log_info "Processing Ledger at path [%s]" device_info.Hidapi.path ;
match Hidapi.(open_path device_info.path) with match Hidapi.(open_path device_info.path) with
| None -> return_none | None -> return_none
| Some h -> | Some h ->
Lwt.finalize Lwt.finalize
(fun () -> Ledger.of_hidapi ?pkh device_info h) (fun () -> Ledger.of_hidapi ?id device_info h)
(fun () -> Hidapi.close h ; Lwt.return_unit) (fun () -> Hidapi.close h ; Lwt.return_unit)
end ledgers end ledgers
let with_ledger pkh f = let with_ledger id f =
find_ledgers ~pkh () >>=? function find_ledgers ~id () >>=? function
| [] -> | [] ->
failwith "No Ledger found for %a" Signature.Public_key_hash.pp pkh failwith "No Ledger found for %a" pp_id id
| { device_info ; version ; of_curve ; of_pkh ; _ } :: _ -> | { device_info ; version ; of_curve ; of_pkh ; _ } :: _ ->
match Hidapi.open_path device_info.path with match Hidapi.open_path device_info.path with
| None -> | None ->
failwith "Cannot open Ledger %a at path %s" failwith "Cannot open Ledger %a at path %s"
Signature.Public_key_hash.pp pkh device_info.path pp_id id device_info.path
| Some h -> | Some h ->
Lwt.finalize Lwt.finalize
(fun () -> f h version of_curve of_pkh) (fun () -> f h version of_curve of_pkh)
@ -289,37 +342,31 @@ let int32_of_path_element_exn x =
let neuterize (sk : sk_uri) = return (make_pk_uri (sk :> Uri.t)) let neuterize (sk : sk_uri) = return (make_pk_uri (sk :> Uri.t))
let pkh_of_pk_uri (uri : pk_uri) =
let uri = (uri :> Uri.t) in
match Option.apply (Uri.host uri)
~f:Signature.Public_key_hash.of_b58check_opt with
| None ->
failwith "No public key hash in %a" Uri.pp_hum uri
| Some pkh -> return pkh
let pkh_of_sk_uri (uri : sk_uri) =
let uri = (uri :> Uri.t) in
match Option.apply (Uri.host uri)
~f:Signature.Public_key_hash.of_b58check_opt with
| None ->
failwith "No public key hash in %a" Uri.pp_hum uri
| Some pkh -> return pkh
let path_of_sk_uri (uri : sk_uri) = let path_of_sk_uri (uri : sk_uri) =
TzString.split_path (Uri.path (uri :> Uri.t)) |> match TzString.split_path (Uri.path (uri :> Uri.t)) with
List.map int32_of_path_element_exn | [] -> []
| curve :: path when Ledgerwallet_tezos.curve_of_string curve <> None ->
List.map int32_of_path_element_exn path
| path -> List.map int32_of_path_element_exn path
let path_of_pk_uri (uri : pk_uri) = let path_of_pk_uri (uri : pk_uri) =
TzString.split_path (Uri.path (uri :> Uri.t)) |> match TzString.split_path (Uri.path (uri :> Uri.t)) with
List.map int32_of_path_element_exn | [] -> []
| curve :: path when Ledgerwallet_tezos.curve_of_string curve <> None ->
List.map int32_of_path_element_exn path
| path -> List.map int32_of_path_element_exn path
let public_key (pk_uri : pk_uri) = let public_key (pk_uri : pk_uri) =
let find_ledger of_pkh = function
| Pkh pkh -> snd (List.assoc pkh of_pkh)
| Animals (_, curve) -> curve
in
match Hashtbl.find_opt pks pk_uri with match Hashtbl.find_opt pks pk_uri with
| Some pk -> return pk | Some pk -> return pk
| None -> | None ->
pkh_of_pk_uri pk_uri >>=? fun pkh -> id_of_pk_uri pk_uri >>=? fun id ->
with_ledger pkh begin fun ledger _version _of_curve of_pkh -> with_ledger id begin fun ledger _version _of_curve of_pkh ->
let _root_pk, curve = List.assoc pkh of_pkh in let curve = find_ledger of_pkh id in
let path = path_of_pk_uri pk_uri in let path = path_of_pk_uri pk_uri in
get_public_key ledger curve path >>=? fun pk -> get_public_key ledger curve path >>=? fun pk ->
let pkh = Signature.Public_key.hash pk in let pkh = Signature.Public_key.hash pk in
@ -337,15 +384,19 @@ let public_key_hash pk_uri =
public_key pk_uri >>=? fun pk -> public_key pk_uri >>=? fun pk ->
return (Hashtbl.find pkhs pk_uri, Some pk) return (Hashtbl.find pkhs pk_uri, Some pk)
let curve_of_id = function
| Pkh pkh -> curve_of_pkh pkh
| Animals (_, curve) -> curve
let sign ?watermark sk_uri msg = let sign ?watermark sk_uri msg =
pkh_of_sk_uri sk_uri >>=? fun pkh -> id_of_sk_uri sk_uri >>=? fun id ->
with_ledger pkh begin fun ledger { major; minor; patch; _ } _of_curve _of_pkh -> with_ledger id begin fun ledger { major; minor; patch; _ } _of_curve _of_pkh ->
let msg = Option.unopt_map watermark let msg = Option.unopt_map watermark
~default:msg ~f:begin fun watermark -> ~default:msg ~f:begin fun watermark ->
MBytes.concat "" [Signature.bytes_of_watermark watermark ; MBytes.concat "" [Signature.bytes_of_watermark watermark ;
msg] msg]
end in end in
let curve = curve_of_pkh pkh in let curve = curve_of_id id in
let path = tezos_root @ path_of_sk_uri sk_uri in let path = tezos_root @ path_of_sk_uri sk_uri in
let msg_len = MBytes.length msg in let msg_len = MBytes.length msg in
wrap_ledger_cmd begin fun pp -> wrap_ledger_cmd begin fun pp ->
@ -411,43 +462,27 @@ let commands =
(match git_commit with None -> "unknown" | Some c -> c) (match git_commit with None -> "unknown" | Some c -> c)
manufacturer product path >>= fun () -> manufacturer product path >>= fun () ->
let of_curve = List.rev of_curve in let of_curve = List.rev of_curve in
begin match List.hd_opt of_curve with
| None ->
failwith "No curve available, upgrade Ledger software"
| Some (_, (_, pkh)) ->
return (Ledger_names.crouching_tiger
(Signature.Public_key_hash.to_string pkh))
end >>=? fun animals ->
cctxt#message cctxt#message
"@[<v 0>@,To add the root key of this ledger, use one of@,\ "@[<v 0>@,To use keys at BIP32 path \
\ @[<v 0>%a@]@,\ m/44'/1729'/0'/0' (default Tezos key path), use \
Each of these tz* is a valid Tezos address.@,\ one of@, @[<v 0>%a@]@]"
@,\
To use a derived address, add a hardened BIP32 path suffix \
at the end of the URI.@,\
For instance, to use keys at BIP32 path m/44'/1729'/0'/0', use one of@,\
\ @[<v 0>%a@]@,\
In this case, your Tezos address will be a derived tz*.@,\
It will be displayed when you do the import, \
or using command `show ledger path`.@]"
(Format.pp_print_list (Format.pp_print_list
(fun ppf (curve, (_pk, pkh)) -> (fun ppf (curve, _) ->
Format.fprintf ppf Format.fprintf ppf
"tezos-client import secret key ledger_%s_%s ledger://%a # %s signature" "tezos-client import secret key \
ledger_%s_%a_0_0 \"ledger://%a/0'/0'\" # \
%a signature"
(Sys.getenv "USER") (Sys.getenv "USER")
(match curve with Ledgerwallet_tezos.pp_curve_short curve
| Ledgerwallet_tezos.Ed25519 -> "ed" pp_id (Animals (animals, curve))
| Ledgerwallet_tezos.Secp256k1 -> "secp" Ledgerwallet_tezos.pp_curve curve))
| Ledgerwallet_tezos.Secp256r1 -> "p2")
Signature.Public_key_hash.pp pkh
(match curve with
| Ledgerwallet_tezos.Ed25519 -> "Ed25519"
| Ledgerwallet_tezos.Secp256k1 -> "Secp256k1"
| Ledgerwallet_tezos.Secp256r1 -> "P-256")))
of_curve
(Format.pp_print_list
(fun ppf (curve, (_pk, pkh)) ->
Format.fprintf ppf
"tezos-client import secret key ledger_%s_%s_0_0 \"ledger://%a/0'/0'\""
(Sys.getenv "USER")
(match curve with
| Ledgerwallet_tezos.Ed25519 -> "ed"
| Ledgerwallet_tezos.Secp256k1 -> "secp"
| Ledgerwallet_tezos.Secp256r1 -> "p2")
Signature.Public_key_hash.pp pkh))
of_curve >>= fun () -> of_curve >>= fun () ->
return_unit return_unit
end ledgers) ; end ledgers) ;
@ -460,10 +495,10 @@ let commands =
@@ stop) @@ stop)
(fun () sk_uri (cctxt : Client_context.io_wallet) -> (fun () sk_uri (cctxt : Client_context.io_wallet) ->
neuterize sk_uri >>=? fun pk_uri -> neuterize sk_uri >>=? fun pk_uri ->
pkh_of_pk_uri pk_uri >>=? fun pkh -> id_of_pk_uri pk_uri >>=? fun id ->
find_ledgers ~pkh () >>=? function find_ledgers ~id () >>=? function
| [] -> | [] ->
failwith "No ledger found for %a" Signature.Public_key_hash.pp pkh failwith "No ledger found for %a" pp_id id
| { Ledger.device_info ; version ; _ } :: _ -> | { Ledger.device_info ; version ; _ } :: _ ->
let manufacturer = let manufacturer =
Option.unopt ~default:"(none)" device_info.manufacturer_string in Option.unopt ~default:"(none)" device_info.manufacturer_string in
@ -500,8 +535,8 @@ let commands =
@@ Public_key.alias_param @@ Public_key.alias_param
@@ stop) @@ stop)
(fun () (name, (pk_uri, _)) (cctxt : Client_context.io_wallet) -> (fun () (name, (pk_uri, _)) (cctxt : Client_context.io_wallet) ->
pkh_of_pk_uri pk_uri >>=? fun root_pkh -> id_of_pk_uri pk_uri >>=? fun root_id ->
with_ledger root_pkh begin fun h _version _of_curve _to_curve -> with_ledger root_id begin fun h _version _of_curve _to_curve ->
wrap_ledger_cmd begin fun pp -> wrap_ledger_cmd begin fun pp ->
Ledgerwallet_tezos.get_authorized_key ~pp h Ledgerwallet_tezos.get_authorized_key ~pp h
end >>=? function end >>=? function
@ -524,10 +559,10 @@ let commands =
@@ Public_key.alias_param @@ Public_key.alias_param
@@ stop) @@ stop)
(fun () (_, (pk_uri, _)) (cctxt : Client_context.io_wallet) -> (fun () (_, (pk_uri, _)) (cctxt : Client_context.io_wallet) ->
pkh_of_pk_uri pk_uri >>=? fun root_pkh -> id_of_pk_uri pk_uri >>=? fun root_id ->
with_ledger root_pkh begin fun h _version _of_curve _to_curve -> with_ledger root_id begin fun h _version _of_curve _of_pkh ->
let path = path_of_pk_uri pk_uri in let path = path_of_pk_uri pk_uri in
let curve = curve_of_pkh root_pkh in let curve = curve_of_id root_id in
get_public_key ~authorize_baking:true h curve path >>=? fun pk -> get_public_key ~authorize_baking:true h curve path >>=? fun pk ->
let pkh = Signature.Public_key.hash pk in let pkh = Signature.Public_key.hash pk in
cctxt#message cctxt#message
@ -545,8 +580,8 @@ let commands =
@@ Client_keys.sk_uri_param @@ Client_keys.sk_uri_param
@@ stop) @@ stop)
(fun () sk_uri (cctxt : Client_context.io_wallet) -> (fun () sk_uri (cctxt : Client_context.io_wallet) ->
pkh_of_sk_uri sk_uri >>=? fun pkh -> id_of_sk_uri sk_uri >>=? fun id ->
with_ledger pkh begin fun h version _ _ -> with_ledger id begin fun h version _ _ ->
match version.app_class with match version.app_class with
| Tezos -> | Tezos ->
failwith "Fatal: this operation is only valid with TezBake" failwith "Fatal: this operation is only valid with TezBake"
@ -556,7 +591,7 @@ let commands =
end >>=? fun hwm -> end >>=? fun hwm ->
cctxt#message cctxt#message
"@[<v 0>%a has high water mark: %ld@]" "@[<v 0>%a has high water mark: %ld@]"
Signature.Public_key_hash.pp pkh hwm >>= fun () -> pp_id id hwm >>= fun () ->
return_unit return_unit
end end
) ; ) ;
@ -575,8 +610,8 @@ let commands =
with _ -> failwith "%s is not an int32 value" s))) with _ -> failwith "%s is not an int32 value" s)))
@@ stop) @@ stop)
(fun () sk_uri hwm (cctxt : Client_context.io_wallet) -> (fun () sk_uri hwm (cctxt : Client_context.io_wallet) ->
pkh_of_sk_uri sk_uri >>=? fun pkh -> id_of_sk_uri sk_uri >>=? fun id ->
with_ledger pkh begin fun h version _ _ -> with_ledger id begin fun h version _ _ ->
match version.app_class with match version.app_class with
| Tezos -> | Tezos ->
failwith "Fatal: this operation is only valid with TezBake" failwith "Fatal: this operation is only valid with TezBake"
@ -589,7 +624,7 @@ let commands =
end >>=? fun new_hwm -> end >>=? fun new_hwm ->
cctxt#message cctxt#message
"@[<v 0>%a has now high water mark: %ld@]" "@[<v 0>%a has now high water mark: %ld@]"
Signature.Public_key_hash.pp pkh new_hwm >>= fun () -> pp_id id new_hwm >>= fun () ->
return_unit return_unit
end end
) ; ) ;