{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Test.Cardano.Ledger.Conway.Arbitrary (
genUpdateCommittee,
genNoConfidence,
genTreasuryWithdrawals,
genHardForkInitiation,
genParameterChange,
genNewConstitution,
govActionGenerators,
genConwayPlutusPurposePointer,
genGovAction,
genGovActionState,
genPParamUpdateGovAction,
genHardForkGovAction,
genCommitteeGovAction,
genConstitutionGovAction,
genProposals,
ProposalsNewActions (..),
ProposalsForEnactment (..),
ShuffledGovActionStates (..),
) where
import Cardano.Ledger.Alonzo.Plutus.Evaluate (CollectError)
import Cardano.Ledger.BaseTypes (StrictMaybe (..))
import Cardano.Ledger.Binary (Sized)
import Cardano.Ledger.Conway.Core
import Cardano.Ledger.Conway.Genesis (ConwayGenesis (..))
import Cardano.Ledger.Conway.Governance
import Cardano.Ledger.Conway.PParams (
ConwayPParams (..),
THKD (..),
UpgradeConwayPParams (..),
)
import Cardano.Ledger.Conway.Rules
import Cardano.Ledger.Conway.Scripts (ConwayPlutusPurpose (..))
import Cardano.Ledger.Conway.TxBody
import Cardano.Ledger.Conway.TxCert
import Cardano.Ledger.Conway.TxInfo (ConwayContextError)
import Cardano.Ledger.HKD (HKD, NoUpdate (..))
import Cardano.Ledger.Plutus (Language (PlutusV3))
import Control.State.Transition.Extended (STS (Event))
import Data.Default (def)
import Data.Foldable (toList)
import Data.Functor.Identity (Identity)
import Data.List (nubBy)
import qualified Data.Map.Strict as Map
import qualified Data.Sequence as Seq
import qualified Data.Sequence.Strict as SSeq
import qualified Data.Set as Set
import Data.Word
import Generic.Random (genericArbitraryU)
import Lens.Micro
import Test.Cardano.Data (genNonEmptyMap)
import Test.Cardano.Data.Arbitrary ()
import Test.Cardano.Ledger.Alonzo.Arbitrary (genValidAndUnknownCostModels, genValidCostModel)
import Test.Cardano.Ledger.Babbage.Arbitrary ()
import Test.Cardano.Ledger.Binary.Random (QC (..))
import Test.Cardano.Ledger.Common
import Test.Cardano.Ledger.Core.Arbitrary (uniformSubMap)
instance
(Era era, Arbitrary (PParamsUpdate era)) =>
Arbitrary (PulsingSnapshot era)
where
arbitrary :: Gen (PulsingSnapshot era)
arbitrary = forall era.
StrictSeq (GovActionState era)
-> Map DRep (CompactForm Coin)
-> Map (Credential 'DRepRole) DRepState
-> Map (KeyHash 'StakePool) (CompactForm Coin)
-> PulsingSnapshot era
PulsingSnapshot forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
instance
(Arbitrary (PParams era), Arbitrary (PParamsUpdate era), Era era) =>
Arbitrary (DRepPulsingState era)
where
arbitrary :: Gen (DRepPulsingState era)
arbitrary = forall era.
PulsingSnapshot era -> RatifyState era -> DRepPulsingState era
DRComplete forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
instance
( EraPParams era
, Arbitrary (PlutusPurpose AsItem era)
, Arbitrary (PlutusPurpose AsIx era)
, Arbitrary (TxCert era)
, Arbitrary (PParamsHKD StrictMaybe era)
) =>
Arbitrary (ConwayContextError era)
where
arbitrary :: Gen (ConwayContextError era)
arbitrary = forall a. (GArbitrary UnsizedOpts a, GUniformWeight a) => Gen a
genericArbitraryU
instance Arbitrary ConwayGenesis where
arbitrary :: Gen ConwayGenesis
arbitrary =
UpgradeConwayPParams Identity
-> Constitution ConwayEra
-> Committee ConwayEra
-> ListMap (Credential 'Staking) Delegatee
-> ListMap (Credential 'DRepRole) DRepState
-> ConwayGenesis
ConwayGenesis
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
instance Arbitrary (UpgradeConwayPParams Identity) where
arbitrary :: Gen (UpgradeConwayPParams Identity)
arbitrary =
forall (f :: * -> *).
HKD f PoolVotingThresholds
-> HKD f DRepVotingThresholds
-> HKD f Word16
-> HKD f EpochInterval
-> HKD f EpochInterval
-> HKD f Coin
-> HKD f Coin
-> HKD f EpochInterval
-> HKD f NonNegativeInterval
-> HKD f CostModel
-> UpgradeConwayPParams f
UpgradeConwayPParams
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Language -> Gen CostModel
genValidCostModel Language
PlutusV3
instance Arbitrary Delegatee where
arbitrary :: Gen Delegatee
arbitrary =
forall a. HasCallStack => [Gen a] -> Gen a
oneof
[ KeyHash 'StakePool -> Delegatee
DelegStake forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
, DRep -> Delegatee
DelegVote forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
, KeyHash 'StakePool -> DRep -> Delegatee
DelegStakeVote forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
]
instance Arbitrary ConwayDelegCert where
arbitrary :: Gen ConwayDelegCert
arbitrary =
forall a. HasCallStack => [Gen a] -> Gen a
oneof
[ Credential 'Staking -> StrictMaybe Coin -> ConwayDelegCert
ConwayRegCert forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
, Credential 'Staking -> StrictMaybe Coin -> ConwayDelegCert
ConwayUnRegCert forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
, Credential 'Staking -> Delegatee -> ConwayDelegCert
ConwayDelegCert forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
, Credential 'Staking -> Delegatee -> Coin -> ConwayDelegCert
ConwayRegDelegCert forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
]
instance Era era => Arbitrary (ConwayTxCert era) where
arbitrary :: Gen (ConwayTxCert era)
arbitrary =
forall a. HasCallStack => [Gen a] -> Gen a
oneof
[ forall era. ConwayDelegCert -> ConwayTxCert era
ConwayTxCertDeleg forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
, forall era. PoolCert -> ConwayTxCert era
ConwayTxCertPool forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
, forall era. ConwayGovCert -> ConwayTxCert era
ConwayTxCertGov forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
]
instance Arbitrary ConwayGovCert where
arbitrary :: Gen ConwayGovCert
arbitrary =
forall a. HasCallStack => [Gen a] -> Gen a
oneof
[ Credential 'DRepRole -> Coin -> StrictMaybe Anchor -> ConwayGovCert
ConwayRegDRep forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
, Credential 'DRepRole -> Coin -> ConwayGovCert
ConwayUnRegDRep forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
, Credential 'ColdCommitteeRole
-> Credential 'HotCommitteeRole -> ConwayGovCert
ConwayAuthCommitteeHotKey forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
, Credential 'ColdCommitteeRole
-> StrictMaybe Anchor -> ConwayGovCert
ConwayResignCommitteeColdKey forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
]
instance
(EraPParams era, Arbitrary (PParams era), Arbitrary (PParamsHKD StrictMaybe era)) =>
Arbitrary (ConwayGovState era)
where
arbitrary :: Gen (ConwayGovState era)
arbitrary =
forall era.
Proposals era
-> StrictMaybe (Committee era)
-> Constitution era
-> PParams era
-> PParams era
-> FuturePParams era
-> DRepPulsingState era
-> ConwayGovState era
ConwayGovState
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
shrink :: ConwayGovState era -> [ConwayGovState era]
shrink = forall a.
(Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) =>
a -> [a]
genericShrink
instance
(Era era, Arbitrary (PParams era), Arbitrary (PParamsUpdate era)) =>
Arbitrary (RatifyState era)
where
arbitrary :: Gen (RatifyState era)
arbitrary =
forall era.
EnactState era
-> Seq (GovActionState era)
-> Set GovActionId
-> Bool
-> RatifyState era
RatifyState
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
shrink :: RatifyState era -> [RatifyState era]
shrink (RatifyState EnactState era
a Seq (GovActionState era)
b Set GovActionId
c Bool
d) =
[ forall era.
EnactState era
-> Seq (GovActionState era)
-> Set GovActionId
-> Bool
-> RatifyState era
RatifyState EnactState era
a' (forall a. [a] -> Seq a
Seq.fromList [GovActionState era]
b') Set GovActionId
c' Bool
d'
| (EnactState era
a', [GovActionState era]
b', Set GovActionId
c', Bool
d') <- forall a. Arbitrary a => a -> [a]
shrink (EnactState era
a, forall (t :: * -> *) a. Foldable t => t a -> [a]
toList Seq (GovActionState era)
b, Set GovActionId
c, Bool
d)
]
instance
Era era =>
Arbitrary (RatifyEnv era)
where
arbitrary :: Gen (RatifyEnv era)
arbitrary =
forall era.
Map (Credential 'Staking) (CompactForm Coin)
-> PoolDistr
-> Map DRep (CompactForm Coin)
-> Map (Credential 'DRepRole) DRepState
-> EpochNo
-> CommitteeState era
-> Map (Credential 'Staking) DRep
-> Map (KeyHash 'StakePool) PoolParams
-> RatifyEnv era
RatifyEnv
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
shrink :: RatifyEnv era -> [RatifyEnv era]
shrink = forall a.
(Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) =>
a -> [a]
genericShrink
instance
(Era era, Arbitrary (PParams era)) =>
Arbitrary (EnactState era)
where
arbitrary :: Gen (EnactState era)
arbitrary =
forall era.
StrictMaybe (Committee era)
-> Constitution era
-> PParams era
-> PParams era
-> Coin
-> Map (Credential 'Staking) Coin
-> GovRelation StrictMaybe era
-> EnactState era
EnactState
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
shrink :: EnactState era -> [EnactState era]
shrink = forall a.
(Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) =>
a -> [a]
genericShrink
instance
( EraTxOut era
, Arbitrary (Value era)
, Arbitrary (TxOut era)
, Arbitrary (PredicateFailure (EraRule "UTXOS" era))
) =>
Arbitrary (ConwayUtxoPredFailure era)
where
arbitrary :: Gen (ConwayUtxoPredFailure era)
arbitrary = forall a. (GArbitrary UnsizedOpts a, GUniformWeight a) => Gen a
genericArbitraryU
instance
( Era era
, Arbitrary (PredicateFailure (EraRule "UTXO" era))
, Arbitrary (TxCert era)
, Arbitrary (PlutusPurpose AsItem era)
, Arbitrary (PlutusPurpose AsIx era)
) =>
Arbitrary (ConwayUtxowPredFailure era)
where
arbitrary :: Gen (ConwayUtxowPredFailure era)
arbitrary = forall a. (GArbitrary UnsizedOpts a, GUniformWeight a) => Gen a
genericArbitraryU
_uniqueIdGovActions ::
(Era era, Arbitrary (PParamsUpdate era)) =>
Gen (SSeq.StrictSeq (GovActionState era))
_uniqueIdGovActions :: forall era.
(Era era, Arbitrary (PParamsUpdate era)) =>
Gen (StrictSeq (GovActionState era))
_uniqueIdGovActions = forall a. [a] -> StrictSeq a
SSeq.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> a -> Bool) -> [a] -> [a]
nubBy (\GovActionState era
x GovActionState era
y -> forall era. GovActionState era -> GovActionId
gasId GovActionState era
x forall a. Eq a => a -> a -> Bool
== forall era. GovActionState era -> GovActionId
gasId GovActionState era
y) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
instance
(forall p. Arbitrary (f (GovPurposeId (p :: GovActionPurpose) era))) =>
Arbitrary (GovRelation f era)
where
arbitrary :: Gen (GovRelation f era)
arbitrary = forall (f :: * -> *) era.
f (GovPurposeId 'PParamUpdatePurpose era)
-> f (GovPurposeId 'HardForkPurpose era)
-> f (GovPurposeId 'CommitteePurpose era)
-> f (GovPurposeId 'ConstitutionPurpose era)
-> GovRelation f era
GovRelation forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
data ProposalsForEnactment era
= ProposalsForEnactment
{ forall era. ProposalsForEnactment era -> Proposals era
pfeProposals :: Proposals era
, forall era. ProposalsForEnactment era -> Seq (GovActionState era)
pfeToEnact :: Seq.Seq (GovActionState era)
, forall era. ProposalsForEnactment era -> Set GovActionId
pfeToRemove :: Set.Set GovActionId
, forall era. ProposalsForEnactment era -> Set GovActionId
pfeToRetain :: Set.Set GovActionId
}
deriving (Int -> ProposalsForEnactment era -> ShowS
forall era.
EraPParams era =>
Int -> ProposalsForEnactment era -> ShowS
forall era. EraPParams era => [ProposalsForEnactment era] -> ShowS
forall era. EraPParams era => ProposalsForEnactment era -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProposalsForEnactment era] -> ShowS
$cshowList :: forall era. EraPParams era => [ProposalsForEnactment era] -> ShowS
show :: ProposalsForEnactment era -> String
$cshow :: forall era. EraPParams era => ProposalsForEnactment era -> String
showsPrec :: Int -> ProposalsForEnactment era -> ShowS
$cshowsPrec :: forall era.
EraPParams era =>
Int -> ProposalsForEnactment era -> ShowS
Show, ProposalsForEnactment era -> ProposalsForEnactment era -> Bool
forall era.
EraPParams era =>
ProposalsForEnactment era -> ProposalsForEnactment era -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProposalsForEnactment era -> ProposalsForEnactment era -> Bool
$c/= :: forall era.
EraPParams era =>
ProposalsForEnactment era -> ProposalsForEnactment era -> Bool
== :: ProposalsForEnactment era -> ProposalsForEnactment era -> Bool
$c== :: forall era.
EraPParams era =>
ProposalsForEnactment era -> ProposalsForEnactment era -> Bool
Eq)
instance
(EraPParams era, Arbitrary (PParamsUpdate era), Arbitrary (PParamsHKD StrictMaybe era)) =>
Arbitrary (ProposalsForEnactment era)
where
arbitrary :: Gen (ProposalsForEnactment era)
arbitrary = do
Proposals era
ps <- forall era.
(HasCallStack, EraPParams era,
Arbitrary (PParamsHKD StrictMaybe era)) =>
(Int, Int) -> Gen (Proposals era)
genProposals @era (Int
2, Int
50)
let gasHasNoLineage :: GovActionState era -> Bool
gasHasNoLineage GovActionState era
gas =
case forall era. GovActionState era -> GovAction era
gasAction GovActionState era
gas of
InfoAction {} -> Bool
True
TreasuryWithdrawals {} -> Bool
True
GovAction era
_ -> Bool
False
hasNoLineage :: GovActionId -> Bool
hasNoLineage GovActionId
gaId =
case forall era.
GovActionId -> Proposals era -> Maybe (GovActionState era)
proposalsLookupId GovActionId
gaId Proposals era
ps of
Maybe (GovActionState era)
Nothing -> forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"Expected " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show GovActionId
gaId forall a. [a] -> [a] -> [a]
++ String
" in generated proposals"
Just GovActionState era
gas -> forall {era}. GovActionState era -> Bool
gasHasNoLineage GovActionState era
gas
Seq (GovActionState era)
pparamUpdates <- forall (p :: GovActionPurpose).
(forall (f :: * -> *).
Lens' (GovRelation f era) (f (GovPurposeId p era)))
-> Proposals era
-> Seq (GovActionState era)
-> Gen (Seq (GovActionState era))
chooseLineage forall (f :: * -> *) era.
Lens'
(GovRelation f era) (f (GovPurposeId 'PParamUpdatePurpose era))
grPParamUpdateL Proposals era
ps forall a. Seq a
Seq.Empty
Seq (GovActionState era)
hardForks <- forall (p :: GovActionPurpose).
(forall (f :: * -> *).
Lens' (GovRelation f era) (f (GovPurposeId p era)))
-> Proposals era
-> Seq (GovActionState era)
-> Gen (Seq (GovActionState era))
chooseLineage forall (f :: * -> *) era.
Lens' (GovRelation f era) (f (GovPurposeId 'HardForkPurpose era))
grHardForkL Proposals era
ps forall a. Seq a
Seq.Empty
Seq (GovActionState era)
committees <- forall (p :: GovActionPurpose).
(forall (f :: * -> *).
Lens' (GovRelation f era) (f (GovPurposeId p era)))
-> Proposals era
-> Seq (GovActionState era)
-> Gen (Seq (GovActionState era))
chooseLineage forall (f :: * -> *) era.
Lens' (GovRelation f era) (f (GovPurposeId 'CommitteePurpose era))
grCommitteeL Proposals era
ps forall a. Seq a
Seq.Empty
Seq (GovActionState era)
constitutions <- forall (p :: GovActionPurpose).
(forall (f :: * -> *).
Lens' (GovRelation f era) (f (GovPurposeId p era)))
-> Proposals era
-> Seq (GovActionState era)
-> Gen (Seq (GovActionState era))
chooseLineage forall (f :: * -> *) era.
Lens'
(GovRelation f era) (f (GovPurposeId 'ConstitutionPurpose era))
grConstitutionL Proposals era
ps forall a. Seq a
Seq.Empty
Map GovActionId (GovActionState era)
noLineageMap <- forall g (m :: * -> *) k v.
(StatefulGen g m, Ord k) =>
Maybe Int -> Map k v -> g -> m (Map k v)
uniformSubMap forall a. Maybe a
Nothing (forall a k. (a -> Bool) -> Map k a -> Map k a
Map.filter forall {era}. GovActionState era -> Bool
gasHasNoLineage forall a b. (a -> b) -> a -> b
$ forall era. Proposals era -> Map GovActionId (GovActionState era)
proposalsActionsMap Proposals era
ps) QC
QC
Seq (GovActionState era)
noLineage <- forall a. [a] -> Seq a
Seq.fromList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. [a] -> Gen [a]
shuffle (forall k a. Map k a -> [a]
Map.elems Map GovActionId (GovActionState era)
noLineageMap)
Seq (GovActionState era)
sequencedGass <-
forall a. Seq (Seq a) -> Seq a -> Gen (Seq a)
sequenceLineages
( forall a. (a -> Bool) -> Seq a -> Seq a
Seq.filter
(Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Seq a -> Bool
Seq.null)
(forall a. [a] -> Seq a
Seq.fromList [Seq (GovActionState era)
pparamUpdates, Seq (GovActionState era)
hardForks, Seq (GovActionState era)
committees, Seq (GovActionState era)
constitutions, Seq (GovActionState era)
noLineage])
)
forall a. Seq a
Seq.Empty
let notEnacted :: Set GovActionId
notEnacted =
forall a. Ord a => [a] -> Set a
Set.fromList (forall (t :: * -> *) a. Foldable t => t a -> [a]
toList forall a b. (a -> b) -> a -> b
$ forall era. Proposals era -> StrictSeq GovActionId
proposalsIds Proposals era
ps)
forall a. Ord a => Set a -> Set a -> Set a
`Set.difference` forall a. Ord a => [a] -> Set a
Set.fromList (forall era. GovActionState era -> GovActionId
gasId forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) a. Foldable t => t a -> [a]
toList Seq (GovActionState era)
sequencedGass)
let (Set GovActionId
retained, Set GovActionId
removedDueToConflict) = forall a. (a -> Bool) -> Set a -> (Set a, Set a)
Set.partition GovActionId -> Bool
hasNoLineage Set GovActionId
notEnacted
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$
ProposalsForEnactment
{ pfeProposals :: Proposals era
pfeProposals = Proposals era
ps
, pfeToEnact :: Seq (GovActionState era)
pfeToEnact = Seq (GovActionState era)
sequencedGass
, pfeToRemove :: Set GovActionId
pfeToRemove = Set GovActionId
removedDueToConflict
, pfeToRetain :: Set GovActionId
pfeToRetain = Set GovActionId
retained
}
where
chooseLineage ::
(forall f. Lens' (GovRelation f era) (f (GovPurposeId p era))) ->
Proposals era ->
Seq.Seq (GovActionState era) ->
Gen (Seq.Seq (GovActionState era))
chooseLineage :: forall (p :: GovActionPurpose).
(forall (f :: * -> *).
Lens' (GovRelation f era) (f (GovPurposeId p era)))
-> Proposals era
-> Seq (GovActionState era)
-> Gen (Seq (GovActionState era))
chooseLineage forall (f :: * -> *).
Lens' (GovRelation f era) (f (GovPurposeId p era))
govRelL Proposals era
ps = \case
Seq (GovActionState era)
Seq.Empty ->
let children :: Set (GovPurposeId p era)
children = Proposals era
ps forall s a. s -> Getting a s a -> a
^. forall era. Lens' (Proposals era) (GovRelation PRoot era)
pRootsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *).
Lens' (GovRelation f era) (f (GovPurposeId p era))
govRelL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Lens' (PRoot a) (Set a)
prChildrenL
in if forall a. Set a -> Bool
Set.null Set (GovPurposeId p era)
children
then forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Seq a
Seq.Empty
else do
GovPurposeId p era
child <- forall a. HasCallStack => [a] -> Gen a
elements forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> [a]
toList Set (GovPurposeId p era)
children
forall (p :: GovActionPurpose).
(forall (f :: * -> *).
Lens' (GovRelation f era) (f (GovPurposeId p era)))
-> Proposals era
-> Seq (GovActionState era)
-> Gen (Seq (GovActionState era))
chooseLineage forall (f :: * -> *).
Lens' (GovRelation f era) (f (GovPurposeId p era))
govRelL Proposals era
ps (forall a. Seq a
Seq.Empty forall a. Seq a -> a -> Seq a
Seq.:|> (forall era. Proposals era -> Map GovActionId (GovActionState era)
proposalsActionsMap Proposals era
ps forall k a. Ord k => Map k a -> k -> a
Map.! forall (p :: GovActionPurpose) era.
GovPurposeId p era -> GovActionId
unGovPurposeId GovPurposeId p era
child))
lineage :: Seq (GovActionState era)
lineage@(Seq (GovActionState era)
_ Seq.:|> GovActionState era
gas) ->
let children :: Set (GovPurposeId p era)
children = Proposals era
ps forall s a. s -> Getting a s a -> a
^. forall era. Lens' (Proposals era) (GovRelation PGraph era)
pGraphL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *).
Lens' (GovRelation f era) (f (GovPurposeId p era))
govRelL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Lens' (PGraph a) (Map a (PEdges a))
pGraphNodesL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s a. (s -> a) -> SimpleGetter s a
to (forall k a. Ord k => Map k a -> k -> a
Map.! forall (p :: GovActionPurpose) era.
GovActionId -> GovPurposeId p era
GovPurposeId (forall era. GovActionState era -> GovActionId
gasId GovActionState era
gas)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Lens' (PEdges a) (Set a)
peChildrenL
in if forall a. Set a -> Bool
Set.null Set (GovPurposeId p era)
children
then forall (f :: * -> *) a. Applicative f => a -> f a
pure Seq (GovActionState era)
lineage
else do
GovPurposeId p era
child <- forall a. HasCallStack => [a] -> Gen a
elements forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> [a]
toList Set (GovPurposeId p era)
children
forall (p :: GovActionPurpose).
(forall (f :: * -> *).
Lens' (GovRelation f era) (f (GovPurposeId p era)))
-> Proposals era
-> Seq (GovActionState era)
-> Gen (Seq (GovActionState era))
chooseLineage forall (f :: * -> *).
Lens' (GovRelation f era) (f (GovPurposeId p era))
govRelL Proposals era
ps (Seq (GovActionState era)
lineage forall a. Seq a -> a -> Seq a
Seq.:|> (forall era. Proposals era -> Map GovActionId (GovActionState era)
proposalsActionsMap Proposals era
ps forall k a. Ord k => Map k a -> k -> a
Map.! forall (p :: GovActionPurpose) era.
GovPurposeId p era -> GovActionId
unGovPurposeId GovPurposeId p era
child))
consumeHeadAtIndex :: Int -> Seq.Seq (Seq.Seq a) -> (a, Seq.Seq (Seq.Seq a))
consumeHeadAtIndex :: forall a. Int -> Seq (Seq a) -> (a, Seq (Seq a))
consumeHeadAtIndex Int
idx Seq (Seq a)
ss = (Seq (Seq a)
ss forall a. Seq a -> Int -> a
`Seq.index` Int
idx forall a. Seq a -> Int -> a
`Seq.index` Int
0, forall a. (a -> a) -> Int -> Seq a -> Seq a
Seq.adjust' (forall a. Int -> Seq a -> Seq a
Seq.drop Int
1) Int
idx Seq (Seq a)
ss)
sequenceLineages :: Seq.Seq (Seq.Seq a) -> Seq.Seq a -> Gen (Seq.Seq a)
sequenceLineages :: forall a. Seq (Seq a) -> Seq a -> Gen (Seq a)
sequenceLineages Seq (Seq a)
lineages Seq a
sequenced = case Seq (Seq a)
lineages of
Seq (Seq a)
Seq.Empty -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Seq a
sequenced
Seq (Seq a)
_ -> do
Int
index <- (Int, Int) -> Gen Int
chooseInt (Int
0, forall (t :: * -> *) a. Foldable t => t a -> Int
length Seq (Seq a)
lineages forall a. Num a => a -> a -> a
- Int
1)
let (a
chosen, Seq (Seq a)
adjustedLineages) = forall a. Int -> Seq (Seq a) -> (a, Seq (Seq a))
consumeHeadAtIndex Int
index Seq (Seq a)
lineages
forall a. Seq (Seq a) -> Seq a -> Gen (Seq a)
sequenceLineages (forall a. (a -> Bool) -> Seq a -> Seq a
Seq.filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Seq a -> Bool
Seq.null) Seq (Seq a)
adjustedLineages) (Seq a
sequenced forall a. Seq a -> a -> Seq a
Seq.:|> a
chosen)
data ProposalsNewActions era = ProposalsNewActions (Proposals era) [GovActionState era]
deriving (Int -> ProposalsNewActions era -> ShowS
forall era.
EraPParams era =>
Int -> ProposalsNewActions era -> ShowS
forall era. EraPParams era => [ProposalsNewActions era] -> ShowS
forall era. EraPParams era => ProposalsNewActions era -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProposalsNewActions era] -> ShowS
$cshowList :: forall era. EraPParams era => [ProposalsNewActions era] -> ShowS
show :: ProposalsNewActions era -> String
$cshow :: forall era. EraPParams era => ProposalsNewActions era -> String
showsPrec :: Int -> ProposalsNewActions era -> ShowS
$cshowsPrec :: forall era.
EraPParams era =>
Int -> ProposalsNewActions era -> ShowS
Show, ProposalsNewActions era -> ProposalsNewActions era -> Bool
forall era.
EraPParams era =>
ProposalsNewActions era -> ProposalsNewActions era -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProposalsNewActions era -> ProposalsNewActions era -> Bool
$c/= :: forall era.
EraPParams era =>
ProposalsNewActions era -> ProposalsNewActions era -> Bool
== :: ProposalsNewActions era -> ProposalsNewActions era -> Bool
$c== :: forall era.
EraPParams era =>
ProposalsNewActions era -> ProposalsNewActions era -> Bool
Eq)
instance
(EraPParams era, Arbitrary (PParamsUpdate era), Arbitrary (PParamsHKD StrictMaybe era)) =>
Arbitrary (ProposalsNewActions era)
where
arbitrary :: Gen (ProposalsNewActions era)
arbitrary = do
Proposals era
ps <- forall a. Arbitrary a => Gen a
arbitrary
Int
i <- (Int, Int) -> Gen Int
chooseInt (Int
2, Int
20)
[GovActionState era]
gass <- forall a. Int -> Gen a -> Gen [a]
vectorOf Int
i forall a b. (a -> b) -> a -> b
$ forall era. GovAction era -> Gen (GovActionState era)
genGovActionState forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall era.
(Era era, Arbitrary (PParamsHKD StrictMaybe era)) =>
Proposals era -> Gen (GovAction era)
genGovAction Proposals era
ps
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall era.
Proposals era -> [GovActionState era] -> ProposalsNewActions era
ProposalsNewActions Proposals era
ps [GovActionState era]
gass
instance
(EraPParams era, Arbitrary (PParamsHKD StrictMaybe era)) =>
Arbitrary (Proposals era)
where
arbitrary :: Gen (Proposals era)
arbitrary = forall era.
(HasCallStack, EraPParams era,
Arbitrary (PParamsHKD StrictMaybe era)) =>
(Int, Int) -> Gen (Proposals era)
genProposals (Int
0, Int
30)
shrink :: Proposals era -> [Proposals era]
shrink Proposals era
ps =
[ Proposals era
ps'
| Set GovActionId
gais' <- forall a. Arbitrary a => a -> [a]
shrink Set GovActionId
gais
, let (Proposals era
ps', Map GovActionId (GovActionState era)
_) = forall era.
EraPParams era =>
Set GovActionId
-> Proposals era
-> (Proposals era, Map GovActionId (GovActionState era))
proposalsRemoveWithDescendants (Set GovActionId
gais forall a. Ord a => Set a -> Set a -> Set a
Set.\\ Set GovActionId
gais') Proposals era
ps
]
where
gais :: Set GovActionId
gais = forall a. Ord a => [a] -> Set a
Set.fromList (forall (t :: * -> *) a. Foldable t => t a -> [a]
toList forall a b. (a -> b) -> a -> b
$ forall era. Proposals era -> StrictSeq GovActionId
proposalsIds Proposals era
ps)
genProposals ::
forall era.
( HasCallStack
, EraPParams era
, Arbitrary (PParamsHKD StrictMaybe era)
) =>
(Int, Int) ->
Gen (Proposals era)
genProposals :: forall era.
(HasCallStack, EraPParams era,
Arbitrary (PParamsHKD StrictMaybe era)) =>
(Int, Int) -> Gen (Proposals era)
genProposals (Int, Int)
range = do
GovRelation StrictMaybe era
pgais <- forall a. Arbitrary a => Gen a
arbitrary
Int
i <- (Int, Int) -> Gen Int
chooseInt (Int, Int)
range
Proposals era -> Int -> Gen (Proposals era)
go (forall a. Default a => a
def forall a b. a -> (a -> b) -> b
& forall era. Lens' (Proposals era) (GovRelation PRoot era)
pRootsL forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall era. GovRelation StrictMaybe era -> GovRelation PRoot era
fromPrevGovActionIds GovRelation StrictMaybe era
pgais) Int
i
where
go :: Proposals era -> Int -> Gen (Proposals era)
go :: Proposals era -> Int -> Gen (Proposals era)
go !Proposals era
ps Int
n
| Int
n forall a. Ord a => a -> a -> Bool
<= Int
0 = forall (f :: * -> *) a. Applicative f => a -> f a
pure Proposals era
ps
| Bool
otherwise = do
GovActionState era
gas <- forall era. GovAction era -> Gen (GovActionState era)
genGovActionState @era forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall era.
(Era era, Arbitrary (PParamsHKD StrictMaybe era)) =>
Proposals era -> Gen (GovAction era)
genGovAction Proposals era
ps
case forall era.
(EraPParams era, HasCallStack) =>
GovActionState era -> Proposals era -> Maybe (Proposals era)
proposalsAddAction GovActionState era
gas Proposals era
ps of
Maybe (Proposals era)
Nothing -> forall a. HasCallStack => String -> a
error String
"Error adding GovActionState to Proposals"
Just Proposals era
ps' -> Proposals era -> Int -> Gen (Proposals era)
go Proposals era
ps' (Int
n forall a. Num a => a -> a -> a
- Int
1)
genGovAction ::
forall era.
(Era era, Arbitrary (PParamsHKD StrictMaybe era)) =>
Proposals era ->
Gen (GovAction era)
genGovAction :: forall era.
(Era era, Arbitrary (PParamsHKD StrictMaybe era)) =>
Proposals era -> Gen (GovAction era)
genGovAction Proposals era
ps =
forall a. HasCallStack => [Gen a] -> Gen a
oneof
[ forall (p :: GovActionPurpose).
(StrictMaybe (GovPurposeId p era) -> Gen (GovAction era))
-> (forall (f :: * -> *).
Lens' (GovRelation f era) (f (GovPurposeId p era)))
-> Gen (GovAction era)
genWithParent forall era.
(Era era, Arbitrary (PParamsHKD StrictMaybe era)) =>
StrictMaybe (GovPurposeId 'PParamUpdatePurpose era)
-> Gen (GovAction era)
genPParamUpdateGovAction forall (f :: * -> *) era.
Lens'
(GovRelation f era) (f (GovPurposeId 'PParamUpdatePurpose era))
grPParamUpdateL
, forall (p :: GovActionPurpose).
(StrictMaybe (GovPurposeId p era) -> Gen (GovAction era))
-> (forall (f :: * -> *).
Lens' (GovRelation f era) (f (GovPurposeId p era)))
-> Gen (GovAction era)
genWithParent forall era.
StrictMaybe (GovPurposeId 'HardForkPurpose era)
-> Gen (GovAction era)
genHardForkGovAction forall (f :: * -> *) era.
Lens' (GovRelation f era) (f (GovPurposeId 'HardForkPurpose era))
grHardForkL
, forall era. Gen (GovAction era)
genTreasuryWithdrawals
, forall (p :: GovActionPurpose).
(StrictMaybe (GovPurposeId p era) -> Gen (GovAction era))
-> (forall (f :: * -> *).
Lens' (GovRelation f era) (f (GovPurposeId p era)))
-> Gen (GovAction era)
genWithParent forall era.
StrictMaybe (GovPurposeId 'CommitteePurpose era)
-> Gen (GovAction era)
genCommitteeGovAction forall (f :: * -> *) era.
Lens' (GovRelation f era) (f (GovPurposeId 'CommitteePurpose era))
grCommitteeL
, forall (p :: GovActionPurpose).
(StrictMaybe (GovPurposeId p era) -> Gen (GovAction era))
-> (forall (f :: * -> *).
Lens' (GovRelation f era) (f (GovPurposeId p era)))
-> Gen (GovAction era)
genWithParent forall era.
Era era =>
StrictMaybe (GovPurposeId 'ConstitutionPurpose era)
-> Gen (GovAction era)
genConstitutionGovAction forall (f :: * -> *) era.
Lens'
(GovRelation f era) (f (GovPurposeId 'ConstitutionPurpose era))
grConstitutionL
, forall (f :: * -> *) a. Applicative f => a -> f a
pure forall era. GovAction era
InfoAction
]
where
genWithParent ::
(StrictMaybe (GovPurposeId p era) -> Gen (GovAction era)) ->
(forall f. Lens' (GovRelation f era) (f (GovPurposeId p era))) ->
Gen (GovAction era)
genWithParent :: forall (p :: GovActionPurpose).
(StrictMaybe (GovPurposeId p era) -> Gen (GovAction era))
-> (forall (f :: * -> *).
Lens' (GovRelation f era) (f (GovPurposeId p era)))
-> Gen (GovAction era)
genWithParent StrictMaybe (GovPurposeId p era) -> Gen (GovAction era)
gen forall (f :: * -> *).
Lens' (GovRelation f era) (f (GovPurposeId p era))
govRelL =
StrictMaybe (GovPurposeId p era) -> Gen (GovAction era)
gen
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall a. HasCallStack => [a] -> Gen a
elements
( (Proposals era
ps forall s a. s -> Getting a s a -> a
^. forall era. Lens' (Proposals era) (GovRelation PRoot era)
pRootsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *).
Lens' (GovRelation f era) (f (GovPurposeId p era))
govRelL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Lens' (PRoot a) (StrictMaybe a)
prRootL)
forall a. a -> [a] -> [a]
: forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. a -> StrictMaybe a
SJust (forall k a. Map k a -> [k]
Map.keys forall a b. (a -> b) -> a -> b
$ Proposals era
ps forall s a. s -> Getting a s a -> a
^. forall era. Lens' (Proposals era) (GovRelation PGraph era)
pGraphL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *).
Lens' (GovRelation f era) (f (GovPurposeId p era))
govRelL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Lens' (PGraph a) (Map a (PEdges a))
pGraphNodesL)
)
genPParamUpdateGovAction ::
( Era era
, Arbitrary (PParamsHKD StrictMaybe era)
) =>
StrictMaybe (GovPurposeId 'PParamUpdatePurpose era) ->
Gen (GovAction era)
genPParamUpdateGovAction :: forall era.
(Era era, Arbitrary (PParamsHKD StrictMaybe era)) =>
StrictMaybe (GovPurposeId 'PParamUpdatePurpose era)
-> Gen (GovAction era)
genPParamUpdateGovAction StrictMaybe (GovPurposeId 'PParamUpdatePurpose era)
parent = forall era.
StrictMaybe (GovPurposeId 'PParamUpdatePurpose era)
-> PParamsUpdate era -> StrictMaybe ScriptHash -> GovAction era
ParameterChange StrictMaybe (GovPurposeId 'PParamUpdatePurpose era)
parent forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
genHardForkGovAction ::
StrictMaybe (GovPurposeId 'HardForkPurpose era) ->
Gen (GovAction era)
genHardForkGovAction :: forall era.
StrictMaybe (GovPurposeId 'HardForkPurpose era)
-> Gen (GovAction era)
genHardForkGovAction StrictMaybe (GovPurposeId 'HardForkPurpose era)
parent = forall era.
StrictMaybe (GovPurposeId 'HardForkPurpose era)
-> ProtVer -> GovAction era
HardForkInitiation StrictMaybe (GovPurposeId 'HardForkPurpose era)
parent forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
genCommitteeGovAction ::
StrictMaybe (GovPurposeId 'CommitteePurpose era) ->
Gen (GovAction era)
genCommitteeGovAction :: forall era.
StrictMaybe (GovPurposeId 'CommitteePurpose era)
-> Gen (GovAction era)
genCommitteeGovAction StrictMaybe (GovPurposeId 'CommitteePurpose era)
parent =
forall a. HasCallStack => [Gen a] -> Gen a
oneof
[ forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall era.
StrictMaybe (GovPurposeId 'CommitteePurpose era) -> GovAction era
NoConfidence StrictMaybe (GovPurposeId 'CommitteePurpose era)
parent
, forall era.
StrictMaybe (GovPurposeId 'CommitteePurpose era)
-> Set (Credential 'ColdCommitteeRole)
-> Map (Credential 'ColdCommitteeRole) EpochNo
-> UnitInterval
-> GovAction era
UpdateCommittee StrictMaybe (GovPurposeId 'CommitteePurpose era)
parent forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
]
genConstitutionGovAction ::
Era era =>
StrictMaybe (GovPurposeId 'ConstitutionPurpose era) ->
Gen (GovAction era)
genConstitutionGovAction :: forall era.
Era era =>
StrictMaybe (GovPurposeId 'ConstitutionPurpose era)
-> Gen (GovAction era)
genConstitutionGovAction StrictMaybe (GovPurposeId 'ConstitutionPurpose era)
parent = forall era.
StrictMaybe (GovPurposeId 'ConstitutionPurpose era)
-> Constitution era -> GovAction era
NewConstitution StrictMaybe (GovPurposeId 'ConstitutionPurpose era)
parent forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
genGovActionState :: GovAction era -> Gen (GovActionState era)
genGovActionState :: forall era. GovAction era -> Gen (GovActionState era)
genGovActionState GovAction era
ga =
forall era.
GovActionId
-> Map (Credential 'HotCommitteeRole) Vote
-> Map (Credential 'DRepRole) Vote
-> Map (KeyHash 'StakePool) Vote
-> ProposalProcedure era
-> EpochNo
-> EpochNo
-> GovActionState era
GovActionState
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall era.
Coin
-> RewardAccount
-> GovAction era
-> Anchor
-> ProposalProcedure era
ProposalProcedure forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure GovAction era
ga forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
instance (Era era, Arbitrary (PParamsUpdate era)) => Arbitrary (GovActionState era) where
arbitrary :: Gen (GovActionState era)
arbitrary = forall era. GovAction era -> Gen (GovActionState era)
genGovActionState forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall a. Arbitrary a => Gen a
arbitrary
shrink :: GovActionState era -> [GovActionState era]
shrink = forall a.
(Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) =>
a -> [a]
genericShrink
data ShuffledGovActionStates era
= ShuffledGovActionStates [GovActionState era] [GovActionState era]
deriving (Int -> ShuffledGovActionStates era -> ShowS
forall era.
EraPParams era =>
Int -> ShuffledGovActionStates era -> ShowS
forall era.
EraPParams era =>
[ShuffledGovActionStates era] -> ShowS
forall era. EraPParams era => ShuffledGovActionStates era -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ShuffledGovActionStates era] -> ShowS
$cshowList :: forall era.
EraPParams era =>
[ShuffledGovActionStates era] -> ShowS
show :: ShuffledGovActionStates era -> String
$cshow :: forall era. EraPParams era => ShuffledGovActionStates era -> String
showsPrec :: Int -> ShuffledGovActionStates era -> ShowS
$cshowsPrec :: forall era.
EraPParams era =>
Int -> ShuffledGovActionStates era -> ShowS
Show)
instance
(Era era, Arbitrary (PParamsUpdate era)) =>
Arbitrary (ShuffledGovActionStates era)
where
arbitrary :: Gen (ShuffledGovActionStates era)
arbitrary = do
[GovActionState era]
gass <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (forall era. GovAction era -> Gen (GovActionState era)
genGovActionState forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<) forall era.
(Era era, Arbitrary (PParamsUpdate era)) =>
[Gen (GovAction era)]
govActionGenerators
[GovActionState era]
shuffledGass <- forall a. [a] -> Gen [a]
shuffle [GovActionState era]
gass
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall era.
[GovActionState era]
-> [GovActionState era] -> ShuffledGovActionStates era
ShuffledGovActionStates [GovActionState era]
gass [GovActionState era]
shuffledGass
genParameterChange :: Arbitrary (PParamsUpdate era) => Gen (GovAction era)
genParameterChange :: forall era. Arbitrary (PParamsUpdate era) => Gen (GovAction era)
genParameterChange = forall era.
StrictMaybe (GovPurposeId 'PParamUpdatePurpose era)
-> PParamsUpdate era -> StrictMaybe ScriptHash -> GovAction era
ParameterChange forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
genHardForkInitiation :: Gen (GovAction era)
genHardForkInitiation :: forall era. Gen (GovAction era)
genHardForkInitiation = forall era.
StrictMaybe (GovPurposeId 'HardForkPurpose era)
-> ProtVer -> GovAction era
HardForkInitiation forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
genTreasuryWithdrawals :: Gen (GovAction era)
genTreasuryWithdrawals :: forall era. Gen (GovAction era)
genTreasuryWithdrawals = forall era.
Map RewardAccount Coin -> StrictMaybe ScriptHash -> GovAction era
TreasuryWithdrawals forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
genNoConfidence :: Gen (GovAction era)
genNoConfidence :: forall era. Gen (GovAction era)
genNoConfidence = forall era.
StrictMaybe (GovPurposeId 'CommitteePurpose era) -> GovAction era
NoConfidence forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
genUpdateCommittee :: Gen (GovAction era)
genUpdateCommittee :: forall era. Gen (GovAction era)
genUpdateCommittee =
forall era.
StrictMaybe (GovPurposeId 'CommitteePurpose era)
-> Set (Credential 'ColdCommitteeRole)
-> Map (Credential 'ColdCommitteeRole) EpochNo
-> UnitInterval
-> GovAction era
UpdateCommittee
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
genNewConstitution :: Era era => Gen (GovAction era)
genNewConstitution :: forall era. Era era => Gen (GovAction era)
genNewConstitution = forall era.
StrictMaybe (GovPurposeId 'ConstitutionPurpose era)
-> Constitution era -> GovAction era
NewConstitution forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
govActionGenerators ::
( Era era
, Arbitrary (PParamsUpdate era)
) =>
[Gen (GovAction era)]
govActionGenerators :: forall era.
(Era era, Arbitrary (PParamsUpdate era)) =>
[Gen (GovAction era)]
govActionGenerators =
[ forall era. Arbitrary (PParamsUpdate era) => Gen (GovAction era)
genParameterChange
, forall era. Gen (GovAction era)
genHardForkInitiation
, forall era. Gen (GovAction era)
genTreasuryWithdrawals
, forall era. Gen (GovAction era)
genNoConfidence
, forall era. Gen (GovAction era)
genUpdateCommittee
, forall era. Era era => Gen (GovAction era)
genNewConstitution
, forall (f :: * -> *) a. Applicative f => a -> f a
pure forall era. GovAction era
InfoAction
]
instance (Era era, Arbitrary (PParamsUpdate era)) => Arbitrary (GovAction era) where
arbitrary :: Gen (GovAction era)
arbitrary = forall a. HasCallStack => [Gen a] -> Gen a
oneof forall era.
(Era era, Arbitrary (PParamsUpdate era)) =>
[Gen (GovAction era)]
govActionGenerators
instance Era era => Arbitrary (Committee era) where
arbitrary :: Gen (Committee era)
arbitrary = forall era.
Map (Credential 'ColdCommitteeRole) EpochNo
-> UnitInterval -> Committee era
Committee forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
instance Arbitrary GovActionId where
arbitrary :: Gen GovActionId
arbitrary = TxId -> GovActionIx -> GovActionId
GovActionId forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
deriving instance Arbitrary GovActionIx
deriving instance Arbitrary (GovPurposeId p era)
instance Arbitrary Voter where
arbitrary :: Gen Voter
arbitrary =
forall a. HasCallStack => [Gen a] -> Gen a
oneof
[ Credential 'HotCommitteeRole -> Voter
CommitteeVoter forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
, Credential 'DRepRole -> Voter
DRepVoter forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
, KeyHash 'StakePool -> Voter
StakePoolVoter forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
]
shrink :: Voter -> [Voter]
shrink = forall a.
(Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) =>
a -> [a]
genericShrink
instance Arbitrary Vote where
arbitrary :: Gen Vote
arbitrary = forall a. (Bounded a, Enum a) => Gen a
arbitraryBoundedEnum
shrink :: Vote -> [Vote]
shrink = forall a. (Bounded a, Enum a, Eq a) => a -> [a]
shrinkBoundedEnum
instance
( ConwayEraTxBody era
, Arbitrary (Sized (TxOut era))
, Arbitrary (TxOut era)
, Arbitrary (Value era)
, Arbitrary (Script era)
, Arbitrary (PParamsUpdate era)
) =>
Arbitrary (ConwayTxBody era)
where
arbitrary :: Gen (ConwayTxBody era)
arbitrary =
forall era.
ConwayEraTxBody era =>
Set TxIn
-> Set TxIn
-> Set TxIn
-> StrictSeq (Sized (TxOut era))
-> StrictMaybe (Sized (TxOut era))
-> StrictMaybe Coin
-> OSet (ConwayTxCert era)
-> Withdrawals
-> Coin
-> ValidityInterval
-> Set (KeyHash 'Witness)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> VotingProcedures era
-> OSet (ProposalProcedure era)
-> StrictMaybe Coin
-> Coin
-> ConwayTxBody era
ConwayTxBody
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. (Int -> Int) -> Gen a -> Gen a
scale (forall a. Integral a => a -> a -> a
`div` Int
15) forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. (Int -> Int) -> Gen a -> Gen a
scale (forall a. Integral a => a -> a -> a
`div` Int
15) forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
instance
( Era era
, Arbitrary (TxCert era)
, Arbitrary (PParamsHKD StrictMaybe era)
) =>
Arbitrary (ConwayPlutusPurpose AsItem era)
where
arbitrary :: Gen (ConwayPlutusPurpose AsItem era)
arbitrary =
forall a. HasCallStack => [Gen a] -> Gen a
oneof
[ forall (f :: * -> * -> *) era.
f Word32 TxIn -> ConwayPlutusPurpose f era
ConwaySpending forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
, forall (f :: * -> * -> *) era.
f Word32 PolicyID -> ConwayPlutusPurpose f era
ConwayMinting forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
, forall (f :: * -> * -> *) era.
f Word32 (TxCert era) -> ConwayPlutusPurpose f era
ConwayCertifying forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
, forall (f :: * -> * -> *) era.
f Word32 RewardAccount -> ConwayPlutusPurpose f era
ConwayRewarding forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
, forall (f :: * -> * -> *) era.
f Word32 Voter -> ConwayPlutusPurpose f era
ConwayVoting forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
, forall (f :: * -> * -> *) era.
f Word32 (ProposalProcedure era) -> ConwayPlutusPurpose f era
ConwayProposing forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
]
instance
( Era era
, Arbitrary (TxCert era)
, Arbitrary (PParamsHKD StrictMaybe era)
) =>
Arbitrary (ConwayPlutusPurpose AsIxItem era)
where
arbitrary :: Gen (ConwayPlutusPurpose AsIxItem era)
arbitrary =
forall a. HasCallStack => [Gen a] -> Gen a
oneof
[ forall (f :: * -> * -> *) era.
f Word32 TxIn -> ConwayPlutusPurpose f era
ConwaySpending forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
, forall (f :: * -> * -> *) era.
f Word32 PolicyID -> ConwayPlutusPurpose f era
ConwayMinting forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
, forall (f :: * -> * -> *) era.
f Word32 (TxCert era) -> ConwayPlutusPurpose f era
ConwayCertifying forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
, forall (f :: * -> * -> *) era.
f Word32 RewardAccount -> ConwayPlutusPurpose f era
ConwayRewarding forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
, forall (f :: * -> * -> *) era.
f Word32 Voter -> ConwayPlutusPurpose f era
ConwayVoting forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
, forall (f :: * -> * -> *) era.
f Word32 (ProposalProcedure era) -> ConwayPlutusPurpose f era
ConwayProposing forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
]
instance
Era era =>
Arbitrary (ConwayPlutusPurpose AsIx era)
where
arbitrary :: Gen (ConwayPlutusPurpose AsIx era)
arbitrary = forall a. Arbitrary a => Gen a
arbitrary forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall era. Word32 -> Gen (ConwayPlutusPurpose AsIx era)
genConwayPlutusPurposePointer
genConwayPlutusPurposePointer :: Word32 -> Gen (ConwayPlutusPurpose AsIx era)
genConwayPlutusPurposePointer :: forall era. Word32 -> Gen (ConwayPlutusPurpose AsIx era)
genConwayPlutusPurposePointer Word32
i =
forall a. HasCallStack => [a] -> Gen a
elements
[ forall (f :: * -> * -> *) era.
f Word32 TxIn -> ConwayPlutusPurpose f era
ConwaySpending (forall ix it. ix -> AsIx ix it
AsIx Word32
i)
, forall (f :: * -> * -> *) era.
f Word32 PolicyID -> ConwayPlutusPurpose f era
ConwayMinting (forall ix it. ix -> AsIx ix it
AsIx Word32
i)
, forall (f :: * -> * -> *) era.
f Word32 (TxCert era) -> ConwayPlutusPurpose f era
ConwayCertifying (forall ix it. ix -> AsIx ix it
AsIx Word32
i)
, forall (f :: * -> * -> *) era.
f Word32 RewardAccount -> ConwayPlutusPurpose f era
ConwayRewarding (forall ix it. ix -> AsIx ix it
AsIx Word32
i)
, forall (f :: * -> * -> *) era.
f Word32 Voter -> ConwayPlutusPurpose f era
ConwayVoting (forall ix it. ix -> AsIx ix it
AsIx Word32
i)
, forall (f :: * -> * -> *) era.
f Word32 (ProposalProcedure era) -> ConwayPlutusPurpose f era
ConwayProposing (forall ix it. ix -> AsIx ix it
AsIx Word32
i)
]
instance (Era era, Arbitrary (PParamsHKD Identity era)) => Arbitrary (GovEnv era) where
arbitrary :: Gen (GovEnv era)
arbitrary =
forall era.
TxId
-> EpochNo
-> PParams era
-> StrictMaybe ScriptHash
-> CertState era
-> GovEnv era
GovEnv
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
instance Era era => Arbitrary (VotingProcedure era) where
arbitrary :: Gen (VotingProcedure era)
arbitrary = forall era. Vote -> StrictMaybe Anchor -> VotingProcedure era
VotingProcedure forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
instance Era era => Arbitrary (VotingProcedures era) where
arbitrary :: Gen (VotingProcedures era)
arbitrary = forall era.
Map Voter (Map GovActionId (VotingProcedure era))
-> VotingProcedures era
VotingProcedures forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Arbitrary1 f => Gen a -> Gen (f a)
liftArbitrary (forall k v. Ord k => Gen k -> Gen v -> Gen (Map k v)
genNonEmptyMap forall a. Arbitrary a => Gen a
arbitrary forall a. Arbitrary a => Gen a
arbitrary)
instance (Era era, Arbitrary (PParamsUpdate era)) => Arbitrary (ProposalProcedure era) where
arbitrary :: Gen (ProposalProcedure era)
arbitrary =
forall era.
Coin
-> RewardAccount
-> GovAction era
-> Anchor
-> ProposalProcedure era
ProposalProcedure
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
shrink :: ProposalProcedure era -> [ProposalProcedure era]
shrink (ProposalProcedure Coin
dep RewardAccount
ret GovAction era
gov Anchor
anch) =
[ forall era.
Coin
-> RewardAccount
-> GovAction era
-> Anchor
-> ProposalProcedure era
ProposalProcedure Coin
dep' RewardAccount
ret' GovAction era
gov' Anchor
anch'
| (Coin
dep', RewardAccount
ret', GovAction era
gov', Anchor
anch') <- forall a. Arbitrary a => a -> [a]
shrink (Coin
dep, RewardAccount
ret, GovAction era
gov, Anchor
anch)
]
instance
(EraPParams era, Arbitrary (PParamsUpdate era), Arbitrary (TxCert era)) =>
Arbitrary (GovSignal era)
where
arbitrary :: Gen (GovSignal era)
arbitrary = forall era.
VotingProcedures era
-> OSet (ProposalProcedure era)
-> StrictSeq (TxCert era)
-> GovSignal era
GovSignal forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
shrink :: GovSignal era -> [GovSignal era]
shrink (GovSignal VotingProcedures era
vp OSet (ProposalProcedure era)
pp StrictSeq (TxCert era)
cs) = [forall era.
VotingProcedures era
-> OSet (ProposalProcedure era)
-> StrictSeq (TxCert era)
-> GovSignal era
GovSignal VotingProcedures era
vp' OSet (ProposalProcedure era)
pp' StrictSeq (TxCert era)
cs' | (VotingProcedures era
vp', OSet (ProposalProcedure era)
pp', StrictSeq (TxCert era)
cs') <- forall a. Arbitrary a => a -> [a]
shrink (VotingProcedures era
vp, OSet (ProposalProcedure era)
pp, StrictSeq (TxCert era)
cs)]
instance
( Era era
, Arbitrary (PParamsHKD StrictMaybe era)
) =>
Arbitrary (ConwayGovPredFailure era)
where
arbitrary :: Gen (ConwayGovPredFailure era)
arbitrary = forall a. (GArbitrary UnsizedOpts a, GUniformWeight a) => Gen a
genericArbitraryU
instance
( Era era
, Arbitrary (CollectError era)
) =>
Arbitrary (ConwayUtxosPredFailure era)
where
arbitrary :: Gen (ConwayUtxosPredFailure era)
arbitrary = forall a. (GArbitrary UnsizedOpts a, GUniformWeight a) => Gen a
genericArbitraryU
instance
( Era era
, Arbitrary (PredicateFailure (EraRule "UTXOW" era))
, Arbitrary (PredicateFailure (EraRule "CERTS" era))
, Arbitrary (PredicateFailure (EraRule "GOV" era))
) =>
Arbitrary (ConwayLedgerPredFailure era)
where
arbitrary :: Gen (ConwayLedgerPredFailure era)
arbitrary = forall a. (GArbitrary UnsizedOpts a, GUniformWeight a) => Gen a
genericArbitraryU
instance
( Era era
, Arbitrary (Event (EraRule "POOLREAP" era))
, Arbitrary (Event (EraRule "SNAP" era))
) =>
Arbitrary (ConwayEpochEvent era)
where
arbitrary :: Gen (ConwayEpochEvent era)
arbitrary =
forall a. HasCallStack => [Gen a] -> Gen a
oneof
[ forall era. Event (EraRule "POOLREAP" era) -> ConwayEpochEvent era
PoolReapEvent forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
, forall era. Event (EraRule "SNAP" era) -> ConwayEpochEvent era
SnapEvent forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
]
instance
( Era era
, Arbitrary (Event (EraRule "RUPD" era))
) =>
Arbitrary (ConwayNewEpochEvent era)
where
arbitrary :: Gen (ConwayNewEpochEvent era)
arbitrary =
forall a. HasCallStack => [Gen a] -> Gen a
oneof
[ forall era. Event (EraRule "RUPD" era) -> ConwayNewEpochEvent era
DeltaRewardEvent forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
, forall era.
EpochNo
-> Map (Credential 'Staking) (Set Reward)
-> Set (Credential 'Staking)
-> ConwayNewEpochEvent era
RestrainedRewards forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
]
instance
( Era era
, Arbitrary (PredicateFailure (EraRule "CERT" era))
) =>
Arbitrary (ConwayCertsPredFailure era)
where
arbitrary :: Gen (ConwayCertsPredFailure era)
arbitrary = forall a. (GArbitrary UnsizedOpts a, GUniformWeight a) => Gen a
genericArbitraryU
instance
( Era era
, Arbitrary (PredicateFailure (EraRule "DELEG" era))
, Arbitrary (PredicateFailure (EraRule "POOL" era))
, Arbitrary (PredicateFailure (EraRule "GOVCERT" era))
) =>
Arbitrary (ConwayCertPredFailure era)
where
arbitrary :: Gen (ConwayCertPredFailure era)
arbitrary = forall a. (GArbitrary UnsizedOpts a, GUniformWeight a) => Gen a
genericArbitraryU
instance
Era era =>
Arbitrary (ConwayDelegPredFailure era)
where
arbitrary :: Gen (ConwayDelegPredFailure era)
arbitrary = forall a. (GArbitrary UnsizedOpts a, GUniformWeight a) => Gen a
genericArbitraryU
instance Era era => Arbitrary (ConwayGovCertPredFailure era) where
arbitrary :: Gen (ConwayGovCertPredFailure era)
arbitrary = forall a. (GArbitrary UnsizedOpts a, GUniformWeight a) => Gen a
genericArbitraryU
instance Arbitrary (HKD f a) => Arbitrary (THKD t f a) where
arbitrary :: Gen (THKD t f a)
arbitrary = forall (t :: PPGroups) (f :: * -> *) a. HKD f a -> THKD t f a
THKD forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
instance Era era => Arbitrary (ConwayPParams Identity era) where
arbitrary :: Gen (ConwayPParams Identity era)
arbitrary =
forall (f :: * -> *) era.
THKD ('PPGroups 'EconomicGroup 'SecurityGroup) f Coin
-> THKD ('PPGroups 'EconomicGroup 'SecurityGroup) f Coin
-> THKD ('PPGroups 'NetworkGroup 'SecurityGroup) f Word32
-> THKD ('PPGroups 'NetworkGroup 'SecurityGroup) f Word32
-> THKD ('PPGroups 'NetworkGroup 'SecurityGroup) f Word16
-> THKD ('PPGroups 'EconomicGroup 'NoStakePoolGroup) f Coin
-> THKD ('PPGroups 'EconomicGroup 'NoStakePoolGroup) f Coin
-> THKD
('PPGroups 'TechnicalGroup 'NoStakePoolGroup) f EpochInterval
-> THKD ('PPGroups 'TechnicalGroup 'NoStakePoolGroup) f Word16
-> THKD
('PPGroups 'TechnicalGroup 'NoStakePoolGroup) f NonNegativeInterval
-> THKD ('PPGroups 'EconomicGroup 'NoStakePoolGroup) f UnitInterval
-> THKD ('PPGroups 'EconomicGroup 'NoStakePoolGroup) f UnitInterval
-> HKDNoUpdate f ProtVer
-> THKD ('PPGroups 'EconomicGroup 'NoStakePoolGroup) f Coin
-> THKD ('PPGroups 'EconomicGroup 'SecurityGroup) f CoinPerByte
-> THKD ('PPGroups 'TechnicalGroup 'NoStakePoolGroup) f CostModels
-> THKD ('PPGroups 'EconomicGroup 'NoStakePoolGroup) f Prices
-> THKD ('PPGroups 'NetworkGroup 'NoStakePoolGroup) f OrdExUnits
-> THKD ('PPGroups 'NetworkGroup 'SecurityGroup) f OrdExUnits
-> THKD ('PPGroups 'NetworkGroup 'SecurityGroup) f Word32
-> THKD ('PPGroups 'TechnicalGroup 'NoStakePoolGroup) f Word16
-> THKD ('PPGroups 'NetworkGroup 'NoStakePoolGroup) f Word16
-> THKD
('PPGroups 'GovGroup 'NoStakePoolGroup) f PoolVotingThresholds
-> THKD
('PPGroups 'GovGroup 'NoStakePoolGroup) f DRepVotingThresholds
-> THKD ('PPGroups 'GovGroup 'NoStakePoolGroup) f Word16
-> THKD ('PPGroups 'GovGroup 'NoStakePoolGroup) f EpochInterval
-> THKD ('PPGroups 'GovGroup 'NoStakePoolGroup) f EpochInterval
-> THKD ('PPGroups 'GovGroup 'SecurityGroup) f Coin
-> THKD ('PPGroups 'GovGroup 'NoStakePoolGroup) f Coin
-> THKD ('PPGroups 'GovGroup 'NoStakePoolGroup) f EpochInterval
-> THKD
('PPGroups 'EconomicGroup 'SecurityGroup) f NonNegativeInterval
-> ConwayPParams f era
ConwayPParams
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall (t :: PPGroups) (f :: * -> *) a. HKD f a -> THKD t f a
THKD forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
shrink :: ConwayPParams Identity era -> [ConwayPParams Identity era]
shrink = forall a.
(Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) =>
a -> [a]
genericShrink
instance Era era => Arbitrary (ConwayPParams StrictMaybe era) where
arbitrary :: Gen (ConwayPParams StrictMaybe era)
arbitrary =
forall (f :: * -> *) era.
THKD ('PPGroups 'EconomicGroup 'SecurityGroup) f Coin
-> THKD ('PPGroups 'EconomicGroup 'SecurityGroup) f Coin
-> THKD ('PPGroups 'NetworkGroup 'SecurityGroup) f Word32
-> THKD ('PPGroups 'NetworkGroup 'SecurityGroup) f Word32
-> THKD ('PPGroups 'NetworkGroup 'SecurityGroup) f Word16
-> THKD ('PPGroups 'EconomicGroup 'NoStakePoolGroup) f Coin
-> THKD ('PPGroups 'EconomicGroup 'NoStakePoolGroup) f Coin
-> THKD
('PPGroups 'TechnicalGroup 'NoStakePoolGroup) f EpochInterval
-> THKD ('PPGroups 'TechnicalGroup 'NoStakePoolGroup) f Word16
-> THKD
('PPGroups 'TechnicalGroup 'NoStakePoolGroup) f NonNegativeInterval
-> THKD ('PPGroups 'EconomicGroup 'NoStakePoolGroup) f UnitInterval
-> THKD ('PPGroups 'EconomicGroup 'NoStakePoolGroup) f UnitInterval
-> HKDNoUpdate f ProtVer
-> THKD ('PPGroups 'EconomicGroup 'NoStakePoolGroup) f Coin
-> THKD ('PPGroups 'EconomicGroup 'SecurityGroup) f CoinPerByte
-> THKD ('PPGroups 'TechnicalGroup 'NoStakePoolGroup) f CostModels
-> THKD ('PPGroups 'EconomicGroup 'NoStakePoolGroup) f Prices
-> THKD ('PPGroups 'NetworkGroup 'NoStakePoolGroup) f OrdExUnits
-> THKD ('PPGroups 'NetworkGroup 'SecurityGroup) f OrdExUnits
-> THKD ('PPGroups 'NetworkGroup 'SecurityGroup) f Word32
-> THKD ('PPGroups 'TechnicalGroup 'NoStakePoolGroup) f Word16
-> THKD ('PPGroups 'NetworkGroup 'NoStakePoolGroup) f Word16
-> THKD
('PPGroups 'GovGroup 'NoStakePoolGroup) f PoolVotingThresholds
-> THKD
('PPGroups 'GovGroup 'NoStakePoolGroup) f DRepVotingThresholds
-> THKD ('PPGroups 'GovGroup 'NoStakePoolGroup) f Word16
-> THKD ('PPGroups 'GovGroup 'NoStakePoolGroup) f EpochInterval
-> THKD ('PPGroups 'GovGroup 'NoStakePoolGroup) f EpochInterval
-> THKD ('PPGroups 'GovGroup 'SecurityGroup) f Coin
-> THKD ('PPGroups 'GovGroup 'NoStakePoolGroup) f Coin
-> THKD ('PPGroups 'GovGroup 'NoStakePoolGroup) f EpochInterval
-> THKD
('PPGroups 'EconomicGroup 'SecurityGroup) f NonNegativeInterval
-> ConwayPParams f era
ConwayPParams
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. NoUpdate a
NoUpdate
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall (t :: PPGroups) (f :: * -> *) a. HKD f a -> THKD t f a
THKD forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. HasCallStack => [Gen a] -> Gen a
oneof [forall a. a -> StrictMaybe a
SJust forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen CostModels
genValidAndUnknownCostModels, forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. StrictMaybe a
SNothing])
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
shrink :: ConwayPParams StrictMaybe era -> [ConwayPParams StrictMaybe era]
shrink = forall a.
(Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) =>
a -> [a]
genericShrink
instance Arbitrary PoolVotingThresholds where
arbitrary :: Gen PoolVotingThresholds
arbitrary =
UnitInterval
-> UnitInterval
-> UnitInterval
-> UnitInterval
-> UnitInterval
-> PoolVotingThresholds
PoolVotingThresholds
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
shrink :: PoolVotingThresholds -> [PoolVotingThresholds]
shrink = forall a.
(Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) =>
a -> [a]
genericShrink
instance Arbitrary DRepVotingThresholds where
arbitrary :: Gen DRepVotingThresholds
arbitrary =
UnitInterval
-> UnitInterval
-> UnitInterval
-> UnitInterval
-> UnitInterval
-> UnitInterval
-> UnitInterval
-> UnitInterval
-> UnitInterval
-> UnitInterval
-> DRepVotingThresholds
DRepVotingThresholds
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
shrink :: DRepVotingThresholds -> [DRepVotingThresholds]
shrink = forall a.
(Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) =>
a -> [a]
genericShrink
instance Era era => Arbitrary (Constitution era) where
arbitrary :: Gen (Constitution era)
arbitrary = forall era. Anchor -> StrictMaybe ScriptHash -> Constitution era
Constitution forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary