Alpha: remove index of public keys

For delegate keys, we now use the revealed key of the associated
delegate contract.
This commit is contained in:
Grégoire Henry 2018-02-21 22:08:12 +01:00 committed by Benjamin Canou
parent 92f5ad6212
commit 6d900e3e52
17 changed files with 39 additions and 221 deletions

View File

@ -154,17 +154,3 @@ let may_check_key sourcePubKey sourcePubKeyHash =
(failure "Invalid public key in `client_proto_endorsement`")
| None ->
return ()
let check_public_key cctxt block ?src_pk src_pk_hash =
Alpha_services.Delegate.Key.get cctxt block src_pk_hash >>= function
| Error errors ->
begin
match src_pk with
| None ->
failwith "Unknown public key@ %a" pp_print_error errors
| Some key ->
may_check_key src_pk src_pk_hash >>=? fun () ->
return (Some key)
end
| Ok _ -> return None

View File

@ -53,13 +53,6 @@ val get_delegate:
Contract.t ->
public_key_hash tzresult Lwt.t
val check_public_key :
#Proto_alpha.rpc_context ->
Block_services.block ->
?src_pk:public_key ->
public_key_hash ->
public_key option tzresult Lwt.t
module Contract_tags : module type of Client_tags.Tags (struct
let name = "contract"
end)

View File

@ -37,7 +37,6 @@
"Level_storage",
"Nonce_storage",
"Seed_storage",
"Public_key_storage",
"Roll_storage",
"Contract_storage",
"Reward_storage",

View File

@ -94,8 +94,6 @@ module Constants = struct
constants.michelson_maximum_type_size
end
module Delegates_pubkey = Public_key_storage
module Voting_period = Voting_period_repr
module Level = struct

View File

@ -275,23 +275,6 @@ module Constants : sig
val michelson_maximum_type_size: context -> int
end
(** Global storage for all delegates public keys *)
module Delegates_pubkey : sig
val get:
context -> public_key_hash -> public_key tzresult Lwt.t
val get_option:
context -> public_key_hash -> public_key option tzresult Lwt.t
val reveal:
context -> public_key_hash -> public_key -> context tzresult Lwt.t
val remove:
context -> public_key_hash -> context Lwt.t
val list:
context -> (public_key_hash * public_key) list Lwt.t
end
module Voting_period : sig
include BASIC_DATA
@ -423,6 +406,7 @@ module Contract : sig
val get_delegate_opt:
context -> contract -> public_key_hash option tzresult Lwt.t
val is_delegatable:
context -> contract -> bool tzresult Lwt.t
val is_spendable:
@ -705,6 +689,9 @@ module Roll : sig
val endorsement_rights_owner:
context -> Level.t -> slot:int -> public_key tzresult Lwt.t
val delegate_pubkey:
context -> public_key_hash -> public_key tzresult Lwt.t
end
module Reward : sig

View File

@ -254,7 +254,7 @@ let apply_sourced_operation
pred_block block_prio operation content >>=? fun ctxt ->
return (ctxt, origination_nonce, None)
| Amendment_operation { source ; operation = content } ->
Delegates_pubkey.get ctxt source >>=? fun delegate ->
Roll.delegate_pubkey ctxt source >>=? fun delegate ->
Operation.check_signature delegate operation >>=? fun () ->
(* TODO, see how to extract the public key hash after this operation to
pass it to apply_delegate_operation_content *)

View File

@ -13,7 +13,6 @@ type account = {
}
let init_account ctxt account =
Storage.Public_key.init ctxt account.public_key_hash account.public_key >>=? fun ctxt ->
let contract = Contract_repr.implicit_contract account.public_key_hash in
Contract_storage.credit ctxt contract
Constants_repr.bootstrap_wealth >>=? fun ctxt ->

View File

