{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} module Test.Cardano.Ledger.Conway.GovActionReorderSpec (spec) where import Cardano.Ledger.Conway (ConwayEra) import Cardano.Ledger.Conway.Governance ( GovActionState (..), actionPriority, gasAction, reorderActions, ) import Data.Foldable (Foldable (..)) import Data.List (sort) import qualified Data.Sequence.Strict as Seq import Test.Cardano.Ledger.Binary.Arbitrary () import Test.Cardano.Ledger.Common import Test.Cardano.Ledger.Conway.Arbitrary (ShuffledGovActionStates (..)) spec :: Spec spec :: Spec spec = String -> Spec -> Spec forall a. HasCallStack => String -> SpecWith a -> SpecWith a describe String "Conway governance actions reordering" (Spec -> Spec) -> Spec -> Spec forall a b. (a -> b) -> a -> b $ do String -> (StrictSeq (GovActionState ConwayEra) -> Expectation) -> Spec forall prop. (HasCallStack, Testable prop) => String -> prop -> Spec prop String "preserves length when reordered" ((StrictSeq (GovActionState ConwayEra) -> Expectation) -> Spec) -> (StrictSeq (GovActionState ConwayEra) -> Expectation) -> Spec forall a b. (a -> b) -> a -> b $ \(StrictSeq (GovActionState ConwayEra) actions :: Seq.StrictSeq (GovActionState ConwayEra)) -> StrictSeq (GovActionState ConwayEra) -> Int forall a. StrictSeq a -> Int Seq.length StrictSeq (GovActionState ConwayEra) actions Int -> Int -> Expectation forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation `shouldBe` StrictSeq (GovActionState ConwayEra) -> Int forall a. StrictSeq a -> Int Seq.length (forall era. StrictSeq (GovActionState era) -> StrictSeq (GovActionState era) reorderActions @ConwayEra StrictSeq (GovActionState ConwayEra) actions) String -> (StrictSeq (GovActionState ConwayEra) -> Expectation) -> Spec forall prop. (HasCallStack, Testable prop) => String -> prop -> Spec prop String "sorts by priority" ((StrictSeq (GovActionState ConwayEra) -> Expectation) -> Spec) -> (StrictSeq (GovActionState ConwayEra) -> Expectation) -> Spec forall a b. (a -> b) -> a -> b $ \(StrictSeq (GovActionState ConwayEra) actions :: Seq.StrictSeq (GovActionState ConwayEra)) -> [Int] -> [Int] forall a. Ord a => [a] -> [a] sort (StrictSeq Int -> [Int] forall a. StrictSeq a -> [a] forall (t :: * -> *) a. Foldable t => t a -> [a] toList (GovAction ConwayEra -> Int forall era. GovAction era -> Int actionPriority (GovAction ConwayEra -> Int) -> (GovActionState ConwayEra -> GovAction ConwayEra) -> GovActionState ConwayEra -> Int forall b c a. (b -> c) -> (a -> b) -> a -> c . forall era. GovActionState era -> GovAction era gasAction @ConwayEra (GovActionState ConwayEra -> Int) -> StrictSeq (GovActionState ConwayEra) -> StrictSeq Int forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> StrictSeq (GovActionState ConwayEra) actions)) [Int] -> [Int] -> Expectation forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation `shouldBe` StrictSeq Int -> [Int] forall a. StrictSeq a -> [a] forall (t :: * -> *) a. Foldable t => t a -> [a] toList (GovAction ConwayEra -> Int forall era. GovAction era -> Int actionPriority (GovAction ConwayEra -> Int) -> (GovActionState ConwayEra -> GovAction ConwayEra) -> GovActionState ConwayEra -> Int forall b c a. (b -> c) -> (a -> b) -> a -> c . GovActionState ConwayEra -> GovAction ConwayEra forall era. GovActionState era -> GovAction era gasAction (GovActionState ConwayEra -> Int) -> StrictSeq (GovActionState ConwayEra) -> StrictSeq Int forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> StrictSeq (GovActionState ConwayEra) -> StrictSeq (GovActionState ConwayEra) forall era. StrictSeq (GovActionState era) -> StrictSeq (GovActionState era) reorderActions StrictSeq (GovActionState ConwayEra) actions) String -> (GovActionState ConwayEra -> StrictSeq (GovActionState ConwayEra) -> Expectation) -> Spec forall prop. (HasCallStack, Testable prop) => String -> prop -> Spec prop String "same priority actions are not rearranged" ((GovActionState ConwayEra -> StrictSeq (GovActionState ConwayEra) -> Expectation) -> Spec) -> (GovActionState ConwayEra -> StrictSeq (GovActionState ConwayEra) -> Expectation) -> Spec forall a b. (a -> b) -> a -> b $ \(GovActionState ConwayEra a :: GovActionState ConwayEra) (StrictSeq (GovActionState ConwayEra) as :: Seq.StrictSeq (GovActionState ConwayEra)) -> let filterPrio :: GovActionState era -> Bool filterPrio GovActionState era b = GovAction ConwayEra -> Int forall era. GovAction era -> Int actionPriority (GovActionState ConwayEra -> GovAction ConwayEra forall era. GovActionState era -> GovAction era gasAction GovActionState ConwayEra a) Int -> Int -> Bool forall a. Eq a => a -> a -> Bool == GovAction era -> Int forall era. GovAction era -> Int actionPriority (GovActionState era -> GovAction era forall era. GovActionState era -> GovAction era gasAction GovActionState era b) in (GovActionState ConwayEra -> Bool) -> [GovActionState ConwayEra] -> [GovActionState ConwayEra] forall a. (a -> Bool) -> [a] -> [a] filter GovActionState ConwayEra -> Bool forall {era}. GovActionState era -> Bool filterPrio (StrictSeq (GovActionState ConwayEra) -> [GovActionState ConwayEra] forall a. StrictSeq a -> [a] forall (t :: * -> *) a. Foldable t => t a -> [a] toList (StrictSeq (GovActionState ConwayEra) -> [GovActionState ConwayEra]) -> StrictSeq (GovActionState ConwayEra) -> [GovActionState ConwayEra] forall a b. (a -> b) -> a -> b $ forall era. StrictSeq (GovActionState era) -> StrictSeq (GovActionState era) reorderActions @ConwayEra (GovActionState ConwayEra a GovActionState ConwayEra -> StrictSeq (GovActionState ConwayEra) -> StrictSeq (GovActionState ConwayEra) forall a. a -> StrictSeq a -> StrictSeq a Seq.:<| StrictSeq (GovActionState ConwayEra) as)) [GovActionState ConwayEra] -> [GovActionState ConwayEra] -> Expectation forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation `shouldBe` (GovActionState ConwayEra -> Bool) -> [GovActionState ConwayEra] -> [GovActionState ConwayEra] forall a. (a -> Bool) -> [a] -> [a] filter GovActionState ConwayEra -> Bool forall {era}. GovActionState era -> Bool filterPrio (StrictSeq (GovActionState ConwayEra) -> [GovActionState ConwayEra] forall a. StrictSeq a -> [a] forall (t :: * -> *) a. Foldable t => t a -> [a] toList (StrictSeq (GovActionState ConwayEra) -> [GovActionState ConwayEra]) -> StrictSeq (GovActionState ConwayEra) -> [GovActionState ConwayEra] forall a b. (a -> b) -> a -> b $ StrictSeq (GovActionState ConwayEra) -> StrictSeq (GovActionState ConwayEra) forall era. StrictSeq (GovActionState era) -> StrictSeq (GovActionState era) reorderActions (GovActionState ConwayEra a GovActionState ConwayEra -> StrictSeq (GovActionState ConwayEra) -> StrictSeq (GovActionState ConwayEra) forall a. a -> StrictSeq a -> StrictSeq a Seq.:<| StrictSeq (GovActionState ConwayEra) as)) String -> (ShuffledGovActionStates ConwayEra -> Expectation) -> Spec forall prop. (HasCallStack, Testable prop) => String -> prop -> Spec prop String "orders actions correctly with shuffles" ((ShuffledGovActionStates ConwayEra -> Expectation) -> Spec) -> (ShuffledGovActionStates ConwayEra -> Expectation) -> Spec forall a b. (a -> b) -> a -> b $ \(ShuffledGovActionStates [GovActionState ConwayEra] gass [GovActionState ConwayEra] shuffledGass :: ShuffledGovActionStates ConwayEra) -> do StrictSeq (GovActionState ConwayEra) -> StrictSeq (GovActionState ConwayEra) forall era. StrictSeq (GovActionState era) -> StrictSeq (GovActionState era) reorderActions ([GovActionState ConwayEra] -> StrictSeq (GovActionState ConwayEra) forall a. [a] -> StrictSeq a Seq.fromList [GovActionState ConwayEra] gass) StrictSeq (GovActionState ConwayEra) -> StrictSeq (GovActionState ConwayEra) -> Expectation forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation `shouldBe` StrictSeq (GovActionState ConwayEra) -> StrictSeq (GovActionState ConwayEra) forall era. StrictSeq (GovActionState era) -> StrictSeq (GovActionState era) reorderActions ([GovActionState ConwayEra] -> StrictSeq (GovActionState ConwayEra) forall a. [a] -> StrictSeq a Seq.fromList [GovActionState ConwayEra] shuffledGass)