From 8d3f03878a6ba06ed0dc8fd5652ada4e00de6160 Mon Sep 17 00:00:00 2001 From: Zaynah Dargaye Date: Wed, 6 Jul 2022 00:52:45 +0200 Subject: [PATCH 1/3] Proto/test: add errors in API and modify helpers --- src/proto_alpha/lib_protocol/amendment.mli | 4 ++ src/proto_alpha/lib_protocol/apply.mli | 1 + .../lib_protocol/test/helpers/block.ml | 9 +++ .../lib_protocol/test/helpers/block.mli | 3 + .../lib_protocol/test/helpers/context.ml | 9 +++ .../lib_protocol/test/helpers/context.mli | 11 ++++ .../lib_protocol/test/helpers/incremental.ml | 6 ++ .../lib_protocol/test/helpers/incremental.mli | 9 +++ .../lib_protocol/test/helpers/op.ml | 51 +++++++++++----- .../lib_protocol/test/helpers/op.mli | 58 ++++++++++++++++++- 10 files changed, 144 insertions(+), 17 deletions(-) diff --git a/src/proto_alpha/lib_protocol/amendment.mli b/src/proto_alpha/lib_protocol/amendment.mli index 38a6c5efb96c..fda070b1ac8d 100644 --- a/src/proto_alpha/lib_protocol/amendment.mli +++ b/src/proto_alpha/lib_protocol/amendment.mli @@ -86,6 +86,10 @@ val record_proposals : type error += | Invalid_proposal + | Unexpected_proposal + | Unauthorized_proposal + | Too_many_proposals + | Empty_proposal | Unexpected_ballot | Unauthorized_ballot | Duplicate_ballot diff --git a/src/proto_alpha/lib_protocol/apply.mli b/src/proto_alpha/lib_protocol/apply.mli index dca373aa8f8d..a72fdd8dcce9 100644 --- a/src/proto_alpha/lib_protocol/apply.mli +++ b/src/proto_alpha/lib_protocol/apply.mli @@ -43,6 +43,7 @@ type error += | Tx_rollup_invalid_transaction_ticket_amount | Sc_rollup_feature_disabled | Empty_transaction of Contract.t + | Wrong_voting_period of {expected : int32; provided : int32} val begin_partial_construction : context -> diff --git a/src/proto_alpha/lib_protocol/test/helpers/block.ml b/src/proto_alpha/lib_protocol/test/helpers/block.ml index e802f98e9156..76c56d2d04bc 100644 --- a/src/proto_alpha/lib_protocol/test/helpers/block.ml +++ b/src/proto_alpha/lib_protocol/test/helpers/block.ml @@ -51,6 +51,15 @@ let rpc_ctxt = rpc_context Plugin.RPC.rpc_services +let to_alpha_ctxt b = + Alpha_context.prepare + b.context + ~level:b.header.shell.level + ~predecessor_timestamp:b.header.shell.timestamp + ~timestamp:b.header.shell.timestamp + >|= Environment.wrap_tzresult + >>=? fun (ctxt, _balance_updates, _migration_results) -> return ctxt + (******** Policies ***********) (* Policies are functions that take a block and return a tuple diff --git a/src/proto_alpha/lib_protocol/test/helpers/block.mli b/src/proto_alpha/lib_protocol/test/helpers/block.mli index 79683b6841ea..dc3d70f88721 100644 --- a/src/proto_alpha/lib_protocol/test/helpers/block.mli +++ b/src/proto_alpha/lib_protocol/test/helpers/block.mli @@ -39,6 +39,9 @@ type block = t val rpc_ctxt : t Environment.RPC_context.simple +(** Build an alpha context using {!Alpha_context.prepare}. *) +val to_alpha_ctxt : t -> Alpha_context.t tzresult Lwt.t + (** Policies to select the next baker: - [By_round r] selects the baker at round [r] - [By_account pkh] selects the first slot for baker [pkh] diff --git a/src/proto_alpha/lib_protocol/test/helpers/context.ml b/src/proto_alpha/lib_protocol/test/helpers/context.ml index b99cbef8a1ac..f4a461f70e40 100644 --- a/src/proto_alpha/lib_protocol/test/helpers/context.ml +++ b/src/proto_alpha/lib_protocol/test/helpers/context.ml @@ -36,6 +36,10 @@ let level = function B b -> b.header.shell.level | I i -> Incremental.level i let get_level ctxt = level ctxt |> Raw_level.of_int32 |> Environment.wrap_tzresult +let to_alpha_ctxt = function + | B b -> Block.to_alpha_ctxt b + | I i -> return (Incremental.alpha_ctxt i) + let rpc_ctxt = object method call_proto_service0 @@ -260,6 +264,11 @@ module Vote = struct current_proposals : Protocol_hash.t list; remaining_proposals : int; } + + let recorded_proposal_count_for_delegate ctxt pkh = + to_alpha_ctxt ctxt >>=? fun alpha_ctxt -> + Vote.recorded_proposal_count_for_delegate alpha_ctxt pkh + >|= Environment.wrap_tzresult end module Contract = struct diff --git a/src/proto_alpha/lib_protocol/test/helpers/context.mli b/src/proto_alpha/lib_protocol/test/helpers/context.mli index 989d8480e16f..064f867e8d92 100644 --- a/src/proto_alpha/lib_protocol/test/helpers/context.mli +++ b/src/proto_alpha/lib_protocol/test/helpers/context.mli @@ -34,6 +34,10 @@ val branch : t -> Block_hash.t val get_level : t -> Raw_level.t tzresult +(** Either retrieve the alpha context (in the [Incremental] case) or + build one (in the [Block] case). *) +val to_alpha_ctxt : t -> Alpha_context.t tzresult Lwt.t + val get_endorsers : t -> Plugin.RPC.Validators.t list tzresult Lwt.t val get_first_different_endorsers : @@ -119,6 +123,13 @@ module Vote : sig current_proposals : Protocol_hash.t list; remaining_proposals : int; } + + (** See {!Vote_storage.recorded_proposal_count_for_delegate}. + + Note that unlike most functions in the current module, this one + does not call an RPC. *) + val recorded_proposal_count_for_delegate : + t -> public_key_hash -> int tzresult Lwt.t end module Contract : sig diff --git a/src/proto_alpha/lib_protocol/test/helpers/incremental.ml b/src/proto_alpha/lib_protocol/test/helpers/incremental.ml index 50db1fca0911..32c831150200 100644 --- a/src/proto_alpha/lib_protocol/test/helpers/incremental.ml +++ b/src/proto_alpha/lib_protocol/test/helpers/incremental.ml @@ -254,3 +254,9 @@ let finalize_block st = in let hash = Block_header.hash header in {Block.hash; header; operations; context = result.context} + +let assert_validate_operation_fails expect_failure op block = + let open Lwt_result_syntax in + let* i = begin_construction block in + let* _i = validate_operation ~expect_failure i op in + return_unit diff --git a/src/proto_alpha/lib_protocol/test/helpers/incremental.mli b/src/proto_alpha/lib_protocol/test/helpers/incremental.mli index 804a282f813d..72541d86ccfe 100644 --- a/src/proto_alpha/lib_protocol/test/helpers/incremental.mli +++ b/src/proto_alpha/lib_protocol/test/helpers/incremental.mli @@ -116,6 +116,15 @@ val add_operation : *) val finalize_block : incremental -> Block.t tzresult Lwt.t +(** [assert_validate_operation_fails expect_failure operation block] + calls {!begin_construction} on top of [block], then + {!validate_operation} with [~expect_failure]. *) +val assert_validate_operation_fails : + (tztrace -> unit tzresult Lwt.t) -> + Operation.packed -> + Block.t -> + unit tzresult Lwt.t + val rpc_ctxt : incremental Environment.RPC_context.simple val alpha_ctxt : incremental -> Alpha_context.context diff --git a/src/proto_alpha/lib_protocol/test/helpers/op.ml b/src/proto_alpha/lib_protocol/test/helpers/op.ml index 6cdcb9b87282..c532be84db2a 100644 --- a/src/proto_alpha/lib_protocol/test/helpers/op.ml +++ b/src/proto_alpha/lib_protocol/test/helpers/op.ml @@ -26,6 +26,11 @@ open Protocol open Alpha_context +let pack_operation ctxt signature contents = + let branch = Context.branch ctxt in + Operation.pack + ({shell = {branch}; protocol_data = {contents; signature}} : _ Operation.t) + let sign ?(watermark = Signature.Generic_operation) sk ctxt contents = let branch = Context.branch ctxt in let unsigned = @@ -560,21 +565,37 @@ let vdf_revelation ctxt solution = {contents = Single (Vdf_revelation {solution}); signature = None}; } -let proposals ctxt (pkh : Contract.t) proposals = - let source = Context.Contract.pkh pkh in - Context.Vote.get_current_period ctxt - >>=? fun {voting_period = {index; _}; _} -> - let op = Proposals {source; period = index; proposals} in - Account.find source >|=? fun account -> - sign account.sk ctxt (Contents_list (Single op)) - -let ballot ctxt (pkh : Contract.t) proposal ballot = - let source = Context.Contract.pkh pkh in - Context.Vote.get_current_period ctxt - >>=? fun {voting_period = {index; _}; _} -> - let op = Ballot {source; period = index; proposal; ballot} in - Account.find source >|=? fun account -> - sign account.sk ctxt (Contents_list (Single op)) +let get_period ?period ctxt = + let open Lwt_result_syntax in + match period with + | Some period -> return period + | None -> + let* current_period = Context.Vote.get_current_period ctxt in + return current_period.voting_period.index + +let proposals_contents ctxt proposer ?period proposals = + let open Lwt_result_syntax in + let source = Context.Contract.pkh proposer in + let* period = get_period ?period ctxt in + return (Single (Proposals {source; period; proposals})) + +let proposals ctxt proposer ?period proposals = + let open Lwt_result_syntax in + let* contents = proposals_contents ctxt proposer ?period proposals in + let* account = Account.find (Context.Contract.pkh proposer) in + return (sign account.sk ctxt (Contents_list contents)) + +let ballot_contents ctxt voter ?period proposal ballot = + let open Lwt_result_syntax in + let source = Context.Contract.pkh voter in + let* period = get_period ?period ctxt in + return (Single (Ballot {source; period; proposal; ballot})) + +let ballot ctxt voter ?period proposal ballot = + let open Lwt_result_syntax in + let* contents = ballot_contents ctxt voter ?period proposal ballot in + let* account = Account.find (Context.Contract.pkh voter) in + return (sign account.sk ctxt (Contents_list contents)) let dummy_script = let open Micheline in diff --git a/src/proto_alpha/lib_protocol/test/helpers/op.mli b/src/proto_alpha/lib_protocol/test/helpers/op.mli index 19575638e11c..5c9661760ca6 100644 --- a/src/proto_alpha/lib_protocol/test/helpers/op.mli +++ b/src/proto_alpha/lib_protocol/test/helpers/op.mli @@ -29,6 +29,21 @@ open Alpha_context (* TODO: https://gitlab.com/tezos/tezos/-/issues/3181 Improve documentation of the operation helpers *) +(** Assemble the given signature and [contents_list] into a + [packed_operation]. + + The context argument is used to retrieve the branch. + + If the [signature option] argument is [None], then the resulting + operation is unsigned. + + This function is mainly useful to craft an operation with a + missing or invalid signatue. Otherwise, it is often better to use + one of the helpers below: they handle the signature internally to + directly return well-signed operations. *) +val pack_operation : + Context.t -> signature option -> 'a contents_list -> packed_operation + val endorsement : ?delegate:public_key_hash * Slot.t list -> ?slot:Slot.t -> @@ -284,17 +299,56 @@ val seed_nonce_revelation : (** Reveals a VDF with a proof of correctness *) val vdf_revelation : Context.t -> Seed.vdf_solution -> Operation.packed -(** Propose a list of protocol hashes during the approval voting *) +(** Craft the [contents_list] for a Proposals operation. + + Invocation: [proposals_contents ctxt source ?period proposals]. + + @param period defaults to the index of the current voting period + in [ctxt]. *) +val proposals_contents : + Context.t -> + Contract.t -> + ?period:int32 -> + Protocol_hash.t list -> + Kind.proposals contents_list tzresult Lwt.t + +(** Craft a Proposals operation. + + Invocation: [proposals ctxt source ?period proposals]. + + @param period defaults to the index of the current voting period + in [ctxt]. *) val proposals : Context.t -> Contract.t -> + ?period:int32 -> Protocol_hash.t list -> Operation.packed tzresult Lwt.t -(** Cast a vote yay, nay or pass *) +(** Craft the [contents_list] for a Ballot operation. + + Invocation: [ballot_contents ctxt source ?period proposal ballot]. + + @param period defaults to the index of the current voting period + in [ctxt]. *) +val ballot_contents : + Context.t -> + Contract.t -> + ?period:int32 -> + Protocol_hash.t -> + Vote.ballot -> + Kind.ballot contents_list tzresult Lwt.t + +(** Craft a Ballot operation. + + Invocation: [ballot ctxt source ?period proposal ballot]. + + @param period defaults to the index of the current voting period + in [ctxt]. *) val ballot : Context.t -> Contract.t -> + ?period:int32 -> Protocol_hash.t -> Vote.ballot -> Operation.packed tzresult Lwt.t -- GitLab From cd55150e0ba5ac6c00497509f5a501cf0ebbdb14 Mon Sep 17 00:00:00 2001 From: Diane Gallois-Wong Date: Fri, 22 Jul 2022 18:05:33 +0200 Subject: [PATCH 2/3] Proto/test: clean up existing voting tests --- .../lib_protocol/alpha_context.mli | 10 + .../integration/operations/test_voting.ml | 186 +++++++++++------- src/proto_alpha/lib_protocol/vote_storage.ml | 10 +- src/proto_alpha/lib_protocol/vote_storage.mli | 10 + 4 files changed, 144 insertions(+), 72 deletions(-) diff --git a/src/proto_alpha/lib_protocol/alpha_context.mli b/src/proto_alpha/lib_protocol/alpha_context.mli index 7ca1a80b4f56..b115e31399f0 100644 --- a/src/proto_alpha/lib_protocol/alpha_context.mli +++ b/src/proto_alpha/lib_protocol/alpha_context.mli @@ -2633,8 +2633,18 @@ module Vote : sig type ballots = {yay : int64; nay : int64; pass : int64} + (** See {!Vote_storage.ballots_zero}. *) + val ballots_zero : ballots + + (** See {!Vote_storage.ballots_encoding} *) val ballots_encoding : ballots Data_encoding.t + (** See {!Vote_storage.equal_ballots}. *) + val equal_ballots : ballots -> ballots -> bool + + (** See {!Vote_storage.pp_ballots}. *) + val pp_ballots : Format.formatter -> ballots -> unit + val has_recorded_ballot : context -> public_key_hash -> bool Lwt.t val record_ballot : diff --git a/src/proto_alpha/lib_protocol/test/integration/operations/test_voting.ml b/src/proto_alpha/lib_protocol/test/integration/operations/test_voting.ml index 02f77a71a4c1..3319fad9089e 100644 --- a/src/proto_alpha/lib_protocol/test/integration/operations/test_voting.ml +++ b/src/proto_alpha/lib_protocol/test/integration/operations/test_voting.ml @@ -37,17 +37,8 @@ open Protocol open Alpha_context -(* missing stuff in Vote *) -let ballots_zero = Vote.{yay = 0L; nay = 0L; pass = 0L} +(** {2 Constants and ratios used in voting} -let ballots_equal b1 b2 = - Vote.(b1.yay = b2.yay && b1.nay = b2.nay && b1.pass = b2.pass) - -let ballots_pp ppf v = - Vote.( - Format.fprintf ppf "{ yay = %Ld ; nay = %Ld ; pass = %Ld" v.yay v.nay v.pass) - -(* constants and ratios used in voting: percent_mul denotes the percent multiplier initial_participation is 7000 that is, 7/10 * percent_mul the participation EMA ratio pr_ema_weight / den = 7 / 10 @@ -111,7 +102,7 @@ let protos = "ProtoALphaALphaALphaALphaALphaALphaALpha841f2cQqajX"; |] -(** helper functions *) +(** {2 Helper functions} *) let assert_period_kind expected_kind kind loc = if Stdlib.(expected_kind = kind) then return_unit @@ -153,48 +144,45 @@ let assert_period_remaining expected_remaining remaining loc = let assert_period ?expected_kind ?expected_index ?expected_position ?expected_remaining b loc = - Context.Vote.get_current_period (B b) - >>=? fun {voting_period; position; remaining} -> - (if Option.is_some expected_kind then - assert_period_kind - (WithExceptions.Option.get ~loc:__LOC__ expected_kind) - voting_period.kind - loc - else return_unit) - >>=? fun () -> - (if Option.is_some expected_index then - assert_period_index - (WithExceptions.Option.get ~loc:__LOC__ expected_index) - voting_period.index - loc - else return_unit) - >>=? fun () -> - (if Option.is_some expected_position then - assert_period_position - (WithExceptions.Option.get ~loc:__LOC__ expected_position) - position - loc - else return_unit) - >>=? fun () -> - if Option.is_some expected_remaining then - assert_period_remaining - (WithExceptions.Option.get ~loc:__LOC__ expected_remaining) - remaining - loc - else return_unit + let open Lwt_result_syntax in + let* {voting_period; position; remaining} = + Context.Vote.get_current_period (B b) + in + let* () = + match expected_kind with + | Some expected_kind -> + assert_period_kind expected_kind voting_period.kind loc + | None -> return_unit + in + let* () = + match expected_index with + | Some expected_index -> + assert_period_index expected_index voting_period.index loc + | None -> return_unit + in + let* () = + match expected_position with + | Some expected_position -> + assert_period_position expected_position position loc + | None -> return_unit + in + match expected_remaining with + | Some expected_remaining -> + assert_period_remaining expected_remaining remaining loc + | None -> return_unit let assert_ballots expected_ballots b loc = Context.Vote.get_ballots (B b) >>=? fun ballots -> Assert.equal ~loc - ballots_equal + Vote.equal_ballots "Unexpected ballots" - ballots_pp + Vote.pp_ballots ballots expected_ballots let assert_empty_ballots b loc = - assert_ballots ballots_zero b loc >>=? fun () -> + assert_ballots Vote.ballots_zero b loc >>=? fun () -> Context.Vote.get_ballot_list (B b) >>=? function | [] -> return_unit | _ -> failwith "%s - Unexpected ballot list" loc @@ -262,6 +250,48 @@ let context_init = ~baking_reward_fixed_portion:Tez.zero ~nonce_revelation_threshold:2l +(** {3 Expected protocol errors} *) + +let wrong_error expected_error_name actual_error_trace loc = + failwith + "%s:@,Expected error trace [%s], but got:@,%a" + loc + expected_error_name + Error_monad.pp_print_trace + actual_error_trace + +let empty_proposals loc = function + | [Environment.Ecoproto_error Amendment.Empty_proposal] -> return_unit + | err -> wrong_error "Empty_proposal" err loc + +let too_many_proposals loc = function + | [Environment.Ecoproto_error Amendment.Too_many_proposals] -> return_unit + | err -> wrong_error "Too_many_proposals" err loc + +let duplicate_ballot loc = function + | [Environment.Ecoproto_error Amendment.Duplicate_ballot] -> return_unit + | err -> wrong_error "Duplicate_ballot" err loc + +let assert_validate_proposals_fails ~expected_error ~proposer ~proposals block + loc = + let open Lwt_result_syntax in + let* operation = Op.proposals (B block) proposer proposals in + Incremental.assert_validate_operation_fails + (expected_error loc) + operation + block + +let assert_validate_ballot_fails ~expected_error ~voter ~proposal ~ballot block + loc = + let open Lwt_result_syntax in + let* operation = Op.ballot (B block) voter proposal ballot in + Incremental.assert_validate_operation_fails + (expected_error loc) + operation + block + +(** {2 Tests} *) + (** A normal and successful vote sequence. *) let test_successful_vote num_delegates () = let open Alpha_context in @@ -350,14 +380,21 @@ let test_successful_vote num_delegates () = | None -> failwith "%s - Missing proposal" __LOC__) >>=? fun () -> (* proposing more than maximum_proposals fails *) - Op.proposals (B b) del1 (Protocol_hash.zero :: props) >>=? fun ops -> - Block.bake ~operations:[ops] b >>= fun res -> - Assert.proto_error_with_info ~loc:__LOC__ res "Too many proposals" + assert_validate_proposals_fails + ~expected_error:too_many_proposals + ~proposer:del1 + ~proposals:(Protocol_hash.zero :: props) + b + __LOC__ >>=? fun () -> (* proposing less than one proposal fails *) - Op.proposals (B b) del1 [] >>=? fun ops -> - Block.bake ~operations:[ops] b >>= fun res -> - Assert.proto_error_with_info ~loc:__LOC__ res "Empty proposal" >>=? fun () -> + assert_validate_proposals_fails + ~expected_error:empty_proposals + ~proposer:del1 + ~proposals:[] + b + __LOC__ + >>=? fun () -> (* first block of exploration period *) bake_until_first_block_of_next_period b >>=? fun b -> (* next block is first block of exploration *) @@ -387,8 +424,6 @@ let test_successful_vote num_delegates () = delegates_p2 >>=? fun operations -> Block.bake ~operations b >>=? fun b -> - Op.ballot (B b) del1 Protocol_hash.zero Vote.Nay >>=? fun op -> - Block.bake ~operations:[op] b >>= fun res -> Context.Delegate.voting_info (B b) pkh1 >>=? fun info1 -> assert_equal_info ~loc:__LOC__ @@ -400,7 +435,16 @@ let test_successful_vote num_delegates () = remaining_proposals = 0; } >>=? fun () -> - Assert.proto_error_with_info ~loc:__LOC__ res "Duplicate ballot" + (* Submitting a second ballot for [del1] fails (indeed, [del1] + belongs to [delegates_p2], so they have already sent a ballot + during the unanimous vote right above). *) + assert_validate_ballot_fails + ~expected_error:duplicate_ballot + ~voter:del1 + ~proposal:Protocol_hash.zero + ~ballot:Vote.Nay + b + __LOC__ >>=? fun () -> (* Allocate votes from weight of active delegates *) List.fold_left (fun acc v -> Int64.(add v acc)) 0L power_p2 @@ -545,8 +589,8 @@ let test_not_enough_quorum_in_exploration num_delegates () = let proposer = WithExceptions.Option.get ~loc:__LOC__ @@ List.nth delegates 0 in - Op.proposals (B b) proposer [Protocol_hash.zero] >>=? fun ops -> - Block.bake ~operations:[ops] b >>=? fun b -> + Op.proposals (B b) proposer [Protocol_hash.zero] >>=? fun operation -> + Block.bake ~operation b >>=? fun b -> (* skip to exploration period *) bake_until_first_block_of_next_period b >>=? fun b -> (* we moved to an exploration period with one proposal *) @@ -599,8 +643,8 @@ let test_not_enough_quorum_in_promotion num_delegates () = let proposer = WithExceptions.Option.get ~loc:__LOC__ @@ List.nth delegates 0 in - Op.proposals (B b) proposer [Protocol_hash.zero] >>=? fun ops -> - Block.bake ~operations:[ops] b >>=? fun b -> + Op.proposals (B b) proposer [Protocol_hash.zero] >>=? fun operation -> + Block.bake ~operation b >>=? fun b -> (* skip to exploration period *) bake_until_first_block_of_next_period b >>=? fun b -> (* we moved to an exploration period with one proposal *) @@ -672,8 +716,8 @@ let test_multiple_identical_proposals_count_as_one () = assert_period ~expected_kind:Proposal b __LOC__ >>=? fun () -> let proposer = WithExceptions.Option.get ~loc:__LOC__ @@ List.hd delegates in Op.proposals (B b) proposer [Protocol_hash.zero; Protocol_hash.zero] - >>=? fun ops -> - Block.bake ~operations:[ops] b >>=? fun b -> + >>=? fun operation -> + Block.bake ~operation b >>=? fun b -> (* compute the weight of proposals *) Context.Vote.get_proposals (B b) >>=? fun ps -> (* compute the voting power of proposer *) @@ -774,11 +818,11 @@ let test_quorum_in_proposal has_quorum () = Int64.(div (mul total_tokens quorum) 100_00L) |> Test_tez.of_mutez_exn in Op.transaction (B b) del2 del1 bal >>=? fun op2 -> - Block.bake ~policy ~operations:[op2] b >>=? fun b -> + Block.bake ~policy ~operation:op2 b >>=? fun b -> bake_until_first_block_of_next_period b >>=? fun b -> (* make the proposal *) - Op.proposals (B b) del1 [protos.(0)] >>=? fun ops -> - Block.bake ~policy ~operations:[ops] b >>=? fun b -> + Op.proposals (B b) del1 [protos.(0)] >>=? fun operation -> + Block.bake ~policy ~operation b >>=? fun b -> bake_until_first_block_of_next_period b >>=? fun b -> (* we remain in the proposal period when there is no quorum, otherwise we move to the cooldown vote period *) @@ -793,8 +837,8 @@ let test_supermajority_in_exploration supermajority () = context_init ~min_proposal_quorum 100 () >>=? fun (b, delegates) -> let del1 = WithExceptions.Option.get ~loc:__LOC__ @@ List.nth delegates 0 in let proposal = protos.(0) in - Op.proposals (B b) del1 [proposal] >>=? fun ops1 -> - Block.bake ~operations:[ops1] b >>=? fun b -> + Op.proposals (B b) del1 [proposal] >>=? fun operation -> + Block.bake ~operation b >>=? fun b -> bake_until_first_block_of_next_period b >>=? fun b -> (* move to exploration *) assert_period ~expected_kind:Exploration b __LOC__ >>=? fun () -> @@ -844,8 +888,8 @@ let test_no_winning_proposal num_delegates () = in (* all delegates active in p1 propose the same proposals *) List.map_es (fun del -> Op.proposals (B b) del props) delegates_p1 - >>=? fun ops_list -> - Block.bake ~operations:ops_list b >>=? fun b -> + >>=? fun operations -> + Block.bake ~operations b >>=? fun b -> (* skip to exploration period *) bake_until_first_block_of_next_period b >>=? fun b -> (* we stay in the same proposal period because no winning proposal *) @@ -868,8 +912,8 @@ let test_quorum_capped_maximum num_delegates () = let proposer = WithExceptions.Option.get ~loc:__LOC__ @@ List.nth delegates 0 in - Op.proposals (B b) proposer [protocol] >>=? fun ops -> - Block.bake ~operations:[ops] b >>=? fun b -> + Op.proposals (B b) proposer [protocol] >>=? fun operation -> + Block.bake ~operation b >>=? fun b -> (* skip to exploration period *) bake_until_first_block_of_next_period b >>=? fun b -> (* we moved to an exploration period with one proposal *) @@ -908,8 +952,8 @@ let test_quorum_capped_minimum num_delegates () = let proposer = WithExceptions.Option.get ~loc:__LOC__ @@ List.nth delegates 0 in - Op.proposals (B b) proposer [protocol] >>=? fun ops -> - Block.bake ~operations:[ops] b >>=? fun b -> + Op.proposals (B b) proposer [protocol] >>=? fun operation -> + Block.bake ~operation b >>=? fun b -> (* skip to exploration period *) bake_until_first_block_of_next_period b >>=? fun b -> (* we moved to an exploration period with one proposal *) @@ -1006,9 +1050,9 @@ let test_voting_power_updated_each_voting_period () = let policy = Block.Excluding [baker1; baker2] in (* Transfer 30,000 tez from baker1 to baker2 *) let amount = Tez.of_mutez_exn 30_000_000_000L in - Op.transaction (B genesis) con1 con2 amount >>=? fun op -> + Op.transaction (B genesis) con1 con2 amount >>=? fun operation -> (* Bake the block containing the transaction *) - Block.bake ~policy ~operations:[op] genesis >>=? fun block -> + Block.bake ~policy ~operation genesis >>=? fun block -> (* Retrieve balance of con1 *) Context.Contract.balance (B block) con1 >>=? fun balance1 -> (* Assert balance has changed by deducing the amount *) diff --git a/src/proto_alpha/lib_protocol/vote_storage.ml b/src/proto_alpha/lib_protocol/vote_storage.ml index 42d50aeb0d96..a37403dc565c 100644 --- a/src/proto_alpha/lib_protocol/vote_storage.ml +++ b/src/proto_alpha/lib_protocol/vote_storage.ml @@ -54,6 +54,8 @@ let clear_proposals ctxt = type ballots = {yay : int64; nay : int64; pass : int64} +let ballots_zero = {yay = 0L; nay = 0L; pass = 0L} + let ballots_encoding = let open Data_encoding in conv @@ -61,6 +63,12 @@ let ballots_encoding = (fun (yay, nay, pass) -> {yay; nay; pass}) @@ obj3 (req "yay" int64) (req "nay" int64) (req "pass" int64) +let equal_ballots b1 b2 = + Int64.(equal b1.yay b2.yay && equal b1.nay b2.nay && equal b1.pass b2.pass) + +let pp_ballots ppf b = + Format.fprintf ppf "{ yay = %Ld; nay = %Ld; pass = %Ld }" b.yay b.nay b.pass + let has_recorded_ballot = Storage.Vote.Ballots.mem let record_ballot = Storage.Vote.Ballots.init @@ -79,7 +87,7 @@ let get_ballots ctxt = | Yay -> {ballots with yay = count ballots.yay} | Nay -> {ballots with nay = count ballots.nay} | Pass -> {ballots with pass = count ballots.pass} )) - ~init:(ok {yay = 0L; nay = 0L; pass = 0L}) + ~init:(ok ballots_zero) let get_ballot_list = Storage.Vote.Ballots.bindings diff --git a/src/proto_alpha/lib_protocol/vote_storage.mli b/src/proto_alpha/lib_protocol/vote_storage.mli index c719beb8c32f..b814c8a54d9a 100644 --- a/src/proto_alpha/lib_protocol/vote_storage.mli +++ b/src/proto_alpha/lib_protocol/vote_storage.mli @@ -44,8 +44,18 @@ val clear_proposals : Raw_context.t -> Raw_context.t Lwt.t (** Counts of the votes *) type ballots = {yay : int64; nay : int64; pass : int64} +(** All vote counts set to zero. *) +val ballots_zero : ballots + +(** Encoding for {!ballots}. *) val ballots_encoding : ballots Data_encoding.t +(** Equality check for {!ballots}. *) +val equal_ballots : ballots -> ballots -> bool + +(** Pretty printer for {!ballots}. *) +val pp_ballots : Format.formatter -> ballots -> unit + val has_recorded_ballot : Raw_context.t -> Signature.Public_key_hash.t -> bool Lwt.t -- GitLab From 2055aa4f2b6a0265bbef6f7368617aaa3f6648bc Mon Sep 17 00:00:00 2001 From: Zaynah Dargaye Date: Wed, 6 Jul 2022 00:55:53 +0200 Subject: [PATCH 3/3] Proto/test: add tests on voting operations --- .../lib_protocol/alpha_context.mli | 2 + .../lib_protocol/test/helpers/context.mli | 6 + .../integration/operations/test_voting.ml | 797 +++++++++++++++++- 3 files changed, 784 insertions(+), 21 deletions(-) diff --git a/src/proto_alpha/lib_protocol/alpha_context.mli b/src/proto_alpha/lib_protocol/alpha_context.mli index b115e31399f0..e7bbcbd0f8d9 100644 --- a/src/proto_alpha/lib_protocol/alpha_context.mli +++ b/src/proto_alpha/lib_protocol/alpha_context.mli @@ -2605,6 +2605,8 @@ module Vote : sig val equal_ballot : ballot -> ballot -> bool + val pp_ballot : Format.formatter -> ballot -> unit + type delegate_info = { voting_power : Int64.t option; current_ballot : ballot option; diff --git a/src/proto_alpha/lib_protocol/test/helpers/context.mli b/src/proto_alpha/lib_protocol/test/helpers/context.mli index 064f867e8d92..e9e504eb5f22 100644 --- a/src/proto_alpha/lib_protocol/test/helpers/context.mli +++ b/src/proto_alpha/lib_protocol/test/helpers/context.mli @@ -279,6 +279,12 @@ type 'accounts init := unit -> (Block.t * 'accounts) tzresult Lwt.t +(** Returns an initial block and the implicit contracts corresponding + to its bootstrap accounts. The number of bootstrap accounts, and + the structure of the returned contracts, are specified by the [tup] + argument. *) +val init_gen : (Alpha_context.Contract.t, 'accounts) tup -> 'accounts init + (** [init_n n] : returns an initial block with [n] initialized accounts and the associated implicit contracts *) val init_n : int -> Alpha_context.Contract.t list init diff --git a/src/proto_alpha/lib_protocol/test/integration/operations/test_voting.ml b/src/proto_alpha/lib_protocol/test/integration/operations/test_voting.ml index 3319fad9089e..c4076897eb58 100644 --- a/src/proto_alpha/lib_protocol/test/integration/operations/test_voting.ml +++ b/src/proto_alpha/lib_protocol/test/integration/operations/test_voting.ml @@ -104,17 +104,25 @@ let protos = (** {2 Helper functions} *) -let assert_period_kind expected_kind kind loc = - if Stdlib.(expected_kind = kind) then return_unit +let assert_period_kinds expected_kinds kind loc = + if + List.exists + (fun expected_kind -> Stdlib.(expected_kind = kind)) + expected_kinds + then return_unit else Alcotest.failf "%s - Unexpected voting period kind - expected %a, got %a" loc - Voting_period.pp_kind - expected_kind + (Format.pp_print_list + ~pp_sep:(fun fmt () -> Format.fprintf fmt " or ") + Voting_period.pp_kind) + expected_kinds Voting_period.pp_kind kind +let assert_period_kind expected_kind = assert_period_kinds [expected_kind] + let assert_period_index expected_index index loc = if expected_index = index then return_unit else @@ -142,17 +150,23 @@ let assert_period_remaining expected_remaining remaining loc = expected_remaining remaining -let assert_period ?expected_kind ?expected_index ?expected_position - ?expected_remaining b loc = +let assert_period ?expected_kind ?expected_kinds ?expected_index + ?expected_position ?expected_remaining b loc = let open Lwt_result_syntax in let* {voting_period; position; remaining} = Context.Vote.get_current_period (B b) in let* () = - match expected_kind with - | Some expected_kind -> + match (expected_kind, expected_kinds) with + | None, None -> return_unit + | Some expected_kind, None -> assert_period_kind expected_kind voting_period.kind loc - | None -> return_unit + | None, Some expected_kinds -> + assert_period_kinds expected_kinds voting_period.kind loc + | Some _, Some _ -> + invalid_arg + "assert_period: arguments expected_kind and expected_kinds should \ + not both be provided." in let* () = match expected_index with @@ -234,15 +248,16 @@ let bake_until_first_block_of_next_period ?policy b = Context.Vote.get_current_period (B b) >>=? fun {remaining; _} -> Block.bake_n ?policy Int32.(add remaining one |> to_int) b -let context_init = +let context_init_tup tup ?(blocks_per_cycle = 4l) = (* Note that some of these tests assume (more or less) that the accounts remain active during a voting period, which roughly translates to the following condition being assumed to hold: `blocks_per_voting_period <= preserved_cycles * blocks_per_cycle.` We also set baking and endorsing rewards to zero in order to ease accounting of exact baker stake. *) - Context.init_n - ~blocks_per_cycle:4l + Context.init_gen + tup + ~blocks_per_cycle ~cycles_per_voting_period:1l ~consensus_threshold:0 ~endorsing_reward_per_slot:Tez.zero @@ -250,6 +265,40 @@ let context_init = ~baking_reward_fixed_portion:Tez.zero ~nonce_revelation_threshold:2l +(** [context_init n ()] returns [(block, contracts)] where [block] is + an initial block with [n] bootstrap accounts, and [contracts] is + the list of associated implicit contracts. + + See {!context_init_tup} and {!Context.init_gen} for optional + arguments. *) +let context_init n = context_init_tup (Context.TList n) + +(** [context_init1 ()] returns [(block, contract)] where [block] is an + initial block with one bootstrap account, and [contract] is the + associated implicit contract. *) +let context_init1 = context_init_tup Context.T1 + +(** [context_init2 ()] returns [(block, contracts)] where [block] is + an initial block with two bootstrap accounts, and [contracts] is + the pair of associated implicit contracts. *) +let context_init2 = context_init_tup Context.T2 + +(** Call {!context_init2}, then inject a Proposals operation and bake + blocks in order to move on to an Exploration period. Return a + block, a delegate (distinct from the one who submitted the + Proposals), and the current proposal. *) +let context_init_exploration ?(proposal = protos.(0)) () = + let open Lwt_result_syntax in + let* block, (proposer, other_delegate) = context_init2 () in + let* operation = Op.proposals (B block) proposer [proposal] in + let* block = Block.bake block ~operation in + let* block = bake_until_first_block_of_next_period block in + let* () = assert_period ~expected_kind:Exploration block __LOC__ in + return (block, other_delegate, proposal) + +let append_loc ~caller_loc loc = + Format.sprintf "%s@.Called from %s" loc caller_loc + (** {3 Expected protocol errors} *) let wrong_error expected_error_name actual_error_trace loc = @@ -260,7 +309,40 @@ let wrong_error expected_error_name actual_error_trace loc = Error_monad.pp_print_trace actual_error_trace -let empty_proposals loc = function +let unregistered_delegate delegate loc = function + | [Environment.Ecoproto_error (Delegate_storage.Unregistered_delegate pkh)] -> + Assert.equal_pkh ~loc:(append_loc ~caller_loc:loc __LOC__) pkh delegate + | err -> wrong_error "Unregistered_delegate" err loc + +let missing_signature loc = function + | [Environment.Ecoproto_error Operation.Missing_signature] -> return_unit + | err -> wrong_error "Missing_signature" err loc + +let invalid_signature loc = function + | [Environment.Ecoproto_error Operation.Invalid_signature] -> return_unit + | err -> wrong_error "Invalid_signature" err loc + +let wrong_voting_period ~current_index ~op_index loc = function + | [ + Environment.Ecoproto_error (Apply.Wrong_voting_period {expected; provided}); + ] -> + let open Lwt_result_syntax in + let make_loc = append_loc ~caller_loc:loc in + let* () = + Assert.equal_int32 ~loc:(make_loc __LOC__) expected current_index + in + Assert.equal_int32 ~loc:(make_loc __LOC__) provided op_index + | err -> wrong_error "Wrong_voting_period" err loc + +let unexpected_proposal loc = function + | [Environment.Ecoproto_error Amendment.Unexpected_proposal] -> return_unit + | err -> wrong_error "Unexpected_proposal" err loc + +let unauthorized_proposal loc = function + | [Environment.Ecoproto_error Amendment.Unauthorized_proposal] -> return_unit + | err -> wrong_error "Unauthorized_proposal" err loc + +let empty_proposal loc = function | [Environment.Ecoproto_error Amendment.Empty_proposal] -> return_unit | err -> wrong_error "Empty_proposal" err loc @@ -268,29 +350,41 @@ let too_many_proposals loc = function | [Environment.Ecoproto_error Amendment.Too_many_proposals] -> return_unit | err -> wrong_error "Too_many_proposals" err loc +let unexpected_ballot loc = function + | [Environment.Ecoproto_error Amendment.Unexpected_ballot] -> return_unit + | err -> wrong_error "Unexpected_ballot" err loc + +let invalid_proposal loc = function + | [Environment.Ecoproto_error Amendment.Invalid_proposal] -> return_unit + | err -> wrong_error "Invalid_proposal" err loc + let duplicate_ballot loc = function | [Environment.Ecoproto_error Amendment.Duplicate_ballot] -> return_unit | err -> wrong_error "Duplicate_ballot" err loc -let assert_validate_proposals_fails ~expected_error ~proposer ~proposals block - loc = +let unauthorized_ballot loc = function + | [Environment.Ecoproto_error Amendment.Unauthorized_ballot] -> return_unit + | err -> wrong_error "Unauthorized_ballot" err loc + +let assert_validate_proposals_fails ~expected_error ~proposer ~proposals ?period + block loc = let open Lwt_result_syntax in - let* operation = Op.proposals (B block) proposer proposals in + let* operation = Op.proposals (B block) proposer ?period proposals in Incremental.assert_validate_operation_fails (expected_error loc) operation block -let assert_validate_ballot_fails ~expected_error ~voter ~proposal ~ballot block - loc = +let assert_validate_ballot_fails ~expected_error ~voter ~proposal ~ballot + ?period block loc = let open Lwt_result_syntax in - let* operation = Op.ballot (B block) voter proposal ballot in + let* operation = Op.ballot (B block) voter ?period proposal ballot in Incremental.assert_validate_operation_fails (expected_error loc) operation block -(** {2 Tests} *) +(** {2 Scenarized tests} *) (** A normal and successful vote sequence. *) let test_successful_vote num_delegates () = @@ -389,7 +483,7 @@ let test_successful_vote num_delegates () = >>=? fun () -> (* proposing less than one proposal fails *) assert_validate_proposals_fails - ~expected_error:empty_proposals + ~expected_error:empty_proposal ~proposer:del1 ~proposals:[] b @@ -1129,8 +1223,614 @@ let test_voting_period_pp () = (Format.asprintf "%a" Voting_period_repr.pp vp) "index: 123, kind:proposal, start_position: 321" +(** {2 Validity tests} + + For each vote operation (Proposals and Ballot), we define a serie + of negative tests and a positive test. + + Negative tests target errors that can occur during + application. They check that the appropriate error is triggered. + + If the operation is valid, then its application must succeed when + it is baked into a block. Positive tests observe the effects of the + operation application by comparing the states before and after the + block. *) + +(** {3 Proposal -- Negative tests} *) + +(** Test that a Proposals operation fails when its source is not a + registered delegate. *) +let test_proposals_unregistered_delegate () = + let open Lwt_result_syntax in + let* block, _delegate = context_init1 () in + let fresh_account = Account.new_account () in + assert_validate_proposals_fails + ~expected_error:(unregistered_delegate fresh_account.pkh) + ~proposer:(Contract.Implicit fresh_account.pkh) + ~proposals:[Protocol_hash.zero] + block + __LOC__ + +(** Test that a Proposals operation fails when it is unsigned. *) +let test_proposals_missing_signature () = + let open Lwt_result_syntax in + let* block, proposer = context_init1 () in + let* contents = Op.proposals_contents (B block) proposer [protos.(0)] in + let op = Op.pack_operation (B block) None contents in + Incremental.assert_validate_operation_fails + (missing_signature __LOC__) + op + block + +(** Test that a Proposals operation fails when its signature is invalid. *) +let test_proposals_invalid_signature () = + let open Lwt_result_syntax in + let* block, proposer = context_init1 () in + let* contents = Op.proposals_contents (B block) proposer [protos.(0)] in + let op = Op.pack_operation (B block) (Some Signature.zero) contents in + Incremental.assert_validate_operation_fails + (invalid_signature __LOC__) + op + block + +(** Test that a Proposals operation fails when the period index + provided in the operation is not the current voting period index. *) +let test_proposals_wrong_voting_period () = + let open Lwt_result_syntax in + let* block, proposer = context_init1 () in + let* current_period = Context.Vote.get_current_period (B block) in + let current_index = current_period.voting_period.index in + let op_index = Int32.succ current_index in + assert_validate_proposals_fails + ~expected_error:(wrong_voting_period ~current_index ~op_index) + ~proposer + ~proposals:[Protocol_hash.zero] + ~period:op_index + block + __LOC__ + +(** Test that a Proposals operation fails when it occurs in a + non-Proposal voting period. *) +let test_unexpected_proposal () = + let open Lwt_result_syntax in + let* block, proposer = context_init1 () in + let proposal = protos.(0) in + let assert_proposals_fails_with_unexpected_proposal = + assert_validate_proposals_fails + ~expected_error:unexpected_proposal + ~proposer + ~proposals:[proposal] + in + (* End the initial Proposals period with a submitted + proposal, to move on to an Exploration period. *) + let* operation = Op.proposals (B block) proposer [proposal] in + let* block = Block.bake block ~operation in + let* block = bake_until_first_block_of_next_period block in + (* Proposals during Exploration. *) + let* () = assert_period ~expected_kind:Exploration block __LOC__ in + let* () = assert_proposals_fails_with_unexpected_proposal block __LOC__ in + (* End the Exploration period with enough votes to move on to a + Cooldown period. *) + let* operation = Op.ballot (B block) proposer proposal Vote.Yay in + let* block = Block.bake ~operation block in + let* block = bake_until_first_block_of_next_period block in + (* Proposals during Cooldown. *) + let* () = assert_period ~expected_kind:Cooldown block __LOC__ in + let* () = assert_proposals_fails_with_unexpected_proposal block __LOC__ in + (* Proposals during Promotion. *) + let* block = bake_until_first_block_of_next_period block in + let* () = assert_period ~expected_kind:Promotion block __LOC__ in + let* () = assert_proposals_fails_with_unexpected_proposal block __LOC__ in + (* End the Promotion period with enough votes to move on to an + Adoption period. *) + let* operation = Op.ballot (B block) proposer proposal Vote.Yay in + let* block = Block.bake ~operation block in + let* block = bake_until_first_block_of_next_period block in + (* Proposals during Adoption. *) + let* () = assert_period ~expected_kind:Adoption block __LOC__ in + assert_proposals_fails_with_unexpected_proposal block __LOC__ + +(** Test that a Proposals operation fails when the proposer is not in + the vote listings. *) +let test_unauthorized_proposal () = + let open Lwt_result_syntax in + let* block, funder = context_init1 () in + let account = Account.new_account () in + let proposer = Contract.Implicit account.pkh in + let* operation = Op.transaction (B block) funder proposer Tez.one in + let* block = Block.bake block ~operation in + let* operation = + Op.delegation ~force_reveal:true (B block) proposer (Some account.pkh) + in + let* block = Block.bake block ~operation in + assert_validate_proposals_fails + ~expected_error:unauthorized_proposal + ~proposer + ~proposals:[Protocol_hash.zero] + block + __LOC__ + +(** Test that a Proposals operation fails when its proposal list is + empty. *) +let test_empty_proposal () = + let open Lwt_result_syntax in + let* block, proposer = context_init1 () in + assert_validate_proposals_fails + ~expected_error:empty_proposal + ~proposer + ~proposals:[] + block + __LOC__ + +(** Test that a Proposals operation fails when its proposal list is + longer than the [max_proposals_per_delegate] protocol constant. *) +let test_operation_has_too_many_proposals () = + let open Lwt_result_syntax in + let* block, proposer = context_init1 () in + assert (Array.length protos >= Constants.max_proposals_per_delegate + 1) ; + let proposals = + List.map (Array.get protos) (0 -- Constants.max_proposals_per_delegate) + in + assert_validate_proposals_fails + ~expected_error:too_many_proposals + ~proposer + ~proposals + block + __LOC__ + +(** Test that a Proposals operation fails when it would make the total + count of proposals submitted by the proposer exceed the + [max_proposals_per_delegate] protocol constant. *) +let test_too_many_proposals () = + let open Lwt_result_syntax in + let* block, proposer = context_init1 () in + assert (Array.length protos >= Constants.max_proposals_per_delegate + 1) ; + let proposals = + List.map (Array.get protos) (1 -- Constants.max_proposals_per_delegate) + in + let* operation = Op.proposals (B block) proposer proposals in + let* block = Block.bake block ~operation in + assert_validate_proposals_fails + ~expected_error:too_many_proposals + ~proposer + ~proposals:[protos.(0)] + block + __LOC__ + +(** {3 Proposals -- Positive test} + + A Proposals operation is valid when: + + - its source is a registered delegate and belongs to the voting + listings, + + - the current voting period is a Proposal period and has the same + index as the period provided in the operation, + + - its list of proposals is not empty, + + - it won't make the total proposal count of the proposer exceed + the [max_proposals_per_delegate] protocol constant, and + + - its signature is valid. + + We can observe the successful application of the Proposals + operation from a pre-state to a post-state as follows: + + - the proposal count of the proposer has been incremented by the + number of proposals in the operation, + + - the operation proposals have been added to the recorded + proposals of the proposer, and + + - the total weight supporting each of the proposals has been + incremented by the voting power of the proposer. *) + +let observe_proposals pre_state post_state op caller_loc = + let open Lwt_result_syntax in + let make_loc = append_loc ~caller_loc in + let* (Proposals {source; period; proposals}) = + let (Operation_data {contents; _}) = op.protocol_data in + match contents with + | Single (Proposals _ as contents) -> return contents + | _ -> failwith "%s - Expected a Proposals operation" (make_loc __LOC__) + in + + (* Validity conditions *) + let proposals_num = List.length proposals in + let* () = Assert.not_equal_int ~loc:(make_loc __LOC__) 0 proposals_num in + let* () = + assert_period ~expected_kind:Proposal pre_state (make_loc __LOC__) + in + let* pre_period = Context.Vote.get_current_period (B pre_state) in + let* () = + Assert.equal_int32 + ~loc:(make_loc __LOC__) + period + pre_period.voting_period.index + in + let* del = + Context.Contract.delegate (B pre_state) (Contract.Implicit source) + in + let* () = Assert.equal_pkh ~loc:(make_loc __LOC__) source del in + let* dels, _powers = get_delegates_and_power_from_listings pre_state in + assert (List.mem ~equal:Contract.equal (Contract.Implicit source) dels) ; + let* pre_voting_infos = Context.Delegate.voting_info (B pre_state) source in + let* () = + Assert.not_equal_int + ~loc:(make_loc __LOC__) + 0 + pre_voting_infos.remaining_proposals + in + let* () = + Assert.leq_int + ~loc:(make_loc __LOC__) + proposals_num + pre_voting_infos.remaining_proposals + in + + (* Observations *) + (* Check [voting_info] update. *) + let* post_voting_infos = Context.Delegate.voting_info (B post_state) source in + let* () = + Assert.equal_int + ~loc:(make_loc __LOC__) + post_voting_infos.remaining_proposals + (pre_voting_infos.remaining_proposals - proposals_num) + in + assert ( + List.for_all + (fun a -> Stdlib.List.mem a post_voting_infos.current_proposals) + proposals) ; + (* Check [Storage.Vote.Proposals_count] update. *) + let* proposal_count_pre = + Context.Vote.recorded_proposal_count_for_delegate (B pre_state) source + in + let* proposal_count_post = + Context.Vote.recorded_proposal_count_for_delegate (B post_state) source + in + let* () = + Assert.equal_int + ~loc:(make_loc __LOC__) + (proposal_count_pre + proposals_num) + proposal_count_post + in + (* Check the update of the total weight of supporters for each proposal. *) + let* proposal_weights_pre = Context.Vote.get_proposals (B pre_state) in + let* proposal_weights_post = Context.Vote.get_proposals (B post_state) in + let* source_power = + Assert.get_some ~loc:(make_loc __LOC__) pre_voting_infos.voting_power + in + List.iter_es + (fun proposal -> + let weight_pre = + Environment.Protocol_hash.Map.find proposal proposal_weights_pre + |> Option.value ~default:Int64.zero + in + let* weight_post = + Assert.get_some + ~loc:(make_loc __LOC__) + (Environment.Protocol_hash.Map.find proposal proposal_weights_post) + in + Assert.equal_int64 + ~loc:(make_loc __LOC__) + weight_post + (Int64.add weight_pre source_power)) + proposals + +(* Bake blocks with various valid Proposals operations, and observe + that their effects are correctly applied. *) +let test_valid_proposals () = + let open Lwt_result_syntax in + (* We use a higher [blocks_per_cycle] than the + {!default_blocks_per_cycle} (which is [4l]), so that we can bake + each operation in a separate block without reaching the end of + the voting cycle. *) + let* b0, (proposer0, proposer1) = context_init2 ~blocks_per_cycle:10l () in + let* op0 = Op.proposals (B b0) proposer0 [protos.(0)] in + let* b1 = Block.bake b0 ~operation:op0 in + let* () = observe_proposals b0 b1 op0 __LOC__ in + let* op1 = + Op.proposals (B b1) proposer0 [protos.(1); protos.(2); protos.(3)] + in + let* b2 = Block.bake b1 ~operation:op1 in + let* () = observe_proposals b1 b2 op1 __LOC__ in + let* op2 = + Op.proposals + (B b2) + proposer1 + [protos.(0); protos.(2); protos.(4); protos.(5)] + in + let* b3 = Block.bake b2 ~operation:op2 in + let* () = observe_proposals b2 b3 op2 __LOC__ in + let* op3 = Op.proposals (B b3) proposer0 [protos.(5); protos.(6)] in + let* b4 = Block.bake b3 ~operation:op3 in + observe_proposals b3 b4 op3 __LOC__ + +(** {3 Proposals -- Incoming semantic change} *) + +(** Test that a Proposals operation can be replayed + (this will no longer be true in an upcoming commit). *) +let test_replay_proposals () = + let open Lwt_result_syntax in + let* bpre, proposer = context_init1 ~blocks_per_cycle:10l () in + let* operation = Op.proposals (B bpre) proposer [protos.(0)] in + let* bpost = Block.bake bpre ~operation in + let* () = observe_proposals bpre bpost operation __LOC__ in + (* We do not observe the effects of replayed operations because they + are different from fresh operations: since the proposals were + already recorded for the proposer, + [voting_infos.remaining_proposals] does not decrease, nor does + the total supporting weight increase. + + We simply check that [Block.bake] does not fail. *) + let* bpost = Block.bake bpost ~operation in + let* _bpost = Block.bake bpost ~operations:[operation; operation] in + return_unit + +(** {3 Ballot -- Negative tests} *) + +(** Test that a Ballot operation fails when its source is not a + registered delegate. *) +let test_ballot_unregistered_delegate () = + let open Lwt_result_syntax in + let* block, _delegate, proposal = context_init_exploration () in + let fresh_account = Account.new_account () in + assert_validate_ballot_fails + ~expected_error:(unregistered_delegate fresh_account.pkh) + ~voter:(Contract.Implicit fresh_account.pkh) + ~proposal + ~ballot:Vote.Yay + block + __LOC__ + +(** Test that a Ballot operation fails when it is unsigned. *) +let test_ballot_missing_signature () = + let open Lwt_result_syntax in + let* block, voter, proposal = context_init_exploration () in + let* contents = Op.ballot_contents (B block) voter proposal Vote.Yay in + let op = Op.pack_operation (B block) None contents in + Incremental.assert_validate_operation_fails + (missing_signature __LOC__) + op + block + +(** Test that a Ballot operation fails when its signature is invalid. *) +let test_ballot_invalid_signature () = + let open Lwt_result_syntax in + let* block, voter, proposal = context_init_exploration () in + let* contents = Op.ballot_contents (B block) voter proposal Vote.Yay in + let op = Op.pack_operation (B block) (Some Signature.zero) contents in + Incremental.assert_validate_operation_fails + (invalid_signature __LOC__) + op + block + +(** Test that a Ballot operation fails when the period index provided + in the operation is not the current voting period index. *) +let test_ballot_wrong_voting_period () = + let open Lwt_result_syntax in + let* block, voter = context_init1 () in + let* current_period = Context.Vote.get_current_period (B block) in + let current_index = current_period.voting_period.index in + let op_index = Int32.succ current_index in + assert_validate_ballot_fails + ~expected_error:(wrong_voting_period ~current_index ~op_index) + ~voter + ~proposal:protos.(0) + ~ballot:Vote.Yay + ~period:op_index + block + __LOC__ + +(** Test that a Ballot operation fails when it occurs outside of an + Exploration or Promotion voting period. *) +let test_unexpected_ballot () = + let open Lwt_result_syntax in + let* block, voter = context_init1 () in + let proposal = protos.(0) in + let assert_ballot_fails_with_unexpected_ballot = + assert_validate_ballot_fails + ~expected_error:unexpected_ballot + ~voter + ~proposal + ~ballot:Vote.Nay + in + (* Ballot during Proposals. *) + let* () = assert_period ~expected_kind:Proposal block __LOC__ in + let* () = assert_ballot_fails_with_unexpected_ballot block __LOC__ in + (* End the Proposals period with a submitted proposal, to move on to + an Exploration period. *) + let* operation = Op.proposals (B block) voter [proposal] in + let* block = Block.bake block ~operation in + let* block = bake_until_first_block_of_next_period block in + (* End the Exploration period with enough votes to move on to a + Cooldown period. *) + let* operation = Op.ballot (B block) voter proposal Vote.Yay in + let* block = Block.bake block ~operation in + let* block = bake_until_first_block_of_next_period block in + (* Ballot during Cooldown. *) + let* () = assert_period ~expected_kind:Cooldown block __LOC__ in + let* () = assert_ballot_fails_with_unexpected_ballot block __LOC__ in + (* End the Cooldown period, then end the Promotion period with + enough votes to move on to an Adoption period. *) + let* block = bake_until_first_block_of_next_period block in + let* operation = Op.ballot (B block) voter proposal Vote.Yay in + let* block = Block.bake ~operation block in + let* block = bake_until_first_block_of_next_period block in + (* Ballot during Adoption. *) + let* () = assert_period ~expected_kind:Adoption block __LOC__ in + assert_ballot_fails_with_unexpected_ballot block __LOC__ + +(** Test that a Ballot operation fails when its proposal is not the + current proposal. *) +let test_ballot_on_invalid_proposal () = + let open Lwt_result_syntax in + let* block, voter, _proposal = + context_init_exploration ~proposal:protos.(0) () + in + assert_validate_ballot_fails + ~expected_error:invalid_proposal + ~voter + ~proposal:protos.(1) + ~ballot:Vote.Yay + block + __LOC__ + +(** Test that a Ballot operation fails when its source has already + submitted a Ballot. *) +let test_duplicate_ballot () = + let open Lwt_result_syntax in + let* block, voter, proposal = context_init_exploration () in + let* operation = Op.ballot (B block) voter proposal Vote.Yay in + let* block = Block.bake ~operation block in + assert_validate_ballot_fails + ~expected_error:duplicate_ballot + ~voter + ~proposal + ~ballot:Vote.Nay + block + __LOC__ + +(** Test that a Ballot operation fails when its source is not in the + vote listings. *) +let test_unauthorized_ballot () = + let open Lwt_result_syntax in + let* block, funder, proposal = context_init_exploration () in + let account = Account.new_account () in + let voter = Contract.Implicit account.pkh in + let* operation = Op.transaction (B block) funder voter Tez.one in + let* block = Block.bake block ~operation in + let* operation = + Op.delegation ~force_reveal:true (B block) voter (Some account.pkh) + in + let* block = Block.bake block ~operation in + assert_validate_ballot_fails + ~expected_error:unauthorized_ballot + ~voter + ~proposal + ~ballot:Vote.Yay + block + __LOC__ + +(** {3 Ballot -- Positive test} + + A Ballot operation is valid when: + + - its source is a registered delegate and belongs to the voting + listings, + + - the current voting period is an Exploration or Promotion period, + and has the same index as the period provided in the operation, + + - its proposal is the current proposal in the context, + + - the voter had submitted no ballot in the current voting period + yet, and + + - its signature is valid. + + We can observe the successful application of a Ballot operation by + checking that: + + - the ballot has been recorded for the voter in the post-state, + and + + - the score of the ballot's vote (yay/nay/pass) has been + incremented by the voting power of the source. *) + +let observe_ballot pre_state post_state op caller_loc = + let open Lwt_result_syntax in + let make_loc = append_loc ~caller_loc in + let* (Ballot {source; period; proposal; ballot}) = + let (Operation_data {contents; _}) = op.protocol_data in + match contents with + | Single (Ballot _ as contents) -> return contents + | _ -> failwith "%s - Expected a Ballot operation" (make_loc __LOC__) + in + (* Validity conditions *) + let* () = + assert_period + ~expected_kinds:[Exploration; Promotion] + pre_state + (make_loc __LOC__) + in + let* pre_period = Context.Vote.get_current_period (B pre_state) in + let* () = + Assert.equal_int32 + ~loc:(make_loc __LOC__) + period + pre_period.voting_period.index + in + let* del = + Context.Contract.delegate (B pre_state) (Contract.Implicit source) + in + let* () = Assert.equal_pkh ~loc:(make_loc __LOC__) source del in + let* dels, _powers = get_delegates_and_power_from_listings pre_state in + assert (List.mem ~equal:Contract.equal (Contract.Implicit source) dels) ; + let* pre_voting_infos = Context.Delegate.voting_info (B pre_state) source in + let* () = + Assert.is_none + ~loc:(make_loc __LOC__) + ~pp:(fun fmt _ -> Format.fprintf fmt "Voter already has a ballot.@.") + pre_voting_infos.current_ballot + in + let* current_proposal = Context.Vote.get_current_proposal (B pre_state) in + let* current_proposal = + Assert.get_some ~loc:(make_loc __LOC__) current_proposal + in + assert (Protocol_hash.equal proposal current_proposal) ; + (* Observations *) + let* post_voting_infos = Context.Delegate.voting_info (B post_state) source in + let* recorded_ballot = + Assert.get_some ~loc:(make_loc __LOC__) post_voting_infos.current_ballot + in + let* () = + Assert.equal + ~loc:(make_loc __LOC__) + Vote.equal_ballot + "Wrong ballot recorded" + Vote.pp_ballot + ballot + recorded_ballot + in + let* ballots_pre = Context.Vote.get_ballots (B pre_state) in + let* source_power = + Assert.get_some ~loc:(make_loc __LOC__) pre_voting_infos.voting_power + in + let expected_ballots_post = + match ballot with + | Yay -> {ballots_pre with yay = Int64.add ballots_pre.yay source_power} + | Nay -> {ballots_pre with nay = Int64.add ballots_pre.nay source_power} + | Pass -> {ballots_pre with pass = Int64.add ballots_pre.pass source_power} + in + assert_ballots expected_ballots_post post_state (make_loc __LOC__) + +let test_valid_ballot () = + let open Lwt_result_syntax in + let* block, delegates = context_init ~blocks_per_cycle:10l 4 () in + let* proposer, voter1, voter2, voter3 = + match delegates with + | [a; b; c; d] -> return (a, b, c, d) + | _ -> failwith "%s@,[context_init n] should return [n] delegates" __LOC__ + in + let proposal = protos.(0) in + let* operation = Op.proposals (B block) proposer [proposal] in + let* block = Block.bake block ~operation in + let* b0 = bake_until_first_block_of_next_period block in + let* operation = Op.ballot (B b0) voter1 proposal Vote.Yay in + let* b1 = Block.bake b0 ~operation in + let* () = observe_ballot b0 b1 operation __LOC__ in + let* operation = Op.ballot (B b1) voter2 proposal Vote.Nay in + let* b2 = Block.bake b1 ~operation in + let* () = observe_ballot b1 b2 operation __LOC__ in + let* operation = Op.ballot (B b2) voter3 proposal Vote.Pass in + let* b3 = Block.bake b2 ~operation in + observe_ballot b2 b3 operation __LOC__ + let tests = [ + (* Scenarized tests *) Tztest.tztest "voting successful_vote" `Quick (test_successful_vote 137); Tztest.tztest "voting cooldown, not enough quorum" @@ -1185,4 +1885,59 @@ let tests = `Quick test_voting_power_updated_each_voting_period; Tztest.tztest "voting period pretty print" `Quick test_voting_period_pp; + (* Validity tests on Proposals *) + Tztest.tztest + "Proposals from unregistered delegate" + `Quick + test_proposals_unregistered_delegate; + Tztest.tztest + "Proposals missing signature" + `Quick + test_proposals_missing_signature; + Tztest.tztest + "Proposals invalid signature" + `Quick + test_proposals_invalid_signature; + Tztest.tztest + "Proposals wrong voting period" + `Quick + test_proposals_wrong_voting_period; + Tztest.tztest "Unexpected proposals" `Quick test_unexpected_proposal; + Tztest.tztest "Unauthorized proposal" `Quick test_unauthorized_proposal; + Tztest.tztest "Empty proposal" `Quick test_empty_proposal; + Tztest.tztest + "Operation has too many proposals" + `Quick + test_operation_has_too_many_proposals; + Tztest.tztest + "Too many proposals (over two operations)" + `Quick + test_too_many_proposals; + Tztest.tztest "Valid Proposals operations" `Quick test_valid_proposals; + Tztest.tztest "Replay proposals" `Quick test_replay_proposals; + (* Validity tests on Ballot *) + Tztest.tztest + "Ballot from unregistered delegate" + `Quick + test_ballot_unregistered_delegate; + Tztest.tztest + "Ballot missing signature" + `Quick + test_ballot_missing_signature; + Tztest.tztest + "Ballot invalid signature" + `Quick + test_ballot_invalid_signature; + Tztest.tztest + "Ballot wrong voting period" + `Quick + test_ballot_wrong_voting_period; + Tztest.tztest "Unexpected ballot" `Quick test_unexpected_ballot; + Tztest.tztest + "Ballot on invalid proposal" + `Quick + test_ballot_on_invalid_proposal; + Tztest.tztest "Duplicate ballot" `Quick test_duplicate_ballot; + Tztest.tztest "Unauthorized ballot" `Quick test_unauthorized_ballot; + Tztest.tztest "Valid Ballot operations" `Quick test_valid_ballot; ] -- GitLab