@ -18,7 +18,6 @@ type error +=
| Inconsistent_public_key of Ed25519.Public_key.t * Ed25519.Public_key.t (* `Permanent *)
| Missing_public_key of Ed25519.Public_key_hash.t (* `Permanent *)
| Failure of string (* `Permanent *)
| Unregistred_delegate of Ed25519.Public_key_hash.t (* `Permanent *)
let () =
register_error_kind
@ -151,18 +150,7 @@ let () =
~pp:(fun ppf s -> Format.fprintf ppf "Contract_storage.Failure %S" s)
Data_encoding.(obj1 (req "message" string))
(function Failure s -> Some s | _ -> None)
(fun s -> Failure s) ;
register_error_kind
`Permanent
~id:"contract.manager.unregistred_delegate"
~title:"Unregistred delegate"
~description:"A contract cannot be delegated to an unregistred delegate"
~pp:(fun ppf (k) ->
Format.fprintf ppf "The delegate public key (with hash %a) is missing"
Ed25519.Public_key_hash.pp k)
Data_encoding.(obj1 (req "hash" Ed25519.Public_key_hash.encoding))
(function Unregistred_delegate (k) -> Some (k) | _ -> None)
(fun (k) -> Unregistred_delegate (k))
(fun s -> Failure s)
let failwith msg = fail (Failure msg)
@ -354,7 +342,7 @@ let set_delegate c contract delegate =
| Some pkh -> Ed25519.Public_key_hash.equal pkh delegate
| None -> false in
if not known_delegate || not (registred_delegate || self_delegation) then
fail (Unregistred_delegate delegate)
fail (Roll_storage.Unregistred_delegate delegate)
else if not (delegatable || self_delegation) then
fail (Non_delegatable_contract contract)
else

View File

@ -321,55 +321,5 @@ module Endorser = struct
end
module Key = struct
module S = struct
open Data_encoding
let custom_root =
RPC_path.(open_root / "context" / "key")
let pk_encoding =
(obj2
(req "hash" Ed25519.Public_key_hash.encoding)
(req "public_key" Ed25519.Public_key.encoding))
let list =
RPC_service.post_service
~description: "List the known public keys"
~query: RPC_query.empty
~input: empty
~output: (list pk_encoding)
custom_root
let get =
RPC_service.post_service
~description: "Fetch the stored public key"
~query: RPC_query.empty
~input: empty
~output: pk_encoding
RPC_path.(custom_root /: Ed25519.Public_key_hash.rpc_arg )
end
let () =
let open Services_registration in
register1 S.get begin fun ctxt hash () () ->
Delegates_pubkey.get ctxt hash >>=? fun pk ->
return (hash, pk)
end ;
register0 S.list begin fun ctxt () () ->
Delegates_pubkey.list ctxt >>= return
end
let list ctxt block =
RPC_context.make_call0 S.list ctxt block () ()
let get ctxt block pkh =
RPC_context.make_call1 S.get ctxt block pkh () ()
end
let baking_rights = Baker.I.baking_rights
let endorsement_rights = Endorser.I.endorsement_rights

View File

@ -45,19 +45,6 @@ module Endorser : sig
end
module Key : sig
val list:
'a #RPC_context.simple -> 'a ->
(Ed25519.Public_key_hash.t * Ed25519.Public_key.t) list shell_tzresult Lwt.t
val get:
'a #RPC_context.simple -> 'a ->
Ed25519.Public_key_hash.t ->
(Ed25519.Public_key_hash.t * Ed25519.Public_key.t) shell_tzresult Lwt.t
end
(* temporary export *)
val endorsement_rights:
Alpha_context.t ->

View File

@ -477,7 +477,7 @@ module Parse = struct
| Some key -> return key
| None ->
Contract.get_manager ctxt op.source >>=? fun manager ->
Delegates_pubkey.get ctxt manager
Roll.delegate_pubkey ctxt manager
end >>=? fun public_key ->
Operation.check_signature public_key
{ signature ; shell ; contents ; hash = Operation_hash.zero }
@ -487,7 +487,7 @@ module Parse = struct
Operation.check_signature public_key
{ signature ; shell ; contents ; hash = Operation_hash.zero }
| Sourced_operations (Amendment_operation { source ; _ }) ->
Delegates_pubkey.get ctxt source >>=? fun source ->
Roll.delegate_pubkey ctxt source >>=? fun source ->
Operation.check_signature source
{ signature ; shell ; contents ; hash = Operation_hash.zero }
| Sourced_operations (Dictator_operation _) ->

View File

@ -1,50 +0,0 @@
(**************************************************************************)
(* *)
(* Copyright (c) 2014 - 2018. *)
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
(* *)
(* All rights reserved. No warranty, explicit or implicit, provided. *)
(* *)
(**************************************************************************)
open Ed25519
type error += Inconsistent_hash of Public_key.t * Public_key_hash.t * Public_key_hash.t
let () =
register_error_kind
`Permanent
~id:"public_key.inconsistent_hash"
~title:"Inconsistent public key hash"
~description:"A revealed public key is inconsistent with the announced hash"
~pp:(fun ppf (k, eh, ph) ->
Format.fprintf ppf "Hash of public key %s is not %a as announced but %a"
(Public_key.to_b58check k)
Public_key_hash.pp ph
Public_key_hash.pp eh)
Data_encoding.(obj3
(req "public_key" Public_key.encoding)
(req "expected_hash" Public_key_hash.encoding)
(req "provided_hash" Public_key_hash.encoding))
(function Inconsistent_hash (k, eh, ph) -> Some (k, eh, ph) | _ -> None)
(fun (k, eh, ph) -> Inconsistent_hash (k, eh, ph))
let get = Storage.Public_key.get
let get_option = Storage.Public_key.get_option
let reveal c hash key =
let actual_hash = Ed25519.Public_key.hash key in
if Ed25519.Public_key_hash.equal hash actual_hash then
Storage.Public_key.init_set c hash key >>= return
else
fail (Inconsistent_hash (key, actual_hash, hash))
let remove = Storage.Public_key.remove
let list ctxt =
Storage.Public_key.fold ctxt
~init:[]
~f:begin fun pk_h pk acc ->
Lwt.return @@ (pk_h, pk) :: acc
end

View File

@ -1,24 +0,0 @@
(**************************************************************************)
(* *)
(* Copyright (c) 2014 - 2018. *)
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
(* *)
(* All rights reserved. No warranty, explicit or implicit, provided. *)
(* *)
(**************************************************************************)
open Ed25519
type error += Inconsistent_hash of Public_key.t * Public_key_hash.t * Public_key_hash.t
val get:
Raw_context.t -> Public_key_hash.t -> Public_key.t tzresult Lwt.t
val get_option:
Raw_context.t -> Public_key_hash.t -> Public_key.t option tzresult Lwt.t
val reveal:
Raw_context.t -> Public_key_hash.t -> Public_key.t -> Raw_context.t tzresult Lwt.t
val remove:
Raw_context.t -> Public_key_hash.t -> Raw_context.t Lwt.t
val list:
Raw_context.t -> (Public_key_hash.t * Public_key.t) list Lwt.t

View File

@ -12,14 +12,35 @@ type error +=
| No_roll_in_contract
| Deleted_contract_owning_rolls
| No_roll_snapshot_for_cycle of Cycle_repr.t
| Unregistred_delegate of Ed25519.Public_key_hash.t (* `Permanent *)
let () =
register_error_kind
`Permanent
~id:"contract.manager.unregistred_delegate"
~title:"Unregistred delegate"
~description:"A contract cannot be delegated to an unregistred delegate"
~pp:(fun ppf (k) ->
Format.fprintf ppf "The provided public key (with hash %a) is \
\ not registred as valid delegate key."
Ed25519.Public_key_hash.pp k)
Data_encoding.(obj1 (req "hash" Ed25519.Public_key_hash.encoding))
(function Unregistred_delegate (k) -> Some (k) | _ -> None)
(fun (k) -> Unregistred_delegate (k))
let get_contract_delegate c contract =
Storage.Contract.Delegate.get_option c contract
let get_contract_delegate_at_cycle c cycle contract =
match Contract_repr.is_implicit contract with
| Some manager -> return (Some manager)
| None -> Storage.Contract.Delegate.Snapshot.get_option c (cycle, contract)
Storage.Contract.Delegate.Snapshot.get_option c (cycle, contract)
let delegate_pubkey ctxt delegate =
Storage.Contract.Manager.get_option ctxt
(Contract_repr.implicit_contract delegate) >>=? function
| None | Some (Manager_repr.Hash _) ->
fail (Unregistred_delegate delegate)
| Some (Manager_repr.Public_key pk) ->
return pk
let clear_cycle c cycle =
Storage.Roll.Last_for_cycle.delete c cycle >>=? fun c ->
@ -78,10 +99,7 @@ module Random = struct
| None ->
loop sequence
| Some delegate ->
Public_key_storage.get_option c delegate >>=? function
| None -> loop sequence
| Some delegate -> return delegate
in
delegate_pubkey c delegate in
Storage.Roll.Owner.snapshot_exists c cycle >>= fun snapshot_exists ->
fail_unless snapshot_exists (No_roll_snapshot_for_cycle cycle) >>=? fun () ->
loop sequence

View File

@ -20,6 +20,7 @@
type error +=
| Consume_roll_change
| No_roll_in_contract
| Unregistred_delegate of Ed25519.Public_key_hash.t (* `Permanent *)
val init : Raw_context.t -> Raw_context.t tzresult Lwt.t
@ -57,6 +58,10 @@ module Contract : sig
end
val delegate_pubkey:
Raw_context.t -> Ed25519.Public_key_hash.t ->
Ed25519.Public_key.t tzresult Lwt.t
(**/**)
val get_contract_delegate:

View File

@ -308,16 +308,6 @@ module Vote = struct
end
(** Keys *)
module Public_key =
Make_indexed_data_storage
(Make_subcontext
(Raw_context)
(struct let name = ["public_keys"; "ed25519"] end))
(Ed25519.Public_key_hash)
(Make_value(Ed25519.Public_key))
(** Seed *)
module Seed = struct

View File

@ -188,14 +188,6 @@ module Vote : sig
end
(** Keys *)
module Public_key : Indexed_data_storage
with type key = Ed25519.Public_key_hash.t
and type value = Ed25519.Public_key.t
and type t := Raw_context.t
(** Seed *)
module Seed : sig